{-# 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.JobUpdate
-- 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.JobUpdate 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 information used to update an existing job definition. The
-- previous job definition is completely overwritten by this information.
--
-- /See:/ 'newJobUpdate' smart constructor.
data JobUpdate = JobUpdate'
  { -- | This field is deprecated. Use @MaxCapacity@ instead.
    --
    -- The number of Glue data processing units (DPUs) to allocate to 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>.
    JobUpdate -> 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.
    JobUpdate
-> Maybe (Sensitive (HashMap Text CodeGenConfigurationNode))
codeGenConfigurationNodes :: Prelude.Maybe (Data.Sensitive (Prelude.HashMap Prelude.Text CodeGenConfigurationNode)),
    -- | The @JobCommand@ that runs this job (required).
    JobUpdate -> Maybe JobCommand
command :: Prelude.Maybe JobCommand,
    -- | The connections used for this job.
    JobUpdate -> Maybe ConnectionsList
connections :: Prelude.Maybe ConnectionsList,
    -- | The default arguments for this job.
    --
    -- 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.
    JobUpdate -> Maybe (HashMap Text Text)
defaultArguments :: Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text),
    -- | Description of the job being defined.
    JobUpdate -> 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.
    JobUpdate -> Maybe ExecutionClass
executionClass :: Prelude.Maybe ExecutionClass,
    -- | An @ExecutionProperty@ specifying the maximum number of concurrent runs
    -- allowed for this job.
    JobUpdate -> 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.
    JobUpdate -> Maybe Text
glueVersion :: Prelude.Maybe Prelude.Text,
    -- | This field is reserved for future use.
    JobUpdate -> 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 or an Apache Spark 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@.
    JobUpdate -> Maybe Double
maxCapacity :: Prelude.Maybe Prelude.Double,
    -- | The maximum number of times to retry this job if it fails.
    JobUpdate -> Maybe Int
maxRetries :: Prelude.Maybe Prelude.Int,
    -- | Non-overridable arguments for this job, specified as name-value pairs.
    JobUpdate -> Maybe (HashMap Text Text)
nonOverridableArguments :: Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text),
    -- | Specifies the configuration properties of a job notification.
    JobUpdate -> Maybe NotificationProperty
notificationProperty :: Prelude.Maybe NotificationProperty,
    -- | The number of workers of a defined @workerType@ that are allocated when
    -- a job runs.
    JobUpdate -> Maybe Int
numberOfWorkers :: Prelude.Maybe Prelude.Int,
    -- | The name or Amazon Resource Name (ARN) of the IAM role associated with
    -- this job (required).
    JobUpdate -> Maybe Text
role' :: Prelude.Maybe Prelude.Text,
    -- | The name of the @SecurityConfiguration@ structure to be used with this
    -- job.
    JobUpdate -> 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.
    JobUpdate -> 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).
    JobUpdate -> 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.
    JobUpdate -> Maybe WorkerType
workerType :: Prelude.Maybe WorkerType
  }
  deriving (JobUpdate -> JobUpdate -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: JobUpdate -> JobUpdate -> Bool
$c/= :: JobUpdate -> JobUpdate -> Bool
== :: JobUpdate -> JobUpdate -> Bool
$c== :: JobUpdate -> JobUpdate -> Bool
Prelude.Eq, Int -> JobUpdate -> ShowS
[JobUpdate] -> ShowS
JobUpdate -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [JobUpdate] -> ShowS
$cshowList :: [JobUpdate] -> ShowS
show :: JobUpdate -> String
$cshow :: JobUpdate -> String
showsPrec :: Int -> JobUpdate -> ShowS
$cshowsPrec :: Int -> JobUpdate -> ShowS
Prelude.Show, forall x. Rep JobUpdate x -> JobUpdate
forall x. JobUpdate -> Rep JobUpdate x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep JobUpdate x -> JobUpdate
$cfrom :: forall x. JobUpdate -> Rep JobUpdate x
Prelude.Generic)

-- |
-- Create a value of 'JobUpdate' 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', 'jobUpdate_allocatedCapacity' - This field is deprecated. Use @MaxCapacity@ instead.
--
-- The number of Glue data processing units (DPUs) to allocate to 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', 'jobUpdate_codeGenConfigurationNodes' - The representation of a directed acyclic graph on which both the Glue
-- Studio visual component and Glue Studio code generation is based.
--
-- 'command', 'jobUpdate_command' - The @JobCommand@ that runs this job (required).
--
-- 'connections', 'jobUpdate_connections' - The connections used for this job.
--
-- 'defaultArguments', 'jobUpdate_defaultArguments' - The default arguments for this job.
--
-- 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', 'jobUpdate_description' - Description of the job being defined.
--
-- 'executionClass', 'jobUpdate_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', 'jobUpdate_executionProperty' - An @ExecutionProperty@ specifying the maximum number of concurrent runs
-- allowed for this job.
--
-- 'glueVersion', 'jobUpdate_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.
--
-- 'logUri', 'jobUpdate_logUri' - This field is reserved for future use.
--
-- 'maxCapacity', 'jobUpdate_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 or an Apache Spark 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', 'jobUpdate_maxRetries' - The maximum number of times to retry this job if it fails.
--
-- 'nonOverridableArguments', 'jobUpdate_nonOverridableArguments' - Non-overridable arguments for this job, specified as name-value pairs.
--
-- 'notificationProperty', 'jobUpdate_notificationProperty' - Specifies the configuration properties of a job notification.
--
-- 'numberOfWorkers', 'jobUpdate_numberOfWorkers' - The number of workers of a defined @workerType@ that are allocated when
-- a job runs.
--
-- 'role'', 'jobUpdate_role' - The name or Amazon Resource Name (ARN) of the IAM role associated with
-- this job (required).
--
-- 'securityConfiguration', 'jobUpdate_securityConfiguration' - The name of the @SecurityConfiguration@ structure to be used with this
-- job.
--
-- 'sourceControlDetails', 'jobUpdate_sourceControlDetails' - The details for a source control configuration for a job, allowing
-- synchronization of job artifacts to or from a remote repository.
--
-- 'timeout', 'jobUpdate_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', 'jobUpdate_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.
newJobUpdate ::
  JobUpdate
newJobUpdate :: JobUpdate
newJobUpdate =
  JobUpdate'
    { $sel:allocatedCapacity:JobUpdate' :: Maybe Int
allocatedCapacity = forall a. Maybe a
Prelude.Nothing,
      $sel:codeGenConfigurationNodes:JobUpdate' :: Maybe (Sensitive (HashMap Text CodeGenConfigurationNode))
codeGenConfigurationNodes = forall a. Maybe a
Prelude.Nothing,
      $sel:command:JobUpdate' :: Maybe JobCommand
command = forall a. Maybe a
Prelude.Nothing,
      $sel:connections:JobUpdate' :: Maybe ConnectionsList
connections = forall a. Maybe a
Prelude.Nothing,
      $sel:defaultArguments:JobUpdate' :: Maybe (HashMap Text Text)
defaultArguments = forall a. Maybe a
Prelude.Nothing,
      $sel:description:JobUpdate' :: Maybe Text
description = forall a. Maybe a
Prelude.Nothing,
      $sel:executionClass:JobUpdate' :: Maybe ExecutionClass
executionClass = forall a. Maybe a
Prelude.Nothing,
      $sel:executionProperty:JobUpdate' :: Maybe ExecutionProperty
executionProperty = forall a. Maybe a
Prelude.Nothing,
      $sel:glueVersion:JobUpdate' :: Maybe Text
glueVersion = forall a. Maybe a
Prelude.Nothing,
      $sel:logUri:JobUpdate' :: Maybe Text
logUri = forall a. Maybe a
Prelude.Nothing,
      $sel:maxCapacity:JobUpdate' :: Maybe Double
maxCapacity = forall a. Maybe a
Prelude.Nothing,
      $sel:maxRetries:JobUpdate' :: Maybe Int
maxRetries = forall a. Maybe a
Prelude.Nothing,
      $sel:nonOverridableArguments:JobUpdate' :: Maybe (HashMap Text Text)
nonOverridableArguments = forall a. Maybe a
Prelude.Nothing,
      $sel:notificationProperty:JobUpdate' :: Maybe NotificationProperty
notificationProperty = forall a. Maybe a
Prelude.Nothing,
      $sel:numberOfWorkers:JobUpdate' :: Maybe Int
numberOfWorkers = forall a. Maybe a
Prelude.Nothing,
      $sel:role':JobUpdate' :: Maybe Text
role' = forall a. Maybe a
Prelude.Nothing,
      $sel:securityConfiguration:JobUpdate' :: Maybe Text
securityConfiguration = forall a. Maybe a
Prelude.Nothing,
      $sel:sourceControlDetails:JobUpdate' :: Maybe SourceControlDetails
sourceControlDetails = forall a. Maybe a
Prelude.Nothing,
      $sel:timeout:JobUpdate' :: Maybe Natural
timeout = forall a. Maybe a
Prelude.Nothing,
      $sel:workerType:JobUpdate' :: Maybe WorkerType
workerType = forall a. Maybe a
Prelude.Nothing
    }

-- | This field is deprecated. Use @MaxCapacity@ instead.
--
-- The number of Glue data processing units (DPUs) to allocate to 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>.
jobUpdate_allocatedCapacity :: Lens.Lens' JobUpdate (Prelude.Maybe Prelude.Int)
jobUpdate_allocatedCapacity :: Lens' JobUpdate (Maybe Int)
jobUpdate_allocatedCapacity = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\JobUpdate' {Maybe Int
allocatedCapacity :: Maybe Int
$sel:allocatedCapacity:JobUpdate' :: JobUpdate -> Maybe Int
allocatedCapacity} -> Maybe Int
allocatedCapacity) (\s :: JobUpdate
s@JobUpdate' {} Maybe Int
a -> JobUpdate
s {$sel:allocatedCapacity:JobUpdate' :: Maybe Int
allocatedCapacity = Maybe Int
a} :: JobUpdate)

-- | The representation of a directed acyclic graph on which both the Glue
-- Studio visual component and Glue Studio code generation is based.
jobUpdate_codeGenConfigurationNodes :: Lens.Lens' JobUpdate (Prelude.Maybe (Prelude.HashMap Prelude.Text CodeGenConfigurationNode))
jobUpdate_codeGenConfigurationNodes :: Lens' JobUpdate (Maybe (HashMap Text CodeGenConfigurationNode))
jobUpdate_codeGenConfigurationNodes = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\JobUpdate' {Maybe (Sensitive (HashMap Text CodeGenConfigurationNode))
codeGenConfigurationNodes :: Maybe (Sensitive (HashMap Text CodeGenConfigurationNode))
$sel:codeGenConfigurationNodes:JobUpdate' :: JobUpdate
-> Maybe (Sensitive (HashMap Text CodeGenConfigurationNode))
codeGenConfigurationNodes} -> Maybe (Sensitive (HashMap Text CodeGenConfigurationNode))
codeGenConfigurationNodes) (\s :: JobUpdate
s@JobUpdate' {} Maybe (Sensitive (HashMap Text CodeGenConfigurationNode))
a -> JobUpdate
s {$sel:codeGenConfigurationNodes:JobUpdate' :: Maybe (Sensitive (HashMap Text CodeGenConfigurationNode))
codeGenConfigurationNodes = Maybe (Sensitive (HashMap Text CodeGenConfigurationNode))
a} :: JobUpdate) 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 (required).
jobUpdate_command :: Lens.Lens' JobUpdate (Prelude.Maybe JobCommand)
jobUpdate_command :: Lens' JobUpdate (Maybe JobCommand)
jobUpdate_command = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\JobUpdate' {Maybe JobCommand
command :: Maybe JobCommand
$sel:command:JobUpdate' :: JobUpdate -> Maybe JobCommand
command} -> Maybe JobCommand
command) (\s :: JobUpdate
s@JobUpdate' {} Maybe JobCommand
a -> JobUpdate
s {$sel:command:JobUpdate' :: Maybe JobCommand
command = Maybe JobCommand
a} :: JobUpdate)

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

-- | The default arguments for this job.
--
-- 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.
jobUpdate_defaultArguments :: Lens.Lens' JobUpdate (Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text))
jobUpdate_defaultArguments :: Lens' JobUpdate (Maybe (HashMap Text Text))
jobUpdate_defaultArguments = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\JobUpdate' {Maybe (HashMap Text Text)
defaultArguments :: Maybe (HashMap Text Text)
$sel:defaultArguments:JobUpdate' :: JobUpdate -> Maybe (HashMap Text Text)
defaultArguments} -> Maybe (HashMap Text Text)
defaultArguments) (\s :: JobUpdate
s@JobUpdate' {} Maybe (HashMap Text Text)
a -> JobUpdate
s {$sel:defaultArguments:JobUpdate' :: Maybe (HashMap Text Text)
defaultArguments = Maybe (HashMap Text Text)
a} :: JobUpdate) 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

-- | Description of the job being defined.
jobUpdate_description :: Lens.Lens' JobUpdate (Prelude.Maybe Prelude.Text)
jobUpdate_description :: Lens' JobUpdate (Maybe Text)
jobUpdate_description = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\JobUpdate' {Maybe Text
description :: Maybe Text
$sel:description:JobUpdate' :: JobUpdate -> Maybe Text
description} -> Maybe Text
description) (\s :: JobUpdate
s@JobUpdate' {} Maybe Text
a -> JobUpdate
s {$sel:description:JobUpdate' :: Maybe Text
description = Maybe Text
a} :: JobUpdate)

-- | 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.
jobUpdate_executionClass :: Lens.Lens' JobUpdate (Prelude.Maybe ExecutionClass)
jobUpdate_executionClass :: Lens' JobUpdate (Maybe ExecutionClass)
jobUpdate_executionClass = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\JobUpdate' {Maybe ExecutionClass
executionClass :: Maybe ExecutionClass
$sel:executionClass:JobUpdate' :: JobUpdate -> Maybe ExecutionClass
executionClass} -> Maybe ExecutionClass
executionClass) (\s :: JobUpdate
s@JobUpdate' {} Maybe ExecutionClass
a -> JobUpdate
s {$sel:executionClass:JobUpdate' :: Maybe ExecutionClass
executionClass = Maybe ExecutionClass
a} :: JobUpdate)

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

-- | 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.
jobUpdate_glueVersion :: Lens.Lens' JobUpdate (Prelude.Maybe Prelude.Text)
jobUpdate_glueVersion :: Lens' JobUpdate (Maybe Text)
jobUpdate_glueVersion = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\JobUpdate' {Maybe Text
glueVersion :: Maybe Text
$sel:glueVersion:JobUpdate' :: JobUpdate -> Maybe Text
glueVersion} -> Maybe Text
glueVersion) (\s :: JobUpdate
s@JobUpdate' {} Maybe Text
a -> JobUpdate
s {$sel:glueVersion:JobUpdate' :: Maybe Text
glueVersion = Maybe Text
a} :: JobUpdate)

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

-- | 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 or an Apache Spark 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@.
jobUpdate_maxCapacity :: Lens.Lens' JobUpdate (Prelude.Maybe Prelude.Double)
jobUpdate_maxCapacity :: Lens' JobUpdate (Maybe Double)
jobUpdate_maxCapacity = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\JobUpdate' {Maybe Double
maxCapacity :: Maybe Double
$sel:maxCapacity:JobUpdate' :: JobUpdate -> Maybe Double
maxCapacity} -> Maybe Double
maxCapacity) (\s :: JobUpdate
s@JobUpdate' {} Maybe Double
a -> JobUpdate
s {$sel:maxCapacity:JobUpdate' :: Maybe Double
maxCapacity = Maybe Double
a} :: JobUpdate)

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

