module Stratosphere.NetworkFirewall.RuleGroup.RuleDefinitionProperty (
module Exports, RuleDefinitionProperty(..),
mkRuleDefinitionProperty
) where
import qualified Data.Aeson as JSON
import qualified Stratosphere.Prelude as Prelude
import Stratosphere.Property
import {-# SOURCE #-} Stratosphere.NetworkFirewall.RuleGroup.MatchAttributesProperty as Exports
import Stratosphere.ResourceProperties
import Stratosphere.Value
data RuleDefinitionProperty
=
RuleDefinitionProperty {RuleDefinitionProperty -> ()
haddock_workaround_ :: (),
RuleDefinitionProperty -> ValueList Text
actions :: (ValueList Prelude.Text),
RuleDefinitionProperty -> MatchAttributesProperty
matchAttributes :: MatchAttributesProperty}
deriving stock (RuleDefinitionProperty -> RuleDefinitionProperty -> Bool
(RuleDefinitionProperty -> RuleDefinitionProperty -> Bool)
-> (RuleDefinitionProperty -> RuleDefinitionProperty -> Bool)
-> Eq RuleDefinitionProperty
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: RuleDefinitionProperty -> RuleDefinitionProperty -> Bool
== :: RuleDefinitionProperty -> RuleDefinitionProperty -> Bool
$c/= :: RuleDefinitionProperty -> RuleDefinitionProperty -> Bool
/= :: RuleDefinitionProperty -> RuleDefinitionProperty -> Bool
Prelude.Eq, Int -> RuleDefinitionProperty -> ShowS
[RuleDefinitionProperty] -> ShowS
RuleDefinitionProperty -> String
(Int -> RuleDefinitionProperty -> ShowS)
-> (RuleDefinitionProperty -> String)
-> ([RuleDefinitionProperty] -> ShowS)
-> Show RuleDefinitionProperty
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> RuleDefinitionProperty -> ShowS
showsPrec :: Int -> RuleDefinitionProperty -> ShowS
$cshow :: RuleDefinitionProperty -> String
show :: RuleDefinitionProperty -> String
$cshowList :: [RuleDefinitionProperty] -> ShowS
showList :: [RuleDefinitionProperty] -> ShowS
Prelude.Show)
mkRuleDefinitionProperty ::
ValueList Prelude.Text
-> MatchAttributesProperty -> RuleDefinitionProperty
mkRuleDefinitionProperty :: ValueList Text -> MatchAttributesProperty -> RuleDefinitionProperty
mkRuleDefinitionProperty ValueList Text
actions MatchAttributesProperty
matchAttributes
= RuleDefinitionProperty
{haddock_workaround_ :: ()
haddock_workaround_ = (), actions :: ValueList Text
actions = ValueList Text
actions,
matchAttributes :: MatchAttributesProperty
matchAttributes = MatchAttributesProperty
matchAttributes}
instance ToResourceProperties RuleDefinitionProperty where
toResourceProperties :: RuleDefinitionProperty -> ResourceProperties
toResourceProperties RuleDefinitionProperty {()
ValueList Text
MatchAttributesProperty
haddock_workaround_ :: RuleDefinitionProperty -> ()
actions :: RuleDefinitionProperty -> ValueList Text
matchAttributes :: RuleDefinitionProperty -> MatchAttributesProperty
haddock_workaround_ :: ()
actions :: ValueList Text
matchAttributes :: MatchAttributesProperty
..}
= ResourceProperties
{awsType :: Text
awsType = Text
"AWS::NetworkFirewall::RuleGroup.RuleDefinition",
supportsTags :: Bool
supportsTags = Bool
Prelude.False,
properties :: Object
properties = [Key
"Actions" Key -> ValueList Text -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
JSON..= ValueList Text
actions,
Key
"MatchAttributes" Key -> MatchAttributesProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
JSON..= MatchAttributesProperty
matchAttributes]}
instance JSON.ToJSON RuleDefinitionProperty where
toJSON :: RuleDefinitionProperty -> Value
toJSON RuleDefinitionProperty {()
ValueList Text
MatchAttributesProperty
haddock_workaround_ :: RuleDefinitionProperty -> ()
actions :: RuleDefinitionProperty -> ValueList Text
matchAttributes :: RuleDefinitionProperty -> MatchAttributesProperty
haddock_workaround_ :: ()
actions :: ValueList Text
matchAttributes :: MatchAttributesProperty
..}
= [(Key, Value)] -> Value
JSON.object
[Key
"Actions" Key -> ValueList Text -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
JSON..= ValueList Text
actions,
Key
"MatchAttributes" Key -> MatchAttributesProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
JSON..= MatchAttributesProperty
matchAttributes]
instance Property "Actions" RuleDefinitionProperty where
type PropertyType "Actions" RuleDefinitionProperty = ValueList Prelude.Text
set :: PropertyType "Actions" RuleDefinitionProperty
-> RuleDefinitionProperty -> RuleDefinitionProperty
set PropertyType "Actions" RuleDefinitionProperty
newValue RuleDefinitionProperty {()
ValueList Text
MatchAttributesProperty
haddock_workaround_ :: RuleDefinitionProperty -> ()
actions :: RuleDefinitionProperty -> ValueList Text
matchAttributes :: RuleDefinitionProperty -> MatchAttributesProperty
haddock_workaround_ :: ()
actions :: ValueList Text
matchAttributes :: MatchAttributesProperty
..}
= RuleDefinitionProperty {actions :: ValueList Text
actions = PropertyType "Actions" RuleDefinitionProperty
ValueList Text
newValue, ()
MatchAttributesProperty
haddock_workaround_ :: ()
matchAttributes :: MatchAttributesProperty
haddock_workaround_ :: ()
matchAttributes :: MatchAttributesProperty
..}
instance Property "MatchAttributes" RuleDefinitionProperty where
type PropertyType "MatchAttributes" RuleDefinitionProperty = MatchAttributesProperty
set :: PropertyType "MatchAttributes" RuleDefinitionProperty
-> RuleDefinitionProperty -> RuleDefinitionProperty
set PropertyType "MatchAttributes" RuleDefinitionProperty
newValue RuleDefinitionProperty {()
ValueList Text
MatchAttributesProperty
haddock_workaround_ :: RuleDefinitionProperty -> ()
actions :: RuleDefinitionProperty -> ValueList Text
matchAttributes :: RuleDefinitionProperty -> MatchAttributesProperty
haddock_workaround_ :: ()
actions :: ValueList Text
matchAttributes :: MatchAttributesProperty
..}
= RuleDefinitionProperty {matchAttributes :: MatchAttributesProperty
matchAttributes = PropertyType "MatchAttributes" RuleDefinitionProperty
MatchAttributesProperty
newValue, ()
ValueList Text
haddock_workaround_ :: ()
actions :: ValueList Text
haddock_workaround_ :: ()
actions :: ValueList Text
..}