{-# 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.DataBrew.DescribeJobRun
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Represents one run of a DataBrew job.
module Amazonka.DataBrew.DescribeJobRun
  ( -- * Creating a Request
    DescribeJobRun (..),
    newDescribeJobRun,

    -- * Request Lenses
    describeJobRun_name,
    describeJobRun_runId,

    -- * Destructuring the Response
    DescribeJobRunResponse (..),
    newDescribeJobRunResponse,

    -- * Response Lenses
    describeJobRunResponse_attempt,
    describeJobRunResponse_completedOn,
    describeJobRunResponse_dataCatalogOutputs,
    describeJobRunResponse_databaseOutputs,
    describeJobRunResponse_datasetName,
    describeJobRunResponse_errorMessage,
    describeJobRunResponse_executionTime,
    describeJobRunResponse_jobSample,
    describeJobRunResponse_logGroupName,
    describeJobRunResponse_logSubscription,
    describeJobRunResponse_outputs,
    describeJobRunResponse_profileConfiguration,
    describeJobRunResponse_recipeReference,
    describeJobRunResponse_runId,
    describeJobRunResponse_startedBy,
    describeJobRunResponse_startedOn,
    describeJobRunResponse_state,
    describeJobRunResponse_validationConfigurations,
    describeJobRunResponse_httpStatus,
    describeJobRunResponse_jobName,
  )
where

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

-- | /See:/ 'newDescribeJobRun' smart constructor.
data DescribeJobRun = DescribeJobRun'
  { -- | The name of the job being processed during this run.
    DescribeJobRun -> Text
name :: Prelude.Text,
    -- | The unique identifier of the job run.
    DescribeJobRun -> Text
runId :: Prelude.Text
  }
  deriving (DescribeJobRun -> DescribeJobRun -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DescribeJobRun -> DescribeJobRun -> Bool
$c/= :: DescribeJobRun -> DescribeJobRun -> Bool
== :: DescribeJobRun -> DescribeJobRun -> Bool
$c== :: DescribeJobRun -> DescribeJobRun -> Bool
Prelude.Eq, ReadPrec [DescribeJobRun]
ReadPrec DescribeJobRun
Int -> ReadS DescribeJobRun
ReadS [DescribeJobRun]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DescribeJobRun]
$creadListPrec :: ReadPrec [DescribeJobRun]
readPrec :: ReadPrec DescribeJobRun
$creadPrec :: ReadPrec DescribeJobRun
readList :: ReadS [DescribeJobRun]
$creadList :: ReadS [DescribeJobRun]
readsPrec :: Int -> ReadS DescribeJobRun
$creadsPrec :: Int -> ReadS DescribeJobRun
Prelude.Read, Int -> DescribeJobRun -> ShowS
[DescribeJobRun] -> ShowS
DescribeJobRun -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DescribeJobRun] -> ShowS
$cshowList :: [DescribeJobRun] -> ShowS
show :: DescribeJobRun -> String
$cshow :: DescribeJobRun -> String
showsPrec :: Int -> DescribeJobRun -> ShowS
$cshowsPrec :: Int -> DescribeJobRun -> ShowS
Prelude.Show, forall x. Rep DescribeJobRun x -> DescribeJobRun
forall x. DescribeJobRun -> Rep DescribeJobRun x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DescribeJobRun x -> DescribeJobRun
$cfrom :: forall x. DescribeJobRun -> Rep DescribeJobRun x
Prelude.Generic)

-- |
-- Create a value of 'DescribeJobRun' 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:
--
-- 'name', 'describeJobRun_name' - The name of the job being processed during this run.
--
-- 'runId', 'describeJobRun_runId' - The unique identifier of the job run.
newDescribeJobRun ::
  -- | 'name'
  Prelude.Text ->
  -- | 'runId'
  Prelude.Text ->
  DescribeJobRun
newDescribeJobRun :: Text -> Text -> DescribeJobRun
newDescribeJobRun Text
pName_ Text
pRunId_ =
  DescribeJobRun' {$sel:name:DescribeJobRun' :: Text
name = Text
pName_, $sel:runId:DescribeJobRun' :: Text
runId = Text
pRunId_}

-- | The name of the job being processed during this run.
describeJobRun_name :: Lens.Lens' DescribeJobRun Prelude.Text
describeJobRun_name :: Lens' DescribeJobRun Text
describeJobRun_name = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeJobRun' {Text
name :: Text
$sel:name:DescribeJobRun' :: DescribeJobRun -> Text
name} -> Text
name) (\s :: DescribeJobRun
s@DescribeJobRun' {} Text
a -> DescribeJobRun
s {$sel:name:DescribeJobRun' :: Text
name = Text
a} :: DescribeJobRun)

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

instance Core.AWSRequest DescribeJobRun where
  type
    AWSResponse DescribeJobRun =
      DescribeJobRunResponse
  request :: (Service -> Service) -> DescribeJobRun -> Request DescribeJobRun
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 DescribeJobRun
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse DescribeJobRun)))
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 Int
-> Maybe POSIX
-> Maybe (NonEmpty DataCatalogOutput)
-> Maybe (NonEmpty DatabaseOutput)
-> Maybe Text
-> Maybe Text
-> Maybe Int
-> Maybe JobSample
-> Maybe Text
-> Maybe LogSubscription
-> Maybe (NonEmpty Output)
-> Maybe ProfileConfiguration
-> Maybe RecipeReference
-> Maybe Text
-> Maybe Text
-> Maybe POSIX
-> Maybe JobRunState
-> Maybe (NonEmpty ValidationConfiguration)
-> Int
-> Text
-> DescribeJobRunResponse
DescribeJobRunResponse'
            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
