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