{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DuplicateRecordFields #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE StrictData #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# 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.Types.JobRun
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
module Amazonka.DataBrew.Types.JobRun 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.DataCatalogOutput
import Amazonka.DataBrew.Types.DatabaseOutput
import Amazonka.DataBrew.Types.JobRunState
import Amazonka.DataBrew.Types.JobSample
import Amazonka.DataBrew.Types.LogSubscription
import Amazonka.DataBrew.Types.Output
import Amazonka.DataBrew.Types.RecipeReference
import Amazonka.DataBrew.Types.ValidationConfiguration
import qualified Amazonka.Prelude as Prelude

-- | Represents one run of a DataBrew job.
--
-- /See:/ 'newJobRun' smart constructor.
data JobRun = JobRun'
  { -- | The number of times that DataBrew has attempted to run the job.
    JobRun -> Maybe Int
attempt :: Prelude.Maybe Prelude.Int,
    -- | The date and time when the job completed processing.
    JobRun -> Maybe POSIX
completedOn :: Prelude.Maybe Data.POSIX,
    -- | One or more artifacts that represent the Glue Data Catalog output from
    -- running the job.
    JobRun -> 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.
    JobRun -> Maybe (NonEmpty DatabaseOutput)
databaseOutputs :: Prelude.Maybe (Prelude.NonEmpty DatabaseOutput),
    -- | The name of the dataset for the job to process.
    JobRun -> Maybe Text
datasetName :: Prelude.Maybe Prelude.Text,
    -- | A message indicating an error (if any) that was encountered when the job
    -- ran.
    JobRun -> Maybe Text
errorMessage :: Prelude.Maybe Prelude.Text,
    -- | The amount of time, in seconds, during which a job run consumed
    -- resources.
    JobRun -> Maybe Int
executionTime :: Prelude.Maybe Prelude.Int,
    -- | The name of the job being processed during this run.
    JobRun -> Maybe Text
jobName :: Prelude.Maybe Prelude.Text,
    -- | A sample configuration for profile jobs only, which determines the
    -- number of rows on which the profile job is run. If a @JobSample@ value
    -- isn\'t provided, the default is used. The default value is CUSTOM_ROWS
    -- for the mode parameter and 20,000 for the size parameter.
    JobRun -> Maybe JobSample
jobSample :: Prelude.Maybe JobSample,
    -- | The name of an Amazon CloudWatch log group, where the job writes
    -- diagnostic messages when it runs.
    JobRun -> Maybe Text
logGroupName :: Prelude.Maybe Prelude.Text,
    -- | The current status of Amazon CloudWatch logging for the job run.
    JobRun -> Maybe LogSubscription
logSubscription :: Prelude.Maybe LogSubscription,
    -- | One or more output artifacts from a job run.
    JobRun -> Maybe (NonEmpty Output)
outputs :: Prelude.Maybe (Prelude.NonEmpty Output),
    -- | The set of steps processed by the job.
    JobRun -> Maybe RecipeReference
recipeReference :: Prelude.Maybe RecipeReference,
    -- | The unique identifier of the job run.
    JobRun -> Maybe Text
runId :: Prelude.Maybe Prelude.Text,
    -- | The Amazon Resource Name (ARN) of the user who initiated the job run.
    JobRun -> Maybe Text
startedBy :: Prelude.Maybe Prelude.Text,
    -- | The date and time when the job run began.
    JobRun -> Maybe POSIX
startedOn :: Prelude.Maybe Data.POSIX,
    -- | The current state of the job run entity itself.
    JobRun -> Maybe JobRunState
state :: Prelude.Maybe JobRunState,
    -- | List of validation configurations that are applied to the profile job
    -- run.
    JobRun -> Maybe (NonEmpty ValidationConfiguration)
validationConfigurations :: Prelude.Maybe (Prelude.NonEmpty ValidationConfiguration)
  }
  deriving (JobRun -> JobRun -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: JobRun -> JobRun -> Bool
$c/= :: JobRun -> JobRun -> Bool
== :: JobRun -> JobRun -> Bool
$c== :: JobRun -> JobRun -> Bool
Prelude.Eq, ReadPrec [JobRun]
ReadPrec JobRun
Int -> ReadS JobRun
ReadS [JobRun]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [JobRun]
$creadListPrec :: ReadPrec [JobRun]
readPrec :: ReadPrec JobRun
$creadPrec :: ReadPrec JobRun
readList :: ReadS [JobRun]
$creadList :: ReadS [JobRun]
readsPrec :: Int -> ReadS JobRun
$creadsPrec :: Int -> ReadS JobRun
Prelude.Read, Int -> JobRun -> ShowS
[JobRun] -> ShowS
JobRun -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [JobRun] -> ShowS
$cshowList :: [JobRun] -> ShowS
show :: JobRun -> String
$cshow :: JobRun -> String
showsPrec :: Int -> JobRun -> ShowS
$cshowsPrec :: Int -> JobRun -> ShowS
Prelude.Show, forall x. Rep JobRun x -> JobRun
forall x. JobRun -> Rep JobRun x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep JobRun x -> JobRun
$cfrom :: forall x. JobRun -> Rep JobRun x
Prelude.Generic)

-- |
-- Create a value of 'JobRun' 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', 'jobRun_attempt' - The number of times that DataBrew has attempted to run the job.
--
-- 'completedOn', 'jobRun_completedOn' - The date and time when the job completed processing.
--
-- 'dataCatalogOutputs', 'jobRun_dataCatalogOutputs' - One or more artifacts that represent the Glue Data Catalog output from
-- running the job.
--
-- 'databaseOutputs', 'jobRun_databaseOutputs' - Represents a list of JDBC database output objects which defines the
-- output destination for a DataBrew recipe job to write into.
--
-- 'datasetName', 'jobRun_datasetName' - The name of the dataset for the job to process.
--
-- 'errorMessage', 'jobRun_errorMessage' - A message indicating an error (if any) that was encountered when the job
-- ran.
--
-- 'executionTime', 'jobRun_executionTime' - The amount of time, in seconds, during which a job run consumed
-- resources.
--
-- 'jobName', 'jobRun_jobName' - The name of the job being processed during this run.
--
-- 'jobSample', 'jobRun_jobSample' - A sample configuration for profile jobs only, which determines the
-- number of rows on which the profile job is run. If a @JobSample@ value
-- isn\'t provided, the default is used. The default value is CUSTOM_ROWS
-- for the mode parameter and 20,000 for the size parameter.
--
-- 'logGroupName', 'jobRun_logGroupName' - The name of an Amazon CloudWatch log group, where the job writes
-- diagnostic messages when it runs.
--
-- 'logSubscription', 'jobRun_logSubscription' - The current status of Amazon CloudWatch logging for the job run.
--
-- 'outputs', 'jobRun_outputs' - One or more output artifacts from a job run.
--
-- 'recipeReference', 'jobRun_recipeReference' - The set of steps processed by the job.
--
-- 'runId', 'jobRun_runId' - The unique identifier of the job run.
--
-- 'startedBy', 'jobRun_startedBy' - The Amazon Resource Name (ARN) of the user who initiated the job run.
--
-- 'startedOn', 'jobRun_startedOn' - The date and time when the job run began.
--
-- 'state', 'jobRun_state' - The current state of the job run entity itself.
--
-- 'validationConfigurations', 'jobRun_validationConfigurations' - List of validation configurations that are applied to the profile job
-- run.
newJobRun ::
  JobRun
newJobRun :: JobRun
newJobRun =
  JobRun'
    { $sel:attempt:JobRun' :: Maybe Int
attempt = forall a. Maybe a
Prelude.Nothing,
      $sel:completedOn:JobRun' :: Maybe POSIX
completedOn = forall a. Maybe a
Prelude.Nothing,
      $sel:dataCatalogOutputs:JobRun' :: Maybe (NonEmpty DataCatalogOutput)
dataCatalogOutputs = forall a. Maybe a
Prelude.Nothing,
      $sel:databaseOutputs:JobRun' :: Maybe (NonEmpty DatabaseOutput)
databaseOutputs = forall a. Maybe a
Prelude.Nothing,
      $sel:datasetName:JobRun' :: Maybe Text
datasetName = forall a. Maybe a
Prelude.Nothing,
      $sel:errorMessage:JobRun' :: Maybe Text
errorMessage = forall a. Maybe a
Prelude.Nothing,
      $sel:executionTime:JobRun' :: Maybe Int
executionTime = forall a. Maybe a
Prelude.Nothing,
      $sel:jobName:JobRun' :: Maybe Text
jobName = forall a. Maybe a
Prelude.Nothing,
      $sel:jobSample:JobRun' :: Maybe JobSample
jobSample = forall a. Maybe a
Prelude.Nothing,
      $sel:logGroupName:JobRun' :: Maybe Text
logGroupName = forall a. Maybe a
Prelude.Nothing,
      $sel:logSubscription:JobRun' :: Maybe LogSubscription
logSubscription = forall a. Maybe a
Prelude.Nothing,
      $sel:outputs:JobRun' :: Maybe (NonEmpty Output)
outputs = forall a. Maybe a
Prelude.Nothing,
      $sel:recipeReference:JobRun' :: Maybe RecipeReference
recipeReference = forall a. Maybe a
Prelude.Nothing,
      $sel:runId:JobRun' :: Maybe Text
runId = forall a. Maybe a
Prelude.Nothing,
      $sel:startedBy:JobRun' :: Maybe Text
startedBy = forall a. Maybe a
Prelude.Nothing,
      $sel:startedOn:JobRun' :: Maybe POSIX
startedOn = forall a. Maybe a
Prelude.Nothing,
      $sel:state:JobRun' :: Maybe JobRunState
state = forall a. Maybe a
Prelude.Nothing,
      $sel:validationConfigurations:JobRun' :: Maybe (NonEmpty ValidationConfiguration)
validationConfigurations = forall a. Maybe a
Prelude.Nothing
    }

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

-- | The date and time when the job completed processing.
jobRun_completedOn :: Lens.Lens' JobRun (Prelude.Maybe Prelude.UTCTime)
jobRun_completedOn :: Lens' JobRun (Maybe UTCTime)
jobRun_completedOn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\JobRun' {Maybe POSIX
completedOn :: Maybe POSIX
$sel:completedOn:JobRun' :: JobRun -> Maybe POSIX
completedOn} -> Maybe POSIX
completedOn) (\s :: JobRun
s@JobRun' {} Maybe POSIX
a -> JobRun
s {$sel:completedOn:JobRun' :: Maybe POSIX
completedOn = Maybe POSIX
a} :: JobRun) 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.
jobRun_dataCatalogOutputs :: Lens.Lens' JobRun (Prelude.Maybe (Prelude.NonEmpty DataCatalogOutput))
jobRun_dataCatalogOutputs :: Lens' JobRun (Maybe (NonEmpty DataCatalogOutput))
jobRun_dataCatalogOutputs = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\JobRun' {Maybe (NonEmpty DataCatalogOutput)
dataCatalogOutputs :: Maybe (NonEmpty DataCatalogOutput)
$sel:dataCatalogOutputs:JobRun' :: JobRun -> Maybe (NonEmpty DataCatalogOutput)
dataCatalogOutputs} -> Maybe (NonEmpty DataCatalogOutput)
dataCatalogOutputs) (\s :: JobRun
s@JobRun' {} Maybe (NonEmpty DataCatalogOutput)
a -> JobRun
s {$sel:dataCatalogOutputs:JobRun' :: Maybe (NonEmpty DataCatalogOutput)
dataCatalogOutputs = Maybe (NonEmpty DataCatalogOutput)
a} :: JobRun) 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.
jobRun_databaseOutputs :: Lens.Lens' JobRun (Prelude.Maybe (Prelude.NonEmpty DatabaseOutput))
jobRun_databaseOutputs :: Lens' JobRun (Maybe (NonEmpty DatabaseOutput))
jobRun_databaseOutputs = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\JobRun' {Maybe (NonEmpty DatabaseOutput)
databaseOutputs :: Maybe (NonEmpty DatabaseOutput)
$sel:databaseOutputs:JobRun' :: JobRun -> Maybe (NonEmpty DatabaseOutput)
databaseOutputs} -> Maybe (NonEmpty DatabaseOutput)
databaseOutputs) (\s :: JobRun
s@JobRun' {} Maybe (NonEmpty DatabaseOutput)
a -> JobRun
s {$sel:databaseOutputs:JobRun' :: Maybe (NonEmpty DatabaseOutput)
databaseOutputs = Maybe (NonEmpty DatabaseOutput)
a} :: JobRun) 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.
jobRun_datasetName :: Lens.Lens' JobRun (Prelude.Maybe Prelude.Text)
jobRun_datasetName :: Lens' JobRun (Maybe Text)
jobRun_datasetName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\JobRun' {Maybe Text
datasetName :: Maybe Text
$sel:datasetName:JobRun' :: JobRun -> Maybe Text
datasetName} -> Maybe Text
datasetName) (\s :: JobRun
s@JobRun' {} Maybe Text
a -> JobRun
s {$sel:datasetName:JobRun' :: Maybe Text
datasetName = Maybe Text
a} :: JobRun)

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

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

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