"Attempt")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"CompletedOn")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"DataCatalogOutputs")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"DatabaseOutputs")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"DatasetName")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"ErrorMessage")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"ExecutionTime")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"JobSample")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"LogGroupName")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"LogSubscription")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"Outputs")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"ProfileConfiguration")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"RecipeReference")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"RunId")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"StartedBy")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"StartedOn")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"State")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"ValidationConfigurations")
            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))
            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
"JobName")
      )

instance Prelude.Hashable DescribeJobRun where
  hashWithSalt :: Int -> DescribeJobRun -> Int
hashWithSalt Int
_salt DescribeJobRun' {Text
runId :: Text
name :: Text
$sel:runId:DescribeJobRun' :: DescribeJobRun -> Text
$sel:name:DescribeJobRun' :: DescribeJobRun -> Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
name
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
runId

instance Prelude.NFData DescribeJobRun where
  rnf :: DescribeJobRun -> ()
rnf DescribeJobRun' {Text
runId :: Text
name :: Text
$sel:runId:DescribeJobRun' :: DescribeJobRun -> Text
$sel:name:DescribeJobRun' :: DescribeJobRun -> Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Text
name seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
runId

instance Data.ToHeaders DescribeJobRun where
  toHeaders :: DescribeJobRun -> 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 DescribeJobRun where
  toPath :: DescribeJobRun -> ByteString
toPath DescribeJobRun' {Text
runId :: Text
name :: Text
$sel:runId:DescribeJobRun' :: DescribeJobRun -> Text
$sel:name:DescribeJobRun' :: DescribeJobRun -> Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"/jobs/",
        forall a. ToByteString a => a -> ByteString
Data.toBS Text
name,
        ByteString
"/jobRun/",
        forall a. ToByteString a => a -> ByteString
Data.toBS Text
runId
      ]

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

-- | /See:/ 'newDescribeJobRunResponse' smart constructor.
data DescribeJobRunResponse = DescribeJobRunResponse'
  { -- | The number of times that DataBrew has attempted to run the job.
    DescribeJobRunResponse -> Maybe Int
attempt :: Prelude.Maybe Prelude.Int,
    -- | The date and time when the job completed processing.
    DescribeJobRunResponse -> Maybe POSIX
completedOn :: Prelude.Maybe Data.POSIX,
    -- | One or more artifacts that represent the Glue Data Catalog output from
    -- running the job.
    DescribeJobRunResponse -> Maybe (NonEmpty DataCatalogOutput)
dataCatalogOutputs :: Prelude.Maybe (Prelude.NonEmpty DataCatalogOutput),
    -- | Represents a list of JDBC database output objects which defines the
    -- output destination for a DataBrew recipe job to write into.
    DescribeJobRunResponse -> Maybe (NonEmpty DatabaseOutput)
databaseOutputs :: Prelude.Maybe (Prelude.NonEmpty DatabaseOutput),
    -- | The name of the dataset for the job to process.
    DescribeJobRunResponse -> Maybe Text
datasetName :: Prelude.Maybe Prelude.Text,
    -- | A message indicating an error (if any) that was encountered when the job
    -- ran.
    DescribeJobRunResponse -> Maybe Text
errorMessage :: Prelude.Maybe Prelude.Text,
    -- | The amount of time, in seconds, during which the job run consumed
    -- resources.
    DescribeJobRunResponse -> Maybe Int
executionTime :: Prelude.Maybe Prelude.Int,
    -- | Sample configuration for profile jobs only. Determines the number of
    -- rows on which the profile job will be executed. If a JobSample value is
    -- not provided, the default value will be used. The default value is
    -- CUSTOM_ROWS for the mode parameter and 20000 for the size parameter.
    DescribeJobRunResponse -> Maybe JobSample
jobSample :: Prelude.Maybe JobSample,
    -- | The name of an Amazon CloudWatch log group, where the job writes
    -- diagnostic messages when it runs.
    DescribeJobRunResponse -> Maybe Text
logGroupName :: Prelude.Maybe Prelude.Text,
    -- | The current status of Amazon CloudWatch logging for the job run.
    DescribeJobRunResponse -> Maybe LogSubscription
logSubscription :: Prelude.Maybe LogSubscription,
    -- | One or more output artifacts from a job run.
    DescribeJobRunResponse -> Maybe (NonEmpty Output)
outputs :: Prelude.Maybe (Prelude.NonEmpty Output),
    -- | Configuration for profile jobs. Used to select columns, do evaluations,
    -- and override default parameters of evaluations. When configuration is
    -- null, the profile job will run with default settings.
    DescribeJobRunResponse -> Maybe ProfileConfiguration
profileConfiguration :: Prelude.Maybe ProfileConfiguration,
    DescribeJobRunResponse -> Maybe RecipeReference
recipeReference :: Prelude.Maybe RecipeReference,
    -- | The unique identifier of the job run.
    DescribeJobRunResponse -> Maybe Text
runId :: Prelude.Maybe Prelude.Text,
    -- | The Amazon Resource Name (ARN) of the user who started the job run.
    DescribeJobRunResponse -> Maybe Text
startedBy :: Prelude.Maybe Prelude.Text,
    -- | The date and time when the job run began.
    DescribeJobRunResponse -> Maybe POSIX
startedOn :: Prelude.Maybe Data.POSIX,
    -- | The current state of the job run entity itself.
    DescribeJobRunResponse -> Maybe JobRunState
state :: Prelude.Maybe JobRunState,
    -- | List of validation configurations that are applied to the profile job.
    DescribeJobRunResponse -> Maybe (NonEmpty ValidationConfiguration)
validationConfigurations :: Prelude.Maybe (Prelude.NonEmpty ValidationConfiguration),
    -- | The response's http status code.
    DescribeJobRunResponse -> Int
httpStatus :: Prelude.Int,
    -- | The name of the job being processed during this run.
    DescribeJobRunResponse -> Text
jobName :: Prelude.Text
  }
  deriving (DescribeJobRunResponse -> DescribeJobRunResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DescribeJobRunResponse -> DescribeJobRunResponse -> Bool
$c/= :: DescribeJobRunResponse -> DescribeJobRunResponse -> Bool
== :: DescribeJobRunResponse -> DescribeJobRunResponse -> Bool
$c== :: DescribeJobRunResponse -> DescribeJobRunResponse -> Bool
Prelude.Eq, ReadPrec [DescribeJobRunResponse]
ReadPrec DescribeJobRunResponse
Int -> ReadS DescribeJobRunResponse
ReadS [DescribeJobRunResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DescribeJobRunResponse]
$creadListPrec :: ReadPrec [DescribeJobRunResponse]
readPrec :: ReadPrec DescribeJobRunResponse
$creadPrec :: ReadPrec DescribeJobRunResponse
readList :: ReadS [DescribeJobRunResponse]
$creadList :: ReadS [DescribeJobRunResponse]
readsPrec :: Int -> ReadS DescribeJobRunResponse
$creadsPrec :: Int -> ReadS DescribeJobRunResponse
Prelude.Read, Int -> DescribeJobRunResponse -> ShowS
[DescribeJobRunResponse] -> ShowS
DescribeJobRunResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DescribeJobRunResponse] -> ShowS
$cshowList :: [DescribeJobRunResponse] -> ShowS
show :: DescribeJobRunResponse -> String
$cshow :: DescribeJobRunResponse -> String
showsPrec :: Int -> DescribeJobRunResponse -> ShowS
$cshowsPrec :: Int -> DescribeJobRunResponse -> ShowS
Prelude.Show, forall x. Rep DescribeJobRunResponse x -> DescribeJobRunResponse
forall x. DescribeJobRunResponse -> Rep DescribeJobRunResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DescribeJobRunResponse x -> DescribeJobRunResponse
$cfrom :: forall x. DescribeJobRunResponse -> Rep DescribeJobRunResponse x
Prelude.Generic)

