module Stratosphere.WAFv2.RuleGroup.RateLimitUriPathProperty (
module Exports, RateLimitUriPathProperty(..),
mkRateLimitUriPathProperty
) 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
data RateLimitUriPathProperty
=
RateLimitUriPathProperty {RateLimitUriPathProperty -> ()
haddock_workaround_ :: (),
RateLimitUriPathProperty -> [TextTransformationProperty]
textTransformations :: [TextTransformationProperty]}
deriving stock (RateLimitUriPathProperty -> RateLimitUriPathProperty -> Bool
(RateLimitUriPathProperty -> RateLimitUriPathProperty -> Bool)
-> (RateLimitUriPathProperty -> RateLimitUriPathProperty -> Bool)
-> Eq RateLimitUriPathProperty
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: RateLimitUriPathProperty -> RateLimitUriPathProperty -> Bool
== :: RateLimitUriPathProperty -> RateLimitUriPathProperty -> Bool
$c/= :: RateLimitUriPathProperty -> RateLimitUriPathProperty -> Bool
/= :: RateLimitUriPathProperty -> RateLimitUriPathProperty -> Bool
Prelude.Eq, Int -> RateLimitUriPathProperty -> ShowS
[RateLimitUriPathProperty] -> ShowS
RateLimitUriPathProperty -> String
(Int -> RateLimitUriPathProperty -> ShowS)
-> (RateLimitUriPathProperty -> String)
-> ([RateLimitUriPathProperty] -> ShowS)
-> Show RateLimitUriPathProperty
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> RateLimitUriPathProperty -> ShowS
showsPrec :: Int -> RateLimitUriPathProperty -> ShowS
$cshow :: RateLimitUriPathProperty -> String
show :: RateLimitUriPathProperty -> String
$cshowList :: [RateLimitUriPathProperty] -> ShowS
showList :: [RateLimitUriPathProperty] -> ShowS
Prelude.Show)
mkRateLimitUriPathProperty ::
[TextTransformationProperty] -> RateLimitUriPathProperty
mkRateLimitUriPathProperty :: [TextTransformationProperty] -> RateLimitUriPathProperty
mkRateLimitUriPathProperty [TextTransformationProperty]
textTransformations
= RateLimitUriPathProperty
{haddock_workaround_ :: ()
haddock_workaround_ = (),
textTransformations :: [TextTransformationProperty]
textTransformations = [TextTransformationProperty]
textTransformations}
instance ToResourceProperties RateLimitUriPathProperty where
toResourceProperties :: RateLimitUriPathProperty -> ResourceProperties
toResourceProperties RateLimitUriPathProperty {[TextTransformationProperty]
()
haddock_workaround_ :: RateLimitUriPathProperty -> ()
textTransformations :: RateLimitUriPathProperty -> [TextTransformationProperty]
haddock_workaround_ :: ()
textTransformations :: [TextTransformationProperty]
..}
= ResourceProperties
{awsType :: Text
awsType = Text
"AWS::WAFv2::RuleGroup.RateLimitUriPath",
supportsTags :: Bool
supportsTags = Bool
Prelude.False,
properties :: Object
properties = [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 RateLimitUriPathProperty where
toJSON :: RateLimitUriPathProperty -> Value
toJSON RateLimitUriPathProperty {[TextTransformationProperty]
()
haddock_workaround_ :: RateLimitUriPathProperty -> ()
textTransformations :: RateLimitUriPathProperty -> [TextTransformationProperty]
haddock_workaround_ :: ()
textTransformations :: [TextTransformationProperty]
..}
= [(Key, Value)] -> Value
JSON.object [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 "TextTransformations" RateLimitUriPathProperty where
type PropertyType "TextTransformations" RateLimitUriPathProperty = [TextTransformationProperty]
set :: PropertyType "TextTransformations" RateLimitUriPathProperty
-> RateLimitUriPathProperty -> RateLimitUriPathProperty
set PropertyType "TextTransformations" RateLimitUriPathProperty
newValue RateLimitUriPathProperty {[TextTransformationProperty]
()
haddock_workaround_ :: RateLimitUriPathProperty -> ()
textTransformations :: RateLimitUriPathProperty -> [TextTransformationProperty]
haddock_workaround_ :: ()
textTransformations :: [TextTransformationProperty]
..}
= RateLimitUriPathProperty {textTransformations :: [TextTransformationProperty]
textTransformations = [TextTransformationProperty]
PropertyType "TextTransformations" RateLimitUriPathProperty
newValue, ()
haddock_workaround_ :: ()
haddock_workaround_ :: ()
..}