{-# 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.AppConfig.StopDeployment
-- 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 a deployment. This API action works only on deployments that have
-- a status of @DEPLOYING@. This action moves the deployment to a status of
-- @ROLLED_BACK@.
module Amazonka.AppConfig.StopDeployment
  ( -- * Creating a Request
    StopDeployment (..),
    newStopDeployment,

    -- * Request Lenses
    stopDeployment_applicationId,
    stopDeployment_environmentId,
    stopDeployment_deploymentNumber,

    -- * Destructuring the Response
    Deployment (..),
    newDeployment,

    -- * Response Lenses
    deployment_applicationId,
    deployment_appliedExtensions,
    deployment_completedAt,
    deployment_configurationLocationUri,
    deployment_configurationName,
    deployment_configurationProfileId,
    deployment_configurationVersion,
    deployment_deploymentDurationInMinutes,
    deployment_deploymentNumber,
    deployment_deploymentStrategyId,
    deployment_description,
    deployment_environmentId,
    deployment_eventLog,
    deployment_finalBakeTimeInMinutes,
    deployment_growthFactor,
    deployment_growthType,
    deployment_percentageComplete,
    deployment_startedAt,
    deployment_state,
  )
where

import Amazonka.AppConfig.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

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

-- |
-- Create a value of 'StopDeployment' 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:
--
-- 'applicationId', 'stopDeployment_applicationId' - The application ID.
--
-- 'environmentId', 'stopDeployment_environmentId' - The environment ID.
--
-- 'deploymentNumber', 'stopDeployment_deploymentNumber' - The sequence number of the deployment.
newStopDeployment ::
  -- | 'applicationId'
  Prelude.Text ->
  -- | 'environmentId'
  Prelude.Text ->
  -- | 'deploymentNumber'
  Prelude.Int ->
  StopDeployment
newStopDeployment :: Text -> Text -> Int -> StopDeployment
newStopDeployment
  Text
pApplicationId_
  Text
pEnvironmentId_
  Int
pDeploymentNumber_ =
    StopDeployment'
      { $sel:applicationId:StopDeployment' :: Text
applicationId = Text
pApplicationId_,
        $sel:environmentId:StopDeployment' :: Text
environmentId = Text
pEnvironmentId_,
        $sel:deploymentNumber:StopDeployment' :: Int
deploymentNumber = Int
pDeploymentNumber_
      }

-- | The application ID.
stopDeployment_applicationId :: Lens.Lens' StopDeployment Prelude.Text
stopDeployment_applicationId :: Lens' StopDeployment Text
stopDeployment_applicationId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StopDeployment' {Text
applicationId :: Text
$sel:applicationId:StopDeployment' :: StopDeployment -> Text
applicationId} -> Text
applicationId) (\s :: StopDeployment
s@StopDeployment' {} Text
a -> StopDeployment
s {$sel:applicationId:StopDeployment' :: Text
applicationId = Text
a} :: StopDeployment)

-- | The environment ID.
stopDeployment_environmentId :: Lens.Lens' StopDeployment Prelude.Text
stopDeployment_environmentId :: Lens' StopDeployment Text
stopDeployment_environmentId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StopDeployment' {Text
environmentId :: Text
$sel:environmentId:StopDeployment' :: StopDeployment -> Text
environmentId} -> Text
environmentId) (\s :: StopDeployment
s@StopDeployment' {} Text
a -> StopDeployment
s {$sel:environmentId:StopDeployment' :: Text
environmentId = Text
a} :: StopDeployment)

-- | The sequence number of the deployment.
stopDeployment_deploymentNumber :: Lens.Lens' StopDeployment Prelude.Int
stopDeployment_deploymentNumber :: Lens' StopDeployment Int
stopDeployment_deploymentNumber = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StopDeployment' {Int
deploymentNumber :: Int
$sel:deploymentNumber:StopDeployment' :: StopDeployment -> Int
deploymentNumber} -> Int
deploymentNumber) (\s :: StopDeployment
s@StopDeployment' {} Int
a -> StopDeployment
s {$sel:deploymentNumber:StopDeployment' :: Int
deploymentNumber = Int
a} :: StopDeployment)

instance Core.AWSRequest StopDeployment where
  type AWSResponse StopDeployment = Deployment
  request :: (Service -> Service) -> StopDeployment -> Request StopDeployment
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 StopDeployment
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse StopDeployment)))
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 -> forall a. FromJSON a => Object -> Either String a
Data.eitherParseJSON Object
x)

instance Prelude.Hashable StopDeployment where
  hashWithSalt :: Int -> StopDeployment -> Int
hashWithSalt Int
_salt StopDeployment' {Int
Text
deploymentNumber :: Int
environmentId :: Text
applicationId :: Text
$sel:deploymentNumber:StopDeployment' :: StopDeployment -> Int
$sel:environmentId:StopDeployment' :: StopDeployment -> Text
$sel:applicationId:StopDeployment' :: StopDeployment -> Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
applicationId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
environmentId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Int
deploymentNumber

instance Prelude.NFData StopDeployment where
  rnf :: StopDeployment -> ()
rnf StopDeployment' {Int
Text
deploymentNumber :: Int
environmentId :: Text
applicationId :: Text
$sel:deploymentNumber:StopDeployment' :: StopDeployment -> Int
$sel:environmentId:StopDeployment' :: StopDeployment -> Text
$sel:applicationId:StopDeployment' :: StopDeployment -> Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Text
applicationId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
environmentId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
deploymentNumber

instance Data.ToHeaders StopDeployment where
  toHeaders :: StopDeployment -> 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.ToPath StopDeployment where
  toPath :: StopDeployment -> ByteString
toPath StopDeployment' {Int
Text
deploymentNumber :: Int
environmentId :: Text
applicationId :: Text
$sel:deploymentNumber:StopDeployment' :: StopDeployment -> Int
$sel:environmentId:StopDeployment' :: StopDeployment -> Text
$sel:applicationId:StopDeployment' :: StopDeployment -> Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"/applications/",
        forall a. ToByteString a => a -> ByteString
Data.toBS Text
applicationId,
        ByteString
"/environments/",
        forall a. ToByteString a => a -> ByteString
Data.toBS Text
environmentId,
        ByteString
"/deployments/",
        forall a. ToByteString a => a -> ByteString
Data.toBS Int
deploymentNumber
      ]

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