-- | Non-overridable arguments for this job, specified as name-value pairs.
jobUpdate_nonOverridableArguments :: Lens.Lens' JobUpdate (Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text))
jobUpdate_nonOverridableArguments :: Lens' JobUpdate (Maybe (HashMap Text Text))
jobUpdate_nonOverridableArguments = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\JobUpdate' {Maybe (HashMap Text Text)
nonOverridableArguments :: Maybe (HashMap Text Text)
$sel:nonOverridableArguments:JobUpdate' :: JobUpdate -> Maybe (HashMap Text Text)
nonOverridableArguments} -> Maybe (HashMap Text Text)
nonOverridableArguments) (\s :: JobUpdate
s@JobUpdate' {} Maybe (HashMap Text Text)
a -> JobUpdate
s {$sel:nonOverridableArguments:JobUpdate' :: Maybe (HashMap Text Text)
nonOverridableArguments = Maybe (HashMap Text Text)
a} :: JobUpdate) 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 the configuration properties of a job notification.
jobUpdate_notificationProperty :: Lens.Lens' JobUpdate (Prelude.Maybe NotificationProperty)
jobUpdate_notificationProperty :: Lens' JobUpdate (Maybe NotificationProperty)
jobUpdate_notificationProperty = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\JobUpdate' {Maybe NotificationProperty
notificationProperty :: Maybe NotificationProperty
$sel:notificationProperty:JobUpdate' :: JobUpdate -> Maybe NotificationProperty
notificationProperty} -> Maybe NotificationProperty
notificationProperty) (\s :: JobUpdate
s@JobUpdate' {} Maybe NotificationProperty
a -> JobUpdate
s {$sel:notificationProperty:JobUpdate' :: Maybe NotificationProperty
notificationProperty = Maybe NotificationProperty
a} :: JobUpdate)

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

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

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

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

-- | 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).
jobUpdate_timeout :: Lens.Lens' JobUpdate (Prelude.Maybe Prelude.Natural)
jobUpdate_timeout :: Lens' JobUpdate (Maybe Natural)
jobUpdate_timeout = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\JobUpdate' {Maybe Natural
timeout :: Maybe Natural
$sel:timeout:JobUpdate' :: JobUpdate -> Maybe Natural
timeout} -> Maybe Natural
timeout) (\s :: JobUpdate
s@JobUpdate' {} Maybe Natural
a -> JobUpdate
s {$sel:timeout:JobUpdate' :: Maybe Natural
timeout = Maybe Natural
a} :: JobUpdate)

-- | 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.
jobUpdate_workerType :: Lens.Lens' JobUpdate (Prelude.Maybe WorkerType)
jobUpdate_workerType :: Lens' JobUpdate (Maybe WorkerType)
jobUpdate_workerType = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\JobUpdate' {Maybe WorkerType
workerType :: Maybe WorkerType
$sel:workerType:JobUpdate' :: JobUpdate -> Maybe WorkerType
workerType} -> Maybe WorkerType
workerType) (\s :: JobUpdate
s@JobUpdate' {} Maybe WorkerType
a -> JobUpdate
s {$sel:workerType:JobUpdate' :: Maybe WorkerType
workerType = Maybe WorkerType
a} :: JobUpdate)

instance Prelude.Hashable JobUpdate where
  hashWithSalt :: Int -> JobUpdate -> Int
hashWithSalt Int
_salt JobUpdate' {Maybe Double
Maybe Int
Maybe Natural
Maybe Text
Maybe (HashMap Text Text)
Maybe (Sensitive (HashMap Text CodeGenConfigurationNode))
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)
maxRetries :: Maybe Int
maxCapacity :: Maybe Double
logUri :: Maybe Text
glueVersion :: Maybe Text
executionProperty :: Maybe ExecutionProperty
executionClass :: Maybe ExecutionClass
description :: Maybe Text
defaultArguments :: Maybe (HashMap Text Text)
connections :: Maybe ConnectionsList
command :: Maybe JobCommand
codeGenConfigurationNodes :: Maybe (Sensitive (HashMap Text CodeGenConfigurationNode))
allocatedCapacity :: Maybe Int
$sel:workerType:JobUpdate' :: JobUpdate -> Maybe WorkerType
$sel:timeout:JobUpdate' :: JobUpdate -> Maybe Natural
$sel:sourceControlDetails:JobUpdate' :: JobUpdate -> Maybe SourceControlDetails
$sel:securityConfiguration:JobUpdate' :: JobUpdate -> Maybe Text
$sel:role':JobUpdate' :: JobUpdate -> Maybe Text
$sel:numberOfWorkers:JobUpdate' :: JobUpdate -> Maybe Int
$sel:notificationProperty:JobUpdate' :: JobUpdate -> Maybe NotificationProperty
$sel:nonOverridableArguments:JobUpdate' :: JobUpdate -> Maybe (HashMap Text Text)
$sel:maxRetries:JobUpdate' :: JobUpdate -> Maybe Int
$sel:maxCapacity:JobUpdate' :: JobUpdate -> Maybe Double
$sel:logUri:JobUpdate' :: JobUpdate -> Maybe Text
$sel:glueVersion:JobUpdate' :: JobUpdate -> Maybe Text
$sel:executionProperty:JobUpdate' :: JobUpdate -> Maybe ExecutionProperty
$sel:executionClass:JobUpdate' :: JobUpdate -> Maybe ExecutionClass
$sel:description:JobUpdate' :: JobUpdate -> Maybe Text
$sel:defaultArguments:JobUpdate' :: JobUpdate -> Maybe (HashMap Text Text)
$sel:connections:JobUpdate' :: JobUpdate -> Maybe ConnectionsList
$sel:command:JobUpdate' :: JobUpdate -> Maybe JobCommand
$sel:codeGenConfigurationNodes:JobUpdate' :: JobUpdate
-> Maybe (Sensitive (HashMap Text CodeGenConfigurationNode))
$sel:allocatedCapacity:JobUpdate' :: JobUpdate -> 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 (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 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 (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 JobUpdate where
  rnf :: JobUpdate -> ()
