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