amazonka-cloudformation-1.4.2: Amazon CloudFormation SDK.

Copyright(c) 2013-2016 Brendan Hay
LicenseMozilla Public License, v. 2.0.
MaintainerBrendan Hay <brendan.g.hay@gmail.com>
Stabilityauto-generated
Portabilitynon-portable (GHC extensions)
Safe HaskellNone
LanguageHaskell2010

Network.AWS.CloudFormation

Contents

Description

AWS CloudFormation

AWS CloudFormation enables you to create and manage AWS infrastructure deployments predictably and repeatedly. AWS CloudFormation helps you leverage AWS products such as Amazon EC2, EBS, Amazon SNS, ELB, and Auto Scaling to build highly-reliable, highly scalable, cost effective applications without worrying about creating and configuring the underlying AWS infrastructure.

With AWS CloudFormation, you declare all of your resources and dependencies in a template file. The template defines a collection of resources as a single unit called a stack. AWS CloudFormation creates and deletes all member resources of the stack together and manages all dependencies between the resources for you.

For more information about this product, go to the CloudFormation Product Page.

Amazon CloudFormation makes use of other AWS products. If you need additional technical information about a specific AWS product, you can find the product's technical documentation at http://docs.aws.amazon.com/documentation/.

Synopsis

Service Configuration

cloudFormation :: Service Source #

API version '2010-05-15' of the Amazon CloudFormation SDK configuration.

Errors

Error matchers are designed for use with the functions provided by Control.Exception.Lens. This allows catching (and rethrowing) service specific errors returned by CloudFormation.

ChangeSetNotFoundException

_ChangeSetNotFoundException :: AsError a => Getting (First ServiceError) a ServiceError Source #

The specified change set name or ID doesn't exit. To view valid change sets for a stack, use the ListChangeSets action.

InvalidChangeSetStatusException

_InvalidChangeSetStatusException :: AsError a => Getting (First ServiceError) a ServiceError Source #

The specified change set cannot be used to update the stack. For example, the change set status might be CREATE_IN_PROGRESS or the stack status might be UPDATE_IN_PROGRESS.

InsufficientCapabilitiesException

_InsufficientCapabilitiesException :: AsError a => Getting (First ServiceError) a ServiceError Source #

The template contains resources with capabilities that were not specified in the Capabilities parameter.

AlreadyExistsException

_AlreadyExistsException :: AsError a => Getting (First ServiceError) a ServiceError Source #

Resource with the name requested already exists.

LimitExceededException

_LimitExceededException :: AsError a => Getting (First ServiceError) a ServiceError Source #

Quota for the resource has already been reached.

Waiters

Waiters poll by repeatedly sending a request until some remote success condition configured by the Wait specification is fulfilled. The Wait specification determines how many attempts should be made, in addition to delay and retry strategies.

StackCreateComplete

stackCreateComplete :: Wait DescribeStacks Source #

Polls DescribeStacks every 30 seconds until a successful state is reached. An error is returned after 120 failed checks.

StackUpdateComplete

stackUpdateComplete :: Wait DescribeStacks Source #

Polls DescribeStacks every 30 seconds until a successful state is reached. An error is returned after 120 failed checks.

StackExists

stackExists :: Wait DescribeStacks Source #

Polls DescribeStacks every 5 seconds until a successful state is reached. An error is returned after 20 failed checks.

StackDeleteComplete

stackDeleteComplete :: Wait DescribeStacks Source #

Polls DescribeStacks every 30 seconds until a successful state is reached. An error is returned after 120 failed checks.

Operations

Some AWS operations return results that are incomplete and require subsequent requests in order to obtain the entire result set. The process of sending subsequent requests to continue where a previous request left off is called pagination. For example, the ListObjects operation of Amazon S3 returns up to 1000 objects at a time, and you must send subsequent requests with the appropriate Marker in order to retrieve the next page of results.

Operations that have an AWSPager instance can transparently perform subsequent requests, correctly setting Markers and other request facets to iterate through the entire result set of a truncated API operation. Operations which support this have an additional note in the documentation.

Many operations have the ability to filter results on the server side. See the individual operation parameters for details.

DeleteStack

UpdateStack

GetTemplateSummary

ListChangeSets

ListStackResources (Paginated)

GetStackPolicy

DescribeStacks (Paginated)

CreateChangeSet

ExecuteChangeSet

ContinueUpdateRollback

ValidateTemplate

CancelUpdateStack

DescribeStackEvents (Paginated)

SignalResource

SetStackPolicy

ListStacks (Paginated)

DescribeAccountLimits

DescribeStackResources

CreateStack

EstimateTemplateCost

DeleteChangeSet

GetTemplate

DescribeChangeSet

DescribeStackResource

Types

Capability

data Capability Source #

Constructors

CapabilityIAM 

Instances

Bounded Capability Source # 
Enum Capability Source # 
Eq Capability Source # 
Data Capability Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Capability -> c Capability #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Capability #

toConstr :: Capability -> Constr #

dataTypeOf :: Capability -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Capability) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Capability) #

gmapT :: (forall b. Data b => b -> b) -> Capability -> Capability #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Capability -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Capability -> r #

gmapQ :: (forall d. Data d => d -> u) -> Capability -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Capability -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Capability -> m Capability #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Capability -> m Capability #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Capability -> m Capability #

Ord Capability Source # 
Read Capability Source # 
Show Capability Source # 
Generic Capability Source # 

Associated Types

type Rep Capability :: * -> * #

Hashable Capability Source # 
NFData Capability Source # 

Methods

rnf :: Capability -> () #

FromXML Capability Source # 
ToQuery Capability Source # 
ToHeader Capability Source # 
ToByteString Capability Source # 
FromText Capability Source # 
ToText Capability Source # 

Methods

toText :: Capability -> Text #

type Rep Capability Source # 
type Rep Capability = D1 (MetaData "Capability" "Network.AWS.CloudFormation.Types.Sum" "amazonka-cloudformation-1.4.2-3voa5o7VdaaGgHhcqNcvoX" False) (C1 (MetaCons "CapabilityIAM" PrefixI False) U1)

ChangeAction

data ChangeAction Source #

Constructors

Add 
Modify 
Remove 

Instances

Bounded ChangeAction Source # 
Enum ChangeAction Source # 
Eq ChangeAction Source # 
Data ChangeAction Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ChangeAction -> c ChangeAction #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ChangeAction #

toConstr :: ChangeAction -> Constr #

dataTypeOf :: ChangeAction -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c ChangeAction) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ChangeAction) #

gmapT :: (forall b. Data b => b -> b) -> ChangeAction -> ChangeAction #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ChangeAction -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ChangeAction -> r #

gmapQ :: (forall d. Data d => d -> u) -> ChangeAction -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ChangeAction -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ChangeAction -> m ChangeAction #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ChangeAction -> m ChangeAction #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ChangeAction -> m ChangeAction #

Ord ChangeAction Source # 
Read ChangeAction Source # 
Show ChangeAction Source # 
Generic ChangeAction Source # 

Associated Types

type Rep ChangeAction :: * -> * #

Hashable ChangeAction Source # 
NFData ChangeAction Source # 

Methods

rnf :: ChangeAction -> () #

FromXML ChangeAction Source # 
ToQuery ChangeAction Source # 
ToHeader ChangeAction Source # 
ToByteString ChangeAction Source # 
FromText ChangeAction Source # 
ToText ChangeAction Source # 

Methods

toText :: ChangeAction -> Text #

type Rep ChangeAction Source # 
type Rep ChangeAction = D1 (MetaData "ChangeAction" "Network.AWS.CloudFormation.Types.Sum" "amazonka-cloudformation-1.4.2-3voa5o7VdaaGgHhcqNcvoX" False) ((:+:) (C1 (MetaCons "Add" PrefixI False) U1) ((:+:) (C1 (MetaCons "Modify" PrefixI False) U1) (C1 (MetaCons "Remove" PrefixI False) U1)))

ChangeSetStatus

data ChangeSetStatus Source #

Instances

Bounded ChangeSetStatus Source # 
Enum ChangeSetStatus Source # 
Eq ChangeSetStatus Source # 
Data ChangeSetStatus Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ChangeSetStatus -> c ChangeSetStatus #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ChangeSetStatus #

toConstr :: ChangeSetStatus -> Constr #

dataTypeOf :: ChangeSetStatus -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c ChangeSetStatus) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ChangeSetStatus) #

gmapT :: (forall b. Data b => b -> b) -> ChangeSetStatus -> ChangeSetStatus #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ChangeSetStatus -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ChangeSetStatus -> r #

gmapQ :: (forall d. Data d => d -> u) -> ChangeSetStatus -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ChangeSetStatus -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ChangeSetStatus -> m ChangeSetStatus #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ChangeSetStatus -> m ChangeSetStatus #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ChangeSetStatus -> m ChangeSetStatus #

Ord ChangeSetStatus Source # 
Read ChangeSetStatus Source # 
Show ChangeSetStatus Source # 
Generic ChangeSetStatus Source # 
Hashable ChangeSetStatus Source # 
NFData ChangeSetStatus Source # 

Methods

rnf :: ChangeSetStatus -> () #

