module Stratosphere.EC2.NetworkInsightsAccessScope.AccessScopePathRequestProperty (
module Exports, AccessScopePathRequestProperty(..),
mkAccessScopePathRequestProperty
) where
import qualified Data.Aeson as JSON
import qualified Stratosphere.Prelude as Prelude
import Stratosphere.Property
import {-# SOURCE #-} Stratosphere.EC2.NetworkInsightsAccessScope.PathStatementRequestProperty as Exports
import {-# SOURCE #-} Stratosphere.EC2.NetworkInsightsAccessScope.ThroughResourcesStatementRequestProperty as Exports
import Stratosphere.ResourceProperties
data AccessScopePathRequestProperty
=
AccessScopePathRequestProperty {AccessScopePathRequestProperty -> ()
haddock_workaround_ :: (),
AccessScopePathRequestProperty
-> Maybe PathStatementRequestProperty
destination :: (Prelude.Maybe PathStatementRequestProperty),
AccessScopePathRequestProperty
-> Maybe PathStatementRequestProperty
source :: (Prelude.Maybe PathStatementRequestProperty),
AccessScopePathRequestProperty
-> Maybe [ThroughResourcesStatementRequestProperty]
throughResources :: (Prelude.Maybe [ThroughResourcesStatementRequestProperty])}
deriving stock (AccessScopePathRequestProperty
-> AccessScopePathRequestProperty -> Bool
(AccessScopePathRequestProperty
-> AccessScopePathRequestProperty -> Bool)
-> (AccessScopePathRequestProperty
-> AccessScopePathRequestProperty -> Bool)
-> Eq AccessScopePathRequestProperty
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: AccessScopePathRequestProperty
-> AccessScopePathRequestProperty -> Bool
== :: AccessScopePathRequestProperty
-> AccessScopePathRequestProperty -> Bool
$c/= :: AccessScopePathRequestProperty
-> AccessScopePathRequestProperty -> Bool
/= :: AccessScopePathRequestProperty
-> AccessScopePathRequestProperty -> Bool
Prelude.Eq, Int -> AccessScopePathRequestProperty -> ShowS
[AccessScopePathRequestProperty] -> ShowS
AccessScopePathRequestProperty -> String
(Int -> AccessScopePathRequestProperty -> ShowS)
-> (AccessScopePathRequestProperty -> String)
-> ([AccessScopePathRequestProperty] -> ShowS)
-> Show AccessScopePathRequestProperty
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> AccessScopePathRequestProperty -> ShowS
showsPrec :: Int -> AccessScopePathRequestProperty -> ShowS
$cshow :: AccessScopePathRequestProperty -> String
show :: AccessScopePathRequestProperty -> String
$cshowList :: [AccessScopePathRequestProperty] -> ShowS
showList :: [AccessScopePathRequestProperty] -> ShowS
Prelude.Show)
mkAccessScopePathRequestProperty :: AccessScopePathRequestProperty
mkAccessScopePathRequestProperty :: AccessScopePathRequestProperty
mkAccessScopePathRequestProperty
= AccessScopePathRequestProperty
{haddock_workaround_ :: ()
haddock_workaround_ = (), destination :: Maybe PathStatementRequestProperty
destination = Maybe PathStatementRequestProperty
forall a. Maybe a
Prelude.Nothing,
source :: Maybe PathStatementRequestProperty
source = Maybe PathStatementRequestProperty
forall a. Maybe a
Prelude.Nothing, throughResources :: Maybe [ThroughResourcesStatementRequestProperty]
throughResources = Maybe [ThroughResourcesStatementRequestProperty]
forall a. Maybe a
Prelude.Nothing}
instance ToResourceProperties AccessScopePathRequestProperty where
toResourceProperties :: AccessScopePathRequestProperty -> ResourceProperties
toResourceProperties AccessScopePathRequestProperty {Maybe [ThroughResourcesStatementRequestProperty]
Maybe PathStatementRequestProperty
()
haddock_workaround_ :: AccessScopePathRequestProperty -> ()
destination :: AccessScopePathRequestProperty
-> Maybe PathStatementRequestProperty
source :: AccessScopePathRequestProperty
-> Maybe PathStatementRequestProperty
throughResources :: AccessScopePathRequestProperty
-> Maybe [ThroughResourcesStatementRequestProperty]
haddock_workaround_ :: ()
destination :: Maybe PathStatementRequestProperty
source :: Maybe PathStatementRequestProperty
throughResources :: Maybe [ThroughResourcesStatementRequestProperty]
..}
= ResourceProperties
{awsType :: Text
awsType = Text
"AWS::EC2::NetworkInsightsAccessScope.AccessScopePathRequest",
supportsTags :: Bool
supportsTags = Bool
Prelude.False,
properties :: Object
properties = [Item Object] -> Object
forall l. IsList l => [Item l] -> l
Prelude.fromList
([Maybe (Key, Value)] -> [(Key, Value)]
forall a. [Maybe a] -> [a]
Prelude.catMaybes
[Key -> PathStatementRequestProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"Destination" (PathStatementRequestProperty -> (Key, Value))
-> Maybe PathStatementRequestProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe PathStatementRequestProperty
destination,
Key -> PathStatementRequestProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"Source" (PathStatementRequestProperty -> (Key, Value))
-> Maybe PathStatementRequestProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe PathStatementRequestProperty
source,
Key -> [ThroughResourcesStatementRequestProperty] -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"ThroughResources" ([ThroughResourcesStatementRequestProperty] -> (Key, Value))
-> Maybe [ThroughResourcesStatementRequestProperty]
-> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [ThroughResourcesStatementRequestProperty]
throughResources])}
instance JSON.ToJSON AccessScopePathRequestProperty where
toJSON :: AccessScopePathRequestProperty -> Value
toJSON AccessScopePathRequestProperty {Maybe [ThroughResourcesStatementRequestProperty]
Maybe PathStatementRequestProperty
()
haddock_workaround_ :: AccessScopePathRequestProperty -> ()
destination :: AccessScopePathRequestProperty
-> Maybe PathStatementRequestProperty
source :: AccessScopePathRequestProperty
-> Maybe PathStatementRequestProperty
throughResources :: AccessScopePathRequestProperty
-> Maybe [ThroughResourcesStatementRequestProperty]
haddock_workaround_ :: ()
destination :: Maybe PathStatementRequestProperty
source :: Maybe PathStatementRequestProperty
throughResources :: Maybe [ThroughResourcesStatementRequestProperty]
..}
= [(Key, Value)] -> Value
JSON.object
([Item [(Key, Value)]] -> [(Key, Value)]
forall l. IsList l => [Item l] -> l
Prelude.fromList
([Maybe (Key, Value)] -> [(Key, Value)]
forall a. [Maybe a] -> [a]
Prelude.catMaybes
[Key -> PathStatementRequestProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"Destination" (PathStatementRequestProperty -> (Key, Value))
-> Maybe PathStatementRequestProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe PathStatementRequestProperty
destination,
Key -> PathStatementRequestProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"Source" (PathStatementRequestProperty -> (Key, Value))
-> Maybe PathStatementRequestProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe PathStatementRequestProperty
source,
Key -> [ThroughResourcesStatementRequestProperty] -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"ThroughResources" ([ThroughResourcesStatementRequestProperty] -> (Key, Value))
-> Maybe [ThroughResourcesStatementRequestProperty]
-> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [ThroughResourcesStatementRequestProperty]
throughResources]))
instance Property "Destination" AccessScopePathRequestProperty where
type PropertyType "Destination" AccessScopePathRequestProperty = PathStatementRequestProperty
set :: PropertyType "Destination" AccessScopePathRequestProperty
-> AccessScopePathRequestProperty -> AccessScopePathRequestProperty
set PropertyType "Destination" AccessScopePathRequestProperty
newValue AccessScopePathRequestProperty {Maybe [ThroughResourcesStatementRequestProperty]
Maybe PathStatementRequestProperty
()
haddock_workaround_ :: AccessScopePathRequestProperty -> ()
destination :: AccessScopePathRequestProperty
-> Maybe PathStatementRequestProperty
source :: AccessScopePathRequestProperty
-> Maybe PathStatementRequestProperty
throughResources :: AccessScopePathRequestProperty
-> Maybe [ThroughResourcesStatementRequestProperty]
haddock_workaround_ :: ()
destination :: Maybe PathStatementRequestProperty
source :: Maybe PathStatementRequestProperty
throughResources :: Maybe [ThroughResourcesStatementRequestProperty]
..}
= AccessScopePathRequestProperty
{destination :: Maybe PathStatementRequestProperty
destination = PathStatementRequestProperty -> Maybe PathStatementRequestProperty
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "Destination" AccessScopePathRequestProperty
PathStatementRequestProperty
newValue, Maybe [ThroughResourcesStatementRequestProperty]
Maybe PathStatementRequestProperty
()
haddock_workaround_ :: ()
source :: Maybe PathStatementRequestProperty
throughResources :: Maybe [ThroughResourcesStatementRequestProperty]
haddock_workaround_ :: ()
source :: Maybe PathStatementRequestProperty
throughResources :: Maybe [ThroughResourcesStatementRequestProperty]
..}
instance Property "Source" AccessScopePathRequestProperty where
type PropertyType "Source" AccessScopePathRequestProperty = PathStatementRequestProperty
set :: PropertyType "Source" AccessScopePathRequestProperty
-> AccessScopePathRequestProperty -> AccessScopePathRequestProperty
set PropertyType "Source" AccessScopePathRequestProperty
newValue AccessScopePathRequestProperty {Maybe [ThroughResourcesStatementRequestProperty]
Maybe PathStatementRequestProperty
()
haddock_workaround_ :: AccessScopePathRequestProperty -> ()
destination :: AccessScopePathRequestProperty
-> Maybe PathStatementRequestProperty
source :: AccessScopePathRequestProperty
-> Maybe PathStatementRequestProperty
throughResources :: AccessScopePathRequestProperty
-> Maybe [ThroughResourcesStatementRequestProperty]
haddock_workaround_ :: ()
destination :: Maybe PathStatementRequestProperty
source :: Maybe PathStatementRequestProperty
throughResources :: Maybe [ThroughResourcesStatementRequestProperty]
..}
= AccessScopePathRequestProperty
{source :: Maybe PathStatementRequestProperty
source = PathStatementRequestProperty -> Maybe PathStatementRequestProperty
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "Source" AccessScopePathRequestProperty
PathStatementRequestProperty
newValue, Maybe [ThroughResourcesStatementRequestProperty]
Maybe PathStatementRequestProperty
()
haddock_workaround_ :: ()
destination :: Maybe PathStatementRequestProperty
throughResources :: Maybe [ThroughResourcesStatementRequestProperty]
haddock_workaround_ :: ()
destination :: Maybe PathStatementRequestProperty
throughResources :: Maybe [ThroughResourcesStatementRequestProperty]
..}
instance Property "ThroughResources" AccessScopePathRequestProperty where
type PropertyType "ThroughResources" AccessScopePathRequestProperty = [ThroughResourcesStatementRequestProperty]
set :: PropertyType "ThroughResources" AccessScopePathRequestProperty
-> AccessScopePathRequestProperty -> AccessScopePathRequestProperty
set PropertyType "ThroughResources" AccessScopePathRequestProperty
newValue AccessScopePathRequestProperty {Maybe [ThroughResourcesStatementRequestProperty]
Maybe PathStatementRequestProperty
()
haddock_workaround_ :: AccessScopePathRequestProperty -> ()
destination :: AccessScopePathRequestProperty
-> Maybe PathStatementRequestProperty
source :: AccessScopePathRequestProperty
-> Maybe PathStatementRequestProperty
throughResources :: AccessScopePathRequestProperty
-> Maybe [ThroughResourcesStatementRequestProperty]
haddock_workaround_ :: ()
destination :: Maybe PathStatementRequestProperty
source :: Maybe PathStatementRequestProperty
throughResources :: Maybe [ThroughResourcesStatementRequestProperty]
..}
= AccessScopePathRequestProperty
{throughResources :: Maybe [ThroughResourcesStatementRequestProperty]
throughResources = [ThroughResourcesStatementRequestProperty]
-> Maybe [ThroughResourcesStatementRequestProperty]
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure [ThroughResourcesStatementRequestProperty]
PropertyType "ThroughResources" AccessScopePathRequestProperty
newValue, Maybe PathStatementRequestProperty
()
haddock_workaround_ :: ()
destination :: Maybe PathStatementRequestProperty
source :: Maybe PathStatementRequestProperty
haddock_workaround_ :: ()
destination :: Maybe PathStatementRequestProperty
source :: Maybe PathStatementRequestProperty
..}