module Stratosphere.WAFRegional.WebACL.RuleProperty (
module Exports, RuleProperty(..), mkRuleProperty
) where
import qualified Data.Aeson as JSON
import qualified Stratosphere.Prelude as Prelude
import Stratosphere.Property
import {-# SOURCE #-} Stratosphere.WAFRegional.WebACL.ActionProperty as Exports
import Stratosphere.ResourceProperties
import Stratosphere.Value
data RuleProperty
=
RuleProperty {RuleProperty -> ()
haddock_workaround_ :: (),
RuleProperty -> ActionProperty
action :: ActionProperty,
RuleProperty -> Value Integer
priority :: (Value Prelude.Integer),
RuleProperty -> Value Text
ruleId :: (Value Prelude.Text)}
deriving stock (RuleProperty -> RuleProperty -> Bool
(RuleProperty -> RuleProperty -> Bool)
-> (RuleProperty -> RuleProperty -> Bool) -> Eq RuleProperty
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: RuleProperty -> RuleProperty -> Bool
== :: RuleProperty -> RuleProperty -> Bool
$c/= :: RuleProperty -> RuleProperty -> Bool
/= :: RuleProperty -> RuleProperty -> Bool
Prelude.Eq, Int -> RuleProperty -> ShowS
[RuleProperty] -> ShowS
RuleProperty -> String
(Int -> RuleProperty -> ShowS)
-> (RuleProperty -> String)
-> ([RuleProperty] -> ShowS)
-> Show RuleProperty
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> RuleProperty -> ShowS
showsPrec :: Int -> RuleProperty -> ShowS
$cshow :: RuleProperty -> String
show :: RuleProperty -> String
$cshowList :: [RuleProperty] -> ShowS
showList :: [RuleProperty] -> ShowS
Prelude.Show)
mkRuleProperty ::
ActionProperty
-> Value Prelude.Integer -> Value Prelude.Text -> RuleProperty
mkRuleProperty :: ActionProperty -> Value Integer -> Value Text -> RuleProperty
mkRuleProperty ActionProperty
action Value Integer
priority Value Text
ruleId
= RuleProperty
{haddock_workaround_ :: ()
haddock_workaround_ = (), action :: ActionProperty
action = ActionProperty
action, priority :: Value Integer
priority = Value Integer
priority,
ruleId :: Value Text
ruleId = Value Text
ruleId}
instance ToResourceProperties RuleProperty where
toResourceProperties :: RuleProperty -> ResourceProperties
toResourceProperties RuleProperty {()
Value Integer
Value Text
ActionProperty
haddock_workaround_ :: RuleProperty -> ()
action :: RuleProperty -> ActionProperty
priority :: RuleProperty -> Value Integer
ruleId :: RuleProperty -> Value Text
haddock_workaround_ :: ()
action :: ActionProperty
priority :: Value Integer
ruleId :: Value Text
..}
= ResourceProperties
{awsType :: Text
awsType = Text
"AWS::WAFRegional::WebACL.Rule",
supportsTags :: Bool
supportsTags = Bool
Prelude.False,
properties :: Object
properties = [Key
"Action" Key -> ActionProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
JSON..= ActionProperty
action, Key
"Priority" Key -> Value Integer -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
JSON..= Value Integer
priority,
Key
"RuleId" Key -> Value Text -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
JSON..= Value Text
ruleId]}
instance JSON.ToJSON RuleProperty where
toJSON :: RuleProperty -> Value
toJSON RuleProperty {()
Value Integer
Value Text
ActionProperty
haddock_workaround_ :: RuleProperty -> ()
action :: RuleProperty -> ActionProperty
priority :: RuleProperty -> Value Integer
ruleId :: RuleProperty -> Value Text
haddock_workaround_ :: ()
action :: ActionProperty
priority :: Value Integer
ruleId :: Value Text
..}
= [(Key, Value)] -> Value
JSON.object
[Key
"Action" Key -> ActionProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
JSON..= ActionProperty
action, Key
"Priority" Key -> Value Integer -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
JSON..= Value Integer
priority,
Key
"RuleId" Key -> Value Text -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
JSON..= Value Text
ruleId]
instance Property "Action" RuleProperty where
type PropertyType "Action" RuleProperty = ActionProperty
set :: PropertyType "Action" RuleProperty -> RuleProperty -> RuleProperty
set PropertyType "Action" RuleProperty
newValue RuleProperty {()
Value Integer
Value Text
ActionProperty
haddock_workaround_ :: RuleProperty -> ()
action :: RuleProperty -> ActionProperty
priority :: RuleProperty -> Value Integer
ruleId :: RuleProperty -> Value Text
haddock_workaround_ :: ()
action :: ActionProperty
priority :: Value Integer
ruleId :: Value Text
..}
= RuleProperty {action :: ActionProperty
action = PropertyType "Action" RuleProperty
ActionProperty
newValue, ()
Value Integer
Value Text
haddock_workaround_ :: ()
priority :: Value Integer
ruleId :: Value Text
haddock_workaround_ :: ()
priority :: Value Integer
ruleId :: Value Text
..}
instance Property "Priority" RuleProperty where
type PropertyType "Priority" RuleProperty = Value Prelude.Integer
set :: PropertyType "Priority" RuleProperty
-> RuleProperty -> RuleProperty
set PropertyType "Priority" RuleProperty
newValue RuleProperty {()
Value Integer
Value Text
ActionProperty
haddock_workaround_ :: RuleProperty -> ()
action :: RuleProperty -> ActionProperty
priority :: RuleProperty -> Value Integer
ruleId :: RuleProperty -> Value Text
haddock_workaround_ :: ()
action :: ActionProperty
priority :: Value Integer
ruleId :: Value Text
..}
= RuleProperty {priority :: Value Integer
priority = PropertyType "Priority" RuleProperty
Value Integer
newValue, ()
Value Text
ActionProperty
haddock_workaround_ :: ()
action :: ActionProperty
ruleId :: Value Text
haddock_workaround_ :: ()
action :: ActionProperty
ruleId :: Value Text
..}
instance Property "RuleId" RuleProperty where
type PropertyType "RuleId" RuleProperty = Value Prelude.Text
set :: PropertyType "RuleId" RuleProperty -> RuleProperty -> RuleProperty
set PropertyType "RuleId" RuleProperty
newValue RuleProperty {()
Value Integer
Value Text
ActionProperty
haddock_workaround_ :: RuleProperty -> ()
action :: RuleProperty -> ActionProperty
priority :: RuleProperty -> Value Integer
ruleId :: RuleProperty -> Value Text
haddock_workaround_ :: ()
action :: ActionProperty
priority :: Value Integer
ruleId :: Value Text
..}
= RuleProperty {ruleId :: Value Text
ruleId = PropertyType "RuleId" RuleProperty
Value Text
newValue, ()
Value Integer
ActionProperty
haddock_workaround_ :: ()
action :: ActionProperty
priority :: Value Integer
haddock_workaround_ :: ()
action :: ActionProperty
priority :: Value Integer
..}