FromXML ChangeSetStatus Source # 
ToQuery ChangeSetStatus Source # 
ToHeader ChangeSetStatus Source # 
ToByteString ChangeSetStatus Source # 
FromText ChangeSetStatus Source # 
ToText ChangeSetStatus Source # 
type Rep ChangeSetStatus Source # 
type Rep ChangeSetStatus = D1 (MetaData "ChangeSetStatus" "Network.AWS.CloudFormation.Types.Sum" "amazonka-cloudformation-1.4.2-3voa5o7VdaaGgHhcqNcvoX" False) ((:+:) ((:+:) (C1 (MetaCons "CSSCreateComplete" PrefixI False) U1) (C1 (MetaCons "CSSCreateInProgress" PrefixI False) U1)) ((:+:) (C1 (MetaCons "CSSCreatePending" PrefixI False) U1) ((:+:) (C1 (MetaCons "CSSDeleteComplete" PrefixI False) U1) (C1 (MetaCons "CSSFailed" PrefixI False) U1))))

ChangeSource

data ChangeSource Source #

Instances

Bounded ChangeSource Source # 
Enum ChangeSource Source # 
Eq ChangeSource Source # 
Data ChangeSource Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ChangeSource -> c ChangeSource #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ChangeSource #

toConstr :: ChangeSource -> Constr #

dataTypeOf :: ChangeSource -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c ChangeSource) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ChangeSource) #

gmapT :: (forall b. Data b => b -> b) -> ChangeSource -> ChangeSource #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ChangeSource -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ChangeSource -> r #

gmapQ :: (forall d. Data d => d -> u) -> ChangeSource -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ChangeSource -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ChangeSource -> m ChangeSource #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ChangeSource -> m ChangeSource #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ChangeSource -> m ChangeSource #

Ord ChangeSource Source # 
Read ChangeSource Source # 
Show ChangeSource Source # 
Generic ChangeSource Source # 

Associated Types

type Rep ChangeSource :: * -> * #

Hashable ChangeSource Source # 
NFData ChangeSource Source # 

Methods

rnf :: ChangeSource -> () #

FromXML ChangeSource Source # 
ToQuery ChangeSource Source # 
ToHeader ChangeSource Source # 
ToByteString ChangeSource Source # 
FromText ChangeSource Source # 
ToText ChangeSource Source # 

Methods

toText :: ChangeSource -> Text #

type Rep ChangeSource Source # 
type Rep ChangeSource = D1 (MetaData "ChangeSource" "Network.AWS.CloudFormation.Types.Sum" "amazonka-cloudformation-1.4.2-3voa5o7VdaaGgHhcqNcvoX" False) ((:+:) ((:+:) (C1 (MetaCons "Automatic" PrefixI False) U1) (C1 (MetaCons "DirectModification" PrefixI False) U1)) ((:+:) (C1 (MetaCons "ParameterReference" PrefixI False) U1) ((:+:) (C1 (MetaCons "ResourceAttribute" PrefixI False) U1) (C1 (MetaCons "ResourceReference" PrefixI False) U1))))

ChangeType

data ChangeType Source #

Constructors

Resource 

Instances

Bounded ChangeType Source # 
Enum ChangeType Source # 
Eq ChangeType Source # 
Data ChangeType Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ChangeType -> c ChangeType #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ChangeType #

toConstr :: ChangeType -> Constr #

dataTypeOf :: ChangeType -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c ChangeType) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ChangeType) #

gmapT :: (forall b. Data b => b -> b) -> ChangeType -> ChangeType #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ChangeType -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ChangeType -> r #

gmapQ :: (forall d. Data d => d -> u) -> ChangeType -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ChangeType -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ChangeType -> m ChangeType #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ChangeType -> m ChangeType #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ChangeType -> m ChangeType #

Ord ChangeType Source # 
Read ChangeType Source # 
Show ChangeType Source # 
Generic ChangeType Source # 

Associated Types

type Rep ChangeType :: * -> * #

Hashable ChangeType Source # 
NFData ChangeType Source # 

Methods

rnf :: ChangeType -> () #

FromXML ChangeType Source # 
ToQuery ChangeType Source # 
ToHeader ChangeType Source # 
ToByteString ChangeType Source # 
FromText ChangeType Source # 
ToText ChangeType Source # 

Methods

toText :: ChangeType -> Text #

type Rep ChangeType Source # 
type Rep ChangeType = D1 (MetaData "ChangeType" "Network.AWS.CloudFormation.Types.Sum" "amazonka-cloudformation-1.4.2-3voa5o7VdaaGgHhcqNcvoX" False) (C1 (MetaCons "Resource" PrefixI False) U1)

EvaluationType

data EvaluationType Source #

Constructors

Dynamic 
Static 

Instances

Bounded EvaluationType Source # 
Enum EvaluationType Source # 
Eq EvaluationType Source # 
Data EvaluationType Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> EvaluationType -> c EvaluationType #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c EvaluationType #

toConstr :: EvaluationType -> Constr #

dataTypeOf :: EvaluationType -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c EvaluationType) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c EvaluationType) #

gmapT :: (forall b. Data b => b -> b) -> EvaluationType -> EvaluationType #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> EvaluationType -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> EvaluationType -> r #

gmapQ :: (forall d. Data d => d -> u) -> EvaluationType -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> EvaluationType -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> EvaluationType -> m EvaluationType #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> EvaluationType -> m EvaluationType #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> EvaluationType -> m EvaluationType #

Ord EvaluationType Source # 
Read EvaluationType Source # 
Show EvaluationType Source # 
Generic EvaluationType Source # 

Associated Types

type Rep EvaluationType :: * -> * #

Hashable EvaluationType Source # 
NFData EvaluationType Source # 

Methods

rnf :: EvaluationType -> () #

FromXML EvaluationType Source # 
ToQuery EvaluationType Source # 
ToHeader EvaluationType Source # 
ToByteString EvaluationType Source # 
FromText EvaluationType Source # 
ToText EvaluationType Source # 
type Rep EvaluationType Source # 
type Rep EvaluationType = D1 (MetaData "EvaluationType" "Network.AWS.CloudFormation.Types.Sum" "amazonka-cloudformation-1.4.2-3voa5o7VdaaGgHhcqNcvoX" False) ((:+:) (C1 (MetaCons "Dynamic" PrefixI False) U1) (C1 (MetaCons "Static" PrefixI False) U1))

OnFailure

data OnFailure Source #

Constructors

Delete 
DoNothing 
Rollback 

Instances

Bounded OnFailure Source # 
Enum OnFailure Source # 
Eq OnFailure Source # 
Data OnFailure Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> OnFailure -> c OnFailure #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c OnFailure #

toConstr :: OnFailure -> Constr #

dataTypeOf :: OnFailure -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c OnFailure) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c OnFailure) #

gmapT :: (forall b. Data b => b -> b) -> OnFailure -> OnFailure #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> OnFailure -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> OnFailure -> r #

gmapQ :: (forall d. Data d => d -> u) -> OnFailure -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> OnFailure -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> OnFailure -> m OnFailure #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> OnFailure -> m OnFailure #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> OnFailure -> m OnFailure #

Ord OnFailure Source # 
Read OnFailure Source # 
Show OnFailure Source # 
Generic OnFailure Source # 

Associated Types

type Rep OnFailure :: * -> * #

Hashable OnFailure Source # 
NFData OnFailure Source # 

Methods

rnf :: OnFailure -> () #

ToQuery OnFailure Source # 
ToHeader OnFailure Source # 
ToByteString OnFailure Source # 

Methods

toBS :: OnFailure -> ByteString #

FromText OnFailure Source # 
ToText OnFailure Source # 

Methods

toText :: OnFailure -> Text #

type Rep OnFailure Source # 
type Rep OnFailure = D1 (MetaData "OnFailure" "Network.AWS.CloudFormation.Types.Sum" "amazonka-cloudformation-1.4.2-3voa5o7VdaaGgHhcqNcvoX" False) ((:+:) (C1 (MetaCons "Delete" PrefixI False) U1) ((:+:) (C1 (MetaCons "DoNothing" PrefixI False) U1) (C1 (MetaCons "Rollback" PrefixI False) U1)))

Replacement

data Replacement Source #

Constructors

Conditional 
False' 
True' 

Instances

Bounded Replacement Source # 
Enum Replacement Source # 
Eq Replacement Source # 
Data Replacement Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Replacement -> c Replacement #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Replacement #

toConstr :: Replacement -> Constr #

dataTypeOf :: Replacement -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Replacement) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Replacement) #

gmapT :: (forall b. Data b => b -> b) -> Replacement -> Replacement #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Replacement -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Replacement -> r #

gmapQ :: (forall d. Data d => d -> u) -> Replacement -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Replacement -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Replacement -> m Replacement #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Replacement -> m Replacement #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Replacement -> m Replacement #

Ord Replacement Source # 
Read Replacement Source # 
Show Replacement Source # 
Generic Replacement Source # 

Associated Types

type Rep Replacement :: * -> * #

Hashable Replacement Source # 
NFData Replacement Source # 

Methods

rnf :: Replacement -> () #

FromXML Replacement Source # 
ToQuery Replacement Source # 
ToHeader Replacement Source # 
ToByteString Replacement Source # 
FromText Replacement Source # 
ToText Replacement Source # 

Methods

toText :: Replacement -> Text #

type Rep Replacement Source # 
type Rep Replacement = D1 (MetaData "Replacement" "Network.AWS.CloudFormation.Types.Sum" "amazonka-cloudformation-1.4.2-3voa5o7VdaaGgHhcqNcvoX" False) ((:+:) (C1 (MetaCons "Conditional" PrefixI False) U1) ((:+:) (C1 (MetaCons "False'" PrefixI False) U1) (C1 (MetaCons "True'" PrefixI False) U1)))

RequiresRecreation

data RequiresRecreation Source #

Constructors

Always 
Conditionally 
Never 

Instances