-- | A sample configuration for profile jobs only, which determines the
-- number of rows on which the profile job is run. If a @JobSample@ value
-- isn\'t provided, the default is used. The default value is CUSTOM_ROWS
-- for the mode parameter and 20,000 for the size parameter.
jobRun_jobSample :: Lens.Lens' JobRun (Prelude.Maybe JobSample)
jobRun_jobSample :: Lens' JobRun (Maybe JobSample)
jobRun_jobSample = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\JobRun' {Maybe JobSample
jobSample :: Maybe JobSample
$sel:jobSample:JobRun' :: JobRun -> Maybe JobSample
jobSample} -> Maybe JobSample
jobSample) (\s :: JobRun
s@JobRun' {} Maybe JobSample
a -> JobRun
s {$sel:jobSample:JobRun' :: Maybe JobSample
jobSample = Maybe JobSample
a} :: JobRun)

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

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

-- | One or more output artifacts from a job run.
jobRun_outputs :: Lens.Lens' JobRun (Prelude.Maybe (Prelude.NonEmpty Output))
jobRun_outputs :: Lens' JobRun (Maybe (NonEmpty Output))
jobRun_outputs = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\JobRun' {Maybe (NonEmpty Output)
outputs :: Maybe (NonEmpty Output)
$sel:outputs:JobRun' :: JobRun -> Maybe (NonEmpty Output)
outputs} -> Maybe (NonEmpty Output)
outputs) (\s :: JobRun
s@JobRun' {} Maybe (NonEmpty Output)
a -> JobRun
s {$sel:outputs:JobRun' :: Maybe (NonEmpty Output)
outputs = Maybe (NonEmpty Output)
a} :: JobRun) 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 set of steps processed by the job.
jobRun_recipeReference :: Lens.Lens' JobRun (Prelude.Maybe RecipeReference)
jobRun_recipeReference :: Lens' JobRun (Maybe RecipeReference)
jobRun_recipeReference = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\JobRun' {Maybe RecipeReference
recipeReference :: Maybe RecipeReference
$sel:recipeReference:JobRun' :: JobRun -> Maybe RecipeReference
recipeReference} -> Maybe RecipeReference
recipeReference) (\s :: JobRun
s@JobRun' {} Maybe RecipeReference
a -> JobRun
s {$sel:recipeReference:JobRun' :: Maybe RecipeReference
recipeReference = Maybe RecipeReference
a} :: JobRun)

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

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

