module Stratosphere.OpsWorks.Stack (
module Exports, Stack(..), mkStack
) where
import qualified Data.Aeson as JSON
import qualified Stratosphere.Prelude as Prelude
import Stratosphere.Property
import {-# SOURCE #-} Stratosphere.OpsWorks.Stack.ChefConfigurationProperty as Exports
import {-# SOURCE #-} Stratosphere.OpsWorks.Stack.ElasticIpProperty as Exports
import {-# SOURCE #-} Stratosphere.OpsWorks.Stack.RdsDbInstanceProperty as Exports
import {-# SOURCE #-} Stratosphere.OpsWorks.Stack.SourceProperty as Exports
import {-# SOURCE #-} Stratosphere.OpsWorks.Stack.StackConfigurationManagerProperty as Exports
import Stratosphere.ResourceProperties
import Stratosphere.Tag
import Stratosphere.Value
data Stack
=
Stack {Stack -> ()
haddock_workaround_ :: (),
Stack -> Maybe (Value Text)
agentVersion :: (Prelude.Maybe (Value Prelude.Text)),
Stack -> Maybe (Map Text (Value Text))
attributes :: (Prelude.Maybe (Prelude.Map Prelude.Text (Value Prelude.Text))),
Stack -> Maybe ChefConfigurationProperty
chefConfiguration :: (Prelude.Maybe ChefConfigurationProperty),
Stack -> Maybe (ValueList Text)
cloneAppIds :: (Prelude.Maybe (ValueList Prelude.Text)),
Stack -> Maybe (Value Bool)
clonePermissions :: (Prelude.Maybe (Value Prelude.Bool)),
Stack -> Maybe StackConfigurationManagerProperty
configurationManager :: (Prelude.Maybe StackConfigurationManagerProperty),
Stack -> Maybe SourceProperty
customCookbooksSource :: (Prelude.Maybe SourceProperty),
Stack -> Maybe Object
customJson :: (Prelude.Maybe JSON.Object),
Stack -> Maybe (Value Text)
defaultAvailabilityZone :: (Prelude.Maybe (Value Prelude.Text)),
Stack -> Value Text
defaultInstanceProfileArn :: (Value Prelude.Text),
Stack -> Maybe (Value Text)
defaultOs :: (Prelude.Maybe (Value Prelude.Text)),
Stack -> Maybe (Value Text)
defaultRootDeviceType :: (Prelude.Maybe (Value Prelude.Text)),
Stack -> Maybe (Value Text)
defaultSshKeyName :: (Prelude.Maybe (Value Prelude.Text)),
Stack -> Maybe (Value Text)
defaultSubnetId :: (Prelude.Maybe (Value Prelude.Text)),
Stack -> Maybe (Value Text)
ecsClusterArn :: (Prelude.Maybe (Value Prelude.Text)),
Stack -> Maybe [ElasticIpProperty]
elasticIps :: (Prelude.Maybe [ElasticIpProperty]),
Stack -> Maybe (Value Text)
hostnameTheme :: (Prelude.Maybe (Value Prelude.Text)),
Stack -> Value Text
name :: (Value Prelude.Text),
Stack -> Maybe [RdsDbInstanceProperty]
rdsDbInstances :: (Prelude.Maybe [RdsDbInstanceProperty]),
Stack -> Value Text
serviceRoleArn :: (Value Prelude.Text),
Stack -> Maybe (Value Text)
sourceStackId :: (Prelude.Maybe (Value Prelude.Text)),
Stack -> Maybe [Tag]
tags :: (Prelude.Maybe [Tag]),
Stack -> Maybe (Value Bool)
useCustomCookbooks :: (Prelude.Maybe (Value Prelude.Bool)),
Stack -> Maybe (Value Bool)
useOpsworksSecurityGroups :: (Prelude.Maybe (Value Prelude.Bool)),
Stack -> Maybe (Value Text)
vpcId :: (Prelude.Maybe (Value Prelude.Text))}
deriving stock (Stack -> Stack -> Bool
(Stack -> Stack -> Bool) -> (Stack -> Stack -> Bool) -> Eq Stack
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Stack -> Stack -> Bool
== :: Stack -> Stack -> Bool
$c/= :: Stack -> Stack -> Bool
/= :: Stack -> Stack -> Bool
Prelude.Eq, Int -> Stack -> ShowS
[Stack] -> ShowS
Stack -> String
(Int -> Stack -> ShowS)
-> (Stack -> String) -> ([Stack] -> ShowS) -> Show Stack
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Stack -> ShowS
showsPrec :: Int -> Stack -> ShowS
$cshow :: Stack -> String
show :: Stack -> String
$cshowList :: [Stack] -> ShowS
showList :: [Stack] -> ShowS
Prelude.Show)
mkStack ::
Value Prelude.Text
-> Value Prelude.Text -> Value Prelude.Text -> Stack
mkStack :: Value Text -> Value Text -> Value Text -> Stack
mkStack Value Text
defaultInstanceProfileArn Value Text
name Value Text
serviceRoleArn
= Stack
{haddock_workaround_ :: ()
haddock_workaround_ = (),
defaultInstanceProfileArn :: Value Text
defaultInstanceProfileArn = Value Text
defaultInstanceProfileArn, name :: Value Text
name = Value Text
name,
serviceRoleArn :: Value Text
serviceRoleArn = Value Text
serviceRoleArn, agentVersion :: Maybe (Value Text)
agentVersion = Maybe (Value Text)
forall a. Maybe a
Prelude.Nothing,
attributes :: Maybe (Map Text (Value Text))
attributes = Maybe (Map Text (Value Text))
forall a. Maybe a
Prelude.Nothing, chefConfiguration :: Maybe ChefConfigurationProperty
chefConfiguration = Maybe ChefConfigurationProperty
forall a. Maybe a
Prelude.Nothing,
cloneAppIds :: Maybe (ValueList Text)
cloneAppIds = Maybe (ValueList Text)
forall a. Maybe a
Prelude.Nothing, clonePermissions :: Maybe (Value Bool)
clonePermissions = Maybe (Value Bool)
forall a. Maybe a
Prelude.Nothing,
configurationManager :: Maybe StackConfigurationManagerProperty
configurationManager = Maybe StackConfigurationManagerProperty
forall a. Maybe a
Prelude.Nothing,
customCookbooksSource :: Maybe SourceProperty
customCookbooksSource = Maybe SourceProperty
forall a. Maybe a
Prelude.Nothing,
customJson :: Maybe Object
customJson = Maybe Object
forall a. Maybe a
Prelude.Nothing,
defaultAvailabilityZone :: Maybe (Value Text)
defaultAvailabilityZone = Maybe (Value Text)
forall a. Maybe a
Prelude.Nothing,
defaultOs :: Maybe (Value Text)
defaultOs = Maybe (Value Text)
forall a. Maybe a
Prelude.Nothing,
defaultRootDeviceType :: Maybe (Value Text)
defaultRootDeviceType = Maybe (Value Text)
forall a. Maybe a
Prelude.Nothing,
defaultSshKeyName :: Maybe (Value Text)
defaultSshKeyName = Maybe (Value Text)
forall a. Maybe a
Prelude.Nothing,
defaultSubnetId :: Maybe (Value Text)
defaultSubnetId = Maybe (Value Text)
forall a. Maybe a
Prelude.Nothing, ecsClusterArn :: Maybe (Value Text)
ecsClusterArn = Maybe (Value Text)
forall a. Maybe a
Prelude.Nothing,
elasticIps :: Maybe [ElasticIpProperty]
elasticIps = Maybe [ElasticIpProperty]
forall a. Maybe a
Prelude.Nothing, hostnameTheme :: Maybe (Value Text)
hostnameTheme = Maybe (Value Text)
forall a. Maybe a
Prelude.Nothing,
rdsDbInstances :: Maybe [RdsDbInstanceProperty]
rdsDbInstances = Maybe [RdsDbInstanceProperty]
forall a. Maybe a
Prelude.Nothing, sourceStackId :: Maybe (Value Text)
sourceStackId = Maybe (Value Text)
forall a. Maybe a
Prelude.Nothing,
tags :: Maybe [Tag]
tags = Maybe [Tag]
forall a. Maybe a
Prelude.Nothing, useCustomCookbooks :: Maybe (Value Bool)
useCustomCookbooks = Maybe (Value Bool)
forall a. Maybe a
Prelude.Nothing,
useOpsworksSecurityGroups :: Maybe (Value Bool)
useOpsworksSecurityGroups = Maybe (Value Bool)
forall a. Maybe a
Prelude.Nothing,
vpcId :: Maybe (Value Text)
vpcId = Maybe (Value Text)
forall a. Maybe a
Prelude.Nothing}
instance ToResourceProperties Stack where
toResourceProperties :: Stack -> ResourceProperties
toResourceProperties Stack {Maybe [Tag]
Maybe [ElasticIpProperty]
Maybe [RdsDbInstanceProperty]
Maybe Object
Maybe (Map Text (Value Text))
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Text)
Maybe ChefConfigurationProperty
Maybe SourceProperty
Maybe StackConfigurationManagerProperty
()
Value Text
haddock_workaround_ :: Stack -> ()
agentVersion :: Stack -> Maybe (Value Text)
attributes :: Stack -> Maybe (Map Text (Value Text))
chefConfiguration :: Stack -> Maybe ChefConfigurationProperty
cloneAppIds :: Stack -> Maybe (ValueList Text)
clonePermissions :: Stack -> Maybe (Value Bool)
configurationManager :: Stack -> Maybe StackConfigurationManagerProperty
customCookbooksSource :: Stack -> Maybe SourceProperty
customJson :: Stack -> Maybe Object
defaultAvailabilityZone :: Stack -> Maybe (Value Text)
defaultInstanceProfileArn :: Stack -> Value Text
defaultOs :: Stack -> Maybe (Value Text)
defaultRootDeviceType :: Stack -> Maybe (Value Text)
defaultSshKeyName :: Stack -> Maybe (Value Text)
defaultSubnetId :: Stack -> Maybe (Value Text)
ecsClusterArn :: Stack -> Maybe (Value Text)
elasticIps :: Stack -> Maybe [ElasticIpProperty]
hostnameTheme :: Stack -> Maybe (Value Text)
name :: Stack -> Value Text
rdsDbInstances :: Stack -> Maybe [RdsDbInstanceProperty]
serviceRoleArn :: Stack -> Value Text
sourceStackId :: Stack -> Maybe (Value Text)
tags :: Stack -> Maybe [Tag]
useCustomCookbooks :: Stack -> Maybe (Value Bool)
useOpsworksSecurityGroups :: Stack -> Maybe (Value Bool)
vpcId :: Stack -> Maybe (Value Text)
haddock_workaround_ :: ()
agentVersion :: Maybe (Value Text)
attributes :: Maybe (Map Text (Value Text))
chefConfiguration :: Maybe ChefConfigurationProperty
cloneAppIds :: Maybe (ValueList Text)
clonePermissions :: Maybe (Value Bool)
configurationManager :: Maybe StackConfigurationManagerProperty
customCookbooksSource :: Maybe SourceProperty
customJson :: Maybe Object
defaultAvailabilityZone :: Maybe (Value Text)
defaultInstanceProfileArn :: Value Text
defaultOs :: Maybe (Value Text)
defaultRootDeviceType :: Maybe (Value Text)
defaultSshKeyName :: Maybe (Value Text)
defaultSubnetId :: Maybe (Value Text)
ecsClusterArn :: Maybe (Value Text)
elasticIps :: Maybe [ElasticIpProperty]
hostnameTheme :: Maybe (Value Text)
name :: Value Text
rdsDbInstances :: Maybe [RdsDbInstanceProperty]
serviceRoleArn :: Value Text
sourceStackId :: Maybe (Value Text)
tags :: Maybe [Tag]
useCustomCookbooks :: Maybe (Value Bool)
useOpsworksSecurityGroups :: Maybe (Value Bool)
vpcId :: Maybe (Value Text)
..}
= ResourceProperties
{awsType :: Text
awsType = Text
"AWS::OpsWorks::Stack", supportsTags :: Bool
supportsTags = Bool
Prelude.True,
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
"DefaultInstanceProfileArn" 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
defaultInstanceProfileArn,
Key
"Name" 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
name, Key
"ServiceRoleArn" 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
serviceRoleArn]
([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
"AgentVersion" (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)
agentVersion,
Key -> Map Text (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
"Attributes" (Map Text (Value Text) -> (Key, Value))
-> Maybe (Map Text (Value Text)) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Map Text (Value Text))
attributes,
Key -> ChefConfigurationProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"ChefConfiguration" (ChefConfigurationProperty -> (Key, Value))
-> Maybe ChefConfigurationProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe ChefConfigurationProperty
chefConfiguration,
Key -> ValueList 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
"CloneAppIds" (ValueList Text -> (Key, Value))
-> Maybe (ValueList Text) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (ValueList Text)
cloneAppIds,
Key -> Value Bool -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"ClonePermissions" (Value Bool -> (Key, Value))
-> Maybe (Value Bool) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Bool)
clonePermissions,
Key -> StackConfigurationManagerProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"ConfigurationManager" (StackConfigurationManagerProperty -> (Key, Value))
-> Maybe StackConfigurationManagerProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe StackConfigurationManagerProperty
configurationManager,
Key -> SourceProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"CustomCookbooksSource"
(SourceProperty -> (Key, Value))
-> Maybe SourceProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe SourceProperty
customCookbooksSource,
Key -> Object -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"CustomJson" (Object -> (Key, Value)) -> Maybe Object -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Object
customJson,
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
"DefaultAvailabilityZone"
(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)
defaultAvailabilityZone,
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
"DefaultOs" (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)
defaultOs,
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
"DefaultRootDeviceType"
(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)
defaultRootDeviceType,
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
"DefaultSshKeyName" (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)
defaultSshKeyName,
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
"DefaultSubnetId" (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)
defaultSubnetId,
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
"EcsClusterArn" (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)
ecsClusterArn,
Key -> [ElasticIpProperty] -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"ElasticIps" ([ElasticIpProperty] -> (Key, Value))
-> Maybe [ElasticIpProperty] -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [ElasticIpProperty]
elasticIps,
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
"HostnameTheme" (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)
hostnameTheme,
Key -> [RdsDbInstanceProperty] -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"RdsDbInstances" ([RdsDbInstanceProperty] -> (Key, Value))
-> Maybe [RdsDbInstanceProperty] -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [RdsDbInstanceProperty]
rdsDbInstances,
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
"SourceStackId" (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)
sourceStackId,
Key -> [Tag] -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"Tags" ([Tag] -> (Key, Value)) -> Maybe [Tag] -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [Tag]
tags,
Key -> Value Bool -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"UseCustomCookbooks" (Value Bool -> (Key, Value))
-> Maybe (Value Bool) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Bool)
useCustomCookbooks,
Key -> Value Bool -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"UseOpsworksSecurityGroups"
(Value Bool -> (Key, Value))
-> Maybe (Value Bool) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Bool)
useOpsworksSecurityGroups,
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
"VpcId" (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)
vpcId]))}
instance JSON.ToJSON Stack where
toJSON :: Stack -> Value
toJSON Stack {Maybe [Tag]
Maybe [ElasticIpProperty]
Maybe [RdsDbInstanceProperty]
Maybe Object
Maybe (Map Text (Value Text))
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Text)
Maybe ChefConfigurationProperty
Maybe SourceProperty
Maybe StackConfigurationManagerProperty
()
Value Text
haddock_workaround_ :: Stack -> ()
agentVersion :: Stack -> Maybe (Value Text)
attributes :: Stack -> Maybe (Map Text (Value Text))
chefConfiguration :: Stack -> Maybe ChefConfigurationProperty
cloneAppIds :: Stack -> Maybe (ValueList Text)
clonePermissions :: Stack -> Maybe (Value Bool)
configurationManager :: Stack -> Maybe StackConfigurationManagerProperty
customCookbooksSource :: Stack -> Maybe SourceProperty
customJson :: Stack -> Maybe Object
defaultAvailabilityZone :: Stack -> Maybe (Value Text)
defaultInstanceProfileArn :: Stack -> Value Text
defaultOs :: Stack -> Maybe (Value Text)
defaultRootDeviceType :: Stack -> Maybe (Value Text)
defaultSshKeyName :: Stack -> Maybe (Value Text)
defaultSubnetId :: Stack -> Maybe (Value Text)
ecsClusterArn :: Stack -> Maybe (Value Text)
elasticIps :: Stack -> Maybe [ElasticIpProperty]
hostnameTheme :: Stack -> Maybe (Value Text)
name :: Stack -> Value Text
rdsDbInstances :: Stack -> Maybe [RdsDbInstanceProperty]
serviceRoleArn :: Stack -> Value Text
sourceStackId :: Stack -> Maybe (Value Text)
tags :: Stack -> Maybe [Tag]
useCustomCookbooks :: Stack -> Maybe (Value Bool)
useOpsworksSecurityGroups :: Stack -> Maybe (Value Bool)
vpcId :: Stack -> Maybe (Value Text)
haddock_workaround_ :: ()
agentVersion :: Maybe (Value Text)
attributes :: Maybe (Map Text (Value Text))
chefConfiguration :: Maybe ChefConfigurationProperty
cloneAppIds :: Maybe (ValueList Text)
clonePermissions :: Maybe (Value Bool)
configurationManager :: Maybe StackConfigurationManagerProperty
customCookbooksSource :: Maybe SourceProperty
customJson :: Maybe Object
defaultAvailabilityZone :: Maybe (Value Text)
defaultInstanceProfileArn :: Value Text
defaultOs :: Maybe (Value Text)
defaultRootDeviceType :: Maybe (Value Text)
defaultSshKeyName :: Maybe (Value Text)
defaultSubnetId :: Maybe (Value Text)
ecsClusterArn :: Maybe (Value Text)
elasticIps :: Maybe [ElasticIpProperty]
hostnameTheme :: Maybe (Value Text)
name :: Value Text
rdsDbInstances :: Maybe [RdsDbInstanceProperty]
serviceRoleArn :: Value Text
sourceStackId :: Maybe (Value Text)
tags :: Maybe [Tag]
useCustomCookbooks :: Maybe (Value Bool)
useOpsworksSecurityGroups :: Maybe (Value Bool)
vpcId :: 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
"DefaultInstanceProfileArn" 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
defaultInstanceProfileArn,
Key
"Name" 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
name, Key
"ServiceRoleArn" 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
serviceRoleArn]
([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
"AgentVersion" (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)
agentVersion,
Key -> Map Text (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
"Attributes" (Map Text (Value Text) -> (Key, Value))
-> Maybe (Map Text (Value Text)) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Map Text (Value Text))
attributes,
Key -> ChefConfigurationProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"ChefConfiguration" (ChefConfigurationProperty -> (Key, Value))
-> Maybe ChefConfigurationProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe ChefConfigurationProperty
chefConfiguration,
Key -> ValueList 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
"CloneAppIds" (ValueList Text -> (Key, Value))
-> Maybe (ValueList Text) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (ValueList Text)
cloneAppIds,
Key -> Value Bool -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"ClonePermissions" (Value Bool -> (Key, Value))
-> Maybe (Value Bool) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Bool)
clonePermissions,
Key -> StackConfigurationManagerProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"ConfigurationManager" (StackConfigurationManagerProperty -> (Key, Value))
-> Maybe StackConfigurationManagerProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe StackConfigurationManagerProperty
configurationManager,
Key -> SourceProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"CustomCookbooksSource"
(SourceProperty -> (Key, Value))
-> Maybe SourceProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe SourceProperty
customCookbooksSource,
Key -> Object -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"CustomJson" (Object -> (Key, Value)) -> Maybe Object -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Object
customJson,
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
"DefaultAvailabilityZone"
(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)
defaultAvailabilityZone,
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
"DefaultOs" (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)
defaultOs,
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
"DefaultRootDeviceType"
(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)
defaultRootDeviceType,
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
"DefaultSshKeyName" (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)
defaultSshKeyName,
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
"DefaultSubnetId" (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)
defaultSubnetId,
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
"EcsClusterArn" (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)
ecsClusterArn,
Key -> [ElasticIpProperty] -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"ElasticIps" ([ElasticIpProperty] -> (Key, Value))
-> Maybe [ElasticIpProperty] -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [ElasticIpProperty]
elasticIps,
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
"HostnameTheme" (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)
hostnameTheme,
Key -> [RdsDbInstanceProperty] -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"RdsDbInstances" ([RdsDbInstanceProperty] -> (Key, Value))
-> Maybe [RdsDbInstanceProperty] -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [RdsDbInstanceProperty]
rdsDbInstances,
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
"SourceStackId" (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)
sourceStackId,
Key -> [Tag] -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"Tags" ([Tag] -> (Key, Value)) -> Maybe [Tag] -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [Tag]
tags,
Key -> Value Bool -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"UseCustomCookbooks" (Value Bool -> (Key, Value))
-> Maybe (Value Bool) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Bool)
useCustomCookbooks,
Key -> Value Bool -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"UseOpsworksSecurityGroups"
(Value Bool -> (Key, Value))
-> Maybe (Value Bool) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Bool)
useOpsworksSecurityGroups,
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
"VpcId" (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)
vpcId])))
instance Property "AgentVersion" Stack where
type PropertyType "AgentVersion" Stack = Value Prelude.Text
set :: PropertyType "AgentVersion" Stack -> Stack -> Stack
set PropertyType "AgentVersion" Stack
newValue Stack {Maybe [Tag]
Maybe [ElasticIpProperty]
Maybe [RdsDbInstanceProperty]
Maybe Object
Maybe (Map Text (Value Text))
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Text)
Maybe ChefConfigurationProperty
Maybe SourceProperty
Maybe StackConfigurationManagerProperty
()
Value Text
haddock_workaround_ :: Stack -> ()
agentVersion :: Stack -> Maybe (Value Text)
attributes :: Stack -> Maybe (Map Text (Value Text))
chefConfiguration :: Stack -> Maybe ChefConfigurationProperty
cloneAppIds :: Stack -> Maybe (ValueList Text)
clonePermissions :: Stack -> Maybe (Value Bool)
configurationManager :: Stack -> Maybe StackConfigurationManagerProperty
customCookbooksSource :: Stack -> Maybe SourceProperty
customJson :: Stack -> Maybe Object
defaultAvailabilityZone :: Stack -> Maybe (Value Text)
defaultInstanceProfileArn :: Stack -> Value Text
defaultOs :: Stack -> Maybe (Value Text)
defaultRootDeviceType :: Stack -> Maybe (Value Text)
defaultSshKeyName :: Stack -> Maybe (Value Text)
defaultSubnetId :: Stack -> Maybe (Value Text)
ecsClusterArn :: Stack -> Maybe (Value Text)
elasticIps :: Stack -> Maybe [ElasticIpProperty]
hostnameTheme :: Stack -> Maybe (Value Text)
name :: Stack -> Value Text
rdsDbInstances :: Stack -> Maybe [RdsDbInstanceProperty]
serviceRoleArn :: Stack -> Value Text
sourceStackId :: Stack -> Maybe (Value Text)
tags :: Stack -> Maybe [Tag]
useCustomCookbooks :: Stack -> Maybe (Value Bool)
useOpsworksSecurityGroups :: Stack -> Maybe (Value Bool)
vpcId :: Stack -> Maybe (Value Text)
haddock_workaround_ :: ()
agentVersion :: Maybe (Value Text)
attributes :: Maybe (Map Text (Value Text))
chefConfiguration :: Maybe ChefConfigurationProperty
cloneAppIds :: Maybe (ValueList Text)
clonePermissions :: Maybe (Value Bool)
configurationManager :: Maybe StackConfigurationManagerProperty
customCookbooksSource :: Maybe SourceProperty
customJson :: Maybe Object
defaultAvailabilityZone :: Maybe (Value Text)
defaultInstanceProfileArn :: Value Text
defaultOs :: Maybe (Value Text)
defaultRootDeviceType :: Maybe (Value Text)
defaultSshKeyName :: Maybe (Value Text)
defaultSubnetId :: Maybe (Value Text)
ecsClusterArn :: Maybe (Value Text)
elasticIps :: Maybe [ElasticIpProperty]
hostnameTheme :: Maybe (Value Text)
name :: Value Text
rdsDbInstances :: Maybe [RdsDbInstanceProperty]
serviceRoleArn :: Value Text
sourceStackId :: Maybe (Value Text)
tags :: Maybe [Tag]
useCustomCookbooks :: Maybe (Value Bool)
useOpsworksSecurityGroups :: Maybe (Value Bool)
vpcId :: Maybe (Value Text)
..}
= Stack {agentVersion :: Maybe (Value Text)
agentVersion = Value Text -> Maybe (Value Text)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "AgentVersion" Stack
Value Text
newValue, Maybe [Tag]
Maybe [ElasticIpProperty]
Maybe [RdsDbInstanceProperty]
Maybe Object
Maybe (Map Text (Value Text))
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Text)
Maybe ChefConfigurationProperty
Maybe SourceProperty
Maybe StackConfigurationManagerProperty
()
Value Text
haddock_workaround_ :: ()
attributes :: Maybe (Map Text (Value Text))
chefConfiguration :: Maybe ChefConfigurationProperty
cloneAppIds :: Maybe (ValueList Text)
clonePermissions :: Maybe (Value Bool)
configurationManager :: Maybe StackConfigurationManagerProperty
customCookbooksSource :: Maybe SourceProperty
customJson :: Maybe Object
defaultAvailabilityZone :: Maybe (Value Text)
defaultInstanceProfileArn :: Value Text
defaultOs :: Maybe (Value Text)
defaultRootDeviceType :: Maybe (Value Text)
defaultSshKeyName :: Maybe (Value Text)
defaultSubnetId :: Maybe (Value Text)
ecsClusterArn :: Maybe (Value Text)
elasticIps :: Maybe [ElasticIpProperty]
hostnameTheme :: Maybe (Value Text)
name :: Value Text
rdsDbInstances :: Maybe [RdsDbInstanceProperty]
serviceRoleArn :: Value Text
sourceStackId :: Maybe (Value Text)
tags :: Maybe [Tag]
useCustomCookbooks :: Maybe (Value Bool)
useOpsworksSecurityGroups :: Maybe (Value Bool)
vpcId :: Maybe (Value Text)
haddock_workaround_ :: ()
attributes :: Maybe (Map Text (Value Text))
chefConfiguration :: Maybe ChefConfigurationProperty
cloneAppIds :: Maybe (ValueList Text)
clonePermissions :: Maybe (Value Bool)
configurationManager :: Maybe StackConfigurationManagerProperty
customCookbooksSource :: Maybe SourceProperty
customJson :: Maybe Object
defaultAvailabilityZone :: Maybe (Value Text)
defaultInstanceProfileArn :: Value Text
defaultOs :: Maybe (Value Text)
defaultRootDeviceType :: Maybe (Value Text)
defaultSshKeyName :: Maybe (Value Text)
defaultSubnetId :: Maybe (Value Text)
ecsClusterArn :: Maybe (Value Text)
elasticIps :: Maybe [ElasticIpProperty]
hostnameTheme :: Maybe (Value Text)
name :: Value Text
rdsDbInstances :: Maybe [RdsDbInstanceProperty]
serviceRoleArn :: Value Text
sourceStackId :: Maybe (Value Text)
tags :: Maybe [Tag]
useCustomCookbooks :: Maybe (Value Bool)
useOpsworksSecurityGroups :: Maybe (Value Bool)
vpcId :: Maybe (Value Text)
..}
instance Property "Attributes" Stack where
type PropertyType "Attributes" Stack = Prelude.Map Prelude.Text (Value Prelude.Text)
set :: PropertyType "Attributes" Stack -> Stack -> Stack
set PropertyType "Attributes" Stack
newValue Stack {Maybe [Tag]
Maybe [ElasticIpProperty]
Maybe [RdsDbInstanceProperty]
Maybe Object
Maybe (Map Text (Value Text))
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Text)
Maybe ChefConfigurationProperty
Maybe SourceProperty
Maybe StackConfigurationManagerProperty
()
Value Text
haddock_workaround_ :: Stack -> ()
agentVersion :: Stack -> Maybe (Value Text)
attributes :: Stack -> Maybe (Map Text (Value Text))
chefConfiguration :: Stack -> Maybe ChefConfigurationProperty
cloneAppIds :: Stack -> Maybe (ValueList Text)
clonePermissions :: Stack -> Maybe (Value Bool)
configurationManager :: Stack -> Maybe StackConfigurationManagerProperty
customCookbooksSource :: Stack -> Maybe SourceProperty
customJson :: Stack -> Maybe Object
defaultAvailabilityZone :: Stack -> Maybe (Value Text)
defaultInstanceProfileArn :: Stack -> Value Text
defaultOs :: Stack -> Maybe (Value Text)
defaultRootDeviceType :: Stack -> Maybe (Value Text)
defaultSshKeyName :: Stack -> Maybe (Value Text)
defaultSubnetId :: Stack -> Maybe (Value Text)
ecsClusterArn :: Stack -> Maybe (Value Text)
elasticIps :: Stack -> Maybe [ElasticIpProperty]
hostnameTheme :: Stack -> Maybe (Value Text)
name :: Stack -> Value Text
rdsDbInstances :: Stack -> Maybe [RdsDbInstanceProperty]
serviceRoleArn :: Stack -> Value Text
sourceStackId :: Stack -> Maybe (Value Text)
tags :: Stack -> Maybe [Tag]
useCustomCookbooks :: Stack -> Maybe (Value Bool)
useOpsworksSecurityGroups :: Stack -> Maybe (Value Bool)
vpcId :: Stack -> Maybe (Value Text)
haddock_workaround_ :: ()
agentVersion :: Maybe (Value Text)
attributes :: Maybe (Map Text (Value Text))
chefConfiguration :: Maybe ChefConfigurationProperty
cloneAppIds :: Maybe (ValueList Text)
clonePermissions :: Maybe (Value Bool)
configurationManager :: Maybe StackConfigurationManagerProperty
customCookbooksSource :: Maybe SourceProperty
customJson :: Maybe Object
defaultAvailabilityZone :: Maybe (Value Text)
defaultInstanceProfileArn :: Value Text
defaultOs :: Maybe (Value Text)
defaultRootDeviceType :: Maybe (Value Text)
defaultSshKeyName :: Maybe (Value Text)
defaultSubnetId :: Maybe (Value Text)
ecsClusterArn :: Maybe (Value Text)
elasticIps :: Maybe [ElasticIpProperty]
hostnameTheme :: Maybe (Value Text)
name :: Value Text
rdsDbInstances :: Maybe [RdsDbInstanceProperty]
serviceRoleArn :: Value Text
sourceStackId :: Maybe (Value Text)
tags :: Maybe [Tag]
useCustomCookbooks :: Maybe (Value Bool)
useOpsworksSecurityGroups :: Maybe (Value Bool)
vpcId :: Maybe (Value Text)
..}
= Stack {attributes :: Maybe (Map Text (Value Text))
attributes = Map Text (Value Text) -> Maybe (Map Text (Value Text))
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure Map Text (Value Text)
PropertyType "Attributes" Stack
newValue, Maybe [Tag]
Maybe [ElasticIpProperty]
Maybe [RdsDbInstanceProperty]
Maybe Object
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Text)
Maybe ChefConfigurationProperty
Maybe SourceProperty
Maybe StackConfigurationManagerProperty
()
Value Text
haddock_workaround_ :: ()
agentVersion :: Maybe (Value Text)
chefConfiguration :: Maybe ChefConfigurationProperty
cloneAppIds :: Maybe (ValueList Text)
clonePermissions :: Maybe (Value Bool)
configurationManager :: Maybe StackConfigurationManagerProperty
customCookbooksSource :: Maybe SourceProperty
customJson :: Maybe Object
defaultAvailabilityZone :: Maybe (Value Text)
defaultInstanceProfileArn :: Value Text
defaultOs :: Maybe (Value Text)
defaultRootDeviceType :: Maybe (Value Text)
defaultSshKeyName :: Maybe (Value Text)
defaultSubnetId :: Maybe (Value Text)
ecsClusterArn :: Maybe (Value Text)
elasticIps :: Maybe [ElasticIpProperty]
hostnameTheme :: Maybe (Value Text)
name :: Value Text
rdsDbInstances :: Maybe [RdsDbInstanceProperty]
serviceRoleArn :: Value Text
sourceStackId :: Maybe (Value Text)
tags :: Maybe [Tag]
useCustomCookbooks :: Maybe (Value Bool)
useOpsworksSecurityGroups :: Maybe (Value Bool)
vpcId :: Maybe (Value Text)
haddock_workaround_ :: ()
agentVersion :: Maybe (Value Text)
chefConfiguration :: Maybe ChefConfigurationProperty
cloneAppIds :: Maybe (ValueList Text)
clonePermissions :: Maybe (Value Bool)
configurationManager :: Maybe StackConfigurationManagerProperty
customCookbooksSource :: Maybe SourceProperty
customJson :: Maybe Object
defaultAvailabilityZone :: Maybe (Value Text)
defaultInstanceProfileArn :: Value Text
defaultOs :: Maybe (Value Text)
defaultRootDeviceType :: Maybe (Value Text)
defaultSshKeyName :: Maybe (Value Text)
defaultSubnetId :: Maybe (Value Text)
ecsClusterArn :: Maybe (Value Text)
elasticIps :: Maybe [ElasticIpProperty]
hostnameTheme :: Maybe (Value Text)
name :: Value Text
rdsDbInstances :: Maybe [RdsDbInstanceProperty]
serviceRoleArn :: Value Text
sourceStackId :: Maybe (Value Text)
tags :: Maybe [Tag]
useCustomCookbooks :: Maybe (Value Bool)
useOpsworksSecurityGroups :: Maybe (Value Bool)
vpcId :: Maybe (Value Text)
..}
instance Property "ChefConfiguration" Stack where
type PropertyType "ChefConfiguration" Stack = ChefConfigurationProperty
set :: PropertyType "ChefConfiguration" Stack -> Stack -> Stack
set PropertyType "ChefConfiguration" Stack
newValue Stack {Maybe [Tag]
Maybe [ElasticIpProperty]
Maybe [RdsDbInstanceProperty]
Maybe Object
Maybe (Map Text (Value Text))
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Text)
Maybe ChefConfigurationProperty
Maybe SourceProperty
Maybe StackConfigurationManagerProperty
()
Value Text
haddock_workaround_ :: Stack -> ()
agentVersion :: Stack -> Maybe (Value Text)
attributes :: Stack -> Maybe (Map Text (Value Text))
chefConfiguration :: Stack -> Maybe ChefConfigurationProperty
cloneAppIds :: Stack -> Maybe (ValueList Text)
clonePermissions :: Stack -> Maybe (Value Bool)
configurationManager :: Stack -> Maybe StackConfigurationManagerProperty
customCookbooksSource :: Stack -> Maybe SourceProperty
customJson :: Stack -> Maybe Object
defaultAvailabilityZone :: Stack -> Maybe (Value Text)
defaultInstanceProfileArn :: Stack -> Value Text
defaultOs :: Stack -> Maybe (Value Text)
defaultRootDeviceType :: Stack -> Maybe (Value Text)
defaultSshKeyName :: Stack -> Maybe (Value Text)
defaultSubnetId :: Stack -> Maybe (Value Text)
ecsClusterArn :: Stack -> Maybe (Value Text)
elasticIps :: Stack -> Maybe [ElasticIpProperty]
hostnameTheme :: Stack -> Maybe (Value Text)
name :: Stack -> Value Text
rdsDbInstances :: Stack -> Maybe [RdsDbInstanceProperty]
serviceRoleArn :: Stack -> Value Text
sourceStackId :: Stack -> Maybe (Value Text)
tags :: Stack -> Maybe [Tag]
useCustomCookbooks :: Stack -> Maybe (Value Bool)
useOpsworksSecurityGroups :: Stack -> Maybe (Value Bool)
vpcId :: Stack -> Maybe (Value Text)
haddock_workaround_ :: ()
agentVersion :: Maybe (Value Text)
attributes :: Maybe (Map Text (Value Text))
chefConfiguration :: Maybe ChefConfigurationProperty
cloneAppIds :: Maybe (ValueList Text)
clonePermissions :: Maybe (Value Bool)
configurationManager :: Maybe StackConfigurationManagerProperty
customCookbooksSource :: Maybe SourceProperty
customJson :: Maybe Object
defaultAvailabilityZone :: Maybe (Value Text)
defaultInstanceProfileArn :: Value Text
defaultOs :: Maybe (Value Text)
defaultRootDeviceType :: Maybe (Value Text)
defaultSshKeyName :: Maybe (Value Text)
defaultSubnetId :: Maybe (Value Text)
ecsClusterArn :: Maybe (Value Text)
elasticIps :: Maybe [ElasticIpProperty]
hostnameTheme :: Maybe (Value Text)
name :: Value Text
rdsDbInstances :: Maybe [RdsDbInstanceProperty]
serviceRoleArn :: Value Text
sourceStackId :: Maybe (Value Text)
tags :: Maybe [Tag]
useCustomCookbooks :: Maybe (Value Bool)
useOpsworksSecurityGroups :: Maybe (Value Bool)
vpcId :: Maybe (Value Text)
..}
= Stack {chefConfiguration :: Maybe ChefConfigurationProperty
chefConfiguration = ChefConfigurationProperty -> Maybe ChefConfigurationProperty
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "ChefConfiguration" Stack
ChefConfigurationProperty
newValue, Maybe [Tag]
Maybe [ElasticIpProperty]
Maybe [RdsDbInstanceProperty]
Maybe Object
Maybe (Map Text (Value Text))
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Text)
Maybe SourceProperty
Maybe StackConfigurationManagerProperty
()
Value Text
haddock_workaround_ :: ()
agentVersion :: Maybe (Value Text)
attributes :: Maybe (Map Text (Value Text))
cloneAppIds :: Maybe (ValueList Text)
clonePermissions :: Maybe (Value Bool)
configurationManager :: Maybe StackConfigurationManagerProperty
customCookbooksSource :: Maybe SourceProperty
customJson :: Maybe Object
defaultAvailabilityZone :: Maybe (Value Text)
defaultInstanceProfileArn :: Value Text
defaultOs :: Maybe (Value Text)
defaultRootDeviceType :: Maybe (Value Text)
defaultSshKeyName :: Maybe (Value Text)
defaultSubnetId :: Maybe (Value Text)
ecsClusterArn :: Maybe (Value Text)
elasticIps :: Maybe [ElasticIpProperty]
hostnameTheme :: Maybe (Value Text)
name :: Value Text
rdsDbInstances :: Maybe [RdsDbInstanceProperty]
serviceRoleArn :: Value Text
sourceStackId :: Maybe (Value Text)
tags :: Maybe [Tag]
useCustomCookbooks :: Maybe (Value Bool)
useOpsworksSecurityGroups :: Maybe (Value Bool)
vpcId :: Maybe (Value Text)
haddock_workaround_ :: ()
agentVersion :: Maybe (Value Text)
attributes :: Maybe (Map Text (Value Text))
cloneAppIds :: Maybe (ValueList Text)
clonePermissions :: Maybe (Value Bool)
configurationManager :: Maybe StackConfigurationManagerProperty
customCookbooksSource :: Maybe SourceProperty
customJson :: Maybe Object
defaultAvailabilityZone :: Maybe (Value Text)
defaultInstanceProfileArn :: Value Text
defaultOs :: Maybe (Value Text)
defaultRootDeviceType :: Maybe (Value Text)
defaultSshKeyName :: Maybe (Value Text)
defaultSubnetId :: Maybe (Value Text)
ecsClusterArn :: Maybe (Value Text)
elasticIps :: Maybe [ElasticIpProperty]
hostnameTheme :: Maybe (Value Text)
name :: Value Text
rdsDbInstances :: Maybe [RdsDbInstanceProperty]
serviceRoleArn :: Value Text
sourceStackId :: Maybe (Value Text)
tags :: Maybe [Tag]
useCustomCookbooks :: Maybe (Value Bool)
useOpsworksSecurityGroups :: Maybe (Value Bool)
vpcId :: Maybe (Value Text)
..}
instance Property "CloneAppIds" Stack where
type PropertyType "CloneAppIds" Stack = ValueList Prelude.Text
set :: PropertyType "CloneAppIds" Stack -> Stack -> Stack
set PropertyType "CloneAppIds" Stack
newValue Stack {Maybe [Tag]
Maybe [ElasticIpProperty]
Maybe [RdsDbInstanceProperty]
Maybe Object
Maybe (Map Text (Value Text))
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Text)
Maybe ChefConfigurationProperty
Maybe SourceProperty
Maybe StackConfigurationManagerProperty
()
Value Text
haddock_workaround_ :: Stack -> ()
agentVersion :: Stack -> Maybe (Value Text)
attributes :: Stack -> Maybe (Map Text (Value Text))
chefConfiguration :: Stack -> Maybe ChefConfigurationProperty
cloneAppIds :: Stack -> Maybe (ValueList Text)
clonePermissions :: Stack -> Maybe (Value Bool)
configurationManager :: Stack -> Maybe StackConfigurationManagerProperty
customCookbooksSource :: Stack -> Maybe SourceProperty
customJson :: Stack -> Maybe Object
defaultAvailabilityZone :: Stack -> Maybe (Value Text)
defaultInstanceProfileArn :: Stack -> Value Text
defaultOs :: Stack -> Maybe (Value Text)
defaultRootDeviceType :: Stack -> Maybe (Value Text)
defaultSshKeyName :: Stack -> Maybe (Value Text)
defaultSubnetId :: Stack -> Maybe (Value Text)
ecsClusterArn :: Stack -> Maybe (Value Text)
elasticIps :: Stack -> Maybe [ElasticIpProperty]
hostnameTheme :: Stack -> Maybe (Value Text)
name :: Stack -> Value Text
rdsDbInstances :: Stack -> Maybe [RdsDbInstanceProperty]
serviceRoleArn :: Stack -> Value Text
sourceStackId :: Stack -> Maybe (Value Text)
tags :: Stack -> Maybe [Tag]
useCustomCookbooks :: Stack -> Maybe (Value Bool)
useOpsworksSecurityGroups :: Stack -> Maybe (Value Bool)
vpcId :: Stack -> Maybe (Value Text)
haddock_workaround_ :: ()
agentVersion :: Maybe (Value Text)
attributes :: Maybe (Map Text (Value Text))
chefConfiguration :: Maybe ChefConfigurationProperty
cloneAppIds :: Maybe (ValueList Text)
clonePermissions :: Maybe (Value Bool)
configurationManager :: Maybe StackConfigurationManagerProperty
customCookbooksSource :: Maybe SourceProperty
customJson :: Maybe Object
defaultAvailabilityZone :: Maybe (Value Text)
defaultInstanceProfileArn :: Value Text
defaultOs :: Maybe (Value Text)
defaultRootDeviceType :: Maybe (Value Text)
defaultSshKeyName :: Maybe (Value Text)
defaultSubnetId :: Maybe (Value Text)
ecsClusterArn :: Maybe (Value Text)
elasticIps :: Maybe [ElasticIpProperty]
hostnameTheme :: Maybe (Value Text)
name :: Value Text
rdsDbInstances :: Maybe [RdsDbInstanceProperty]
serviceRoleArn :: Value Text
sourceStackId :: Maybe (Value Text)
tags :: Maybe [Tag]
useCustomCookbooks :: Maybe (Value Bool)
useOpsworksSecurityGroups :: Maybe (Value Bool)
vpcId :: Maybe (Value Text)
..}
= Stack {cloneAppIds :: Maybe (ValueList Text)
cloneAppIds = ValueList Text -> Maybe (ValueList Text)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "CloneAppIds" Stack
ValueList Text
newValue, Maybe [Tag]
Maybe [ElasticIpProperty]
Maybe [RdsDbInstanceProperty]
Maybe Object
Maybe (Map Text (Value Text))
Maybe (Value Bool)
Maybe (Value Text)
Maybe ChefConfigurationProperty
Maybe SourceProperty
Maybe StackConfigurationManagerProperty
()
Value Text
haddock_workaround_ :: ()
agentVersion :: Maybe (Value Text)
attributes :: Maybe (Map Text (Value Text))
chefConfiguration :: Maybe ChefConfigurationProperty
clonePermissions :: Maybe (Value Bool)
configurationManager :: Maybe StackConfigurationManagerProperty
customCookbooksSource :: Maybe SourceProperty
customJson :: Maybe Object
defaultAvailabilityZone :: Maybe (Value Text)
defaultInstanceProfileArn :: Value Text
defaultOs :: Maybe (Value Text)
defaultRootDeviceType :: Maybe (Value Text)
defaultSshKeyName :: Maybe (Value Text)
defaultSubnetId :: Maybe (Value Text)
ecsClusterArn :: Maybe (Value Text)
elasticIps :: Maybe [ElasticIpProperty]
hostnameTheme :: Maybe (Value Text)
name :: Value Text
rdsDbInstances :: Maybe [RdsDbInstanceProperty]
serviceRoleArn :: Value Text
sourceStackId :: Maybe (Value Text)
tags :: Maybe [Tag]
useCustomCookbooks :: Maybe (Value Bool)
useOpsworksSecurityGroups :: Maybe (Value Bool)
vpcId :: Maybe (Value Text)
haddock_workaround_ :: ()
agentVersion :: Maybe (Value Text)
attributes :: Maybe (Map Text (Value Text))
chefConfiguration :: Maybe ChefConfigurationProperty
clonePermissions :: Maybe (Value Bool)
configurationManager :: Maybe StackConfigurationManagerProperty
customCookbooksSource :: Maybe SourceProperty
customJson :: Maybe Object
defaultAvailabilityZone :: Maybe (Value Text)
defaultInstanceProfileArn :: Value Text
defaultOs :: Maybe (Value Text)
defaultRootDeviceType :: Maybe (Value Text)
defaultSshKeyName :: Maybe (Value Text)
defaultSubnetId :: Maybe (Value Text)
ecsClusterArn :: Maybe (Value Text)
elasticIps :: Maybe [ElasticIpProperty]
hostnameTheme :: Maybe (Value Text)
name :: Value Text
rdsDbInstances :: Maybe [RdsDbInstanceProperty]
serviceRoleArn :: Value Text
sourceStackId :: Maybe (Value Text)
tags :: Maybe [Tag]
useCustomCookbooks :: Maybe (Value Bool)
useOpsworksSecurityGroups :: Maybe (Value Bool)
vpcId :: Maybe (Value Text)
..}
instance Property "ClonePermissions" Stack where
type PropertyType "ClonePermissions" Stack = Value Prelude.Bool
set :: PropertyType "ClonePermissions" Stack -> Stack -> Stack
set PropertyType "ClonePermissions" Stack
newValue Stack {Maybe [Tag]
Maybe [ElasticIpProperty]
Maybe [RdsDbInstanceProperty]
Maybe Object
Maybe (Map Text (Value Text))
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Text)
Maybe ChefConfigurationProperty
Maybe SourceProperty
Maybe StackConfigurationManagerProperty
()
Value Text
haddock_workaround_ :: Stack -> ()
agentVersion :: Stack -> Maybe (Value Text)
attributes :: Stack -> Maybe (Map Text (Value Text))
chefConfiguration :: Stack -> Maybe ChefConfigurationProperty
cloneAppIds :: Stack -> Maybe (ValueList Text)
clonePermissions :: Stack -> Maybe (Value Bool)
configurationManager :: Stack -> Maybe StackConfigurationManagerProperty
customCookbooksSource :: Stack -> Maybe SourceProperty
customJson :: Stack -> Maybe Object
defaultAvailabilityZone :: Stack -> Maybe (Value Text)
defaultInstanceProfileArn :: Stack -> Value Text
defaultOs :: Stack -> Maybe (Value Text)
defaultRootDeviceType :: Stack -> Maybe (Value Text)
defaultSshKeyName :: Stack -> Maybe (Value Text)
defaultSubnetId :: Stack -> Maybe (Value Text)
ecsClusterArn :: Stack -> Maybe (Value Text)
elasticIps :: Stack -> Maybe [ElasticIpProperty]
hostnameTheme :: Stack -> Maybe (Value Text)
name :: Stack -> Value Text
rdsDbInstances :: Stack -> Maybe [RdsDbInstanceProperty]
serviceRoleArn :: Stack -> Value Text
sourceStackId :: Stack -> Maybe (Value Text)
tags :: Stack -> Maybe [Tag]
useCustomCookbooks :: Stack -> Maybe (Value Bool)
useOpsworksSecurityGroups :: Stack -> Maybe (Value Bool)
vpcId :: Stack -> Maybe (Value Text)
haddock_workaround_ :: ()
agentVersion :: Maybe (Value Text)
attributes :: Maybe (Map Text (Value Text))
chefConfiguration :: Maybe ChefConfigurationProperty
cloneAppIds :: Maybe (ValueList Text)
clonePermissions :: Maybe (Value Bool)
configurationManager :: Maybe StackConfigurationManagerProperty
customCookbooksSource :: Maybe SourceProperty
customJson :: Maybe Object
defaultAvailabilityZone :: Maybe (Value Text)
defaultInstanceProfileArn :: Value Text
defaultOs :: Maybe (Value Text)
defaultRootDeviceType :: Maybe (Value Text)
defaultSshKeyName :: Maybe (Value Text)
defaultSubnetId :: Maybe (Value Text)
ecsClusterArn :: Maybe (Value Text)
elasticIps :: Maybe [ElasticIpProperty]
hostnameTheme :: Maybe (Value Text)
name :: Value Text
rdsDbInstances :: Maybe [RdsDbInstanceProperty]
serviceRoleArn :: Value Text
sourceStackId :: Maybe (Value Text)
tags :: Maybe [Tag]
useCustomCookbooks :: Maybe (Value Bool)
useOpsworksSecurityGroups :: Maybe (Value Bool)
vpcId :: Maybe (Value Text)
..}
= Stack {clonePermissions :: Maybe (Value Bool)
clonePermissions = Value Bool -> Maybe (Value Bool)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "ClonePermissions" Stack
Value Bool
newValue, Maybe [Tag]
Maybe [ElasticIpProperty]
Maybe [RdsDbInstanceProperty]
Maybe Object
Maybe (Map Text (Value Text))
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Text)
Maybe ChefConfigurationProperty
Maybe SourceProperty
Maybe StackConfigurationManagerProperty
()
Value Text
haddock_workaround_ :: ()
agentVersion :: Maybe (Value Text)
attributes :: Maybe (Map Text (Value Text))
chefConfiguration :: Maybe ChefConfigurationProperty
cloneAppIds :: Maybe (ValueList Text)
configurationManager :: Maybe StackConfigurationManagerProperty
customCookbooksSource :: Maybe SourceProperty
customJson :: Maybe Object
defaultAvailabilityZone :: Maybe (Value Text)
defaultInstanceProfileArn :: Value Text
defaultOs :: Maybe (Value Text)
defaultRootDeviceType :: Maybe (Value Text)
defaultSshKeyName :: Maybe (Value Text)
defaultSubnetId :: Maybe (Value Text)
ecsClusterArn :: Maybe (Value Text)
elasticIps :: Maybe [ElasticIpProperty]
hostnameTheme :: Maybe (Value Text)
name :: Value Text
rdsDbInstances :: Maybe [RdsDbInstanceProperty]
serviceRoleArn :: Value Text
sourceStackId :: Maybe (Value Text)
tags :: Maybe [Tag]
useCustomCookbooks :: Maybe (Value Bool)
useOpsworksSecurityGroups :: Maybe (Value Bool)
vpcId :: Maybe (Value Text)
haddock_workaround_ :: ()
agentVersion :: Maybe (Value Text)
attributes :: Maybe (Map Text (Value Text))
chefConfiguration :: Maybe ChefConfigurationProperty
cloneAppIds :: Maybe (ValueList Text)
configurationManager :: Maybe StackConfigurationManagerProperty
customCookbooksSource :: Maybe SourceProperty
customJson :: Maybe Object
defaultAvailabilityZone :: Maybe (Value Text)
defaultInstanceProfileArn :: Value Text
defaultOs :: Maybe (Value Text)
defaultRootDeviceType :: Maybe (Value Text)
defaultSshKeyName :: Maybe (Value Text)
defaultSubnetId :: Maybe (Value Text)
ecsClusterArn :: Maybe (Value Text)
elasticIps :: Maybe [ElasticIpProperty]
hostnameTheme :: Maybe (Value Text)
name :: Value Text
rdsDbInstances :: Maybe [RdsDbInstanceProperty]
serviceRoleArn :: Value Text
sourceStackId :: Maybe (Value Text)
tags :: Maybe [Tag]
useCustomCookbooks :: Maybe (Value Bool)
useOpsworksSecurityGroups :: Maybe (Value Bool)
vpcId :: Maybe (Value Text)
..}
instance Property "ConfigurationManager" Stack where
type PropertyType "ConfigurationManager" Stack = StackConfigurationManagerProperty
set :: PropertyType "ConfigurationManager" Stack -> Stack -> Stack
set PropertyType "ConfigurationManager" Stack
newValue Stack {Maybe [Tag]
Maybe [ElasticIpProperty]
Maybe [RdsDbInstanceProperty]
Maybe Object
Maybe (Map Text (Value Text))
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Text)
Maybe ChefConfigurationProperty
Maybe SourceProperty
Maybe StackConfigurationManagerProperty
()
Value Text
haddock_workaround_ :: Stack -> ()
agentVersion :: Stack -> Maybe (Value Text)
attributes :: Stack -> Maybe (Map Text (Value Text))
chefConfiguration :: Stack -> Maybe ChefConfigurationProperty
cloneAppIds :: Stack -> Maybe (ValueList Text)
clonePermissions :: Stack -> Maybe (Value Bool)
configurationManager :: Stack -> Maybe StackConfigurationManagerProperty
customCookbooksSource :: Stack -> Maybe SourceProperty
customJson :: Stack -> Maybe Object
defaultAvailabilityZone :: Stack -> Maybe (Value Text)
defaultInstanceProfileArn :: Stack -> Value Text
defaultOs :: Stack -> Maybe (Value Text)
defaultRootDeviceType :: Stack -> Maybe (Value Text)
defaultSshKeyName :: Stack -> Maybe (Value Text)
defaultSubnetId :: Stack -> Maybe (Value Text)
ecsClusterArn :: Stack -> Maybe (Value Text)
elasticIps :: Stack -> Maybe [ElasticIpProperty]
hostnameTheme :: Stack -> Maybe (Value Text)
name :: Stack -> Value Text
rdsDbInstances :: Stack -> Maybe [RdsDbInstanceProperty]
serviceRoleArn :: Stack -> Value Text
sourceStackId :: Stack -> Maybe (Value Text)
tags :: Stack -> Maybe [Tag]
useCustomCookbooks :: Stack -> Maybe (Value Bool)
useOpsworksSecurityGroups :: Stack -> Maybe (Value Bool)
vpcId :: Stack -> Maybe (Value Text)
haddock_workaround_ :: ()
agentVersion :: Maybe (Value Text)
attributes :: Maybe (Map Text (Value Text))
chefConfiguration :: Maybe ChefConfigurationProperty
cloneAppIds :: Maybe (ValueList Text)
clonePermissions :: Maybe (Value Bool)
configurationManager :: Maybe StackConfigurationManagerProperty
customCookbooksSource :: Maybe SourceProperty
customJson :: Maybe Object
defaultAvailabilityZone :: Maybe (Value Text)
defaultInstanceProfileArn :: Value Text
defaultOs :: Maybe (Value Text)
defaultRootDeviceType :: Maybe (Value Text)
defaultSshKeyName :: Maybe (Value Text)
defaultSubnetId :: Maybe (Value Text)
ecsClusterArn :: Maybe (Value Text)
elasticIps :: Maybe [ElasticIpProperty]
hostnameTheme :: Maybe (Value Text)
name :: Value Text
rdsDbInstances :: Maybe [RdsDbInstanceProperty]
serviceRoleArn :: Value Text
sourceStackId :: Maybe (Value Text)
tags :: Maybe [Tag]
useCustomCookbooks :: Maybe (Value Bool)
useOpsworksSecurityGroups :: Maybe (Value Bool)
vpcId :: Maybe (Value Text)
..}
= Stack {configurationManager :: Maybe StackConfigurationManagerProperty
configurationManager = StackConfigurationManagerProperty
-> Maybe StackConfigurationManagerProperty
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "ConfigurationManager" Stack
StackConfigurationManagerProperty
newValue, Maybe [Tag]
Maybe [ElasticIpProperty]
Maybe [RdsDbInstanceProperty]
Maybe Object
Maybe (Map Text (Value Text))
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Text)
Maybe ChefConfigurationProperty
Maybe SourceProperty
()
Value Text
haddock_workaround_ :: ()
agentVersion :: Maybe (Value Text)
attributes :: Maybe (Map Text (Value Text))
chefConfiguration :: Maybe ChefConfigurationProperty
cloneAppIds :: Maybe (ValueList Text)
clonePermissions :: Maybe (Value Bool)
customCookbooksSource :: Maybe SourceProperty
customJson :: Maybe Object
defaultAvailabilityZone :: Maybe (Value Text)
defaultInstanceProfileArn :: Value Text
defaultOs :: Maybe (Value Text)
defaultRootDeviceType :: Maybe (Value Text)
defaultSshKeyName :: Maybe (Value Text)
defaultSubnetId :: Maybe (Value Text)
ecsClusterArn :: Maybe (Value Text)
elasticIps :: Maybe [ElasticIpProperty]
hostnameTheme :: Maybe (Value Text)
name :: Value Text
rdsDbInstances :: Maybe [RdsDbInstanceProperty]
serviceRoleArn :: Value Text
sourceStackId :: Maybe (Value Text)
tags :: Maybe [Tag]
useCustomCookbooks :: Maybe (Value Bool)
useOpsworksSecurityGroups :: Maybe (Value Bool)
vpcId :: Maybe (Value Text)
haddock_workaround_ :: ()
agentVersion :: Maybe (Value Text)
attributes :: Maybe (Map Text (Value Text))
chefConfiguration :: Maybe ChefConfigurationProperty
cloneAppIds :: Maybe (ValueList Text)
clonePermissions :: Maybe (Value Bool)
customCookbooksSource :: Maybe SourceProperty
customJson :: Maybe Object
defaultAvailabilityZone :: Maybe (Value Text)
defaultInstanceProfileArn :: Value Text
defaultOs :: Maybe (Value Text)
defaultRootDeviceType :: Maybe (Value Text)
defaultSshKeyName :: Maybe (Value Text)
defaultSubnetId :: Maybe (Value Text)
ecsClusterArn :: Maybe (Value Text)
elasticIps :: Maybe [ElasticIpProperty]
hostnameTheme :: Maybe (Value Text)
name :: Value Text
rdsDbInstances :: Maybe [RdsDbInstanceProperty]
serviceRoleArn :: Value Text
sourceStackId :: Maybe (Value Text)
tags :: Maybe [Tag]
useCustomCookbooks :: Maybe (Value Bool)
useOpsworksSecurityGroups :: Maybe (Value Bool)
vpcId :: Maybe (Value Text)
..}
instance Property "CustomCookbooksSource" Stack where
type PropertyType "CustomCookbooksSource" Stack = SourceProperty
set :: PropertyType "CustomCookbooksSource" Stack -> Stack -> Stack
set PropertyType "CustomCookbooksSource" Stack
newValue Stack {Maybe [Tag]
Maybe [ElasticIpProperty]
Maybe [RdsDbInstanceProperty]
Maybe Object
Maybe (Map Text (Value Text))
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Text)
Maybe ChefConfigurationProperty
Maybe SourceProperty
Maybe StackConfigurationManagerProperty
()
Value Text
haddock_workaround_ :: Stack -> ()
agentVersion :: Stack -> Maybe (Value Text)
attributes :: Stack -> Maybe (Map Text (Value Text))
chefConfiguration :: Stack -> Maybe ChefConfigurationProperty
cloneAppIds :: Stack -> Maybe (ValueList Text)
clonePermissions :: Stack -> Maybe (Value Bool)
configurationManager :: Stack -> Maybe StackConfigurationManagerProperty
customCookbooksSource :: Stack -> Maybe SourceProperty
customJson :: Stack -> Maybe Object
defaultAvailabilityZone :: Stack -> Maybe (Value Text)
defaultInstanceProfileArn :: Stack -> Value Text
defaultOs :: Stack -> Maybe (Value Text)
defaultRootDeviceType :: Stack -> Maybe (Value Text)
defaultSshKeyName :: Stack -> Maybe (Value Text)
defaultSubnetId :: Stack -> Maybe (Value Text)
ecsClusterArn :: Stack -> Maybe (Value Text)
elasticIps :: Stack -> Maybe [ElasticIpProperty]
hostnameTheme :: Stack -> Maybe (Value Text)
name :: Stack -> Value Text
rdsDbInstances :: Stack -> Maybe [RdsDbInstanceProperty]
serviceRoleArn :: Stack -> Value Text
sourceStackId :: Stack -> Maybe (Value Text)
tags :: Stack -> Maybe [Tag]
useCustomCookbooks :: Stack -> Maybe (Value Bool)
useOpsworksSecurityGroups :: Stack -> Maybe (Value Bool)
vpcId :: Stack -> Maybe (Value Text)
haddock_workaround_ :: ()
agentVersion :: Maybe (Value Text)
attributes :: Maybe (Map Text (Value Text))
chefConfiguration :: Maybe ChefConfigurationProperty
cloneAppIds :: Maybe (ValueList Text)
clonePermissions :: Maybe (Value Bool)
configurationManager :: Maybe StackConfigurationManagerProperty
customCookbooksSource :: Maybe SourceProperty
customJson :: Maybe Object
defaultAvailabilityZone :: Maybe (Value Text)
defaultInstanceProfileArn :: Value Text
defaultOs :: Maybe (Value Text)
defaultRootDeviceType :: Maybe (Value Text)
defaultSshKeyName :: Maybe (Value Text)
defaultSubnetId :: Maybe (Value Text)
ecsClusterArn :: Maybe (Value Text)
elasticIps :: Maybe [ElasticIpProperty]
hostnameTheme :: Maybe (Value Text)
name :: Value Text
rdsDbInstances :: Maybe [RdsDbInstanceProperty]
serviceRoleArn :: Value Text
sourceStackId :: Maybe (Value Text)
tags :: Maybe [Tag]
useCustomCookbooks :: Maybe (Value Bool)
useOpsworksSecurityGroups :: Maybe (Value Bool)
vpcId :: Maybe (Value Text)
..}
= Stack {customCookbooksSource :: Maybe SourceProperty
customCookbooksSource = SourceProperty -> Maybe SourceProperty
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "CustomCookbooksSource" Stack
SourceProperty
newValue, Maybe [Tag]
Maybe [ElasticIpProperty]
Maybe [RdsDbInstanceProperty]
Maybe Object
Maybe (Map Text (Value Text))
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Text)
Maybe ChefConfigurationProperty
Maybe StackConfigurationManagerProperty
()
Value Text
haddock_workaround_ :: ()
agentVersion :: Maybe (Value Text)
attributes :: Maybe (Map Text (Value Text))
chefConfiguration :: Maybe ChefConfigurationProperty
cloneAppIds :: Maybe (ValueList Text)
clonePermissions :: Maybe (Value Bool)
configurationManager :: Maybe StackConfigurationManagerProperty
customJson :: Maybe Object
defaultAvailabilityZone :: Maybe (Value Text)
defaultInstanceProfileArn :: Value Text
defaultOs :: Maybe (Value Text)
defaultRootDeviceType :: Maybe (Value Text)
defaultSshKeyName :: Maybe (Value Text)
defaultSubnetId :: Maybe (Value Text)
ecsClusterArn :: Maybe (Value Text)
elasticIps :: Maybe [ElasticIpProperty]
hostnameTheme :: Maybe (Value Text)
name :: Value Text
rdsDbInstances :: Maybe [RdsDbInstanceProperty]
serviceRoleArn :: Value Text
sourceStackId :: Maybe (Value Text)
tags :: Maybe [Tag]
useCustomCookbooks :: Maybe (Value Bool)
useOpsworksSecurityGroups :: Maybe (Value Bool)
vpcId :: Maybe (Value Text)
haddock_workaround_ :: ()
agentVersion :: Maybe (Value Text)
attributes :: Maybe (Map Text (Value Text))
chefConfiguration :: Maybe ChefConfigurationProperty
cloneAppIds :: Maybe (ValueList Text)
clonePermissions :: Maybe (Value Bool)
configurationManager :: Maybe StackConfigurationManagerProperty
customJson :: Maybe Object
defaultAvailabilityZone :: Maybe (Value Text)
defaultInstanceProfileArn :: Value Text
defaultOs :: Maybe (Value Text)
defaultRootDeviceType :: Maybe (Value Text)
defaultSshKeyName :: Maybe (Value Text)
defaultSubnetId :: Maybe (Value Text)
ecsClusterArn :: Maybe (Value Text)
elasticIps :: Maybe [ElasticIpProperty]
hostnameTheme :: Maybe (Value Text)
name :: Value Text
rdsDbInstances :: Maybe [RdsDbInstanceProperty]
serviceRoleArn :: Value Text
sourceStackId :: Maybe (Value Text)
tags :: Maybe [Tag]
useCustomCookbooks :: Maybe (Value Bool)
useOpsworksSecurityGroups :: Maybe (Value Bool)
vpcId :: Maybe (Value Text)
..}
instance Property "CustomJson" Stack where
type PropertyType "CustomJson" Stack = JSON.Object
set :: PropertyType "CustomJson" Stack -> Stack -> Stack
set PropertyType "CustomJson" Stack
newValue Stack {Maybe [Tag]
Maybe [ElasticIpProperty]
Maybe [RdsDbInstanceProperty]
Maybe Object
Maybe (Map Text (Value Text))
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Text)
Maybe ChefConfigurationProperty
Maybe SourceProperty
Maybe StackConfigurationManagerProperty
()
Value Text
haddock_workaround_ :: Stack -> ()
agentVersion :: Stack -> Maybe (Value Text)
attributes :: Stack -> Maybe (Map Text (Value Text))
chefConfiguration :: Stack -> Maybe ChefConfigurationProperty
cloneAppIds :: Stack -> Maybe (ValueList Text)
clonePermissions :: Stack -> Maybe (Value Bool)
configurationManager :: Stack -> Maybe StackConfigurationManagerProperty
customCookbooksSource :: Stack -> Maybe SourceProperty
customJson :: Stack -> Maybe Object
defaultAvailabilityZone :: Stack -> Maybe (Value Text)
defaultInstanceProfileArn :: Stack -> Value Text
defaultOs :: Stack -> Maybe (Value Text)
defaultRootDeviceType :: Stack -> Maybe (Value Text)
defaultSshKeyName :: Stack -> Maybe (Value Text)
defaultSubnetId :: Stack -> Maybe (Value Text)
ecsClusterArn :: Stack -> Maybe (Value Text)
elasticIps :: Stack -> Maybe [ElasticIpProperty]
hostnameTheme :: Stack -> Maybe (Value Text)
name :: Stack -> Value Text
rdsDbInstances :: Stack -> Maybe [RdsDbInstanceProperty]
serviceRoleArn :: Stack -> Value Text
sourceStackId :: Stack -> Maybe (Value Text)
tags :: Stack -> Maybe [Tag]
useCustomCookbooks :: Stack -> Maybe (Value Bool)
useOpsworksSecurityGroups :: Stack -> Maybe (Value Bool)
vpcId :: Stack -> Maybe (Value Text)
haddock_workaround_ :: ()
agentVersion :: Maybe (Value Text)
attributes :: Maybe (Map Text (Value Text))
chefConfiguration :: Maybe ChefConfigurationProperty
cloneAppIds :: Maybe (ValueList Text)
clonePermissions :: Maybe (Value Bool)
configurationManager :: Maybe StackConfigurationManagerProperty
customCookbooksSource :: Maybe SourceProperty
customJson :: Maybe Object
defaultAvailabilityZone :: Maybe (Value Text)
defaultInstanceProfileArn :: Value Text
defaultOs :: Maybe (Value Text)
defaultRootDeviceType :: Maybe (Value Text)
defaultSshKeyName :: Maybe (Value Text)
defaultSubnetId :: Maybe (Value Text)
ecsClusterArn :: Maybe (Value Text)
elasticIps :: Maybe [ElasticIpProperty]
hostnameTheme :: Maybe (Value Text)
name :: Value Text
rdsDbInstances :: Maybe [RdsDbInstanceProperty]
serviceRoleArn :: Value Text
sourceStackId :: Maybe (Value Text)
tags :: Maybe [Tag]
useCustomCookbooks :: Maybe (Value Bool)
useOpsworksSecurityGroups :: Maybe (Value Bool)
vpcId :: Maybe (Value Text)
..}
= Stack {customJson :: Maybe Object
customJson = Object -> Maybe Object
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure Object
PropertyType "CustomJson" Stack
newValue, Maybe [Tag]
Maybe [ElasticIpProperty]
Maybe [RdsDbInstanceProperty]
Maybe (Map Text (Value Text))
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Text)
Maybe ChefConfigurationProperty
Maybe SourceProperty
Maybe StackConfigurationManagerProperty
()
Value Text
haddock_workaround_ :: ()
agentVersion :: Maybe (Value Text)
attributes :: Maybe (Map Text (Value Text))
chefConfiguration :: Maybe ChefConfigurationProperty
cloneAppIds :: Maybe (ValueList Text)
clonePermissions :: Maybe (Value Bool)
configurationManager :: Maybe StackConfigurationManagerProperty
customCookbooksSource :: Maybe SourceProperty
defaultAvailabilityZone :: Maybe (Value Text)
defaultInstanceProfileArn :: Value Text
defaultOs :: Maybe (Value Text)
defaultRootDeviceType :: Maybe (Value Text)
defaultSshKeyName :: Maybe (Value Text)
defaultSubnetId :: Maybe (Value Text)
ecsClusterArn :: Maybe (Value Text)
elasticIps :: Maybe [ElasticIpProperty]
hostnameTheme :: Maybe (Value Text)
name :: Value Text
rdsDbInstances :: Maybe [RdsDbInstanceProperty]
serviceRoleArn :: Value Text
sourceStackId :: Maybe (Value Text)
tags :: Maybe [Tag]
useCustomCookbooks :: Maybe (Value Bool)
useOpsworksSecurityGroups :: Maybe (Value Bool)
vpcId :: Maybe (Value Text)
haddock_workaround_ :: ()
agentVersion :: Maybe (Value Text)
attributes :: Maybe (Map Text (Value Text))
chefConfiguration :: Maybe ChefConfigurationProperty
cloneAppIds :: Maybe (ValueList Text)
clonePermissions :: Maybe (Value Bool)
configurationManager :: Maybe StackConfigurationManagerProperty
customCookbooksSource :: Maybe SourceProperty
defaultAvailabilityZone :: Maybe (Value Text)
defaultInstanceProfileArn :: Value Text
defaultOs :: Maybe (Value Text)
defaultRootDeviceType :: Maybe (Value Text)
defaultSshKeyName :: Maybe (Value Text)
defaultSubnetId :: Maybe (Value Text)
ecsClusterArn :: Maybe (Value Text)
elasticIps :: Maybe [ElasticIpProperty]
hostnameTheme :: Maybe (Value Text)
name :: Value Text
rdsDbInstances :: Maybe [RdsDbInstanceProperty]
serviceRoleArn :: Value Text
sourceStackId :: Maybe (Value Text)
tags :: Maybe [Tag]
useCustomCookbooks :: Maybe (Value Bool)
useOpsworksSecurityGroups :: Maybe (Value Bool)
vpcId :: Maybe (Value Text)
..}
instance Property "DefaultAvailabilityZone" Stack where
type PropertyType "DefaultAvailabilityZone" Stack = Value Prelude.Text
set :: PropertyType "DefaultAvailabilityZone" Stack -> Stack -> Stack
set PropertyType "DefaultAvailabilityZone" Stack
newValue Stack {Maybe [Tag]
Maybe [ElasticIpProperty]
Maybe [RdsDbInstanceProperty]
Maybe Object
Maybe (Map Text (Value Text))
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Text)
Maybe ChefConfigurationProperty
Maybe SourceProperty
Maybe StackConfigurationManagerProperty
()
Value Text
haddock_workaround_ :: Stack -> ()
agentVersion :: Stack -> Maybe (Value Text)
attributes :: Stack -> Maybe (Map Text (Value Text))
chefConfiguration :: Stack -> Maybe ChefConfigurationProperty
cloneAppIds :: Stack -> Maybe (ValueList Text)
clonePermissions :: Stack -> Maybe (Value Bool)
configurationManager :: Stack -> Maybe StackConfigurationManagerProperty
customCookbooksSource :: Stack -> Maybe SourceProperty
customJson :: Stack -> Maybe Object
defaultAvailabilityZone :: Stack -> Maybe (Value Text)
defaultInstanceProfileArn :: Stack -> Value Text
defaultOs :: Stack -> Maybe (Value Text)
defaultRootDeviceType :: Stack -> Maybe (Value Text)
defaultSshKeyName :: Stack -> Maybe (Value Text)
defaultSubnetId :: Stack -> Maybe (Value Text)
ecsClusterArn :: Stack -> Maybe (Value Text)
elasticIps :: Stack -> Maybe [ElasticIpProperty]
hostnameTheme :: Stack -> Maybe (Value Text)
name :: Stack -> Value Text
rdsDbInstances :: Stack -> Maybe [RdsDbInstanceProperty]
serviceRoleArn :: Stack -> Value Text
sourceStackId :: Stack -> Maybe (Value Text)
tags :: Stack -> Maybe [Tag]
useCustomCookbooks :: Stack -> Maybe (Value Bool)
useOpsworksSecurityGroups :: Stack -> Maybe (Value Bool)
vpcId :: Stack -> Maybe (Value Text)
haddock_workaround_ :: ()
agentVersion :: Maybe (Value Text)
attributes :: Maybe (Map Text (Value Text))
chefConfiguration :: Maybe ChefConfigurationProperty
cloneAppIds :: Maybe (ValueList Text)
clonePermissions :: Maybe (Value Bool)
configurationManager :: Maybe StackConfigurationManagerProperty
customCookbooksSource :: Maybe SourceProperty
customJson :: Maybe Object
defaultAvailabilityZone :: Maybe (Value Text)
defaultInstanceProfileArn :: Value Text
defaultOs :: Maybe (Value Text)
defaultRootDeviceType :: Maybe (Value Text)
defaultSshKeyName :: Maybe (Value Text)
defaultSubnetId :: Maybe (Value Text)
ecsClusterArn :: Maybe (Value Text)
elasticIps :: Maybe [ElasticIpProperty]
hostnameTheme :: Maybe (Value Text)
name :: Value Text
rdsDbInstances :: Maybe [RdsDbInstanceProperty]
serviceRoleArn :: Value Text
sourceStackId :: Maybe (Value Text)
tags :: Maybe [Tag]
useCustomCookbooks :: Maybe (Value Bool)
useOpsworksSecurityGroups :: Maybe (Value Bool)
vpcId :: Maybe (Value Text)
..}
= Stack {defaultAvailabilityZone :: Maybe (Value Text)
defaultAvailabilityZone = Value Text -> Maybe (Value Text)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "DefaultAvailabilityZone" Stack
Value Text
newValue, Maybe [Tag]
Maybe [ElasticIpProperty]
Maybe [RdsDbInstanceProperty]
Maybe Object
Maybe (Map Text (Value Text))
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Text)
Maybe ChefConfigurationProperty
Maybe SourceProperty
Maybe StackConfigurationManagerProperty
()
Value Text
haddock_workaround_ :: ()
agentVersion :: Maybe (Value Text)
attributes :: Maybe (Map Text (Value Text))
chefConfiguration :: Maybe ChefConfigurationProperty
cloneAppIds :: Maybe (ValueList Text)
clonePermissions :: Maybe (Value Bool)
configurationManager :: Maybe StackConfigurationManagerProperty
customCookbooksSource :: Maybe SourceProperty
customJson :: Maybe Object
defaultInstanceProfileArn :: Value Text
defaultOs :: Maybe (Value Text)
defaultRootDeviceType :: Maybe (Value Text)
defaultSshKeyName :: Maybe (Value Text)
defaultSubnetId :: Maybe (Value Text)
ecsClusterArn :: Maybe (Value Text)
elasticIps :: Maybe [ElasticIpProperty]
hostnameTheme :: Maybe (Value Text)
name :: Value Text
rdsDbInstances :: Maybe [RdsDbInstanceProperty]
serviceRoleArn :: Value Text
sourceStackId :: Maybe (Value Text)
tags :: Maybe [Tag]
useCustomCookbooks :: Maybe (Value Bool)
useOpsworksSecurityGroups :: Maybe (Value Bool)
vpcId :: Maybe (Value Text)
haddock_workaround_ :: ()
agentVersion :: Maybe (Value Text)
attributes :: Maybe (Map Text (Value Text))
chefConfiguration :: Maybe ChefConfigurationProperty
cloneAppIds :: Maybe (ValueList Text)
clonePermissions :: Maybe (Value Bool)
configurationManager :: Maybe StackConfigurationManagerProperty
customCookbooksSource :: Maybe SourceProperty
customJson :: Maybe Object
defaultInstanceProfileArn :: Value Text
defaultOs :: Maybe (Value Text)
defaultRootDeviceType :: Maybe (Value Text)
defaultSshKeyName :: Maybe (Value Text)
defaultSubnetId :: Maybe (Value Text)
ecsClusterArn :: Maybe (Value Text)
elasticIps :: Maybe [ElasticIpProperty]
hostnameTheme :: Maybe (Value Text)
name :: Value Text
rdsDbInstances :: Maybe [RdsDbInstanceProperty]
serviceRoleArn :: Value Text
sourceStackId :: Maybe (Value Text)
tags :: Maybe [Tag]
useCustomCookbooks :: Maybe (Value Bool)
useOpsworksSecurityGroups :: Maybe (Value Bool)
vpcId :: Maybe (Value Text)
..}
instance Property "DefaultInstanceProfileArn" Stack where
type PropertyType "DefaultInstanceProfileArn" Stack = Value Prelude.Text
set :: PropertyType "DefaultInstanceProfileArn" Stack -> Stack -> Stack
set PropertyType "DefaultInstanceProfileArn" Stack
newValue Stack {Maybe [Tag]
Maybe [ElasticIpProperty]
Maybe [RdsDbInstanceProperty]
Maybe Object
Maybe (Map Text (Value Text))
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Text)
Maybe ChefConfigurationProperty
Maybe SourceProperty
Maybe StackConfigurationManagerProperty
()
Value Text
haddock_workaround_ :: Stack -> ()
agentVersion :: Stack -> Maybe (Value Text)
attributes :: Stack -> Maybe (Map Text (Value Text))
chefConfiguration :: Stack -> Maybe ChefConfigurationProperty
cloneAppIds :: Stack -> Maybe (ValueList Text)
clonePermissions :: Stack -> Maybe (Value Bool)
configurationManager :: Stack -> Maybe StackConfigurationManagerProperty
customCookbooksSource :: Stack -> Maybe SourceProperty
customJson :: Stack -> Maybe Object
defaultAvailabilityZone :: Stack -> Maybe (Value Text)
defaultInstanceProfileArn :: Stack -> Value Text
defaultOs :: Stack -> Maybe (Value Text)
defaultRootDeviceType :: Stack -> Maybe (Value Text)
defaultSshKeyName :: Stack -> Maybe (Value Text)
defaultSubnetId :: Stack -> Maybe (Value Text)
ecsClusterArn :: Stack -> Maybe (Value Text)
elasticIps :: Stack -> Maybe [ElasticIpProperty]
hostnameTheme :: Stack -> Maybe (Value Text)
name :: Stack -> Value Text
rdsDbInstances :: Stack -> Maybe [RdsDbInstanceProperty]
serviceRoleArn :: Stack -> Value Text
sourceStackId :: Stack -> Maybe (Value Text)
tags :: Stack -> Maybe [Tag]
useCustomCookbooks :: Stack -> Maybe (Value Bool)
useOpsworksSecurityGroups :: Stack -> Maybe (Value Bool)
vpcId :: Stack -> Maybe (Value Text)
haddock_workaround_ :: ()
agentVersion :: Maybe (Value Text)
attributes :: Maybe (Map Text (Value Text))
chefConfiguration :: Maybe ChefConfigurationProperty
cloneAppIds :: Maybe (ValueList Text)
clonePermissions :: Maybe (Value Bool)
configurationManager :: Maybe StackConfigurationManagerProperty
customCookbooksSource :: Maybe SourceProperty
customJson :: Maybe Object
defaultAvailabilityZone :: Maybe (Value Text)
defaultInstanceProfileArn :: Value Text
defaultOs :: Maybe (Value Text)
defaultRootDeviceType :: Maybe (Value Text)
defaultSshKeyName :: Maybe (Value Text)
defaultSubnetId :: Maybe (Value Text)
ecsClusterArn :: Maybe (Value Text)
elasticIps :: Maybe [ElasticIpProperty]
hostnameTheme :: Maybe (Value Text)
name :: Value Text
rdsDbInstances :: Maybe [RdsDbInstanceProperty]
serviceRoleArn :: Value Text
sourceStackId :: Maybe (Value Text)
tags :: Maybe [Tag]
useCustomCookbooks :: Maybe (Value Bool)
useOpsworksSecurityGroups :: Maybe (Value Bool)
vpcId :: Maybe (Value Text)
..}
= Stack {defaultInstanceProfileArn :: Value Text
defaultInstanceProfileArn = PropertyType "DefaultInstanceProfileArn" Stack
Value Text
newValue, Maybe [Tag]
Maybe [ElasticIpProperty]
Maybe [RdsDbInstanceProperty]
Maybe Object
Maybe (Map Text (Value Text))
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Text)
Maybe ChefConfigurationProperty
Maybe SourceProperty
Maybe StackConfigurationManagerProperty
()
Value Text
haddock_workaround_ :: ()
agentVersion :: Maybe (Value Text)
attributes :: Maybe (Map Text (Value Text))
chefConfiguration :: Maybe ChefConfigurationProperty
cloneAppIds :: Maybe (ValueList Text)
clonePermissions :: Maybe (Value Bool)
configurationManager :: Maybe StackConfigurationManagerProperty
customCookbooksSource :: Maybe SourceProperty
customJson :: Maybe Object
defaultAvailabilityZone :: Maybe (Value Text)
defaultOs :: Maybe (Value Text)
defaultRootDeviceType :: Maybe (Value Text)
defaultSshKeyName :: Maybe (Value Text)
defaultSubnetId :: Maybe (Value Text)
ecsClusterArn :: Maybe (Value Text)
elasticIps :: Maybe [ElasticIpProperty]
hostnameTheme :: Maybe (Value Text)
name :: Value Text
rdsDbInstances :: Maybe [RdsDbInstanceProperty]
serviceRoleArn :: Value Text
sourceStackId :: Maybe (Value Text)
tags :: Maybe [Tag]
useCustomCookbooks :: Maybe (Value Bool)
useOpsworksSecurityGroups :: Maybe (Value Bool)
vpcId :: Maybe (Value Text)
haddock_workaround_ :: ()
agentVersion :: Maybe (Value Text)
attributes :: Maybe (Map Text (Value Text))
chefConfiguration :: Maybe ChefConfigurationProperty
cloneAppIds :: Maybe (ValueList Text)
clonePermissions :: Maybe (Value Bool)
configurationManager :: Maybe StackConfigurationManagerProperty
customCookbooksSource :: Maybe SourceProperty
customJson :: Maybe Object
defaultAvailabilityZone :: Maybe (Value Text)
defaultOs :: Maybe (Value Text)
defaultRootDeviceType :: Maybe (Value Text)
defaultSshKeyName :: Maybe (Value Text)
defaultSubnetId :: Maybe (Value Text)
ecsClusterArn :: Maybe (Value Text)
elasticIps :: Maybe [ElasticIpProperty]
hostnameTheme :: Maybe (Value Text)
name :: Value Text
rdsDbInstances :: Maybe [RdsDbInstanceProperty]
serviceRoleArn :: Value Text
sourceStackId :: Maybe (Value Text)
tags :: Maybe [Tag]
useCustomCookbooks :: Maybe (Value Bool)
useOpsworksSecurityGroups :: Maybe (Value Bool)
vpcId :: Maybe (Value Text)
..}
instance Property "DefaultOs" Stack where
type PropertyType "DefaultOs" Stack = Value Prelude.Text
set :: PropertyType "DefaultOs" Stack -> Stack -> Stack
set PropertyType "DefaultOs" Stack
newValue Stack {Maybe [Tag]
Maybe [ElasticIpProperty]
Maybe [RdsDbInstanceProperty]
Maybe Object
Maybe (Map Text (Value Text))
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Text)
Maybe ChefConfigurationProperty
Maybe SourceProperty
Maybe StackConfigurationManagerProperty
()
Value Text
haddock_workaround_ :: Stack -> ()
agentVersion :: Stack -> Maybe (Value Text)
attributes :: Stack -> Maybe (Map Text (Value Text))
chefConfiguration :: Stack -> Maybe ChefConfigurationProperty
cloneAppIds :: Stack -> Maybe (ValueList Text)
clonePermissions :: Stack -> Maybe (Value Bool)
configurationManager :: Stack -> Maybe StackConfigurationManagerProperty
customCookbooksSource :: Stack -> Maybe SourceProperty
customJson :: Stack -> Maybe Object
defaultAvailabilityZone :: Stack -> Maybe (Value Text)
defaultInstanceProfileArn :: Stack -> Value Text
defaultOs :: Stack -> Maybe (Value Text)
defaultRootDeviceType :: Stack -> Maybe (Value Text)
defaultSshKeyName :: Stack -> Maybe (Value Text)
defaultSubnetId :: Stack -> Maybe (Value Text)
ecsClusterArn :: Stack -> Maybe (Value Text)
elasticIps :: Stack -> Maybe [ElasticIpProperty]
hostnameTheme :: Stack -> Maybe (Value Text)
name :: Stack -> Value Text
rdsDbInstances :: Stack -> Maybe [RdsDbInstanceProperty]
serviceRoleArn :: Stack -> Value Text
sourceStackId :: Stack -> Maybe (Value Text)
tags :: Stack -> Maybe [Tag]
useCustomCookbooks :: Stack -> Maybe (Value Bool)
useOpsworksSecurityGroups :: Stack -> Maybe (Value Bool)
vpcId :: Stack -> Maybe (Value Text)
haddock_workaround_ :: ()
agentVersion :: Maybe (Value Text)
attributes :: Maybe (Map Text (Value Text))
chefConfiguration :: Maybe ChefConfigurationProperty
cloneAppIds :: Maybe (ValueList Text)
clonePermissions :: Maybe (Value Bool)
configurationManager :: Maybe StackConfigurationManagerProperty
customCookbooksSource :: Maybe SourceProperty
customJson :: Maybe Object
defaultAvailabilityZone :: Maybe (Value Text)
defaultInstanceProfileArn :: Value Text
defaultOs :: Maybe (Value Text)
defaultRootDeviceType :: Maybe (Value Text)
defaultSshKeyName :: Maybe (Value Text)
defaultSubnetId :: Maybe (Value Text)
ecsClusterArn :: Maybe (Value Text)
elasticIps :: Maybe [ElasticIpProperty]
hostnameTheme :: Maybe (Value Text)
name :: Value Text
rdsDbInstances :: Maybe [RdsDbInstanceProperty]
serviceRoleArn :: Value Text
sourceStackId :: Maybe (Value Text)
tags :: Maybe [Tag]
useCustomCookbooks :: Maybe (Value Bool)
useOpsworksSecurityGroups :: Maybe (Value Bool)
vpcId :: Maybe (Value Text)
..}
= Stack {defaultOs :: Maybe (Value Text)
defaultOs = Value Text -> Maybe (Value Text)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "DefaultOs" Stack
Value Text
newValue, Maybe [Tag]
Maybe [ElasticIpProperty]
Maybe [RdsDbInstanceProperty]
Maybe Object
Maybe (Map Text (Value Text))
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Text)
Maybe ChefConfigurationProperty
Maybe SourceProperty
Maybe StackConfigurationManagerProperty
()
Value Text
haddock_workaround_ :: ()
agentVersion :: Maybe (Value Text)
attributes :: Maybe (Map Text (Value Text))
chefConfiguration :: Maybe ChefConfigurationProperty
cloneAppIds :: Maybe (ValueList Text)
clonePermissions :: Maybe (Value Bool)
configurationManager :: Maybe StackConfigurationManagerProperty
customCookbooksSource :: Maybe SourceProperty
customJson :: Maybe Object
defaultAvailabilityZone :: Maybe (Value Text)
defaultInstanceProfileArn :: Value Text
defaultRootDeviceType :: Maybe (Value Text)
defaultSshKeyName :: Maybe (Value Text)
defaultSubnetId :: Maybe (Value Text)
ecsClusterArn :: Maybe (Value Text)
elasticIps :: Maybe [ElasticIpProperty]
hostnameTheme :: Maybe (Value Text)
name :: Value Text
rdsDbInstances :: Maybe [RdsDbInstanceProperty]
serviceRoleArn :: Value Text
sourceStackId :: Maybe (Value Text)
tags :: Maybe [Tag]
useCustomCookbooks :: Maybe (Value Bool)
useOpsworksSecurityGroups :: Maybe (Value Bool)
vpcId :: Maybe (Value Text)
haddock_workaround_ :: ()
agentVersion :: Maybe (Value Text)
attributes :: Maybe (Map Text (Value Text))
chefConfiguration :: Maybe ChefConfigurationProperty
cloneAppIds :: Maybe (ValueList Text)
clonePermissions :: Maybe (Value Bool)
configurationManager :: Maybe StackConfigurationManagerProperty
customCookbooksSource :: Maybe SourceProperty
customJson :: Maybe Object
defaultAvailabilityZone :: Maybe (Value Text)
defaultInstanceProfileArn :: Value Text
defaultRootDeviceType :: Maybe (Value Text)
defaultSshKeyName :: Maybe (Value Text)
defaultSubnetId :: Maybe (Value Text)
ecsClusterArn :: Maybe (Value Text)
elasticIps :: Maybe [ElasticIpProperty]
hostnameTheme :: Maybe (Value Text)
name :: Value Text
rdsDbInstances :: Maybe [RdsDbInstanceProperty]
serviceRoleArn :: Value Text
sourceStackId :: Maybe (Value Text)
tags :: Maybe [Tag]
useCustomCookbooks :: Maybe (Value Bool)
useOpsworksSecurityGroups :: Maybe (Value Bool)
vpcId :: Maybe (Value Text)
..}
instance Property "DefaultRootDeviceType" Stack where
type PropertyType "DefaultRootDeviceType" Stack = Value Prelude.Text
set :: PropertyType "DefaultRootDeviceType" Stack -> Stack -> Stack
set PropertyType "DefaultRootDeviceType" Stack
newValue Stack {Maybe [Tag]
Maybe [ElasticIpProperty]
Maybe [RdsDbInstanceProperty]
Maybe Object
Maybe (Map Text (Value Text))
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Text)
Maybe ChefConfigurationProperty
Maybe SourceProperty
Maybe StackConfigurationManagerProperty
()
Value Text
haddock_workaround_ :: Stack -> ()
agentVersion :: Stack -> Maybe (Value Text)
attributes :: Stack -> Maybe (Map Text (Value Text))
chefConfiguration :: Stack -> Maybe ChefConfigurationProperty
cloneAppIds :: Stack -> Maybe (ValueList Text)
clonePermissions :: Stack -> Maybe (Value Bool)
configurationManager :: Stack -> Maybe StackConfigurationManagerProperty
customCookbooksSource :: Stack -> Maybe SourceProperty
customJson :: Stack -> Maybe Object
defaultAvailabilityZone :: Stack -> Maybe (Value Text)
defaultInstanceProfileArn :: Stack -> Value Text
defaultOs :: Stack -> Maybe (Value Text)
defaultRootDeviceType :: Stack -> Maybe (Value Text)
defaultSshKeyName :: Stack -> Maybe (Value Text)
defaultSubnetId :: Stack -> Maybe (Value Text)
ecsClusterArn :: Stack -> Maybe (Value Text)
elasticIps :: Stack -> Maybe [ElasticIpProperty]
hostnameTheme :: Stack -> Maybe (Value Text)
name :: Stack -> Value Text
rdsDbInstances :: Stack -> Maybe [RdsDbInstanceProperty]
serviceRoleArn :: Stack -> Value Text
sourceStackId :: Stack -> Maybe (Value Text)
tags :: Stack -> Maybe [Tag]
useCustomCookbooks :: Stack -> Maybe (Value Bool)
useOpsworksSecurityGroups :: Stack -> Maybe (Value Bool)
vpcId :: Stack -> Maybe (Value Text)
haddock_workaround_ :: ()
agentVersion :: Maybe (Value Text)
attributes :: Maybe (Map Text (Value Text))
chefConfiguration :: Maybe ChefConfigurationProperty
cloneAppIds :: Maybe (ValueList Text)
clonePermissions :: Maybe (Value Bool)
configurationManager :: Maybe StackConfigurationManagerProperty
customCookbooksSource :: Maybe SourceProperty
customJson :: Maybe Object
defaultAvailabilityZone :: Maybe (Value Text)
defaultInstanceProfileArn :: Value Text
defaultOs :: Maybe (Value Text)
defaultRootDeviceType :: Maybe (Value Text)
defaultSshKeyName :: Maybe (Value Text)
defaultSubnetId :: Maybe (Value Text)
ecsClusterArn :: Maybe (Value Text)
elasticIps :: Maybe [ElasticIpProperty]
hostnameTheme :: Maybe (Value Text)
name :: Value Text
rdsDbInstances :: Maybe [RdsDbInstanceProperty]
serviceRoleArn :: Value Text
sourceStackId :: Maybe (Value Text)
tags :: Maybe [Tag]
useCustomCookbooks :: Maybe (Value Bool)
useOpsworksSecurityGroups :: Maybe (Value Bool)
vpcId :: Maybe (Value Text)
..}
= Stack {defaultRootDeviceType :: Maybe (Value Text)
defaultRootDeviceType = Value Text -> Maybe (Value Text)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "DefaultRootDeviceType" Stack
Value Text
newValue, Maybe [Tag]
Maybe [ElasticIpProperty]
Maybe [RdsDbInstanceProperty]
Maybe Object
Maybe (Map Text (Value Text))
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Text)
Maybe ChefConfigurationProperty
Maybe SourceProperty
Maybe StackConfigurationManagerProperty
()
Value Text
haddock_workaround_ :: ()
agentVersion :: Maybe (Value Text)
attributes :: Maybe (Map Text (Value Text))
chefConfiguration :: Maybe ChefConfigurationProperty
cloneAppIds :: Maybe (ValueList Text)
clonePermissions :: Maybe (Value Bool)
configurationManager :: Maybe StackConfigurationManagerProperty
customCookbooksSource :: Maybe SourceProperty
customJson :: Maybe Object
defaultAvailabilityZone :: Maybe (Value Text)
defaultInstanceProfileArn :: Value Text
defaultOs :: Maybe (Value Text)
defaultSshKeyName :: Maybe (Value Text)
defaultSubnetId :: Maybe (Value Text)
ecsClusterArn :: Maybe (Value Text)
elasticIps :: Maybe [ElasticIpProperty]
hostnameTheme :: Maybe (Value Text)
name :: Value Text
rdsDbInstances :: Maybe [RdsDbInstanceProperty]
serviceRoleArn :: Value Text
sourceStackId :: Maybe (Value Text)
tags :: Maybe [Tag]
useCustomCookbooks :: Maybe (Value Bool)
useOpsworksSecurityGroups :: Maybe (Value Bool)
vpcId :: Maybe (Value Text)
haddock_workaround_ :: ()
agentVersion :: Maybe (Value Text)
attributes :: Maybe (Map Text (Value Text))
chefConfiguration :: Maybe ChefConfigurationProperty
cloneAppIds :: Maybe (ValueList Text)
clonePermissions :: Maybe (Value Bool)
configurationManager :: Maybe StackConfigurationManagerProperty
customCookbooksSource :: Maybe SourceProperty
customJson :: Maybe Object
defaultAvailabilityZone :: Maybe (Value Text)
defaultInstanceProfileArn :: Value Text
defaultOs :: Maybe (Value Text)
defaultSshKeyName :: Maybe (Value Text)
defaultSubnetId :: Maybe (Value Text)
ecsClusterArn :: Maybe (Value Text)
elasticIps :: Maybe [ElasticIpProperty]
hostnameTheme :: Maybe (Value Text)
name :: Value Text
rdsDbInstances :: Maybe [RdsDbInstanceProperty]
serviceRoleArn :: Value Text
sourceStackId :: Maybe (Value Text)
tags :: Maybe [Tag]
useCustomCookbooks :: Maybe (Value Bool)
useOpsworksSecurityGroups :: Maybe (Value Bool)
vpcId :: Maybe (Value Text)
..}
instance Property "DefaultSshKeyName" Stack where
type PropertyType "DefaultSshKeyName" Stack = Value Prelude.Text
set :: PropertyType "DefaultSshKeyName" Stack -> Stack -> Stack
set PropertyType "DefaultSshKeyName" Stack
newValue Stack {Maybe [Tag]
Maybe [ElasticIpProperty]
Maybe [RdsDbInstanceProperty]
Maybe Object
Maybe (Map Text (Value Text))
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Text)
Maybe ChefConfigurationProperty
Maybe SourceProperty
Maybe StackConfigurationManagerProperty
()
Value Text
haddock_workaround_ :: Stack -> ()
agentVersion :: Stack -> Maybe (Value Text)
attributes :: Stack -> Maybe (Map Text (Value Text))
chefConfiguration :: Stack -> Maybe ChefConfigurationProperty
cloneAppIds :: Stack -> Maybe (ValueList Text)
clonePermissions :: Stack -> Maybe (Value Bool)
configurationManager :: Stack -> Maybe StackConfigurationManagerProperty
customCookbooksSource :: Stack -> Maybe SourceProperty
customJson :: Stack -> Maybe Object
defaultAvailabilityZone :: Stack -> Maybe (Value Text)
defaultInstanceProfileArn :: Stack -> Value Text
defaultOs :: Stack -> Maybe (Value Text)
defaultRootDeviceType :: Stack -> Maybe (Value Text)
defaultSshKeyName :: Stack -> Maybe (Value Text)
defaultSubnetId :: Stack -> Maybe (Value Text)
ecsClusterArn :: Stack -> Maybe (Value Text)
elasticIps :: Stack -> Maybe [ElasticIpProperty]
hostnameTheme :: Stack -> Maybe (Value Text)
name :: Stack -> Value Text
rdsDbInstances :: Stack -> Maybe [RdsDbInstanceProperty]
serviceRoleArn :: Stack -> Value Text
sourceStackId :: Stack -> Maybe (Value Text)
tags :: Stack -> Maybe [Tag]
useCustomCookbooks :: Stack -> Maybe (Value Bool)
useOpsworksSecurityGroups :: Stack -> Maybe (Value Bool)
vpcId :: Stack -> Maybe (Value Text)
haddock_workaround_ :: ()
agentVersion :: Maybe (Value Text)
attributes :: Maybe (Map Text (Value Text))
chefConfiguration :: Maybe ChefConfigurationProperty
cloneAppIds :: Maybe (ValueList Text)
clonePermissions :: Maybe (Value Bool)
configurationManager :: Maybe StackConfigurationManagerProperty
customCookbooksSource :: Maybe SourceProperty
customJson :: Maybe Object
defaultAvailabilityZone :: Maybe (Value Text)
defaultInstanceProfileArn :: Value Text
defaultOs :: Maybe (Value Text)
defaultRootDeviceType :: Maybe (Value Text)
defaultSshKeyName :: Maybe (Value Text)
defaultSubnetId :: Maybe (Value Text)
ecsClusterArn :: Maybe (Value Text)
elasticIps :: Maybe [ElasticIpProperty]
hostnameTheme :: Maybe (Value Text)
name :: Value Text
rdsDbInstances :: Maybe [RdsDbInstanceProperty]
serviceRoleArn :: Value Text
sourceStackId :: Maybe (Value Text)
tags :: Maybe [Tag]
useCustomCookbooks :: Maybe (Value Bool)
useOpsworksSecurityGroups :: Maybe (Value Bool)
vpcId :: Maybe (Value Text)
..}
= Stack {defaultSshKeyName :: Maybe (Value Text)
defaultSshKeyName = Value Text -> Maybe (Value Text)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "DefaultSshKeyName" Stack
Value Text
newValue, Maybe [Tag]
Maybe [ElasticIpProperty]
Maybe [RdsDbInstanceProperty]
Maybe Object
Maybe (Map Text (Value Text))
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Text)
Maybe ChefConfigurationProperty
Maybe SourceProperty
Maybe StackConfigurationManagerProperty
()
Value Text
haddock_workaround_ :: ()
agentVersion :: Maybe (Value Text)
attributes :: Maybe (Map Text (Value Text))
chefConfiguration :: Maybe ChefConfigurationProperty
cloneAppIds :: Maybe (ValueList Text)
clonePermissions :: Maybe (Value Bool)
configurationManager :: Maybe StackConfigurationManagerProperty
customCookbooksSource :: Maybe SourceProperty
customJson :: Maybe Object
defaultAvailabilityZone :: Maybe (Value Text)
defaultInstanceProfileArn :: Value Text
defaultOs :: Maybe (Value Text)
defaultRootDeviceType :: Maybe (Value Text)
defaultSubnetId :: Maybe (Value Text)
ecsClusterArn :: Maybe (Value Text)
elasticIps :: Maybe [ElasticIpProperty]
hostnameTheme :: Maybe (Value Text)
name :: Value Text
rdsDbInstances :: Maybe [RdsDbInstanceProperty]
serviceRoleArn :: Value Text
sourceStackId :: Maybe (Value Text)
tags :: Maybe [Tag]
useCustomCookbooks :: Maybe (Value Bool)
useOpsworksSecurityGroups :: Maybe (Value Bool)
vpcId :: Maybe (Value Text)
haddock_workaround_ :: ()
agentVersion :: Maybe (Value Text)
attributes :: Maybe (Map Text (Value Text))
chefConfiguration :: Maybe ChefConfigurationProperty
cloneAppIds :: Maybe (ValueList Text)
clonePermissions :: Maybe (Value Bool)
configurationManager :: Maybe StackConfigurationManagerProperty
customCookbooksSource :: Maybe SourceProperty
customJson :: Maybe Object
defaultAvailabilityZone :: Maybe (Value Text)
defaultInstanceProfileArn :: Value Text
defaultOs :: Maybe (Value Text)
defaultRootDeviceType :: Maybe (Value Text)
defaultSubnetId :: Maybe (Value Text)
ecsClusterArn :: Maybe (Value Text)
elasticIps :: Maybe [ElasticIpProperty]
hostnameTheme :: Maybe (Value Text)
name :: Value Text
rdsDbInstances :: Maybe [RdsDbInstanceProperty]
serviceRoleArn :: Value Text
sourceStackId :: Maybe (Value Text)
tags :: Maybe [Tag]
useCustomCookbooks :: Maybe (Value Bool)
useOpsworksSecurityGroups :: Maybe (Value Bool)
vpcId :: Maybe (Value Text)
..}
instance Property "DefaultSubnetId" Stack where
type PropertyType "DefaultSubnetId" Stack = Value Prelude.Text
set :: PropertyType "DefaultSubnetId" Stack -> Stack -> Stack
set PropertyType "DefaultSubnetId" Stack
newValue Stack {Maybe [Tag]
Maybe [ElasticIpProperty]
Maybe [RdsDbInstanceProperty]
Maybe Object
Maybe (Map Text (Value Text))
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Text)
Maybe ChefConfigurationProperty
Maybe SourceProperty
Maybe StackConfigurationManagerProperty
()
Value Text
haddock_workaround_ :: Stack -> ()
agentVersion :: Stack -> Maybe (Value Text)
attributes :: Stack -> Maybe (Map Text (Value Text))
chefConfiguration :: Stack -> Maybe ChefConfigurationProperty
cloneAppIds :: Stack -> Maybe (ValueList Text)
clonePermissions :: Stack -> Maybe (Value Bool)
configurationManager :: Stack -> Maybe StackConfigurationManagerProperty
customCookbooksSource :: Stack -> Maybe SourceProperty
customJson :: Stack -> Maybe Object
defaultAvailabilityZone :: Stack -> Maybe (Value Text)
defaultInstanceProfileArn :: Stack -> Value Text
defaultOs :: Stack -> Maybe (Value Text)
defaultRootDeviceType :: Stack -> Maybe (Value Text)
defaultSshKeyName :: Stack -> Maybe (Value Text)
defaultSubnetId :: Stack -> Maybe (Value Text)
ecsClusterArn :: Stack -> Maybe (Value Text)
elasticIps :: Stack -> Maybe [ElasticIpProperty]
hostnameTheme :: Stack -> Maybe (Value Text)
name :: Stack -> Value Text
rdsDbInstances :: Stack -> Maybe [RdsDbInstanceProperty]
serviceRoleArn :: Stack -> Value Text
sourceStackId :: Stack -> Maybe (Value Text)
tags :: Stack -> Maybe [Tag]
useCustomCookbooks :: Stack -> Maybe (Value Bool)
useOpsworksSecurityGroups :: Stack -> Maybe (Value Bool)
vpcId :: Stack -> Maybe (Value Text)
haddock_workaround_ :: ()
agentVersion :: Maybe (Value Text)
attributes :: Maybe (Map Text (Value Text))
chefConfiguration :: Maybe ChefConfigurationProperty
cloneAppIds :: Maybe (ValueList Text)
clonePermissions :: Maybe (Value Bool)
configurationManager :: Maybe StackConfigurationManagerProperty
customCookbooksSource :: Maybe SourceProperty
customJson :: Maybe Object
defaultAvailabilityZone :: Maybe (Value Text)
defaultInstanceProfileArn :: Value Text
defaultOs :: Maybe (Value Text)
defaultRootDeviceType :: Maybe (Value Text)
defaultSshKeyName :: Maybe (Value Text)
defaultSubnetId :: Maybe (Value Text)
ecsClusterArn :: Maybe (Value Text)
elasticIps :: Maybe [ElasticIpProperty]
hostnameTheme :: Maybe (Value Text)
name :: Value Text
rdsDbInstances :: Maybe [RdsDbInstanceProperty]
serviceRoleArn :: Value Text
sourceStackId :: Maybe (Value Text)
tags :: Maybe [Tag]
useCustomCookbooks :: Maybe (Value Bool)
useOpsworksSecurityGroups :: Maybe (Value Bool)
vpcId :: Maybe (Value Text)
..}
= Stack {defaultSubnetId :: Maybe (Value Text)
defaultSubnetId = Value Text -> Maybe (Value Text)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "DefaultSubnetId" Stack
Value Text
newValue, Maybe [Tag]
Maybe [ElasticIpProperty]
Maybe [RdsDbInstanceProperty]
Maybe Object
Maybe (Map Text (Value Text))
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Text)
Maybe ChefConfigurationProperty
Maybe SourceProperty
Maybe StackConfigurationManagerProperty
()
Value Text
haddock_workaround_ :: ()
agentVersion :: Maybe (Value Text)
attributes :: Maybe (Map Text (Value Text))
chefConfiguration :: Maybe ChefConfigurationProperty
cloneAppIds :: Maybe (ValueList Text)
clonePermissions :: Maybe (Value Bool)
configurationManager :: Maybe StackConfigurationManagerProperty
customCookbooksSource :: Maybe SourceProperty
customJson :: Maybe Object
defaultAvailabilityZone :: Maybe (Value Text)
defaultInstanceProfileArn :: Value Text
defaultOs :: Maybe (Value Text)
defaultRootDeviceType :: Maybe (Value Text)
defaultSshKeyName :: Maybe (Value Text)
ecsClusterArn :: Maybe (Value Text)
elasticIps :: Maybe [ElasticIpProperty]
hostnameTheme :: Maybe (Value Text)
name :: Value Text
rdsDbInstances :: Maybe [RdsDbInstanceProperty]
serviceRoleArn :: Value Text
sourceStackId :: Maybe (Value Text)
tags :: Maybe [Tag]
useCustomCookbooks :: Maybe (Value Bool)
useOpsworksSecurityGroups :: Maybe (Value Bool)
vpcId :: Maybe (Value Text)
haddock_workaround_ :: ()
agentVersion :: Maybe (Value Text)
attributes :: Maybe (Map Text (Value Text))
chefConfiguration :: Maybe ChefConfigurationProperty
cloneAppIds :: Maybe (ValueList Text)
clonePermissions :: Maybe (Value Bool)
configurationManager :: Maybe StackConfigurationManagerProperty
customCookbooksSource :: Maybe SourceProperty
customJson :: Maybe Object
defaultAvailabilityZone :: Maybe (Value Text)
defaultInstanceProfileArn :: Value Text
defaultOs :: Maybe (Value Text)
defaultRootDeviceType :: Maybe (Value Text)
defaultSshKeyName :: Maybe (Value Text)
ecsClusterArn :: Maybe (Value Text)
elasticIps :: Maybe [ElasticIpProperty]
hostnameTheme :: Maybe (Value Text)
name :: Value Text
rdsDbInstances :: Maybe [RdsDbInstanceProperty]
serviceRoleArn :: Value Text
sourceStackId :: Maybe (Value Text)
tags :: Maybe [Tag]
useCustomCookbooks :: Maybe (Value Bool)
useOpsworksSecurityGroups :: Maybe (Value Bool)
vpcId :: Maybe (Value Text)
..}
instance Property "EcsClusterArn" Stack where
type PropertyType "EcsClusterArn" Stack = Value Prelude.Text
set :: PropertyType "EcsClusterArn" Stack -> Stack -> Stack
set PropertyType "EcsClusterArn" Stack
newValue Stack {Maybe [Tag]
Maybe [ElasticIpProperty]
Maybe [RdsDbInstanceProperty]
Maybe Object
Maybe (Map Text (Value Text))
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Text)
Maybe ChefConfigurationProperty
Maybe SourceProperty
Maybe StackConfigurationManagerProperty
()
Value Text
haddock_workaround_ :: Stack -> ()
agentVersion :: Stack -> Maybe (Value Text)
attributes :: Stack -> Maybe (Map Text (Value Text))
chefConfiguration :: Stack -> Maybe ChefConfigurationProperty
cloneAppIds :: Stack -> Maybe (ValueList Text)
clonePermissions :: Stack -> Maybe (Value Bool)
configurationManager :: Stack -> Maybe StackConfigurationManagerProperty
customCookbooksSource :: Stack -> Maybe SourceProperty
customJson :: Stack -> Maybe Object
defaultAvailabilityZone :: Stack -> Maybe (Value Text)
defaultInstanceProfileArn :: Stack -> Value Text
defaultOs :: Stack -> Maybe (Value Text)
defaultRootDeviceType :: Stack -> Maybe (Value Text)
defaultSshKeyName :: Stack -> Maybe (Value Text)
defaultSubnetId :: Stack -> Maybe (Value Text)
ecsClusterArn :: Stack -> Maybe (Value Text)
elasticIps :: Stack -> Maybe [ElasticIpProperty]
hostnameTheme :: Stack -> Maybe (Value Text)
name :: Stack -> Value Text
rdsDbInstances :: Stack -> Maybe [RdsDbInstanceProperty]
serviceRoleArn :: Stack -> Value Text
sourceStackId :: Stack -> Maybe (Value Text)
tags :: Stack -> Maybe [Tag]
useCustomCookbooks :: Stack -> Maybe (Value Bool)
useOpsworksSecurityGroups :: Stack -> Maybe (Value Bool)
vpcId :: Stack -> Maybe (Value Text)
haddock_workaround_ :: ()
agentVersion :: Maybe (Value Text)
attributes :: Maybe (Map Text (Value Text))
chefConfiguration :: Maybe ChefConfigurationProperty
cloneAppIds :: Maybe (ValueList Text)
clonePermissions :: Maybe (Value Bool)
configurationManager :: Maybe StackConfigurationManagerProperty
customCookbooksSource :: Maybe SourceProperty
customJson :: Maybe Object
defaultAvailabilityZone :: Maybe (Value Text)
defaultInstanceProfileArn :: Value Text
defaultOs :: Maybe (Value Text)
defaultRootDeviceType :: Maybe (Value Text)
defaultSshKeyName :: Maybe (Value Text)
defaultSubnetId :: Maybe (Value Text)
ecsClusterArn :: Maybe (Value Text)
elasticIps :: Maybe [ElasticIpProperty]
hostnameTheme :: Maybe (Value Text)
name :: Value Text
rdsDbInstances :: Maybe [RdsDbInstanceProperty]
serviceRoleArn :: Value Text
sourceStackId :: Maybe (Value Text)
tags :: Maybe [Tag]
useCustomCookbooks :: Maybe (Value Bool)
useOpsworksSecurityGroups :: Maybe (Value Bool)
vpcId :: Maybe (Value Text)
..}
= Stack {ecsClusterArn :: Maybe (Value Text)
ecsClusterArn = Value Text -> Maybe (Value Text)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "EcsClusterArn" Stack
Value Text
newValue, Maybe [Tag]
Maybe [ElasticIpProperty]
Maybe [RdsDbInstanceProperty]
Maybe Object
Maybe (Map Text (Value Text))
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Text)
Maybe ChefConfigurationProperty
Maybe SourceProperty
Maybe StackConfigurationManagerProperty
()
Value Text
haddock_workaround_ :: ()
agentVersion :: Maybe (Value Text)
attributes :: Maybe (Map Text (Value Text))
chefConfiguration :: Maybe ChefConfigurationProperty
cloneAppIds :: Maybe (ValueList Text)
clonePermissions :: Maybe (Value Bool)
configurationManager :: Maybe StackConfigurationManagerProperty
customCookbooksSource :: Maybe SourceProperty
customJson :: Maybe Object
defaultAvailabilityZone :: Maybe (Value Text)
defaultInstanceProfileArn :: Value Text
defaultOs :: Maybe (Value Text)
defaultRootDeviceType :: Maybe (Value Text)
defaultSshKeyName :: Maybe (Value Text)
defaultSubnetId :: Maybe (Value Text)
elasticIps :: Maybe [ElasticIpProperty]
hostnameTheme :: Maybe (Value Text)
name :: Value Text
rdsDbInstances :: Maybe [RdsDbInstanceProperty]
serviceRoleArn :: Value Text
sourceStackId :: Maybe (Value Text)
tags :: Maybe [Tag]
useCustomCookbooks :: Maybe (Value Bool)
useOpsworksSecurityGroups :: Maybe (Value Bool)
vpcId :: Maybe (Value Text)
haddock_workaround_ :: ()
agentVersion :: Maybe (Value Text)
attributes :: Maybe (Map Text (Value Text))
chefConfiguration :: Maybe ChefConfigurationProperty
cloneAppIds :: Maybe (ValueList Text)
clonePermissions :: Maybe (Value Bool)
configurationManager :: Maybe StackConfigurationManagerProperty
customCookbooksSource :: Maybe SourceProperty
customJson :: Maybe Object
defaultAvailabilityZone :: Maybe (Value Text)
defaultInstanceProfileArn :: Value Text
defaultOs :: Maybe (Value Text)
defaultRootDeviceType :: Maybe (Value Text)
defaultSshKeyName :: Maybe (Value Text)
defaultSubnetId :: Maybe (Value Text)
elasticIps :: Maybe [ElasticIpProperty]
hostnameTheme :: Maybe (Value Text)
name :: Value Text
rdsDbInstances :: Maybe [RdsDbInstanceProperty]
serviceRoleArn :: Value Text
sourceStackId :: Maybe (Value Text)
tags :: Maybe [Tag]
useCustomCookbooks :: Maybe (Value Bool)
useOpsworksSecurityGroups :: Maybe (Value Bool)
vpcId :: Maybe (Value Text)
..}
instance Property "ElasticIps" Stack where
type PropertyType "ElasticIps" Stack = [ElasticIpProperty]
set :: PropertyType "ElasticIps" Stack -> Stack -> Stack
set PropertyType "ElasticIps" Stack
newValue Stack {Maybe [Tag]
Maybe [ElasticIpProperty]
Maybe [RdsDbInstanceProperty]
Maybe Object
Maybe (Map Text (Value Text))
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Text)
Maybe ChefConfigurationProperty
Maybe SourceProperty
Maybe StackConfigurationManagerProperty
()
Value Text
haddock_workaround_ :: Stack -> ()
agentVersion :: Stack -> Maybe (Value Text)
attributes :: Stack -> Maybe (Map Text (Value Text))
chefConfiguration :: Stack -> Maybe ChefConfigurationProperty
cloneAppIds :: Stack -> Maybe (ValueList Text)
clonePermissions :: Stack -> Maybe (Value Bool)
configurationManager :: Stack -> Maybe StackConfigurationManagerProperty
customCookbooksSource :: Stack -> Maybe SourceProperty
customJson :: Stack -> Maybe Object
defaultAvailabilityZone :: Stack -> Maybe (Value Text)
defaultInstanceProfileArn :: Stack -> Value Text
defaultOs :: Stack -> Maybe (Value Text)
defaultRootDeviceType :: Stack -> Maybe (Value Text)
defaultSshKeyName :: Stack -> Maybe (Value Text)
defaultSubnetId :: Stack -> Maybe (Value Text)
ecsClusterArn :: Stack -> Maybe (Value Text)
elasticIps :: Stack -> Maybe [ElasticIpProperty]
hostnameTheme :: Stack -> Maybe (Value Text)
name :: Stack -> Value Text
rdsDbInstances :: Stack -> Maybe [RdsDbInstanceProperty]
serviceRoleArn :: Stack -> Value Text
sourceStackId :: Stack -> Maybe (Value Text)
tags :: Stack -> Maybe [Tag]
useCustomCookbooks :: Stack -> Maybe (Value Bool)
useOpsworksSecurityGroups :: Stack -> Maybe (Value Bool)
vpcId :: Stack -> Maybe (Value Text)
haddock_workaround_ :: ()
agentVersion :: Maybe (Value Text)
attributes :: Maybe (Map Text (Value Text))
chefConfiguration :: Maybe ChefConfigurationProperty
cloneAppIds :: Maybe (ValueList Text)
clonePermissions :: Maybe (Value Bool)
configurationManager :: Maybe StackConfigurationManagerProperty
customCookbooksSource :: Maybe SourceProperty
customJson :: Maybe Object
defaultAvailabilityZone :: Maybe (Value Text)
defaultInstanceProfileArn :: Value Text
defaultOs :: Maybe (Value Text)
defaultRootDeviceType :: Maybe (Value Text)
defaultSshKeyName :: Maybe (Value Text)
defaultSubnetId :: Maybe (Value Text)
ecsClusterArn :: Maybe (Value Text)
elasticIps :: Maybe [ElasticIpProperty]
hostnameTheme :: Maybe (Value Text)
name :: Value Text
rdsDbInstances :: Maybe [RdsDbInstanceProperty]
serviceRoleArn :: Value Text
sourceStackId :: Maybe (Value Text)
tags :: Maybe [Tag]
useCustomCookbooks :: Maybe (Value Bool)
useOpsworksSecurityGroups :: Maybe (Value Bool)
vpcId :: Maybe (Value Text)
..}
= Stack {elasticIps :: Maybe [ElasticIpProperty]
elasticIps = [ElasticIpProperty] -> Maybe [ElasticIpProperty]
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure [ElasticIpProperty]
PropertyType "ElasticIps" Stack
newValue, Maybe [Tag]
Maybe [RdsDbInstanceProperty]
Maybe Object
Maybe (Map Text (Value Text))
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Text)
Maybe ChefConfigurationProperty
Maybe SourceProperty
Maybe StackConfigurationManagerProperty
()
Value Text
haddock_workaround_ :: ()
agentVersion :: Maybe (Value Text)
attributes :: Maybe (Map Text (Value Text))
chefConfiguration :: Maybe ChefConfigurationProperty
cloneAppIds :: Maybe (ValueList Text)
clonePermissions :: Maybe (Value Bool)
configurationManager :: Maybe StackConfigurationManagerProperty
customCookbooksSource :: Maybe SourceProperty
customJson :: Maybe Object
defaultAvailabilityZone :: Maybe (Value Text)
defaultInstanceProfileArn :: Value Text
defaultOs :: Maybe (Value Text)
defaultRootDeviceType :: Maybe (Value Text)
defaultSshKeyName :: Maybe (Value Text)
defaultSubnetId :: Maybe (Value Text)
ecsClusterArn :: Maybe (Value Text)
hostnameTheme :: Maybe (Value Text)
name :: Value Text
rdsDbInstances :: Maybe [RdsDbInstanceProperty]
serviceRoleArn :: Value Text
sourceStackId :: Maybe (Value Text)
tags :: Maybe [Tag]
useCustomCookbooks :: Maybe (Value Bool)
useOpsworksSecurityGroups :: Maybe (Value Bool)
vpcId :: Maybe (Value Text)
haddock_workaround_ :: ()
agentVersion :: Maybe (Value Text)
attributes :: Maybe (Map Text (Value Text))
chefConfiguration :: Maybe ChefConfigurationProperty
cloneAppIds :: Maybe (ValueList Text)
clonePermissions :: Maybe (Value Bool)
configurationManager :: Maybe StackConfigurationManagerProperty
customCookbooksSource :: Maybe SourceProperty
customJson :: Maybe Object
defaultAvailabilityZone :: Maybe (Value Text)
defaultInstanceProfileArn :: Value Text
defaultOs :: Maybe (Value Text)
defaultRootDeviceType :: Maybe (Value Text)
defaultSshKeyName :: Maybe (Value Text)
defaultSubnetId :: Maybe (Value Text)
ecsClusterArn :: Maybe (Value Text)
hostnameTheme :: Maybe (Value Text)
name :: Value Text
rdsDbInstances :: Maybe [RdsDbInstanceProperty]
serviceRoleArn :: Value Text
sourceStackId :: Maybe (Value Text)
tags :: Maybe [Tag]
useCustomCookbooks :: Maybe (Value Bool)
useOpsworksSecurityGroups :: Maybe (Value Bool)
vpcId :: Maybe (Value Text)
..}
instance Property "HostnameTheme" Stack where
type PropertyType "HostnameTheme" Stack = Value Prelude.Text
set :: PropertyType "HostnameTheme" Stack -> Stack -> Stack
set PropertyType "HostnameTheme" Stack
newValue Stack {Maybe [Tag]
Maybe [ElasticIpProperty]
Maybe [RdsDbInstanceProperty]
Maybe Object
Maybe (Map Text (Value Text))
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Text)
Maybe ChefConfigurationProperty
Maybe SourceProperty
Maybe StackConfigurationManagerProperty
()
Value Text
haddock_workaround_ :: Stack -> ()
agentVersion :: Stack -> Maybe (Value Text)
attributes :: Stack -> Maybe (Map Text (Value Text))
chefConfiguration :: Stack -> Maybe ChefConfigurationProperty
cloneAppIds :: Stack -> Maybe (ValueList Text)
clonePermissions :: Stack -> Maybe (Value Bool)
configurationManager :: Stack -> Maybe StackConfigurationManagerProperty
customCookbooksSource :: Stack -> Maybe SourceProperty
customJson :: Stack -> Maybe Object
defaultAvailabilityZone :: Stack -> Maybe (Value Text)
defaultInstanceProfileArn :: Stack -> Value Text
defaultOs :: Stack -> Maybe (Value Text)
defaultRootDeviceType :: Stack -> Maybe (Value Text)
defaultSshKeyName :: Stack -> Maybe (Value Text)
defaultSubnetId :: Stack -> Maybe (Value Text)
ecsClusterArn :: Stack -> Maybe (Value Text)
elasticIps :: Stack -> Maybe [ElasticIpProperty]
hostnameTheme :: Stack -> Maybe (Value Text)
name :: Stack -> Value Text
rdsDbInstances :: Stack -> Maybe [RdsDbInstanceProperty]
serviceRoleArn :: Stack -> Value Text
sourceStackId :: Stack -> Maybe (Value Text)
tags :: Stack -> Maybe [Tag]
useCustomCookbooks :: Stack -> Maybe (Value Bool)
useOpsworksSecurityGroups :: Stack -> Maybe (Value Bool)
vpcId :: Stack -> Maybe (Value Text)
haddock_workaround_ :: ()
agentVersion :: Maybe (Value Text)
attributes :: Maybe (Map Text (Value Text))
chefConfiguration :: Maybe ChefConfigurationProperty
cloneAppIds :: Maybe (ValueList Text)
clonePermissions :: Maybe (Value Bool)
configurationManager :: Maybe StackConfigurationManagerProperty
customCookbooksSource :: Maybe SourceProperty
customJson :: Maybe Object
defaultAvailabilityZone :: Maybe (Value Text)
defaultInstanceProfileArn :: Value Text
defaultOs :: Maybe (Value Text)
defaultRootDeviceType :: Maybe (Value Text)
defaultSshKeyName :: Maybe (Value Text)
defaultSubnetId :: Maybe (Value Text)
ecsClusterArn :: Maybe (Value Text)
elasticIps :: Maybe [ElasticIpProperty]
hostnameTheme :: Maybe (Value Text)
name :: Value Text
rdsDbInstances :: Maybe [RdsDbInstanceProperty]
serviceRoleArn :: Value Text
sourceStackId :: Maybe (Value Text)
tags :: Maybe [Tag]
useCustomCookbooks :: Maybe (Value Bool)
useOpsworksSecurityGroups :: Maybe (Value Bool)
vpcId :: Maybe (Value Text)
..}
= Stack {hostnameTheme :: Maybe (Value Text)
hostnameTheme = Value Text -> Maybe (Value Text)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "HostnameTheme" Stack
Value Text
newValue, Maybe [Tag]
Maybe [ElasticIpProperty]
Maybe [RdsDbInstanceProperty]
Maybe Object
Maybe (Map Text (Value Text))
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Text)
Maybe ChefConfigurationProperty
Maybe SourceProperty
Maybe StackConfigurationManagerProperty
()
Value Text
haddock_workaround_ :: ()
agentVersion :: Maybe (Value Text)
attributes :: Maybe (Map Text (Value Text))
chefConfiguration :: Maybe ChefConfigurationProperty
cloneAppIds :: Maybe (ValueList Text)
clonePermissions :: Maybe (Value Bool)
configurationManager :: Maybe StackConfigurationManagerProperty
customCookbooksSource :: Maybe SourceProperty
customJson :: Maybe Object
defaultAvailabilityZone :: Maybe (Value Text)
defaultInstanceProfileArn :: Value Text
defaultOs :: Maybe (Value Text)
defaultRootDeviceType :: Maybe (Value Text)
defaultSshKeyName :: Maybe (Value Text)
defaultSubnetId :: Maybe (Value Text)
ecsClusterArn :: Maybe (Value Text)
elasticIps :: Maybe [ElasticIpProperty]
name :: Value Text
rdsDbInstances :: Maybe [RdsDbInstanceProperty]
serviceRoleArn :: Value Text
sourceStackId :: Maybe (Value Text)
tags :: Maybe [Tag]
useCustomCookbooks :: Maybe (Value Bool)
useOpsworksSecurityGroups :: Maybe (Value Bool)
vpcId :: Maybe (Value Text)
haddock_workaround_ :: ()
agentVersion :: Maybe (Value Text)
attributes :: Maybe (Map Text (Value Text))
chefConfiguration :: Maybe ChefConfigurationProperty
cloneAppIds :: Maybe (ValueList Text)
clonePermissions :: Maybe (Value Bool)
configurationManager :: Maybe StackConfigurationManagerProperty
customCookbooksSource :: Maybe SourceProperty
customJson :: Maybe Object
defaultAvailabilityZone :: Maybe (Value Text)
defaultInstanceProfileArn :: Value Text
defaultOs :: Maybe (Value Text)
defaultRootDeviceType :: Maybe (Value Text)
defaultSshKeyName :: Maybe (Value Text)
defaultSubnetId :: Maybe (Value Text)
ecsClusterArn :: Maybe (Value Text)
elasticIps :: Maybe [ElasticIpProperty]
name :: Value Text
rdsDbInstances :: Maybe [RdsDbInstanceProperty]
serviceRoleArn :: Value Text
sourceStackId :: Maybe (Value Text)
tags :: Maybe [Tag]
useCustomCookbooks :: Maybe (Value Bool)
useOpsworksSecurityGroups :: Maybe (Value Bool)
vpcId :: Maybe (Value Text)
..}
instance Property "Name" Stack where
type PropertyType "Name" Stack = Value Prelude.Text
set :: PropertyType "Name" Stack -> Stack -> Stack
set PropertyType "Name" Stack
newValue Stack {Maybe [Tag]
Maybe [ElasticIpProperty]
Maybe [RdsDbInstanceProperty]
Maybe Object
Maybe (Map Text (Value Text))
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Text)
Maybe ChefConfigurationProperty
Maybe SourceProperty
Maybe StackConfigurationManagerProperty
()
Value Text
haddock_workaround_ :: Stack -> ()
agentVersion :: Stack -> Maybe (Value Text)
attributes :: Stack -> Maybe (Map Text (Value Text))
chefConfiguration :: Stack -> Maybe ChefConfigurationProperty
cloneAppIds :: Stack -> Maybe (ValueList Text)
clonePermissions :: Stack -> Maybe (Value Bool)
configurationManager :: Stack -> Maybe StackConfigurationManagerProperty
customCookbooksSource :: Stack -> Maybe SourceProperty
customJson :: Stack -> Maybe Object
defaultAvailabilityZone :: Stack -> Maybe (Value Text)
defaultInstanceProfileArn :: Stack -> Value Text
defaultOs :: Stack -> Maybe (Value Text)
defaultRootDeviceType :: Stack -> Maybe (Value Text)
defaultSshKeyName :: Stack -> Maybe (Value Text)
defaultSubnetId :: Stack -> Maybe (Value Text)
ecsClusterArn :: Stack -> Maybe (Value Text)
elasticIps :: Stack -> Maybe [ElasticIpProperty]
hostnameTheme :: Stack -> Maybe (Value Text)
name :: Stack -> Value Text
rdsDbInstances :: Stack -> Maybe [RdsDbInstanceProperty]
serviceRoleArn :: Stack -> Value Text
sourceStackId :: Stack -> Maybe (Value Text)
tags :: Stack -> Maybe [Tag]
useCustomCookbooks :: Stack -> Maybe (Value Bool)
useOpsworksSecurityGroups :: Stack -> Maybe (Value Bool)
vpcId :: Stack -> Maybe (Value Text)
haddock_workaround_ :: ()
agentVersion :: Maybe (Value Text)
attributes :: Maybe (Map Text (Value Text))
chefConfiguration :: Maybe ChefConfigurationProperty
cloneAppIds :: Maybe (ValueList Text)
clonePermissions :: Maybe (Value Bool)
configurationManager :: Maybe StackConfigurationManagerProperty
customCookbooksSource :: Maybe SourceProperty
customJson :: Maybe Object
defaultAvailabilityZone :: Maybe (Value Text)
defaultInstanceProfileArn :: Value Text
defaultOs :: Maybe (Value Text)
defaultRootDeviceType :: Maybe (Value Text)
defaultSshKeyName :: Maybe (Value Text)
defaultSubnetId :: Maybe (Value Text)
ecsClusterArn :: Maybe (Value Text)
elasticIps :: Maybe [ElasticIpProperty]
hostnameTheme :: Maybe (Value Text)
name :: Value Text
rdsDbInstances :: Maybe [RdsDbInstanceProperty]
serviceRoleArn :: Value Text
sourceStackId :: Maybe (Value Text)
tags :: Maybe [Tag]
useCustomCookbooks :: Maybe (Value Bool)
useOpsworksSecurityGroups :: Maybe (Value Bool)
vpcId :: Maybe (Value Text)
..} = Stack {name :: Value Text
name = PropertyType "Name" Stack
Value Text
newValue, Maybe [Tag]
Maybe [ElasticIpProperty]
Maybe [RdsDbInstanceProperty]
Maybe Object
Maybe (Map Text (Value Text))
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Text)
Maybe ChefConfigurationProperty
Maybe SourceProperty
Maybe StackConfigurationManagerProperty
()
Value Text
haddock_workaround_ :: ()
agentVersion :: Maybe (Value Text)
attributes :: Maybe (Map Text (Value Text))
chefConfiguration :: Maybe ChefConfigurationProperty
cloneAppIds :: Maybe (ValueList Text)
clonePermissions :: Maybe (Value Bool)
configurationManager :: Maybe StackConfigurationManagerProperty
customCookbooksSource :: Maybe SourceProperty
customJson :: Maybe Object
defaultAvailabilityZone :: Maybe (Value Text)
defaultInstanceProfileArn :: Value Text
defaultOs :: Maybe (Value Text)
defaultRootDeviceType :: Maybe (Value Text)
defaultSshKeyName :: Maybe (Value Text)
defaultSubnetId :: Maybe (Value Text)
ecsClusterArn :: Maybe (Value Text)
elasticIps :: Maybe [ElasticIpProperty]
hostnameTheme :: Maybe (Value Text)
rdsDbInstances :: Maybe [RdsDbInstanceProperty]
serviceRoleArn :: Value Text
sourceStackId :: Maybe (Value Text)
tags :: Maybe [Tag]
useCustomCookbooks :: Maybe (Value Bool)
useOpsworksSecurityGroups :: Maybe (Value Bool)
vpcId :: Maybe (Value Text)
haddock_workaround_ :: ()
agentVersion :: Maybe (Value Text)
attributes :: Maybe (Map Text (Value Text))
chefConfiguration :: Maybe ChefConfigurationProperty
cloneAppIds :: Maybe (ValueList Text)
clonePermissions :: Maybe (Value Bool)
configurationManager :: Maybe StackConfigurationManagerProperty
customCookbooksSource :: Maybe SourceProperty
customJson :: Maybe Object
defaultAvailabilityZone :: Maybe (Value Text)
defaultInstanceProfileArn :: Value Text
defaultOs :: Maybe (Value Text)
defaultRootDeviceType :: Maybe (Value Text)
defaultSshKeyName :: Maybe (Value Text)
defaultSubnetId :: Maybe (Value Text)
ecsClusterArn :: Maybe (Value Text)
elasticIps :: Maybe [ElasticIpProperty]
hostnameTheme :: Maybe (Value Text)
rdsDbInstances :: Maybe [RdsDbInstanceProperty]
serviceRoleArn :: Value Text
sourceStackId :: Maybe (Value Text)
tags :: Maybe [Tag]
useCustomCookbooks :: Maybe (Value Bool)
useOpsworksSecurityGroups :: Maybe (Value Bool)
vpcId :: Maybe (Value Text)
..}
instance Property "RdsDbInstances" Stack where
type PropertyType "RdsDbInstances" Stack = [RdsDbInstanceProperty]
set :: PropertyType "RdsDbInstances" Stack -> Stack -> Stack
set PropertyType "RdsDbInstances" Stack
newValue Stack {Maybe [Tag]
Maybe [ElasticIpProperty]
Maybe [RdsDbInstanceProperty]
Maybe Object
Maybe (Map Text (Value Text))
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Text)
Maybe ChefConfigurationProperty
Maybe SourceProperty
Maybe StackConfigurationManagerProperty
()
Value Text
haddock_workaround_ :: Stack -> ()
agentVersion :: Stack -> Maybe (Value Text)
attributes :: Stack -> Maybe (Map Text (Value Text))
chefConfiguration :: Stack -> Maybe ChefConfigurationProperty
cloneAppIds :: Stack -> Maybe (ValueList Text)
clonePermissions :: Stack -> Maybe (Value Bool)
configurationManager :: Stack -> Maybe StackConfigurationManagerProperty
customCookbooksSource :: Stack -> Maybe SourceProperty
customJson :: Stack -> Maybe Object
defaultAvailabilityZone :: Stack -> Maybe (Value Text)
defaultInstanceProfileArn :: Stack -> Value Text
defaultOs :: Stack -> Maybe (Value Text)
defaultRootDeviceType :: Stack -> Maybe (Value Text)
defaultSshKeyName :: Stack -> Maybe (Value Text)
defaultSubnetId :: Stack -> Maybe (Value Text)
ecsClusterArn :: Stack -> Maybe (Value Text)
elasticIps :: Stack -> Maybe [ElasticIpProperty]
hostnameTheme :: Stack -> Maybe (Value Text)
name :: Stack -> Value Text
rdsDbInstances :: Stack -> Maybe [RdsDbInstanceProperty]
serviceRoleArn :: Stack -> Value Text
sourceStackId :: Stack -> Maybe (Value Text)
tags :: Stack -> Maybe [Tag]
useCustomCookbooks :: Stack -> Maybe (Value Bool)
useOpsworksSecurityGroups :: Stack -> Maybe (Value Bool)
vpcId :: Stack -> Maybe (Value Text)
haddock_workaround_ :: ()
agentVersion :: Maybe (Value Text)
attributes :: Maybe (Map Text (Value Text))
chefConfiguration :: Maybe ChefConfigurationProperty
cloneAppIds :: Maybe (ValueList Text)
clonePermissions :: Maybe (Value Bool)
configurationManager :: Maybe StackConfigurationManagerProperty
customCookbooksSource :: Maybe SourceProperty
customJson :: Maybe Object
defaultAvailabilityZone :: Maybe (Value Text)
defaultInstanceProfileArn :: Value Text
defaultOs :: Maybe (Value Text)
defaultRootDeviceType :: Maybe (Value Text)
defaultSshKeyName :: Maybe (Value Text)
defaultSubnetId :: Maybe (Value Text)
ecsClusterArn :: Maybe (Value Text)
elasticIps :: Maybe [ElasticIpProperty]
hostnameTheme :: Maybe (Value Text)
name :: Value Text
rdsDbInstances :: Maybe [RdsDbInstanceProperty]
serviceRoleArn :: Value Text
sourceStackId :: Maybe (Value Text)
tags :: Maybe [Tag]
useCustomCookbooks :: Maybe (Value Bool)
useOpsworksSecurityGroups :: Maybe (Value Bool)
vpcId :: Maybe (Value Text)
..}
= Stack {rdsDbInstances :: Maybe [RdsDbInstanceProperty]
rdsDbInstances = [RdsDbInstanceProperty] -> Maybe [RdsDbInstanceProperty]
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure [RdsDbInstanceProperty]
PropertyType "RdsDbInstances" Stack
newValue, Maybe [Tag]
Maybe [ElasticIpProperty]
Maybe Object
Maybe (Map Text (Value Text))
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Text)
Maybe ChefConfigurationProperty
Maybe SourceProperty
Maybe StackConfigurationManagerProperty
()
Value Text
haddock_workaround_ :: ()
agentVersion :: Maybe (Value Text)
attributes :: Maybe (Map Text (Value Text))
chefConfiguration :: Maybe ChefConfigurationProperty
cloneAppIds :: Maybe (ValueList Text)
clonePermissions :: Maybe (Value Bool)
configurationManager :: Maybe StackConfigurationManagerProperty
customCookbooksSource :: Maybe SourceProperty
customJson :: Maybe Object
defaultAvailabilityZone :: Maybe (Value Text)
defaultInstanceProfileArn :: Value Text
defaultOs :: Maybe (Value Text)
defaultRootDeviceType :: Maybe (Value Text)
defaultSshKeyName :: Maybe (Value Text)
defaultSubnetId :: Maybe (Value Text)
ecsClusterArn :: Maybe (Value Text)
elasticIps :: Maybe [ElasticIpProperty]
hostnameTheme :: Maybe (Value Text)
name :: Value Text
serviceRoleArn :: Value Text
sourceStackId :: Maybe (Value Text)
tags :: Maybe [Tag]
useCustomCookbooks :: Maybe (Value Bool)
useOpsworksSecurityGroups :: Maybe (Value Bool)
vpcId :: Maybe (Value Text)
haddock_workaround_ :: ()
agentVersion :: Maybe (Value Text)
attributes :: Maybe (Map Text (Value Text))
chefConfiguration :: Maybe ChefConfigurationProperty
cloneAppIds :: Maybe (ValueList Text)
clonePermissions :: Maybe (Value Bool)
configurationManager :: Maybe StackConfigurationManagerProperty
customCookbooksSource :: Maybe SourceProperty
customJson :: Maybe Object
defaultAvailabilityZone :: Maybe (Value Text)
defaultInstanceProfileArn :: Value Text
defaultOs :: Maybe (Value Text)
defaultRootDeviceType :: Maybe (Value Text)
defaultSshKeyName :: Maybe (Value Text)
defaultSubnetId :: Maybe (Value Text)
ecsClusterArn :: Maybe (Value Text)
elasticIps :: Maybe [ElasticIpProperty]
hostnameTheme :: Maybe (Value Text)
name :: Value Text
serviceRoleArn :: Value Text
sourceStackId :: Maybe (Value Text)
tags :: Maybe [Tag]
useCustomCookbooks :: Maybe (Value Bool)
useOpsworksSecurityGroups :: Maybe (Value Bool)
vpcId :: Maybe (Value Text)
..}
instance Property "ServiceRoleArn" Stack where
type PropertyType "ServiceRoleArn" Stack = Value Prelude.Text
set :: PropertyType "ServiceRoleArn" Stack -> Stack -> Stack
set PropertyType "ServiceRoleArn" Stack
newValue Stack {Maybe [Tag]
Maybe [ElasticIpProperty]
Maybe [RdsDbInstanceProperty]
Maybe Object
Maybe (Map Text (Value Text))
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Text)
Maybe ChefConfigurationProperty
Maybe SourceProperty
Maybe StackConfigurationManagerProperty
()
Value Text
haddock_workaround_ :: Stack -> ()
agentVersion :: Stack -> Maybe (Value Text)
attributes :: Stack -> Maybe (Map Text (Value Text))
chefConfiguration :: Stack -> Maybe ChefConfigurationProperty
cloneAppIds :: Stack -> Maybe (ValueList Text)
clonePermissions :: Stack -> Maybe (Value Bool)
configurationManager :: Stack -> Maybe StackConfigurationManagerProperty
customCookbooksSource :: Stack -> Maybe SourceProperty
customJson :: Stack -> Maybe Object
defaultAvailabilityZone :: Stack -> Maybe (Value Text)
defaultInstanceProfileArn :: Stack -> Value Text
defaultOs :: Stack -> Maybe (Value Text)
defaultRootDeviceType :: Stack -> Maybe (Value Text)
defaultSshKeyName :: Stack -> Maybe (Value Text)
defaultSubnetId :: Stack -> Maybe (Value Text)
ecsClusterArn :: Stack -> Maybe (Value Text)
elasticIps :: Stack -> Maybe [ElasticIpProperty]
hostnameTheme :: Stack -> Maybe (Value Text)
name :: Stack -> Value Text
rdsDbInstances :: Stack -> Maybe [RdsDbInstanceProperty]
serviceRoleArn :: Stack -> Value Text
sourceStackId :: Stack -> Maybe (Value Text)
tags :: Stack -> Maybe [Tag]
useCustomCookbooks :: Stack -> Maybe (Value Bool)
useOpsworksSecurityGroups :: Stack -> Maybe (Value Bool)
vpcId :: Stack -> Maybe (Value Text)
haddock_workaround_ :: ()
agentVersion :: Maybe (Value Text)
attributes :: Maybe (Map Text (Value Text))
chefConfiguration :: Maybe ChefConfigurationProperty
cloneAppIds :: Maybe (ValueList Text)
clonePermissions :: Maybe (Value Bool)
configurationManager :: Maybe StackConfigurationManagerProperty
customCookbooksSource :: Maybe SourceProperty
customJson :: Maybe Object
defaultAvailabilityZone :: Maybe (Value Text)
defaultInstanceProfileArn :: Value Text
defaultOs :: Maybe (Value Text)
defaultRootDeviceType :: Maybe (Value Text)
defaultSshKeyName :: Maybe (Value Text)
defaultSubnetId :: Maybe (Value Text)
ecsClusterArn :: Maybe (Value Text)
elasticIps :: Maybe [ElasticIpProperty]
hostnameTheme :: Maybe (Value Text)
name :: Value Text
rdsDbInstances :: Maybe [RdsDbInstanceProperty]
serviceRoleArn :: Value Text
sourceStackId :: Maybe (Value Text)
tags :: Maybe [Tag]
useCustomCookbooks :: Maybe (Value Bool)
useOpsworksSecurityGroups :: Maybe (Value Bool)
vpcId :: Maybe (Value Text)
..} = Stack {serviceRoleArn :: Value Text
serviceRoleArn = PropertyType "ServiceRoleArn" Stack
Value Text
newValue, Maybe [Tag]
Maybe [ElasticIpProperty]
Maybe [RdsDbInstanceProperty]
Maybe Object
Maybe (Map Text (Value Text))
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Text)
Maybe ChefConfigurationProperty
Maybe SourceProperty
Maybe StackConfigurationManagerProperty
()
Value Text
haddock_workaround_ :: ()
agentVersion :: Maybe (Value Text)
attributes :: Maybe (Map Text (Value Text))
chefConfiguration :: Maybe ChefConfigurationProperty
cloneAppIds :: Maybe (ValueList Text)
clonePermissions :: Maybe (Value Bool)
configurationManager :: Maybe StackConfigurationManagerProperty
customCookbooksSource :: Maybe SourceProperty
customJson :: Maybe Object
defaultAvailabilityZone :: Maybe (Value Text)
defaultInstanceProfileArn :: Value Text
defaultOs :: Maybe (Value Text)
defaultRootDeviceType :: Maybe (Value Text)
defaultSshKeyName :: Maybe (Value Text)
defaultSubnetId :: Maybe (Value Text)
ecsClusterArn :: Maybe (Value Text)
elasticIps :: Maybe [ElasticIpProperty]
hostnameTheme :: Maybe (Value Text)
name :: Value Text
rdsDbInstances :: Maybe [RdsDbInstanceProperty]
sourceStackId :: Maybe (Value Text)
tags :: Maybe [Tag]
useCustomCookbooks :: Maybe (Value Bool)
useOpsworksSecurityGroups :: Maybe (Value Bool)
vpcId :: Maybe (Value Text)
haddock_workaround_ :: ()
agentVersion :: Maybe (Value Text)
attributes :: Maybe (Map Text (Value Text))
chefConfiguration :: Maybe ChefConfigurationProperty
cloneAppIds :: Maybe (ValueList Text)
clonePermissions :: Maybe (Value Bool)
configurationManager :: Maybe StackConfigurationManagerProperty
customCookbooksSource :: Maybe SourceProperty
customJson :: Maybe Object
defaultAvailabilityZone :: Maybe (Value Text)
defaultInstanceProfileArn :: Value Text
defaultOs :: Maybe (Value Text)
defaultRootDeviceType :: Maybe (Value Text)
defaultSshKeyName :: Maybe (Value Text)
defaultSubnetId :: Maybe (Value Text)
ecsClusterArn :: Maybe (Value Text)
elasticIps :: Maybe [ElasticIpProperty]
hostnameTheme :: Maybe (Value Text)
name :: Value Text
rdsDbInstances :: Maybe [RdsDbInstanceProperty]
sourceStackId :: Maybe (Value Text)
tags :: Maybe [Tag]
useCustomCookbooks :: Maybe (Value Bool)
useOpsworksSecurityGroups :: Maybe (Value Bool)
vpcId :: Maybe (Value Text)
..}
instance Property "SourceStackId" Stack where
type PropertyType "SourceStackId" Stack = Value Prelude.Text
set :: PropertyType "SourceStackId" Stack -> Stack -> Stack
set PropertyType "SourceStackId" Stack
newValue Stack {Maybe [Tag]
Maybe [ElasticIpProperty]
Maybe [RdsDbInstanceProperty]
Maybe Object
Maybe (Map Text (Value Text))
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Text)
Maybe ChefConfigurationProperty
Maybe SourceProperty
Maybe StackConfigurationManagerProperty
()
Value Text
haddock_workaround_ :: Stack -> ()
agentVersion :: Stack -> Maybe (Value Text)
attributes :: Stack -> Maybe (Map Text (Value Text))
chefConfiguration :: Stack -> Maybe ChefConfigurationProperty
cloneAppIds :: Stack -> Maybe (ValueList Text)
clonePermissions :: Stack -> Maybe (Value Bool)
configurationManager :: Stack -> Maybe StackConfigurationManagerProperty
customCookbooksSource :: Stack -> Maybe SourceProperty
customJson :: Stack -> Maybe Object
defaultAvailabilityZone :: Stack -> Maybe (Value Text)
defaultInstanceProfileArn :: Stack -> Value Text
defaultOs :: Stack -> Maybe (Value Text)
defaultRootDeviceType :: Stack -> Maybe (Value Text)
defaultSshKeyName :: Stack -> Maybe (Value Text)
defaultSubnetId :: Stack -> Maybe (Value Text)
ecsClusterArn :: Stack -> Maybe (Value Text)
elasticIps :: Stack -> Maybe [ElasticIpProperty]
hostnameTheme :: Stack -> Maybe (Value Text)
name :: Stack -> Value Text
rdsDbInstances :: Stack -> Maybe [RdsDbInstanceProperty]
serviceRoleArn :: Stack -> Value Text
sourceStackId :: Stack -> Maybe (Value Text)
tags :: Stack -> Maybe [Tag]
useCustomCookbooks :: Stack -> Maybe (Value Bool)
useOpsworksSecurityGroups :: Stack -> Maybe (Value Bool)
vpcId :: Stack -> Maybe (Value Text)
haddock_workaround_ :: ()
agentVersion :: Maybe (Value Text)
attributes :: Maybe (Map Text (Value Text))
chefConfiguration :: Maybe ChefConfigurationProperty
cloneAppIds :: Maybe (ValueList Text)
clonePermissions :: Maybe (Value Bool)
configurationManager :: Maybe StackConfigurationManagerProperty
customCookbooksSource :: Maybe SourceProperty
customJson :: Maybe Object
defaultAvailabilityZone :: Maybe (Value Text)
defaultInstanceProfileArn :: Value Text
defaultOs :: Maybe (Value Text)
defaultRootDeviceType :: Maybe (Value Text)
defaultSshKeyName :: Maybe (Value Text)
defaultSubnetId :: Maybe (Value Text)
ecsClusterArn :: Maybe (Value Text)
elasticIps :: Maybe [ElasticIpProperty]
hostnameTheme :: Maybe (Value Text)
name :: Value Text
rdsDbInstances :: Maybe [RdsDbInstanceProperty]
serviceRoleArn :: Value Text
sourceStackId :: Maybe (Value Text)
tags :: Maybe [Tag]
useCustomCookbooks :: Maybe (Value Bool)
useOpsworksSecurityGroups :: Maybe (Value Bool)
vpcId :: Maybe (Value Text)
..}
= Stack {sourceStackId :: Maybe (Value Text)
sourceStackId = Value Text -> Maybe (Value Text)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "SourceStackId" Stack
Value Text
newValue, Maybe [Tag]
Maybe [ElasticIpProperty]
Maybe [RdsDbInstanceProperty]
Maybe Object
Maybe (Map Text (Value Text))
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Text)
Maybe ChefConfigurationProperty
Maybe SourceProperty
Maybe StackConfigurationManagerProperty
()
Value Text
haddock_workaround_ :: ()
agentVersion :: Maybe (Value Text)
attributes :: Maybe (Map Text (Value Text))
chefConfiguration :: Maybe ChefConfigurationProperty
cloneAppIds :: Maybe (ValueList Text)
clonePermissions :: Maybe (Value Bool)
configurationManager :: Maybe StackConfigurationManagerProperty
customCookbooksSource :: Maybe SourceProperty
customJson :: Maybe Object
defaultAvailabilityZone :: Maybe (Value Text)
defaultInstanceProfileArn :: Value Text
defaultOs :: Maybe (Value Text)
defaultRootDeviceType :: Maybe (Value Text)
defaultSshKeyName :: Maybe (Value Text)
defaultSubnetId :: Maybe (Value Text)
ecsClusterArn :: Maybe (Value Text)
elasticIps :: Maybe [ElasticIpProperty]
hostnameTheme :: Maybe (Value Text)
name :: Value Text
rdsDbInstances :: Maybe [RdsDbInstanceProperty]
serviceRoleArn :: Value Text
tags :: Maybe [Tag]
useCustomCookbooks :: Maybe (Value Bool)
useOpsworksSecurityGroups :: Maybe (Value Bool)
vpcId :: Maybe (Value Text)
haddock_workaround_ :: ()
agentVersion :: Maybe (Value Text)
attributes :: Maybe (Map Text (Value Text))
chefConfiguration :: Maybe ChefConfigurationProperty
cloneAppIds :: Maybe (ValueList Text)
clonePermissions :: Maybe (Value Bool)
configurationManager :: Maybe StackConfigurationManagerProperty
customCookbooksSource :: Maybe SourceProperty
customJson :: Maybe Object
defaultAvailabilityZone :: Maybe (Value Text)
defaultInstanceProfileArn :: Value Text
defaultOs :: Maybe (Value Text)
defaultRootDeviceType :: Maybe (Value Text)
defaultSshKeyName :: Maybe (Value Text)
defaultSubnetId :: Maybe (Value Text)
ecsClusterArn :: Maybe (Value Text)
elasticIps :: Maybe [ElasticIpProperty]
hostnameTheme :: Maybe (Value Text)
name :: Value Text
rdsDbInstances :: Maybe [RdsDbInstanceProperty]
serviceRoleArn :: Value Text
tags :: Maybe [Tag]
useCustomCookbooks :: Maybe (Value Bool)
useOpsworksSecurityGroups :: Maybe (Value Bool)
vpcId :: Maybe (Value Text)
..}
instance Property "Tags" Stack where
type PropertyType "Tags" Stack = [Tag]
set :: PropertyType "Tags" Stack -> Stack -> Stack
set PropertyType "Tags" Stack
newValue Stack {Maybe [Tag]
Maybe [ElasticIpProperty]
Maybe [RdsDbInstanceProperty]
Maybe Object
Maybe (Map Text (Value Text))
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Text)
Maybe ChefConfigurationProperty
Maybe SourceProperty
Maybe StackConfigurationManagerProperty
()
Value Text
haddock_workaround_ :: Stack -> ()
agentVersion :: Stack -> Maybe (Value Text)
attributes :: Stack -> Maybe (Map Text (Value Text))
chefConfiguration :: Stack -> Maybe ChefConfigurationProperty
cloneAppIds :: Stack -> Maybe (ValueList Text)
clonePermissions :: Stack -> Maybe (Value Bool)
configurationManager :: Stack -> Maybe StackConfigurationManagerProperty
customCookbooksSource :: Stack -> Maybe SourceProperty
customJson :: Stack -> Maybe Object
defaultAvailabilityZone :: Stack -> Maybe (Value Text)
defaultInstanceProfileArn :: Stack -> Value Text
defaultOs :: Stack -> Maybe (Value Text)
defaultRootDeviceType :: Stack -> Maybe (Value Text)
defaultSshKeyName :: Stack -> Maybe (Value Text)
defaultSubnetId :: Stack -> Maybe (Value Text)
ecsClusterArn :: Stack -> Maybe (Value Text)
elasticIps :: Stack -> Maybe [ElasticIpProperty]
hostnameTheme :: Stack -> Maybe (Value Text)
name :: Stack -> Value Text
rdsDbInstances :: Stack -> Maybe [RdsDbInstanceProperty]
serviceRoleArn :: Stack -> Value Text
sourceStackId :: Stack -> Maybe (Value Text)
tags :: Stack -> Maybe [Tag]
useCustomCookbooks :: Stack -> Maybe (Value Bool)
useOpsworksSecurityGroups :: Stack -> Maybe (Value Bool)
vpcId :: Stack -> Maybe (Value Text)
haddock_workaround_ :: ()
agentVersion :: Maybe (Value Text)
attributes :: Maybe (Map Text (Value Text))
chefConfiguration :: Maybe ChefConfigurationProperty
cloneAppIds :: Maybe (ValueList Text)
clonePermissions :: Maybe (Value Bool)
configurationManager :: Maybe StackConfigurationManagerProperty
customCookbooksSource :: Maybe SourceProperty
customJson :: Maybe Object
defaultAvailabilityZone :: Maybe (Value Text)
defaultInstanceProfileArn :: Value Text
defaultOs :: Maybe (Value Text)
defaultRootDeviceType :: Maybe (Value Text)
defaultSshKeyName :: Maybe (Value Text)
defaultSubnetId :: Maybe (Value Text)
ecsClusterArn :: Maybe (Value Text)
elasticIps :: Maybe [ElasticIpProperty]
hostnameTheme :: Maybe (Value Text)
name :: Value Text
rdsDbInstances :: Maybe [RdsDbInstanceProperty]
serviceRoleArn :: Value Text
sourceStackId :: Maybe (Value Text)
tags :: Maybe [Tag]
useCustomCookbooks :: Maybe (Value Bool)
useOpsworksSecurityGroups :: Maybe (Value Bool)
vpcId :: Maybe (Value Text)
..} = Stack {tags :: Maybe [Tag]
tags = [Tag] -> Maybe [Tag]
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure [Tag]
PropertyType "Tags" Stack
newValue, Maybe [ElasticIpProperty]
Maybe [RdsDbInstanceProperty]
Maybe Object
Maybe (Map Text (Value Text))
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Text)
Maybe ChefConfigurationProperty
Maybe SourceProperty
Maybe StackConfigurationManagerProperty
()
Value Text
haddock_workaround_ :: ()
agentVersion :: Maybe (Value Text)
attributes :: Maybe (Map Text (Value Text))
chefConfiguration :: Maybe ChefConfigurationProperty
cloneAppIds :: Maybe (ValueList Text)
clonePermissions :: Maybe (Value Bool)
configurationManager :: Maybe StackConfigurationManagerProperty
customCookbooksSource :: Maybe SourceProperty
customJson :: Maybe Object
defaultAvailabilityZone :: Maybe (Value Text)
defaultInstanceProfileArn :: Value Text
defaultOs :: Maybe (Value Text)
defaultRootDeviceType :: Maybe (Value Text)
defaultSshKeyName :: Maybe (Value Text)
defaultSubnetId :: Maybe (Value Text)
ecsClusterArn :: Maybe (Value Text)
elasticIps :: Maybe [ElasticIpProperty]
hostnameTheme :: Maybe (Value Text)
name :: Value Text
rdsDbInstances :: Maybe [RdsDbInstanceProperty]
serviceRoleArn :: Value Text
sourceStackId :: Maybe (Value Text)
useCustomCookbooks :: Maybe (Value Bool)
useOpsworksSecurityGroups :: Maybe (Value Bool)
vpcId :: Maybe (Value Text)
haddock_workaround_ :: ()
agentVersion :: Maybe (Value Text)
attributes :: Maybe (Map Text (Value Text))
chefConfiguration :: Maybe ChefConfigurationProperty
cloneAppIds :: Maybe (ValueList Text)
clonePermissions :: Maybe (Value Bool)
configurationManager :: Maybe StackConfigurationManagerProperty
customCookbooksSource :: Maybe SourceProperty
customJson :: Maybe Object
defaultAvailabilityZone :: Maybe (Value Text)
defaultInstanceProfileArn :: Value Text
defaultOs :: Maybe (Value Text)
defaultRootDeviceType :: Maybe (Value Text)
defaultSshKeyName :: Maybe (Value Text)
defaultSubnetId :: Maybe (Value Text)
ecsClusterArn :: Maybe (Value Text)
elasticIps :: Maybe [ElasticIpProperty]
hostnameTheme :: Maybe (Value Text)
name :: Value Text
rdsDbInstances :: Maybe [RdsDbInstanceProperty]
serviceRoleArn :: Value Text
sourceStackId :: Maybe (Value Text)
useCustomCookbooks :: Maybe (Value Bool)
useOpsworksSecurityGroups :: Maybe (Value Bool)
vpcId :: Maybe (Value Text)
..}
instance Property "UseCustomCookbooks" Stack where
type PropertyType "UseCustomCookbooks" Stack = Value Prelude.Bool
set :: PropertyType "UseCustomCookbooks" Stack -> Stack -> Stack
set PropertyType "UseCustomCookbooks" Stack
newValue Stack {Maybe [Tag]
Maybe [ElasticIpProperty]
Maybe [RdsDbInstanceProperty]
Maybe Object
Maybe (Map Text (Value Text))
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Text)
Maybe ChefConfigurationProperty
Maybe SourceProperty
Maybe StackConfigurationManagerProperty
()
Value Text
haddock_workaround_ :: Stack -> ()
agentVersion :: Stack -> Maybe (Value Text)
attributes :: Stack -> Maybe (Map Text (Value Text))
chefConfiguration :: Stack -> Maybe ChefConfigurationProperty
cloneAppIds :: Stack -> Maybe (ValueList Text)
clonePermissions :: Stack -> Maybe (Value Bool)
configurationManager :: Stack -> Maybe StackConfigurationManagerProperty
customCookbooksSource :: Stack -> Maybe SourceProperty
customJson :: Stack -> Maybe Object
defaultAvailabilityZone :: Stack -> Maybe (Value Text)
defaultInstanceProfileArn :: Stack -> Value Text
defaultOs :: Stack -> Maybe (Value Text)
defaultRootDeviceType :: Stack -> Maybe (Value Text)
defaultSshKeyName :: Stack -> Maybe (Value Text)
defaultSubnetId :: Stack -> Maybe (Value Text)
ecsClusterArn :: Stack -> Maybe (Value Text)
elasticIps :: Stack -> Maybe [ElasticIpProperty]
hostnameTheme :: Stack -> Maybe (Value Text)
name :: Stack -> Value Text
rdsDbInstances :: Stack -> Maybe [RdsDbInstanceProperty]
serviceRoleArn :: Stack -> Value Text
sourceStackId :: Stack -> Maybe (Value Text)
tags :: Stack -> Maybe [Tag]
useCustomCookbooks :: Stack -> Maybe (Value Bool)
useOpsworksSecurityGroups :: Stack -> Maybe (Value Bool)
vpcId :: Stack -> Maybe (Value Text)
haddock_workaround_ :: ()
agentVersion :: Maybe (Value Text)
attributes :: Maybe (Map Text (Value Text))
chefConfiguration :: Maybe ChefConfigurationProperty
cloneAppIds :: Maybe (ValueList Text)
clonePermissions :: Maybe (Value Bool)
configurationManager :: Maybe StackConfigurationManagerProperty
customCookbooksSource :: Maybe SourceProperty
customJson :: Maybe Object
defaultAvailabilityZone :: Maybe (Value Text)
defaultInstanceProfileArn :: Value Text
defaultOs :: Maybe (Value Text)
defaultRootDeviceType :: Maybe (Value Text)
defaultSshKeyName :: Maybe (Value Text)
defaultSubnetId :: Maybe (Value Text)
ecsClusterArn :: Maybe (Value Text)
elasticIps :: Maybe [ElasticIpProperty]
hostnameTheme :: Maybe (Value Text)
name :: Value Text
rdsDbInstances :: Maybe [RdsDbInstanceProperty]
serviceRoleArn :: Value Text
sourceStackId :: Maybe (Value Text)
tags :: Maybe [Tag]
useCustomCookbooks :: Maybe (Value Bool)
useOpsworksSecurityGroups :: Maybe (Value Bool)
vpcId :: Maybe (Value Text)
..}
= Stack {useCustomCookbooks :: Maybe (Value Bool)
useCustomCookbooks = Value Bool -> Maybe (Value Bool)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "UseCustomCookbooks" Stack
Value Bool
newValue, Maybe [Tag]
Maybe [ElasticIpProperty]
Maybe [RdsDbInstanceProperty]
Maybe Object
Maybe (Map Text (Value Text))
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Text)
Maybe ChefConfigurationProperty
Maybe SourceProperty
Maybe StackConfigurationManagerProperty
()
Value Text
haddock_workaround_ :: ()
agentVersion :: Maybe (Value Text)
attributes :: Maybe (Map Text (Value Text))
chefConfiguration :: Maybe ChefConfigurationProperty
cloneAppIds :: Maybe (ValueList Text)
clonePermissions :: Maybe (Value Bool)
configurationManager :: Maybe StackConfigurationManagerProperty
customCookbooksSource :: Maybe SourceProperty
customJson :: Maybe Object
defaultAvailabilityZone :: Maybe (Value Text)
defaultInstanceProfileArn :: Value Text
defaultOs :: Maybe (Value Text)
defaultRootDeviceType :: Maybe (Value Text)
defaultSshKeyName :: Maybe (Value Text)
defaultSubnetId :: Maybe (Value Text)
ecsClusterArn :: Maybe (Value Text)
elasticIps :: Maybe [ElasticIpProperty]
hostnameTheme :: Maybe (Value Text)
name :: Value Text
rdsDbInstances :: Maybe [RdsDbInstanceProperty]
serviceRoleArn :: Value Text
sourceStackId :: Maybe (Value Text)
tags :: Maybe [Tag]
useOpsworksSecurityGroups :: Maybe (Value Bool)
vpcId :: Maybe (Value Text)
haddock_workaround_ :: ()
agentVersion :: Maybe (Value Text)
attributes :: Maybe (Map Text (Value Text))
chefConfiguration :: Maybe ChefConfigurationProperty
cloneAppIds :: Maybe (ValueList Text)
clonePermissions :: Maybe (Value Bool)
configurationManager :: Maybe StackConfigurationManagerProperty
customCookbooksSource :: Maybe SourceProperty
customJson :: Maybe Object
defaultAvailabilityZone :: Maybe (Value Text)
defaultInstanceProfileArn :: Value Text
defaultOs :: Maybe (Value Text)
defaultRootDeviceType :: Maybe (Value Text)
defaultSshKeyName :: Maybe (Value Text)
defaultSubnetId :: Maybe (Value Text)
ecsClusterArn :: Maybe (Value Text)
elasticIps :: Maybe [ElasticIpProperty]
hostnameTheme :: Maybe (Value Text)
name :: Value Text
rdsDbInstances :: Maybe [RdsDbInstanceProperty]
serviceRoleArn :: Value Text
sourceStackId :: Maybe (Value Text)
tags :: Maybe [Tag]
useOpsworksSecurityGroups :: Maybe (Value Bool)
vpcId :: Maybe (Value Text)
..}
instance Property "UseOpsworksSecurityGroups" Stack where
type PropertyType "UseOpsworksSecurityGroups" Stack = Value Prelude.Bool
set :: PropertyType "UseOpsworksSecurityGroups" Stack -> Stack -> Stack
set PropertyType "UseOpsworksSecurityGroups" Stack
newValue Stack {Maybe [Tag]
Maybe [ElasticIpProperty]
Maybe [RdsDbInstanceProperty]
Maybe Object
Maybe (Map Text (Value Text))
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Text)
Maybe ChefConfigurationProperty
Maybe SourceProperty
Maybe StackConfigurationManagerProperty
()
Value Text
haddock_workaround_ :: Stack -> ()
agentVersion :: Stack -> Maybe (Value Text)
attributes :: Stack -> Maybe (Map Text (Value Text))
chefConfiguration :: Stack -> Maybe ChefConfigurationProperty
cloneAppIds :: Stack -> Maybe (ValueList Text)
clonePermissions :: Stack -> Maybe (Value Bool)
configurationManager :: Stack -> Maybe StackConfigurationManagerProperty
customCookbooksSource :: Stack -> Maybe SourceProperty
customJson :: Stack -> Maybe Object
defaultAvailabilityZone :: Stack -> Maybe (Value Text)
defaultInstanceProfileArn :: Stack -> Value Text
defaultOs :: Stack -> Maybe (Value Text)
defaultRootDeviceType :: Stack -> Maybe (Value Text)
defaultSshKeyName :: Stack -> Maybe (Value Text)
defaultSubnetId :: Stack -> Maybe (Value Text)
ecsClusterArn :: Stack -> Maybe (Value Text)
elasticIps :: Stack -> Maybe [ElasticIpProperty]
hostnameTheme :: Stack -> Maybe (Value Text)
name :: Stack -> Value Text
rdsDbInstances :: Stack -> Maybe [RdsDbInstanceProperty]
serviceRoleArn :: Stack -> Value Text
sourceStackId :: Stack -> Maybe (Value Text)
tags :: Stack -> Maybe [Tag]
useCustomCookbooks :: Stack -> Maybe (Value Bool)
useOpsworksSecurityGroups :: Stack -> Maybe (Value Bool)
vpcId :: Stack -> Maybe (Value Text)
haddock_workaround_ :: ()
agentVersion :: Maybe (Value Text)
attributes :: Maybe (Map Text (Value Text))
chefConfiguration :: Maybe ChefConfigurationProperty
cloneAppIds :: Maybe (ValueList Text)
clonePermissions :: Maybe (Value Bool)
configurationManager :: Maybe StackConfigurationManagerProperty
customCookbooksSource :: Maybe SourceProperty
customJson :: Maybe Object
defaultAvailabilityZone :: Maybe (Value Text)
defaultInstanceProfileArn :: Value Text
defaultOs :: Maybe (Value Text)
defaultRootDeviceType :: Maybe (Value Text)
defaultSshKeyName :: Maybe (Value Text)
defaultSubnetId :: Maybe (Value Text)
ecsClusterArn :: Maybe (Value Text)
elasticIps :: Maybe [ElasticIpProperty]
hostnameTheme :: Maybe (Value Text)
name :: Value Text
rdsDbInstances :: Maybe [RdsDbInstanceProperty]
serviceRoleArn :: Value Text
sourceStackId :: Maybe (Value Text)
tags :: Maybe [Tag]
useCustomCookbooks :: Maybe (Value Bool)
useOpsworksSecurityGroups :: Maybe (Value Bool)
vpcId :: Maybe (Value Text)
..}
= Stack {useOpsworksSecurityGroups :: Maybe (Value Bool)
useOpsworksSecurityGroups = Value Bool -> Maybe (Value Bool)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "UseOpsworksSecurityGroups" Stack
Value Bool
newValue, Maybe [Tag]
Maybe [ElasticIpProperty]
Maybe [RdsDbInstanceProperty]
Maybe Object
Maybe (Map Text (Value Text))
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Text)
Maybe ChefConfigurationProperty
Maybe SourceProperty
Maybe StackConfigurationManagerProperty
()
Value Text
haddock_workaround_ :: ()
agentVersion :: Maybe (Value Text)
attributes :: Maybe (Map Text (Value Text))
chefConfiguration :: Maybe ChefConfigurationProperty
cloneAppIds :: Maybe (ValueList Text)
clonePermissions :: Maybe (Value Bool)
configurationManager :: Maybe StackConfigurationManagerProperty
customCookbooksSource :: Maybe SourceProperty
customJson :: Maybe Object
defaultAvailabilityZone :: Maybe (Value Text)
defaultInstanceProfileArn :: Value Text
defaultOs :: Maybe (Value Text)
defaultRootDeviceType :: Maybe (Value Text)
defaultSshKeyName :: Maybe (Value Text)
defaultSubnetId :: Maybe (Value Text)
ecsClusterArn :: Maybe (Value Text)
elasticIps :: Maybe [ElasticIpProperty]
hostnameTheme :: Maybe (Value Text)
name :: Value Text
rdsDbInstances :: Maybe [RdsDbInstanceProperty]
serviceRoleArn :: Value Text
sourceStackId :: Maybe (Value Text)
tags :: Maybe [Tag]
useCustomCookbooks :: Maybe (Value Bool)
vpcId :: Maybe (Value Text)
haddock_workaround_ :: ()
agentVersion :: Maybe (Value Text)
attributes :: Maybe (Map Text (Value Text))
chefConfiguration :: Maybe ChefConfigurationProperty
cloneAppIds :: Maybe (ValueList Text)
clonePermissions :: Maybe (Value Bool)
configurationManager :: Maybe StackConfigurationManagerProperty
customCookbooksSource :: Maybe SourceProperty
customJson :: Maybe Object
defaultAvailabilityZone :: Maybe (Value Text)
defaultInstanceProfileArn :: Value Text
defaultOs :: Maybe (Value Text)
defaultRootDeviceType :: Maybe (Value Text)
defaultSshKeyName :: Maybe (Value Text)
defaultSubnetId :: Maybe (Value Text)
ecsClusterArn :: Maybe (Value Text)
elasticIps :: Maybe [ElasticIpProperty]
hostnameTheme :: Maybe (Value Text)
name :: Value Text
rdsDbInstances :: Maybe [RdsDbInstanceProperty]
serviceRoleArn :: Value Text
sourceStackId :: Maybe (Value Text)
tags :: Maybe [Tag]
useCustomCookbooks :: Maybe (Value Bool)
vpcId :: Maybe (Value Text)
..}
instance Property "VpcId" Stack where
type PropertyType "VpcId" Stack = Value Prelude.Text
set :: PropertyType "VpcId" Stack -> Stack -> Stack
set PropertyType "VpcId" Stack
newValue Stack {Maybe [Tag]
Maybe [ElasticIpProperty]
Maybe [RdsDbInstanceProperty]
Maybe Object
Maybe (Map Text (Value Text))
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Text)
Maybe ChefConfigurationProperty
Maybe SourceProperty
Maybe StackConfigurationManagerProperty
()
Value Text
haddock_workaround_ :: Stack -> ()
agentVersion :: Stack -> Maybe (Value Text)
attributes :: Stack -> Maybe (Map Text (Value Text))
chefConfiguration :: Stack -> Maybe ChefConfigurationProperty
cloneAppIds :: Stack -> Maybe (ValueList Text)
clonePermissions :: Stack -> Maybe (Value Bool)
configurationManager :: Stack -> Maybe StackConfigurationManagerProperty
customCookbooksSource :: Stack -> Maybe SourceProperty
customJson :: Stack -> Maybe Object
defaultAvailabilityZone :: Stack -> Maybe (Value Text)
defaultInstanceProfileArn :: Stack -> Value Text
defaultOs :: Stack -> Maybe (Value Text)
defaultRootDeviceType :: Stack -> Maybe (Value Text)
defaultSshKeyName :: Stack -> Maybe (Value Text)
defaultSubnetId :: Stack -> Maybe (Value Text)
ecsClusterArn :: Stack -> Maybe (Value Text)
elasticIps :: Stack -> Maybe [ElasticIpProperty]
hostnameTheme :: Stack -> Maybe (Value Text)
name :: Stack -> Value Text
rdsDbInstances :: Stack -> Maybe [RdsDbInstanceProperty]
serviceRoleArn :: Stack -> Value Text
sourceStackId :: Stack -> Maybe (Value Text)
tags :: Stack -> Maybe [Tag]
useCustomCookbooks :: Stack -> Maybe (Value Bool)
useOpsworksSecurityGroups :: Stack -> Maybe (Value Bool)
vpcId :: Stack -> Maybe (Value Text)
haddock_workaround_ :: ()
agentVersion :: Maybe (Value Text)
attributes :: Maybe (Map Text (Value Text))
chefConfiguration :: Maybe ChefConfigurationProperty
cloneAppIds :: Maybe (ValueList Text)
clonePermissions :: Maybe (Value Bool)
configurationManager :: Maybe StackConfigurationManagerProperty
customCookbooksSource :: Maybe SourceProperty
customJson :: Maybe Object
defaultAvailabilityZone :: Maybe (Value Text)
defaultInstanceProfileArn :: Value Text
defaultOs :: Maybe (Value Text)
defaultRootDeviceType :: Maybe (Value Text)
defaultSshKeyName :: Maybe (Value Text)
defaultSubnetId :: Maybe (Value Text)
ecsClusterArn :: Maybe (Value Text)
elasticIps :: Maybe [ElasticIpProperty]
hostnameTheme :: Maybe (Value Text)
name :: Value Text
rdsDbInstances :: Maybe [RdsDbInstanceProperty]
serviceRoleArn :: Value Text
sourceStackId :: Maybe (Value Text)
tags :: Maybe [Tag]
useCustomCookbooks :: Maybe (Value Bool)
useOpsworksSecurityGroups :: Maybe (Value Bool)
vpcId :: Maybe (Value Text)
..} = Stack {vpcId :: Maybe (Value Text)
vpcId = Value Text -> Maybe (Value Text)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "VpcId" Stack
Value Text
newValue, Maybe [Tag]
Maybe [ElasticIpProperty]
Maybe [RdsDbInstanceProperty]
Maybe Object
Maybe (Map Text (Value Text))
Maybe (ValueList Text)
Maybe (Value Bool)
Maybe (Value Text)
Maybe ChefConfigurationProperty
Maybe SourceProperty
Maybe StackConfigurationManagerProperty
()
Value Text
haddock_workaround_ :: ()
agentVersion :: Maybe (Value Text)
attributes :: Maybe (Map Text (Value Text))
chefConfiguration :: Maybe ChefConfigurationProperty
cloneAppIds :: Maybe (ValueList Text)
clonePermissions :: Maybe (Value Bool)
configurationManager :: Maybe StackConfigurationManagerProperty
customCookbooksSource :: Maybe SourceProperty
customJson :: Maybe Object
defaultAvailabilityZone :: Maybe (Value Text)
defaultInstanceProfileArn :: Value Text
defaultOs :: Maybe (Value Text)
defaultRootDeviceType :: Maybe (Value Text)
defaultSshKeyName :: Maybe (Value Text)
defaultSubnetId :: Maybe (Value Text)
ecsClusterArn :: Maybe (Value Text)
elasticIps :: Maybe [ElasticIpProperty]
hostnameTheme :: Maybe (Value Text)
name :: Value Text
rdsDbInstances :: Maybe [RdsDbInstanceProperty]
serviceRoleArn :: Value Text
sourceStackId :: Maybe (Value Text)
tags :: Maybe [Tag]
useCustomCookbooks :: Maybe (Value Bool)
useOpsworksSecurityGroups :: Maybe (Value Bool)
haddock_workaround_ :: ()
agentVersion :: Maybe (Value Text)
attributes :: Maybe (Map Text (Value Text))
chefConfiguration :: Maybe ChefConfigurationProperty
cloneAppIds :: Maybe (ValueList Text)
clonePermissions :: Maybe (Value Bool)
configurationManager :: Maybe StackConfigurationManagerProperty
customCookbooksSource :: Maybe SourceProperty
customJson :: Maybe Object
defaultAvailabilityZone :: Maybe (Value Text)
defaultInstanceProfileArn :: Value Text
defaultOs :: Maybe (Value Text)
defaultRootDeviceType :: Maybe (Value Text)
defaultSshKeyName :: Maybe (Value Text)
defaultSubnetId :: Maybe (Value Text)
ecsClusterArn :: Maybe (Value Text)
elasticIps :: Maybe [ElasticIpProperty]
hostnameTheme :: Maybe (Value Text)
name :: Value Text
rdsDbInstances :: Maybe [RdsDbInstanceProperty]
serviceRoleArn :: Value Text
sourceStackId :: Maybe (Value Text)
tags :: Maybe [Tag]
useCustomCookbooks :: Maybe (Value Bool)
useOpsworksSecurityGroups :: Maybe (Value Bool)
..}