Bounded RequiresRecreation Source # 
Enum RequiresRecreation Source # 
Eq RequiresRecreation Source # 
Data RequiresRecreation Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> RequiresRecreation -> c RequiresRecreation #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c RequiresRecreation #

toConstr :: RequiresRecreation -> Constr #

dataTypeOf :: RequiresRecreation -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c RequiresRecreation) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c RequiresRecreation) #

gmapT :: (forall b. Data b => b -> b) -> RequiresRecreation -> RequiresRecreation #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> RequiresRecreation -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> RequiresRecreation -> r #

gmapQ :: (forall d. Data d => d -> u) -> RequiresRecreation -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> RequiresRecreation -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> RequiresRecreation -> m RequiresRecreation #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> RequiresRecreation -> m RequiresRecreation #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> RequiresRecreation -> m RequiresRecreation #

Ord RequiresRecreation Source # 
Read RequiresRecreation Source # 
Show RequiresRecreation Source # 
Generic RequiresRecreation Source # 
Hashable RequiresRecreation Source # 
NFData RequiresRecreation Source # 

Methods

rnf :: RequiresRecreation -> () #

FromXML RequiresRecreation Source # 
ToQuery RequiresRecreation Source # 
ToHeader RequiresRecreation Source # 
ToByteString RequiresRecreation Source # 
FromText RequiresRecreation Source # 
ToText RequiresRecreation Source # 
type Rep RequiresRecreation Source # 
type Rep RequiresRecreation = D1 (MetaData "RequiresRecreation" "Network.AWS.CloudFormation.Types.Sum" "amazonka-cloudformation-1.4.2-3voa5o7VdaaGgHhcqNcvoX" False) ((:+:) (C1 (MetaCons "Always" PrefixI False) U1) ((:+:) (C1 (MetaCons "Conditionally" PrefixI False) U1) (C1 (MetaCons "Never" PrefixI False) U1)))

ResourceAttribute

data ResourceAttribute Source #

Instances

Bounded ResourceAttribute Source # 
Enum ResourceAttribute Source # 
Eq ResourceAttribute Source # 
Data ResourceAttribute Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ResourceAttribute -> c ResourceAttribute #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ResourceAttribute #

toConstr :: ResourceAttribute -> Constr #

dataTypeOf :: ResourceAttribute -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c ResourceAttribute) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ResourceAttribute) #

gmapT :: (forall b. Data b => b -> b) -> ResourceAttribute -> ResourceAttribute #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ResourceAttribute -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ResourceAttribute -> r #

gmapQ :: (forall d. Data d => d -> u) -> ResourceAttribute -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ResourceAttribute -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ResourceAttribute -> m ResourceAttribute #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ResourceAttribute -> m ResourceAttribute #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ResourceAttribute -> m ResourceAttribute #

Ord ResourceAttribute Source # 
Read ResourceAttribute Source # 
Show ResourceAttribute Source # 
Generic ResourceAttribute Source # 
Hashable ResourceAttribute Source # 
NFData ResourceAttribute Source # 

Methods

rnf :: ResourceAttribute -> () #

FromXML ResourceAttribute Source # 
ToQuery ResourceAttribute Source # 
ToHeader ResourceAttribute Source # 
ToByteString ResourceAttribute Source # 
FromText ResourceAttribute Source # 
ToText ResourceAttribute Source # 
type Rep ResourceAttribute Source # 
type Rep ResourceAttribute = D1 (MetaData "ResourceAttribute" "Network.AWS.CloudFormation.Types.Sum" "amazonka-cloudformation-1.4.2-3voa5o7VdaaGgHhcqNcvoX" False) ((:+:) ((:+:) (C1 (MetaCons "CreationPolicy" PrefixI False) U1) ((:+:) (C1 (MetaCons "DeletionPolicy" PrefixI False) U1) (C1 (MetaCons "Metadata" PrefixI False) U1))) ((:+:) (C1 (MetaCons "Properties" PrefixI False) U1) ((:+:) (C1 (MetaCons "Tags" PrefixI False) U1) (C1 (MetaCons "UpdatePolicy" PrefixI False) U1))))

ResourceSignalStatus

data ResourceSignalStatus Source #

Constructors

Failure 
Success 

Instances

Bounded ResourceSignalStatus Source # 
Enum ResourceSignalStatus Source # 
Eq ResourceSignalStatus Source # 
Data ResourceSignalStatus Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ResourceSignalStatus -> c ResourceSignalStatus #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ResourceSignalStatus #

toConstr :: ResourceSignalStatus -> Constr #

dataTypeOf :: ResourceSignalStatus -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c ResourceSignalStatus) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ResourceSignalStatus) #

gmapT :: (forall b. Data b => b -> b) -> ResourceSignalStatus -> ResourceSignalStatus #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ResourceSignalStatus -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ResourceSignalStatus -> r #

gmapQ :: (forall d. Data d => d -> u) -> ResourceSignalStatus -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ResourceSignalStatus -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ResourceSignalStatus -> m ResourceSignalStatus #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ResourceSignalStatus -> m ResourceSignalStatus #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ResourceSignalStatus -> m ResourceSignalStatus #

Ord ResourceSignalStatus Source # 
Read ResourceSignalStatus Source # 
Show ResourceSignalStatus Source # 
Generic ResourceSignalStatus Source # 
Hashable ResourceSignalStatus Source # 
NFData ResourceSignalStatus Source # 

Methods

rnf :: ResourceSignalStatus -> () #

ToQuery ResourceSignalStatus Source # 
ToHeader ResourceSignalStatus Source # 
ToByteString ResourceSignalStatus Source # 
FromText ResourceSignalStatus Source # 
ToText ResourceSignalStatus Source # 
type Rep ResourceSignalStatus Source # 
type Rep ResourceSignalStatus = D1 (MetaData "ResourceSignalStatus" "Network.AWS.CloudFormation.Types.Sum" "amazonka-cloudformation-1.4.2-3voa5o7VdaaGgHhcqNcvoX" False) ((:+:) (C1 (MetaCons "Failure" PrefixI False) U1) (C1 (MetaCons "Success" PrefixI False) U1))

ResourceStatus

data ResourceStatus Source #

Instances

Bounded ResourceStatus Source # 
Enum ResourceStatus Source # 
Eq ResourceStatus Source # 
Data ResourceStatus Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ResourceStatus -> c ResourceStatus #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ResourceStatus #

toConstr :: ResourceStatus -> Constr #

dataTypeOf :: ResourceStatus -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c ResourceStatus) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ResourceStatus) #

gmapT :: (forall b. Data b => b -> b) -> ResourceStatus -> ResourceStatus #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ResourceStatus -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ResourceStatus -> r #

gmapQ :: (forall d. Data d => d -> u) -> ResourceStatus -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ResourceStatus -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ResourceStatus -> m ResourceStatus #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ResourceStatus -> m ResourceStatus #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ResourceStatus -> m ResourceStatus #

Ord ResourceStatus Source # 
Read ResourceStatus Source # 
Show ResourceStatus Source # 
Generic ResourceStatus Source # 

Associated Types

type Rep ResourceStatus :: * -> * #

Hashable ResourceStatus Source # 
NFData ResourceStatus Source # 

Methods

rnf :: ResourceStatus -> () #

FromXML ResourceStatus Source # 
ToQuery ResourceStatus Source # 
ToHeader ResourceStatus Source # 
ToByteString ResourceStatus Source # 
FromText ResourceStatus Source # 
ToText ResourceStatus Source # 
type Rep ResourceStatus Source # 
type Rep ResourceStatus = D1 (MetaData "ResourceStatus" "Network.AWS.CloudFormation.Types.Sum" "amazonka-cloudformation-1.4.2-3voa5o7VdaaGgHhcqNcvoX" False) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "CreateComplete" PrefixI False) U1) (C1 (MetaCons "CreateFailed" PrefixI False) U1)) ((:+:) (C1 (MetaCons "CreateInProgress" PrefixI False) U1) ((:+:) (C1 (MetaCons "DeleteComplete" PrefixI False) U1) (C1 (MetaCons "DeleteFailed" PrefixI False) U1)))) ((:+:) ((:+:) (C1 (MetaCons "DeleteInProgress" PrefixI False) U1) (C1 (MetaCons "DeleteSkipped" PrefixI False) U1)) ((:+:) (C1 (MetaCons "UpdateComplete" PrefixI False) U1) ((:+:) (C1 (MetaCons "UpdateFailed" PrefixI False) U1) (C1 (MetaCons "UpdateInProgress" PrefixI False) U1)))))

StackStatus

data StackStatus Source #

Instances

Bounded StackStatus Source # 
Enum StackStatus Source # 
Eq StackStatus Source # 
Data StackStatus Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> StackStatus -> c StackStatus #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c StackStatus #

toConstr :: StackStatus -> Constr #

dataTypeOf :: StackStatus -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c StackStatus) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c StackStatus) #

gmapT :: (forall b. Data b => b -> b) -> StackStatus -> StackStatus #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> StackStatus -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> StackStatus -> r #

gmapQ :: (forall d. Data d => d -> u) -> StackStatus -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> StackStatus -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> StackStatus -> m StackStatus #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> StackStatus -> m StackStatus #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> StackStatus -> m StackStatus #

Ord StackStatus Source # 
Read StackStatus Source # 
Show StackStatus Source # 
Generic StackStatus Source # 

Associated Types

type Rep StackStatus :: * -> * #

Hashable StackStatus Source # 
NFData StackStatus Source # 

Methods

rnf :: StackStatus -> () #

