module Stratosphere.Shield.Protection.ApplicationLayerAutomaticResponseConfigurationProperty (
module Exports,
ApplicationLayerAutomaticResponseConfigurationProperty(..),
mkApplicationLayerAutomaticResponseConfigurationProperty
) where
import qualified Data.Aeson as JSON
import qualified Stratosphere.Prelude as Prelude
import Stratosphere.Property
import {-# SOURCE #-} Stratosphere.Shield.Protection.ActionProperty as Exports
import Stratosphere.ResourceProperties
import Stratosphere.Value
data ApplicationLayerAutomaticResponseConfigurationProperty
=
ApplicationLayerAutomaticResponseConfigurationProperty {ApplicationLayerAutomaticResponseConfigurationProperty -> ()
haddock_workaround_ :: (),
ApplicationLayerAutomaticResponseConfigurationProperty
-> ActionProperty
action :: ActionProperty,
ApplicationLayerAutomaticResponseConfigurationProperty
-> Value Text
status :: (Value Prelude.Text)}
deriving stock (ApplicationLayerAutomaticResponseConfigurationProperty
-> ApplicationLayerAutomaticResponseConfigurationProperty -> Bool
(ApplicationLayerAutomaticResponseConfigurationProperty
-> ApplicationLayerAutomaticResponseConfigurationProperty -> Bool)
-> (ApplicationLayerAutomaticResponseConfigurationProperty
-> ApplicationLayerAutomaticResponseConfigurationProperty -> Bool)
-> Eq ApplicationLayerAutomaticResponseConfigurationProperty
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ApplicationLayerAutomaticResponseConfigurationProperty
-> ApplicationLayerAutomaticResponseConfigurationProperty -> Bool
== :: ApplicationLayerAutomaticResponseConfigurationProperty
-> ApplicationLayerAutomaticResponseConfigurationProperty -> Bool
$c/= :: ApplicationLayerAutomaticResponseConfigurationProperty
-> ApplicationLayerAutomaticResponseConfigurationProperty -> Bool
/= :: ApplicationLayerAutomaticResponseConfigurationProperty
-> ApplicationLayerAutomaticResponseConfigurationProperty -> Bool
Prelude.Eq, Int
-> ApplicationLayerAutomaticResponseConfigurationProperty -> ShowS
[ApplicationLayerAutomaticResponseConfigurationProperty] -> ShowS
ApplicationLayerAutomaticResponseConfigurationProperty -> String
(Int
-> ApplicationLayerAutomaticResponseConfigurationProperty -> ShowS)
-> (ApplicationLayerAutomaticResponseConfigurationProperty
-> String)
-> ([ApplicationLayerAutomaticResponseConfigurationProperty]
-> ShowS)
-> Show ApplicationLayerAutomaticResponseConfigurationProperty
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int
-> ApplicationLayerAutomaticResponseConfigurationProperty -> ShowS
showsPrec :: Int
-> ApplicationLayerAutomaticResponseConfigurationProperty -> ShowS
$cshow :: ApplicationLayerAutomaticResponseConfigurationProperty -> String
show :: ApplicationLayerAutomaticResponseConfigurationProperty -> String
$cshowList :: [ApplicationLayerAutomaticResponseConfigurationProperty] -> ShowS
showList :: [ApplicationLayerAutomaticResponseConfigurationProperty] -> ShowS
Prelude.Show)
mkApplicationLayerAutomaticResponseConfigurationProperty ::
ActionProperty
-> Value Prelude.Text
-> ApplicationLayerAutomaticResponseConfigurationProperty
mkApplicationLayerAutomaticResponseConfigurationProperty :: ActionProperty
-> Value Text
-> ApplicationLayerAutomaticResponseConfigurationProperty
mkApplicationLayerAutomaticResponseConfigurationProperty
ActionProperty
action
Value Text
status
= ApplicationLayerAutomaticResponseConfigurationProperty
{haddock_workaround_ :: ()
haddock_workaround_ = (), action :: ActionProperty
action = ActionProperty
action, status :: Value Text
status = Value Text
status}
instance ToResourceProperties ApplicationLayerAutomaticResponseConfigurationProperty where
toResourceProperties :: ApplicationLayerAutomaticResponseConfigurationProperty
-> ResourceProperties
toResourceProperties
ApplicationLayerAutomaticResponseConfigurationProperty {()
Value Text
ActionProperty
haddock_workaround_ :: ApplicationLayerAutomaticResponseConfigurationProperty -> ()
action :: ApplicationLayerAutomaticResponseConfigurationProperty
-> ActionProperty
status :: ApplicationLayerAutomaticResponseConfigurationProperty
-> Value Text
haddock_workaround_ :: ()
action :: ActionProperty
status :: Value Text
..}
= ResourceProperties
{awsType :: Text
awsType = Text
"AWS::Shield::Protection.ApplicationLayerAutomaticResponseConfiguration",
supportsTags :: Bool
supportsTags = Bool
Prelude.False,
properties :: Object
properties = [Key
"Action" Key -> ActionProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
JSON..= ActionProperty
action, Key
"Status" 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
status]}
instance JSON.ToJSON ApplicationLayerAutomaticResponseConfigurationProperty where
toJSON :: ApplicationLayerAutomaticResponseConfigurationProperty -> Value
toJSON ApplicationLayerAutomaticResponseConfigurationProperty {()
Value Text
ActionProperty
haddock_workaround_ :: ApplicationLayerAutomaticResponseConfigurationProperty -> ()
action :: ApplicationLayerAutomaticResponseConfigurationProperty
-> ActionProperty
status :: ApplicationLayerAutomaticResponseConfigurationProperty
-> Value Text
haddock_workaround_ :: ()
action :: ActionProperty
status :: Value Text
..}
= [(Key, Value)] -> Value
JSON.object [Key
"Action" Key -> ActionProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
JSON..= ActionProperty
action, Key
"Status" 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
status]
instance Property "Action" ApplicationLayerAutomaticResponseConfigurationProperty where
type PropertyType "Action" ApplicationLayerAutomaticResponseConfigurationProperty = ActionProperty
set :: PropertyType
"Action" ApplicationLayerAutomaticResponseConfigurationProperty
-> ApplicationLayerAutomaticResponseConfigurationProperty
-> ApplicationLayerAutomaticResponseConfigurationProperty
set
PropertyType
"Action" ApplicationLayerAutomaticResponseConfigurationProperty
newValue
ApplicationLayerAutomaticResponseConfigurationProperty {()
Value Text
ActionProperty
haddock_workaround_ :: ApplicationLayerAutomaticResponseConfigurationProperty -> ()
action :: ApplicationLayerAutomaticResponseConfigurationProperty
-> ActionProperty
status :: ApplicationLayerAutomaticResponseConfigurationProperty
-> Value Text
haddock_workaround_ :: ()
action :: ActionProperty
status :: Value Text
..}
= ApplicationLayerAutomaticResponseConfigurationProperty
{action :: ActionProperty
action = PropertyType
"Action" ApplicationLayerAutomaticResponseConfigurationProperty
ActionProperty
newValue, ()
Value Text
haddock_workaround_ :: ()
status :: Value Text
haddock_workaround_ :: ()
status :: Value Text
..}
instance Property "Status" ApplicationLayerAutomaticResponseConfigurationProperty where
type PropertyType "Status" ApplicationLayerAutomaticResponseConfigurationProperty = Value Prelude.Text
set :: PropertyType
"Status" ApplicationLayerAutomaticResponseConfigurationProperty
-> ApplicationLayerAutomaticResponseConfigurationProperty
-> ApplicationLayerAutomaticResponseConfigurationProperty
set
PropertyType
"Status" ApplicationLayerAutomaticResponseConfigurationProperty
newValue
ApplicationLayerAutomaticResponseConfigurationProperty {()
Value Text
ActionProperty
haddock_workaround_ :: ApplicationLayerAutomaticResponseConfigurationProperty -> ()
action :: ApplicationLayerAutomaticResponseConfigurationProperty
-> ActionProperty
status :: ApplicationLayerAutomaticResponseConfigurationProperty
-> Value Text
haddock_workaround_ :: ()
action :: ActionProperty
status :: Value Text
..}
= ApplicationLayerAutomaticResponseConfigurationProperty
{status :: Value Text
status = PropertyType
"Status" ApplicationLayerAutomaticResponseConfigurationProperty
Value Text
newValue, ()
ActionProperty
haddock_workaround_ :: ()
action :: ActionProperty
haddock_workaround_ :: ()
action :: ActionProperty
..}