-- | The date and time when the job run began.
jobRun_startedOn :: Lens.Lens' JobRun (Prelude.Maybe Prelude.UTCTime)
jobRun_startedOn :: Lens' JobRun (Maybe UTCTime)
jobRun_startedOn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\JobRun' {Maybe POSIX
startedOn :: Maybe POSIX
$sel:startedOn:JobRun' :: JobRun -> Maybe POSIX
startedOn} -> Maybe POSIX
startedOn) (\s :: JobRun
s@JobRun' {} Maybe POSIX
a -> JobRun
s {$sel:startedOn:JobRun' :: Maybe POSIX
startedOn = Maybe POSIX
a} :: JobRun) 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.
jobRun_state :: Lens.Lens' JobRun (Prelude.Maybe JobRunState)
jobRun_state :: Lens' JobRun (Maybe JobRunState)
jobRun_state = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\JobRun' {Maybe JobRunState
state :: Maybe JobRunState
$sel:state:JobRun' :: JobRun -> Maybe JobRunState
state} -> Maybe JobRunState
state) (\s :: JobRun
s@JobRun' {} Maybe JobRunState
a -> JobRun
s {$sel:state:JobRun' :: Maybe JobRunState
state = Maybe JobRunState
a} :: JobRun)

-- | List of validation configurations that are applied to the profile job
-- run.
jobRun_validationConfigurations :: Lens.Lens' JobRun (Prelude.Maybe (Prelude.NonEmpty ValidationConfiguration))
jobRun_validationConfigurations :: Lens' JobRun (Maybe (NonEmpty ValidationConfiguration))
jobRun_validationConfigurations = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\JobRun' {Maybe (NonEmpty ValidationConfiguration)
validationConfigurations :: Maybe (NonEmpty ValidationConfiguration)
$sel:validationConfigurations:JobRun' :: JobRun -> Maybe (NonEmpty ValidationConfiguration)
validationConfigurations} -> Maybe (NonEmpty ValidationConfiguration)
validationConfigurations) (\s :: JobRun
s@JobRun' {} Maybe (NonEmpty ValidationConfiguration)
a -> JobRun
s {$sel:validationConfigurations:JobRun' :: Maybe (NonEmpty ValidationConfiguration)
validationConfigurations = Maybe (NonEmpty ValidationConfiguration)
a} :: JobRun) 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

