{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DuplicateRecordFields #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE StrictData #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# OPTIONS_GHC -fno-warn-unused-binds #-}
{-# OPTIONS_GHC -fno-warn-unused-imports #-}
{-# OPTIONS_GHC -fno-warn-unused-matches #-}
module Amazonka.CloudFormation.CreateStackInstances
(
CreateStackInstances (..),
newCreateStackInstances,
createStackInstances_accounts,
createStackInstances_callAs,
createStackInstances_deploymentTargets,
createStackInstances_operationId,
createStackInstances_operationPreferences,
createStackInstances_parameterOverrides,
createStackInstances_stackSetName,
createStackInstances_regions,
CreateStackInstancesResponse (..),
newCreateStackInstancesResponse,
createStackInstancesResponse_operationId,
createStackInstancesResponse_httpStatus,
)
where
import Amazonka.CloudFormation.Types
import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import qualified Amazonka.Prelude as Prelude
import qualified Amazonka.Request as Request
import qualified Amazonka.Response as Response
data CreateStackInstances = CreateStackInstances'
{
CreateStackInstances -> Maybe [Text]
accounts :: Prelude.Maybe [Prelude.Text],
CreateStackInstances -> Maybe CallAs
callAs :: Prelude.Maybe CallAs,
CreateStackInstances -> Maybe DeploymentTargets
deploymentTargets :: Prelude.Maybe DeploymentTargets,
CreateStackInstances -> Maybe Text
operationId :: Prelude.Maybe Prelude.Text,
CreateStackInstances -> Maybe StackSetOperationPreferences
operationPreferences :: Prelude.Maybe StackSetOperationPreferences,
CreateStackInstances -> Maybe [Parameter]
parameterOverrides :: Prelude.Maybe [Parameter],
CreateStackInstances -> Text
stackSetName :: Prelude.Text,
CreateStackInstances -> [Text]
regions :: [Prelude.Text]
}
deriving (CreateStackInstances -> CreateStackInstances -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CreateStackInstances -> CreateStackInstances -> Bool
$c/= :: CreateStackInstances -> CreateStackInstances -> Bool
== :: CreateStackInstances -> CreateStackInstances -> Bool
$c== :: CreateStackInstances -> CreateStackInstances -> Bool
Prelude.Eq, ReadPrec [CreateStackInstances]
ReadPrec CreateStackInstances
Int -> ReadS CreateStackInstances
ReadS [CreateStackInstances]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CreateStackInstances]
$creadListPrec :: ReadPrec [CreateStackInstances]
readPrec :: ReadPrec CreateStackInstances
$creadPrec :: ReadPrec CreateStackInstances
readList :: ReadS [CreateStackInstances]
$creadList :: ReadS [CreateStackInstances]
readsPrec :: Int -> ReadS CreateStackInstances
$creadsPrec :: Int -> ReadS CreateStackInstances
Prelude.Read, Int -> CreateStackInstances -> ShowS
[CreateStackInstances] -> ShowS
CreateStackInstances -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CreateStackInstances] -> ShowS
$cshowList :: [CreateStackInstances] -> ShowS
show :: CreateStackInstances -> String
$cshow :: CreateStackInstances -> String
showsPrec :: Int -> CreateStackInstances -> ShowS
$cshowsPrec :: Int -> CreateStackInstances -> ShowS
Prelude.Show, forall x. Rep CreateStackInstances x -> CreateStackInstances
forall x. CreateStackInstances -> Rep CreateStackInstances x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CreateStackInstances x -> CreateStackInstances
$cfrom :: forall x. CreateStackInstances -> Rep CreateStackInstances x
Prelude.Generic)
newCreateStackInstances ::
Prelude.Text ->
CreateStackInstances
newCreateStackInstances :: Text -> CreateStackInstances
newCreateStackInstances Text
pStackSetName_ =
CreateStackInstances'
{ $sel:accounts:CreateStackInstances' :: Maybe [Text]
accounts = forall a. Maybe a
Prelude.Nothing,
$sel:callAs:CreateStackInstances' :: Maybe CallAs
callAs = forall a. Maybe a
Prelude.Nothing,
$sel:deploymentTargets:CreateStackInstances' :: Maybe DeploymentTargets
deploymentTargets = forall a. Maybe a
Prelude.Nothing,
$sel:operationId:CreateStackInstances' :: Maybe Text
operationId = forall a. Maybe a
Prelude.Nothing,
$sel:operationPreferences:CreateStackInstances' :: Maybe StackSetOperationPreferences
operationPreferences = forall a. Maybe a
Prelude.Nothing,
$sel:parameterOverrides:CreateStackInstances' :: Maybe [Parameter]
parameterOverrides = forall a. Maybe a
Prelude.Nothing,
$sel:stackSetName:CreateStackInstances' :: Text
stackSetName = Text
pStackSetName_,
$sel:regions:CreateStackInstances' :: [Text]
regions = forall a. Monoid a => a
Prelude.mempty
}
createStackInstances_accounts :: Lens.Lens' CreateStackInstances (Prelude.Maybe [Prelude.Text])
createStackInstances_accounts :: Lens' CreateStackInstances (Maybe [Text])
createStackInstances_accounts = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateStackInstances' {Maybe [Text]
accounts :: Maybe [Text]
$sel:accounts:CreateStackInstances' :: CreateStackInstances -> Maybe [Text]
accounts} -> Maybe [Text]
accounts) (\s :: CreateStackInstances
s@CreateStackInstances' {} Maybe [Text]
a -> CreateStackInstances
s {$sel:accounts:CreateStackInstances' :: Maybe [Text]
accounts = Maybe [Text]
a} :: CreateStackInstances) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
Lens.mapping forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced
createStackInstances_callAs :: Lens.Lens' CreateStackInstances (Prelude.Maybe CallAs)
createStackInstances_callAs :: Lens' CreateStackInstances (Maybe CallAs)
createStackInstances_callAs = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateStackInstances' {Maybe CallAs
callAs :: Maybe CallAs
$sel:callAs:CreateStackInstances' :: CreateStackInstances -> Maybe CallAs
callAs} -> Maybe CallAs
callAs) (\s :: CreateStackInstances
s@CreateStackInstances' {} Maybe CallAs
a -> CreateStackInstances
s {$sel:callAs:CreateStackInstances' :: Maybe CallAs
callAs = Maybe CallAs
a} :: CreateStackInstances)
createStackInstances_deploymentTargets :: Lens.Lens' CreateStackInstances (Prelude.Maybe DeploymentTargets)
createStackInstances_deploymentTargets :: Lens' CreateStackInstances (Maybe DeploymentTargets)
createStackInstances_deploymentTargets = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateStackInstances' {Maybe DeploymentTargets
deploymentTargets :: Maybe DeploymentTargets
$sel:deploymentTargets:CreateStackInstances' :: CreateStackInstances -> Maybe DeploymentTargets
deploymentTargets} -> Maybe DeploymentTargets
deploymentTargets) (\s :: CreateStackInstances
s@CreateStackInstances' {} Maybe DeploymentTargets
a -> CreateStackInstances
s {$sel:deploymentTargets:CreateStackInstances' :: Maybe DeploymentTargets
deploymentTargets = Maybe DeploymentTargets
a} :: CreateStackInstances)
createStackInstances_operationId :: Lens.Lens' CreateStackInstances (Prelude.Maybe Prelude.Text)
createStackInstances_operationId :: Lens' CreateStackInstances (Maybe Text)
createStackInstances_operationId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateStackInstances' {Maybe Text
operationId :: Maybe Text
$sel:operationId:CreateStackInstances' :: CreateStackInstances -> Maybe Text
operationId} -> Maybe Text
operationId) (\s :: CreateStackInstances
s@CreateStackInstances' {} Maybe Text
a -> CreateStackInstances
s {$sel:operationId:CreateStackInstances' :: Maybe Text
operationId = Maybe Text
a} :: CreateStackInstances)
createStackInstances_operationPreferences :: Lens.Lens' CreateStackInstances (Prelude.Maybe StackSetOperationPreferences)
createStackInstances_operationPreferences :: Lens' CreateStackInstances (Maybe StackSetOperationPreferences)
createStackInstances_operationPreferences = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateStackInstances' {Maybe StackSetOperationPreferences
operationPreferences :: Maybe StackSetOperationPreferences
$sel:operationPreferences:CreateStackInstances' :: CreateStackInstances -> Maybe StackSetOperationPreferences
operationPreferences} -> Maybe StackSetOperationPreferences
operationPreferences) (\s :: CreateStackInstances
s@CreateStackInstances' {} Maybe StackSetOperationPreferences
a -> CreateStackInstances
s {$sel:operationPreferences:CreateStackInstances' :: Maybe StackSetOperationPreferences
operationPreferences = Maybe StackSetOperationPreferences
a} :: CreateStackInstances)
createStackInstances_parameterOverrides :: Lens.Lens' CreateStackInstances (Prelude.Maybe [Parameter])
createStackInstances_parameterOverrides :: Lens' CreateStackInstances (Maybe [Parameter])
createStackInstances_parameterOverrides = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateStackInstances' {Maybe [Parameter]
parameterOverrides :: Maybe [Parameter]
$sel:parameterOverrides:CreateStackInstances' :: CreateStackInstances -> Maybe [Parameter]
parameterOverrides} -> Maybe [Parameter]
parameterOverrides) (\s :: CreateStackInstances
s@CreateStackInstances' {} Maybe [Parameter]
a -> CreateStackInstances
s {$sel:parameterOverrides:CreateStackInstances' :: Maybe [Parameter]
parameterOverrides = Maybe [Parameter]
a} :: CreateStackInstances) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
Lens.mapping forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced
createStackInstances_stackSetName :: Lens.Lens' CreateStackInstances Prelude.Text
createStackInstances_stackSetName :: Lens' CreateStackInstances Text
createStackInstances_stackSetName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateStackInstances' {Text
stackSetName :: Text
$sel:stackSetName:CreateStackInstances' :: CreateStackInstances -> Text
stackSetName} -> Text
stackSetName) (\s :: CreateStackInstances
s@CreateStackInstances' {} Text
a -> CreateStackInstances
s {$sel:stackSetName:CreateStackInstances' :: Text
stackSetName = Text
a} :: CreateStackInstances)
createStackInstances_regions :: Lens.Lens' CreateStackInstances [Prelude.Text]
createStackInstances_regions :: Lens' CreateStackInstances [Text]
createStackInstances_regions = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateStackInstances' {[Text]
regions :: [Text]
$sel:regions:CreateStackInstances' :: CreateStackInstances -> [Text]
regions} -> [Text]
regions) (\s :: CreateStackInstances
s@CreateStackInstances' {} [Text]
a -> CreateStackInstances
s {$sel:regions:CreateStackInstances' :: [Text]
regions = [Text]
a} :: CreateStackInstances) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced
instance Core.AWSRequest CreateStackInstances where
type
AWSResponse CreateStackInstances =
CreateStackInstancesResponse
request :: (Service -> Service)
-> CreateStackInstances -> Request CreateStackInstances
request Service -> Service
overrides =
forall a. ToRequest a => Service -> a -> Request a
Request.postQuery (Service -> Service
overrides Service
defaultService)
response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy CreateStackInstances
-> ClientResponse ClientBody
-> m (Either
Error (ClientResponse (AWSResponse CreateStackInstances)))
response =
forall (m :: * -> *) a.
MonadResource m =>
Text
-> (Int
-> ResponseHeaders -> [Node] -> Either String (AWSResponse a))
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveXMLWrapper
Text
"CreateStackInstancesResult"
( \Int
s ResponseHeaders
h [Node]
x ->
Maybe Text -> Int -> CreateStackInstancesResponse
CreateStackInstancesResponse'
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"OperationId")
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure (forall a. Enum a => a -> Int
Prelude.fromEnum Int
s))
)
instance Prelude.Hashable CreateStackInstances where
hashWithSalt :: Int -> CreateStackInstances -> Int
hashWithSalt Int
_salt CreateStackInstances' {[Text]
Maybe [Text]
Maybe [Parameter]
Maybe Text
Maybe CallAs
Maybe DeploymentTargets
Maybe StackSetOperationPreferences
Text
regions :: [Text]
stackSetName :: Text
parameterOverrides :: Maybe [Parameter]
operationPreferences :: Maybe StackSetOperationPreferences
operationId :: Maybe Text
deploymentTargets :: Maybe DeploymentTargets
callAs :: Maybe CallAs
accounts :: Maybe [Text]
$sel:regions:CreateStackInstances' :: CreateStackInstances -> [Text]
$sel:stackSetName:CreateStackInstances' :: CreateStackInstances -> Text
$sel:parameterOverrides:CreateStackInstances' :: CreateStackInstances -> Maybe [Parameter]
$sel:operationPreferences:CreateStackInstances' :: CreateStackInstances -> Maybe StackSetOperationPreferences
$sel:operationId:CreateStackInstances' :: CreateStackInstances -> Maybe Text
$sel:deploymentTargets:CreateStackInstances' :: CreateStackInstances -> Maybe DeploymentTargets
$sel:callAs:CreateStackInstances' :: CreateStackInstances -> Maybe CallAs
$sel:accounts:CreateStackInstances' :: CreateStackInstances -> Maybe [Text]
..} =
Int
_salt
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [Text]
accounts
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe CallAs
callAs
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe DeploymentTargets
deploymentTargets
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
operationId
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe StackSetOperationPreferences
operationPreferences
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [Parameter]
parameterOverrides
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
stackSetName
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` [Text]
regions
instance Prelude.NFData CreateStackInstances where
rnf :: CreateStackInstances -> ()
rnf CreateStackInstances' {[Text]
Maybe [Text]
Maybe [Parameter]
Maybe Text
Maybe CallAs
Maybe DeploymentTargets
Maybe StackSetOperationPreferences
Text
regions :: [Text]
stackSetName :: Text
parameterOverrides :: Maybe [Parameter]
operationPreferences :: Maybe StackSetOperationPreferences
operationId :: Maybe Text
deploymentTargets :: Maybe DeploymentTargets
callAs :: Maybe CallAs
accounts :: Maybe [Text]
$sel:regions:CreateStackInstances' :: CreateStackInstances -> [Text]
$sel:stackSetName:CreateStackInstances' :: CreateStackInstances -> Text
$sel:parameterOverrides:CreateStackInstances' :: CreateStackInstances -> Maybe [Parameter]
$sel:operationPreferences:CreateStackInstances' :: CreateStackInstances -> Maybe StackSetOperationPreferences
$sel:operationId:CreateStackInstances' :: CreateStackInstances -> Maybe Text
$sel:deploymentTargets:CreateStackInstances' :: CreateStackInstances -> Maybe DeploymentTargets
$sel:callAs:CreateStackInstances' :: CreateStackInstances -> Maybe CallAs
$sel:accounts:CreateStackInstances' :: CreateStackInstances -> Maybe [Text]
..} =
forall a. NFData a => a -> ()
Prelude.rnf Maybe [Text]
accounts
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe CallAs
callAs
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe DeploymentTargets
deploymentTargets
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
operationId
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe StackSetOperationPreferences
operationPreferences
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [Parameter]
parameterOverrides
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
stackSetName
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf [Text]
regions
instance Data.ToHeaders CreateStackInstances where
toHeaders :: CreateStackInstances -> ResponseHeaders
toHeaders = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty
instance Data.ToPath CreateStackInstances where
toPath :: CreateStackInstances -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/"
instance Data.ToQuery CreateStackInstances where
toQuery :: CreateStackInstances -> QueryString
toQuery CreateStackInstances' {[Text]
Maybe [Text]
Maybe [Parameter]
Maybe Text
Maybe CallAs
Maybe DeploymentTargets
Maybe StackSetOperationPreferences
Text
regions :: [Text]
stackSetName :: Text
parameterOverrides :: Maybe [Parameter]
operationPreferences :: Maybe StackSetOperationPreferences
operationId :: Maybe Text
deploymentTargets :: Maybe DeploymentTargets
callAs :: Maybe CallAs
accounts :: Maybe [Text]
$sel:regions:CreateStackInstances' :: CreateStackInstances -> [Text]
$sel:stackSetName:CreateStackInstances' :: CreateStackInstances -> Text
$sel:parameterOverrides:CreateStackInstances' :: CreateStackInstances -> Maybe [Parameter]
$sel:operationPreferences:CreateStackInstances' :: CreateStackInstances -> Maybe StackSetOperationPreferences
$sel:operationId:CreateStackInstances' :: CreateStackInstances -> Maybe Text
$sel:deploymentTargets:CreateStackInstances' :: CreateStackInstances -> Maybe DeploymentTargets
$sel:callAs:CreateStackInstances' :: CreateStackInstances -> Maybe CallAs
$sel:accounts:CreateStackInstances' :: CreateStackInstances -> Maybe [Text]
..} =
forall a. Monoid a => [a] -> a
Prelude.mconcat
[ ByteString
"Action"
forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"CreateStackInstances" :: Prelude.ByteString),
ByteString
"Version"
forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"2010-05-15" :: Prelude.ByteString),
ByteString
"Accounts"
forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: forall a. ToQuery a => a -> QueryString
Data.toQuery
(forall a.
(IsList a, ToQuery (Item a)) =>
ByteString -> a -> QueryString
Data.toQueryList ByteString
"member" forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [Text]
accounts),
ByteString
"CallAs" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe CallAs
callAs,
ByteString
"DeploymentTargets" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe DeploymentTargets
deploymentTargets,
ByteString
"OperationId" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
operationId,
ByteString
"OperationPreferences" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe StackSetOperationPreferences
operationPreferences,
ByteString
"ParameterOverrides"
forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: forall a. ToQuery a => a -> QueryString
Data.toQuery
( forall a.
(IsList a, ToQuery (Item a)) =>
ByteString -> a -> QueryString
Data.toQueryList ByteString
"member"
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [Parameter]
parameterOverrides
),
ByteString
"StackSetName" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Text
stackSetName,
ByteString
"Regions" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: forall a.
(IsList a, ToQuery (Item a)) =>
ByteString -> a -> QueryString
Data.toQueryList ByteString
"member" [Text]
regions
]
data CreateStackInstancesResponse = CreateStackInstancesResponse'
{
CreateStackInstancesResponse -> Maybe Text
operationId :: Prelude.Maybe Prelude.Text,
CreateStackInstancesResponse -> Int
httpStatus :: Prelude.Int
}
deriving (CreateStackInstancesResponse
-> CreateStackInstancesResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CreateStackInstancesResponse
-> CreateStackInstancesResponse -> Bool
$c/= :: CreateStackInstancesResponse
-> CreateStackInstancesResponse -> Bool
== :: CreateStackInstancesResponse
-> CreateStackInstancesResponse -> Bool
$c== :: CreateStackInstancesResponse
-> CreateStackInstancesResponse -> Bool
Prelude.Eq, ReadPrec [CreateStackInstancesResponse]
ReadPrec CreateStackInstancesResponse
Int -> ReadS CreateStackInstancesResponse
ReadS [CreateStackInstancesResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CreateStackInstancesResponse]
$creadListPrec :: ReadPrec [CreateStackInstancesResponse]
readPrec :: ReadPrec CreateStackInstancesResponse
$creadPrec :: ReadPrec CreateStackInstancesResponse
readList :: ReadS [CreateStackInstancesResponse]
$creadList :: ReadS [CreateStackInstancesResponse]
readsPrec :: Int -> ReadS CreateStackInstancesResponse
$creadsPrec :: Int -> ReadS CreateStackInstancesResponse
Prelude.Read, Int -> CreateStackInstancesResponse -> ShowS
[CreateStackInstancesResponse] -> ShowS
CreateStackInstancesResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CreateStackInstancesResponse] -> ShowS
$cshowList :: [CreateStackInstancesResponse] -> ShowS
show :: CreateStackInstancesResponse -> String
$cshow :: CreateStackInstancesResponse -> String
showsPrec :: Int -> CreateStackInstancesResponse -> ShowS
$cshowsPrec :: Int -> CreateStackInstancesResponse -> ShowS
Prelude.Show, forall x.
Rep CreateStackInstancesResponse x -> CreateStackInstancesResponse
forall x.
CreateStackInstancesResponse -> Rep CreateStackInstancesResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep CreateStackInstancesResponse x -> CreateStackInstancesResponse
$cfrom :: forall x.
CreateStackInstancesResponse -> Rep CreateStackInstancesResponse x
Prelude.Generic)
newCreateStackInstancesResponse ::
Prelude.Int ->
CreateStackInstancesResponse
newCreateStackInstancesResponse :: Int -> CreateStackInstancesResponse
newCreateStackInstancesResponse Int
pHttpStatus_ =
CreateStackInstancesResponse'
{ $sel:operationId:CreateStackInstancesResponse' :: Maybe Text
operationId =
forall a. Maybe a
Prelude.Nothing,
$sel:httpStatus:CreateStackInstancesResponse' :: Int
httpStatus = Int
pHttpStatus_
}
createStackInstancesResponse_operationId :: Lens.Lens' CreateStackInstancesResponse (Prelude.Maybe Prelude.Text)
createStackInstancesResponse_operationId :: Lens' CreateStackInstancesResponse (Maybe Text)
createStackInstancesResponse_operationId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateStackInstancesResponse' {Maybe Text
operationId :: Maybe Text
$sel:operationId:CreateStackInstancesResponse' :: CreateStackInstancesResponse -> Maybe Text
operationId} -> Maybe Text
operationId) (\s :: CreateStackInstancesResponse
s@CreateStackInstancesResponse' {} Maybe Text
a -> CreateStackInstancesResponse
s {$sel:operationId:CreateStackInstancesResponse' :: Maybe Text
operationId = Maybe Text
a} :: CreateStackInstancesResponse)
createStackInstancesResponse_httpStatus :: Lens.Lens' CreateStackInstancesResponse Prelude.Int
createStackInstancesResponse_httpStatus :: Lens' CreateStackInstancesResponse Int
createStackInstancesResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateStackInstancesResponse' {Int
httpStatus :: Int
$sel:httpStatus:CreateStackInstancesResponse' :: CreateStackInstancesResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: CreateStackInstancesResponse
s@CreateStackInstancesResponse' {} Int
a -> CreateStackInstancesResponse
s {$sel:httpStatus:CreateStackInstancesResponse' :: Int
httpStatus = Int
a} :: CreateStackInstancesResponse)
instance Prelude.NFData CreateStackInstancesResponse where
rnf :: CreateStackInstancesResponse -> ()
rnf CreateStackInstancesResponse' {Int
Maybe Text
httpStatus :: Int
operationId :: Maybe Text
$sel:httpStatus:CreateStackInstancesResponse' :: CreateStackInstancesResponse -> Int
$sel:operationId:CreateStackInstancesResponse' :: CreateStackInstancesResponse -> Maybe Text
..} =
forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
operationId
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus