{-# 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.GreengrassV2.CancelDeployment
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Cancels a deployment. This operation cancels the deployment for devices
-- that haven\'t yet received it. If a device already received the
-- deployment, this operation doesn\'t change anything for that device.
module Amazonka.GreengrassV2.CancelDeployment
  ( -- * Creating a Request
    CancelDeployment (..),
    newCancelDeployment,

    -- * Request Lenses
    cancelDeployment_deploymentId,

    -- * Destructuring the Response
    CancelDeploymentResponse (..),
    newCancelDeploymentResponse,

    -- * Response Lenses
    cancelDeploymentResponse_message,
    cancelDeploymentResponse_httpStatus,
  )
where

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

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

-- |
-- Create a value of 'CancelDeployment' 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:
--
-- 'deploymentId', 'cancelDeployment_deploymentId' - The ID of the deployment.
newCancelDeployment ::
  -- | 'deploymentId'
  Prelude.Text ->
  CancelDeployment
newCancelDeployment :: Text -> CancelDeployment
newCancelDeployment Text
pDeploymentId_ =
  CancelDeployment' {$sel:deploymentId:CancelDeployment' :: Text
deploymentId = Text
pDeploymentId_}

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

instance Core.AWSRequest CancelDeployment where
  type
    AWSResponse CancelDeployment =
      CancelDeploymentResponse
  request :: (Service -> Service)
-> CancelDeployment -> Request CancelDeployment
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 CancelDeployment
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse CancelDeployment)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
(Int -> ResponseHeaders -> Object -> Either String (AWSResponse a))
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveJSON
      ( \Int
s ResponseHeaders
h Object
x ->
          Maybe Text -> Int -> CancelDeploymentResponse
CancelDeploymentResponse'
            forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"message")
            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 CancelDeployment where
  hashWithSalt :: Int -> CancelDeployment -> Int
hashWithSalt Int
_salt CancelDeployment' {Text
deploymentId :: Text
$sel:deploymentId:CancelDeployment' :: CancelDeployment -> Text
..} =
    Int
_salt forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
deploymentId

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

instance Data.ToHeaders CancelDeployment where
  toHeaders :: CancelDeployment -> ResponseHeaders
toHeaders = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty

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

instance Data.ToPath CancelDeployment where
  toPath :: CancelDeployment -> ByteString
toPath CancelDeployment' {Text
deploymentId :: Text
$sel:deploymentId:CancelDeployment' :: CancelDeployment -> Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"/greengrass/v2/deployments/",
        forall a. ToByteString a => a -> ByteString
Data.toBS Text
deploymentId,
        ByteString
"/cancel"
      ]

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

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

-- |
-- Create a value of 'CancelDeploymentResponse' 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:
--
-- 'message', 'cancelDeploymentResponse_message' - A message that communicates if the cancel was successful.
--
-- 'httpStatus', 'cancelDeploymentResponse_httpStatus' - The response's http status code.
newCancelDeploymentResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  CancelDeploymentResponse
newCancelDeploymentResponse :: Int -> CancelDeploymentResponse
newCancelDeploymentResponse Int
pHttpStatus_ =
  CancelDeploymentResponse'
    { $sel:message:CancelDeploymentResponse' :: Maybe Text
message =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:CancelDeploymentResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | A message that communicates if the cancel was successful.
cancelDeploymentResponse_message :: Lens.Lens' CancelDeploymentResponse (Prelude.Maybe Prelude.Text)
cancelDeploymentResponse_message :: Lens' CancelDeploymentResponse (Maybe Text)
cancelDeploymentResponse_message = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CancelDeploymentResponse' {Maybe Text
message :: Maybe Text
$sel:message:CancelDeploymentResponse' :: CancelDeploymentResponse -> Maybe Text
message} -> Maybe Text
message) (\s :: CancelDeploymentResponse
s@CancelDeploymentResponse' {} Maybe Text
a -> CancelDeploymentResponse
s {$sel:message:CancelDeploymentResponse' :: Maybe Text
message = Maybe Text
a} :: CancelDeploymentResponse)

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

instance Prelude.NFData CancelDeploymentResponse where
  rnf :: CancelDeploymentResponse -> ()
rnf CancelDeploymentResponse' {Int
Maybe Text
httpStatus :: Int
message :: Maybe Text
$sel:httpStatus:CancelDeploymentResponse' :: CancelDeploymentResponse -> Int
$sel:message:CancelDeploymentResponse' :: CancelDeploymentResponse -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
message
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus