{-# 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.CodePipeline.GetJobDetails
-- 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 job. Used for custom actions only.
--
-- When this API is called, AWS CodePipeline returns temporary credentials
-- for the S3 bucket used to store artifacts for the pipeline, if the
-- action requires access to that S3 bucket for input or output artifacts.
-- This API also returns any secret values defined for the action.
module Amazonka.CodePipeline.GetJobDetails
  ( -- * Creating a Request
    GetJobDetails (..),
    newGetJobDetails,

    -- * Request Lenses
    getJobDetails_jobId,

    -- * Destructuring the Response
    GetJobDetailsResponse (..),
    newGetJobDetailsResponse,

    -- * Response Lenses
    getJobDetailsResponse_jobDetails,
    getJobDetailsResponse_httpStatus,
  )
where

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

-- | Represents the input of a @GetJobDetails@ action.
--
-- /See:/ 'newGetJobDetails' smart constructor.
data GetJobDetails = GetJobDetails'
  { -- | The unique system-generated ID for the job.
    GetJobDetails -> Text
jobId :: Prelude.Text
  }
  deriving (GetJobDetails -> GetJobDetails -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetJobDetails -> GetJobDetails -> Bool
$c/= :: GetJobDetails -> GetJobDetails -> Bool
== :: GetJobDetails -> GetJobDetails -> Bool
$c== :: GetJobDetails -> GetJobDetails -> Bool
Prelude.Eq, ReadPrec [GetJobDetails]
ReadPrec GetJobDetails
Int -> ReadS GetJobDetails
ReadS [GetJobDetails]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetJobDetails]
$creadListPrec :: ReadPrec [GetJobDetails]
readPrec :: ReadPrec GetJobDetails
$creadPrec :: ReadPrec GetJobDetails
readList :: ReadS [GetJobDetails]
$creadList :: ReadS [GetJobDetails]
readsPrec :: Int -> ReadS GetJobDetails
$creadsPrec :: Int -> ReadS GetJobDetails
Prelude.Read, Int -> GetJobDetails -> ShowS
[GetJobDetails] -> ShowS
GetJobDetails -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetJobDetails] -> ShowS
$cshowList :: [GetJobDetails] -> ShowS
show :: GetJobDetails -> String
$cshow :: GetJobDetails -> String
showsPrec :: Int -> GetJobDetails -> ShowS
$cshowsPrec :: Int -> GetJobDetails -> ShowS
Prelude.Show, forall x. Rep GetJobDetails x -> GetJobDetails
forall x. GetJobDetails -> Rep GetJobDetails x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetJobDetails x -> GetJobDetails
$cfrom :: forall x. GetJobDetails -> Rep GetJobDetails x
Prelude.Generic)

-- |
-- Create a value of 'GetJobDetails' 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:
--
-- 'jobId', 'getJobDetails_jobId' - The unique system-generated ID for the job.
newGetJobDetails ::
  -- | 'jobId'
  Prelude.Text ->
  GetJobDetails
newGetJobDetails :: Text -> GetJobDetails
newGetJobDetails Text
pJobId_ =
  GetJobDetails' {$sel:jobId:GetJobDetails' :: Text
jobId = Text
pJobId_}

-- | The unique system-generated ID for the job.
getJobDetails_jobId :: Lens.Lens' GetJobDetails Prelude.Text
getJobDetails_jobId :: Lens' GetJobDetails Text
getJobDetails_jobId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetJobDetails' {Text
jobId :: Text
$sel:jobId:GetJobDetails' :: GetJobDetails -> Text
jobId} -> Text
jobId) (\s :: GetJobDetails
s@GetJobDetails' {} Text
a -> GetJobDetails
s {$sel:jobId:GetJobDetails' :: Text
jobId = Text
a} :: GetJobDetails)

instance Core.AWSRequest GetJobDetails where
  type
    AWSResponse GetJobDetails =
      GetJobDetailsResponse
  request :: (Service -> Service) -> GetJobDetails -> Request GetJobDetails
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 GetJobDetails
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse GetJobDetails)))
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 JobDetails -> Int -> GetJobDetailsResponse
GetJobDetailsResponse'
            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
"jobDetails")
            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 GetJobDetails where
  hashWithSalt :: Int -> GetJobDetails -> Int
hashWithSalt Int
_salt GetJobDetails' {Text
jobId :: Text
$sel:jobId:GetJobDetails' :: GetJobDetails -> Text
..} =
    Int
_salt forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
jobId

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

instance Data.ToHeaders GetJobDetails where
  toHeaders :: GetJobDetails -> 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
"CodePipeline_20150709.GetJobDetails" ::
                          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 GetJobDetails where
  toJSON :: GetJobDetails -> Value
toJSON GetJobDetails' {Text
jobId :: Text
$sel:jobId:GetJobDetails' :: GetJobDetails -> Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [forall a. a -> Maybe a
Prelude.Just (Key
"jobId" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
jobId)]
      )

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

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

-- | Represents the output of a @GetJobDetails@ action.
--
-- /See:/ 'newGetJobDetailsResponse' smart constructor.
data GetJobDetailsResponse = GetJobDetailsResponse'
  { -- | The details of the job.
    --
    -- If AWSSessionCredentials is used, a long-running job can call
    -- @GetJobDetails@ again to obtain new credentials.
    GetJobDetailsResponse -> Maybe JobDetails
jobDetails :: Prelude.Maybe JobDetails,
    -- | The response's http status code.
    GetJobDetailsResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (GetJobDetailsResponse -> GetJobDetailsResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetJobDetailsResponse -> GetJobDetailsResponse -> Bool
$c/= :: GetJobDetailsResponse -> GetJobDetailsResponse -> Bool
== :: GetJobDetailsResponse -> GetJobDetailsResponse -> Bool
$c== :: GetJobDetailsResponse -> GetJobDetailsResponse -> Bool
Prelude.Eq, Int -> GetJobDetailsResponse -> ShowS
[GetJobDetailsResponse] -> ShowS
GetJobDetailsResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetJobDetailsResponse] -> ShowS
$cshowList :: [GetJobDetailsResponse] -> ShowS
show :: GetJobDetailsResponse -> String
$cshow :: GetJobDetailsResponse -> String
showsPrec :: Int -> GetJobDetailsResponse -> ShowS
$cshowsPrec :: Int -> GetJobDetailsResponse -> ShowS
Prelude.Show, forall x. Rep GetJobDetailsResponse x -> GetJobDetailsResponse
forall x. GetJobDetailsResponse -> Rep GetJobDetailsResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetJobDetailsResponse x -> GetJobDetailsResponse
$cfrom :: forall x. GetJobDetailsResponse -> Rep GetJobDetailsResponse x
Prelude.Generic)

-- |
-- Create a value of 'GetJobDetailsResponse' 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:
--
-- 'jobDetails', 'getJobDetailsResponse_jobDetails' - The details of the job.
--
-- If AWSSessionCredentials is used, a long-running job can call
-- @GetJobDetails@ again to obtain new credentials.
--
-- 'httpStatus', 'getJobDetailsResponse_httpStatus' - The response's http status code.
newGetJobDetailsResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  GetJobDetailsResponse
newGetJobDetailsResponse :: Int -> GetJobDetailsResponse
newGetJobDetailsResponse Int
pHttpStatus_ =
  GetJobDetailsResponse'
    { $sel:jobDetails:GetJobDetailsResponse' :: Maybe JobDetails
jobDetails =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:GetJobDetailsResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The details of the job.
--
-- If AWSSessionCredentials is used, a long-running job can call
-- @GetJobDetails@ again to obtain new credentials.
getJobDetailsResponse_jobDetails :: Lens.Lens' GetJobDetailsResponse (Prelude.Maybe JobDetails)
getJobDetailsResponse_jobDetails :: Lens' GetJobDetailsResponse (Maybe JobDetails)
getJobDetailsResponse_jobDetails = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetJobDetailsResponse' {Maybe JobDetails
jobDetails :: Maybe JobDetails
$sel:jobDetails:GetJobDetailsResponse' :: GetJobDetailsResponse -> Maybe JobDetails
jobDetails} -> Maybe JobDetails
jobDetails) (\s :: GetJobDetailsResponse
s@GetJobDetailsResponse' {} Maybe JobDetails
a -> GetJobDetailsResponse
s {$sel:jobDetails:GetJobDetailsResponse' :: Maybe JobDetails
jobDetails = Maybe JobDetails
a} :: GetJobDetailsResponse)

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

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