{-# 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.DeleteDeployment
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Deletes a deployment. To delete an active deployment, you must first
-- cancel it. For more information, see
-- <https://docs.aws.amazon.com/iot/latest/apireference/API_CancelDeployment.html CancelDeployment>.
--
-- Deleting a deployment doesn\'t affect core devices that run that
-- deployment, because core devices store the deployment\'s configuration
-- on the device. Additionally, core devices can roll back to a previous
-- deployment that has been deleted.
module Amazonka.GreengrassV2.DeleteDeployment
  ( -- * Creating a Request
    DeleteDeployment (..),
    newDeleteDeployment,

    -- * Request Lenses
    deleteDeployment_deploymentId,

    -- * Destructuring the Response
    DeleteDeploymentResponse (..),
    newDeleteDeploymentResponse,
  )
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:/ 'newDeleteDeployment' smart constructor.
data DeleteDeployment = DeleteDeployment'
  { -- | The ID of the deployment.
    DeleteDeployment -> Text
deploymentId :: Prelude.Text
  }
  deriving (DeleteDeployment -> DeleteDeployment -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DeleteDeployment -> DeleteDeployment -> Bool
$c/= :: DeleteDeployment -> DeleteDeployment -> Bool
== :: DeleteDeployment -> DeleteDeployment -> Bool
$c== :: DeleteDeployment -> DeleteDeployment -> Bool
Prelude.Eq, ReadPrec [DeleteDeployment]
ReadPrec DeleteDeployment
Int -> ReadS DeleteDeployment
ReadS [DeleteDeployment]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DeleteDeployment]
$creadListPrec :: ReadPrec [DeleteDeployment]
readPrec :: ReadPrec DeleteDeployment
$creadPrec :: ReadPrec DeleteDeployment
readList :: ReadS [DeleteDeployment]
$creadList :: ReadS [DeleteDeployment]
readsPrec :: Int -> ReadS DeleteDeployment
$creadsPrec :: Int -> ReadS DeleteDeployment
Prelude.Read, Int -> DeleteDeployment -> ShowS
[DeleteDeployment] -> ShowS
DeleteDeployment -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DeleteDeployment] -> ShowS
$cshowList :: [DeleteDeployment] -> ShowS
show :: DeleteDeployment -> String
$cshow :: DeleteDeployment -> String
showsPrec :: Int -> DeleteDeployment -> ShowS
$cshowsPrec :: Int -> DeleteDeployment -> ShowS
Prelude.Show, forall x. Rep DeleteDeployment x -> DeleteDeployment
forall x. DeleteDeployment -> Rep DeleteDeployment x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DeleteDeployment x -> DeleteDeployment
$cfrom :: forall x. DeleteDeployment -> Rep DeleteDeployment x
Prelude.Generic)

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

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

instance Core.AWSRequest DeleteDeployment where
  type
    AWSResponse DeleteDeployment =
      DeleteDeploymentResponse
  request :: (Service -> Service)
-> DeleteDeployment -> Request DeleteDeployment
request Service -> Service
overrides =
    forall a. ToRequest a => Service -> a -> Request a
Request.delete (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy DeleteDeployment
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse DeleteDeployment)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
AWSResponse a
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveNull DeleteDeploymentResponse
DeleteDeploymentResponse'

instance Prelude.Hashable DeleteDeployment where
  hashWithSalt :: Int -> DeleteDeployment -> Int
hashWithSalt Int
_salt DeleteDeployment' {Text
deploymentId :: Text
$sel:deploymentId:DeleteDeployment' :: DeleteDeployment -> Text
..} =
    Int
_salt forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
deploymentId

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

instance Data.ToHeaders DeleteDeployment where
  toHeaders :: DeleteDeployment -> [Header]
toHeaders = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty

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

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

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

-- |
-- Create a value of 'DeleteDeploymentResponse' 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.
newDeleteDeploymentResponse ::
  DeleteDeploymentResponse
newDeleteDeploymentResponse :: DeleteDeploymentResponse
newDeleteDeploymentResponse =
  DeleteDeploymentResponse
DeleteDeploymentResponse'

instance Prelude.NFData DeleteDeploymentResponse where
  rnf :: DeleteDeploymentResponse -> ()
rnf DeleteDeploymentResponse
_ = ()