{-# 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.OpsWorks.StopStack
(
StopStack (..),
newStopStack,
stopStack_stackId,
StopStackResponse (..),
newStopStackResponse,
)
where
import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import Amazonka.OpsWorks.Types
import qualified Amazonka.Prelude as Prelude
import qualified Amazonka.Request as Request
import qualified Amazonka.Response as Response
data StopStack = StopStack'
{
StopStack -> Text
stackId :: Prelude.Text
}
deriving (StopStack -> StopStack -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: StopStack -> StopStack -> Bool
$c/= :: StopStack -> StopStack -> Bool
== :: StopStack -> StopStack -> Bool
$c== :: StopStack -> StopStack -> Bool
Prelude.Eq, ReadPrec [StopStack]
ReadPrec StopStack
Int -> ReadS StopStack
ReadS [StopStack]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [StopStack]
$creadListPrec :: ReadPrec [StopStack]
readPrec :: ReadPrec StopStack
$creadPrec :: ReadPrec StopStack
readList :: ReadS [StopStack]
$creadList :: ReadS [StopStack]
readsPrec :: Int -> ReadS StopStack
$creadsPrec :: Int -> ReadS StopStack
Prelude.Read, Int -> StopStack -> ShowS
[StopStack] -> ShowS
StopStack -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [StopStack] -> ShowS
$cshowList :: [StopStack] -> ShowS
show :: StopStack -> String
$cshow :: StopStack -> String
showsPrec :: Int -> StopStack -> ShowS
$cshowsPrec :: Int -> StopStack -> ShowS
Prelude.Show, forall x. Rep StopStack x -> StopStack
forall x. StopStack -> Rep StopStack x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep StopStack x -> StopStack
$cfrom :: forall x. StopStack -> Rep StopStack x
Prelude.Generic)
newStopStack ::
Prelude.Text ->
StopStack
newStopStack :: Text -> StopStack
newStopStack Text
pStackId_ =
StopStack' {$sel:stackId:StopStack' :: Text
stackId = Text
pStackId_}
stopStack_stackId :: Lens.Lens' StopStack Prelude.Text
stopStack_stackId :: Lens' StopStack Text
stopStack_stackId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StopStack' {Text
stackId :: Text
$sel:stackId:StopStack' :: StopStack -> Text
stackId} -> Text
stackId) (\s :: StopStack
s@StopStack' {} Text
a -> StopStack
s {$sel:stackId:StopStack' :: Text
stackId = Text
a} :: StopStack)
instance Core.AWSRequest StopStack where
type AWSResponse StopStack = StopStackResponse
request :: (Service -> Service) -> StopStack -> Request StopStack
request Service -> Service
overrides =
forall a. (ToRequest a, ToJSON a) => Service -> a -> Request a
Request.postJSON (Service -> Service
overrides Service
defaultService)
response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy StopStack
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse StopStack)))
response = forall (m :: * -> *) a.
MonadResource m =>
AWSResponse a
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveNull StopStackResponse
StopStackResponse'
instance Prelude.Hashable StopStack where
hashWithSalt :: Int -> StopStack -> Int
hashWithSalt Int
_salt StopStack' {Text
stackId :: Text
$sel:stackId:StopStack' :: StopStack -> Text
..} =
Int
_salt forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
stackId
instance Prelude.NFData StopStack where
rnf :: StopStack -> ()
rnf StopStack' {Text
stackId :: Text
$sel:stackId:StopStack' :: StopStack -> Text
..} = forall a. NFData a => a -> ()
Prelude.rnf Text
stackId
instance Data.ToHeaders StopStack where
toHeaders :: StopStack -> [Header]
toHeaders =
forall a b. a -> b -> a
Prelude.const
( forall a. Monoid a => [a] -> a
Prelude.mconcat
[ HeaderName
"X-Amz-Target"
forall a. ToHeader a => HeaderName -> a -> [Header]
Data.=# ( ByteString
"OpsWorks_20130218.StopStack" ::
Prelude.ByteString
),
HeaderName
"Content-Type"
forall a. ToHeader a => HeaderName -> a -> [Header]
Data.=# ( ByteString
"application/x-amz-json-1.1" ::
Prelude.ByteString
)
]
)
instance Data.ToJSON StopStack where
toJSON :: StopStack -> Value
toJSON StopStack' {Text
stackId :: Text
$sel:stackId:StopStack' :: StopStack -> Text
..} =
[Pair] -> Value
Data.object
( forall a. [Maybe a] -> [a]
Prelude.catMaybes
[forall a. a -> Maybe a
Prelude.Just (Key
"StackId" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
stackId)]
)
instance Data.ToPath StopStack where
toPath :: StopStack -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/"
instance Data.ToQuery StopStack where
toQuery :: StopStack -> QueryString
toQuery = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty
data StopStackResponse = StopStackResponse'
{
}
deriving (StopStackResponse -> StopStackResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: StopStackResponse -> StopStackResponse -> Bool
$c/= :: StopStackResponse -> StopStackResponse -> Bool
== :: StopStackResponse -> StopStackResponse -> Bool
$c== :: StopStackResponse -> StopStackResponse -> Bool
Prelude.Eq, ReadPrec [StopStackResponse]
ReadPrec StopStackResponse
Int -> ReadS StopStackResponse
ReadS [StopStackResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [StopStackResponse]
$creadListPrec :: ReadPrec [StopStackResponse]
readPrec :: ReadPrec StopStackResponse
$creadPrec :: ReadPrec StopStackResponse
readList :: ReadS [StopStackResponse]
$creadList :: ReadS [StopStackResponse]
readsPrec :: Int -> ReadS StopStackResponse
$creadsPrec :: Int -> ReadS StopStackResponse
Prelude.Read, Int -> StopStackResponse -> ShowS
[StopStackResponse] -> ShowS
StopStackResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [StopStackResponse] -> ShowS
$cshowList :: [StopStackResponse] -> ShowS
show :: StopStackResponse -> String
$cshow :: StopStackResponse -> String
showsPrec :: Int -> StopStackResponse -> ShowS
$cshowsPrec :: Int -> StopStackResponse -> ShowS
Prelude.Show, forall x. Rep StopStackResponse x -> StopStackResponse
forall x. StopStackResponse -> Rep StopStackResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep StopStackResponse x -> StopStackResponse
$cfrom :: forall x. StopStackResponse -> Rep StopStackResponse x
Prelude.Generic)
newStopStackResponse ::
StopStackResponse
newStopStackResponse :: StopStackResponse
newStopStackResponse = StopStackResponse
StopStackResponse'
instance Prelude.NFData StopStackResponse where
rnf :: StopStackResponse -> ()
rnf StopStackResponse
_ = ()