rnf JobUpdate' {Maybe Double
Maybe Int
Maybe Natural
Maybe Text
Maybe (HashMap Text Text)
Maybe (Sensitive (HashMap Text CodeGenConfigurationNode))
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)
maxRetries :: Maybe Int
maxCapacity :: Maybe Double
logUri :: Maybe Text
glueVersion :: Maybe Text
executionProperty :: Maybe ExecutionProperty
executionClass :: Maybe ExecutionClass
description :: Maybe Text
defaultArguments :: Maybe (HashMap Text Text)
connections :: Maybe ConnectionsList
command :: Maybe JobCommand
codeGenConfigurationNodes :: Maybe (Sensitive (HashMap Text CodeGenConfigurationNode))
allocatedCapacity :: Maybe Int
$sel:workerType:JobUpdate' :: JobUpdate -> Maybe WorkerType
$sel:timeout:JobUpdate' :: JobUpdate -> Maybe Natural
$sel:sourceControlDetails:JobUpdate' :: JobUpdate -> Maybe SourceControlDetails
$sel:securityConfiguration:JobUpdate' :: JobUpdate -> Maybe Text
$sel:role':JobUpdate' :: JobUpdate -> Maybe Text
$sel:numberOfWorkers:JobUpdate' :: JobUpdate -> Maybe Int
$sel:notificationProperty:JobUpdate' :: JobUpdate -> Maybe NotificationProperty
$sel:nonOverridableArguments:JobUpdate' :: JobUpdate -> Maybe (HashMap Text Text)
$sel:maxRetries:JobUpdate' :: JobUpdate -> Maybe Int
$sel:maxCapacity:JobUpdate' :: JobUpdate -> Maybe Double
$sel:logUri:JobUpdate' :: JobUpdate -> Maybe Text
$sel:glueVersion:JobUpdate' :: JobUpdate -> Maybe Text
$sel:executionProperty:JobUpdate' :: JobUpdate -> Maybe ExecutionProperty
$sel:executionClass:JobUpdate' :: JobUpdate -> Maybe ExecutionClass
$sel:description:JobUpdate' :: JobUpdate -> Maybe Text
$sel:defaultArguments:JobUpdate' :: JobUpdate -> Maybe (HashMap Text Text)
$sel:connections:JobUpdate' :: JobUpdate -> Maybe ConnectionsList
$sel:command:JobUpdate' :: JobUpdate -> Maybe JobCommand
$sel:codeGenConfigurationNodes:JobUpdate' :: JobUpdate
-> Maybe (Sensitive (HashMap Text CodeGenConfigurationNode))
$sel:allocatedCapacity:JobUpdate' :: JobUpdate -> 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 (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 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 (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

instance Data.ToJSON JobUpdate where
  toJSON :: JobUpdate -> Value
toJSON JobUpdate' {Maybe Double
Maybe Int
Maybe Natural
Maybe Text
Maybe (HashMap Text Text)
Maybe (Sensitive (HashMap Text CodeGenConfigurationNode))
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)
maxRetries :: Maybe Int
maxCapacity :: Maybe Double
logUri :: Maybe Text
glueVersion :: Maybe Text
executionProperty :: Maybe ExecutionProperty
executionClass :: Maybe ExecutionClass
description :: Maybe Text
defaultArguments :: Maybe (HashMap Text Text)
connections :: Maybe ConnectionsList
command :: Maybe JobCommand
codeGenConfigurationNodes :: Maybe (Sensitive (HashMap Text CodeGenConfigurationNode))
allocatedCapacity :: Maybe Int
$sel:workerType:JobUpdate' :: JobUpdate -> Maybe WorkerType
$sel:timeout:JobUpdate' :: JobUpdate -> Maybe Natural
$sel:sourceControlDetails:JobUpdate' :: JobUpdate -> Maybe SourceControlDetails
$sel:securityConfiguration:JobUpdate' :: JobUpdate -> Maybe Text
$sel:role':JobUpdate' :: JobUpdate -> Maybe Text
$sel:numberOfWorkers:JobUpdate' :: JobUpdate -> Maybe Int
$sel:notificationProperty:JobUpdate' :: JobUpdate -> Maybe NotificationProperty
$sel:nonOverridableArguments:JobUpdate' :: JobUpdate -> Maybe (HashMap Text Text)
$sel:maxRetries:JobUpdate' :: JobUpdate -> Maybe Int
$sel:maxCapacity:JobUpdate' :: JobUpdate -> Maybe Double
$sel:logUri:JobUpdate' :: JobUpdate -> Maybe Text
$sel:glueVersion:JobUpdate' :: JobUpdate -> Maybe Text
$sel:executionProperty:JobUpdate' :: JobUpdate -> Maybe ExecutionProperty
$sel:executionClass:JobUpdate' :: JobUpdate -> Maybe ExecutionClass
$sel:description:JobUpdate' :: JobUpdate -> Maybe Text
$sel:defaultArguments:JobUpdate' :: JobUpdate -> Maybe (HashMap Text Text)
$sel:connections:JobUpdate' :: JobUpdate -> Maybe ConnectionsList
$sel:command:JobUpdate' :: JobUpdate -> Maybe JobCommand
$sel:codeGenConfigurationNodes:JobUpdate' :: JobUpdate
-> Maybe (Sensitive (HashMap Text CodeGenConfigurationNode))
$sel:allocatedCapacity:JobUpdate' :: JobUpdate -> Maybe Int
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"AllocatedCapacity" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=)
              forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Int
allocatedCapacity,
            (Key
"CodeGenConfigurationNodes" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=)
              forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Sensitive (HashMap Text CodeGenConfigurationNode))
codeGenConfigurationNodes,
            (Key
"Command" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe JobCommand
command,
            (Key
"Connections" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe ConnectionsList
connections,
            (Key
"DefaultArguments" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=)
              forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (HashMap Text Text)
defaultArguments,
            (Key
"Description" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Text
description,
            (Key
"ExecutionClass" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=)
              forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe ExecutionClass
executionClass,
            (Key
"ExecutionProperty" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=)
              forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe ExecutionProperty
executionProperty,
            (Key
"GlueVersion" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Text
glueVersion,
            (Key
"LogUri" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Text
logUri,
            (Key
"MaxCapacity" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Double
maxCapacity,
            (Key
"MaxRetries" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Int
maxRetries,
            (Key
"NonOverridableArguments" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=)
              forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (HashMap Text Text)
nonOverridableArguments,
            (Key
"NotificationProperty" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=)
              forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe NotificationProperty
notificationProperty,
            (Key
"NumberOfWorkers" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=)
              forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Int
numberOfWorkers,
            (Key
"Role" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Text
role',
            (Key
"SecurityConfiguration" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=)
              forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Text
securityConfiguration,
            (Key
"SourceControlDetails" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=)
              forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe SourceControlDetails
sourceControlDetails,
            (Key
"Timeout" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Natural
timeout,
            (Key
"WorkerType" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe WorkerType
workerType
          ]
      )