module Stratosphere.WAFv2.WebACL.CustomResponseBodyProperty (
CustomResponseBodyProperty(..), mkCustomResponseBodyProperty
) where
import qualified Data.Aeson as JSON
import qualified Stratosphere.Prelude as Prelude
import Stratosphere.Property
import Stratosphere.ResourceProperties
import Stratosphere.Value
data CustomResponseBodyProperty
=
CustomResponseBodyProperty {CustomResponseBodyProperty -> ()
haddock_workaround_ :: (),
CustomResponseBodyProperty -> Value Text
content :: (Value Prelude.Text),
CustomResponseBodyProperty -> Value Text
contentType :: (Value Prelude.Text)}
deriving stock (CustomResponseBodyProperty -> CustomResponseBodyProperty -> Bool
(CustomResponseBodyProperty -> CustomResponseBodyProperty -> Bool)
-> (CustomResponseBodyProperty
-> CustomResponseBodyProperty -> Bool)
-> Eq CustomResponseBodyProperty
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: CustomResponseBodyProperty -> CustomResponseBodyProperty -> Bool
== :: CustomResponseBodyProperty -> CustomResponseBodyProperty -> Bool
$c/= :: CustomResponseBodyProperty -> CustomResponseBodyProperty -> Bool
/= :: CustomResponseBodyProperty -> CustomResponseBodyProperty -> Bool
Prelude.Eq, Int -> CustomResponseBodyProperty -> ShowS
[CustomResponseBodyProperty] -> ShowS
CustomResponseBodyProperty -> String
(Int -> CustomResponseBodyProperty -> ShowS)
-> (CustomResponseBodyProperty -> String)
-> ([CustomResponseBodyProperty] -> ShowS)
-> Show CustomResponseBodyProperty
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> CustomResponseBodyProperty -> ShowS
showsPrec :: Int -> CustomResponseBodyProperty -> ShowS
$cshow :: CustomResponseBodyProperty -> String
show :: CustomResponseBodyProperty -> String
$cshowList :: [CustomResponseBodyProperty] -> ShowS
showList :: [CustomResponseBodyProperty] -> ShowS
Prelude.Show)
mkCustomResponseBodyProperty ::
Value Prelude.Text
-> Value Prelude.Text -> CustomResponseBodyProperty
mkCustomResponseBodyProperty :: Value Text -> Value Text -> CustomResponseBodyProperty
mkCustomResponseBodyProperty Value Text
content Value Text
contentType
= CustomResponseBodyProperty
{haddock_workaround_ :: ()
haddock_workaround_ = (), content :: Value Text
content = Value Text
content,
contentType :: Value Text
contentType = Value Text
contentType}
instance ToResourceProperties CustomResponseBodyProperty where
toResourceProperties :: CustomResponseBodyProperty -> ResourceProperties
toResourceProperties CustomResponseBodyProperty {()
Value Text
haddock_workaround_ :: CustomResponseBodyProperty -> ()
content :: CustomResponseBodyProperty -> Value Text
contentType :: CustomResponseBodyProperty -> Value Text
haddock_workaround_ :: ()
content :: Value Text
contentType :: Value Text
..}
= ResourceProperties
{awsType :: Text
awsType = Text
"AWS::WAFv2::WebACL.CustomResponseBody",
supportsTags :: Bool
supportsTags = Bool
Prelude.False,
properties :: Object
properties = [Key
"Content" 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
content,
Key
"ContentType" 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
contentType]}
instance JSON.ToJSON CustomResponseBodyProperty where
toJSON :: CustomResponseBodyProperty -> Value
toJSON CustomResponseBodyProperty {()
Value Text
haddock_workaround_ :: CustomResponseBodyProperty -> ()
content :: CustomResponseBodyProperty -> Value Text
contentType :: CustomResponseBodyProperty -> Value Text
haddock_workaround_ :: ()
content :: Value Text
contentType :: Value Text
..}
= [(Key, Value)] -> Value
JSON.object
[Key
"Content" 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
content, Key
"ContentType" 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
contentType]
instance Property "Content" CustomResponseBodyProperty where
type PropertyType "Content" CustomResponseBodyProperty = Value Prelude.Text
set :: PropertyType "Content" CustomResponseBodyProperty
-> CustomResponseBodyProperty -> CustomResponseBodyProperty
set PropertyType "Content" CustomResponseBodyProperty
newValue CustomResponseBodyProperty {()
Value Text
haddock_workaround_ :: CustomResponseBodyProperty -> ()
content :: CustomResponseBodyProperty -> Value Text
contentType :: CustomResponseBodyProperty -> Value Text
haddock_workaround_ :: ()
content :: Value Text
contentType :: Value Text
..}
= CustomResponseBodyProperty {content :: Value Text
content = PropertyType "Content" CustomResponseBodyProperty
Value Text
newValue, ()
Value Text
haddock_workaround_ :: ()
contentType :: Value Text
haddock_workaround_ :: ()
contentType :: Value Text
..}
instance Property "ContentType" CustomResponseBodyProperty where
type PropertyType "ContentType" CustomResponseBodyProperty = Value Prelude.Text
set :: PropertyType "ContentType" CustomResponseBodyProperty
-> CustomResponseBodyProperty -> CustomResponseBodyProperty
set PropertyType "ContentType" CustomResponseBodyProperty
newValue CustomResponseBodyProperty {()
Value Text
haddock_workaround_ :: CustomResponseBodyProperty -> ()
content :: CustomResponseBodyProperty -> Value Text
contentType :: CustomResponseBodyProperty -> Value Text
haddock_workaround_ :: ()
content :: Value Text
contentType :: Value Text
..}
= CustomResponseBodyProperty {contentType :: Value Text
contentType = PropertyType "ContentType" CustomResponseBodyProperty
Value Text
newValue, ()
Value Text
haddock_workaround_ :: ()
content :: Value Text
haddock_workaround_ :: ()
content :: Value Text
..}