FromXML StackStatus Source # 
ToQuery StackStatus Source # 
ToHeader StackStatus Source # 
ToByteString StackStatus Source # 
FromText StackStatus Source # 
ToText StackStatus Source # 

Methods

toText :: StackStatus -> Text #

type Rep StackStatus Source # 
type Rep StackStatus = D1 (MetaData "StackStatus" "Network.AWS.CloudFormation.Types.Sum" "amazonka-cloudformation-1.4.2-3voa5o7VdaaGgHhcqNcvoX" False) ((:+:) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "SSCreateComplete" PrefixI False) U1) (C1 (MetaCons "SSCreateFailed" PrefixI False) U1)) ((:+:) (C1 (MetaCons "SSCreateInProgress" PrefixI False) U1) (C1 (MetaCons "SSDeleteComplete" PrefixI False) U1))) ((:+:) ((:+:) (C1 (MetaCons "SSDeleteFailed" PrefixI False) U1) (C1 (MetaCons "SSDeleteInProgress" PrefixI False) U1)) ((:+:) (C1 (MetaCons "SSRollbackComplete" PrefixI False) U1) (C1 (MetaCons "SSRollbackFailed" PrefixI False) U1)))) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "SSRollbackInProgress" PrefixI False) U1) (C1 (MetaCons "SSUpdateComplete" PrefixI False) U1)) ((:+:) (C1 (MetaCons "SSUpdateCompleteCleanupInProgress" PrefixI False) U1) (C1 (MetaCons "SSUpdateInProgress" PrefixI False) U1))) ((:+:) ((:+:) (C1 (MetaCons "SSUpdateRollbackComplete" PrefixI False) U1) (C1 (MetaCons "SSUpdateRollbackCompleteCleanupInProgress" PrefixI False) U1)) ((:+:) (C1 (MetaCons "SSUpdateRollbackFailed" PrefixI False) U1) (C1 (MetaCons "SSUpdateRollbackInProgress" PrefixI False) U1)))))

AccountLimit

data AccountLimit Source #

The AccountLimit data type.

See: accountLimit smart constructor.

Instances

Eq AccountLimit Source # 
Data AccountLimit Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> AccountLimit -> c AccountLimit #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c AccountLimit #

toConstr :: AccountLimit -> Constr #

dataTypeOf :: AccountLimit -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c AccountLimit) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c AccountLimit) #

gmapT :: (forall b. Data b => b -> b) -> AccountLimit -> AccountLimit #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> AccountLimit -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> AccountLimit -> r #

gmapQ :: (forall d. Data d => d -> u) -> AccountLimit -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> AccountLimit -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> AccountLimit -> m AccountLimit #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> AccountLimit -> m AccountLimit #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> AccountLimit -> m AccountLimit #

Read AccountLimit Source # 
Show AccountLimit Source # 
Generic AccountLimit Source # 

Associated Types

type Rep AccountLimit :: * -> * #

Hashable AccountLimit Source # 
NFData AccountLimit Source # 

Methods

rnf :: AccountLimit -> () #

FromXML AccountLimit Source # 
type Rep AccountLimit Source # 
type Rep AccountLimit = D1 (MetaData "AccountLimit" "Network.AWS.CloudFormation.Types.Product" "amazonka-cloudformation-1.4.2-3voa5o7VdaaGgHhcqNcvoX" False) (C1 (MetaCons "AccountLimit'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_alValue") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Int))) (S1 (MetaSel (Just Symbol "_alName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))))

accountLimit :: AccountLimit Source #

Creates a value of AccountLimit with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

alValue :: Lens' AccountLimit (Maybe Int) Source #

The value that is associated with the account limit name.

alName :: Lens' AccountLimit (Maybe Text) Source #

The name of the account limit. Currently, the only account limit is StackLimit.

Change

data Change Source #

The Change structure describes the changes AWS CloudFormation will perform if you execute the change set.

See: change smart constructor.

Instances

Eq Change Source # 

Methods

(==) :: Change -> Change -> Bool #

(/=) :: Change -> Change -> Bool #

Data Change Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Change -> c Change #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Change #

toConstr :: Change -> Constr #

dataTypeOf :: Change -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Change) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Change) #

gmapT :: (forall b. Data b => b -> b) -> Change -> Change #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Change -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Change -> r #

gmapQ :: (forall d. Data d => d -> u) -> Change -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Change -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Change -> m Change #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Change -> m Change #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Change -> m Change #

Read Change Source # 
Show Change Source # 
Generic Change Source # 

Associated Types

type Rep Change :: * -> * #

Methods

from :: Change -> Rep Change x #

to :: Rep Change x -> Change #

Hashable Change Source # 

Methods

hashWithSalt :: Int -> Change -> Int #

hash :: Change -> Int #

NFData Change Source # 

Methods

rnf :: Change -> () #

FromXML Change Source # 
type Rep Change Source # 
type Rep Change = D1 (MetaData "Change" "Network.AWS.CloudFormation.Types.Product" "amazonka-cloudformation-1.4.2-3voa5o7VdaaGgHhcqNcvoX" False) (C1 (MetaCons "Change'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_cResourceChange") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe ResourceChange))) (S1 (MetaSel (Just Symbol "_cType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe ChangeType)))))

change :: Change Source #

Creates a value of Change with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

cResourceChange :: Lens' Change (Maybe ResourceChange) Source #

A ResourceChange structure that describes the resource and action that AWS CloudFormation will perform.

cType :: Lens' Change (Maybe ChangeType) Source #

The type of entity that AWS CloudFormation changes. Currently, the only entity type is Resource.

ChangeSetSummary

data ChangeSetSummary Source #

The ChangeSetSummary structure describes a change set, its status, and the stack with which it's associated.

See: changeSetSummary smart constructor.

Instances

Eq ChangeSetSummary Source # 
Data ChangeSetSummary Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ChangeSetSummary -> c ChangeSetSummary #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ChangeSetSummary #

toConstr :: ChangeSetSummary -> Constr #

dataTypeOf :: ChangeSetSummary -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c ChangeSetSummary) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ChangeSetSummary) #

gmapT :: (forall b. Data b => b -> b) -> ChangeSetSummary -> ChangeSetSummary #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ChangeSetSummary -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ChangeSetSummary -> r #

gmapQ :: (forall d. Data d => d -> u) -> ChangeSetSummary -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ChangeSetSummary -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ChangeSetSummary -> m ChangeSetSummary #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ChangeSetSummary -> m ChangeSetSummary #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ChangeSetSummary -> m ChangeSetSummary #

Read ChangeSetSummary Source # 
Show ChangeSetSummary Source # 
Generic ChangeSetSummary Source # 
Hashable ChangeSetSummary Source # 
NFData ChangeSetSummary Source # 

Methods

rnf :: ChangeSetSummary -> () #

FromXML ChangeSetSummary Source # 
type Rep ChangeSetSummary Source # 

changeSetSummary :: ChangeSetSummary Source #

Creates a value of ChangeSetSummary with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

cssCreationTime :: Lens' ChangeSetSummary (Maybe UTCTime) Source #

The start time when the change set was created, in UTC.

cssStatus :: Lens' ChangeSetSummary (Maybe ChangeSetStatus) Source #

The state of the change set, such as CREATE_IN_PROGRESS, CREATE_COMPLETE, or FAILED.

cssChangeSetName :: Lens' ChangeSetSummary (Maybe Text) Source #

The name of the change set.

cssChangeSetId :: Lens' ChangeSetSummary (Maybe Text) Source #

The ID of the change set.

cssStatusReason :: Lens' ChangeSetSummary (Maybe Text) Source #

A description of the change set's status. For example, if your change set is in the FAILED state, AWS CloudFormation shows the error message.

cssStackId :: Lens' ChangeSetSummary (Maybe Text) Source #

The ID of the stack with which the change set is associated.

cssDescription :: Lens' ChangeSetSummary (Maybe Text) Source #

Descriptive information about the change set.

cssStackName :: Lens' ChangeSetSummary (Maybe Text) Source #

The name of the stack with which the change set is associated.

Output

data Output Source #

The Output data type.

See: output smart constructor.

Instances

Eq Output Source # 

Methods

(==) :: Output -> Output -> Bool #

(/=) :: Output -> Output -> Bool #

Data Output Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Output -> c Output #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Output #

toConstr :: Output -> Constr #

dataTypeOf :: Output -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Output) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Output) #

gmapT :: (forall b. Data b => b -> b) -> Output -> Output #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Output -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Output -> r #

gmapQ :: (forall d. Data d => d -> u) -> Output -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Output -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Output -> m Output #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Output -> m Output #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Output -> m Output #

Read Output Source # 
Show Output Source # 
Generic Output Source # 

Associated Types

type Rep Output :: * -> * #

Methods

from :: Output -> Rep Output x #

to :: Rep Output x -> Output #

Hashable Output Source # 

Methods

hashWithSalt :: Int -> Output -> Int #

hash :: Output -> Int #

NFData Output Source # 

Methods

rnf :: Output -> () #

FromXML Output Source # 
type Rep Output Source # 
type Rep Output = D1 (MetaData "Output" "Network.AWS.CloudFormation.Types.Product" "amazonka-cloudformation-1.4.2-3voa5o7VdaaGgHhcqNcvoX" False) (C1 (MetaCons "Output'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_oOutputValue") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) ((:*:) (S1 (MetaSel (Just Symbol "_oOutputKey") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_oDescription") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))))))

output :: Output Source #

Creates a value of Output with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

oOutputValue :: Lens' Output (Maybe Text) Source #

The value associated with the output.

oOutputKey :: Lens' Output (Maybe Text) Source #

The key associated with the output.

oDescription :: Lens' Output (Maybe Text) Source #

User defined description associated with the output.

Parameter

data Parameter Source #

The Parameter data type.

See: parameter smart constructor.

Instances

Eq Parameter Source # 
Data Parameter Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Parameter -> c Parameter #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Parameter #

toConstr :: Parameter -> Constr #

dataTypeOf :: Parameter -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Parameter) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Parameter) #

gmapT :: (forall b. Data b => b -> b) -> Parameter -> Parameter #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Parameter -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Parameter -> r #

gmapQ :: (forall d. Data d => d -> u) -> Parameter -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Parameter -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Parameter -> m Parameter #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Parameter -> m Parameter #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Parameter -> m Parameter #

Read Parameter Source # 
Show Parameter Source # 
Generic Parameter Source # 

Associated Types

type Rep Parameter :: * -> * #

Hashable Parameter Source # 
NFData Parameter Source # 

Methods

rnf :: Parameter -> () #

FromXML Parameter Source # 
ToQuery Parameter Source # 
type Rep Parameter Source # 
type Rep Parameter = D1 (MetaData "Parameter" "Network.AWS.CloudFormation.Types.Product" "amazonka-cloudformation-1.4.2-3voa5o7VdaaGgHhcqNcvoX" False) (C1 (MetaCons "Parameter'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_pParameterValue") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) ((:*:) (S1 (MetaSel (Just Symbol "_pParameterKey") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_pUsePreviousValue") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool))))))

parameter :: Parameter Source #

Creates a value of Parameter with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

pParameterValue :: Lens' Parameter (Maybe Text) Source #

The value associated with the parameter.

pParameterKey :: Lens' Parameter (Maybe Text) Source #

The key associated with the parameter. If you don't specify a key and value for a particular parameter, AWS CloudFormation uses the default value that is specified in your template.

pUsePreviousValue :: Lens' Parameter (Maybe Bool) Source #

During a stack update, use the existing parameter value that the stack is using for a given parameter key. If you specify true, do not specify a parameter value.

ParameterConstraints

data ParameterConstraints Source #

A set of criteria that AWS CloudFormation uses to validate parameter values. Although other constraints might be defined in the stack template, AWS CloudFormation returns only the AllowedValues property.

See: parameterConstraints smart constructor.

Instances

Eq ParameterConstraints Source # 
Data ParameterConstraints Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ParameterConstraints -> c ParameterConstraints #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ParameterConstraints #

toConstr :: ParameterConstraints -> Constr #

dataTypeOf :: ParameterConstraints -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c ParameterConstraints) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ParameterConstraints) #

gmapT :: (forall b. Data b => b -> b) -> ParameterConstraints -> ParameterConstraints #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ParameterConstraints -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ParameterConstraints -> r #

gmapQ :: (forall d. Data d => d -> u) -> ParameterConstraints -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ParameterConstraints -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ParameterConstraints -> m ParameterConstraints #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ParameterConstraints -> m ParameterConstraints #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ParameterConstraints -> m ParameterConstraints #

Read ParameterConstraints Source # 
Show ParameterConstraints Source # 
Generic ParameterConstraints Source # 
Hashable ParameterConstraints Source # 
NFData ParameterConstraints Source # 

Methods

rnf :: ParameterConstraints -> () #

FromXML ParameterConstraints Source # 
type Rep ParameterConstraints Source # 
type Rep ParameterConstraints = D1 (MetaData "ParameterConstraints" "Network.AWS.CloudFormation.Types.Product" "amazonka-cloudformation-1.4.2-3voa5o7VdaaGgHhcqNcvoX" True) (C1 (MetaCons "ParameterConstraints'" PrefixI True) (S1 (MetaSel (Just Symbol "_pcAllowedValues") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe [Text]))))

parameterConstraints :: ParameterConstraints Source #

Creates a value of ParameterConstraints with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

pcAllowedValues :: Lens' ParameterConstraints [Text] Source #

A list of values that are permitted for a parameter.

ParameterDeclaration

data ParameterDeclaration Source #

The ParameterDeclaration data type.

See: parameterDeclaration smart constructor.

Instances

Eq ParameterDeclaration Source # 
Data ParameterDeclaration Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ParameterDeclaration -> c ParameterDeclaration #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ParameterDeclaration #

toConstr :: ParameterDeclaration -> Constr #

dataTypeOf :: ParameterDeclaration -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c ParameterDeclaration) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ParameterDeclaration) #

gmapT :: (forall b. Data b => b -> b) -> ParameterDeclaration -> ParameterDeclaration #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ParameterDeclaration -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ParameterDeclaration -> r #

gmapQ :: (forall d. Data d => d -> u) -> ParameterDeclaration -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ParameterDeclaration -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ParameterDeclaration -> m ParameterDeclaration #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ParameterDeclaration -> m ParameterDeclaration #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ParameterDeclaration -> m ParameterDeclaration #

Read ParameterDeclaration Source # 
Show ParameterDeclaration Source # 
Generic ParameterDeclaration Source # 
Hashable ParameterDeclaration Source # 
NFData ParameterDeclaration Source # 

Methods

rnf :: ParameterDeclaration -> () #

FromXML ParameterDeclaration Source # 
type Rep ParameterDeclaration Source # 
type Rep ParameterDeclaration = D1 (MetaData "ParameterDeclaration" "Network.AWS.CloudFormation.Types.Product" "amazonka-cloudformation-1.4.2-3voa5o7VdaaGgHhcqNcvoX" False) (C1 (MetaCons "ParameterDeclaration'" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_pdParameterKey") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) ((:*:) (S1 (MetaSel (Just Symbol "_pdParameterType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_pdParameterConstraints") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe ParameterConstraints))))) ((:*:) (S1 (MetaSel (Just Symbol "_pdDefaultValue") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) ((:*:) (S1 (MetaSel (Just Symbol "_pdNoEcho") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool))) (S1 (MetaSel (Just Symbol "_pdDescription") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))))))

parameterDeclaration :: ParameterDeclaration Source #

Creates a value of ParameterDeclaration with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

pdParameterKey :: Lens' ParameterDeclaration (Maybe Text) Source #

The name that is associated with the parameter.

pdParameterConstraints :: Lens' ParameterDeclaration (Maybe ParameterConstraints) Source #

The criteria that AWS CloudFormation uses to validate parameter values.

pdDefaultValue :: Lens' ParameterDeclaration (Maybe Text) Source #

The default value of the parameter.

pdNoEcho :: Lens' ParameterDeclaration (Maybe Bool) Source #

Flag that indicates whether the parameter value is shown as plain text in logs and in the AWS Management Console.

pdDescription :: Lens' ParameterDeclaration (Maybe Text) Source #

The description that is associate with the parameter.

ResourceChange

data ResourceChange Source #

The ResourceChange structure describes the resource and the action that AWS CloudFormation will perform on it if you execute this change set.

See: resourceChange smart constructor.

Instances

Eq ResourceChange Source # 
Data ResourceChange Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ResourceChange -> c ResourceChange #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ResourceChange #

toConstr :: ResourceChange -> Constr #

dataTypeOf :: ResourceChange -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c ResourceChange) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ResourceChange) #

gmapT :: (forall b. Data b => b -> b) -> ResourceChange -> ResourceChange #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ResourceChange -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ResourceChange -> r #

gmapQ :: (forall d. Data d => d -> u) -> ResourceChange -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ResourceChange -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ResourceChange -> m ResourceChange #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ResourceChange -> m ResourceChange #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ResourceChange -> m ResourceChange #

Read ResourceChange Source # 
Show ResourceChange Source # 
Generic ResourceChange Source # 

Associated Types

type Rep ResourceChange :: * -> * #

Hashable ResourceChange Source # 
NFData ResourceChange Source # 

Methods

rnf :: ResourceChange -> () #

FromXML ResourceChange Source # 
type Rep ResourceChange Source # 

resourceChange :: ResourceChange Source #

Creates a value of ResourceChange with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

rcLogicalResourceId :: Lens' ResourceChange (Maybe Text) Source #

The resource's logical ID, which is defined in the stack's template.

rcPhysicalResourceId :: Lens' ResourceChange (Maybe Text) Source #

The resource's physical ID (resource name). Resources that you are adding don't have physical IDs because they haven't been created.

rcResourceType :: Lens' ResourceChange (Maybe Text) Source #

The type of AWS CloudFormation resource, such as 'AWS::S3::Bucket'.

rcAction :: Lens' ResourceChange (Maybe ChangeAction) Source #

The action that AWS CloudFormation takes on the resource, such as Add (adds a new resource), Modify (changes a resource), or Remove (deletes a resource).

rcScope :: Lens' ResourceChange [ResourceAttribute] Source #

For the Modify action, indicates which resource attribute is triggering this update, such as a change in the resource attribute's Metadata, Properties, or Tags.

rcDetails :: Lens' ResourceChange [ResourceChangeDetail] Source #

For the Modify action, a list of ResourceChangeDetail structures that describes the changes that AWS CloudFormation will make to the resource.

rcReplacement :: Lens' ResourceChange (Maybe Replacement) Source #

For the Modify action, indicates whether AWS CloudFormation will replace the resource by creating a new one and deleting the old one. This value depends on the value of the RequiresRecreation property in the ResourceTargetDefinition structure. For example, if the RequiresRecreation field is Always and the Evaluation field is Static, Replacement is True. If the RequiresRecreation field is Always and the Evaluation field is Dynamic, Replacement is Conditionally.

