{-# 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.GetDeployment
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Retrieves information about a configuration deployment.
module Amazonka.AppConfig.GetDeployment
  ( -- * Creating a Request
    GetDeployment (..),
    newGetDeployment,

    -- * Request Lenses
    getDeployment_applicationId,
    getDeployment_environmentId,
    getDeployment_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:/ 'newGetDeployment' smart constructor.
data GetDeployment = GetDeployment'
  { -- | The ID of the application that includes the deployment you want to get.
    GetDeployment -> Text
applicationId :: Prelude.Text,
    -- | The ID of the environment that includes the deployment you want to get.
    GetDeployment -> Text
environmentId :: Prelude.Text,
    -- | The sequence number of the deployment.
    GetDeployment -> Int
deploymentNumber :: Prelude.Int
  }
  deriving (GetDeployment -> GetDeployment -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetDeployment -> GetDeployment -> Bool
$c/= :: GetDeployment -> GetDeployment -> Bool
== :: GetDeployment -> GetDeployment -> Bool
$c== :: GetDeployment -> GetDeployment -> Bool
Prelude.Eq, ReadPrec [GetDeployment]
ReadPrec GetDeployment
Int -> ReadS GetDeployment
ReadS [GetDeployment]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetDeployment]
$creadListPrec :: ReadPrec [GetDeployment]
readPrec :: ReadPrec GetDeployment
$creadPrec :: ReadPrec GetDeployment
readList :: ReadS [GetDeployment]
$creadList :: ReadS [GetDeployment]
readsPrec :: Int -> ReadS GetDeployment
$creadsPrec :: Int -> ReadS GetDeployment
Prelude.Read, Int -> GetDeployment -> ShowS
[GetDeployment] -> ShowS
GetDeployment -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetDeployment] -> ShowS
$cshowList :: [GetDeployment] -> ShowS
show :: GetDeployment -> String
$cshow :: GetDeployment -> String
showsPrec :: Int -> GetDeployment -> ShowS
$cshowsPrec :: Int -> GetDeployment -> ShowS
Prelude.Show, forall x. Rep GetDeployment x -> GetDeployment
forall x. GetDeployment -> Rep GetDeployment x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetDeployment x -> GetDeployment
$cfrom :: forall x. GetDeployment -> Rep GetDeployment x
Prelude.Generic)

-- |
-- Create a value of 'GetDeployment' 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', 'getDeployment_applicationId' - The ID of the application that includes the deployment you want to get.
--
-- 'environmentId', 'getDeployment_environmentId' - The ID of the environment that includes the deployment you want to get.
--
-- 'deploymentNumber', 'getDeployment_deploymentNumber' - The sequence number of the deployment.
newGetDeployment ::
  -- | 'applicationId'
  Prelude.Text ->
  -- | 'environmentId'
  Prelude.Text ->
  -- | 'deploymentNumber'
  Prelude.Int ->
  GetDeployment
newGetDeployment :: Text -> Text -> Int -> GetDeployment
newGetDeployment
  Text
pApplicationId_
  Text
pEnvironmentId_
  Int
pDeploymentNumber_ =
    GetDeployment'
      { $sel:applicationId:GetDeployment' :: Text
applicationId = Text
pApplicationId_,
        $sel:environmentId:GetDeployment' :: Text
environmentId = Text
pEnvironmentId_,
        $sel:deploymentNumber:GetDeployment' :: Int
deploymentNumber = Int
pDeploymentNumber_
      }

-- | The ID of the application that includes the deployment you want to get.
getDeployment_applicationId :: Lens.Lens' GetDeployment Prelude.Text
getDeployment_applicationId :: Lens' GetDeployment Text
getDeployment_applicationId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetDeployment' {Text
applicationId :: Text
$sel:applicationId:GetDeployment' :: GetDeployment -> Text
applicationId} -> Text
applicationId) (\s :: GetDeployment
s@GetDeployment' {} Text
a -> GetDeployment
s {$sel:applicationId:GetDeployment' :: Text
applicationId = Text
a} :: GetDeployment)

-- | The ID of the environment that includes the deployment you want to get.
getDeployment_environmentId :: Lens.Lens' GetDeployment Prelude.Text
getDeployment_environmentId :: Lens' GetDeployment Text
getDeployment_environmentId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetDeployment' {Text
environmentId :: Text
$sel:environmentId:GetDeployment' :: GetDeployment -> Text
environmentId} -> Text
environmentId) (\s :: GetDeployment
s@GetDeployment' {} Text
a -> GetDeployment
s {$sel:environmentId:GetDeployment' :: Text
environmentId = Text
a} :: GetDeployment)

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

instance Core.AWSRequest GetDeployment where
  type AWSResponse GetDeployment = Deployment
  request :: (Service -> Service) -> GetDeployment -> Request GetDeployment
request Service -> Service
overrides =
    forall a. ToRequest a => Service -> a -> Request a
Request.get (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy GetDeployment
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse GetDeployment)))
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 GetDeployment where
  hashWithSalt :: Int -> GetDeployment -> Int
hashWithSalt Int
_salt GetDeployment' {Int
Text
deploymentNumber :: Int
environmentId :: Text
applicationId :: Text
$sel:deploymentNumber:GetDeployment' :: GetDeployment -> Int
$sel:environmentId:GetDeployment' :: GetDeployment -> Text
$sel:applicationId:GetDeployment' :: GetDeployment -> 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 GetDeployment where
  rnf :: GetDeployment -> ()
rnf GetDeployment' {Int
Text
deploymentNumber :: Int
environmentId :: Text
applicationId :: Text
$sel:deploymentNumber:GetDeployment' :: GetDeployment -> Int
$sel:environmentId:GetDeployment' :: GetDeployment -> Text
$sel:applicationId:GetDeployment' :: GetDeployment -> 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 GetDeployment where
  toHeaders :: GetDeployment -> 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 GetDeployment where
  toPath :: GetDeployment -> ByteString
toPath GetDeployment' {Int
Text
deploymentNumber :: Int
environmentId :: Text
applicationId :: Text
$sel:deploymentNumber:GetDeployment' :: GetDeployment -> Int
$sel:environmentId:GetDeployment' :: GetDeployment -> Text
$sel:applicationId:GetDeployment' :: GetDeployment -> 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 GetDeployment where
  toQuery :: GetDeployment -> QueryString
toQuery = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty