{-# 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.StopStackSetOperation
(
StopStackSetOperation (..),
newStopStackSetOperation,
stopStackSetOperation_callAs,
stopStackSetOperation_stackSetName,
stopStackSetOperation_operationId,
StopStackSetOperationResponse (..),
newStopStackSetOperationResponse,
stopStackSetOperationResponse_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 StopStackSetOperation = StopStackSetOperation'
{
StopStackSetOperation -> Maybe CallAs
callAs :: Prelude.Maybe CallAs,
StopStackSetOperation -> Text
stackSetName :: Prelude.Text,
StopStackSetOperation -> Text
operationId :: Prelude.Text
}
deriving (StopStackSetOperation -> StopStackSetOperation -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: StopStackSetOperation -> StopStackSetOperation -> Bool
$c/= :: StopStackSetOperation -> StopStackSetOperation -> Bool
== :: StopStackSetOperation -> StopStackSetOperation -> Bool
$c== :: StopStackSetOperation -> StopStackSetOperation -> Bool
Prelude.Eq, ReadPrec [StopStackSetOperation]
ReadPrec StopStackSetOperation
Int -> ReadS StopStackSetOperation
ReadS [StopStackSetOperation]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [StopStackSetOperation]
$creadListPrec :: ReadPrec [StopStackSetOperation]
readPrec :: ReadPrec StopStackSetOperation
$creadPrec :: ReadPrec StopStackSetOperation
readList :: ReadS [StopStackSetOperation]
$creadList :: ReadS [StopStackSetOperation]
readsPrec :: Int -> ReadS StopStackSetOperation
$creadsPrec :: Int -> ReadS StopStackSetOperation
Prelude.Read, Int -> StopStackSetOperation -> ShowS
[StopStackSetOperation] -> ShowS
StopStackSetOperation -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [StopStackSetOperation] -> ShowS
$cshowList :: [StopStackSetOperation] -> ShowS
show :: StopStackSetOperation -> String
$cshow :: StopStackSetOperation -> String
showsPrec :: Int -> StopStackSetOperation -> ShowS
$cshowsPrec :: Int -> StopStackSetOperation -> ShowS
Prelude.Show, forall x. Rep StopStackSetOperation x -> StopStackSetOperation
forall x. StopStackSetOperation -> Rep StopStackSetOperation x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep StopStackSetOperation x -> StopStackSetOperation
$cfrom :: forall x. StopStackSetOperation -> Rep StopStackSetOperation x
Prelude.Generic)
newStopStackSetOperation ::
Prelude.Text ->
Prelude.Text ->
StopStackSetOperation
newStopStackSetOperation :: Text -> Text -> StopStackSetOperation
newStopStackSetOperation Text
pStackSetName_ Text
pOperationId_ =
StopStackSetOperation'
{ $sel:callAs:StopStackSetOperation' :: Maybe CallAs
callAs = forall a. Maybe a
Prelude.Nothing,
$sel:stackSetName:StopStackSetOperation' :: Text
stackSetName = Text
pStackSetName_,
$sel:operationId:StopStackSetOperation' :: Text
operationId = Text
pOperationId_
}
stopStackSetOperation_callAs :: Lens.Lens' StopStackSetOperation (Prelude.Maybe CallAs)
stopStackSetOperation_callAs :: Lens' StopStackSetOperation (Maybe CallAs)
stopStackSetOperation_callAs = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StopStackSetOperation' {Maybe CallAs
callAs :: Maybe CallAs
$sel:callAs:StopStackSetOperation' :: StopStackSetOperation -> Maybe CallAs
callAs} -> Maybe CallAs
callAs) (\s :: StopStackSetOperation
s@StopStackSetOperation' {} Maybe CallAs
a -> StopStackSetOperation
s {$sel:callAs:StopStackSetOperation' :: Maybe CallAs
callAs = Maybe CallAs
a} :: StopStackSetOperation)
stopStackSetOperation_stackSetName :: Lens.Lens' StopStackSetOperation Prelude.Text
stopStackSetOperation_stackSetName :: Lens' StopStackSetOperation Text
stopStackSetOperation_stackSetName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StopStackSetOperation' {Text
stackSetName :: Text
$sel:stackSetName:StopStackSetOperation' :: StopStackSetOperation -> Text
stackSetName} -> Text
stackSetName) (\s :: StopStackSetOperation
s@StopStackSetOperation' {} Text
a -> StopStackSetOperation
s {$sel:stackSetName:StopStackSetOperation' :: Text
stackSetName = Text
a} :: StopStackSetOperation)
stopStackSetOperation_operationId :: Lens.Lens' StopStackSetOperation Prelude.Text
stopStackSetOperation_operationId :: Lens' StopStackSetOperation Text
stopStackSetOperation_operationId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StopStackSetOperation' {Text
operationId :: Text
$sel:operationId:StopStackSetOperation' :: StopStackSetOperation -> Text
operationId} -> Text
operationId) (\s :: StopStackSetOperation
s@StopStackSetOperation' {} Text
a -> StopStackSetOperation
s {$sel:operationId:StopStackSetOperation' :: Text
operationId = Text
a} :: StopStackSetOperation)
instance Core.AWSRequest StopStackSetOperation where
type
AWSResponse StopStackSetOperation =
StopStackSetOperationResponse
request :: (Service -> Service)
-> StopStackSetOperation -> Request StopStackSetOperation
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 StopStackSetOperation
-> ClientResponse ClientBody
-> m (Either
Error (ClientResponse (AWSResponse StopStackSetOperation)))
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
"StopStackSetOperationResult"
( \Int
s ResponseHeaders
h [Node]
x ->
Int -> StopStackSetOperationResponse
StopStackSetOperationResponse'
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 StopStackSetOperation where
hashWithSalt :: Int -> StopStackSetOperation -> Int
hashWithSalt Int
_salt StopStackSetOperation' {Maybe CallAs
Text
operationId :: Text
stackSetName :: Text
callAs :: Maybe CallAs
$sel:operationId:StopStackSetOperation' :: StopStackSetOperation -> Text
$sel:stackSetName:StopStackSetOperation' :: StopStackSetOperation -> Text
$sel:callAs:StopStackSetOperation' :: StopStackSetOperation -> Maybe CallAs
..} =
Int
_salt
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe CallAs
callAs
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
stackSetName
forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
operationId
instance Prelude.NFData StopStackSetOperation where
rnf :: StopStackSetOperation -> ()
rnf StopStackSetOperation' {Maybe CallAs
Text
operationId :: Text
stackSetName :: Text
callAs :: Maybe CallAs
$sel:operationId:StopStackSetOperation' :: StopStackSetOperation -> Text
$sel:stackSetName:StopStackSetOperation' :: StopStackSetOperation -> Text
$sel:callAs:StopStackSetOperation' :: StopStackSetOperation -> Maybe CallAs
..} =
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 Text
stackSetName
seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
operationId
instance Data.ToHeaders StopStackSetOperation where
toHeaders :: StopStackSetOperation -> ResponseHeaders
toHeaders = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty
instance Data.ToPath StopStackSetOperation where
toPath :: StopStackSetOperation -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/"
instance Data.ToQuery StopStackSetOperation where
toQuery :: StopStackSetOperation -> QueryString
toQuery StopStackSetOperation' {Maybe CallAs
Text
operationId :: Text
stackSetName :: Text
callAs :: Maybe CallAs
$sel:operationId:StopStackSetOperation' :: StopStackSetOperation -> Text
$sel:stackSetName:StopStackSetOperation' :: StopStackSetOperation -> Text
$sel:callAs:StopStackSetOperation' :: StopStackSetOperation -> Maybe CallAs
..} =
forall a. Monoid a => [a] -> a
Prelude.mconcat
[ ByteString
"Action"
forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"StopStackSetOperation" :: Prelude.ByteString),
ByteString
"Version"
forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"2010-05-15" :: Prelude.ByteString),
ByteString
"CallAs" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe CallAs
callAs,
ByteString
"StackSetName" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Text
stackSetName,
ByteString
"OperationId" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Text
operationId
]
data StopStackSetOperationResponse = StopStackSetOperationResponse'
{
StopStackSetOperationResponse -> Int
httpStatus :: Prelude.Int
}
deriving (StopStackSetOperationResponse
-> StopStackSetOperationResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: StopStackSetOperationResponse
-> StopStackSetOperationResponse -> Bool
$c/= :: StopStackSetOperationResponse
-> StopStackSetOperationResponse -> Bool
== :: StopStackSetOperationResponse
-> StopStackSetOperationResponse -> Bool
$c== :: StopStackSetOperationResponse
-> StopStackSetOperationResponse -> Bool
Prelude.Eq, ReadPrec [StopStackSetOperationResponse]
ReadPrec StopStackSetOperationResponse
Int -> ReadS StopStackSetOperationResponse
ReadS [StopStackSetOperationResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [StopStackSetOperationResponse]
$creadListPrec :: ReadPrec [StopStackSetOperationResponse]
readPrec :: ReadPrec StopStackSetOperationResponse
$creadPrec :: ReadPrec StopStackSetOperationResponse
readList :: ReadS [StopStackSetOperationResponse]
$creadList :: ReadS [StopStackSetOperationResponse]
readsPrec :: Int -> ReadS StopStackSetOperationResponse
$creadsPrec :: Int -> ReadS StopStackSetOperationResponse
Prelude.Read, Int -> StopStackSetOperationResponse -> ShowS
[StopStackSetOperationResponse] -> ShowS
StopStackSetOperationResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [StopStackSetOperationResponse] -> ShowS
$cshowList :: [StopStackSetOperationResponse] -> ShowS
show :: StopStackSetOperationResponse -> String
$cshow :: StopStackSetOperationResponse -> String
showsPrec :: Int -> StopStackSetOperationResponse -> ShowS
$cshowsPrec :: Int -> StopStackSetOperationResponse -> ShowS
Prelude.Show, forall x.
Rep StopStackSetOperationResponse x
-> StopStackSetOperationResponse
forall x.
StopStackSetOperationResponse
-> Rep StopStackSetOperationResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep StopStackSetOperationResponse x
-> StopStackSetOperationResponse
$cfrom :: forall x.
StopStackSetOperationResponse
-> Rep StopStackSetOperationResponse x
Prelude.Generic)
newStopStackSetOperationResponse ::
Prelude.Int ->
StopStackSetOperationResponse
newStopStackSetOperationResponse :: Int -> StopStackSetOperationResponse
newStopStackSetOperationResponse Int
pHttpStatus_ =
StopStackSetOperationResponse'
{ $sel:httpStatus:StopStackSetOperationResponse' :: Int
httpStatus =
Int
pHttpStatus_
}
stopStackSetOperationResponse_httpStatus :: Lens.Lens' StopStackSetOperationResponse Prelude.Int
stopStackSetOperationResponse_httpStatus :: Lens' StopStackSetOperationResponse Int
stopStackSetOperationResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StopStackSetOperationResponse' {Int
httpStatus :: Int
$sel:httpStatus:StopStackSetOperationResponse' :: StopStackSetOperationResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: StopStackSetOperationResponse
s@StopStackSetOperationResponse' {} Int
a -> StopStackSetOperationResponse
s {$sel:httpStatus:StopStackSetOperationResponse' :: Int
httpStatus = Int
a} :: StopStackSetOperationResponse)
instance Prelude.NFData StopStackSetOperationResponse where
rnf :: StopStackSetOperationResponse -> ()
rnf StopStackSetOperationResponse' {Int
httpStatus :: Int
$sel:httpStatus:StopStackSetOperationResponse' :: StopStackSetOperationResponse -> Int
..} =
forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus