{-# 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.EMRServerless.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)
--
-- Displays detailed information about a job run.
module Amazonka.EMRServerless.GetJobRun
  ( -- * Creating a Request
    GetJobRun (..),
    newGetJobRun,

    -- * Request Lenses
    getJobRun_applicationId,
    getJobRun_jobRunId,

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

    -- * Response Lenses
    getJobRunResponse_httpStatus,
    getJobRunResponse_jobRun,
  )
where

import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import Amazonka.EMRServerless.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'
  { -- | The ID of the application on which the job run is submitted.
    GetJobRun -> Text
applicationId :: Prelude.Text,
    -- | The ID of the job run.
    GetJobRun -> Text
jobRunId :: 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:
--
-- 'applicationId', 'getJobRun_applicationId' - The ID of the application on which the job run is submitted.
--
-- 'jobRunId', 'getJobRun_jobRunId' - The ID of the job run.
newGetJobRun ::
  -- | 'applicationId'
  Prelude.Text ->
  -- | 'jobRunId'
  Prelude.Text ->
  GetJobRun
newGetJobRun :: Text -> Text -> GetJobRun
newGetJobRun Text
pApplicationId_ Text
pJobRunId_ =
  GetJobRun'
    { $sel:applicationId:GetJobRun' :: Text
applicationId = Text
pApplicationId_,
      $sel:jobRunId:GetJobRun' :: Text
jobRunId = Text
pJobRunId_
    }

-- | The ID of the application on which the job run is submitted.
getJobRun_applicationId :: Lens.Lens' GetJobRun Prelude.Text
getJobRun_applicationId :: Lens' GetJobRun Text
getJobRun_applicationId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetJobRun' {Text
applicationId :: Text
$sel:applicationId:GetJobRun' :: GetJobRun -> Text
applicationId} -> Text
applicationId) (\s :: GetJobRun
s@GetJobRun' {} Text
a -> GetJobRun
s {$sel:applicationId:GetJobRun' :: Text
applicationId = Text
a} :: GetJobRun)

-- | The ID of the job run.
getJobRun_jobRunId :: Lens.Lens' GetJobRun Prelude.Text
getJobRun_jobRunId :: Lens' GetJobRun Text
getJobRun_jobRunId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetJobRun' {Text
jobRunId :: Text
$sel:jobRunId:GetJobRun' :: GetJobRun -> Text
jobRunId} -> Text
jobRunId) (\s :: GetJobRun
s@GetJobRun' {} Text
a -> GetJobRun
s {$sel:jobRunId:GetJobRun' :: Text
jobRunId = 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 => Service -> a -> Request a
Request.get (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 ->
          Int -> JobRun -> GetJobRunResponse
GetJobRunResponse'
            forall (f :: * -> *) a b. Functor 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))
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String a
Data..:> Key
"jobRun")
      )

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

instance Prelude.NFData GetJobRun where
  rnf :: GetJobRun -> ()
rnf GetJobRun' {Text
jobRunId :: Text
applicationId :: Text
$sel:jobRunId:GetJobRun' :: GetJobRun -> Text
$sel:applicationId:GetJobRun' :: GetJobRun -> 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
jobRunId

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
"Content-Type"
              forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ( ByteString
"application/x-amz-json-1.1" ::
                          Prelude.ByteString
                      )
          ]
      )

instance Data.ToPath GetJobRun where
  toPath :: GetJobRun -> ByteString
toPath GetJobRun' {Text
jobRunId :: Text
applicationId :: Text
$sel:jobRunId:GetJobRun' :: GetJobRun -> Text
$sel:applicationId:GetJobRun' :: GetJobRun -> Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"/applications/",
        forall a. ToByteString a => a -> ByteString
Data.toBS Text
applicationId,
        ByteString
"/jobruns/",
        forall a. ToByteString a => a -> ByteString
Data.toBS Text
jobRunId
      ]

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 response's http status code.
    GetJobRunResponse -> Int
httpStatus :: Prelude.Int,
    -- | The output displays information about the job run.
    GetJobRunResponse -> JobRun
jobRun :: JobRun
  }
  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, 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:
--
-- 'httpStatus', 'getJobRunResponse_httpStatus' - The response's http status code.
--
-- 'jobRun', 'getJobRunResponse_jobRun' - The output displays information about the job run.
newGetJobRunResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  -- | 'jobRun'
  JobRun ->
  GetJobRunResponse
newGetJobRunResponse :: Int -> JobRun -> GetJobRunResponse
newGetJobRunResponse Int
pHttpStatus_ JobRun
pJobRun_ =
  GetJobRunResponse'
    { $sel:httpStatus:GetJobRunResponse' :: Int
httpStatus = Int
pHttpStatus_,
      $sel:jobRun:GetJobRunResponse' :: JobRun
jobRun = JobRun
pJobRun_
    }

-- | 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)

-- | The output displays information about the job run.
getJobRunResponse_jobRun :: Lens.Lens' GetJobRunResponse JobRun
getJobRunResponse_jobRun :: Lens' GetJobRunResponse JobRun
getJobRunResponse_jobRun = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetJobRunResponse' {JobRun
jobRun :: JobRun
$sel:jobRun:GetJobRunResponse' :: GetJobRunResponse -> JobRun
jobRun} -> JobRun
jobRun) (\s :: GetJobRunResponse
s@GetJobRunResponse' {} JobRun
a -> GetJobRunResponse
s {$sel:jobRun:GetJobRunResponse' :: JobRun
jobRun = JobRun
a} :: GetJobRunResponse)

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