{-# 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.Job
-- 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.Job 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.EncryptionMode
import Amazonka.DataBrew.Types.JobSample
import Amazonka.DataBrew.Types.JobType
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 all of the attributes of a DataBrew job.
--
-- /See:/ 'newJob' smart constructor.
data Job = Job'
  { -- | The ID of the Amazon Web Services account that owns the job.
    Job -> Maybe Text
accountId :: Prelude.Maybe Prelude.Text,
    -- | The date and time that the job was created.
    Job -> Maybe POSIX
createDate :: Prelude.Maybe Data.POSIX,
    -- | The Amazon Resource Name (ARN) of the user who created the job.
    Job -> Maybe Text
createdBy :: Prelude.Maybe Prelude.Text,
    -- | One or more artifacts that represent the Glue Data Catalog output from
    -- running the job.
    Job -> 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.
    Job -> Maybe (NonEmpty DatabaseOutput)
databaseOutputs :: Prelude.Maybe (Prelude.NonEmpty DatabaseOutput),
    -- | A dataset that the job is to process.
    Job -> Maybe Text
datasetName :: Prelude.Maybe Prelude.Text,
    -- | The Amazon Resource Name (ARN) of an encryption key that is used to
    -- protect the job output. For more information, see
    -- <https://docs.aws.amazon.com/databrew/latest/dg/encryption-security-configuration.html Encrypting data written by DataBrew jobs>
    Job -> Maybe Text
encryptionKeyArn :: Prelude.Maybe Prelude.Text,
    -- | The encryption mode for the job, which can be one of the following:
    --
    -- -   @SSE-KMS@ - Server-side encryption with keys managed by KMS.
    --
    -- -   @SSE-S3@ - Server-side encryption with keys managed by Amazon S3.
    Job -> Maybe EncryptionMode
encryptionMode :: Prelude.Maybe EncryptionMode,
    -- | 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 value is used. The default value is
    -- CUSTOM_ROWS for the mode parameter and 20,000 for the size parameter.
    Job -> Maybe JobSample
jobSample :: Prelude.Maybe JobSample,
    -- | The Amazon Resource Name (ARN) of the user who last modified the job.
    Job -> Maybe Text
lastModifiedBy :: Prelude.Maybe Prelude.Text,
    -- | The modification date and time of the job.
    Job -> Maybe POSIX
lastModifiedDate :: Prelude.Maybe Data.POSIX,
    -- | The current status of Amazon CloudWatch logging for the job.
    Job -> Maybe LogSubscription
logSubscription :: Prelude.Maybe LogSubscription,
    -- | The maximum number of nodes that can be consumed when the job processes
    -- data.
    Job -> Maybe Int
maxCapacity :: Prelude.Maybe Prelude.Int,
    -- | The maximum number of times to retry the job after a job run fails.
    Job -> Maybe Natural
maxRetries :: Prelude.Maybe Prelude.Natural,
    -- | One or more artifacts that represent output from running the job.
    Job -> Maybe (NonEmpty Output)
outputs :: Prelude.Maybe (Prelude.NonEmpty Output),
    -- | The name of the project that the job is associated with.
    Job -> Maybe Text
projectName :: Prelude.Maybe Prelude.Text,
    -- | A set of steps that the job runs.
    Job -> Maybe RecipeReference
recipeReference :: Prelude.Maybe RecipeReference,
    -- | The unique Amazon Resource Name (ARN) for the job.
    Job -> Maybe Text
resourceArn :: Prelude.Maybe Prelude.Text,
    -- | The Amazon Resource Name (ARN) of the role to be assumed for this job.
    Job -> Maybe Text
roleArn :: Prelude.Maybe Prelude.Text,
    -- | Metadata tags that have been applied to the job.
    Job -> Maybe (HashMap Text Text)
tags :: Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text),
    -- | The job\'s timeout in minutes. A job that attempts to run longer than
    -- this timeout period ends with a status of @TIMEOUT@.
    Job -> Maybe Natural
timeout :: Prelude.Maybe Prelude.Natural,
    -- | The job type of the job, which must be one of the following:
    --
    -- -   @PROFILE@ - A job to analyze a dataset, to determine its size, data
    --     types, data distribution, and more.
    --
    -- -   @RECIPE@ - A job to apply one or more transformations to a dataset.
    Job -> Maybe JobType
type' :: Prelude.Maybe JobType,
    -- | List of validation configurations that are applied to the profile job.
    Job -> Maybe (NonEmpty ValidationConfiguration)
validationConfigurations :: Prelude.Maybe (Prelude.NonEmpty ValidationConfiguration),
    -- | The unique name of the job.
    Job -> Text
name :: Prelude.Text
  }
  deriving (Job -> Job -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Job -> Job -> Bool
$c/= :: Job -> Job -> Bool
== :: Job -> Job -> Bool
$c== :: Job -> Job -> Bool
Prelude.Eq, ReadPrec [Job]
ReadPrec Job
Int -> ReadS Job
ReadS [Job]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [Job]
$creadListPrec :: ReadPrec [Job]
readPrec :: ReadPrec Job
$creadPrec :: ReadPrec Job
readList :: ReadS [Job]
$creadList :: ReadS [Job]
readsPrec :: Int -> ReadS Job
$creadsPrec :: Int -> ReadS Job
Prelude.Read, Int -> Job -> ShowS
[Job] -> ShowS
Job -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Job] -> ShowS
$cshowList :: [Job] -> ShowS
show :: Job -> String
$cshow :: Job -> String
showsPrec :: Int -> Job -> ShowS
$cshowsPrec :: Int -> Job -> ShowS
Prelude.Show, forall x. Rep Job x -> Job
forall x. Job -> Rep Job x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Job x -> Job
$cfrom :: forall x. Job -> Rep Job x
Prelude.Generic)

-- |
-- Create a value of 'Job' 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:
--
-- 'accountId', 'job_accountId' - The ID of the Amazon Web Services account that owns the job.
--
-- 'createDate', 'job_createDate' - The date and time that the job was created.
--
-- 'createdBy', 'job_createdBy' - The Amazon Resource Name (ARN) of the user who created the job.
--
-- 'dataCatalogOutputs', 'job_dataCatalogOutputs' - One or more artifacts that represent the Glue Data Catalog output from
-- running the job.
--
-- 'databaseOutputs', 'job_databaseOutputs' - Represents a list of JDBC database output objects which defines the
-- output destination for a DataBrew recipe job to write into.
--
-- 'datasetName', 'job_datasetName' - A dataset that the job is to process.
--
-- 'encryptionKeyArn', 'job_encryptionKeyArn' - The Amazon Resource Name (ARN) of an encryption key that is used to
-- protect the job output. For more information, see
-- <https://docs.aws.amazon.com/databrew/latest/dg/encryption-security-configuration.html Encrypting data written by DataBrew jobs>
--
-- 'encryptionMode', 'job_encryptionMode' - The encryption mode for the job, which can be one of the following:
--
-- -   @SSE-KMS@ - Server-side encryption with keys managed by KMS.
--
-- -   @SSE-S3@ - Server-side encryption with keys managed by Amazon S3.
--
-- 'jobSample', 'job_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 value is used. The default value is
-- CUSTOM_ROWS for the mode parameter and 20,000 for the size parameter.
--
-- 'lastModifiedBy', 'job_lastModifiedBy' - The Amazon Resource Name (ARN) of the user who last modified the job.
--
-- 'lastModifiedDate', 'job_lastModifiedDate' - The modification date and time of the job.
--
-- 'logSubscription', 'job_logSubscription' - The current status of Amazon CloudWatch logging for the job.
--
-- 'maxCapacity', 'job_maxCapacity' - The maximum number of nodes that can be consumed when the job processes
-- data.
--
-- 'maxRetries', 'job_maxRetries' - The maximum number of times to retry the job after a job run fails.
--
-- 'outputs', 'job_outputs' - One or more artifacts that represent output from running the job.
--
-- 'projectName', 'job_projectName' - The name of the project that the job is associated with.
--
-- 'recipeReference', 'job_recipeReference' - A set of steps that the job runs.
--
-- 'resourceArn', 'job_resourceArn' - The unique Amazon Resource Name (ARN) for the job.
--
-- 'roleArn', 'job_roleArn' - The Amazon Resource Name (ARN) of the role to be assumed for this job.
--
-- 'tags', 'job_tags' - Metadata tags that have been applied to the job.
--
-- 'timeout', 'job_timeout' - The job\'s timeout in minutes. A job that attempts to run longer than
-- this timeout period ends with a status of @TIMEOUT@.
--
-- 'type'', 'job_type' - The job type of the job, which must be one of the following:
--
-- -   @PROFILE@ - A job to analyze a dataset, to determine its size, data
--     types, data distribution, and more.
--
-- -   @RECIPE@ - A job to apply one or more transformations to a dataset.
--
-- 'validationConfigurations', 'job_validationConfigurations' - List of validation configurations that are applied to the profile job.
--
-- 'name', 'job_name' - The unique name of the job.
newJob ::
  -- | 'name'
  Prelude.Text ->
  Job
newJob :: Text -> Job
newJob Text
pName_ =
  Job'
    { $sel:accountId:Job' :: Maybe Text
accountId = forall a. Maybe a
Prelude.Nothing,
      $sel:createDate:Job' :: Maybe POSIX
createDate = forall a. Maybe a
Prelude.Nothing,
      $sel:createdBy:Job' :: Maybe Text
createdBy = forall a. Maybe a
Prelude.Nothing,
      $sel:dataCatalogOutputs:Job' :: Maybe (NonEmpty DataCatalogOutput)
dataCatalogOutputs = forall a. Maybe a
Prelude.Nothing,
      $sel:databaseOutputs:Job' :: Maybe (NonEmpty DatabaseOutput)
databaseOutputs = forall a. Maybe a
Prelude.Nothing,
      $sel:datasetName:Job' :: Maybe Text
datasetName = forall a. Maybe a
Prelude.Nothing,
      $sel:encryptionKeyArn:Job' :: Maybe Text
encryptionKeyArn = forall a. Maybe a
Prelude.Nothing,
      $sel:encryptionMode:Job' :: Maybe EncryptionMode
encryptionMode = forall a. Maybe a
Prelude.Nothing,
      $sel:jobSample:Job' :: Maybe JobSample
jobSample = forall a. Maybe a
Prelude.Nothing,
      $sel:lastModifiedBy:Job' :: Maybe Text
lastModifiedBy = forall a. Maybe a
Prelude.Nothing,
      $sel:lastModifiedDate:Job' :: Maybe POSIX
lastModifiedDate = forall a. Maybe a
Prelude.Nothing,
      $sel:logSubscription:Job' :: Maybe LogSubscription
logSubscription = forall a. Maybe a
Prelude.Nothing,
      $sel:maxCapacity:Job' :: Maybe Int
maxCapacity = forall a. Maybe a
Prelude.Nothing,
      $sel:maxRetries:Job' :: Maybe Natural
maxRetries = forall a. Maybe a
Prelude.Nothing,
      $sel:outputs:Job' :: Maybe (NonEmpty Output)
outputs = forall a. Maybe a
Prelude.Nothing,
      $sel:projectName:Job' :: Maybe Text
projectName = forall a. Maybe a
Prelude.Nothing,
      $sel:recipeReference:Job' :: Maybe RecipeReference
recipeReference = forall a. Maybe a
Prelude.Nothing,
      $sel:resourceArn:Job' :: Maybe Text
resourceArn = forall a. Maybe a
Prelude.Nothing,
      $sel:roleArn:Job' :: Maybe Text
roleArn = forall a. Maybe a
Prelude.Nothing,
      $sel:tags:Job' :: Maybe (HashMap Text Text)
tags = forall a. Maybe a
Prelude.Nothing,
      $sel:timeout:Job' :: Maybe Natural
timeout = forall a. Maybe a
Prelude.Nothing,
      $sel:type':Job' :: Maybe JobType
type' = forall a. Maybe a
Prelude.Nothing,
      $sel:validationConfigurations:Job' :: Maybe (NonEmpty ValidationConfiguration)
validationConfigurations = forall a. Maybe a
Prelude.Nothing,
      $sel:name:Job' :: Text
name = Text
pName_
    }

-- | The ID of the Amazon Web Services account that owns the job.
job_accountId :: Lens.Lens' Job (Prelude.Maybe Prelude.Text)
job_accountId :: Lens' Job (Maybe Text)
job_accountId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Job' {Maybe Text
accountId :: Maybe Text
$sel:accountId:Job' :: Job -> Maybe Text
accountId} -> Maybe Text
accountId) (\s :: Job
s@Job' {} Maybe Text
a -> Job
s {$sel:accountId:Job' :: Maybe Text
accountId = Maybe Text
a} :: Job)

-- | The date and time that the job was created.
job_createDate :: Lens.Lens' Job (Prelude.Maybe Prelude.UTCTime)
job_createDate :: Lens' Job (Maybe UTCTime)
job_createDate = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Job' {Maybe POSIX
createDate :: Maybe POSIX
$sel:createDate:Job' :: Job -> Maybe POSIX
createDate} -> Maybe POSIX
createDate) (\s :: Job
s@Job' {} Maybe POSIX
a -> Job
s {$sel:createDate:Job' :: Maybe POSIX
createDate = Maybe POSIX
a} :: Job) 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 Amazon Resource Name (ARN) of the user who created the job.
job_createdBy :: Lens.Lens' Job (Prelude.Maybe Prelude.Text)
job_createdBy :: Lens' Job (Maybe Text)
job_createdBy = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Job' {Maybe Text
createdBy :: Maybe Text
$sel:createdBy:Job' :: Job -> Maybe Text
createdBy} -> Maybe Text
createdBy) (\s :: Job
s@Job' {} Maybe Text
a -> Job
s {$sel:createdBy:Job' :: Maybe Text
createdBy = Maybe Text
a} :: Job)

-- | One or more artifacts that represent the Glue Data Catalog output from
-- running the job.
job_dataCatalogOutputs :: Lens.Lens' Job (Prelude.Maybe (Prelude.NonEmpty DataCatalogOutput))
job_dataCatalogOutputs :: Lens' Job (Maybe (NonEmpty DataCatalogOutput))
job_dataCatalogOutputs = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Job' {Maybe (NonEmpty DataCatalogOutput)
dataCatalogOutputs :: Maybe (NonEmpty DataCatalogOutput)
$sel:dataCatalogOutputs:Job' :: Job -> Maybe (NonEmpty DataCatalogOutput)
dataCatalogOutputs} -> Maybe (NonEmpty DataCatalogOutput)
dataCatalogOutputs) (\s :: Job
s@Job' {} Maybe (NonEmpty DataCatalogOutput)
a -> Job
s {$sel:dataCatalogOutputs:Job' :: Maybe (NonEmpty DataCatalogOutput)
dataCatalogOutputs = Maybe (NonEmpty DataCatalogOutput)
a} :: Job) 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.
job_databaseOutputs :: Lens.Lens' Job (Prelude.Maybe (Prelude.NonEmpty DatabaseOutput))
job_databaseOutputs :: Lens' Job (Maybe (NonEmpty DatabaseOutput))
job_databaseOutputs = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Job' {Maybe (NonEmpty DatabaseOutput)
databaseOutputs :: Maybe (NonEmpty DatabaseOutput)
$sel:databaseOutputs:Job' :: Job -> Maybe (NonEmpty DatabaseOutput)
databaseOutputs} -> Maybe (NonEmpty DatabaseOutput)
databaseOutputs) (\s :: Job
s@Job' {} Maybe (NonEmpty DatabaseOutput)
a -> Job
s {$sel:databaseOutputs:Job' :: Maybe (NonEmpty DatabaseOutput)
databaseOutputs = Maybe (NonEmpty DatabaseOutput)
a} :: Job) 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

-- | A dataset that the job is to process.
job_datasetName :: Lens.Lens' Job (Prelude.Maybe Prelude.Text)
job_datasetName :: Lens' Job (Maybe Text)
job_datasetName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Job' {Maybe Text
datasetName :: Maybe Text
$sel:datasetName:Job' :: Job -> Maybe Text
datasetName} -> Maybe Text
datasetName) (\s :: Job
s@Job' {} Maybe Text
a -> Job
s {$sel:datasetName:Job' :: Maybe Text
datasetName = Maybe Text
a} :: Job)

-- | The Amazon Resource Name (ARN) of an encryption key that is used to
-- protect the job output. For more information, see
-- <https://docs.aws.amazon.com/databrew/latest/dg/encryption-security-configuration.html Encrypting data written by DataBrew jobs>
job_encryptionKeyArn :: Lens.Lens' Job (Prelude.Maybe Prelude.Text)
job_encryptionKeyArn :: Lens' Job (Maybe Text)
job_encryptionKeyArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Job' {Maybe Text
encryptionKeyArn :: Maybe Text
$sel:encryptionKeyArn:Job' :: Job -> Maybe Text
encryptionKeyArn} -> Maybe Text
encryptionKeyArn) (\s :: Job
s@Job' {} Maybe Text
a -> Job
s {$sel:encryptionKeyArn:Job' :: Maybe Text
encryptionKeyArn = Maybe Text
a} :: Job)

-- | The encryption mode for the job, which can be one of the following:
--
-- -   @SSE-KMS@ - Server-side encryption with keys managed by KMS.
--
-- -   @SSE-S3@ - Server-side encryption with keys managed by Amazon S3.
job_encryptionMode :: Lens.Lens' Job (Prelude.Maybe EncryptionMode)
job_encryptionMode :: Lens' Job (Maybe EncryptionMode)
job_encryptionMode = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Job' {Maybe EncryptionMode
encryptionMode :: Maybe EncryptionMode
$sel:encryptionMode:Job' :: Job -> Maybe EncryptionMode
encryptionMode} -> Maybe EncryptionMode
encryptionMode) (\s :: Job
s@Job' {} Maybe EncryptionMode
a -> Job
s {$sel:encryptionMode:Job' :: Maybe EncryptionMode
encryptionMode = Maybe EncryptionMode
a} :: Job)

