module Stratosphere.WAFv2.RuleGroup.RateLimitCookieProperty (
module Exports, RateLimitCookieProperty(..),
mkRateLimitCookieProperty
) where
import qualified Data.Aeson as JSON
import qualified Stratosphere.Prelude as Prelude
import Stratosphere.Property
import {-# SOURCE #-} Stratosphere.WAFv2.RuleGroup.TextTransformationProperty as Exports
import Stratosphere.ResourceProperties
import Stratosphere.Value
data RateLimitCookieProperty
=
RateLimitCookieProperty {RateLimitCookieProperty -> ()
haddock_workaround_ :: (),
RateLimitCookieProperty -> Value Text
name :: (Value Prelude.Text),
RateLimitCookieProperty -> [TextTransformationProperty]
textTransformations :: [TextTransformationProperty]}
deriving stock (RateLimitCookieProperty -> RateLimitCookieProperty -> Bool
(RateLimitCookieProperty -> RateLimitCookieProperty -> Bool)
-> (RateLimitCookieProperty -> RateLimitCookieProperty -> Bool)
-> Eq RateLimitCookieProperty
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: RateLimitCookieProperty -> RateLimitCookieProperty -> Bool
== :: RateLimitCookieProperty -> RateLimitCookieProperty -> Bool
$c/= :: RateLimitCookieProperty -> RateLimitCookieProperty -> Bool
/= :: RateLimitCookieProperty -> RateLimitCookieProperty -> Bool
Prelude.Eq, Int -> RateLimitCookieProperty -> ShowS
[RateLimitCookieProperty] -> ShowS
RateLimitCookieProperty -> String
(Int -> RateLimitCookieProperty -> ShowS)
-> (RateLimitCookieProperty -> String)
-> ([RateLimitCookieProperty] -> ShowS)
-> Show RateLimitCookieProperty
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> RateLimitCookieProperty -> ShowS
showsPrec :: Int -> RateLimitCookieProperty -> ShowS
$cshow :: RateLimitCookieProperty -> String
show :: RateLimitCookieProperty -> String
$cshowList :: [RateLimitCookieProperty] -> ShowS
showList :: [RateLimitCookieProperty] -> ShowS
Prelude.Show)
mkRateLimitCookieProperty ::
Value Prelude.Text
-> [TextTransformationProperty] -> RateLimitCookieProperty
mkRateLimitCookieProperty :: Value Text
-> [TextTransformationProperty] -> RateLimitCookieProperty
mkRateLimitCookieProperty Value Text
name [TextTransformationProperty]
textTransformations
= RateLimitCookieProperty
{haddock_workaround_ :: ()
haddock_workaround_ = (), name :: Value Text
name = Value Text
name,
textTransformations :: [TextTransformationProperty]
textTransformations = [TextTransformationProperty]
textTransformations}
instance ToResourceProperties RateLimitCookieProperty where
toResourceProperties :: RateLimitCookieProperty -> ResourceProperties
toResourceProperties RateLimitCookieProperty {[TextTransformationProperty]
()
Value Text
haddock_workaround_ :: RateLimitCookieProperty -> ()
name :: RateLimitCookieProperty -> Value Text
textTransformations :: RateLimitCookieProperty -> [TextTransformationProperty]
haddock_workaround_ :: ()
name :: Value Text
textTransformations :: [TextTransformationProperty]
..}
= ResourceProperties
{awsType :: Text
awsType = Text
"AWS::WAFv2::RuleGroup.RateLimitCookie",
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,
Key
"TextTransformations" Key -> [TextTransformationProperty] -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
JSON..= [TextTransformationProperty]
textTransformations]}
instance JSON.ToJSON RateLimitCookieProperty where
toJSON :: RateLimitCookieProperty -> Value
toJSON RateLimitCookieProperty {[TextTransformationProperty]
()
Value Text
haddock_workaround_ :: RateLimitCookieProperty -> ()
name :: RateLimitCookieProperty -> Value Text
textTransformations :: RateLimitCookieProperty -> [TextTransformationProperty]
haddock_workaround_ :: ()
name :: Value Text
textTransformations :: [TextTransformationProperty]
..}
= [(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,
Key
"TextTransformations" Key -> [TextTransformationProperty] -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
JSON..= [TextTransformationProperty]
textTransformations]
instance Property "Name" RateLimitCookieProperty where
type PropertyType "Name" RateLimitCookieProperty = Value Prelude.Text
set :: PropertyType "Name" RateLimitCookieProperty
-> RateLimitCookieProperty -> RateLimitCookieProperty
set PropertyType "Name" RateLimitCookieProperty
newValue RateLimitCookieProperty {[TextTransformationProperty]
()
Value Text
haddock_workaround_ :: RateLimitCookieProperty -> ()
name :: RateLimitCookieProperty -> Value Text
textTransformations :: RateLimitCookieProperty -> [TextTransformationProperty]
haddock_workaround_ :: ()
name :: Value Text
textTransformations :: [TextTransformationProperty]
..}
= RateLimitCookieProperty {name :: Value Text
name = PropertyType "Name" RateLimitCookieProperty
Value Text
newValue, [TextTransformationProperty]
()
haddock_workaround_ :: ()
textTransformations :: [TextTransformationProperty]
haddock_workaround_ :: ()
textTransformations :: [TextTransformationProperty]
..}
instance Property "TextTransformations" RateLimitCookieProperty where
type PropertyType "TextTransformations" RateLimitCookieProperty = [TextTransformationProperty]
set :: PropertyType "TextTransformations" RateLimitCookieProperty
-> RateLimitCookieProperty -> RateLimitCookieProperty
set PropertyType "TextTransformations" RateLimitCookieProperty
newValue RateLimitCookieProperty {[TextTransformationProperty]
()
Value Text
haddock_workaround_ :: RateLimitCookieProperty -> ()
name :: RateLimitCookieProperty -> Value Text
textTransformations :: RateLimitCookieProperty -> [TextTransformationProperty]
haddock_workaround_ :: ()
name :: Value Text
textTransformations :: [TextTransformationProperty]
..}
= RateLimitCookieProperty {textTransformations :: [TextTransformationProperty]
textTransformations = [TextTransformationProperty]
PropertyType "TextTransformations" RateLimitCookieProperty
newValue, ()
Value Text
haddock_workaround_ :: ()
name :: Value Text
haddock_workaround_ :: ()
name :: Value Text
..}