module Stratosphere.WAFv2.WebACL.ExcludedRuleProperty (
ExcludedRuleProperty(..), mkExcludedRuleProperty
) where
import qualified Data.Aeson as JSON
import qualified Stratosphere.Prelude as Prelude
import Stratosphere.Property
import Stratosphere.ResourceProperties
import Stratosphere.Value
data ExcludedRuleProperty
=
ExcludedRuleProperty {ExcludedRuleProperty -> ()
haddock_workaround_ :: (),
ExcludedRuleProperty -> Value Text
name :: (Value Prelude.Text)}
deriving stock (ExcludedRuleProperty -> ExcludedRuleProperty -> Bool
(ExcludedRuleProperty -> ExcludedRuleProperty -> Bool)
-> (ExcludedRuleProperty -> ExcludedRuleProperty -> Bool)
-> Eq ExcludedRuleProperty
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ExcludedRuleProperty -> ExcludedRuleProperty -> Bool
== :: ExcludedRuleProperty -> ExcludedRuleProperty -> Bool
$c/= :: ExcludedRuleProperty -> ExcludedRuleProperty -> Bool
/= :: ExcludedRuleProperty -> ExcludedRuleProperty -> Bool
Prelude.Eq, Int -> ExcludedRuleProperty -> ShowS
[ExcludedRuleProperty] -> ShowS
ExcludedRuleProperty -> String
(Int -> ExcludedRuleProperty -> ShowS)
-> (ExcludedRuleProperty -> String)
-> ([ExcludedRuleProperty] -> ShowS)
-> Show ExcludedRuleProperty
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ExcludedRuleProperty -> ShowS
showsPrec :: Int -> ExcludedRuleProperty -> ShowS
$cshow :: ExcludedRuleProperty -> String
show :: ExcludedRuleProperty -> String
$cshowList :: [ExcludedRuleProperty] -> ShowS
showList :: [ExcludedRuleProperty] -> ShowS
Prelude.Show)
mkExcludedRuleProperty ::
Value Prelude.Text -> ExcludedRuleProperty
mkExcludedRuleProperty :: Value Text -> ExcludedRuleProperty
mkExcludedRuleProperty Value Text
name
= ExcludedRuleProperty {haddock_workaround_ :: ()
haddock_workaround_ = (), name :: Value Text
name = Value Text
name}
instance ToResourceProperties ExcludedRuleProperty where
toResourceProperties :: ExcludedRuleProperty -> ResourceProperties
toResourceProperties ExcludedRuleProperty {()
Value Text
haddock_workaround_ :: ExcludedRuleProperty -> ()
name :: ExcludedRuleProperty -> Value Text
haddock_workaround_ :: ()
name :: Value Text
..}
= ResourceProperties
{awsType :: Text
awsType = Text
"AWS::WAFv2::WebACL.ExcludedRule",
supportsTags :: Bool
supportsTags = Bool
Prelude.False, properties :: Object
properties = [Key
"Name" 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
name]}
instance JSON.ToJSON ExcludedRuleProperty where
toJSON :: ExcludedRuleProperty -> Value
toJSON ExcludedRuleProperty {()
Value Text
haddock_workaround_ :: ExcludedRuleProperty -> ()
name :: ExcludedRuleProperty -> Value Text
haddock_workaround_ :: ()
name :: Value Text
..}
= [(Key, Value)] -> Value
JSON.object [Key
"Name" 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
name]
instance Property "Name" ExcludedRuleProperty where
type PropertyType "Name" ExcludedRuleProperty = Value Prelude.Text
set :: PropertyType "Name" ExcludedRuleProperty
-> ExcludedRuleProperty -> ExcludedRuleProperty
set PropertyType "Name" ExcludedRuleProperty
newValue ExcludedRuleProperty {()
Value Text
haddock_workaround_ :: ExcludedRuleProperty -> ()
name :: ExcludedRuleProperty -> Value Text
haddock_workaround_ :: ()
name :: Value Text
..}
= ExcludedRuleProperty {name :: Value Text
name = PropertyType "Name" ExcludedRuleProperty
Value Text
newValue, ()
haddock_workaround_ :: ()
haddock_workaround_ :: ()
..}