-- | 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 value is used. The default value is
-- CUSTOM_ROWS for the mode parameter and 20,000 for the size parameter.
job_jobSample :: Lens.Lens' Job (Prelude.Maybe JobSample)
job_jobSample :: Lens' Job (Maybe JobSample)
job_jobSample = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Job' {Maybe JobSample
jobSample :: Maybe JobSample
$sel:jobSample:Job' :: Job -> Maybe JobSample
jobSample} -> Maybe JobSample
jobSample) (\s :: Job
s@Job' {} Maybe JobSample
a -> Job
s {$sel:jobSample:Job' :: Maybe JobSample
jobSample = Maybe JobSample
a} :: Job)

-- | The Amazon Resource Name (ARN) of the user who last modified the job.
job_lastModifiedBy :: Lens.Lens' Job (Prelude.Maybe Prelude.Text)
job_lastModifiedBy :: Lens' Job (Maybe Text)
job_lastModifiedBy = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Job' {Maybe Text
lastModifiedBy :: Maybe Text
$sel:lastModifiedBy:Job' :: Job -> Maybe Text
lastModifiedBy} -> Maybe Text
lastModifiedBy) (\s :: Job
s@Job' {} Maybe Text
a -> Job
s {$sel:lastModifiedBy:Job' :: Maybe Text
lastModifiedBy = Maybe Text
a} :: Job)

-- | The modification date and time of the job.
job_lastModifiedDate :: Lens.Lens' Job (Prelude.Maybe Prelude.UTCTime)
job_lastModifiedDate :: Lens' Job (Maybe UTCTime)
job_lastModifiedDate = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Job' {Maybe POSIX
lastModifiedDate :: Maybe POSIX
$sel:lastModifiedDate:Job' :: Job -> Maybe POSIX
lastModifiedDate} -> Maybe POSIX
lastModifiedDate) (\s :: Job
s@Job' {} Maybe POSIX
a -> Job
s {$sel:lastModifiedDate:Job' :: Maybe POSIX
lastModifiedDate = Maybe POSIX
a} :: Job) 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 status of Amazon CloudWatch logging for the job.
job_logSubscription :: Lens.Lens' Job (Prelude.Maybe LogSubscription)
job_logSubscription :: Lens' Job (Maybe LogSubscription)
job_logSubscription = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Job' {Maybe LogSubscription
logSubscription :: Maybe LogSubscription
$sel:logSubscription:Job' :: Job -> Maybe LogSubscription
logSubscription} -> Maybe LogSubscription
logSubscription) (\s :: Job
s@Job' {} Maybe LogSubscription
a -> Job
s {$sel:logSubscription:Job' :: Maybe LogSubscription
logSubscription = Maybe LogSubscription
a} :: Job)

-- | The maximum number of nodes that can be consumed when the job processes
-- data.
job_maxCapacity :: Lens.Lens' Job (Prelude.Maybe Prelude.Int)
job_maxCapacity :: Lens' Job (Maybe Int)
job_maxCapacity = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Job' {Maybe Int
maxCapacity :: Maybe Int
$sel:maxCapacity:Job' :: Job -> Maybe Int
maxCapacity} -> Maybe Int
maxCapacity) (\s :: Job
s@Job' {} Maybe Int
a -> Job
s {$sel:maxCapacity:Job' :: Maybe Int
maxCapacity = Maybe Int
a} :: Job)

-- | The maximum number of times to retry the job after a job run fails.
job_maxRetries :: Lens.Lens' Job (Prelude.Maybe Prelude.Natural)
job_maxRetries :: Lens' Job (Maybe Natural)
job_maxRetries = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Job' {Maybe Natural
maxRetries :: Maybe Natural
$sel:maxRetries:Job' :: Job -> Maybe Natural
maxRetries} -> Maybe Natural
maxRetries) (\s :: Job
s@Job' {} Maybe Natural
a -> Job
s {$sel:maxRetries:Job' :: Maybe Natural
maxRetries = Maybe Natural
a} :: Job)