If you have multiple changes with different RequiresRecreation values, the Replacement value depends on the change with the most impact. A RequiresRecreation value of Always has the most impact, followed by Conditionally, and then Never.

ResourceChangeDetail

data ResourceChangeDetail Source #

For a resource with Modify as the action, the ResourceChange structure describes the changes AWS CloudFormation will make to that resource.

See: resourceChangeDetail smart constructor.

Instances

Eq ResourceChangeDetail Source # 
Data ResourceChangeDetail Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ResourceChangeDetail -> c ResourceChangeDetail #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ResourceChangeDetail #

toConstr :: ResourceChangeDetail -> Constr #

dataTypeOf :: ResourceChangeDetail -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c ResourceChangeDetail) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ResourceChangeDetail) #

gmapT :: (forall b. Data b => b -> b) -> ResourceChangeDetail -> ResourceChangeDetail #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ResourceChangeDetail -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ResourceChangeDetail -> r #

gmapQ :: (forall d. Data d => d -> u) -> ResourceChangeDetail -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ResourceChangeDetail -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ResourceChangeDetail -> m ResourceChangeDetail #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ResourceChangeDetail -> m ResourceChangeDetail #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ResourceChangeDetail -> m ResourceChangeDetail #

Read ResourceChangeDetail Source # 
Show ResourceChangeDetail Source # 
Generic ResourceChangeDetail Source # 
Hashable ResourceChangeDetail Source # 
NFData ResourceChangeDetail Source # 

Methods

rnf :: ResourceChangeDetail -> () #

FromXML ResourceChangeDetail Source # 
type Rep ResourceChangeDetail Source # 
type Rep ResourceChangeDetail = D1 (MetaData "ResourceChangeDetail" "Network.AWS.CloudFormation.Types.Product" "amazonka-cloudformation-1.4.2-3voa5o7VdaaGgHhcqNcvoX" False) (C1 (MetaCons "ResourceChangeDetail'" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_rcdCausingEntity") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_rcdChangeSource") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe ChangeSource)))) ((:*:) (S1 (MetaSel (Just Symbol "_rcdEvaluation") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe EvaluationType))) (S1 (MetaSel (Just Symbol "_rcdTarget") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe ResourceTargetDefinition))))))

resourceChangeDetail :: ResourceChangeDetail Source #

Creates a value of ResourceChangeDetail with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

rcdCausingEntity :: Lens' ResourceChangeDetail (Maybe Text) Source #

The identity of the entity that triggered this change. This entity is a member of the group that is specified by the ChangeSource field. For example, if you modified the value of the KeyPairName parameter, the CausingEntity is the name of the parameter (KeyPairName).

If the ChangeSource value is DirectModification, no value is given for CausingEntity.

rcdChangeSource :: Lens' ResourceChangeDetail (Maybe ChangeSource) Source #

The group to which the CausingEntity value belongs. There are five entity groups:

  • ResourceReference entities are Ref intrinsic functions that refer to resources in the template, such as '{ "Ref" : "MyEC2InstanceResource" }'.
  • ParameterReference entities are Ref intrinsic functions that get template parameter values, such as '{ "Ref" : "MyPasswordParameter" }'.
  • ResourceAttribute entities are 'Fn::GetAtt' intrinsic functions that get resource attribute values, such as '{ "Fn::GetAtt" : [ "MyEC2InstanceResource", "PublicDnsName" ] }'.
  • DirectModification entities are changes that are made directly to the template.
  • Automatic entities are 'AWS::CloudFormation::Stack' resource types, which are also known as nested stacks. If you made no changes to the 'AWS::CloudFormation::Stack' resource, AWS CloudFormation sets the ChangeSource to Automatic because the nested stack's template might have changed. Changes to a nested stack's template aren't visible to AWS CloudFormation until you run an update on the parent stack.

rcdEvaluation :: Lens' ResourceChangeDetail (Maybe EvaluationType) Source #

Indicates whether AWS CloudFormation can determine the target value, and whether the target value will change before you execute a change set.

For Static evaluations, AWS CloudFormation can determine that the target value will change, and its value. For example, if you directly modify the InstanceType property of an EC2 instance, AWS CloudFormation knows that this property value will change, and its value, so this is a Static evaluation.

For Dynamic evaluations, cannot determine the target value because it depends on the result of an intrinsic function, such as a Ref or 'Fn::GetAtt' intrinsic function, when the stack is updated. For example, if your template includes a reference to a resource that is conditionally recreated, the value of the reference (the physical ID of the resource) might change, depending on if the resource is recreated. If the resource is recreated, it will have a new physical ID, so all references to that resource will also be updated.

rcdTarget :: Lens' ResourceChangeDetail (Maybe ResourceTargetDefinition) Source #

A ResourceTargetDefinition structure that describes the field that AWS CloudFormation will change and whether the resource will be recreated.

ResourceTargetDefinition

data ResourceTargetDefinition Source #

The field that AWS CloudFormation will change, such as the name of a resource's property, and whether the resource will be recreated.

See: resourceTargetDefinition smart constructor.

Instances

Eq ResourceTargetDefinition Source # 
Data ResourceTargetDefinition Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ResourceTargetDefinition -> c ResourceTargetDefinition #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ResourceTargetDefinition #

toConstr :: ResourceTargetDefinition -> Constr #

dataTypeOf :: ResourceTargetDefinition -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c ResourceTargetDefinition) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ResourceTargetDefinition) #

gmapT :: (forall b. Data b => b -> b) -> ResourceTargetDefinition -> ResourceTargetDefinition #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ResourceTargetDefinition -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ResourceTargetDefinition -> r #

gmapQ :: (forall d. Data d => d -> u) -> ResourceTargetDefinition -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ResourceTargetDefinition -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ResourceTargetDefinition -> m ResourceTargetDefinition #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ResourceTargetDefinition -> m ResourceTargetDefinition #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ResourceTargetDefinition -> m ResourceTargetDefinition #

