{-# 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.Glue.GetJobRun
-- 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 the metadata for a given job run.
module Amazonka.Glue.GetJobRun
  ( -- * Creating a Request
    GetJobRun (..),
    newGetJobRun,

    -- * Request Lenses
    getJobRun_predecessorsIncluded,
    getJobRun_jobName,
    getJobRun_runId,

    -- * Destructuring the Response
    GetJobRunResponse (..),
    newGetJobRunResponse,

    -- * Response Lenses
    getJobRunResponse_jobRun,
    getJobRunResponse_httpStatus,
  )
where

import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import Amazonka.Glue.Types
import qualified Amazonka.Prelude as Prelude
import qualified Amazonka.Request as Request
import qualified Amazonka.Response as Response

-- | /See:/ 'newGetJobRun' smart constructor.
data GetJobRun = GetJobRun'
  { -- | True if a list of predecessor runs should be returned.
    GetJobRun -> Maybe Bool
predecessorsIncluded :: Prelude.Maybe Prelude.Bool,
    -- | Name of the job definition being run.
    GetJobRun -> Text
jobName :: Prelude.Text,
    -- | The ID of the job run.
    GetJobRun -> Text
runId :: Prelude.Text
  }
  deriving (GetJobRun -> GetJobRun -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetJobRun -> GetJobRun -> Bool
$c/= :: GetJobRun -> GetJobRun -> Bool
== :: GetJobRun -> GetJobRun -> Bool
$c== :: GetJobRun -> GetJobRun -> Bool
Prelude.Eq, ReadPrec [GetJobRun]
ReadPrec GetJobRun
Int -> ReadS GetJobRun
ReadS [GetJobRun]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetJobRun]
$creadListPrec :: ReadPrec [GetJobRun]
readPrec :: ReadPrec GetJobRun
$creadPrec :: ReadPrec GetJobRun
readList :: ReadS [GetJobRun]
$creadList :: ReadS [GetJobRun]
readsPrec :: Int -> ReadS GetJobRun
$creadsPrec :: Int -> ReadS GetJobRun
Prelude.Read, Int -> GetJobRun -> ShowS
[GetJobRun] -> ShowS
GetJobRun -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetJobRun] -> ShowS
$cshowList :: [GetJobRun] -> ShowS
show :: GetJobRun -> String
$cshow :: GetJobRun -> String
showsPrec :: Int -> GetJobRun -> ShowS
$cshowsPrec :: Int -> GetJobRun -> ShowS
Prelude.Show, forall x. Rep GetJobRun x -> GetJobRun
forall x. GetJobRun -> Rep GetJobRun x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetJobRun x -> GetJobRun
$cfrom :: forall x. GetJobRun -> Rep GetJobRun x
Prelude.Generic)

-- |
-- Create a value of 'GetJobRun' 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:
--
-- 'predecessorsIncluded', 'getJobRun_predecessorsIncluded' - True if a list of predecessor runs should be returned.
--
-- 'jobName', 'getJobRun_jobName' - Name of the job definition being run.
--
-- 'runId', 'getJobRun_runId' - The ID of the job run.
newGetJobRun ::
  -- | 'jobName'
  Prelude.Text ->
  -- | 'runId'
  Prelude.Text ->
  GetJobRun
newGetJobRun :: Text -> Text -> GetJobRun
newGetJobRun Text
pJobName_ Text
pRunId_ =
  GetJobRun'
    { $sel:predecessorsIncluded:GetJobRun' :: Maybe Bool
predecessorsIncluded = forall a. Maybe a
Prelude.Nothing,
      $sel:jobName:GetJobRun' :: Text
jobName = Text
pJobName_,
      $sel:runId:GetJobRun' :: Text
runId = Text
pRunId_
    }

-- | True if a list of predecessor runs should be returned.
getJobRun_predecessorsIncluded :: Lens.Lens' GetJobRun (Prelude.Maybe Prelude.Bool)
getJobRun_predecessorsIncluded :: Lens' GetJobRun (Maybe Bool)
getJobRun_predecessorsIncluded = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetJobRun' {Maybe Bool
predecessorsIncluded :: Maybe Bool
$sel:predecessorsIncluded:GetJobRun' :: GetJobRun -> Maybe Bool
predecessorsIncluded} -> Maybe Bool
predecessorsIncluded) (\s :: GetJobRun
s@GetJobRun' {} Maybe Bool
a -> GetJobRun
s {$sel:predecessorsIncluded:GetJobRun' :: Maybe Bool
predecessorsIncluded = Maybe Bool
a} :: GetJobRun)

-- | Name of the job definition being run.
getJobRun_jobName :: Lens.Lens' GetJobRun Prelude.Text
getJobRun_jobName :: Lens' GetJobRun Text
getJobRun_jobName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetJobRun' {Text
jobName :: Text
$sel:jobName:GetJobRun' :: GetJobRun -> Text
jobName} -> Text
jobName) (\s :: GetJobRun
s@GetJobRun' {} Text
a -> GetJobRun
s {$sel:jobName:GetJobRun' :: Text
jobName = Text
a} :: GetJobRun)

-- | The ID of the job run.
getJobRun_runId :: Lens.Lens' GetJobRun Prelude.Text
getJobRun_runId :: Lens' GetJobRun Text
getJobRun_runId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetJobRun' {Text
runId :: Text
$sel:runId:GetJobRun' :: GetJobRun -> Text
runId} -> Text
runId) (\s :: GetJobRun
s@GetJobRun' {} Text
a -> GetJobRun
s {$sel:runId:GetJobRun' :: Text
runId = Text
a} :: GetJobRun)

instance Core.AWSRequest GetJobRun where
  type AWSResponse GetJobRun = GetJobRunResponse
  request :: (Service -> Service) -> GetJobRun -> Request GetJobRun
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 GetJobRun
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse GetJobRun)))
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 JobRun -> Int -> GetJobRunResponse
GetJobRunResponse'
            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
"JobRun")
            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 GetJobRun where
  hashWithSalt :: Int -> GetJobRun -> Int
hashWithSalt Int
_salt GetJobRun' {Maybe Bool
Text
runId :: Text
jobName :: Text
predecessorsIncluded :: Maybe Bool
$sel:runId:GetJobRun' :: GetJobRun -> Text
$sel:jobName:GetJobRun' :: GetJobRun -> Text
$sel:predecessorsIncluded:GetJobRun' :: GetJobRun -> Maybe Bool
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
predecessorsIncluded
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
jobName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
runId

instance Prelude.NFData GetJobRun where
  rnf :: GetJobRun -> ()
rnf GetJobRun' {Maybe Bool
Text
runId :: Text
jobName :: Text
predecessorsIncluded :: Maybe Bool
$sel:runId:GetJobRun' :: GetJobRun -> Text
$sel:jobName:GetJobRun' :: GetJobRun -> Text
$sel:predecessorsIncluded:GetJobRun' :: GetJobRun -> Maybe Bool
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Bool
predecessorsIncluded
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
jobName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
runId

instance Data.ToHeaders GetJobRun where
  toHeaders :: GetJobRun -> 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
"AWSGlue.GetJobRun" :: 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 GetJobRun where
  toJSON :: GetJobRun -> Value
toJSON GetJobRun' {Maybe Bool
Text
runId :: Text
jobName :: Text
predecessorsIncluded :: Maybe Bool
$sel:runId:GetJobRun' :: GetJobRun -> Text
$sel:jobName:GetJobRun' :: GetJobRun -> Text
$sel:predecessorsIncluded:GetJobRun' :: GetJobRun -> Maybe Bool
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"PredecessorsIncluded" 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 Bool
predecessorsIncluded,
            forall a. a -> Maybe a
Prelude.Just (Key
"JobName" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
jobName),
            forall a. a -> Maybe a
Prelude.Just (Key
"RunId" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
runId)
          ]
      )

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

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

-- | /See:/ 'newGetJobRunResponse' smart constructor.
data GetJobRunResponse = GetJobRunResponse'
  { -- | The requested job-run metadata.
    GetJobRunResponse -> Maybe JobRun
jobRun :: Prelude.Maybe JobRun,
    -- | The response's http status code.
    GetJobRunResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (GetJobRunResponse -> GetJobRunResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetJobRunResponse -> GetJobRunResponse -> Bool
$c/= :: GetJobRunResponse -> GetJobRunResponse -> Bool
== :: GetJobRunResponse -> GetJobRunResponse -> Bool
$c== :: GetJobRunResponse -> GetJobRunResponse -> Bool
Prelude.Eq, ReadPrec [GetJobRunResponse]
ReadPrec GetJobRunResponse
Int -> ReadS GetJobRunResponse
ReadS [GetJobRunResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetJobRunResponse]
$creadListPrec :: ReadPrec [GetJobRunResponse]
readPrec :: ReadPrec GetJobRunResponse
$creadPrec :: ReadPrec GetJobRunResponse
readList :: ReadS [GetJobRunResponse]
$creadList :: ReadS [GetJobRunResponse]
readsPrec :: Int -> ReadS GetJobRunResponse
$creadsPrec :: Int -> ReadS GetJobRunResponse
Prelude.Read, Int -> GetJobRunResponse -> ShowS
[GetJobRunResponse] -> ShowS
GetJobRunResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetJobRunResponse] -> ShowS
$cshowList :: [GetJobRunResponse] -> ShowS
show :: GetJobRunResponse -> String
$cshow :: GetJobRunResponse -> String
showsPrec :: Int -> GetJobRunResponse -> ShowS
$cshowsPrec :: Int -> GetJobRunResponse -> ShowS
Prelude.Show, forall x. Rep GetJobRunResponse x -> GetJobRunResponse
forall x. GetJobRunResponse -> Rep GetJobRunResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetJobRunResponse x -> GetJobRunResponse
$cfrom :: forall x. GetJobRunResponse -> Rep GetJobRunResponse x
Prelude.Generic)

-- |
-- Create a value of 'GetJobRunResponse' 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:
--
-- 'jobRun', 'getJobRunResponse_jobRun' - The requested job-run metadata.
--
-- 'httpStatus', 'getJobRunResponse_httpStatus' - The response's http status code.
newGetJobRunResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  GetJobRunResponse
newGetJobRunResponse :: Int -> GetJobRunResponse
newGetJobRunResponse Int
pHttpStatus_ =
  GetJobRunResponse'
    { $sel:jobRun:GetJobRunResponse' :: Maybe JobRun
jobRun = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:GetJobRunResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The requested job-run metadata.
getJobRunResponse_jobRun :: Lens.Lens' GetJobRunResponse (Prelude.Maybe JobRun)
getJobRunResponse_jobRun :: Lens' GetJobRunResponse (Maybe JobRun)
getJobRunResponse_jobRun = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetJobRunResponse' {Maybe JobRun
jobRun :: Maybe JobRun
$sel:jobRun:GetJobRunResponse' :: GetJobRunResponse -> Maybe JobRun
jobRun} -> Maybe JobRun
jobRun) (\s :: GetJobRunResponse
s@GetJobRunResponse' {} Maybe JobRun
a -> GetJobRunResponse
s {$sel:jobRun:GetJobRunResponse' :: Maybe JobRun
jobRun = Maybe JobRun
a} :: GetJobRunResponse)

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

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