-- | One or more artifacts that represent output from running the job.
job_outputs :: Lens.Lens' Job (Prelude.Maybe (Prelude.NonEmpty Output))
job_outputs :: Lens' Job (Maybe (NonEmpty Output))
job_outputs = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Job' {Maybe (NonEmpty Output)
outputs :: Maybe (NonEmpty Output)
$sel:outputs:Job' :: Job -> Maybe (NonEmpty Output)
outputs} -> Maybe (NonEmpty Output)
outputs) (\s :: Job
s@Job' {} Maybe (NonEmpty Output)
a -> Job
s {$sel:outputs:Job' :: Maybe (NonEmpty Output)
outputs = Maybe (NonEmpty Output)
a} :: Job) 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 project that the job is associated with.
job_projectName :: Lens.Lens' Job (Prelude.Maybe Prelude.Text)
job_projectName :: Lens' Job (Maybe Text)
job_projectName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Job' {Maybe Text
projectName :: Maybe Text
$sel:projectName:Job' :: Job -> Maybe Text
projectName} -> Maybe Text
projectName) (\s :: Job
s@Job' {} Maybe Text
a -> Job
s {$sel:projectName:Job' :: Maybe Text
projectName = Maybe Text
a} :: Job)

-- | A set of steps that the job runs.
job_recipeReference :: Lens.Lens' Job (Prelude.Maybe RecipeReference)
job_recipeReference :: Lens' Job (Maybe RecipeReference)
job_recipeReference = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Job' {Maybe RecipeReference
recipeReference :: Maybe RecipeReference
$sel:recipeReference:Job' :: Job -> Maybe RecipeReference
recipeReference} -> Maybe RecipeReference
recipeReference) (\s :: Job
s@Job' {} Maybe RecipeReference
a -> Job
s {$sel:recipeReference:Job' :: Maybe RecipeReference
recipeReference = Maybe RecipeReference
a} :: Job)

-- | The unique Amazon Resource Name (ARN) for the job.
job_resourceArn :: Lens.Lens' Job (Prelude.Maybe Prelude.Text)
job_resourceArn :: Lens' Job (Maybe Text)
job_resourceArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Job' {Maybe Text
resourceArn :: Maybe Text
$sel:resourceArn:Job' :: Job -> Maybe Text
resourceArn} -> Maybe Text
resourceArn) (\s :: Job
s@Job' {} Maybe Text
a -> Job
s {$sel:resourceArn:Job' :: Maybe Text
resourceArn = Maybe Text
a} :: Job)

-- | The Amazon Resource Name (ARN) of the role to be assumed for this job.
job_roleArn :: Lens.Lens' Job (Prelude.Maybe Prelude.Text)
job_roleArn :: Lens' Job (Maybe Text)
job_roleArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Job' {Maybe Text
roleArn :: Maybe Text
$sel:roleArn:Job' :: Job -> Maybe Text
roleArn} -> Maybe Text
roleArn) (\s :: Job
s@Job' {} Maybe Text
a -> Job
s {$sel:roleArn:Job' :: Maybe Text
roleArn = Maybe Text
a} :: Job)

-- | Metadata tags that have been applied to the job.
job_tags :: Lens.Lens' Job (Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text))
job_tags :: Lens' Job (Maybe (HashMap Text Text))
job_tags = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Job' {Maybe (HashMap Text Text)
tags :: Maybe (HashMap Text Text)
$sel:tags:Job' :: Job -> Maybe (HashMap Text Text)
tags} -> Maybe (HashMap Text Text)
tags) (\s :: Job
s@Job' {} Maybe (HashMap Text Text)
a -> Job
s {$sel:tags:Job' :: Maybe (HashMap Text Text)
tags = Maybe (HashMap Text Text)
a} :: Job) 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 job\'s timeout in minutes. A job that attempts to run longer than
-- this timeout period ends with a status of @TIMEOUT@.
job_timeout :: Lens.Lens' Job (Prelude.Maybe Prelude.Natural)
job_timeout :: Lens' Job (Maybe Natural)
job_timeout = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Job' {Maybe Natural
timeout :: Maybe Natural
$sel:timeout:Job' :: Job -> Maybe Natural
timeout} -> Maybe Natural
timeout) (\s :: Job
s@Job' {} Maybe Natural
a -> Job
s {$sel:timeout:Job' :: Maybe Natural
timeout = Maybe Natural
a} :: Job)

-- | The job type of the job, which must be one of the following:
--
-- -   @PROFILE@ - A job to analyze a dataset, to determine its size, data
--     types, data distribution, and more.
--
-- -   @RECIPE@ - A job to apply one or more transformations to a dataset.
job_type :: Lens.Lens' Job (Prelude.Maybe JobType)
job_type :: Lens' Job (Maybe JobType)
job_type = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Job' {Maybe JobType
type' :: Maybe JobType
$sel:type':Job' :: Job -> Maybe JobType
type'} -> Maybe JobType
type') (\s :: Job
s@Job' {} Maybe JobType
a -> Job
s {$sel:type':Job' :: Maybe JobType
type' = Maybe JobType
a} :: Job)

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

instance Data.FromJSON Job where
  parseJSON :: Value -> Parser Job
parseJSON =
    forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.withObject
      String
"Job"
      ( \Object
x ->
          Maybe Text
-> Maybe POSIX
-> Maybe Text
-> Maybe (NonEmpty DataCatalogOutput)
-> Maybe (NonEmpty DatabaseOutput)
-> Maybe Text
-> Maybe Text
-> Maybe EncryptionMode
-> Maybe JobSample
-> Maybe Text
-> Maybe POSIX
-> Maybe LogSubscription
-> Maybe Int
-> Maybe Natural
-> Maybe (NonEmpty Output)
-> Maybe Text
-> Maybe RecipeReference
-> Maybe Text
-> Maybe Text
-> Maybe (HashMap Text Text)
-> Maybe Natural
-> Maybe JobType
-> Maybe (NonEmpty ValidationConfiguration)
-> Text
-> Job
Job'
            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
"AccountId")
            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
"CreateDate")
            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
"CreatedBy")
            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
"EncryptionKeyArn")
            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
"EncryptionMode")
            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
"LastModifiedBy")
            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
"LastModifiedDate")
            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
"MaxCapacity")
            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
"MaxRetries")
            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
"ProjectName")
            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
"ResourceArn")
            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
"RoleArn")
            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
"Tags" forall a. Parser (Maybe a) -> a -> Parser a
Data..!= forall a. Monoid a => a
Prelude.mempty)
            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
"Timeout")
            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
"Type")
            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")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser a
Data..: Key
"Name")
      )

instance Prelude.Hashable Job where
  hashWithSalt :: Int -> Job -> Int
hashWithSalt Int
_salt Job' {Maybe Int
Maybe Natural
Maybe (NonEmpty Output)
Maybe (NonEmpty DatabaseOutput)
Maybe (NonEmpty DataCatalogOutput)
Maybe (NonEmpty ValidationConfiguration)
Maybe Text
Maybe (HashMap Text Text)
Maybe POSIX
Maybe EncryptionMode
Maybe JobType
Maybe LogSubscription
Maybe RecipeReference
Maybe JobSample
Text
name :: Text
validationConfigurations :: Maybe (NonEmpty ValidationConfiguration)
type' :: Maybe JobType
timeout :: Maybe Natural
tags :: Maybe (HashMap Text Text)
roleArn :: Maybe Text
resourceArn :: Maybe Text
recipeReference :: Maybe RecipeReference
projectName :: Maybe Text
outputs :: Maybe (NonEmpty Output)
maxRetries :: Maybe Natural
maxCapacity :: Maybe Int
logSubscription :: Maybe LogSubscription
lastModifiedDate :: Maybe POSIX
lastModifiedBy :: Maybe Text
jobSample :: Maybe JobSample
encryptionMode :: Maybe EncryptionMode
encryptionKeyArn :: Maybe Text
datasetName :: Maybe Text
databaseOutputs :: Maybe (NonEmpty DatabaseOutput)
dataCatalogOutputs :: Maybe (NonEmpty DataCatalogOutput)
createdBy :: Maybe Text
createDate :: Maybe POSIX
accountId :: Maybe Text
$sel:name:Job' :: Job -> Text
$sel:validationConfigurations:Job' :: Job -> Maybe (NonEmpty ValidationConfiguration)
$sel:type':Job' :: Job -> Maybe JobType
$sel:timeout:Job' :: Job -> Maybe Natural
$sel:tags:Job' :: Job -> Maybe (HashMap Text Text)
$sel:roleArn:Job' :: Job -> Maybe Text
$sel:resourceArn:Job' :: Job -> Maybe Text
$sel:recipeReference:Job' :: Job -> Maybe RecipeReference
$sel:projectName:Job' :: Job -> Maybe Text
$sel:outputs:Job' :: Job -> Maybe (NonEmpty Output)
$sel:maxRetries:Job' :: Job -> Maybe Natural
$sel:maxCapacity:Job' :: Job -> Maybe Int
$sel:logSubscription:Job' :: Job -> Maybe LogSubscription
$sel:lastModifiedDate:Job' :: Job -> Maybe POSIX
$sel:lastModifiedBy:Job' :: Job -> Maybe Text
$sel:jobSample:Job' :: Job -> Maybe JobSample
$sel:encryptionMode:Job' :: Job -> Maybe EncryptionMode
$sel:encryptionKeyArn:Job' :: Job -> Maybe Text
$sel:datasetName:Job' :: Job -> Maybe Text
$sel:databaseOutputs:Job' :: Job -> Maybe (NonEmpty DatabaseOutput)
$sel:dataCatalogOutputs:Job' :: Job -> Maybe (NonEmpty DataCatalogOutput)
$sel:createdBy:Job' :: Job -> Maybe Text
$sel:createDate:Job' :: Job -> Maybe POSIX
$sel:accountId:Job' :: Job -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
accountId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe POSIX
createDate
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
createdBy
      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
encryptionKeyArn
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe EncryptionMode
encryptionMode
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe JobSample
jobSample
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
lastModifiedBy
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe POSIX
lastModifiedDate
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe LogSubscription
logSubscription
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Int
maxCapacity
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Natural
maxRetries
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe (NonEmpty Output)
outputs
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
projectName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe RecipeReference
recipeReference
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
resourceArn
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
roleArn
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe (HashMap Text Text)
tags
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Natural
timeout
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe JobType
type'
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe (NonEmpty ValidationConfiguration)
validationConfigurations
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
name

instance Prelude.NFData Job where
  rnf :: Job -> ()
rnf Job' {Maybe Int
Maybe Natural
Maybe (NonEmpty Output)
Maybe (NonEmpty DatabaseOutput)
Maybe (NonEmpty DataCatalogOutput)
Maybe (NonEmpty ValidationConfiguration)
Maybe Text
Maybe (HashMap Text Text)
Maybe POSIX
Maybe EncryptionMode
Maybe JobType
Maybe LogSubscription
Maybe RecipeReference
Maybe JobSample
Text
name :: Text
validationConfigurations :: Maybe (NonEmpty ValidationConfiguration)
type' :: Maybe JobType
timeout :: Maybe Natural
tags :: Maybe (HashMap Text Text)
roleArn :: Maybe Text
resourceArn :: Maybe Text
recipeReference :: Maybe RecipeReference
projectName :: Maybe Text
outputs :: Maybe (NonEmpty Output)
maxRetries :: Maybe Natural
maxCapacity :: Maybe Int
logSubscription :: Maybe LogSubscription
lastModifiedDate :: Maybe POSIX
lastModifiedBy :: Maybe Text
jobSample :: Maybe JobSample
encryptionMode :: Maybe EncryptionMode
encryptionKeyArn :: Maybe Text
datasetName :: Maybe Text
databaseOutputs :: Maybe (NonEmpty DatabaseOutput)
dataCatalogOutputs :: Maybe (NonEmpty DataCatalogOutput)
createdBy :: Maybe Text
createDate :: Maybe POSIX
accountId :: Maybe Text
$sel:name:Job' :: Job -> Text
$sel:validationConfigurations:Job' :: Job -> Maybe (NonEmpty ValidationConfiguration)
$sel:type':Job' :: Job -> Maybe JobType
$sel:timeout:Job' :: Job -> Maybe Natural
$sel:tags:Job' :: Job -> Maybe (HashMap Text Text)
$sel:roleArn:Job' :: Job -> Maybe Text
$sel:resourceArn:Job' :: Job -> Maybe Text
$sel:recipeReference:Job' :: Job -> Maybe RecipeReference
$sel:projectName:Job' :: Job -> Maybe Text
$sel:outputs:Job' :: Job -> Maybe (NonEmpty Output)
$sel:maxRetries:Job' :: Job -> Maybe Natural
$sel:maxCapacity:Job' :: Job -> Maybe Int
$sel:logSubscription:Job' :: Job -> Maybe LogSubscription
$sel:lastModifiedDate:Job' :: Job -> Maybe POSIX
$sel:lastModifiedBy:Job' :: Job -> Maybe Text
$sel:jobSample:Job' :: Job -> Maybe JobSample
$sel:encryptionMode:Job' :: Job -> Maybe EncryptionMode
$sel:encryptionKeyArn:Job' :: Job -> Maybe Text
$sel:datasetName:Job' :: Job -> Maybe Text
$sel:databaseOutputs:Job' :: Job -> Maybe (NonEmpty DatabaseOutput)
$sel:dataCatalogOutputs:Job' :: Job -> Maybe (NonEmpty DataCatalogOutput)
$sel:createdBy:Job' :: Job -> Maybe Text
$sel:createDate:Job' :: Job -> Maybe POSIX
$sel:accountId:Job' :: Job -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
accountId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe POSIX
createDate
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
createdBy
      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
encryptionKeyArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe EncryptionMode
encryptionMode
      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
lastModifiedBy
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe POSIX
lastModifiedDate
      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 Int
maxCapacity
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Natural
maxRetries
      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 Text
projectName
      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
resourceArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
roleArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe (HashMap Text Text)
tags
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Natural
timeout
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe JobType
type'
      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 Text
name