Read ResourceTargetDefinition Source # 
Show ResourceTargetDefinition Source # 
Generic ResourceTargetDefinition Source # 
Hashable ResourceTargetDefinition Source # 
NFData ResourceTargetDefinition Source # 
FromXML ResourceTargetDefinition Source # 
type Rep ResourceTargetDefinition Source # 
type Rep ResourceTargetDefinition = D1 (MetaData "ResourceTargetDefinition" "Network.AWS.CloudFormation.Types.Product" "amazonka-cloudformation-1.4.2-3voa5o7VdaaGgHhcqNcvoX" False) (C1 (MetaCons "ResourceTargetDefinition'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_rtdAttribute") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe ResourceAttribute))) ((:*:) (S1 (MetaSel (Just Symbol "_rtdRequiresRecreation") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe RequiresRecreation))) (S1 (MetaSel (Just Symbol "_rtdName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))))))

resourceTargetDefinition :: ResourceTargetDefinition Source #

Creates a value of ResourceTargetDefinition with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

rtdAttribute :: Lens' ResourceTargetDefinition (Maybe ResourceAttribute) Source #

Indicates which resource attribute is triggering this update, such as a change in the resource attribute's Metadata, Properties, or Tags.

rtdRequiresRecreation :: Lens' ResourceTargetDefinition (Maybe RequiresRecreation) Source #

If the Attribute value is Properties, indicates whether a change to this property causes the resource to be recreated. The value can be Never, Always, or Conditionally. To determine the conditions for a Conditionally recreation, see the update behavior for that property in the AWS CloudFormation User Guide.

rtdName :: Lens' ResourceTargetDefinition (Maybe Text) Source #

If the Attribute value is Properties, the name of the property. For all other attributes, the value is null.

Stack

data Stack Source #

The Stack data type.

See: stack smart constructor.

Instances

Eq Stack Source # 

Methods

(==) :: Stack -> Stack -> Bool #

(/=) :: Stack -> Stack -> Bool #

Data Stack Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Stack -> c Stack #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Stack #

toConstr :: Stack -> Constr #

dataTypeOf :: Stack -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Stack) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Stack) #

gmapT :: (forall b. Data b => b -> b) -> Stack -> Stack #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Stack -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Stack -> r #

gmapQ :: (forall d. Data d => d -> u) -> Stack -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Stack -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Stack -> m Stack #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Stack -> m Stack #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Stack -> m Stack #

Read Stack Source # 
Show Stack Source # 

Methods

showsPrec :: Int -> Stack -> ShowS #

show :: Stack -> String #

showList :: [Stack] -> ShowS #

Generic Stack Source # 

Associated Types

type Rep Stack :: * -> * #

Methods

from :: Stack -> Rep Stack x #

to :: Rep Stack x -> Stack #

Hashable Stack Source # 

Methods

hashWithSalt :: Int -> Stack -> Int #

hash :: Stack -> Int #

NFData Stack Source # 

Methods

rnf :: Stack -> () #

FromXML Stack Source # 

Methods

parseXML :: [Node] -> Either String Stack #

type Rep Stack Source # 
type Rep Stack = D1 (MetaData "Stack" "Network.AWS.CloudFormation.Types.Product" "amazonka-cloudformation-1.4.2-3voa5o7VdaaGgHhcqNcvoX" False) (C1 (MetaCons "Stack'" PrefixI True) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_sDisableRollback") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool))) ((:*:) (S1 (MetaSel (Just Symbol "_sLastUpdatedTime") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe ISO8601))) (S1 (MetaSel (Just Symbol "_sNotificationARNs") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [Text]))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_sStackStatusReason") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_sOutputs") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [Output])))) ((:*:) (S1 (MetaSel (Just Symbol "_sParameters") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [Parameter]))) (S1 (MetaSel (Just Symbol "_sStackId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_sDescription") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) ((:*:) (S1 (MetaSel (Just Symbol "_sCapabilities") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [Capability]))) (S1 (MetaSel (Just Symbol "_sTags") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [Tag]))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_sTimeoutInMinutes") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Nat))) (S1 (MetaSel (Just Symbol "_sStackName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text))) ((:*:) (S1 (MetaSel (Just Symbol "_sCreationTime") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 ISO8601)) (S1 (MetaSel (Just Symbol "_sStackStatus") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 StackStatus)))))))

sDisableRollback :: Lens' Stack (Maybe Bool) Source #

Boolean to enable or disable rollback on stack creation failures:

  • true: disable rollback
  • false: enable rollback

sLastUpdatedTime :: Lens' Stack (Maybe UTCTime) Source #

The time the stack was last updated. This field will only be returned if the stack has been updated at least once.

sNotificationARNs :: Lens' Stack [Text] Source #

SNS topic ARNs to which stack related events are published.

sStackStatusReason :: Lens' Stack (Maybe Text) Source #

Success/failure message associated with the stack status.

sOutputs :: Lens' Stack [Output] Source #

A list of output structures.

sParameters :: Lens' Stack [Parameter] Source #

A list of Parameter structures.

sStackId :: Lens' Stack (Maybe Text) Source #

Unique identifier of the stack.

sDescription :: Lens' Stack (Maybe Text) Source #

A user-defined description associated with the stack.

sCapabilities :: Lens' Stack [Capability] Source #

The capabilities allowed in the stack.

sTags :: Lens' Stack [Tag] Source #

A list of Tags that specify information about the stack.

sTimeoutInMinutes :: Lens' Stack (Maybe Natural) Source #

The amount of time within which stack creation should complete.

sStackName :: Lens' Stack Text Source #

The name associated with the stack.

sCreationTime :: Lens' Stack UTCTime Source #

The time at which the stack was created.

sStackStatus :: Lens' Stack StackStatus Source #

Current status of the stack.

StackEvent

data StackEvent Source #

The StackEvent data type.

See: stackEvent smart constructor.

Instances

Eq StackEvent Source # 
Data StackEvent Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> StackEvent -> c StackEvent #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c StackEvent #

toConstr :: StackEvent -> Constr #

dataTypeOf :: StackEvent -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c StackEvent) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c StackEvent) #

gmapT :: (forall b. Data b => b -> b) -> StackEvent -> StackEvent #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> StackEvent -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> StackEvent -> r #

gmapQ :: (forall d. Data d => d -> u) -> StackEvent -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> StackEvent -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> StackEvent -> m StackEvent #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> StackEvent -> m StackEvent #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> StackEvent -> m StackEvent #

Read StackEvent Source # 
Show StackEvent Source # 
Generic StackEvent Source # 

Associated Types

type Rep StackEvent :: * -> * #

Hashable StackEvent Source # 
NFData StackEvent Source # 

Methods

rnf :: StackEvent -> () #

FromXML StackEvent Source # 
type Rep StackEvent Source # 

stackEvent Source #

Creates a value of StackEvent with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

seLogicalResourceId :: Lens' StackEvent (Maybe Text) Source #

The logical name of the resource specified in the template.

sePhysicalResourceId :: Lens' StackEvent (Maybe Text) Source #

The name or unique identifier associated with the physical instance of the resource.

seResourceType :: Lens' StackEvent (Maybe Text) Source #

Type of resource. (For more information, go to AWS Resource Types Reference in the AWS CloudFormation User Guide.)

seResourceStatusReason :: Lens' StackEvent (Maybe Text) Source #

Success/failure message associated with the resource.

seResourceProperties :: Lens' StackEvent (Maybe Text) Source #

BLOB of the properties used to create the resource.

seResourceStatus :: Lens' StackEvent (Maybe ResourceStatus) Source #

Current status of the resource.

seStackId :: Lens' StackEvent Text Source #

The unique ID name of the instance of the stack.

seEventId :: Lens' StackEvent Text Source #

The unique ID of this event.

seStackName :: Lens' StackEvent Text Source #

The name associated with a stack.

seTimestamp :: Lens' StackEvent UTCTime Source #

Time the status was updated.

StackResource

data StackResource Source #

The StackResource data type.

See: stackResource smart constructor.

Instances

Eq StackResource Source # 
Data StackResource Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> StackResource -> c StackResource #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c StackResource #

toConstr :: StackResource -> Constr #

dataTypeOf :: StackResource -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c StackResource) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c StackResource) #

gmapT :: (forall b. Data b => b -> b) -> StackResource -> StackResource #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> StackResource -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> StackResource -> r #

gmapQ :: (forall d. Data d => d -> u) -> StackResource -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> StackResource -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> StackResource -> m StackResource #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> StackResource -> m StackResource #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> StackResource -> m StackResource #

Read StackResource Source # 
Show StackResource Source # 
Generic StackResource Source # 

Associated Types

type Rep StackResource :: * -> * #

Hashable StackResource Source # 
NFData StackResource Source # 

Methods

rnf :: StackResource -> () #

FromXML StackResource Source # 
type Rep StackResource Source # 

srPhysicalResourceId :: Lens' StackResource (Maybe Text) Source #

The name or unique identifier that corresponds to a physical instance ID of a resource supported by AWS CloudFormation.

srResourceStatusReason :: Lens' StackResource (Maybe Text) Source #

Success/failure message associated with the resource.

srStackId :: Lens' StackResource (Maybe Text) Source #

Unique identifier of the stack.

srDescription :: Lens' StackResource (Maybe Text) Source #

User defined description associated with the resource.

srStackName :: Lens' StackResource (Maybe Text) Source #

The name associated with the stack.

srLogicalResourceId :: Lens' StackResource Text Source #

The logical name of the resource specified in the template.

srResourceType :: Lens' StackResource Text Source #

Type of resource. (For more information, go to AWS Resource Types Reference in the AWS CloudFormation User Guide.)

srTimestamp :: Lens' StackResource UTCTime Source #

Time the status was updated.

srResourceStatus :: Lens' StackResource ResourceStatus Source #

Current status of the resource.

StackResourceDetail

data StackResourceDetail Source #

Contains detailed information about the specified stack resource.

See: stackResourceDetail smart constructor.

Instances

Eq StackResourceDetail Source # 
Data StackResourceDetail Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> StackResourceDetail -> c StackResourceDetail #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c StackResourceDetail #

toConstr :: StackResourceDetail -> Constr #

dataTypeOf :: StackResourceDetail -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c StackResourceDetail) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c StackResourceDetail) #

gmapT :: (forall b. Data b => b -> b) -> StackResourceDetail -> StackResourceDetail #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> StackResourceDetail -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> StackResourceDetail -> r #

gmapQ :: (forall d. Data d => d -> u) -> StackResourceDetail -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> StackResourceDetail -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> StackResourceDetail -> m StackResourceDetail #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> StackResourceDetail -> m StackResourceDetail #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> StackResourceDetail -> m StackResourceDetail #

Read StackResourceDetail Source # 
Show StackResourceDetail Source # 
Generic StackResourceDetail Source # 
Hashable StackResourceDetail Source # 
NFData StackResourceDetail Source # 

Methods

rnf :: StackResourceDetail -> () #

FromXML StackResourceDetail Source # 
type Rep StackResourceDetail Source # 
type Rep StackResourceDetail = D1 (MetaData "StackResourceDetail" "Network.AWS.CloudFormation.Types.Product" "amazonka-cloudformation-1.4.2-3voa5o7VdaaGgHhcqNcvoX" False) (C1 (MetaCons "StackResourceDetail'" PrefixI True) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_srdPhysicalResourceId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_srdResourceStatusReason") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))) ((:*:) (S1 (MetaSel (Just Symbol "_srdMetadata") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) ((:*:) (S1 (MetaSel (Just Symbol "_srdStackId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_srdDescription") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_srdStackName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_srdLogicalResourceId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text))) ((:*:) (S1 (MetaSel (Just Symbol "_srdResourceType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text)) ((:*:) (S1 (MetaSel (Just Symbol "_srdLastUpdatedTimestamp") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 ISO8601)) (S1 (MetaSel (Just Symbol "_srdResourceStatus") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 ResourceStatus)))))))

srdPhysicalResourceId :: Lens' StackResourceDetail (Maybe Text) Source #

The name or unique identifier that corresponds to a physical instance ID of a resource supported by AWS CloudFormation.

srdResourceStatusReason :: Lens' StackResourceDetail (Maybe Text) Source #

Success/failure message associated with the resource.

srdMetadata :: Lens' StackResourceDetail (Maybe Text) Source #

The JSON format content of the Metadata attribute declared for the resource. For more information, see Metadata Attribute in the AWS CloudFormation User Guide.

srdStackId :: Lens' StackResourceDetail (Maybe Text) Source #

Unique identifier of the stack.

srdDescription :: Lens' StackResourceDetail (Maybe Text) Source #

User defined description associated with the resource.

srdStackName :: Lens' StackResourceDetail (Maybe Text) Source #

The name associated with the stack.

srdLogicalResourceId :: Lens' StackResourceDetail Text Source #

The logical name of the resource specified in the template.

srdResourceType :: Lens' StackResourceDetail Text Source #

