module Stratosphere.WAFv2.WebACL.RateBasedStatementProperty (
module Exports, RateBasedStatementProperty(..),
mkRateBasedStatementProperty
) where
import qualified Data.Aeson as JSON
import qualified Stratosphere.Prelude as Prelude
import Stratosphere.Property
import {-# SOURCE #-} Stratosphere.WAFv2.WebACL.ForwardedIPConfigurationProperty as Exports
import {-# SOURCE #-} Stratosphere.WAFv2.WebACL.RateBasedStatementCustomKeyProperty as Exports
import {-# SOURCE #-} Stratosphere.WAFv2.WebACL.StatementProperty as Exports
import Stratosphere.ResourceProperties
import Stratosphere.Value
data RateBasedStatementProperty
=
RateBasedStatementProperty {RateBasedStatementProperty -> ()
haddock_workaround_ :: (),
RateBasedStatementProperty -> Value Text
aggregateKeyType :: (Value Prelude.Text),
RateBasedStatementProperty
-> Maybe [RateBasedStatementCustomKeyProperty]
customKeys :: (Prelude.Maybe [RateBasedStatementCustomKeyProperty]),
RateBasedStatementProperty -> Maybe (Value Integer)
evaluationWindowSec :: (Prelude.Maybe (Value Prelude.Integer)),
RateBasedStatementProperty
-> Maybe ForwardedIPConfigurationProperty
forwardedIPConfig :: (Prelude.Maybe ForwardedIPConfigurationProperty),
RateBasedStatementProperty -> Value Integer
limit :: (Value Prelude.Integer),
RateBasedStatementProperty -> Maybe StatementProperty
scopeDownStatement :: (Prelude.Maybe StatementProperty)}
deriving stock (RateBasedStatementProperty -> RateBasedStatementProperty -> Bool
(RateBasedStatementProperty -> RateBasedStatementProperty -> Bool)
-> (RateBasedStatementProperty
-> RateBasedStatementProperty -> Bool)
-> Eq RateBasedStatementProperty
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: RateBasedStatementProperty -> RateBasedStatementProperty -> Bool
== :: RateBasedStatementProperty -> RateBasedStatementProperty -> Bool
$c/= :: RateBasedStatementProperty -> RateBasedStatementProperty -> Bool
/= :: RateBasedStatementProperty -> RateBasedStatementProperty -> Bool
Prelude.Eq, Int -> RateBasedStatementProperty -> ShowS
[RateBasedStatementProperty] -> ShowS
RateBasedStatementProperty -> String
(Int -> RateBasedStatementProperty -> ShowS)
-> (RateBasedStatementProperty -> String)
-> ([RateBasedStatementProperty] -> ShowS)
-> Show RateBasedStatementProperty
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> RateBasedStatementProperty -> ShowS
showsPrec :: Int -> RateBasedStatementProperty -> ShowS
$cshow :: RateBasedStatementProperty -> String
show :: RateBasedStatementProperty -> String
$cshowList :: [RateBasedStatementProperty] -> ShowS
showList :: [RateBasedStatementProperty] -> ShowS
Prelude.Show)
mkRateBasedStatementProperty ::
Value Prelude.Text
-> Value Prelude.Integer -> RateBasedStatementProperty
mkRateBasedStatementProperty :: Value Text -> Value Integer -> RateBasedStatementProperty
mkRateBasedStatementProperty Value Text
aggregateKeyType Value Integer
limit
= RateBasedStatementProperty
{haddock_workaround_ :: ()
haddock_workaround_ = (), aggregateKeyType :: Value Text
aggregateKeyType = Value Text
aggregateKeyType,
limit :: Value Integer
limit = Value Integer
limit, customKeys :: Maybe [RateBasedStatementCustomKeyProperty]
customKeys = Maybe [RateBasedStatementCustomKeyProperty]
forall a. Maybe a
Prelude.Nothing,
evaluationWindowSec :: Maybe (Value Integer)
evaluationWindowSec = Maybe (Value Integer)
forall a. Maybe a
Prelude.Nothing,
forwardedIPConfig :: Maybe ForwardedIPConfigurationProperty
forwardedIPConfig = Maybe ForwardedIPConfigurationProperty
forall a. Maybe a
Prelude.Nothing,
scopeDownStatement :: Maybe StatementProperty
scopeDownStatement = Maybe StatementProperty
forall a. Maybe a
Prelude.Nothing}
instance ToResourceProperties RateBasedStatementProperty where
toResourceProperties :: RateBasedStatementProperty -> ResourceProperties
toResourceProperties RateBasedStatementProperty {Maybe [RateBasedStatementCustomKeyProperty]
Maybe (Value Integer)
Maybe ForwardedIPConfigurationProperty
Maybe StatementProperty
()
Value Integer
Value Text
haddock_workaround_ :: RateBasedStatementProperty -> ()
aggregateKeyType :: RateBasedStatementProperty -> Value Text
customKeys :: RateBasedStatementProperty
-> Maybe [RateBasedStatementCustomKeyProperty]
evaluationWindowSec :: RateBasedStatementProperty -> Maybe (Value Integer)
forwardedIPConfig :: RateBasedStatementProperty
-> Maybe ForwardedIPConfigurationProperty
limit :: RateBasedStatementProperty -> Value Integer
scopeDownStatement :: RateBasedStatementProperty -> Maybe StatementProperty
haddock_workaround_ :: ()
aggregateKeyType :: Value Text
customKeys :: Maybe [RateBasedStatementCustomKeyProperty]
evaluationWindowSec :: Maybe (Value Integer)
forwardedIPConfig :: Maybe ForwardedIPConfigurationProperty
limit :: Value Integer
scopeDownStatement :: Maybe StatementProperty
..}
= ResourceProperties
{awsType :: Text
awsType = Text
"AWS::WAFv2::WebACL.RateBasedStatement",
supportsTags :: Bool
supportsTags = Bool
Prelude.False,
properties :: Object
properties = [Item Object] -> Object
forall l. IsList l => [Item l] -> l
Prelude.fromList
([(Key, Value)] -> [(Key, Value)] -> [(Key, Value)]
forall a. Semigroup a => a -> a -> a
(Prelude.<>)
[Key
"AggregateKeyType" 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
aggregateKeyType,
Key
"Limit" 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
limit]
([Maybe (Key, Value)] -> [(Key, Value)]
forall a. [Maybe a] -> [a]
Prelude.catMaybes
[Key -> [RateBasedStatementCustomKeyProperty] -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"CustomKeys" ([RateBasedStatementCustomKeyProperty] -> (Key, Value))
-> Maybe [RateBasedStatementCustomKeyProperty]
-> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [RateBasedStatementCustomKeyProperty]
customKeys,
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..=) Key
"EvaluationWindowSec" (Value Integer -> (Key, Value))
-> Maybe (Value Integer) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Integer)
evaluationWindowSec,
Key -> ForwardedIPConfigurationProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"ForwardedIPConfig" (ForwardedIPConfigurationProperty -> (Key, Value))
-> Maybe ForwardedIPConfigurationProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe ForwardedIPConfigurationProperty
forwardedIPConfig,
Key -> StatementProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"ScopeDownStatement" (StatementProperty -> (Key, Value))
-> Maybe StatementProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe StatementProperty
scopeDownStatement]))}
instance JSON.ToJSON RateBasedStatementProperty where
toJSON :: RateBasedStatementProperty -> Value
toJSON RateBasedStatementProperty {Maybe [RateBasedStatementCustomKeyProperty]
Maybe (Value Integer)
Maybe ForwardedIPConfigurationProperty
Maybe StatementProperty
()
Value Integer
Value Text
haddock_workaround_ :: RateBasedStatementProperty -> ()
aggregateKeyType :: RateBasedStatementProperty -> Value Text
customKeys :: RateBasedStatementProperty
-> Maybe [RateBasedStatementCustomKeyProperty]
evaluationWindowSec :: RateBasedStatementProperty -> Maybe (Value Integer)
forwardedIPConfig :: RateBasedStatementProperty
-> Maybe ForwardedIPConfigurationProperty
limit :: RateBasedStatementProperty -> Value Integer
scopeDownStatement :: RateBasedStatementProperty -> Maybe StatementProperty
haddock_workaround_ :: ()
aggregateKeyType :: Value Text
customKeys :: Maybe [RateBasedStatementCustomKeyProperty]
evaluationWindowSec :: Maybe (Value Integer)
forwardedIPConfig :: Maybe ForwardedIPConfigurationProperty
limit :: Value Integer
scopeDownStatement :: Maybe StatementProperty
..}
= [(Key, Value)] -> Value
JSON.object
([Item [(Key, Value)]] -> [(Key, Value)]
forall l. IsList l => [Item l] -> l
Prelude.fromList
([(Key, Value)] -> [(Key, Value)] -> [(Key, Value)]
forall a. Semigroup a => a -> a -> a
(Prelude.<>)
[Key
"AggregateKeyType" 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
aggregateKeyType,
Key
"Limit" 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
limit]
([Maybe (Key, Value)] -> [(Key, Value)]
forall a. [Maybe a] -> [a]
Prelude.catMaybes
[Key -> [RateBasedStatementCustomKeyProperty] -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"CustomKeys" ([RateBasedStatementCustomKeyProperty] -> (Key, Value))
-> Maybe [RateBasedStatementCustomKeyProperty]
-> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [RateBasedStatementCustomKeyProperty]
customKeys,
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..=) Key
"EvaluationWindowSec" (Value Integer -> (Key, Value))
-> Maybe (Value Integer) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Integer)
evaluationWindowSec,
Key -> ForwardedIPConfigurationProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"ForwardedIPConfig" (ForwardedIPConfigurationProperty -> (Key, Value))
-> Maybe ForwardedIPConfigurationProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe ForwardedIPConfigurationProperty
forwardedIPConfig,
Key -> StatementProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"ScopeDownStatement" (StatementProperty -> (Key, Value))
-> Maybe StatementProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe StatementProperty
scopeDownStatement])))
instance Property "AggregateKeyType" RateBasedStatementProperty where
type PropertyType "AggregateKeyType" RateBasedStatementProperty = Value Prelude.Text
set :: PropertyType "AggregateKeyType" RateBasedStatementProperty
-> RateBasedStatementProperty -> RateBasedStatementProperty
set PropertyType "AggregateKeyType" RateBasedStatementProperty
newValue RateBasedStatementProperty {Maybe [RateBasedStatementCustomKeyProperty]
Maybe (Value Integer)
Maybe ForwardedIPConfigurationProperty
Maybe StatementProperty
()
Value Integer
Value Text
haddock_workaround_ :: RateBasedStatementProperty -> ()
aggregateKeyType :: RateBasedStatementProperty -> Value Text
customKeys :: RateBasedStatementProperty
-> Maybe [RateBasedStatementCustomKeyProperty]
evaluationWindowSec :: RateBasedStatementProperty -> Maybe (Value Integer)
forwardedIPConfig :: RateBasedStatementProperty
-> Maybe ForwardedIPConfigurationProperty
limit :: RateBasedStatementProperty -> Value Integer
scopeDownStatement :: RateBasedStatementProperty -> Maybe StatementProperty
haddock_workaround_ :: ()
aggregateKeyType :: Value Text
customKeys :: Maybe [RateBasedStatementCustomKeyProperty]
evaluationWindowSec :: Maybe (Value Integer)
forwardedIPConfig :: Maybe ForwardedIPConfigurationProperty
limit :: Value Integer
scopeDownStatement :: Maybe StatementProperty
..}
= RateBasedStatementProperty {aggregateKeyType :: Value Text
aggregateKeyType = PropertyType "AggregateKeyType" RateBasedStatementProperty
Value Text
newValue, Maybe [RateBasedStatementCustomKeyProperty]
Maybe (Value Integer)
Maybe ForwardedIPConfigurationProperty
Maybe StatementProperty
()
Value Integer
haddock_workaround_ :: ()
customKeys :: Maybe [RateBasedStatementCustomKeyProperty]
evaluationWindowSec :: Maybe (Value Integer)
forwardedIPConfig :: Maybe ForwardedIPConfigurationProperty
limit :: Value Integer
scopeDownStatement :: Maybe StatementProperty
haddock_workaround_ :: ()
customKeys :: Maybe [RateBasedStatementCustomKeyProperty]
evaluationWindowSec :: Maybe (Value Integer)
forwardedIPConfig :: Maybe ForwardedIPConfigurationProperty
limit :: Value Integer
scopeDownStatement :: Maybe StatementProperty
..}
instance Property "CustomKeys" RateBasedStatementProperty where
type PropertyType "CustomKeys" RateBasedStatementProperty = [RateBasedStatementCustomKeyProperty]
set :: PropertyType "CustomKeys" RateBasedStatementProperty
-> RateBasedStatementProperty -> RateBasedStatementProperty
set PropertyType "CustomKeys" RateBasedStatementProperty
newValue RateBasedStatementProperty {Maybe [RateBasedStatementCustomKeyProperty]
Maybe (Value Integer)
Maybe ForwardedIPConfigurationProperty
Maybe StatementProperty
()
Value Integer
Value Text
haddock_workaround_ :: RateBasedStatementProperty -> ()
aggregateKeyType :: RateBasedStatementProperty -> Value Text
customKeys :: RateBasedStatementProperty
-> Maybe [RateBasedStatementCustomKeyProperty]
evaluationWindowSec :: RateBasedStatementProperty -> Maybe (Value Integer)
forwardedIPConfig :: RateBasedStatementProperty
-> Maybe ForwardedIPConfigurationProperty
limit :: RateBasedStatementProperty -> Value Integer
scopeDownStatement :: RateBasedStatementProperty -> Maybe StatementProperty
haddock_workaround_ :: ()
aggregateKeyType :: Value Text
customKeys :: Maybe [RateBasedStatementCustomKeyProperty]
evaluationWindowSec :: Maybe (Value Integer)
forwardedIPConfig :: Maybe ForwardedIPConfigurationProperty
limit :: Value Integer
scopeDownStatement :: Maybe StatementProperty
..}
= RateBasedStatementProperty
{customKeys :: Maybe [RateBasedStatementCustomKeyProperty]
customKeys = [RateBasedStatementCustomKeyProperty]
-> Maybe [RateBasedStatementCustomKeyProperty]
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure [RateBasedStatementCustomKeyProperty]
PropertyType "CustomKeys" RateBasedStatementProperty
newValue, Maybe (Value Integer)
Maybe ForwardedIPConfigurationProperty
Maybe StatementProperty
()
Value Integer
Value Text
haddock_workaround_ :: ()
aggregateKeyType :: Value Text
evaluationWindowSec :: Maybe (Value Integer)
forwardedIPConfig :: Maybe ForwardedIPConfigurationProperty
limit :: Value Integer
scopeDownStatement :: Maybe StatementProperty
haddock_workaround_ :: ()
aggregateKeyType :: Value Text
evaluationWindowSec :: Maybe (Value Integer)
forwardedIPConfig :: Maybe ForwardedIPConfigurationProperty
limit :: Value Integer
scopeDownStatement :: Maybe StatementProperty
..}
instance Property "EvaluationWindowSec" RateBasedStatementProperty where
type PropertyType "EvaluationWindowSec" RateBasedStatementProperty = Value Prelude.Integer
set :: PropertyType "EvaluationWindowSec" RateBasedStatementProperty
-> RateBasedStatementProperty -> RateBasedStatementProperty
set PropertyType "EvaluationWindowSec" RateBasedStatementProperty
newValue RateBasedStatementProperty {Maybe [RateBasedStatementCustomKeyProperty]
Maybe (Value Integer)
Maybe ForwardedIPConfigurationProperty
Maybe StatementProperty
()
Value Integer
Value Text
haddock_workaround_ :: RateBasedStatementProperty -> ()
aggregateKeyType :: RateBasedStatementProperty -> Value Text
customKeys :: RateBasedStatementProperty
-> Maybe [RateBasedStatementCustomKeyProperty]
evaluationWindowSec :: RateBasedStatementProperty -> Maybe (Value Integer)
forwardedIPConfig :: RateBasedStatementProperty
-> Maybe ForwardedIPConfigurationProperty
limit :: RateBasedStatementProperty -> Value Integer
scopeDownStatement :: RateBasedStatementProperty -> Maybe StatementProperty
haddock_workaround_ :: ()
aggregateKeyType :: Value Text
customKeys :: Maybe [RateBasedStatementCustomKeyProperty]
evaluationWindowSec :: Maybe (Value Integer)
forwardedIPConfig :: Maybe ForwardedIPConfigurationProperty
limit :: Value Integer
scopeDownStatement :: Maybe StatementProperty
..}
= RateBasedStatementProperty
{evaluationWindowSec :: Maybe (Value Integer)
evaluationWindowSec = Value Integer -> Maybe (Value Integer)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "EvaluationWindowSec" RateBasedStatementProperty
Value Integer
newValue, Maybe [RateBasedStatementCustomKeyProperty]
Maybe ForwardedIPConfigurationProperty
Maybe StatementProperty
()
Value Integer
Value Text
haddock_workaround_ :: ()
aggregateKeyType :: Value Text
customKeys :: Maybe [RateBasedStatementCustomKeyProperty]
forwardedIPConfig :: Maybe ForwardedIPConfigurationProperty
limit :: Value Integer
scopeDownStatement :: Maybe StatementProperty
haddock_workaround_ :: ()
aggregateKeyType :: Value Text
customKeys :: Maybe [RateBasedStatementCustomKeyProperty]
forwardedIPConfig :: Maybe ForwardedIPConfigurationProperty
limit :: Value Integer
scopeDownStatement :: Maybe StatementProperty
..}
instance Property "ForwardedIPConfig" RateBasedStatementProperty where
type PropertyType "ForwardedIPConfig" RateBasedStatementProperty = ForwardedIPConfigurationProperty
set :: PropertyType "ForwardedIPConfig" RateBasedStatementProperty
-> RateBasedStatementProperty -> RateBasedStatementProperty
set PropertyType "ForwardedIPConfig" RateBasedStatementProperty
newValue RateBasedStatementProperty {Maybe [RateBasedStatementCustomKeyProperty]
Maybe (Value Integer)
Maybe ForwardedIPConfigurationProperty
Maybe StatementProperty
()
Value Integer
Value Text
haddock_workaround_ :: RateBasedStatementProperty -> ()
aggregateKeyType :: RateBasedStatementProperty -> Value Text
customKeys :: RateBasedStatementProperty
-> Maybe [RateBasedStatementCustomKeyProperty]
evaluationWindowSec :: RateBasedStatementProperty -> Maybe (Value Integer)
forwardedIPConfig :: RateBasedStatementProperty
-> Maybe ForwardedIPConfigurationProperty
limit :: RateBasedStatementProperty -> Value Integer
scopeDownStatement :: RateBasedStatementProperty -> Maybe StatementProperty
haddock_workaround_ :: ()
aggregateKeyType :: Value Text
customKeys :: Maybe [RateBasedStatementCustomKeyProperty]
evaluationWindowSec :: Maybe (Value Integer)
forwardedIPConfig :: Maybe ForwardedIPConfigurationProperty
limit :: Value Integer
scopeDownStatement :: Maybe StatementProperty
..}
= RateBasedStatementProperty
{forwardedIPConfig :: Maybe ForwardedIPConfigurationProperty
forwardedIPConfig = ForwardedIPConfigurationProperty
-> Maybe ForwardedIPConfigurationProperty
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "ForwardedIPConfig" RateBasedStatementProperty
ForwardedIPConfigurationProperty
newValue, Maybe [RateBasedStatementCustomKeyProperty]
Maybe (Value Integer)
Maybe StatementProperty
()
Value Integer
Value Text
haddock_workaround_ :: ()
aggregateKeyType :: Value Text
customKeys :: Maybe [RateBasedStatementCustomKeyProperty]
evaluationWindowSec :: Maybe (Value Integer)
limit :: Value Integer
scopeDownStatement :: Maybe StatementProperty
haddock_workaround_ :: ()
aggregateKeyType :: Value Text
customKeys :: Maybe [RateBasedStatementCustomKeyProperty]
evaluationWindowSec :: Maybe (Value Integer)
limit :: Value Integer
scopeDownStatement :: Maybe StatementProperty
..}
instance Property "Limit" RateBasedStatementProperty where
type PropertyType "Limit" RateBasedStatementProperty = Value Prelude.Integer
set :: PropertyType "Limit" RateBasedStatementProperty
-> RateBasedStatementProperty -> RateBasedStatementProperty
set PropertyType "Limit" RateBasedStatementProperty
newValue RateBasedStatementProperty {Maybe [RateBasedStatementCustomKeyProperty]
Maybe (Value Integer)
Maybe ForwardedIPConfigurationProperty
Maybe StatementProperty
()
Value Integer
Value Text
haddock_workaround_ :: RateBasedStatementProperty -> ()
aggregateKeyType :: RateBasedStatementProperty -> Value Text
customKeys :: RateBasedStatementProperty
-> Maybe [RateBasedStatementCustomKeyProperty]
evaluationWindowSec :: RateBasedStatementProperty -> Maybe (Value Integer)
forwardedIPConfig :: RateBasedStatementProperty
-> Maybe ForwardedIPConfigurationProperty
limit :: RateBasedStatementProperty -> Value Integer
scopeDownStatement :: RateBasedStatementProperty -> Maybe StatementProperty
haddock_workaround_ :: ()
aggregateKeyType :: Value Text
customKeys :: Maybe [RateBasedStatementCustomKeyProperty]
evaluationWindowSec :: Maybe (Value Integer)
forwardedIPConfig :: Maybe ForwardedIPConfigurationProperty
limit :: Value Integer
scopeDownStatement :: Maybe StatementProperty
..}
= RateBasedStatementProperty {limit :: Value Integer
limit = PropertyType "Limit" RateBasedStatementProperty
Value Integer
newValue, Maybe [RateBasedStatementCustomKeyProperty]
Maybe (Value Integer)
Maybe ForwardedIPConfigurationProperty
Maybe StatementProperty
()
Value Text
haddock_workaround_ :: ()
aggregateKeyType :: Value Text
customKeys :: Maybe [RateBasedStatementCustomKeyProperty]
evaluationWindowSec :: Maybe (Value Integer)
forwardedIPConfig :: Maybe ForwardedIPConfigurationProperty
scopeDownStatement :: Maybe StatementProperty
haddock_workaround_ :: ()
aggregateKeyType :: Value Text
customKeys :: Maybe [RateBasedStatementCustomKeyProperty]
evaluationWindowSec :: Maybe (Value Integer)
forwardedIPConfig :: Maybe ForwardedIPConfigurationProperty
scopeDownStatement :: Maybe StatementProperty
..}
instance Property "ScopeDownStatement" RateBasedStatementProperty where
type PropertyType "ScopeDownStatement" RateBasedStatementProperty = StatementProperty
set :: PropertyType "ScopeDownStatement" RateBasedStatementProperty
-> RateBasedStatementProperty -> RateBasedStatementProperty
set PropertyType "ScopeDownStatement" RateBasedStatementProperty
newValue RateBasedStatementProperty {Maybe [RateBasedStatementCustomKeyProperty]
Maybe (Value Integer)
Maybe ForwardedIPConfigurationProperty
Maybe StatementProperty
()
Value Integer
Value Text
haddock_workaround_ :: RateBasedStatementProperty -> ()
aggregateKeyType :: RateBasedStatementProperty -> Value Text
customKeys :: RateBasedStatementProperty
-> Maybe [RateBasedStatementCustomKeyProperty]
evaluationWindowSec :: RateBasedStatementProperty -> Maybe (Value Integer)
forwardedIPConfig :: RateBasedStatementProperty
-> Maybe ForwardedIPConfigurationProperty
limit :: RateBasedStatementProperty -> Value Integer
scopeDownStatement :: RateBasedStatementProperty -> Maybe StatementProperty
haddock_workaround_ :: ()
aggregateKeyType :: Value Text
customKeys :: Maybe [RateBasedStatementCustomKeyProperty]
evaluationWindowSec :: Maybe (Value Integer)
forwardedIPConfig :: Maybe ForwardedIPConfigurationProperty
limit :: Value Integer
scopeDownStatement :: Maybe StatementProperty
..}
= RateBasedStatementProperty
{scopeDownStatement :: Maybe StatementProperty
scopeDownStatement = StatementProperty -> Maybe StatementProperty
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "ScopeDownStatement" RateBasedStatementProperty
StatementProperty
newValue, Maybe [RateBasedStatementCustomKeyProperty]
Maybe (Value Integer)
Maybe ForwardedIPConfigurationProperty
()
Value Integer
Value Text
haddock_workaround_ :: ()
aggregateKeyType :: Value Text
customKeys :: Maybe [RateBasedStatementCustomKeyProperty]
evaluationWindowSec :: Maybe (Value Integer)
forwardedIPConfig :: Maybe ForwardedIPConfigurationProperty
limit :: Value Integer
haddock_workaround_ :: ()
aggregateKeyType :: Value Text
customKeys :: Maybe [RateBasedStatementCustomKeyProperty]
evaluationWindowSec :: Maybe (Value Integer)
forwardedIPConfig :: Maybe ForwardedIPConfigurationProperty
limit :: Value Integer
..}