module Stratosphere.FMS.Policy.NetworkAclCommonPolicyProperty (
module Exports, NetworkAclCommonPolicyProperty(..),
mkNetworkAclCommonPolicyProperty
) where
import qualified Data.Aeson as JSON
import qualified Stratosphere.Prelude as Prelude
import Stratosphere.Property
import {-# SOURCE #-} Stratosphere.FMS.Policy.NetworkAclEntrySetProperty as Exports
import Stratosphere.ResourceProperties
data NetworkAclCommonPolicyProperty
=
NetworkAclCommonPolicyProperty {NetworkAclCommonPolicyProperty -> ()
haddock_workaround_ :: (),
NetworkAclCommonPolicyProperty -> NetworkAclEntrySetProperty
networkAclEntrySet :: NetworkAclEntrySetProperty}
deriving stock (NetworkAclCommonPolicyProperty
-> NetworkAclCommonPolicyProperty -> Bool
(NetworkAclCommonPolicyProperty
-> NetworkAclCommonPolicyProperty -> Bool)
-> (NetworkAclCommonPolicyProperty
-> NetworkAclCommonPolicyProperty -> Bool)
-> Eq NetworkAclCommonPolicyProperty
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: NetworkAclCommonPolicyProperty
-> NetworkAclCommonPolicyProperty -> Bool
== :: NetworkAclCommonPolicyProperty
-> NetworkAclCommonPolicyProperty -> Bool
$c/= :: NetworkAclCommonPolicyProperty
-> NetworkAclCommonPolicyProperty -> Bool
/= :: NetworkAclCommonPolicyProperty
-> NetworkAclCommonPolicyProperty -> Bool
Prelude.Eq, Int -> NetworkAclCommonPolicyProperty -> ShowS
[NetworkAclCommonPolicyProperty] -> ShowS
NetworkAclCommonPolicyProperty -> String
(Int -> NetworkAclCommonPolicyProperty -> ShowS)
-> (NetworkAclCommonPolicyProperty -> String)
-> ([NetworkAclCommonPolicyProperty] -> ShowS)
-> Show NetworkAclCommonPolicyProperty
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> NetworkAclCommonPolicyProperty -> ShowS
showsPrec :: Int -> NetworkAclCommonPolicyProperty -> ShowS
$cshow :: NetworkAclCommonPolicyProperty -> String
show :: NetworkAclCommonPolicyProperty -> String
$cshowList :: [NetworkAclCommonPolicyProperty] -> ShowS
showList :: [NetworkAclCommonPolicyProperty] -> ShowS
Prelude.Show)
mkNetworkAclCommonPolicyProperty ::
NetworkAclEntrySetProperty -> NetworkAclCommonPolicyProperty
mkNetworkAclCommonPolicyProperty :: NetworkAclEntrySetProperty -> NetworkAclCommonPolicyProperty
mkNetworkAclCommonPolicyProperty NetworkAclEntrySetProperty
networkAclEntrySet
= NetworkAclCommonPolicyProperty
{haddock_workaround_ :: ()
haddock_workaround_ = (), networkAclEntrySet :: NetworkAclEntrySetProperty
networkAclEntrySet = NetworkAclEntrySetProperty
networkAclEntrySet}
instance ToResourceProperties NetworkAclCommonPolicyProperty where
toResourceProperties :: NetworkAclCommonPolicyProperty -> ResourceProperties
toResourceProperties NetworkAclCommonPolicyProperty {()
NetworkAclEntrySetProperty
haddock_workaround_ :: NetworkAclCommonPolicyProperty -> ()
networkAclEntrySet :: NetworkAclCommonPolicyProperty -> NetworkAclEntrySetProperty
haddock_workaround_ :: ()
networkAclEntrySet :: NetworkAclEntrySetProperty
..}
= ResourceProperties
{awsType :: Text
awsType = Text
"AWS::FMS::Policy.NetworkAclCommonPolicy",
supportsTags :: Bool
supportsTags = Bool
Prelude.False,
properties :: Object
properties = [Key
"NetworkAclEntrySet" Key -> NetworkAclEntrySetProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
JSON..= NetworkAclEntrySetProperty
networkAclEntrySet]}
instance JSON.ToJSON NetworkAclCommonPolicyProperty where
toJSON :: NetworkAclCommonPolicyProperty -> Value
toJSON NetworkAclCommonPolicyProperty {()
NetworkAclEntrySetProperty
haddock_workaround_ :: NetworkAclCommonPolicyProperty -> ()
networkAclEntrySet :: NetworkAclCommonPolicyProperty -> NetworkAclEntrySetProperty
haddock_workaround_ :: ()
networkAclEntrySet :: NetworkAclEntrySetProperty
..}
= [(Key, Value)] -> Value
JSON.object [Key
"NetworkAclEntrySet" Key -> NetworkAclEntrySetProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
JSON..= NetworkAclEntrySetProperty
networkAclEntrySet]
instance Property "NetworkAclEntrySet" NetworkAclCommonPolicyProperty where
type PropertyType "NetworkAclEntrySet" NetworkAclCommonPolicyProperty = NetworkAclEntrySetProperty
set :: PropertyType "NetworkAclEntrySet" NetworkAclCommonPolicyProperty
-> NetworkAclCommonPolicyProperty -> NetworkAclCommonPolicyProperty
set PropertyType "NetworkAclEntrySet" NetworkAclCommonPolicyProperty
newValue NetworkAclCommonPolicyProperty {()
NetworkAclEntrySetProperty
haddock_workaround_ :: NetworkAclCommonPolicyProperty -> ()
networkAclEntrySet :: NetworkAclCommonPolicyProperty -> NetworkAclEntrySetProperty
haddock_workaround_ :: ()
networkAclEntrySet :: NetworkAclEntrySetProperty
..}
= NetworkAclCommonPolicyProperty
{networkAclEntrySet :: NetworkAclEntrySetProperty
networkAclEntrySet = PropertyType "NetworkAclEntrySet" NetworkAclCommonPolicyProperty
NetworkAclEntrySetProperty
newValue, ()
haddock_workaround_ :: ()
haddock_workaround_ :: ()
..}