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

    -- * Request Lenses
    getDeploymentTarget_deploymentId,
    getDeploymentTarget_targetId,

    -- * Destructuring the Response
    GetDeploymentTargetResponse (..),
    newGetDeploymentTargetResponse,

    -- * Response Lenses
    getDeploymentTargetResponse_deploymentTarget,
    getDeploymentTargetResponse_httpStatus,
  )
where

import Amazonka.CodeDeploy.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:/ 'newGetDeploymentTarget' smart constructor.
data GetDeploymentTarget = GetDeploymentTarget'
  { -- | The unique ID of a deployment.
    GetDeploymentTarget -> Maybe Text
deploymentId :: Prelude.Maybe Prelude.Text,
    -- | The unique ID of a deployment target.
    GetDeploymentTarget -> Maybe Text
targetId :: Prelude.Maybe Prelude.Text
  }
  deriving (GetDeploymentTarget -> GetDeploymentTarget -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetDeploymentTarget -> GetDeploymentTarget -> Bool
$c/= :: GetDeploymentTarget -> GetDeploymentTarget -> Bool
== :: GetDeploymentTarget -> GetDeploymentTarget -> Bool
$c== :: GetDeploymentTarget -> GetDeploymentTarget -> Bool
Prelude.Eq, ReadPrec [GetDeploymentTarget]
ReadPrec GetDeploymentTarget
Int -> ReadS GetDeploymentTarget
ReadS [GetDeploymentTarget]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetDeploymentTarget]
$creadListPrec :: ReadPrec [GetDeploymentTarget]
readPrec :: ReadPrec GetDeploymentTarget
$creadPrec :: ReadPrec GetDeploymentTarget
readList :: ReadS [GetDeploymentTarget]
$creadList :: ReadS [GetDeploymentTarget]
readsPrec :: Int -> ReadS GetDeploymentTarget
$creadsPrec :: Int -> ReadS GetDeploymentTarget
Prelude.Read, Int -> GetDeploymentTarget -> ShowS
[GetDeploymentTarget] -> ShowS
GetDeploymentTarget -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetDeploymentTarget] -> ShowS
$cshowList :: [GetDeploymentTarget] -> ShowS
show :: GetDeploymentTarget -> String
$cshow :: GetDeploymentTarget -> String
showsPrec :: Int -> GetDeploymentTarget -> ShowS
$cshowsPrec :: Int -> GetDeploymentTarget -> ShowS
Prelude.Show, forall x. Rep GetDeploymentTarget x -> GetDeploymentTarget
forall x. GetDeploymentTarget -> Rep GetDeploymentTarget x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetDeploymentTarget x -> GetDeploymentTarget
$cfrom :: forall x. GetDeploymentTarget -> Rep GetDeploymentTarget x
Prelude.Generic)

-- |
-- Create a value of 'GetDeploymentTarget' 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', 'getDeploymentTarget_deploymentId' - The unique ID of a deployment.
--
-- 'targetId', 'getDeploymentTarget_targetId' - The unique ID of a deployment target.
newGetDeploymentTarget ::
  GetDeploymentTarget
newGetDeploymentTarget :: GetDeploymentTarget
newGetDeploymentTarget =
  GetDeploymentTarget'
    { $sel:deploymentId:GetDeploymentTarget' :: Maybe Text
deploymentId =
        forall a. Maybe a
Prelude.Nothing,
      $sel:targetId:GetDeploymentTarget' :: Maybe Text
targetId = forall a. Maybe a
Prelude.Nothing
    }

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

-- | The unique ID of a deployment target.
getDeploymentTarget_targetId :: Lens.Lens' GetDeploymentTarget (Prelude.Maybe Prelude.Text)
getDeploymentTarget_targetId :: Lens' GetDeploymentTarget (Maybe Text)
getDeploymentTarget_targetId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetDeploymentTarget' {Maybe Text
targetId :: Maybe Text
$sel:targetId:GetDeploymentTarget' :: GetDeploymentTarget -> Maybe Text
targetId} -> Maybe Text
targetId) (\s :: GetDeploymentTarget
s@GetDeploymentTarget' {} Maybe Text
a -> GetDeploymentTarget
s {$sel:targetId:GetDeploymentTarget' :: Maybe Text
targetId = Maybe Text
a} :: GetDeploymentTarget)

instance Core.AWSRequest GetDeploymentTarget where
  type
    AWSResponse GetDeploymentTarget =
      GetDeploymentTargetResponse
  request :: (Service -> Service)
-> GetDeploymentTarget -> Request GetDeploymentTarget
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 GetDeploymentTarget
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse GetDeploymentTarget)))
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 DeploymentTarget -> Int -> GetDeploymentTargetResponse
GetDeploymentTargetResponse'
            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
"deploymentTarget")
            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 GetDeploymentTarget where
  hashWithSalt :: Int -> GetDeploymentTarget -> Int
hashWithSalt Int
_salt GetDeploymentTarget' {Maybe Text
targetId :: Maybe Text
deploymentId :: Maybe Text
$sel:targetId:GetDeploymentTarget' :: GetDeploymentTarget -> Maybe Text
$sel:deploymentId:GetDeploymentTarget' :: GetDeploymentTarget -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
deploymentId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
targetId

instance Prelude.NFData GetDeploymentTarget where
  rnf :: GetDeploymentTarget -> ()
rnf GetDeploymentTarget' {Maybe Text
targetId :: Maybe Text
deploymentId :: Maybe Text
$sel:targetId:GetDeploymentTarget' :: GetDeploymentTarget -> Maybe Text
$sel:deploymentId:GetDeploymentTarget' :: GetDeploymentTarget -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
deploymentId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
targetId

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

instance Data.ToJSON GetDeploymentTarget where
  toJSON :: GetDeploymentTarget -> Value
