module Stratosphere.WAFv2.LoggingConfiguration.FilterProperty (
module Exports, FilterProperty(..), mkFilterProperty
) where
import qualified Data.Aeson as JSON
import qualified Stratosphere.Prelude as Prelude
import Stratosphere.Property
import {-# SOURCE #-} Stratosphere.WAFv2.LoggingConfiguration.ConditionProperty as Exports
import Stratosphere.ResourceProperties
import Stratosphere.Value
data FilterProperty
=
FilterProperty {FilterProperty -> ()
haddock_workaround_ :: (),
FilterProperty -> Value Text
behavior :: (Value Prelude.Text),
FilterProperty -> [ConditionProperty]
conditions :: [ConditionProperty],
FilterProperty -> Value Text
requirement :: (Value Prelude.Text)}
deriving stock (FilterProperty -> FilterProperty -> Bool
(FilterProperty -> FilterProperty -> Bool)
-> (FilterProperty -> FilterProperty -> Bool) -> Eq FilterProperty
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: FilterProperty -> FilterProperty -> Bool
== :: FilterProperty -> FilterProperty -> Bool
$c/= :: FilterProperty -> FilterProperty -> Bool
/= :: FilterProperty -> FilterProperty -> Bool
Prelude.Eq, Int -> FilterProperty -> ShowS
[FilterProperty] -> ShowS
FilterProperty -> String
(Int -> FilterProperty -> ShowS)
-> (FilterProperty -> String)
-> ([FilterProperty] -> ShowS)
-> Show FilterProperty
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> FilterProperty -> ShowS
showsPrec :: Int -> FilterProperty -> ShowS
$cshow :: FilterProperty -> String
show :: FilterProperty -> String
$cshowList :: [FilterProperty] -> ShowS
showList :: [FilterProperty] -> ShowS
Prelude.Show)
mkFilterProperty ::
Value Prelude.Text
-> [ConditionProperty] -> Value Prelude.Text -> FilterProperty
mkFilterProperty :: Value Text -> [ConditionProperty] -> Value Text -> FilterProperty
mkFilterProperty Value Text
behavior [ConditionProperty]
conditions Value Text
requirement
= FilterProperty
{haddock_workaround_ :: ()
haddock_workaround_ = (), behavior :: Value Text
behavior = Value Text
behavior,
conditions :: [ConditionProperty]
conditions = [ConditionProperty]
conditions, requirement :: Value Text
requirement = Value Text
requirement}
instance ToResourceProperties FilterProperty where
toResourceProperties :: FilterProperty -> ResourceProperties
toResourceProperties FilterProperty {[ConditionProperty]
()
Value Text
haddock_workaround_ :: FilterProperty -> ()
behavior :: FilterProperty -> Value Text
conditions :: FilterProperty -> [ConditionProperty]
requirement :: FilterProperty -> Value Text
haddock_workaround_ :: ()
behavior :: Value Text
conditions :: [ConditionProperty]
requirement :: Value Text
..}
= ResourceProperties
{awsType :: Text
awsType = Text
"AWS::WAFv2::LoggingConfiguration.Filter",
supportsTags :: Bool
supportsTags = Bool
Prelude.False,
properties :: Object
properties = [Key
"Behavior" 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
behavior,
Key
"Conditions" Key -> [ConditionProperty] -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
JSON..= [ConditionProperty]
conditions,
Key
"Requirement" 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
requirement]}
instance JSON.ToJSON FilterProperty where
toJSON :: FilterProperty -> Value
toJSON FilterProperty {[ConditionProperty]
()
Value Text
haddock_workaround_ :: FilterProperty -> ()
behavior :: FilterProperty -> Value Text
conditions :: FilterProperty -> [ConditionProperty]
requirement :: FilterProperty -> Value Text
haddock_workaround_ :: ()
behavior :: Value Text
conditions :: [ConditionProperty]
requirement :: Value Text
..}
= [(Key, Value)] -> Value
JSON.object
[Key
"Behavior" 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
behavior, Key
"Conditions" Key -> [ConditionProperty] -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
JSON..= [ConditionProperty]
conditions,
Key
"Requirement" 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
requirement]
instance Property "Behavior" FilterProperty where
type PropertyType "Behavior" FilterProperty = Value Prelude.Text
set :: PropertyType "Behavior" FilterProperty
-> FilterProperty -> FilterProperty
set PropertyType "Behavior" FilterProperty
newValue FilterProperty {[ConditionProperty]
()
Value Text
haddock_workaround_ :: FilterProperty -> ()
behavior :: FilterProperty -> Value Text
conditions :: FilterProperty -> [ConditionProperty]
requirement :: FilterProperty -> Value Text
haddock_workaround_ :: ()
behavior :: Value Text
conditions :: [ConditionProperty]
requirement :: Value Text
..}
= FilterProperty {behavior :: Value Text
behavior = PropertyType "Behavior" FilterProperty
Value Text
newValue, [ConditionProperty]
()
Value Text
haddock_workaround_ :: ()
conditions :: [ConditionProperty]
requirement :: Value Text
haddock_workaround_ :: ()
conditions :: [ConditionProperty]
requirement :: Value Text
..}
instance Property "Conditions" FilterProperty where
type PropertyType "Conditions" FilterProperty = [ConditionProperty]
set :: PropertyType "Conditions" FilterProperty
-> FilterProperty -> FilterProperty
set PropertyType "Conditions" FilterProperty
newValue FilterProperty {[ConditionProperty]
()
Value Text
haddock_workaround_ :: FilterProperty -> ()
behavior :: FilterProperty -> Value Text
conditions :: FilterProperty -> [ConditionProperty]
requirement :: FilterProperty -> Value Text
haddock_workaround_ :: ()
behavior :: Value Text
conditions :: [ConditionProperty]
requirement :: Value Text
..}
= FilterProperty {conditions :: [ConditionProperty]
conditions = [ConditionProperty]
PropertyType "Conditions" FilterProperty
newValue, ()
Value Text
haddock_workaround_ :: ()
behavior :: Value Text
requirement :: Value Text
haddock_workaround_ :: ()
behavior :: Value Text
requirement :: Value Text
..}
instance Property "Requirement" FilterProperty where
type PropertyType "Requirement" FilterProperty = Value Prelude.Text
set :: PropertyType "Requirement" FilterProperty
-> FilterProperty -> FilterProperty
set PropertyType "Requirement" FilterProperty
newValue FilterProperty {[ConditionProperty]
()
Value Text
haddock_workaround_ :: FilterProperty -> ()
behavior :: FilterProperty -> Value Text
conditions :: FilterProperty -> [ConditionProperty]
requirement :: FilterProperty -> Value Text
haddock_workaround_ :: ()
behavior :: Value Text
conditions :: [ConditionProperty]
requirement :: Value Text
..}
= FilterProperty {requirement :: Value Text
requirement = PropertyType "Requirement" FilterProperty
Value Text
newValue, [ConditionProperty]
()
Value Text
haddock_workaround_ :: ()
behavior :: Value Text
conditions :: [ConditionProperty]
haddock_workaround_ :: ()
behavior :: Value Text
conditions :: [ConditionProperty]
..}