{-# 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.ContinueUpdateRollback
(
ContinueUpdateRollback (..),
newContinueUpdateRollback,
continueUpdateRollback_clientRequestToken,
continueUpdateRollback_resourcesToSkip,
continueUpdateRollback_roleARN,
continueUpdateRollback_stackName,
ContinueUpdateRollbackResponse (..),
newContinueUpdateRollbackResponse,
continueUpdateRollbackResponse_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 ContinueUpdateRollback = ContinueUpdateRollback'
{
ContinueUpdateRollback -> Maybe Text
clientRequestToken :: Prelude.Maybe Prelude.Text,
ContinueUpdateRollback -> Maybe [Text]
resourcesToSkip :: Prelude.Maybe [Prelude.Text],
ContinueUpdateRollback -> Maybe Text
roleARN :: Prelude.Maybe Prelude.Text,
ContinueUpdateRollback -> Text
stackName :: Prelude.Text
}
deriving (ContinueUpdateRollback -> ContinueUpdateRollback -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ContinueUpdateRollback -> ContinueUpdateRollback -> Bool
$c/= :: ContinueUpdateRollback -> ContinueUpdateRollback -> Bool
== :: ContinueUpdateRollback -> ContinueUpdateRollback -> Bool
$c== :: ContinueUpdateRollback -> ContinueUpdateRollback -> Bool
Prelude.Eq, ReadPrec [ContinueUpdateRollback]
ReadPrec ContinueUpdateRollback
Int -> ReadS ContinueUpdateRollback
ReadS [ContinueUpdateRollback]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ContinueUpdateRollback]
$creadListPrec :: ReadPrec [ContinueUpdateRollback]
readPrec :: ReadPrec ContinueUpdateRollback
$creadPrec :: ReadPrec ContinueUpdateRollback
readList :: ReadS [ContinueUpdateRollback]
$creadList :: ReadS [ContinueUpdateRollback]
readsPrec :: Int -> ReadS ContinueUpdateRollback
$creadsPrec :: Int -> ReadS ContinueUpdateRollback
Prelude.Read, Int -> ContinueUpdateRollback -> ShowS
[ContinueUpdateRollback] -> ShowS
ContinueUpdateRollback -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ContinueUpdateRollback] -> ShowS
$cshowList :: [ContinueUpdateRollback] -> ShowS
show :: ContinueUpdateRollback -> String
$cshow :: ContinueUpdateRollback -> String
showsPrec :: Int -> ContinueUpdateRollback -> ShowS
$cshowsPrec :: Int -> ContinueUpdateRollback -> ShowS
Prelude.Show, forall x. Rep ContinueUpdateRollback x -> ContinueUpdateRollback
forall x. ContinueUpdateRollback -> Rep ContinueUpdateRollback x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ContinueUpdateRollback x -> ContinueUpdateRollback
$cfrom :: forall x. ContinueUpdateRollback -> Rep ContinueUpdateRollback x
Prelude.Generic)
newContinueUpdateRollback ::
Prelude.Text ->
ContinueUpdateRollback
newContinueUpdateRollback :: Text -> ContinueUpdateRollback
newContinueUpdateRollback Text
pStackName_ =
ContinueUpdateRollback'
{ $sel:clientRequestToken:ContinueUpdateRollback' :: Maybe Text
clientRequestToken =
forall a. Maybe a
Prelude.Nothing,
$sel:resourcesToSkip:ContinueUpdateRollback' :: Maybe [Text]
resourcesToSkip = forall a. Maybe a
Prelude.Nothing,
$sel:roleARN:ContinueUpdateRollback' :: Maybe Text
roleARN = forall a. Maybe a
Prelude.Nothing,
$sel:stackName:ContinueUpdateRollback' :: Text
stackName = Text
pStackName_
}
continueUpdateRollback_clientRequestToken :: Lens.Lens' ContinueUpdateRollback (Prelude.Maybe Prelude.Text)
continueUpdateRollback_clientRequestToken :: Lens' ContinueUpdateRollback (Maybe Text)
continueUpdateRollback_clientRequestToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ContinueUpdateRollback' {Maybe Text
clientRequestToken :: Maybe Text
$sel:clientRequestToken:ContinueUpdateRollback' :: ContinueUpdateRollback -> Maybe Text
clientRequestToken} -> Maybe Text
clientRequestToken) (\s :: ContinueUpdateRollback
s@ContinueUpdateRollback' {} Maybe Text
a -> ContinueUpdateRollback
s {$sel:clientRequestToken:ContinueUpdateRollback' :: Maybe Text
clientRequestToken = Maybe Text
a} :: ContinueUpdateRollback)
continueUpdateRollback_resourcesToSkip :: Lens.Lens' ContinueUpdateRollback (Prelude.Maybe [Prelude.Text])
continueUpdateRollback_resourcesToSkip :: Lens' ContinueUpdateRollback (Maybe [Text])
continueUpdateRollback_resourcesToSkip = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ContinueUpdateRollback' {Maybe [Text]
resourcesToSkip :: Maybe [Text]
$sel:resourcesToSkip:ContinueUpdateRollback' :: ContinueUpdateRollback -> Maybe [Text]
resourcesToSkip} -> Maybe [Text]
resourcesToSkip) (\s :: ContinueUpdateRollback
s@ContinueUpdateRollback' {} Maybe [Text]
a -> ContinueUpdateRollback
s {$sel:resourcesToSkip:ContinueUpdateRollback' :: Maybe [Text]
resourcesToSkip = Maybe [Text]
a} :: ContinueUpdateRollback) 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
continueUpdateRollback_roleARN :: Lens.Lens' ContinueUpdateRollback (Prelude.Maybe Prelude.Text)
continueUpdateRollback_roleARN :: Lens' ContinueUpdateRollback (Maybe Text)
continueUpdateRollback_roleARN = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ContinueUpdateRollback' {Maybe Text
roleARN :: Maybe Text
$sel:roleARN:ContinueUpdateRollback' :: ContinueUpdateRollback -> Maybe Text
roleARN} -> Maybe Text
roleARN) (\s :: ContinueUpdateRollback
s@ContinueUpdateRollback' {} Maybe Text
a -> ContinueUpdateRollback
s {$sel:roleARN:ContinueUpdateRollback' :: Maybe Text
roleARN = Maybe Text
a} :: ContinueUpdateRollback)
continueUpdateRollback_stackName :: Lens.Lens' ContinueUpdateRollback Prelude.Text
continueUpdateRollback_stackName :: Lens' ContinueUpdateRollback Text
continueUpdateRollback_stackName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ContinueUpdateRollback' {Text
stackName :: Text
$sel:stackName:ContinueUpdateRollback' :: ContinueUpdateRollback -> Text
stackName} -> Text
stackName) (\s :: ContinueUpdateRollback
s@ContinueUpdateRollback' {} Text
a -> ContinueUpdateRollback
s {$sel:stackName:ContinueUpdateRollback' :: Text
stackName = Text
a} :: ContinueUpdateRollback)
instance Core.AWSRequest ContinueUpdateRollback where
type
AWSResponse ContinueUpdateRollback =
ContinueUpdateRollbackResponse
request :: (Service -> Service)
-> ContinueUpdateRollback -> Request ContinueUpdateRollback
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 ContinueUpdateRollback
-> ClientResponse ClientBody
-> m (Either
Error (ClientResponse (AWSResponse ContinueUpdateRollback)))
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
"ContinueUpdateRollbackResult"
( \Int
s ResponseHeaders
h [Node]
x ->
Int -> ContinueUpdateRollbackResponse
ContinueUpdateRollbackResponse'
forall (f :: * -> *) a b. Functor 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 ContinueUpdateRollback where
hashWithSalt :: Int -> ContinueUpdateRollback -> Int
hashWithSalt Int
_salt ContinueUpdateRollback' {Maybe [Text]
Maybe Text
Text
stackName :: Text
roleARN :: Maybe Text
resourcesToSkip :: Maybe [Text]
clientRequestToken :: Maybe Text
$sel:stackName:ContinueUpdateRollback' :: ContinueUpdateRollback -> Text
$sel:roleARN:ContinueUpdateRollback' :: ContinueUpdateRollback -> Maybe Text
$sel:resourcesToSkip:ContinueUpdateRollback' :: ContinueUpdateRollback -> Maybe [Text]
$sel:clientRequestToken:ContinueUpdateRollback' :: ContinueUpdateRollback -> Maybe Text
..} =
Int
_salt
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
clientRequestToken
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [Text]
resourcesToSkip
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
roleARN
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
stackName
instance Prelude.NFData ContinueUpdateRollback where
rnf :: ContinueUpdateRollback -> ()
rnf ContinueUpdateRollback' {Maybe [Text]
Maybe Text
Text
stackName :: Text
roleARN :: Maybe Text
resourcesToSkip :: Maybe [Text]
clientRequestToken :: Maybe Text
$sel:stackName:ContinueUpdateRollback' :: ContinueUpdateRollback -> Text
$sel:roleARN:ContinueUpdateRollback' :: ContinueUpdateRollback -> Maybe Text
$sel:resourcesToSkip:ContinueUpdateRollback' :: ContinueUpdateRollback -> Maybe [Text]
$sel:clientRequestToken:ContinueUpdateRollback' :: ContinueUpdateRollback -> Maybe Text
..} =
forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
clientRequestToken
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [Text]
resourcesToSkip
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
roleARN
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
stackName
instance Data.ToHeaders ContinueUpdateRollback where
toHeaders :: ContinueUpdateRollback -> ResponseHeaders
toHeaders = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty
instance Data.ToPath ContinueUpdateRollback where
toPath :: ContinueUpdateRollback -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/"
instance Data.ToQuery ContinueUpdateRollback where
toQuery :: ContinueUpdateRollback -> QueryString
toQuery ContinueUpdateRollback' {Maybe [Text]
Maybe Text
Text
stackName :: Text
roleARN :: Maybe Text
resourcesToSkip :: Maybe [Text]
clientRequestToken :: Maybe Text
$sel:stackName:ContinueUpdateRollback' :: ContinueUpdateRollback -> Text
$sel:roleARN:ContinueUpdateRollback' :: ContinueUpdateRollback -> Maybe Text
$sel:resourcesToSkip:ContinueUpdateRollback' :: ContinueUpdateRollback -> Maybe [Text]
$sel:clientRequestToken:ContinueUpdateRollback' :: ContinueUpdateRollback -> Maybe Text
..} =
forall a. Monoid a => [a] -> a
Prelude.mconcat
[ ByteString
"Action"
forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"ContinueUpdateRollback" :: Prelude.ByteString),
ByteString
"Version"
forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"2010-05-15" :: Prelude.ByteString),
ByteString
"ClientRequestToken" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
clientRequestToken,
ByteString
"ResourcesToSkip"
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]
resourcesToSkip
),
ByteString
"RoleARN" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
roleARN,
ByteString
"StackName" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Text
stackName
]
data ContinueUpdateRollbackResponse = ContinueUpdateRollbackResponse'
{
ContinueUpdateRollbackResponse -> Int
httpStatus :: Prelude.Int
}
deriving (ContinueUpdateRollbackResponse
-> ContinueUpdateRollbackResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ContinueUpdateRollbackResponse
-> ContinueUpdateRollbackResponse -> Bool
$c/= :: ContinueUpdateRollbackResponse
-> ContinueUpdateRollbackResponse -> Bool
== :: ContinueUpdateRollbackResponse
-> ContinueUpdateRollbackResponse -> Bool
$c== :: ContinueUpdateRollbackResponse
-> ContinueUpdateRollbackResponse -> Bool
Prelude.Eq, ReadPrec [ContinueUpdateRollbackResponse]
ReadPrec ContinueUpdateRollbackResponse
Int -> ReadS ContinueUpdateRollbackResponse
ReadS [ContinueUpdateRollbackResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ContinueUpdateRollbackResponse]
$creadListPrec :: ReadPrec [ContinueUpdateRollbackResponse]
readPrec :: ReadPrec ContinueUpdateRollbackResponse
$creadPrec :: ReadPrec ContinueUpdateRollbackResponse
readList :: ReadS [ContinueUpdateRollbackResponse]
$creadList :: ReadS [ContinueUpdateRollbackResponse]
readsPrec :: Int -> ReadS ContinueUpdateRollbackResponse
$creadsPrec :: Int -> ReadS ContinueUpdateRollbackResponse
Prelude.Read, Int -> ContinueUpdateRollbackResponse -> ShowS
[ContinueUpdateRollbackResponse] -> ShowS
ContinueUpdateRollbackResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ContinueUpdateRollbackResponse] -> ShowS
$cshowList :: [ContinueUpdateRollbackResponse] -> ShowS
show :: ContinueUpdateRollbackResponse -> String
$cshow :: ContinueUpdateRollbackResponse -> String
showsPrec :: Int -> ContinueUpdateRollbackResponse -> ShowS
$cshowsPrec :: Int -> ContinueUpdateRollbackResponse -> ShowS
Prelude.Show, forall x.
Rep ContinueUpdateRollbackResponse x
-> ContinueUpdateRollbackResponse
forall x.
ContinueUpdateRollbackResponse
-> Rep ContinueUpdateRollbackResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep ContinueUpdateRollbackResponse x
-> ContinueUpdateRollbackResponse
$cfrom :: forall x.
ContinueUpdateRollbackResponse
-> Rep ContinueUpdateRollbackResponse x
Prelude.Generic)
newContinueUpdateRollbackResponse ::
Prelude.Int ->
ContinueUpdateRollbackResponse
newContinueUpdateRollbackResponse :: Int -> ContinueUpdateRollbackResponse
newContinueUpdateRollbackResponse Int
pHttpStatus_ =
ContinueUpdateRollbackResponse'
{ $sel:httpStatus:ContinueUpdateRollbackResponse' :: Int
httpStatus =
Int
pHttpStatus_
}
continueUpdateRollbackResponse_httpStatus :: Lens.Lens' ContinueUpdateRollbackResponse Prelude.Int
continueUpdateRollbackResponse_httpStatus :: Lens' ContinueUpdateRollbackResponse Int
continueUpdateRollbackResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ContinueUpdateRollbackResponse' {Int
httpStatus :: Int
$sel:httpStatus:ContinueUpdateRollbackResponse' :: ContinueUpdateRollbackResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: ContinueUpdateRollbackResponse
s@ContinueUpdateRollbackResponse' {} Int
a -> ContinueUpdateRollbackResponse
s {$sel:httpStatus:ContinueUpdateRollbackResponse' :: Int
httpStatus = Int
a} :: ContinueUpdateRollbackResponse)
instance
Prelude.NFData
ContinueUpdateRollbackResponse
where
rnf :: ContinueUpdateRollbackResponse -> ()
rnf ContinueUpdateRollbackResponse' {Int
httpStatus :: Int
$sel:httpStatus:ContinueUpdateRollbackResponse' :: ContinueUpdateRollbackResponse -> Int
..} =
forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus