module Stratosphere.CloudFormation.HookTypeConfig (
HookTypeConfig(..), mkHookTypeConfig
) where
import qualified Data.Aeson as JSON
import qualified Stratosphere.Prelude as Prelude
import Stratosphere.Property
import Stratosphere.ResourceProperties
import Stratosphere.Value
data HookTypeConfig
=
HookTypeConfig {HookTypeConfig -> ()
haddock_workaround_ :: (),
HookTypeConfig -> Value Text
configuration :: (Value Prelude.Text),
HookTypeConfig -> Maybe (Value Text)
configurationAlias :: (Prelude.Maybe (Value Prelude.Text)),
HookTypeConfig -> Maybe (Value Text)
typeArn :: (Prelude.Maybe (Value Prelude.Text)),
HookTypeConfig -> Maybe (Value Text)
typeName :: (Prelude.Maybe (Value Prelude.Text))}
deriving stock (HookTypeConfig -> HookTypeConfig -> Bool
(HookTypeConfig -> HookTypeConfig -> Bool)
-> (HookTypeConfig -> HookTypeConfig -> Bool) -> Eq HookTypeConfig
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: HookTypeConfig -> HookTypeConfig -> Bool
== :: HookTypeConfig -> HookTypeConfig -> Bool
$c/= :: HookTypeConfig -> HookTypeConfig -> Bool
/= :: HookTypeConfig -> HookTypeConfig -> Bool
Prelude.Eq, Int -> HookTypeConfig -> ShowS
[HookTypeConfig] -> ShowS
HookTypeConfig -> String
(Int -> HookTypeConfig -> ShowS)
-> (HookTypeConfig -> String)
-> ([HookTypeConfig] -> ShowS)
-> Show HookTypeConfig
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> HookTypeConfig -> ShowS
showsPrec :: Int -> HookTypeConfig -> ShowS
$cshow :: HookTypeConfig -> String
show :: HookTypeConfig -> String
$cshowList :: [HookTypeConfig] -> ShowS
showList :: [HookTypeConfig] -> ShowS
Prelude.Show)
mkHookTypeConfig :: Value Prelude.Text -> HookTypeConfig
mkHookTypeConfig :: Value Text -> HookTypeConfig
mkHookTypeConfig Value Text
configuration
= HookTypeConfig
{haddock_workaround_ :: ()
haddock_workaround_ = (), configuration :: Value Text
configuration = Value Text
configuration,
configurationAlias :: Maybe (Value Text)
configurationAlias = Maybe (Value Text)
forall a. Maybe a
Prelude.Nothing, typeArn :: Maybe (Value Text)
typeArn = Maybe (Value Text)
forall a. Maybe a
Prelude.Nothing,
typeName :: Maybe (Value Text)
typeName = Maybe (Value Text)
forall a. Maybe a
Prelude.Nothing}
instance ToResourceProperties HookTypeConfig where
toResourceProperties :: HookTypeConfig -> ResourceProperties
toResourceProperties HookTypeConfig {Maybe (Value Text)
()
Value Text
haddock_workaround_ :: HookTypeConfig -> ()
configuration :: HookTypeConfig -> Value Text
configurationAlias :: HookTypeConfig -> Maybe (Value Text)
typeArn :: HookTypeConfig -> Maybe (Value Text)
typeName :: HookTypeConfig -> Maybe (Value Text)
haddock_workaround_ :: ()
configuration :: Value Text
configurationAlias :: Maybe (Value Text)
typeArn :: Maybe (Value Text)
typeName :: Maybe (Value Text)
..}
= ResourceProperties
{awsType :: Text
awsType = Text
"AWS::CloudFormation::HookTypeConfig",
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
"Configuration" 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
configuration]
([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
"ConfigurationAlias" (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)
configurationAlias,
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
"TypeArn" (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)
typeArn,
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
"TypeName" (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)
typeName]))}
instance JSON.ToJSON HookTypeConfig where
toJSON :: HookTypeConfig -> Value
toJSON HookTypeConfig {Maybe (Value Text)
()
Value Text
haddock_workaround_ :: HookTypeConfig -> ()
configuration :: HookTypeConfig -> Value Text
configurationAlias :: HookTypeConfig -> Maybe (Value Text)
typeArn :: HookTypeConfig -> Maybe (Value Text)
typeName :: HookTypeConfig -> Maybe (Value Text)
haddock_workaround_ :: ()
configuration :: Value Text
configurationAlias :: Maybe (Value Text)
typeArn :: Maybe (Value Text)
typeName :: Maybe (Value Text)
..}
= [(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
"Configuration" 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
configuration]
([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
"ConfigurationAlias" (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)
configurationAlias,
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
"TypeArn" (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)
typeArn,
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
"TypeName" (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)
typeName])))
instance Property "Configuration" HookTypeConfig where
type PropertyType "Configuration" HookTypeConfig = Value Prelude.Text
set :: PropertyType "Configuration" HookTypeConfig
-> HookTypeConfig -> HookTypeConfig
set PropertyType "Configuration" HookTypeConfig
newValue HookTypeConfig {Maybe (Value Text)
()
Value Text
haddock_workaround_ :: HookTypeConfig -> ()
configuration :: HookTypeConfig -> Value Text
configurationAlias :: HookTypeConfig -> Maybe (Value Text)
typeArn :: HookTypeConfig -> Maybe (Value Text)
typeName :: HookTypeConfig -> Maybe (Value Text)
haddock_workaround_ :: ()
configuration :: Value Text
configurationAlias :: Maybe (Value Text)
typeArn :: Maybe (Value Text)
typeName :: Maybe (Value Text)
..}
= HookTypeConfig {configuration :: Value Text
configuration = PropertyType "Configuration" HookTypeConfig
Value Text
newValue, Maybe (Value Text)
()
haddock_workaround_ :: ()
configurationAlias :: Maybe (Value Text)
typeArn :: Maybe (Value Text)
typeName :: Maybe (Value Text)
haddock_workaround_ :: ()
configurationAlias :: Maybe (Value Text)
typeArn :: Maybe (Value Text)
typeName :: Maybe (Value Text)
..}
instance Property "ConfigurationAlias" HookTypeConfig where
type PropertyType "ConfigurationAlias" HookTypeConfig = Value Prelude.Text
set :: PropertyType "ConfigurationAlias" HookTypeConfig
-> HookTypeConfig -> HookTypeConfig
set PropertyType "ConfigurationAlias" HookTypeConfig
newValue HookTypeConfig {Maybe (Value Text)
()
Value Text
haddock_workaround_ :: HookTypeConfig -> ()
configuration :: HookTypeConfig -> Value Text
configurationAlias :: HookTypeConfig -> Maybe (Value Text)
typeArn :: HookTypeConfig -> Maybe (Value Text)
typeName :: HookTypeConfig -> Maybe (Value Text)
haddock_workaround_ :: ()
configuration :: Value Text
configurationAlias :: Maybe (Value Text)
typeArn :: Maybe (Value Text)
typeName :: Maybe (Value Text)
..}
= HookTypeConfig {configurationAlias :: Maybe (Value Text)
configurationAlias = Value Text -> Maybe (Value Text)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "ConfigurationAlias" HookTypeConfig
Value Text
newValue, Maybe (Value Text)
()
Value Text
haddock_workaround_ :: ()
configuration :: Value Text
typeArn :: Maybe (Value Text)
typeName :: Maybe (Value Text)
haddock_workaround_ :: ()
configuration :: Value Text
typeArn :: Maybe (Value Text)
typeName :: Maybe (Value Text)
..}
instance Property "TypeArn" HookTypeConfig where
type PropertyType "TypeArn" HookTypeConfig = Value Prelude.Text
set :: PropertyType "TypeArn" HookTypeConfig
-> HookTypeConfig -> HookTypeConfig
set PropertyType "TypeArn" HookTypeConfig
newValue HookTypeConfig {Maybe (Value Text)
()
Value Text
haddock_workaround_ :: HookTypeConfig -> ()
configuration :: HookTypeConfig -> Value Text
configurationAlias :: HookTypeConfig -> Maybe (Value Text)
typeArn :: HookTypeConfig -> Maybe (Value Text)
typeName :: HookTypeConfig -> Maybe (Value Text)
haddock_workaround_ :: ()
configuration :: Value Text
configurationAlias :: Maybe (Value Text)
typeArn :: Maybe (Value Text)
typeName :: Maybe (Value Text)
..}
= HookTypeConfig {typeArn :: Maybe (Value Text)
typeArn = Value Text -> Maybe (Value Text)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "TypeArn" HookTypeConfig
Value Text
newValue, Maybe (Value Text)
()
Value Text
haddock_workaround_ :: ()
configuration :: Value Text
configurationAlias :: Maybe (Value Text)
typeName :: Maybe (Value Text)
haddock_workaround_ :: ()
configuration :: Value Text
configurationAlias :: Maybe (Value Text)
typeName :: Maybe (Value Text)
..}
instance Property "TypeName" HookTypeConfig where
type PropertyType "TypeName" HookTypeConfig = Value Prelude.Text
set :: PropertyType "TypeName" HookTypeConfig
-> HookTypeConfig -> HookTypeConfig
set PropertyType "TypeName" HookTypeConfig
newValue HookTypeConfig {Maybe (Value Text)
()
Value Text
haddock_workaround_ :: HookTypeConfig -> ()
configuration :: HookTypeConfig -> Value Text
configurationAlias :: HookTypeConfig -> Maybe (Value Text)
typeArn :: HookTypeConfig -> Maybe (Value Text)
typeName :: HookTypeConfig -> Maybe (Value Text)
haddock_workaround_ :: ()
configuration :: Value Text
configurationAlias :: Maybe (Value Text)
typeArn :: Maybe (Value Text)
typeName :: Maybe (Value Text)
..}
= HookTypeConfig {typeName :: Maybe (Value Text)
typeName = Value Text -> Maybe (Value Text)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "TypeName" HookTypeConfig
Value Text
newValue, Maybe (Value Text)
()
Value Text
haddock_workaround_ :: ()
configuration :: Value Text
configurationAlias :: Maybe (Value Text)
typeArn :: Maybe (Value Text)
haddock_workaround_ :: ()
configuration :: Value Text
configurationAlias :: Maybe (Value Text)
typeArn :: Maybe (Value Text)
..}