-- |
-- Create a value of 'DescribeJobRunResponse' 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:
--
-- 'attempt', 'describeJobRunResponse_attempt' - The number of times that DataBrew has attempted to run the job.
--
-- 'completedOn', 'describeJobRunResponse_completedOn' - The date and time when the job completed processing.
--
-- 'dataCatalogOutputs', 'describeJobRunResponse_dataCatalogOutputs' - One or more artifacts that represent the Glue Data Catalog output from
-- running the job.
--
-- 'databaseOutputs', 'describeJobRunResponse_databaseOutputs' - Represents a list of JDBC database output objects which defines the
-- output destination for a DataBrew recipe job to write into.
--
-- 'datasetName', 'describeJobRunResponse_datasetName' - The name of the dataset for the job to process.
--
-- 'errorMessage', 'describeJobRunResponse_errorMessage' - A message indicating an error (if any) that was encountered when the job
-- ran.
--
-- 'executionTime', 'describeJobRunResponse_executionTime' - The amount of time, in seconds, during which the job run consumed
-- resources.
--
-- 'jobSample', 'describeJobRunResponse_jobSample' - Sample configuration for profile jobs only. Determines the number of
-- rows on which the profile job will be executed. If a JobSample value is
-- not provided, the default value will be used. The default value is
-- CUSTOM_ROWS for the mode parameter and 20000 for the size parameter.
--
-- 'logGroupName', 'describeJobRunResponse_logGroupName' - The name of an Amazon CloudWatch log group, where the job writes
-- diagnostic messages when it runs.
--
-- 'logSubscription', 'describeJobRunResponse_logSubscription' - The current status of Amazon CloudWatch logging for the job run.
--
-- 'outputs', 'describeJobRunResponse_outputs' - One or more output artifacts from a job run.
--
-- 'profileConfiguration', 'describeJobRunResponse_profileConfiguration' - Configuration for profile jobs. Used to select columns, do evaluations,
-- and override default parameters of evaluations. When configuration is
-- null, the profile job will run with default settings.
--
-- 'recipeReference', 'describeJobRunResponse_recipeReference' - Undocumented member.
--
-- 'runId', 'describeJobRunResponse_runId' - The unique identifier of the job run.
--
-- 'startedBy', 'describeJobRunResponse_startedBy' - The Amazon Resource Name (ARN) of the user who started the job run.
--
-- 'startedOn', 'describeJobRunResponse_startedOn' - The date and time when the job run began.
--
-- 'state', 'describeJobRunResponse_state' - The current state of the job run entity itself.
--
-- 'validationConfigurations', 'describeJobRunResponse_validationConfigurations' - List of validation configurations that are applied to the profile job.
--
-- 'httpStatus', 'describeJobRunResponse_httpStatus' - The response's http status code.
--
-- 'jobName', 'describeJobRunResponse_jobName' - The name of the job being processed during this run.
newDescribeJobRunResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  -- | 'jobName'
  Prelude.Text ->
  DescribeJobRunResponse