Type of resource. ((For more information, go to AWS Resource Types Reference in the AWS CloudFormation User Guide.)

StackResourceSummary

data StackResourceSummary Source #

Contains high-level information about the specified stack resource.

See: stackResourceSummary smart constructor.

Instances

Eq StackResourceSummary Source # 
Data StackResourceSummary Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> StackResourceSummary -> c StackResourceSummary #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c StackResourceSummary #

toConstr :: StackResourceSummary -> Constr #

dataTypeOf :: StackResourceSummary -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c StackResourceSummary) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c StackResourceSummary) #

gmapT :: (forall b. Data b => b -> b) -> StackResourceSummary -> StackResourceSummary #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> StackResourceSummary -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> StackResourceSummary -> r #

gmapQ :: (forall d. Data d => d -> u) -> StackResourceSummary -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> StackResourceSummary -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> StackResourceSummary -> m StackResourceSummary #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> StackResourceSummary -> m StackResourceSummary #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> StackResourceSummary -> m StackResourceSummary #

Read StackResourceSummary Source # 
Show StackResourceSummary Source # 
Generic StackResourceSummary Source # 
Hashable StackResourceSummary Source # 
NFData StackResourceSummary Source # 

Methods

rnf :: StackResourceSummary -> () #

FromXML StackResourceSummary Source # 
type Rep StackResourceSummary Source # 
type Rep StackResourceSummary = D1 (MetaData "StackResourceSummary" "Network.AWS.CloudFormation.Types.Product" "amazonka-cloudformation-1.4.2-3voa5o7VdaaGgHhcqNcvoX" False) (C1 (MetaCons "StackResourceSummary'" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_srsPhysicalResourceId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) ((:*:) (S1 (MetaSel (Just Symbol "_srsResourceStatusReason") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_srsLogicalResourceId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text)))) ((:*:) (S1 (MetaSel (Just Symbol "_srsResourceType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text)) ((:*:) (S1 (MetaSel (Just Symbol "_srsLastUpdatedTimestamp") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 ISO8601)) (S1 (MetaSel (Just Symbol "_srsResourceStatus") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 ResourceStatus))))))

srsPhysicalResourceId :: Lens' StackResourceSummary (Maybe Text) Source #

The name or unique identifier that corresponds to a physical instance ID of the resource.

srsResourceStatusReason :: Lens' StackResourceSummary (Maybe Text) Source #

Success/failure message associated with the resource.

srsLogicalResourceId :: Lens' StackResourceSummary Text Source #

The logical name of the resource specified in the template.

srsResourceType :: Lens' StackResourceSummary Text Source #

Type of resource. (For more information, go to AWS Resource Types Reference in the AWS CloudFormation User Guide.)

StackSummary

data StackSummary Source #

The StackSummary Data Type

See: stackSummary smart constructor.

Instances

Eq StackSummary Source # 
Data StackSummary Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> StackSummary -> c StackSummary #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c StackSummary #

toConstr :: StackSummary -> Constr #

dataTypeOf :: StackSummary -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c StackSummary) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c StackSummary) #

gmapT :: (forall b. Data b => b -> b) -> StackSummary -> StackSummary #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> StackSummary -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> StackSummary -> r #

gmapQ :: (forall d. Data d => d -> u) -> StackSummary -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> StackSummary -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> StackSummary -> m StackSummary #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> StackSummary -> m StackSummary #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> StackSummary -> m StackSummary #

Read StackSummary Source # 
Show StackSummary Source # 
Generic StackSummary Source # 

Associated Types

type Rep StackSummary :: * -> * #

Hashable StackSummary Source # 
NFData StackSummary Source # 

Methods

rnf :: StackSummary -> () #

FromXML StackSummary Source # 
type Rep StackSummary Source # 
type Rep StackSummary = D1 (MetaData "StackSummary" "Network.AWS.CloudFormation.Types.Product" "amazonka-cloudformation-1.4.2-3voa5o7VdaaGgHhcqNcvoX" False) (C1 (MetaCons "StackSummary'" PrefixI True) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_ssLastUpdatedTime") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe ISO8601))) (S1 (MetaSel (Just Symbol "_ssStackStatusReason") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))) ((:*:) (S1 (MetaSel (Just Symbol "_ssTemplateDescription") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_ssDeletionTime") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe ISO8601))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_ssStackId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_ssStackName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text))) ((:*:) (S1 (MetaSel (Just Symbol "_ssCreationTime") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 ISO8601)) (S1 (MetaSel (Just Symbol "_ssStackStatus") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 StackStatus))))))

stackSummary Source #

Creates a value of StackSummary with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

ssLastUpdatedTime :: Lens' StackSummary (Maybe UTCTime) Source #

The time the stack was last updated. This field will only be returned if the stack has been updated at least once.

ssStackStatusReason :: Lens' StackSummary (Maybe Text) Source #

Success/Failure message associated with the stack status.

ssTemplateDescription :: Lens' StackSummary (Maybe Text) Source #

The template description of the template used to create the stack.

ssDeletionTime :: Lens' StackSummary (Maybe UTCTime) Source #

The time the stack was deleted.

ssStackId :: Lens' StackSummary (Maybe Text) Source #

Unique stack identifier.

ssStackName :: Lens' StackSummary Text Source #

The name associated with the stack.

ssCreationTime :: Lens' StackSummary UTCTime Source #

The time the stack was created.

ssStackStatus :: Lens' StackSummary StackStatus Source #

The current status of the stack.

Tag

data Tag Source #

The Tag type enables you to specify a key-value pair that can be used to store information about an AWS CloudFormation stack.

See: tag smart constructor.

Instances

Eq Tag Source # 

Methods

(==) :: Tag -> Tag -> Bool #

(/=) :: Tag -> Tag -> Bool #

Data Tag Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Tag -> c Tag #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Tag #

toConstr :: Tag -> Constr #

dataTypeOf :: Tag -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Tag) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Tag) #

gmapT :: (forall b. Data b => b -> b) -> Tag -> Tag #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Tag -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Tag -> r #

gmapQ :: (forall d. Data d => d -> u) -> Tag -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Tag -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Tag -> m Tag #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Tag -> m Tag #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Tag -> m Tag #

Read Tag Source # 
Show Tag Source # 

Methods

showsPrec :: Int -> Tag -> ShowS #

show :: Tag -> String #

showList :: [Tag] -> ShowS #

Generic Tag Source # 

Associated Types

type Rep Tag :: * -> * #

Methods

from :: Tag -> Rep Tag x #

to :: Rep Tag x -> Tag #

Hashable Tag Source # 

Methods

hashWithSalt :: Int -> Tag -> Int #

hash :: Tag -> Int #

NFData Tag Source # 

Methods

rnf :: Tag -> () #

FromXML Tag Source # 

Methods

parseXML :: [Node] -> Either String Tag #

ToQuery Tag Source # 

Methods

toQuery :: Tag -> QueryString #

type Rep Tag Source # 
type Rep Tag = D1 (MetaData "Tag" "Network.AWS.CloudFormation.Types.Product" "amazonka-cloudformation-1.4.2-3voa5o7VdaaGgHhcqNcvoX" False) (C1 (MetaCons "Tag'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_tagValue") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_tagKey") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))))

tag :: Tag Source #

Creates a value of Tag with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

tagValue :: Lens' Tag (Maybe Text) Source #

Required. A string containing the value for this tag. You can specify a maximum of 256 characters for a tag value.

tagKey :: Lens' Tag (Maybe Text) Source #

Required. A string used to identify this tag. You can specify a maximum of 128 characters for a tag key. Tags owned by Amazon Web Services (AWS) have the reserved prefix: 'aws:'.

TemplateParameter

data TemplateParameter Source #

The TemplateParameter data type.

See: templateParameter smart constructor.

Instances

Eq TemplateParameter Source # 
Data TemplateParameter Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> TemplateParameter -> c TemplateParameter #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c TemplateParameter #

toConstr :: TemplateParameter -> Constr #

dataTypeOf :: TemplateParameter -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c TemplateParameter) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TemplateParameter) #

gmapT :: (forall b. Data b => b -> b) -> TemplateParameter -> TemplateParameter #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TemplateParameter -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TemplateParameter -> r #

gmapQ :: (forall d. Data d => d -> u) -> TemplateParameter -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> TemplateParameter -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> TemplateParameter -> m TemplateParameter #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TemplateParameter -> m TemplateParameter #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TemplateParameter -> m TemplateParameter #

Read TemplateParameter Source # 
Show TemplateParameter Source # 
Generic TemplateParameter Source # 
Hashable TemplateParameter Source # 
NFData TemplateParameter Source # 

Methods

rnf :: TemplateParameter -> () #

FromXML TemplateParameter Source # 
type Rep TemplateParameter Source # 
type Rep TemplateParameter = D1 (MetaData "TemplateParameter" "Network.AWS.CloudFormation.Types.Product" "amazonka-cloudformation-1.4.2-3voa5o7VdaaGgHhcqNcvoX" False) (C1 (MetaCons "TemplateParameter'" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_tpParameterKey") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_tpDefaultValue") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))) ((:*:) (S1 (MetaSel (Just Symbol "_tpNoEcho") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool))) (S1 (MetaSel (Just Symbol "_tpDescription") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))))))

templateParameter :: TemplateParameter Source #

Creates a value of TemplateParameter with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

tpParameterKey :: Lens' TemplateParameter (Maybe Text) Source #

The name associated with the parameter.

tpDefaultValue :: Lens' TemplateParameter (Maybe Text) Source #

The default value associated with the parameter.

tpNoEcho :: Lens' TemplateParameter (Maybe Bool) Source #

Flag indicating whether the parameter should be displayed as plain text in logs and UIs.

tpDescription :: Lens' TemplateParameter (Maybe Text) Source #

User defined description associated with the parameter.