instance Data.FromJSON JobRun where
  parseJSON :: Value -> Parser JobRun
parseJSON =
    forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.withObject
      String
"JobRun"
      ( \Object
x ->
          Maybe Int
-> Maybe POSIX
-> Maybe (NonEmpty DataCatalogOutput)
-> Maybe (NonEmpty DatabaseOutput)
-> Maybe Text
-> Maybe Text
-> Maybe Int
-> Maybe Text
-> Maybe JobSample
-> Maybe Text
-> Maybe LogSubscription
-> Maybe (NonEmpty Output)
-> Maybe RecipeReference
-> Maybe Text
-> Maybe Text
-> Maybe POSIX
-> Maybe JobRunState
-> Maybe (NonEmpty ValidationConfiguration)
-> JobRun
JobRun'
            forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> (Object
x forall a. FromJSON a => Object -> Key -> Parser (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 -> Parser (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 -> Parser (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 -> Parser (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 -> Parser (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 -> Parser (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 -> Parser (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 -> Parser (Maybe a)
Data..:? Key
"JobName")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (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 -> Parser (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 -> Parser (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 -> Parser (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 -> Parser (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 -> Parser (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 -> Parser (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 -> Parser (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 -> Parser (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 -> Parser (Maybe a)
Data..:? Key
"ValidationConfigurations")
      )

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

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