newDescribeJobRunResponse :: Int -> Text -> DescribeJobRunResponse
newDescribeJobRunResponse Int
pHttpStatus_ Text
pJobName_ =
  DescribeJobRunResponse'
    { $sel:attempt:DescribeJobRunResponse' :: Maybe Int
attempt = forall a. Maybe a
Prelude.Nothing,
      $sel:completedOn:DescribeJobRunResponse' :: Maybe POSIX
completedOn = forall a. Maybe a
Prelude.Nothing,
      $sel:dataCatalogOutputs:DescribeJobRunResponse' :: Maybe (NonEmpty DataCatalogOutput)
dataCatalogOutputs = forall a. Maybe a
Prelude.Nothing,
      $sel:databaseOutputs:DescribeJobRunResponse' :: Maybe (NonEmpty DatabaseOutput)
databaseOutputs = forall a. Maybe a
Prelude.Nothing,
      $sel:datasetName:DescribeJobRunResponse' :: Maybe Text
datasetName = forall a. Maybe a
Prelude.Nothing,
      $sel:errorMessage:DescribeJobRunResponse' :: Maybe Text
errorMessage = forall a. Maybe a
Prelude.Nothing,
      $sel:executionTime:DescribeJobRunResponse' :: Maybe Int
executionTime = forall a. Maybe a
Prelude.Nothing,
      $sel:jobSample:DescribeJobRunResponse' :: Maybe JobSample
jobSample = forall a. Maybe a
Prelude.Nothing,
      $sel:logGroupName:DescribeJobRunResponse' :: Maybe Text
logGroupName = forall a. Maybe a
Prelude.Nothing,
      $sel:logSubscription:DescribeJobRunResponse' :: Maybe LogSubscription
logSubscription = forall a. Maybe a
Prelude.Nothing,
      $sel:outputs:DescribeJobRunResponse' :: Maybe (NonEmpty Output)
outputs = forall a. Maybe a
Prelude.Nothing,
      $sel:profileConfiguration:DescribeJobRunResponse' :: Maybe ProfileConfiguration
profileConfiguration = forall a. Maybe a
Prelude.Nothing,
      $sel:recipeReference:DescribeJobRunResponse' :: Maybe RecipeReference
recipeReference = forall a. Maybe a
Prelude.Nothing,
      $sel:runId:DescribeJobRunResponse' :: Maybe Text
runId = forall a. Maybe a
Prelude.Nothing,
      $sel:startedBy:DescribeJobRunResponse' :: Maybe Text
startedBy = forall a. Maybe a
Prelude.Nothing,
      $sel:startedOn:DescribeJobRunResponse' :: Maybe POSIX
startedOn = forall a. Maybe a
Prelude.Nothing,
      $sel:state:DescribeJobRunResponse' :: Maybe JobRunState
state = forall a. Maybe a
Prelude.Nothing,
      $sel:validationConfigurations:DescribeJobRunResponse' :: Maybe (NonEmpty ValidationConfiguration)
validationConfigurations = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:DescribeJobRunResponse' :: Int
httpStatus = Int
pHttpStatus_,
      $sel:jobName:DescribeJobRunResponse' :: Text
jobName = Text
pJobName_
    }

-- | The number of times that DataBrew has attempted to run the job.
describeJobRunResponse_attempt :: Lens.Lens' DescribeJobRunResponse (Prelude.Maybe Prelude.Int)
describeJobRunResponse_attempt :: Lens' DescribeJobRunResponse (Maybe Int)
describeJobRunResponse_attempt = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeJobRunResponse' {Maybe Int
attempt :: Maybe Int
$sel:attempt:DescribeJobRunResponse' :: DescribeJobRunResponse -> Maybe Int
attempt} -> Maybe Int
attempt) (\s :: DescribeJobRunResponse
s@DescribeJobRunResponse' {} Maybe Int
a -> DescribeJobRunResponse
s {$sel:attempt:DescribeJobRunResponse' :: Maybe Int
attempt = Maybe Int
a} :: DescribeJobRunResponse)

-- | The date and time when the job completed processing.
describeJobRunResponse_completedOn :: Lens.Lens' DescribeJobRunResponse (Prelude.Maybe Prelude.UTCTime)
describeJobRunResponse_completedOn :: Lens' DescribeJobRunResponse (Maybe UTCTime)
describeJobRunResponse_completedOn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeJobRunResponse' {Maybe POSIX
completedOn :: Maybe POSIX
$sel:completedOn:DescribeJobRunResponse' :: DescribeJobRunResponse -> Maybe POSIX
completedOn} -> Maybe POSIX
completedOn) (\s :: DescribeJobRunResponse
s@DescribeJobRunResponse' {} Maybe POSIX
a -> DescribeJobRunResponse
s {$sel:completedOn:DescribeJobRunResponse' :: Maybe POSIX
completedOn = Maybe POSIX
a} :: DescribeJobRunResponse) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
Lens.mapping forall (a :: Format). Iso' (Time a) UTCTime
Data._Time

-- | One or more artifacts that represent the Glue Data Catalog output from
-- running the job.
describeJobRunResponse_dataCatalogOutputs :: Lens.Lens' DescribeJobRunResponse (Prelude.Maybe (Prelude.NonEmpty DataCatalogOutput))
describeJobRunResponse_dataCatalogOutputs :: Lens' DescribeJobRunResponse (Maybe (NonEmpty DataCatalogOutput))
describeJobRunResponse_dataCatalogOutputs = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeJobRunResponse' {Maybe (NonEmpty DataCatalogOutput)
dataCatalogOutputs :: Maybe (NonEmpty DataCatalogOutput)
$sel:dataCatalogOutputs:DescribeJobRunResponse' :: DescribeJobRunResponse -> Maybe (NonEmpty DataCatalogOutput)
dataCatalogOutputs} -> Maybe (NonEmpty DataCatalogOutput)
dataCatalogOutputs) (\s :: DescribeJobRunResponse
s@DescribeJobRunResponse' {} Maybe (NonEmpty DataCatalogOutput)
a -> DescribeJobRunResponse
s {$sel:dataCatalogOutputs:DescribeJobRunResponse' :: Maybe (NonEmpty DataCatalogOutput)
dataCatalogOutputs = Maybe (NonEmpty DataCatalogOutput)
a} :: DescribeJobRunResponse) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
Lens.mapping forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

-- | Represents a list of JDBC database output objects which defines the
-- output destination for a DataBrew recipe job to write into.
describeJobRunResponse_databaseOutputs :: Lens.Lens' DescribeJobRunResponse (Prelude.Maybe (Prelude.NonEmpty DatabaseOutput))
describeJobRunResponse_databaseOutputs :: Lens' DescribeJobRunResponse (Maybe (NonEmpty DatabaseOutput))
describeJobRunResponse_databaseOutputs = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeJobRunResponse' {Maybe (NonEmpty DatabaseOutput)
databaseOutputs :: Maybe (NonEmpty DatabaseOutput)
$sel:databaseOutputs:DescribeJobRunResponse' :: DescribeJobRunResponse -> Maybe (NonEmpty DatabaseOutput)
databaseOutputs} -> Maybe (NonEmpty DatabaseOutput)
databaseOutputs) (\s :: DescribeJobRunResponse
s@DescribeJobRunResponse' {} Maybe (NonEmpty DatabaseOutput)
a -> DescribeJobRunResponse
s {$sel:databaseOutputs:DescribeJobRunResponse' :: Maybe (NonEmpty DatabaseOutput)
databaseOutputs = Maybe (NonEmpty DatabaseOutput)
a} :: DescribeJobRunResponse) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
Lens.mapping forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

-- | The name of the dataset for the job to process.
describeJobRunResponse_datasetName :: Lens.Lens' DescribeJobRunResponse (Prelude.Maybe Prelude.Text)
describeJobRunResponse_datasetName :: Lens' DescribeJobRunResponse (Maybe Text)
describeJobRunResponse_datasetName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeJobRunResponse' {Maybe Text
datasetName :: Maybe Text
$sel:datasetName:DescribeJobRunResponse' :: DescribeJobRunResponse -> Maybe Text
datasetName} -> Maybe Text
datasetName) (\s :: DescribeJobRunResponse
s@DescribeJobRunResponse' {} Maybe Text
a -> DescribeJobRunResponse
s {$sel:datasetName:DescribeJobRunResponse' :: Maybe Text
datasetName = Maybe Text
a} :: DescribeJobRunResponse)

-- | A message indicating an error (if any) that was encountered when the job
-- ran.
describeJobRunResponse_errorMessage :: Lens.Lens' DescribeJobRunResponse (Prelude.Maybe Prelude.Text)
describeJobRunResponse_errorMessage :: Lens' DescribeJobRunResponse (Maybe Text)
describeJobRunResponse_errorMessage = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeJobRunResponse' {Maybe Text
errorMessage :: Maybe Text
$sel:errorMessage:DescribeJobRunResponse' :: DescribeJobRunResponse -> Maybe Text
errorMessage} -> Maybe Text
errorMessage) (\s :: DescribeJobRunResponse
s@DescribeJobRunResponse' {} Maybe Text
a -> DescribeJobRunResponse
s {$sel:errorMessage:DescribeJobRunResponse' :: Maybe Text
errorMessage = Maybe Text
a} :: DescribeJobRunResponse)

-- | The amount of time, in seconds, during which the job run consumed
-- resources.
describeJobRunResponse_executionTime :: Lens.Lens' DescribeJobRunResponse (Prelude.Maybe Prelude.Int)
describeJobRunResponse_executionTime :: Lens' DescribeJobRunResponse (Maybe Int)
describeJobRunResponse_executionTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeJobRunResponse' {Maybe Int
executionTime :: Maybe Int
$sel:executionTime:DescribeJobRunResponse' :: DescribeJobRunResponse -> Maybe Int
executionTime} -> Maybe Int
executionTime) (\s :: DescribeJobRunResponse
s@DescribeJobRunResponse' {} Maybe Int
a -> DescribeJobRunResponse
s {$sel:executionTime:DescribeJobRunResponse' :: Maybe Int
executionTime = Maybe Int
a} :: DescribeJobRunResponse)

-- | Sample configuration for profile jobs only. Determines the number of
-- rows on which the profile job will be executed. If a JobSample value is
-- not provided, the default value will be used. The default value is
-- CUSTOM_ROWS for the mode parameter and 20000 for the size parameter.
describeJobRunResponse_jobSample :: Lens.Lens' DescribeJobRunResponse (Prelude.Maybe JobSample)
describeJobRunResponse_jobSample :: Lens' DescribeJobRunResponse (Maybe JobSample)
describeJobRunResponse_jobSample = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeJobRunResponse' {Maybe JobSample
jobSample :: Maybe JobSample
$sel:jobSample:DescribeJobRunResponse' :: DescribeJobRunResponse -> Maybe JobSample
jobSample} -> Maybe JobSample
jobSample) (\s :: DescribeJobRunResponse
s@DescribeJobRunResponse' {} Maybe JobSample
a -> DescribeJobRunResponse
s {$sel:jobSample:DescribeJobRunResponse' :: Maybe JobSample
jobSample = Maybe JobSample
a} :: DescribeJobRunResponse)

-- | The name of an Amazon CloudWatch log group, where the job writes
-- diagnostic messages when it runs.
describeJobRunResponse_logGroupName :: Lens.Lens' DescribeJobRunResponse (Prelude.Maybe Prelude.Text)
describeJobRunResponse_logGroupName :: Lens' DescribeJobRunResponse (Maybe Text)
describeJobRunResponse_logGroupName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeJobRunResponse' {Maybe Text
logGroupName :: Maybe Text
$sel:logGroupName:DescribeJobRunResponse' :: DescribeJobRunResponse -> Maybe Text
logGroupName} -> Maybe Text
logGroupName) (\s :: DescribeJobRunResponse
s@DescribeJobRunResponse' {} Maybe Text
a -> DescribeJobRunResponse
s {$sel:logGroupName:DescribeJobRunResponse' :: Maybe Text
logGroupName = Maybe Text
a} :: DescribeJobRunResponse)

-- | The current status of Amazon CloudWatch logging for the job run.
describeJobRunResponse_logSubscription :: Lens.Lens' DescribeJobRunResponse (Prelude.Maybe LogSubscription)
describeJobRunResponse_logSubscription :: Lens' DescribeJobRunResponse (Maybe LogSubscription)
describeJobRunResponse_logSubscription = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeJobRunResponse' {Maybe LogSubscription
logSubscription :: Maybe LogSubscription
$sel:logSubscription:DescribeJobRunResponse' :: DescribeJobRunResponse -> Maybe LogSubscription
logSubscription} -> Maybe LogSubscription
logSubscription) (\s :: DescribeJobRunResponse
s@DescribeJobRunResponse' {} Maybe LogSubscription
a -> DescribeJobRunResponse
s {$sel:logSubscription:DescribeJobRunResponse' :: Maybe LogSubscription
logSubscription = Maybe LogSubscription
a} :: DescribeJobRunResponse)

-- | One or more output artifacts from a job run.
describeJobRunResponse_outputs :: Lens.Lens' DescribeJobRunResponse (Prelude.Maybe (Prelude.NonEmpty Output))
describeJobRunResponse_outputs :: Lens' DescribeJobRunResponse (Maybe (NonEmpty Output))
describeJobRunResponse_outputs = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeJobRunResponse' {Maybe (NonEmpty Output)
outputs :: Maybe (NonEmpty Output)
$sel:outputs:DescribeJobRunResponse' :: DescribeJobRunResponse -> Maybe (NonEmpty Output)
outputs} -> Maybe (NonEmpty Output)
outputs) (\s :: DescribeJobRunResponse
s@DescribeJobRunResponse' {} Maybe (NonEmpty Output)
a -> DescribeJobRunResponse
s {$sel:outputs:DescribeJobRunResponse' :: Maybe (NonEmpty Output)
outputs = Maybe (NonEmpty Output)
a} :: DescribeJobRunResponse) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
Lens.mapping forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

-- | Configuration for profile jobs. Used to select columns, do evaluations,
-- and override default parameters of evaluations. When configuration is
-- null, the profile job will run with default settings.
describeJobRunResponse_profileConfiguration :: Lens.Lens' DescribeJobRunResponse (Prelude.Maybe ProfileConfiguration)
describeJobRunResponse_profileConfiguration :: Lens' DescribeJobRunResponse (Maybe ProfileConfiguration)
describeJobRunResponse_profileConfiguration = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeJobRunResponse' {Maybe ProfileConfiguration
profileConfiguration :: Maybe ProfileConfiguration
$sel:profileConfiguration:DescribeJobRunResponse' :: DescribeJobRunResponse -> Maybe ProfileConfiguration
profileConfiguration} -> Maybe ProfileConfiguration
profileConfiguration) (\s :: DescribeJobRunResponse
s@DescribeJobRunResponse' {} Maybe ProfileConfiguration
a -> DescribeJobRunResponse
s {$sel:profileConfiguration:DescribeJobRunResponse' :: Maybe ProfileConfiguration
profileConfiguration = Maybe ProfileConfiguration
a} :: DescribeJobRunResponse)

-- | Undocumented member.
describeJobRunResponse_recipeReference :: Lens.Lens' DescribeJobRunResponse (Prelude.Maybe RecipeReference)
describeJobRunResponse_recipeReference :: Lens' DescribeJobRunResponse (Maybe RecipeReference)
describeJobRunResponse_recipeReference = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeJobRunResponse' {Maybe RecipeReference
recipeReference :: Maybe RecipeReference
$sel:recipeReference:DescribeJobRunResponse' :: DescribeJobRunResponse -> Maybe RecipeReference
recipeReference} -> Maybe RecipeReference
recipeReference) (\s :: DescribeJobRunResponse
s@DescribeJobRunResponse' {} Maybe RecipeReference
a -> DescribeJobRunResponse
s {$sel:recipeReference:DescribeJobRunResponse' :: Maybe RecipeReference
recipeReference = Maybe RecipeReference
a} :: DescribeJobRunResponse)

-- | The unique identifier of the job run.
describeJobRunResponse_runId :: Lens.Lens' DescribeJobRunResponse (Prelude.Maybe Prelude.Text)
describeJobRunResponse_runId :: Lens' DescribeJobRunResponse (Maybe Text)
describeJobRunResponse_runId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeJobRunResponse' {Maybe Text
runId :: Maybe Text
$sel:runId:DescribeJobRunResponse' :: DescribeJobRunResponse -> Maybe Text
runId} -> Maybe Text
runId) (\s :: DescribeJobRunResponse
s@DescribeJobRunResponse' {} Maybe Text
a -> DescribeJobRunResponse
s {$sel:runId:DescribeJobRunResponse' :: Maybe Text
runId = Maybe Text
a} :: DescribeJobRunResponse)

-- | The Amazon Resource Name (ARN) of the user who started the job run.
describeJobRunResponse_startedBy :: Lens.Lens' DescribeJobRunResponse (Prelude.Maybe Prelude.Text)
describeJobRunResponse_startedBy :: Lens' DescribeJobRunResponse (Maybe Text)
describeJobRunResponse_startedBy = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeJobRunResponse' {Maybe Text
startedBy :: Maybe Text
$sel:startedBy:DescribeJobRunResponse' :: DescribeJobRunResponse -> Maybe Text
startedBy} -> Maybe Text
startedBy) (\s :: DescribeJobRunResponse
s@DescribeJobRunResponse' {} Maybe Text
a -> DescribeJobRunResponse
s {$sel:startedBy:DescribeJobRunResponse' :: Maybe Text
startedBy = Maybe Text
a} :: DescribeJobRunResponse)

-- | The date and time when the job run began.
describeJobRunResponse_startedOn :: Lens.Lens' DescribeJobRunResponse (Prelude.Maybe Prelude.UTCTime)
describeJobRunResponse_startedOn :: Lens' DescribeJobRunResponse (Maybe UTCTime)
describeJobRunResponse_startedOn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeJobRunResponse' {Maybe POSIX
startedOn :: Maybe POSIX
$sel:startedOn:DescribeJobRunResponse' :: DescribeJobRunResponse -> Maybe POSIX
startedOn} -> Maybe POSIX
startedOn) (\s :: DescribeJobRunResponse
s@DescribeJobRunResponse' {} Maybe POSIX
a -> DescribeJobRunResponse
s {$sel:startedOn:DescribeJobRunResponse' :: Maybe POSIX
startedOn = Maybe POSIX
a} :: DescribeJobRunResponse) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
Lens.mapping forall (a :: Format). Iso' (Time a) UTCTime
Data._Time

-- | The current state of the job run entity itself.
describeJobRunResponse_state :: Lens.Lens' DescribeJobRunResponse (Prelude.Maybe JobRunState)
describeJobRunResponse_state :: Lens' DescribeJobRunResponse (Maybe JobRunState)
describeJobRunResponse_state = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeJobRunResponse' {Maybe JobRunState
state :: Maybe JobRunState
$sel:state:DescribeJobRunResponse' :: DescribeJobRunResponse -> Maybe JobRunState
state} -> Maybe JobRunState
state) (\s :: DescribeJobRunResponse
s@DescribeJobRunResponse' {} Maybe JobRunState
a -> DescribeJobRunResponse
s {$sel:state:DescribeJobRunResponse' :: Maybe JobRunState
state = Maybe JobRunState
a} :: DescribeJobRunResponse)

-- | List of validation configurations that are applied to the profile job.
describeJobRunResponse_validationConfigurations :: Lens.Lens' DescribeJobRunResponse (Prelude.Maybe (Prelude.NonEmpty ValidationConfiguration))
describeJobRunResponse_validationConfigurations :: Lens'
  DescribeJobRunResponse (Maybe (NonEmpty ValidationConfiguration))
describeJobRunResponse_validationConfigurations = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeJobRunResponse' {Maybe (NonEmpty ValidationConfiguration)
validationConfigurations :: Maybe (NonEmpty ValidationConfiguration)
$sel:validationConfigurations:DescribeJobRunResponse' :: DescribeJobRunResponse -> Maybe (NonEmpty ValidationConfiguration)
validationConfigurations} -> Maybe (NonEmpty ValidationConfiguration)
validationConfigurations) (\s :: DescribeJobRunResponse
s@DescribeJobRunResponse' {} Maybe (NonEmpty ValidationConfiguration)
a -> DescribeJobRunResponse
s {$sel:validationConfigurations:DescribeJobRunResponse' :: Maybe (NonEmpty ValidationConfiguration)
validationConfigurations = Maybe (NonEmpty ValidationConfiguration)
a} :: DescribeJobRunResponse) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
Lens.mapping forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

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

-- | The name of the job being processed during this run.
describeJobRunResponse_jobName :: Lens.Lens' DescribeJobRunResponse Prelude.Text
describeJobRunResponse_jobName :: Lens' DescribeJobRunResponse Text
describeJobRunResponse_jobName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeJobRunResponse' {Text
jobName :: Text
$sel:jobName:DescribeJobRunResponse' :: DescribeJobRunResponse -> Text
jobName} -> Text
jobName) (\s :: DescribeJobRunResponse
s@DescribeJobRunResponse' {} Text
a -> DescribeJobRunResponse
s {$sel:jobName:DescribeJobRunResponse' :: Text
jobName = Text
a} :: DescribeJobRunResponse)

instance Prelude.NFData DescribeJobRunResponse where
  rnf :: DescribeJobRunResponse -> ()
rnf DescribeJobRunResponse' {Int
Maybe Int
Maybe (NonEmpty Output)
Maybe (NonEmpty DatabaseOutput)
Maybe (NonEmpty DataCatalogOutput)
Maybe (NonEmpty ValidationConfiguration)
Maybe Text
Maybe POSIX
Maybe JobRunState
Maybe LogSubscription
Maybe RecipeReference
Maybe JobSample
Maybe ProfileConfiguration
Text
jobName :: Text
httpStatus :: Int
validationConfigurations :: Maybe (NonEmpty ValidationConfiguration)
state :: Maybe JobRunState
startedOn :: Maybe POSIX
startedBy :: Maybe Text
runId :: Maybe Text
recipeReference :: Maybe RecipeReference
profileConfiguration :: Maybe ProfileConfiguration
outputs :: Maybe (NonEmpty Output)
logSubscription :: Maybe LogSubscription
logGroupName :: Maybe Text
jobSample :: Maybe JobSample
executionTime :: Maybe Int
errorMessage :: Maybe Text
datasetName :: Maybe Text
databaseOutputs :: Maybe (NonEmpty DatabaseOutput)
dataCatalogOutputs :: Maybe (NonEmpty DataCatalogOutput)
completedOn :: Maybe POSIX
attempt :: Maybe Int
$sel:jobName:DescribeJobRunResponse' :: DescribeJobRunResponse -> Text
$sel:httpStatus:DescribeJobRunResponse' :: DescribeJobRunResponse -> Int
$sel:validationConfigurations:DescribeJobRunResponse' :: DescribeJobRunResponse -> Maybe (NonEmpty ValidationConfiguration)
$sel:state:DescribeJobRunResponse' :: DescribeJobRunResponse -> Maybe JobRunState
$sel:startedOn:DescribeJobRunResponse' :: DescribeJobRunResponse -> Maybe POSIX
$sel:startedBy:DescribeJobRunResponse' :: DescribeJobRunResponse -> Maybe Text
$sel:runId:DescribeJobRunResponse' :: DescribeJobRunResponse -> Maybe Text
$sel:recipeReference:DescribeJobRunResponse' :: DescribeJobRunResponse -> Maybe RecipeReference
$sel:profileConfiguration:DescribeJobRunResponse' :: DescribeJobRunResponse -> Maybe ProfileConfiguration
$sel:outputs:DescribeJobRunResponse' :: DescribeJobRunResponse -> Maybe (NonEmpty Output)
$sel:logSubscription:DescribeJobRunResponse' :: DescribeJobRunResponse -> Maybe LogSubscription
$sel:logGroupName:DescribeJobRunResponse' :: DescribeJobRunResponse -> Maybe Text
$sel:jobSample:DescribeJobRunResponse' :: DescribeJobRunResponse -> Maybe JobSample
$sel:executionTime:DescribeJobRunResponse' :: DescribeJobRunResponse -> Maybe Int
$sel:errorMessage:DescribeJobRunResponse' :: DescribeJobRunResponse -> Maybe Text
$sel:datasetName:DescribeJobRunResponse' :: DescribeJobRunResponse -> Maybe Text
$sel:databaseOutputs:DescribeJobRunResponse' :: DescribeJobRunResponse -> Maybe (NonEmpty DatabaseOutput)
$sel:dataCatalogOutputs:DescribeJobRunResponse' :: DescribeJobRunResponse -> Maybe (NonEmpty DataCatalogOutput)
$sel:completedOn:DescribeJobRunResponse' :: DescribeJobRunResponse -> Maybe POSIX
$sel:attempt:DescribeJobRunResponse' :: DescribeJobRunResponse -> Maybe Int
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Int
attempt
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe POSIX
completedOn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe (NonEmpty DataCatalogOutput)
dataCatalogOutputs
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe (NonEmpty DatabaseOutput)
databaseOutputs
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
datasetName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
errorMessage
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Int
executionTime
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe JobSample
jobSample
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
logGroupName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe LogSubscription
logSubscription
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe (NonEmpty Output)
outputs
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ProfileConfiguration
profileConfiguration
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe RecipeReference
recipeReference
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
runId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
startedBy
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe POSIX
startedOn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe JobRunState
state
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Maybe (NonEmpty ValidationConfiguration)
validationConfigurations
      seq :: forall a b. a -> b -> b
`Prelude.seq` 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 Text
jobName