{-# 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 #-}

-- Derived from AWS service descriptions, licensed under Apache 2.0.

-- |
-- Module      : Amazonka.Greengrass.StopBulkDeployment
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Stops the execution of a bulk deployment. This action returns a status
-- of \'\'Stopping\'\' until the deployment is stopped. You cannot start a
-- new bulk deployment while a previous deployment is in the
-- \'\'Stopping\'\' state. This action doesn\'t rollback completed
-- deployments or cancel pending deployments.
module Amazonka.Greengrass.StopBulkDeployment
  ( -- * Creating a Request
    StopBulkDeployment (..),
    newStopBulkDeployment,

    -- * Request Lenses
    stopBulkDeployment_bulkDeploymentId,

    -- * Destructuring the Response
    StopBulkDeploymentResponse (..),
    newStopBulkDeploymentResponse,

    -- * Response Lenses
    stopBulkDeploymentResponse_httpStatus,
  )
where

import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import Amazonka.Greengrass.Types
import qualified Amazonka.Prelude as Prelude
import qualified Amazonka.Request as Request
import qualified Amazonka.Response as Response

-- | /See:/ 'newStopBulkDeployment' smart constructor.
data StopBulkDeployment = StopBulkDeployment'
  { -- | The ID of the bulk deployment.
    StopBulkDeployment -> Text
bulkDeploymentId :: Prelude.Text
  }
  deriving (StopBulkDeployment -> StopBulkDeployment -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: StopBulkDeployment -> StopBulkDeployment -> Bool
$c/= :: StopBulkDeployment -> StopBulkDeployment -> Bool
== :: StopBulkDeployment -> StopBulkDeployment -> Bool
$c== :: StopBulkDeployment -> StopBulkDeployment -> Bool
Prelude.Eq, ReadPrec [StopBulkDeployment]
ReadPrec StopBulkDeployment
Int -> ReadS StopBulkDeployment
ReadS [StopBulkDeployment]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [StopBulkDeployment]
$creadListPrec :: ReadPrec [StopBulkDeployment]
readPrec :: ReadPrec StopBulkDeployment
$creadPrec :: ReadPrec StopBulkDeployment
readList :: ReadS [StopBulkDeployment]
$creadList :: ReadS [StopBulkDeployment]
readsPrec :: Int -> ReadS StopBulkDeployment
$creadsPrec :: Int -> ReadS StopBulkDeployment
Prelude.Read, Int -> StopBulkDeployment -> ShowS
[StopBulkDeployment] -> ShowS
StopBulkDeployment -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [StopBulkDeployment] -> ShowS
$cshowList :: [StopBulkDeployment] -> ShowS
show :: StopBulkDeployment -> String
$cshow :: StopBulkDeployment -> String
showsPrec :: Int -> StopBulkDeployment -> ShowS
$cshowsPrec :: Int -> StopBulkDeployment -> ShowS
Prelude.Show, forall x. Rep StopBulkDeployment x -> StopBulkDeployment
forall x. StopBulkDeployment -> Rep StopBulkDeployment x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep StopBulkDeployment x -> StopBulkDeployment
$cfrom :: forall x. StopBulkDeployment -> Rep StopBulkDeployment x
Prelude.Generic)

-- |
-- Create a value of 'StopBulkDeployment' with all optional fields omitted.
--
-- Use <https://hackage.haskell.org/package/generic-lens generic-lens> or <https://hackage.haskell.org/package/optics optics> to modify other optional fields.
--
-- The following record fields are available, with the corresponding lenses provided
-- for backwards compatibility:
--
-- 'bulkDeploymentId', 'stopBulkDeployment_bulkDeploymentId' - The ID of the bulk deployment.
newStopBulkDeployment ::
  -- | 'bulkDeploymentId'
  Prelude.Text ->
  StopBulkDeployment
newStopBulkDeployment :: Text -> StopBulkDeployment
newStopBulkDeployment Text
pBulkDeploymentId_ =
  StopBulkDeployment'
    { $sel:bulkDeploymentId:StopBulkDeployment' :: Text
bulkDeploymentId =
        Text
pBulkDeploymentId_
    }

-- | The ID of the bulk deployment.
stopBulkDeployment_bulkDeploymentId :: Lens.Lens' StopBulkDeployment Prelude.Text
stopBulkDeployment_bulkDeploymentId :: Lens' StopBulkDeployment Text
stopBulkDeployment_bulkDeploymentId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StopBulkDeployment' {Text
bulkDeploymentId :: Text
$sel:bulkDeploymentId:StopBulkDeployment' :: StopBulkDeployment -> Text
bulkDeploymentId} -> Text
bulkDeploymentId) (\s :: StopBulkDeployment
s@StopBulkDeployment' {} Text
a -> StopBulkDeployment
s {$sel:bulkDeploymentId:StopBulkDeployment' :: Text
bulkDeploymentId = Text
a} :: StopBulkDeployment)

