module Stratosphere.WAFv2.WebACL.CustomResponseProperty (
module Exports, CustomResponseProperty(..),
mkCustomResponseProperty
) where
import qualified Data.Aeson as JSON
import qualified Stratosphere.Prelude as Prelude
import Stratosphere.Property
import {-# SOURCE #-} Stratosphere.WAFv2.WebACL.CustomHTTPHeaderProperty as Exports
import Stratosphere.ResourceProperties
import Stratosphere.Value
data CustomResponseProperty
=
CustomResponseProperty {CustomResponseProperty -> ()
haddock_workaround_ :: (),
CustomResponseProperty -> Maybe (Value Text)
customResponseBodyKey :: (Prelude.Maybe (Value Prelude.Text)),
CustomResponseProperty -> Value Integer
responseCode :: (Value Prelude.Integer),
:: (Prelude.Maybe [CustomHTTPHeaderProperty])}
deriving stock (CustomResponseProperty -> CustomResponseProperty -> Bool
(CustomResponseProperty -> CustomResponseProperty -> Bool)
-> (CustomResponseProperty -> CustomResponseProperty -> Bool)
-> Eq CustomResponseProperty
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: CustomResponseProperty -> CustomResponseProperty -> Bool
== :: CustomResponseProperty -> CustomResponseProperty -> Bool
$c/= :: CustomResponseProperty -> CustomResponseProperty -> Bool
/= :: CustomResponseProperty -> CustomResponseProperty -> Bool
Prelude.Eq, Int -> CustomResponseProperty -> ShowS
[CustomResponseProperty] -> ShowS
CustomResponseProperty -> String
(Int -> CustomResponseProperty -> ShowS)
-> (CustomResponseProperty -> String)
-> ([CustomResponseProperty] -> ShowS)
-> Show CustomResponseProperty
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> CustomResponseProperty -> ShowS
showsPrec :: Int -> CustomResponseProperty -> ShowS
$cshow :: CustomResponseProperty -> String
show :: CustomResponseProperty -> String
$cshowList :: [CustomResponseProperty] -> ShowS
showList :: [CustomResponseProperty] -> ShowS
Prelude.Show)
mkCustomResponseProperty ::
Value Prelude.Integer -> CustomResponseProperty
mkCustomResponseProperty :: Value Integer -> CustomResponseProperty
mkCustomResponseProperty Value Integer
responseCode
= CustomResponseProperty
{haddock_workaround_ :: ()
haddock_workaround_ = (), responseCode :: Value Integer
responseCode = Value Integer
responseCode,
customResponseBodyKey :: Maybe (Value Text)
customResponseBodyKey = Maybe (Value Text)
forall a. Maybe a
Prelude.Nothing,
responseHeaders :: Maybe [CustomHTTPHeaderProperty]
responseHeaders = Maybe [CustomHTTPHeaderProperty]
forall a. Maybe a
Prelude.Nothing}
instance ToResourceProperties CustomResponseProperty where
toResourceProperties :: CustomResponseProperty -> ResourceProperties
toResourceProperties CustomResponseProperty {Maybe [CustomHTTPHeaderProperty]
Maybe (Value Text)
()
Value Integer
haddock_workaround_ :: CustomResponseProperty -> ()
customResponseBodyKey :: CustomResponseProperty -> Maybe (Value Text)
responseCode :: CustomResponseProperty -> Value Integer
responseHeaders :: CustomResponseProperty -> Maybe [CustomHTTPHeaderProperty]
haddock_workaround_ :: ()
customResponseBodyKey :: Maybe (Value Text)
responseCode :: Value Integer
responseHeaders :: Maybe [CustomHTTPHeaderProperty]
..}
= ResourceProperties
{awsType :: Text
awsType = Text
"AWS::WAFv2::WebACL.CustomResponse",
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
"ResponseCode" 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
responseCode]
([Maybe (Key, Value)] -> [(Key, Value)]
forall a. [Maybe a] -> [a]
Prelude.catMaybes
[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..=) Key
"CustomResponseBodyKey"
(Value Text -> (Key, Value))
-> Maybe (Value Text) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Text)
customResponseBodyKey,
Key -> [CustomHTTPHeaderProperty] -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"ResponseHeaders" ([CustomHTTPHeaderProperty] -> (Key, Value))
-> Maybe [CustomHTTPHeaderProperty] -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [CustomHTTPHeaderProperty]
responseHeaders]))}
instance JSON.ToJSON CustomResponseProperty where
toJSON :: CustomResponseProperty -> Value
toJSON CustomResponseProperty {Maybe [CustomHTTPHeaderProperty]
Maybe (Value Text)
()
Value Integer
haddock_workaround_ :: CustomResponseProperty -> ()
customResponseBodyKey :: CustomResponseProperty -> Maybe (Value Text)
responseCode :: CustomResponseProperty -> Value Integer
responseHeaders :: CustomResponseProperty -> Maybe [CustomHTTPHeaderProperty]
haddock_workaround_ :: ()
customResponseBodyKey :: Maybe (Value Text)
responseCode :: Value Integer
responseHeaders :: Maybe [CustomHTTPHeaderProperty]
..}
= [(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
"ResponseCode" 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
responseCode]
([Maybe (Key, Value)] -> [(Key, Value)]
forall a. [Maybe a] -> [a]
Prelude.catMaybes
[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..=) Key
"CustomResponseBodyKey"
(Value Text -> (Key, Value))
-> Maybe (Value Text) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Text)
customResponseBodyKey,
Key -> [CustomHTTPHeaderProperty] -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"ResponseHeaders" ([CustomHTTPHeaderProperty] -> (Key, Value))
-> Maybe [CustomHTTPHeaderProperty] -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [CustomHTTPHeaderProperty]
responseHeaders])))
instance Property "CustomResponseBodyKey" CustomResponseProperty where
type PropertyType "CustomResponseBodyKey" CustomResponseProperty = Value Prelude.Text
set :: PropertyType "CustomResponseBodyKey" CustomResponseProperty
-> CustomResponseProperty -> CustomResponseProperty
set PropertyType "CustomResponseBodyKey" CustomResponseProperty
newValue CustomResponseProperty {Maybe [CustomHTTPHeaderProperty]
Maybe (Value Text)
()
Value Integer
haddock_workaround_ :: CustomResponseProperty -> ()
customResponseBodyKey :: CustomResponseProperty -> Maybe (Value Text)
responseCode :: CustomResponseProperty -> Value Integer
responseHeaders :: CustomResponseProperty -> Maybe [CustomHTTPHeaderProperty]
haddock_workaround_ :: ()
customResponseBodyKey :: Maybe (Value Text)
responseCode :: Value Integer
responseHeaders :: Maybe [CustomHTTPHeaderProperty]
..}
= CustomResponseProperty
{customResponseBodyKey :: Maybe (Value Text)
customResponseBodyKey = Value Text -> Maybe (Value Text)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "CustomResponseBodyKey" CustomResponseProperty
Value Text
newValue, Maybe [CustomHTTPHeaderProperty]
()
Value Integer
haddock_workaround_ :: ()
responseCode :: Value Integer
responseHeaders :: Maybe [CustomHTTPHeaderProperty]
haddock_workaround_ :: ()
responseCode :: Value Integer
responseHeaders :: Maybe [CustomHTTPHeaderProperty]
..}
instance Property "ResponseCode" CustomResponseProperty where
type PropertyType "ResponseCode" CustomResponseProperty = Value Prelude.Integer
set :: PropertyType "ResponseCode" CustomResponseProperty
-> CustomResponseProperty -> CustomResponseProperty
set PropertyType "ResponseCode" CustomResponseProperty
newValue CustomResponseProperty {Maybe [CustomHTTPHeaderProperty]
Maybe (Value Text)
()
Value Integer
haddock_workaround_ :: CustomResponseProperty -> ()
customResponseBodyKey :: CustomResponseProperty -> Maybe (Value Text)
responseCode :: CustomResponseProperty -> Value Integer
responseHeaders :: CustomResponseProperty -> Maybe [CustomHTTPHeaderProperty]
haddock_workaround_ :: ()
customResponseBodyKey :: Maybe (Value Text)
responseCode :: Value Integer
responseHeaders :: Maybe [CustomHTTPHeaderProperty]
..}
= CustomResponseProperty {responseCode :: Value Integer
responseCode = PropertyType "ResponseCode" CustomResponseProperty
Value Integer
newValue, Maybe [CustomHTTPHeaderProperty]
Maybe (Value Text)
()
haddock_workaround_ :: ()
customResponseBodyKey :: Maybe (Value Text)
responseHeaders :: Maybe [CustomHTTPHeaderProperty]
haddock_workaround_ :: ()
customResponseBodyKey :: Maybe (Value Text)
responseHeaders :: Maybe [CustomHTTPHeaderProperty]
..}
instance Property "ResponseHeaders" CustomResponseProperty where
type PropertyType "ResponseHeaders" CustomResponseProperty = [CustomHTTPHeaderProperty]
set :: PropertyType "ResponseHeaders" CustomResponseProperty
-> CustomResponseProperty -> CustomResponseProperty
set PropertyType "ResponseHeaders" CustomResponseProperty
newValue CustomResponseProperty {Maybe [CustomHTTPHeaderProperty]
Maybe (Value Text)
()
Value Integer
haddock_workaround_ :: CustomResponseProperty -> ()
customResponseBodyKey :: CustomResponseProperty -> Maybe (Value Text)
responseCode :: CustomResponseProperty -> Value Integer
responseHeaders :: CustomResponseProperty -> Maybe [CustomHTTPHeaderProperty]
haddock_workaround_ :: ()
customResponseBodyKey :: Maybe (Value Text)
responseCode :: Value Integer
responseHeaders :: Maybe [CustomHTTPHeaderProperty]
..}
= CustomResponseProperty
{responseHeaders :: Maybe [CustomHTTPHeaderProperty]
responseHeaders = [CustomHTTPHeaderProperty] -> Maybe [CustomHTTPHeaderProperty]
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure [CustomHTTPHeaderProperty]
PropertyType "ResponseHeaders" CustomResponseProperty
newValue, Maybe (Value Text)
()
Value Integer
haddock_workaround_ :: ()
customResponseBodyKey :: Maybe (Value Text)
responseCode :: Value Integer
haddock_workaround_ :: ()
customResponseBodyKey :: Maybe (Value Text)
responseCode :: Value Integer
..}