toJSON GetDeploymentTarget' {Maybe Text
targetId :: Maybe Text
deploymentId :: Maybe Text
$sel:targetId:GetDeploymentTarget' :: GetDeploymentTarget -> Maybe Text
$sel:deploymentId:GetDeploymentTarget' :: GetDeploymentTarget -> Maybe Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"deploymentId" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Text
deploymentId,
            (Key
"targetId" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Text
targetId
          ]
      )

instance Data.ToPath GetDeploymentTarget where
  toPath :: GetDeploymentTarget -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/"

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

-- | /See:/ 'newGetDeploymentTargetResponse' smart constructor.
data GetDeploymentTargetResponse = GetDeploymentTargetResponse'
  { -- | A deployment target that contains information about a deployment such as
    -- its status, lifecycle events, and when it was last updated. It also
    -- contains metadata about the deployment target. The deployment target
    -- metadata depends on the deployment target\'s type (@instanceTarget@,
    -- @lambdaTarget@, or @ecsTarget@).
    GetDeploymentTargetResponse -> Maybe DeploymentTarget
deploymentTarget :: Prelude.Maybe DeploymentTarget,
    -- | The response's http status code.
    GetDeploymentTargetResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (GetDeploymentTargetResponse -> GetDeploymentTargetResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetDeploymentTargetResponse -> GetDeploymentTargetResponse -> Bool
$c/= :: GetDeploymentTargetResponse -> GetDeploymentTargetResponse -> Bool
== :: GetDeploymentTargetResponse -> GetDeploymentTargetResponse -> Bool
$c== :: GetDeploymentTargetResponse -> GetDeploymentTargetResponse -> Bool
Prelude.Eq, ReadPrec [GetDeploymentTargetResponse]
ReadPrec GetDeploymentTargetResponse
Int -> ReadS GetDeploymentTargetResponse
ReadS [GetDeploymentTargetResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetDeploymentTargetResponse]
$creadListPrec :: ReadPrec [GetDeploymentTargetResponse]
readPrec :: ReadPrec GetDeploymentTargetResponse
$creadPrec :: ReadPrec GetDeploymentTargetResponse
readList :: ReadS [GetDeploymentTargetResponse]
$creadList :: ReadS [GetDeploymentTargetResponse]
readsPrec :: Int -> ReadS GetDeploymentTargetResponse
$creadsPrec :: Int -> ReadS GetDeploymentTargetResponse
Prelude.Read, Int -> GetDeploymentTargetResponse -> ShowS
[GetDeploymentTargetResponse] -> ShowS
GetDeploymentTargetResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetDeploymentTargetResponse] -> ShowS
$cshowList :: [GetDeploymentTargetResponse] -> ShowS
show :: GetDeploymentTargetResponse -> String
$cshow :: GetDeploymentTargetResponse -> String
showsPrec :: Int -> GetDeploymentTargetResponse -> ShowS
$cshowsPrec :: Int -> GetDeploymentTargetResponse -> ShowS
Prelude.Show, forall x.
Rep GetDeploymentTargetResponse x -> GetDeploymentTargetResponse
forall x.
GetDeploymentTargetResponse -> Rep GetDeploymentTargetResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep GetDeploymentTargetResponse x -> GetDeploymentTargetResponse
$cfrom :: forall x.
GetDeploymentTargetResponse -> Rep GetDeploymentTargetResponse x
Prelude.Generic)

-- |
-- Create a value of 'GetDeploymentTargetResponse' 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:
--
-- 'deploymentTarget', 'getDeploymentTargetResponse_deploymentTarget' - A deployment target that contains information about a deployment such as
-- its status, lifecycle events, and when it was last updated. It also
-- contains metadata about the deployment target. The deployment target
-- metadata depends on the deployment target\'s type (@instanceTarget@,
-- @lambdaTarget@, or @ecsTarget@).
--
-- 'httpStatus', 'getDeploymentTargetResponse_httpStatus' - The response's http status code.
newGetDeploymentTargetResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  GetDeploymentTargetResponse
newGetDeploymentTargetResponse :: Int -> GetDeploymentTargetResponse
newGetDeploymentTargetResponse Int
pHttpStatus_ =
  GetDeploymentTargetResponse'
    { $sel:deploymentTarget:GetDeploymentTargetResponse' :: Maybe DeploymentTarget
deploymentTarget =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:GetDeploymentTargetResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | A deployment target that contains information about a deployment such as
-- its status, lifecycle events, and when it was last updated. It also
-- contains metadata about the deployment target. The deployment target
-- metadata depends on the deployment target\'s type (@instanceTarget@,
-- @lambdaTarget@, or @ecsTarget@).
getDeploymentTargetResponse_deploymentTarget :: Lens.Lens' GetDeploymentTargetResponse (Prelude.Maybe DeploymentTarget)
getDeploymentTargetResponse_deploymentTarget :: Lens' GetDeploymentTargetResponse (Maybe DeploymentTarget)
getDeploymentTargetResponse_deploymentTarget = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetDeploymentTargetResponse' {Maybe DeploymentTarget
deploymentTarget :: Maybe DeploymentTarget
$sel:deploymentTarget:GetDeploymentTargetResponse' :: GetDeploymentTargetResponse -> Maybe DeploymentTarget
deploymentTarget} -> Maybe DeploymentTarget
deploymentTarget) (\s :: GetDeploymentTargetResponse
s@GetDeploymentTargetResponse' {} Maybe DeploymentTarget
a -> GetDeploymentTargetResponse
s {$sel:deploymentTarget:GetDeploymentTargetResponse' :: Maybe DeploymentTarget
deploymentTarget = Maybe DeploymentTarget
a} :: GetDeploymentTargetResponse)

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

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