instance Core.AWSRequest StopBulkDeployment where
  type
    AWSResponse StopBulkDeployment =
      StopBulkDeploymentResponse
  request :: (Service -> Service)
-> StopBulkDeployment -> Request StopBulkDeployment
request Service -> Service
overrides =
    forall a. (ToRequest a, ToJSON a) => Service -> a -> Request a
Request.putJSON (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy StopBulkDeployment
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse StopBulkDeployment)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
(Int -> ResponseHeaders -> () -> Either String (AWSResponse a))
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveEmpty
      ( \Int
s ResponseHeaders
h ()
x ->
          Int -> StopBulkDeploymentResponse
StopBulkDeploymentResponse'
            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 StopBulkDeployment where
  hashWithSalt :: Int -> StopBulkDeployment -> Int
hashWithSalt Int
_salt StopBulkDeployment' {Text
bulkDeploymentId :: Text
$sel:bulkDeploymentId:StopBulkDeployment' :: StopBulkDeployment -> Text
..} =
    Int
_salt forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
bulkDeploymentId

instance Prelude.NFData StopBulkDeployment where
  rnf :: StopBulkDeployment -> ()
rnf StopBulkDeployment' {Text
bulkDeploymentId :: Text
$sel:bulkDeploymentId:StopBulkDeployment' :: StopBulkDeployment -> Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Text
bulkDeploymentId

instance Data.ToHeaders StopBulkDeployment where
  toHeaders :: StopBulkDeployment -> ResponseHeaders
toHeaders =
    forall a b. a -> b -> a
Prelude.const
      ( forall a. Monoid a => [a] -> a
Prelude.mconcat
          [ HeaderName
"Content-Type"
              forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ( ByteString
"application/x-amz-json-1.1" ::
                          Prelude.ByteString
                      )
          ]
      )

instance Data.ToJSON StopBulkDeployment where
  toJSON :: StopBulkDeployment -> Value
toJSON = forall a b. a -> b -> a
Prelude.const (Object -> Value
Data.Object forall a. Monoid a => a
Prelude.mempty)

instance Data.ToPath StopBulkDeployment where
  toPath :: StopBulkDeployment -> ByteString
toPath StopBulkDeployment' {Text
bulkDeploymentId :: Text
$sel:bulkDeploymentId:StopBulkDeployment' :: StopBulkDeployment -> Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"/greengrass/bulk/deployments/",
        forall a. ToByteString a => a -> ByteString
Data.toBS Text
bulkDeploymentId,
        ByteString
"/$stop"
      ]

instance Data.ToQuery StopBulkDeployment where
  toQuery :: StopBulkDeployment -> QueryString
toQuery = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty

-- | /See:/ 'newStopBulkDeploymentResponse' smart constructor.
data StopBulkDeploymentResponse = StopBulkDeploymentResponse'
  { -- | The response's http status code.
    StopBulkDeploymentResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (StopBulkDeploymentResponse -> StopBulkDeploymentResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: StopBulkDeploymentResponse -> StopBulkDeploymentResponse -> Bool
$c/= :: StopBulkDeploymentResponse -> StopBulkDeploymentResponse -> Bool
== :: StopBulkDeploymentResponse -> StopBulkDeploymentResponse -> Bool
$c== :: StopBulkDeploymentResponse -> StopBulkDeploymentResponse -> Bool
Prelude.Eq, ReadPrec [StopBulkDeploymentResponse]
ReadPrec StopBulkDeploymentResponse
Int -> ReadS StopBulkDeploymentResponse
ReadS [StopBulkDeploymentResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [StopBulkDeploymentResponse]
$creadListPrec :: ReadPrec [StopBulkDeploymentResponse]
readPrec :: ReadPrec StopBulkDeploymentResponse
$creadPrec :: ReadPrec StopBulkDeploymentResponse
readList :: ReadS [StopBulkDeploymentResponse]
$creadList :: ReadS [StopBulkDeploymentResponse]
readsPrec :: Int -> ReadS StopBulkDeploymentResponse
$creadsPrec :: Int -> ReadS StopBulkDeploymentResponse
Prelude.Read, Int -> StopBulkDeploymentResponse -> ShowS
[StopBulkDeploymentResponse] -> ShowS
StopBulkDeploymentResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [StopBulkDeploymentResponse] -> ShowS
$cshowList :: [StopBulkDeploymentResponse] -> ShowS
show :: StopBulkDeploymentResponse -> String
$cshow :: StopBulkDeploymentResponse -> String
showsPrec :: Int -> StopBulkDeploymentResponse -> ShowS
$cshowsPrec :: Int -> StopBulkDeploymentResponse -> ShowS
Prelude.Show, forall x.
Rep StopBulkDeploymentResponse x -> StopBulkDeploymentResponse
forall x.
StopBulkDeploymentResponse -> Rep StopBulkDeploymentResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep StopBulkDeploymentResponse x -> StopBulkDeploymentResponse
$cfrom :: forall x.
StopBulkDeploymentResponse -> Rep StopBulkDeploymentResponse x
Prelude.Generic)

-- |
-- Create a value of 'StopBulkDeploymentResponse' with all optional fields omitted.
--
-- Use <https://hackage.haskell.org/package/generic-lens generic-lens> or <https://hackage.haskell.org/package/optics optics> to modify other optional fields.
--
-- The following record fields are available, with the corresponding lenses provided
-- for backwards compatibility:
--
-- 'httpStatus', 'stopBulkDeploymentResponse_httpStatus' - The response's http status code.
newStopBulkDeploymentResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  StopBulkDeploymentResponse
newStopBulkDeploymentResponse :: Int -> StopBulkDeploymentResponse
newStopBulkDeploymentResponse Int
pHttpStatus_ =
  StopBulkDeploymentResponse'
    { $sel:httpStatus:StopBulkDeploymentResponse' :: Int
httpStatus =
        Int
pHttpStatus_
    }

-- | The response's http status code.
stopBulkDeploymentResponse_httpStatus :: Lens.Lens' StopBulkDeploymentResponse Prelude.Int
stopBulkDeploymentResponse_httpStatus :: Lens' StopBulkDeploymentResponse Int
stopBulkDeploymentResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StopBulkDeploymentResponse' {Int
httpStatus :: Int
$sel:httpStatus:StopBulkDeploymentResponse' :: StopBulkDeploymentResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: StopBulkDeploymentResponse
s@StopBulkDeploymentResponse' {} Int
a -> StopBulkDeploymentResponse
s {$sel:httpStatus:StopBulkDeploymentResponse' :: Int
httpStatus = Int
a} :: StopBulkDeploymentResponse)

instance Prelude.NFData StopBulkDeploymentResponse where
  rnf :: StopBulkDeploymentResponse -> ()
rnf StopBulkDeploymentResponse' {Int
httpStatus :: Int
$sel:httpStatus:StopBulkDeploymentResponse' :: StopBulkDeploymentResponse -> Int
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus