{-# 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.Glue.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.Glue.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.Glue.Types.CodeGenConfigurationNode
import Amazonka.Glue.Types.ConnectionsList
import Amazonka.Glue.Types.ExecutionClass
import Amazonka.Glue.Types.ExecutionProperty
import Amazonka.Glue.Types.JobCommand
import Amazonka.Glue.Types.NotificationProperty
import Amazonka.Glue.Types.SourceControlDetails
import Amazonka.Glue.Types.WorkerType
import qualified Amazonka.Prelude as Prelude

-- | Specifies a job definition.
--
-- /See:/ 'newJob' smart constructor.
data Job = Job'
  { -- | This field is deprecated. Use @MaxCapacity@ instead.
    --
    -- The number of Glue data processing units (DPUs) allocated to runs of
    -- this job. You can allocate a minimum of 2 DPUs; the default is 10. A DPU
    -- is a relative measure of processing power that consists of 4 vCPUs of
    -- compute capacity and 16 GB of memory. For more information, see the
    -- <https://aws.amazon.com/glue/pricing/ Glue pricing page>.
    Job -> Maybe Int
allocatedCapacity :: Prelude.Maybe Prelude.Int,
    -- | The representation of a directed acyclic graph on which both the Glue
    -- Studio visual component and Glue Studio code generation is based.
    Job -> Maybe (Sensitive (HashMap Text CodeGenConfigurationNode))
codeGenConfigurationNodes :: Prelude.Maybe (Data.Sensitive (Prelude.HashMap Prelude.Text CodeGenConfigurationNode)),
    -- | The @JobCommand@ that runs this job.
    Job -> Maybe JobCommand
command :: Prelude.Maybe JobCommand,
    -- | The connections used for this job.
    Job -> Maybe ConnectionsList
connections :: Prelude.Maybe ConnectionsList,
    -- | The time and date that this job definition was created.
    Job -> Maybe POSIX
createdOn :: Prelude.Maybe Data.POSIX,
    -- | The default arguments for this job, specified as name-value pairs.
    --
    -- You can specify arguments here that your own job-execution script
    -- consumes, as well as arguments that Glue itself consumes.
    --
    -- For information about how to specify and consume your own Job arguments,
    -- see the
    -- <https://docs.aws.amazon.com/glue/latest/dg/aws-glue-programming-python-calling.html Calling Glue APIs in Python>
    -- topic in the developer guide.
    --
    -- For information about the key-value pairs that Glue consumes to set up
    -- your job, see the
    -- <https://docs.aws.amazon.com/glue/latest/dg/aws-glue-programming-etl-glue-arguments.html Special Parameters Used by Glue>
    -- topic in the developer guide.
    Job -> Maybe (HashMap Text Text)
defaultArguments :: Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text),
    -- | A description of the job.
    Job -> Maybe Text
description :: Prelude.Maybe Prelude.Text,
    -- | Indicates whether the job is run with a standard or flexible execution
    -- class. The standard execution class is ideal for time-sensitive
    -- workloads that require fast job startup and dedicated resources.
    --
    -- The flexible execution class is appropriate for time-insensitive jobs
    -- whose start and completion times may vary.
    --
    -- Only jobs with Glue version 3.0 and above and command type @glueetl@
    -- will be allowed to set @ExecutionClass@ to @FLEX@. The flexible
    -- execution class is available for Spark jobs.
    Job -> Maybe ExecutionClass
executionClass :: Prelude.Maybe ExecutionClass,
    -- | An @ExecutionProperty@ specifying the maximum number of concurrent runs
    -- allowed for this job.
    Job -> Maybe ExecutionProperty
executionProperty :: Prelude.Maybe ExecutionProperty,
    -- | Glue version determines the versions of Apache Spark and Python that
    -- Glue supports. The Python version indicates the version supported for
    -- jobs of type Spark.
    --
    -- For more information about the available Glue versions and corresponding
    -- Spark and Python versions, see
    -- <https://docs.aws.amazon.com/glue/latest/dg/add-job.html Glue version>
    -- in the developer guide.
    --
    -- Jobs that are created without specifying a Glue version default to Glue
    -- 0.9.
    Job -> Maybe Text
glueVersion :: Prelude.Maybe Prelude.Text,
    -- | The last point in time when this job definition was modified.
    Job -> Maybe POSIX
lastModifiedOn :: Prelude.Maybe Data.POSIX,
    -- | This field is reserved for future use.
    Job -> Maybe Text
logUri :: Prelude.Maybe Prelude.Text,
    -- | For Glue version 1.0 or earlier jobs, using the standard worker type,
    -- the number of Glue data processing units (DPUs) that can be allocated
    -- when this job runs. A DPU is a relative measure of processing power that
    -- consists of 4 vCPUs of compute capacity and 16 GB of memory. For more
    -- information, see the
    -- <https://aws.amazon.com/glue/pricing/ Glue pricing page>.
    --
    -- Do not set @Max Capacity@ if using @WorkerType@ and @NumberOfWorkers@.
    --
    -- The value that can be allocated for @MaxCapacity@ depends on whether you
    -- are running a Python shell job, an Apache Spark ETL job, or an Apache
    -- Spark streaming ETL job:
    --
    -- -   When you specify a Python shell job
    --     (@JobCommand.Name@=\"pythonshell\"), you can allocate either 0.0625
    --     or 1 DPU. The default is 0.0625 DPU.
    --
    -- -   When you specify an Apache Spark ETL job
    --     (@JobCommand.Name@=\"glueetl\") or Apache Spark streaming ETL job
    --     (@JobCommand.Name@=\"gluestreaming\"), you can allocate a minimum of
    --     2 DPUs. The default is 10 DPUs. This job type cannot have a
    --     fractional DPU allocation.
    --
    -- For Glue version 2.0 jobs, you cannot instead specify a
    -- @Maximum capacity@. Instead, you should specify a @Worker type@ and the
    -- @Number of workers@.
    Job -> Maybe Double
maxCapacity :: Prelude.Maybe Prelude.Double,
    -- | The maximum number of times to retry this job after a JobRun fails.
    Job -> Maybe Int
maxRetries :: Prelude.Maybe Prelude.Int,
    -- | The name you assign to this job definition.
    Job -> Maybe Text
name :: Prelude.Maybe Prelude.Text,
    -- | Non-overridable arguments for this job, specified as name-value pairs.
    Job -> Maybe (HashMap Text Text)
nonOverridableArguments :: Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text),
    -- | Specifies configuration properties of a job notification.
    Job -> Maybe NotificationProperty
notificationProperty :: Prelude.Maybe NotificationProperty,
    -- | The number of workers of a defined @workerType@ that are allocated when
    -- a job runs.
    Job -> Maybe Int
numberOfWorkers :: Prelude.Maybe Prelude.Int,
    -- | The name or Amazon Resource Name (ARN) of the IAM role associated with
    -- this job.
    Job -> Maybe Text
role' :: Prelude.Maybe Prelude.Text,
    -- | The name of the @SecurityConfiguration@ structure to be used with this
    -- job.
    Job -> Maybe Text
securityConfiguration :: Prelude.Maybe Prelude.Text,
    -- | The details for a source control configuration for a job, allowing
    -- synchronization of job artifacts to or from a remote repository.
    Job -> Maybe SourceControlDetails
sourceControlDetails :: Prelude.Maybe SourceControlDetails,
    -- | The job timeout in minutes. This is the maximum time that a job run can
    -- consume resources before it is terminated and enters @TIMEOUT@ status.
    -- The default is 2,880 minutes (48 hours).
    Job -> Maybe Natural
timeout :: Prelude.Maybe Prelude.Natural,
    -- | The type of predefined worker that is allocated when a job runs. Accepts
    -- a value of Standard, G.1X, G.2X, or G.025X.
    --
    -- -   For the @Standard@ worker type, each worker provides 4 vCPU, 16 GB
    --     of memory and a 50GB disk, and 2 executors per worker.
    --
    -- -   For the @G.1X@ worker type, each worker maps to 1 DPU (4 vCPU, 16 GB
    --     of memory, 64 GB disk), and provides 1 executor per worker. We
    --     recommend this worker type for memory-intensive jobs.
    --
    -- -   For the @G.2X@ worker type, each worker maps to 2 DPU (8 vCPU, 32 GB
    --     of memory, 128 GB disk), and provides 1 executor per worker. We
    --     recommend this worker type for memory-intensive jobs.
    --
    -- -   For the @G.025X@ worker type, each worker maps to 0.25 DPU (2 vCPU,
    --     4 GB of memory, 64 GB disk), and provides 1 executor per worker. We
    --     recommend this worker type for low volume streaming jobs. This
    --     worker type is only available for Glue version 3.0 streaming jobs.
    Job -> Maybe WorkerType
workerType :: Prelude.Maybe WorkerType
  }
  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, 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:
--
-- 'allocatedCapacity', 'job_allocatedCapacity' - This field is deprecated. Use @MaxCapacity@ instead.
--
-- The number of Glue data processing units (DPUs) allocated to runs of
-- this job. You can allocate a minimum of 2 DPUs; the default is 10. A DPU
-- is a relative measure of processing power that consists of 4 vCPUs of
-- compute capacity and 16 GB of memory. For more information, see the
-- <https://aws.amazon.com/glue/pricing/ Glue pricing page>.
--
-- 'codeGenConfigurationNodes', 'job_codeGenConfigurationNodes' - The representation of a directed acyclic graph on which both the Glue
-- Studio visual component and Glue Studio code generation is based.
--
-- 'command', 'job_command' - The @JobCommand@ that runs this job.
--
-- 'connections', 'job_connections' - The connections used for this job.
--
-- 'createdOn', 'job_createdOn' - The time and date that this job definition was created.
--
-- 'defaultArguments', 'job_defaultArguments' - The default arguments for this job, specified as name-value pairs.
--
-- You can specify arguments here that your own job-execution script
-- consumes, as well as arguments that Glue itself consumes.
--
-- For information about how to specify and consume your own Job arguments,
-- see the
-- <https://docs.aws.amazon.com/glue/latest/dg/aws-glue-programming-python-calling.html Calling Glue APIs in Python>
-- topic in the developer guide.
--
-- For information about the key-value pairs that Glue consumes to set up
-- your job, see the
-- <https://docs.aws.amazon.com/glue/latest/dg/aws-glue-programming-etl-glue-arguments.html Special Parameters Used by Glue>
-- topic in the developer guide.
--
-- 'description', 'job_description' - A description of the job.
--
-- 'executionClass', 'job_executionClass' - Indicates whether the job is run with a standard or flexible execution
-- class. The standard execution class is ideal for time-sensitive
-- workloads that require fast job startup and dedicated resources.
--
-- The flexible execution class is appropriate for time-insensitive jobs
-- whose start and completion times may vary.
--
-- Only jobs with Glue version 3.0 and above and command type @glueetl@
-- will be allowed to set @ExecutionClass@ to @FLEX@. The flexible
-- execution class is available for Spark jobs.
--
-- 'executionProperty', 'job_executionProperty' - An @ExecutionProperty@ specifying the maximum number of concurrent runs
-- allowed for this job.
--
-- 'glueVersion', 'job_glueVersion' - Glue version determines the versions of Apache Spark and Python that
-- Glue supports. The Python version indicates the version supported for
-- jobs of type Spark.
--
-- For more information about the available Glue versions and corresponding
-- Spark and Python versions, see
-- <https://docs.aws.amazon.com/glue/latest/dg/add-job.html Glue version>
-- in the developer guide.
--
-- Jobs that are created without specifying a Glue version default to Glue
-- 0.9.
--
-- 'lastModifiedOn', 'job_lastModifiedOn' - The last point in time when this job definition was modified.
--
-- 'logUri', 'job_logUri' - This field is reserved for future use.
--
-- 'maxCapacity', 'job_maxCapacity' - For Glue version 1.0 or earlier jobs, using the standard worker type,
-- the number of Glue data processing units (DPUs) that can be allocated
-- when this job runs. A DPU is a relative measure of processing power that
-- consists of 4 vCPUs of compute capacity and 16 GB of memory. For more
-- information, see the
-- <https://aws.amazon.com/glue/pricing/ Glue pricing page>.
--
-- Do not set @Max Capacity@ if using @WorkerType@ and @NumberOfWorkers@.
--
-- The value that can be allocated for @MaxCapacity@ depends on whether you
-- are running a Python shell job, an Apache Spark ETL job, or an Apache
-- Spark streaming ETL job:
--
-- -   When you specify a Python shell job
--     (@JobCommand.Name@=\"pythonshell\"), you can allocate either 0.0625
--     or 1 DPU. The default is 0.0625 DPU.
--
-- -   When you specify an Apache Spark ETL job
--     (@JobCommand.Name@=\"glueetl\") or Apache Spark streaming ETL job
--     (@JobCommand.Name@=\"gluestreaming\"), you can allocate a minimum of
--     2 DPUs. The default is 10 DPUs. This job type cannot have a
--     fractional DPU allocation.
--
-- For Glue version 2.0 jobs, you cannot instead specify a
-- @Maximum capacity@. Instead, you should specify a @Worker type@ and the
-- @Number of workers@.
--
-- 'maxRetries', 'job_maxRetries' - The maximum number of times to retry this job after a JobRun fails.
--
-- 'name', 'job_name' - The name you assign to this job definition.
--
-- 'nonOverridableArguments', 'job_nonOverridableArguments' - Non-overridable arguments for this job, specified as name-value pairs.
--
-- 'notificationProperty', 'job_notificationProperty' - Specifies configuration properties of a job notification.
--
-- 'numberOfWorkers', 'job_numberOfWorkers' - The number of workers of a defined @workerType@ that are allocated when
-- a job runs.
--
-- 'role'', 'job_role' - The name or Amazon Resource Name (ARN) of the IAM role associated with
-- this job.
--
-- 'securityConfiguration', 'job_securityConfiguration' - The name of the @SecurityConfiguration@ structure to be used with this
-- job.
--
-- 'sourceControlDetails', 'job_sourceControlDetails' - The details for a source control configuration for a job, allowing
-- synchronization of job artifacts to or from a remote repository.
--
-- 'timeout', 'job_timeout' - The job timeout in minutes. This is the maximum time that a job run can
-- consume resources before it is terminated and enters @TIMEOUT@ status.
-- The default is 2,880 minutes (48 hours).
--
-- 'workerType', 'job_workerType' - The type of predefined worker that is allocated when a job runs. Accepts
-- a value of Standard, G.1X, G.2X, or G.025X.
--
-- -   For the @Standard@ worker type, each worker provides 4 vCPU, 16 GB
--     of memory and a 50GB disk, and 2 executors per worker.
--
-- -   For the @G.1X@ worker type, each worker maps to 1 DPU (4 vCPU, 16 GB
--     of memory, 64 GB disk), and provides 1 executor per worker. We
--     recommend this worker type for memory-intensive jobs.
--
-- -   For the @G.2X@ worker type, each worker maps to 2 DPU (8 vCPU, 32 GB
--     of memory, 128 GB disk), and provides 1 executor per worker. We
--     recommend this worker type for memory-intensive jobs.
--
-- -   For the @G.025X@ worker type, each worker maps to 0.25 DPU (2 vCPU,
--     4 GB of memory, 64 GB disk), and provides 1 executor per worker. We
--     recommend this worker type for low volume streaming jobs. This
--     worker type is only available for Glue version 3.0 streaming jobs.
newJob ::
  Job
newJob :: Job
newJob =
  Job'
    { $sel:allocatedCapacity:Job' :: Maybe Int
allocatedCapacity = forall a. Maybe a
Prelude.Nothing,
      $sel:codeGenConfigurationNodes:Job' :: Maybe (Sensitive (HashMap Text CodeGenConfigurationNode))
codeGenConfigurationNodes = forall a. Maybe a
Prelude.Nothing,
      $sel:command:Job' :: Maybe JobCommand
command = forall a. Maybe a
Prelude.Nothing,
      $sel:connections:Job' :: Maybe ConnectionsList
connections = forall a. Maybe a
Prelude.Nothing,
      $sel:createdOn:Job' :: Maybe POSIX
createdOn = forall a. Maybe a
Prelude.Nothing,
      $sel:defaultArguments:Job' :: Maybe (HashMap Text Text)
defaultArguments = forall a. Maybe a
Prelude.Nothing,
      $sel:description:Job' :: Maybe Text
description = forall a. Maybe a
Prelude.Nothing,
      $sel:executionClass:Job' :: Maybe ExecutionClass
executionClass = forall a. Maybe a
Prelude.Nothing,
      $sel:executionProperty:Job' :: Maybe ExecutionProperty
executionProperty = forall a. Maybe a
Prelude.Nothing,
      $sel:glueVersion:Job' :: Maybe Text
glueVersion = forall a. Maybe a
Prelude.Nothing,
      $sel:lastModifiedOn:Job' :: Maybe POSIX
lastModifiedOn = forall a. Maybe a
Prelude.Nothing,
      $sel:logUri:Job' :: Maybe Text
logUri = forall a. Maybe a
Prelude.Nothing,
      $sel:maxCapacity:Job' :: Maybe Double
maxCapacity = forall a. Maybe a
Prelude.Nothing,
      $sel:maxRetries:Job' :: Maybe Int
maxRetries = forall a. Maybe a
Prelude.Nothing,
      $sel:name:Job' :: Maybe Text
name = forall a. Maybe a
Prelude.Nothing,
      $sel:nonOverridableArguments:Job' :: Maybe (HashMap Text Text)
nonOverridableArguments = forall a. Maybe a
Prelude.Nothing,
      $sel:notificationProperty:Job' :: Maybe NotificationProperty
notificationProperty = forall a. Maybe a
Prelude.Nothing,
      $sel:numberOfWorkers:Job' :: Maybe Int
numberOfWorkers = forall a. Maybe a
Prelude.Nothing,
      $sel:role':Job' :: Maybe Text
role' = forall a. Maybe a
Prelude.Nothing,
      $sel:securityConfiguration:Job' :: Maybe Text
securityConfiguration = forall a. Maybe a
Prelude.Nothing,
      $sel:sourceControlDetails:Job' :: Maybe SourceControlDetails
sourceControlDetails = forall a. Maybe a
Prelude.Nothing,
      $sel:timeout:Job' :: Maybe Natural
timeout = forall a. Maybe a
Prelude.Nothing,
      $sel:workerType:Job' :: Maybe WorkerType
workerType = forall a. Maybe a
Prelude.Nothing
    }

-- | This field is deprecated. Use @MaxCapacity@ instead.
--
-- The number of Glue data processing units (DPUs) allocated to runs of
-- this job. You can allocate a minimum of 2 DPUs; the default is 10. A DPU
-- is a relative measure of processing power that consists of 4 vCPUs of
-- compute capacity and 16 GB of memory. For more information, see the
-- <https://aws.amazon.com/glue/pricing/ Glue pricing page>.
job_allocatedCapacity :: Lens.Lens' Job (Prelude.Maybe Prelude.Int)
job_allocatedCapacity :: Lens' Job (Maybe Int)
job_allocatedCapacity = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Job' {Maybe Int
allocatedCapacity :: Maybe Int
$sel:allocatedCapacity:Job' :: Job -> Maybe Int
allocatedCapacity} -> Maybe Int
allocatedCapacity) (\s :: Job
s@Job' {} Maybe Int
a -> Job
s {$sel:allocatedCapacity:Job' :: Maybe Int
allocatedCapacity = Maybe Int
a} :: Job)

-- | The representation of a directed acyclic graph on which both the Glue
-- Studio visual component and Glue Studio code generation is based.
job_codeGenConfigurationNodes :: Lens.Lens' Job (Prelude.Maybe (Prelude.HashMap Prelude.Text CodeGenConfigurationNode))
job_codeGenConfigurationNodes :: Lens' Job (Maybe (HashMap Text CodeGenConfigurationNode))
job_codeGenConfigurationNodes = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Job' {Maybe (Sensitive (HashMap Text CodeGenConfigurationNode))
codeGenConfigurationNodes :: Maybe (Sensitive (HashMap Text CodeGenConfigurationNode))
$sel:codeGenConfigurationNodes:Job' :: Job -> Maybe (Sensitive (HashMap Text CodeGenConfigurationNode))
codeGenConfigurationNodes} -> Maybe (Sensitive (HashMap Text CodeGenConfigurationNode))
codeGenConfigurationNodes) (\s :: Job
s@Job' {} Maybe (Sensitive (HashMap Text CodeGenConfigurationNode))
a -> Job
s {$sel:codeGenConfigurationNodes:Job' :: Maybe (Sensitive (HashMap Text CodeGenConfigurationNode))
codeGenConfigurationNodes = Maybe (Sensitive (HashMap Text CodeGenConfigurationNode))
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. Iso' (Sensitive a) a
Data._Sensitive forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced)

-- | The @JobCommand@ that runs this job.
job_command :: Lens.Lens' Job (Prelude.Maybe JobCommand)
job_command :: Lens' Job (Maybe JobCommand)
job_command = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Job' {Maybe JobCommand
command :: Maybe JobCommand
$sel:command:Job' :: Job -> Maybe JobCommand
command} -> Maybe JobCommand
command) (\s :: Job
s@Job' {} Maybe JobCommand
a -> Job
s {$sel:command:Job' :: Maybe JobCommand
command = Maybe JobCommand
a} :: Job)

-- | The connections used for this job.
job_connections :: Lens.Lens' Job (Prelude.Maybe ConnectionsList)
job_connections :: Lens' Job (Maybe ConnectionsList)
job_connections = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Job' {Maybe ConnectionsList
connections :: Maybe ConnectionsList
$sel:connections:Job' :: Job -> Maybe ConnectionsList
connections} -> Maybe ConnectionsList
connections) (\s :: Job
s@Job' {} Maybe ConnectionsList
a -> Job
s {$sel:connections:Job' :: Maybe ConnectionsList
connections = Maybe ConnectionsList
a} :: Job)

-- | The time and date that this job definition was created.
job_createdOn :: Lens.Lens' Job (Prelude.Maybe Prelude.UTCTime)
job_createdOn :: Lens' Job (Maybe UTCTime)
job_createdOn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Job' {Maybe POSIX
createdOn :: Maybe POSIX
$sel:createdOn:Job' :: Job -> Maybe POSIX
createdOn} -> Maybe POSIX
createdOn) (\s :: Job
s@Job' {} Maybe POSIX
a -> Job
s {$sel:createdOn:Job' :: Maybe POSIX
createdOn = 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 default arguments for this job, specified as name-value pairs.
--
-- You can specify arguments here that your own job-execution script
-- consumes, as well as arguments that Glue itself consumes.
--
-- For information about how to specify and consume your own Job arguments,
-- see the
-- <https://docs.aws.amazon.com/glue/latest/dg/aws-glue-programming-python-calling.html Calling Glue APIs in Python>
-- topic in the developer guide.
--
-- For information about the key-value pairs that Glue consumes to set up
-- your job, see the
-- <https://docs.aws.amazon.com/glue/latest/dg/aws-glue-programming-etl-glue-arguments.html Special Parameters Used by Glue>
-- topic in the developer guide.
job_defaultArguments :: Lens.Lens' Job (Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text))
job_defaultArguments :: Lens' Job (Maybe (HashMap Text Text))
job_defaultArguments = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Job' {Maybe (HashMap Text Text)
defaultArguments :: Maybe (HashMap Text Text)
$sel:defaultArguments:Job' :: Job -> Maybe (HashMap Text Text)
defaultArguments} -> Maybe (HashMap Text Text)
defaultArguments) (\s :: Job
s@Job' {} Maybe (HashMap Text Text)
a -> Job
s {$sel:defaultArguments:Job' :: Maybe (HashMap Text Text)
defaultArguments = 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

-- | A description of the job.
job_description :: Lens.Lens' Job (Prelude.Maybe Prelude.Text)
job_description :: Lens' Job (Maybe Text)
job_description = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Job' {Maybe Text
description :: Maybe Text
$sel:description:Job' :: Job -> Maybe Text
description} -> Maybe Text
description) (\s :: Job
s@Job' {} Maybe Text
a -> Job
s {$sel:description:Job' :: Maybe Text
description = Maybe Text
a} :: Job)

-- | Indicates whether the job is run with a standard or flexible execution
-- class. The standard execution class is ideal for time-sensitive
-- workloads that require fast job startup and dedicated resources.
--
-- The flexible execution class is appropriate for time-insensitive jobs
-- whose start and completion times may vary.
--
-- Only jobs with Glue version 3.0 and above and command type @glueetl@
-- will be allowed to set @ExecutionClass@ to @FLEX@. The flexible
-- execution class is available for Spark jobs.
job_executionClass :: Lens.Lens' Job (Prelude.Maybe ExecutionClass)
job_executionClass :: Lens' Job (Maybe ExecutionClass)
job_executionClass = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Job' {Maybe ExecutionClass
executionClass :: Maybe ExecutionClass
$sel:executionClass:Job' :: Job -> Maybe ExecutionClass
executionClass} -> Maybe ExecutionClass
executionClass) (\s :: Job
s@Job' {} Maybe ExecutionClass
a -> Job
s {$sel:executionClass:Job' :: Maybe ExecutionClass
executionClass = Maybe ExecutionClass
a} :: Job)

-- | An @ExecutionProperty@ specifying the maximum number of concurrent runs
-- allowed for this job.
job_executionProperty :: Lens.Lens' Job (Prelude.Maybe ExecutionProperty)
job_executionProperty :: Lens' Job (Maybe ExecutionProperty)
job_executionProperty = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Job' {Maybe ExecutionProperty
executionProperty :: Maybe ExecutionProperty
$sel:executionProperty:Job' :: Job -> Maybe ExecutionProperty
executionProperty} -> Maybe ExecutionProperty
executionProperty) (\s :: Job
s@Job' {} Maybe ExecutionProperty
a -> Job
s {$sel:executionProperty:Job' :: Maybe ExecutionProperty
executionProperty = Maybe ExecutionProperty
a} :: Job)

-- | Glue version determines the versions of Apache Spark and Python that
-- Glue supports. The Python version indicates the version supported for
-- jobs of type Spark.
--
-- For more information about the available Glue versions and corresponding
-- Spark and Python versions, see
-- <https://docs.aws.amazon.com/glue/latest/dg/add-job.html Glue version>
-- in the developer guide.
--
-- Jobs that are created without specifying a Glue version default to Glue
-- 0.9.
job_glueVersion :: Lens.Lens' Job (Prelude.Maybe Prelude.Text)
job_glueVersion :: Lens' Job (Maybe Text)
job_glueVersion = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Job' {Maybe Text
glueVersion :: Maybe Text
$sel:glueVersion:Job' :: Job -> Maybe Text
glueVersion} -> Maybe Text
glueVersion) (\s :: Job
s@Job' {} Maybe Text
a -> Job
s {$sel:glueVersion:Job' :: Maybe Text
glueVersion = Maybe Text
a} :: Job)

-- | The last point in time when this job definition was modified.
job_lastModifiedOn :: Lens.Lens' Job (Prelude.Maybe Prelude.UTCTime)
job_lastModifiedOn :: Lens' Job (Maybe UTCTime)
job_lastModifiedOn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Job' {Maybe POSIX
lastModifiedOn :: Maybe POSIX
$sel:lastModifiedOn:Job' :: Job -> Maybe POSIX
lastModifiedOn} -> Maybe POSIX
lastModifiedOn) (\s :: Job
s@Job' {} Maybe POSIX
a -> Job
s {$sel:lastModifiedOn:Job' :: Maybe POSIX
lastModifiedOn = 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

-- | This field is reserved for future use.
job_logUri :: Lens.Lens' Job (Prelude.Maybe Prelude.Text)
job_logUri :: Lens' Job (Maybe Text)
job_logUri = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Job' {Maybe Text
logUri :: Maybe Text
$sel:logUri:Job' :: Job -> Maybe Text
logUri} -> Maybe Text
logUri) (\s :: Job
s@Job' {} Maybe Text
a -> Job
s {$sel:logUri:Job' :: Maybe Text
logUri = Maybe Text
a} :: Job)

-- | For Glue version 1.0 or earlier jobs, using the standard worker type,
-- the number of Glue data processing units (DPUs) that can be allocated
-- when this job runs. A DPU is a relative measure of processing power that
-- consists of 4 vCPUs of compute capacity and 16 GB of memory. For more
-- information, see the
-- <https://aws.amazon.com/glue/pricing/ Glue pricing page>.
--
-- Do not set @Max Capacity@ if using @WorkerType@ and @NumberOfWorkers@.
--
-- The value that can be allocated for @MaxCapacity@ depends on whether you
-- are running a Python shell job, an Apache Spark ETL job, or an Apache
-- Spark streaming ETL job:
--
-- -   When you specify a Python shell job
--     (@JobCommand.Name@=\"pythonshell\"), you can allocate either 0.0625
--     or 1 DPU. The default is 0.0625 DPU.
--
-- -   When you specify an Apache Spark ETL job
--     (@JobCommand.Name@=\"glueetl\") or Apache Spark streaming ETL job
--     (@JobCommand.Name@=\"gluestreaming\"), you can allocate a minimum of
--     2 DPUs. The default is 10 DPUs. This job type cannot have a
--     fractional DPU allocation.
--
-- For Glue version 2.0 jobs, you cannot instead specify a
-- @Maximum capacity@. Instead, you should specify a @Worker type@ and the
-- @Number of workers@.
job_maxCapacity :: Lens.Lens' Job (Prelude.Maybe Prelude.Double)
job_maxCapacity :: Lens' Job (Maybe Double)
job_maxCapacity = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Job' {Maybe Double
maxCapacity :: Maybe Double
$sel:maxCapacity:Job' :: Job -> Maybe Double
maxCapacity} -> Maybe Double
maxCapacity) (\s :: Job
s@Job' {} Maybe Double
a -> Job
s {$sel:maxCapacity:Job' :: Maybe Double
maxCapacity = Maybe Double
a} :: Job)

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

-- | The name you assign to this job definition.
job_name :: Lens.Lens' Job (Prelude.Maybe Prelude.Text)
job_name :: Lens' Job (Maybe Text)
job_name = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Job' {Maybe Text
name :: Maybe Text
$sel:name:Job' :: Job -> Maybe Text
name} -> Maybe Text
name) (\s :: Job
s@Job' {} Maybe Text
a -> Job
s {$sel:name:Job' :: Maybe Text
name = Maybe Text
a} :: Job)

-- | Non-overridable arguments for this job, specified as name-value pairs.
job_nonOverridableArguments :: Lens.Lens' Job (Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text))
job_nonOverridableArguments :: Lens' Job (Maybe (HashMap Text Text))
job_nonOverridableArguments = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Job' {Maybe (HashMap Text Text)
nonOverridableArguments :: Maybe (HashMap Text Text)
$sel:nonOverridableArguments:Job' :: Job -> Maybe (HashMap Text Text)
nonOverridableArguments} -> Maybe (HashMap Text Text)
nonOverridableArguments) (\s :: Job
s@Job' {} Maybe (HashMap Text Text)
a -> Job
s {$sel:nonOverridableArguments:Job' :: Maybe (HashMap Text Text)
nonOverridableArguments = 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

-- | Specifies configuration properties of a job notification.
job_notificationProperty :: Lens.Lens' Job (Prelude.Maybe NotificationProperty)
job_notificationProperty :: Lens' Job (Maybe NotificationProperty)
job_notificationProperty = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Job' {Maybe NotificationProperty
notificationProperty :: Maybe NotificationProperty
$sel:notificationProperty:Job' :: Job -> Maybe NotificationProperty
notificationProperty} -> Maybe NotificationProperty
notificationProperty) (\s :: Job
s@Job' {} Maybe NotificationProperty
a -> Job
s {$sel:notificationProperty:Job' :: Maybe NotificationProperty
notificationProperty = Maybe NotificationProperty
a} :: Job)

-- | The number of workers of a defined @workerType@ that are allocated when
-- a job runs.
job_numberOfWorkers :: Lens.Lens' Job (Prelude.Maybe Prelude.Int)
job_numberOfWorkers :: Lens' Job (Maybe Int)
job_numberOfWorkers = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Job' {Maybe Int
numberOfWorkers :: Maybe Int
$sel:numberOfWorkers:Job' :: Job -> Maybe Int
numberOfWorkers} -> Maybe Int
numberOfWorkers) (\s :: Job
s@Job' {} Maybe Int
a -> Job
s {$sel:numberOfWorkers:Job' :: Maybe Int
numberOfWorkers = Maybe Int
a} :: Job)

-- | The name or Amazon Resource Name (ARN) of the IAM role associated with
-- this job.
job_role :: Lens.Lens' Job (Prelude.Maybe Prelude.Text)
job_role :: Lens' Job (Maybe Text)
job_role = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Job' {Maybe Text
role' :: Maybe Text
$sel:role':Job' :: Job -> Maybe Text
role'} -> Maybe Text
role') (\s :: Job
s@Job' {} Maybe Text
a -> Job
s {$sel:role':Job' :: Maybe Text
role' = Maybe Text
a} :: Job)

-- | The name of the @SecurityConfiguration@ structure to be used with this
-- job.
job_securityConfiguration :: Lens.Lens' Job (Prelude.Maybe Prelude.Text)
job_securityConfiguration :: Lens' Job (Maybe Text)
job_securityConfiguration = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Job' {Maybe Text
securityConfiguration :: Maybe Text
$sel:securityConfiguration:Job' :: Job -> Maybe Text
securityConfiguration} -> Maybe Text
securityConfiguration) (\s :: Job
s@Job' {} Maybe Text
a -> Job
s {$sel:securityConfiguration:Job' :: Maybe Text
securityConfiguration = Maybe Text
a} :: Job)

-- | The details for a source control configuration for a job, allowing
-- synchronization of job artifacts to or from a remote repository.
job_sourceControlDetails :: Lens.Lens' Job (Prelude.Maybe SourceControlDetails)
job_sourceControlDetails :: Lens' Job (Maybe SourceControlDetails)
job_sourceControlDetails = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Job' {Maybe SourceControlDetails
sourceControlDetails :: Maybe SourceControlDetails
$sel:sourceControlDetails:Job' :: Job -> Maybe SourceControlDetails
sourceControlDetails} -> Maybe SourceControlDetails
sourceControlDetails) (\s :: Job
s@Job' {} Maybe SourceControlDetails
a -> Job
s {$sel:sourceControlDetails:Job' :: Maybe SourceControlDetails
sourceControlDetails = Maybe SourceControlDetails
a} :: Job)

-- | The job timeout in minutes. This is the maximum time that a job run can
-- consume resources before it is terminated and enters @TIMEOUT@ status.
-- The default is 2,880 minutes (48 hours).
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 type of predefined worker that is allocated when a job runs. Accepts
-- a value of Standard, G.1X, G.2X, or G.025X.
--
-- -   For the @Standard@ worker type, each worker provides 4 vCPU, 16 GB
--     of memory and a 50GB disk, and 2 executors per worker.
--
-- -   For the @G.1X@ worker type, each worker maps to 1 DPU (4 vCPU, 16 GB
--     of memory, 64 GB disk), and provides 1 executor per worker. We
--     recommend this worker type for memory-intensive jobs.
--
-- -   For the @G.2X@ worker type, each worker maps to 2 DPU (8 vCPU, 32 GB
--     of memory, 128 GB disk), and provides 1 executor per worker. We
--     recommend this worker type for memory-intensive jobs.
--
-- -   For the @G.025X@ worker type, each worker maps to 0.25 DPU (2 vCPU,
--     4 GB of memory, 64 GB disk), and provides 1 executor per worker. We
--     recommend this worker type for low volume streaming jobs. This
--     worker type is only available for Glue version 3.0 streaming jobs.
job_workerType :: Lens.Lens' Job (Prelude.Maybe WorkerType)
job_workerType :: Lens' Job (Maybe WorkerType)
job_workerType = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Job' {Maybe WorkerType
workerType :: Maybe WorkerType
$sel:workerType:Job' :: Job -> Maybe WorkerType
workerType} -> Maybe WorkerType
workerType) (\s :: Job
s@Job' {} Maybe WorkerType
a -> Job
s {$sel:workerType:Job' :: Maybe WorkerType
workerType = Maybe WorkerType
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 Int
-> Maybe (Sensitive (HashMap Text CodeGenConfigurationNode))
-> Maybe JobCommand
-> Maybe ConnectionsList
-> Maybe POSIX
-> Maybe (HashMap Text Text)
-> Maybe Text
-> Maybe ExecutionClass
-> Maybe ExecutionProperty
-> Maybe Text
-> Maybe POSIX
-> Maybe Text
-> Maybe Double
-> Maybe Int
-> Maybe Text
-> Maybe (HashMap Text Text)
-> Maybe NotificationProperty
-> Maybe Int
-> Maybe Text
-> Maybe Text
-> Maybe SourceControlDetails
-> Maybe Natural
-> Maybe WorkerType
-> 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
"AllocatedCapacity")
            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
"CodeGenConfigurationNodes"
                            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
"Command")
            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
"Connections")
            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
"CreatedOn")
            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
"DefaultArguments"
                            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
"Description")
            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
"ExecutionClass")
            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
"ExecutionProperty")
            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
"GlueVersion")
            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
"LastModifiedOn")
            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
"LogUri")
            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
"Name")
            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
"NonOverridableArguments"
                            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
"NotificationProperty")
            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
"NumberOfWorkers")
            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
"Role")
            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
"SecurityConfiguration")
            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
"SourceControlDetails")
            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
"WorkerType")
      )

instance Prelude.Hashable Job where
  hashWithSalt :: Int -> Job -> Int
hashWithSalt Int
_salt Job' {Maybe Double
Maybe Int
Maybe Natural
Maybe Text
Maybe (HashMap Text Text)
Maybe (Sensitive (HashMap Text CodeGenConfigurationNode))
Maybe POSIX
Maybe ConnectionsList
Maybe ExecutionClass
Maybe ExecutionProperty
Maybe JobCommand
Maybe NotificationProperty
Maybe SourceControlDetails
Maybe WorkerType
workerType :: Maybe WorkerType
timeout :: Maybe Natural
sourceControlDetails :: Maybe SourceControlDetails
securityConfiguration :: Maybe Text
role' :: Maybe Text
numberOfWorkers :: Maybe Int
notificationProperty :: Maybe NotificationProperty
nonOverridableArguments :: Maybe (HashMap Text Text)
name :: Maybe Text
maxRetries :: Maybe Int
maxCapacity :: Maybe Double
logUri :: Maybe Text
lastModifiedOn :: Maybe POSIX
glueVersion :: Maybe Text
executionProperty :: Maybe ExecutionProperty
executionClass :: Maybe ExecutionClass
description :: Maybe Text
defaultArguments :: Maybe (HashMap Text Text)
createdOn :: Maybe POSIX
connections :: Maybe ConnectionsList
command :: Maybe JobCommand
codeGenConfigurationNodes :: Maybe (Sensitive (HashMap Text CodeGenConfigurationNode))
allocatedCapacity :: Maybe Int
$sel:workerType:Job' :: Job -> Maybe WorkerType
$sel:timeout:Job' :: Job -> Maybe Natural
$sel:sourceControlDetails:Job' :: Job -> Maybe SourceControlDetails
$sel:securityConfiguration:Job' :: Job -> Maybe Text
$sel:role':Job' :: Job -> Maybe Text
$sel:numberOfWorkers:Job' :: Job -> Maybe Int
$sel:notificationProperty:Job' :: Job -> Maybe NotificationProperty
$sel:nonOverridableArguments:Job' :: Job -> Maybe (HashMap Text Text)
$sel:name:Job' :: Job -> Maybe Text
$sel:maxRetries:Job' :: Job -> Maybe Int
$sel:maxCapacity:Job' :: Job -> Maybe Double
$sel:logUri:Job' :: Job -> Maybe Text
$sel:lastModifiedOn:Job' :: Job -> Maybe POSIX
$sel:glueVersion:Job' :: Job -> Maybe Text
$sel:executionProperty:Job' :: Job -> Maybe ExecutionProperty
$sel:executionClass:Job' :: Job -> Maybe ExecutionClass
$sel:description:Job' :: Job -> Maybe Text
$sel:defaultArguments:Job' :: Job -> Maybe (HashMap Text Text)
$sel:createdOn:Job' :: Job -> Maybe POSIX
$sel:connections:Job' :: Job -> Maybe ConnectionsList
$sel:command:Job' :: Job -> Maybe JobCommand
$sel:codeGenConfigurationNodes:Job' :: Job -> Maybe (Sensitive (HashMap Text CodeGenConfigurationNode))
$sel:allocatedCapacity:Job' :: Job -> Maybe Int
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Int
allocatedCapacity
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe (Sensitive (HashMap Text CodeGenConfigurationNode))
codeGenConfigurationNodes
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe JobCommand
command
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ConnectionsList
connections
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe POSIX
createdOn
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe (HashMap Text Text)
defaultArguments
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
description
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ExecutionClass
executionClass
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ExecutionProperty
executionProperty
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
glueVersion
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe POSIX
lastModifiedOn
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
logUri
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Double
maxCapacity
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Int
maxRetries
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
name
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe (HashMap Text Text)
nonOverridableArguments
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe NotificationProperty
notificationProperty
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Int
numberOfWorkers
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
role'
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
securityConfiguration
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe SourceControlDetails
sourceControlDetails
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Natural
timeout
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe WorkerType
workerType

instance Prelude.NFData Job where
  rnf :: Job -> ()
rnf Job' {Maybe Double
Maybe Int
Maybe Natural
Maybe Text
Maybe (HashMap Text Text)
Maybe (Sensitive (HashMap Text CodeGenConfigurationNode))
Maybe POSIX
Maybe ConnectionsList
Maybe ExecutionClass
Maybe ExecutionProperty
Maybe JobCommand
Maybe NotificationProperty
Maybe SourceControlDetails
Maybe WorkerType
workerType :: Maybe WorkerType
timeout :: Maybe Natural
sourceControlDetails :: Maybe SourceControlDetails
securityConfiguration :: Maybe Text
role' :: Maybe Text
numberOfWorkers :: Maybe Int
notificationProperty :: Maybe NotificationProperty
nonOverridableArguments :: Maybe (HashMap Text Text)
name :: Maybe Text
maxRetries :: Maybe Int
maxCapacity :: Maybe Double
logUri :: Maybe Text
lastModifiedOn :: Maybe POSIX
glueVersion :: Maybe Text
executionProperty :: Maybe ExecutionProperty
executionClass :: Maybe ExecutionClass
description :: Maybe Text
defaultArguments :: Maybe (HashMap Text Text)
createdOn :: Maybe POSIX
connections :: Maybe ConnectionsList
command :: Maybe JobCommand
codeGenConfigurationNodes :: Maybe (Sensitive (HashMap Text CodeGenConfigurationNode))
allocatedCapacity :: Maybe Int
$sel:workerType:Job' :: Job -> Maybe WorkerType
$sel:timeout:Job' :: Job -> Maybe Natural
$sel:sourceControlDetails:Job' :: Job -> Maybe SourceControlDetails
$sel:securityConfiguration:Job' :: Job -> Maybe Text
$sel:role':Job' :: Job -> Maybe Text
$sel:numberOfWorkers:Job' :: Job -> Maybe Int
$sel:notificationProperty:Job' :: Job -> Maybe NotificationProperty
$sel:nonOverridableArguments:Job' :: Job -> Maybe (HashMap Text Text)
$sel:name:Job' :: Job -> Maybe Text
$sel:maxRetries:Job' :: Job -> Maybe Int
$sel:maxCapacity:Job' :: Job -> Maybe Double
$sel:logUri:Job' :: Job -> Maybe Text
$sel:lastModifiedOn:Job' :: Job -> Maybe POSIX
$sel:glueVersion:Job' :: Job -> Maybe Text
$sel:executionProperty:Job' :: Job -> Maybe ExecutionProperty
$sel:executionClass:Job' :: Job -> Maybe ExecutionClass
$sel:description:Job' :: Job -> Maybe Text
$sel:defaultArguments:Job' :: Job -> Maybe (HashMap Text Text)
$sel:createdOn:Job' :: Job -> Maybe POSIX
$sel:connections:Job' :: Job -> Maybe ConnectionsList
$sel:command:Job' :: Job -> Maybe JobCommand
$sel:codeGenConfigurationNodes:Job' :: Job -> Maybe (Sensitive (HashMap Text CodeGenConfigurationNode))
$sel:allocatedCapacity:Job' :: Job -> Maybe Int
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Int
allocatedCapacity
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe (Sensitive (HashMap Text CodeGenConfigurationNode))
codeGenConfigurationNodes
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe JobCommand
command
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ConnectionsList
connections
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe POSIX
createdOn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe (HashMap Text Text)
defaultArguments
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
description
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ExecutionClass
executionClass
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ExecutionProperty
executionProperty
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
glueVersion
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe POSIX
lastModifiedOn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
logUri
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Double
maxCapacity
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Int
maxRetries
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
name
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe (HashMap Text Text)
nonOverridableArguments
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe NotificationProperty
notificationProperty
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Int
numberOfWorkers
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
role'
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Maybe Text
securityConfiguration
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Maybe SourceControlDetails
sourceControlDetails
      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 WorkerType
workerType