{-# 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.IoT.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.IoT.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.IoT.Types.AbortConfig
import Amazonka.IoT.Types.JobExecutionsRetryConfig
import Amazonka.IoT.Types.JobExecutionsRolloutConfig
import Amazonka.IoT.Types.JobProcessDetails
import Amazonka.IoT.Types.JobStatus
import Amazonka.IoT.Types.PresignedUrlConfig
import Amazonka.IoT.Types.SchedulingConfig
import Amazonka.IoT.Types.TargetSelection
import Amazonka.IoT.Types.TimeoutConfig
import qualified Amazonka.Prelude as Prelude

-- | The @Job@ object contains details about a job.
--
-- /See:/ 'newJob' smart constructor.
data Job = Job'
  { -- | Configuration for criteria to abort the job.
    Job -> Maybe AbortConfig
abortConfig :: Prelude.Maybe AbortConfig,
    -- | If the job was updated, describes the reason for the update.
    Job -> Maybe Text
comment :: Prelude.Maybe Prelude.Text,
    -- | The time, in seconds since the epoch, when the job was completed.
    Job -> Maybe POSIX
completedAt :: Prelude.Maybe Data.POSIX,
    -- | The time, in seconds since the epoch, when the job was created.
    Job -> Maybe POSIX
createdAt :: Prelude.Maybe Data.POSIX,
    -- | A short text description of the job.
    Job -> Maybe Text
description :: Prelude.Maybe Prelude.Text,
    -- | A key-value map that pairs the patterns that need to be replaced in a
    -- managed template job document schema. You can use the description of
    -- each key as a guidance to specify the inputs during runtime when
    -- creating a job.
    --
    -- @documentParameters@ can only be used when creating jobs from Amazon Web
    -- Services managed templates. This parameter can\'t be used with custom
    -- job templates or to create jobs from them.
    Job -> Maybe (HashMap Text Text)
documentParameters :: Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text),
    -- | Will be @true@ if the job was canceled with the optional @force@
    -- parameter set to @true@.
    Job -> Maybe Bool
forceCanceled :: Prelude.Maybe Prelude.Bool,
    -- | Indicates whether a job is concurrent. Will be true when a job is
    -- rolling out new job executions or canceling previously created
    -- executions, otherwise false.
    Job -> Maybe Bool
isConcurrent :: Prelude.Maybe Prelude.Bool,
    -- | An ARN identifying the job with format
    -- \"arn:aws:iot:region:account:job\/jobId\".
    Job -> Maybe Text
jobArn :: Prelude.Maybe Prelude.Text,
    -- | The configuration for the criteria to retry the job.
    Job -> Maybe JobExecutionsRetryConfig
jobExecutionsRetryConfig :: Prelude.Maybe JobExecutionsRetryConfig,
    -- | Allows you to create a staged rollout of a job.
    Job -> Maybe JobExecutionsRolloutConfig
jobExecutionsRolloutConfig :: Prelude.Maybe JobExecutionsRolloutConfig,
    -- | The unique identifier you assigned to this job when it was created.
    Job -> Maybe Text
jobId :: Prelude.Maybe Prelude.Text,
    -- | Details about the job process.
    Job -> Maybe JobProcessDetails
jobProcessDetails :: Prelude.Maybe JobProcessDetails,
    -- | The ARN of the job template used to create the job.
    Job -> Maybe Text
jobTemplateArn :: Prelude.Maybe Prelude.Text,
    -- | The time, in seconds since the epoch, when the job was last updated.
    Job -> Maybe POSIX
lastUpdatedAt :: Prelude.Maybe Data.POSIX,
    -- | The namespace used to indicate that a job is a customer-managed job.
    --
    -- When you specify a value for this parameter, Amazon Web Services IoT
    -- Core sends jobs notifications to MQTT topics that contain the value in
    -- the following format.
    --
    -- @$aws\/things\/@/@THING_NAME@/@\/jobs\/@/@JOB_ID@/@\/notify-namespace-@/@NAMESPACE_ID@/@\/@
    --
    -- The @namespaceId@ feature is in public preview.
    Job -> Maybe Text
namespaceId :: Prelude.Maybe Prelude.Text,
    -- | Configuration for pre-signed S3 URLs.
    Job -> Maybe PresignedUrlConfig
presignedUrlConfig :: Prelude.Maybe PresignedUrlConfig,
    -- | If the job was updated, provides the reason code for the update.
    Job -> Maybe Text
reasonCode :: Prelude.Maybe Prelude.Text,
    -- | The configuration that allows you to schedule a job for a future date
    -- and time in addition to specifying the end behavior for each job
    -- execution.
    Job -> Maybe SchedulingConfig
schedulingConfig :: Prelude.Maybe SchedulingConfig,
    -- | The status of the job, one of @IN_PROGRESS@, @CANCELED@,
    -- @DELETION_IN_PROGRESS@ or @COMPLETED@.
    Job -> Maybe JobStatus
status :: Prelude.Maybe JobStatus,
    -- | Specifies whether the job will continue to run (CONTINUOUS), or will be
    -- complete after all those things specified as targets have completed the
    -- job (SNAPSHOT). If continuous, the job may also be run on a thing when a
    -- change is detected in a target. For example, a job will run on a device
    -- when the thing representing the device is added to a target group, even
    -- after the job was completed by all things originally in the group.
    --
    -- We recommend that you use continuous jobs instead of snapshot jobs for
    -- dynamic thing group targets. By using continuous jobs, devices that join
    -- the group receive the job execution even after the job has been created.
    Job -> Maybe TargetSelection
targetSelection :: Prelude.Maybe TargetSelection,
    -- | A list of IoT things and thing groups to which the job should be sent.
    Job -> Maybe (NonEmpty Text)
targets :: Prelude.Maybe (Prelude.NonEmpty Prelude.Text),
    -- | Specifies the amount of time each device has to finish its execution of
    -- the job. A timer is started when the job execution status is set to
    -- @IN_PROGRESS@. If the job execution status is not set to another
    -- terminal state before the timer expires, it will be automatically set to
    -- @TIMED_OUT@.
    Job -> Maybe TimeoutConfig
timeoutConfig :: Prelude.Maybe TimeoutConfig
  }
  deriving (Job -> Job -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Job -> Job -> Bool
$c/= :: Job -> Job -> Bool
== :: Job -> Job -> Bool
$c== :: Job -> Job -> Bool
Prelude.Eq, ReadPrec [Job]
ReadPrec Job
Int -> ReadS Job
ReadS [Job]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [Job]
$creadListPrec :: ReadPrec [Job]
readPrec :: ReadPrec Job
$creadPrec :: ReadPrec Job
readList :: ReadS [Job]
$creadList :: ReadS [Job]
readsPrec :: Int -> ReadS Job
$creadsPrec :: Int -> ReadS Job
Prelude.Read, Int -> Job -> ShowS
[Job] -> ShowS
Job -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Job] -> ShowS
$cshowList :: [Job] -> ShowS
show :: Job -> String
$cshow :: Job -> String
showsPrec :: Int -> Job -> ShowS
$cshowsPrec :: Int -> Job -> ShowS
Prelude.Show, forall x. Rep Job x -> Job
forall x. Job -> Rep Job x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Job x -> Job
$cfrom :: forall x. Job -> Rep Job x
Prelude.Generic)

-- |
-- Create a value of 'Job' with all optional fields omitted.
--
-- Use <https://hackage.haskell.org/package/generic-lens generic-lens> or <https://hackage.haskell.org/package/optics optics> to modify other optional fields.
--
-- The following record fields are available, with the corresponding lenses provided
-- for backwards compatibility:
--
-- 'abortConfig', 'job_abortConfig' - Configuration for criteria to abort the job.
--
-- 'comment', 'job_comment' - If the job was updated, describes the reason for the update.
--
-- 'completedAt', 'job_completedAt' - The time, in seconds since the epoch, when the job was completed.
--
-- 'createdAt', 'job_createdAt' - The time, in seconds since the epoch, when the job was created.
--
-- 'description', 'job_description' - A short text description of the job.
--
-- 'documentParameters', 'job_documentParameters' - A key-value map that pairs the patterns that need to be replaced in a
-- managed template job document schema. You can use the description of
-- each key as a guidance to specify the inputs during runtime when
-- creating a job.
--
-- @documentParameters@ can only be used when creating jobs from Amazon Web
-- Services managed templates. This parameter can\'t be used with custom
-- job templates or to create jobs from them.
--
-- 'forceCanceled', 'job_forceCanceled' - Will be @true@ if the job was canceled with the optional @force@
-- parameter set to @true@.
--
-- 'isConcurrent', 'job_isConcurrent' - Indicates whether a job is concurrent. Will be true when a job is
-- rolling out new job executions or canceling previously created
-- executions, otherwise false.
--
-- 'jobArn', 'job_jobArn' - An ARN identifying the job with format
-- \"arn:aws:iot:region:account:job\/jobId\".
--
-- 'jobExecutionsRetryConfig', 'job_jobExecutionsRetryConfig' - The configuration for the criteria to retry the job.
--
-- 'jobExecutionsRolloutConfig', 'job_jobExecutionsRolloutConfig' - Allows you to create a staged rollout of a job.
--
-- 'jobId', 'job_jobId' - The unique identifier you assigned to this job when it was created.
--
-- 'jobProcessDetails', 'job_jobProcessDetails' - Details about the job process.
--
-- 'jobTemplateArn', 'job_jobTemplateArn' - The ARN of the job template used to create the job.
--
-- 'lastUpdatedAt', 'job_lastUpdatedAt' - The time, in seconds since the epoch, when the job was last updated.
--
-- 'namespaceId', 'job_namespaceId' - The namespace used to indicate that a job is a customer-managed job.
--
-- When you specify a value for this parameter, Amazon Web Services IoT
-- Core sends jobs notifications to MQTT topics that contain the value in
-- the following format.
--
-- @$aws\/things\/@/@THING_NAME@/@\/jobs\/@/@JOB_ID@/@\/notify-namespace-@/@NAMESPACE_ID@/@\/@
--
-- The @namespaceId@ feature is in public preview.
--
-- 'presignedUrlConfig', 'job_presignedUrlConfig' - Configuration for pre-signed S3 URLs.
--
-- 'reasonCode', 'job_reasonCode' - If the job was updated, provides the reason code for the update.
--
-- 'schedulingConfig', 'job_schedulingConfig' - The configuration that allows you to schedule a job for a future date
-- and time in addition to specifying the end behavior for each job
-- execution.
--
-- 'status', 'job_status' - The status of the job, one of @IN_PROGRESS@, @CANCELED@,
-- @DELETION_IN_PROGRESS@ or @COMPLETED@.
--
-- 'targetSelection', 'job_targetSelection' - Specifies whether the job will continue to run (CONTINUOUS), or will be
-- complete after all those things specified as targets have completed the
-- job (SNAPSHOT). If continuous, the job may also be run on a thing when a
-- change is detected in a target. For example, a job will run on a device
-- when the thing representing the device is added to a target group, even
-- after the job was completed by all things originally in the group.
--
-- We recommend that you use continuous jobs instead of snapshot jobs for
-- dynamic thing group targets. By using continuous jobs, devices that join
-- the group receive the job execution even after the job has been created.
--
-- 'targets', 'job_targets' - A list of IoT things and thing groups to which the job should be sent.
--
-- 'timeoutConfig', 'job_timeoutConfig' - Specifies the amount of time each device has to finish its execution of
-- the job. A timer is started when the job execution status is set to
-- @IN_PROGRESS@. If the job execution status is not set to another
-- terminal state before the timer expires, it will be automatically set to
-- @TIMED_OUT@.
newJob ::
  Job
newJob :: Job
newJob =
  Job'
    { $sel:abortConfig:Job' :: Maybe AbortConfig
abortConfig = forall a. Maybe a
Prelude.Nothing,
      $sel:comment:Job' :: Maybe Text
comment = forall a. Maybe a
Prelude.Nothing,
      $sel:completedAt:Job' :: Maybe POSIX
completedAt = forall a. Maybe a
Prelude.Nothing,
      $sel:createdAt:Job' :: Maybe POSIX
createdAt = forall a. Maybe a
Prelude.Nothing,
      $sel:description:Job' :: Maybe Text
description = forall a. Maybe a
Prelude.Nothing,
      $sel:documentParameters:Job' :: Maybe (HashMap Text Text)
documentParameters = forall a. Maybe a
Prelude.Nothing,
      $sel:forceCanceled:Job' :: Maybe Bool
forceCanceled = forall a. Maybe a
Prelude.Nothing,
      $sel:isConcurrent:Job' :: Maybe Bool
isConcurrent = forall a. Maybe a
Prelude.Nothing,
      $sel:jobArn:Job' :: Maybe Text
jobArn = forall a. Maybe a
Prelude.Nothing,
      $sel:jobExecutionsRetryConfig:Job' :: Maybe JobExecutionsRetryConfig
jobExecutionsRetryConfig = forall a. Maybe a
Prelude.Nothing,
      $sel:jobExecutionsRolloutConfig:Job' :: Maybe JobExecutionsRolloutConfig
jobExecutionsRolloutConfig = forall a. Maybe a
Prelude.Nothing,
      $sel:jobId:Job' :: Maybe Text
jobId = forall a. Maybe a
Prelude.Nothing,
      $sel:jobProcessDetails:Job' :: Maybe JobProcessDetails
jobProcessDetails = forall a. Maybe a
Prelude.Nothing,
      $sel:jobTemplateArn:Job' :: Maybe Text
jobTemplateArn = forall a. Maybe a
Prelude.Nothing,
      $sel:lastUpdatedAt:Job' :: Maybe POSIX
lastUpdatedAt = forall a. Maybe a
Prelude.Nothing,
      $sel:namespaceId:Job' :: Maybe Text
namespaceId = forall a. Maybe a
Prelude.Nothing,
      $sel:presignedUrlConfig:Job' :: Maybe PresignedUrlConfig
presignedUrlConfig = forall a. Maybe a
Prelude.Nothing,
      $sel:reasonCode:Job' :: Maybe Text
reasonCode = forall a. Maybe a
Prelude.Nothing,
      $sel:schedulingConfig:Job' :: Maybe SchedulingConfig
schedulingConfig = forall a. Maybe a
Prelude.Nothing,
      $sel:status:Job' :: Maybe JobStatus
status = forall a. Maybe a
Prelude.Nothing,
      $sel:targetSelection:Job' :: Maybe TargetSelection
targetSelection = forall a. Maybe a
Prelude.Nothing,
      $sel:targets:Job' :: Maybe (NonEmpty Text)
targets = forall a. Maybe a
Prelude.Nothing,
      $sel:timeoutConfig:Job' :: Maybe TimeoutConfig
timeoutConfig = forall a. Maybe a
Prelude.Nothing
    }

-- | Configuration for criteria to abort the job.
job_abortConfig :: Lens.Lens' Job (Prelude.Maybe AbortConfig)
job_abortConfig :: Lens' Job (Maybe AbortConfig)
job_abortConfig = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Job' {Maybe AbortConfig
abortConfig :: Maybe AbortConfig
$sel:abortConfig:Job' :: Job -> Maybe AbortConfig
abortConfig} -> Maybe AbortConfig
abortConfig) (\s :: Job
s@Job' {} Maybe AbortConfig
a -> Job
s {$sel:abortConfig:Job' :: Maybe AbortConfig
abortConfig = Maybe AbortConfig
a} :: Job)

-- | If the job was updated, describes the reason for the update.
job_comment :: Lens.Lens' Job (Prelude.Maybe Prelude.Text)
job_comment :: Lens' Job (Maybe Text)
job_comment = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Job' {Maybe Text
comment :: Maybe Text
$sel:comment:Job' :: Job -> Maybe Text
comment} -> Maybe Text
comment) (\s :: Job
s@Job' {} Maybe Text
a -> Job
s {$sel:comment:Job' :: Maybe Text
comment = Maybe Text
a} :: Job)

-- | The time, in seconds since the epoch, when the job was completed.
job_completedAt :: Lens.Lens' Job (Prelude.Maybe Prelude.UTCTime)
job_completedAt :: Lens' Job (Maybe UTCTime)
job_completedAt = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Job' {Maybe POSIX
completedAt :: Maybe POSIX
$sel:completedAt:Job' :: Job -> Maybe POSIX
completedAt} -> Maybe POSIX
completedAt) (\s :: Job
s@Job' {} Maybe POSIX
a -> Job
s {$sel:completedAt:Job' :: Maybe POSIX
completedAt = 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 time, in seconds since the epoch, when the job was created.
job_createdAt :: Lens.Lens' Job (Prelude.Maybe Prelude.UTCTime)
job_createdAt :: Lens' Job (Maybe UTCTime)
job_createdAt = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Job' {Maybe POSIX
createdAt :: Maybe POSIX
$sel:createdAt:Job' :: Job -> Maybe POSIX
createdAt} -> Maybe POSIX
createdAt) (\s :: Job
s@Job' {} Maybe POSIX
a -> Job
s {$sel:createdAt:Job' :: Maybe POSIX
createdAt = 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

-- | A short text 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)

-- | A key-value map that pairs the patterns that need to be replaced in a
-- managed template job document schema. You can use the description of
-- each key as a guidance to specify the inputs during runtime when
-- creating a job.
--
-- @documentParameters@ can only be used when creating jobs from Amazon Web
-- Services managed templates. This parameter can\'t be used with custom
-- job templates or to create jobs from them.
job_documentParameters :: Lens.Lens' Job (Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text))
job_documentParameters :: Lens' Job (Maybe (HashMap Text Text))
job_documentParameters = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Job' {Maybe (HashMap Text Text)
documentParameters :: Maybe (HashMap Text Text)
$sel:documentParameters:Job' :: Job -> Maybe (HashMap Text Text)
documentParameters} -> Maybe (HashMap Text Text)
documentParameters) (\s :: Job
s@Job' {} Maybe (HashMap Text Text)
a -> Job
s {$sel:documentParameters:Job' :: Maybe (HashMap Text Text)
documentParameters = 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

-- | Will be @true@ if the job was canceled with the optional @force@
-- parameter set to @true@.
job_forceCanceled :: Lens.Lens' Job (Prelude.Maybe Prelude.Bool)
job_forceCanceled :: Lens' Job (Maybe Bool)
job_forceCanceled = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Job' {Maybe Bool
forceCanceled :: Maybe Bool
$sel:forceCanceled:Job' :: Job -> Maybe Bool
forceCanceled} -> Maybe Bool
forceCanceled) (\s :: Job
s@Job' {} Maybe Bool
a -> Job
s {$sel:forceCanceled:Job' :: Maybe Bool
forceCanceled = Maybe Bool
a} :: Job)

-- | Indicates whether a job is concurrent. Will be true when a job is
-- rolling out new job executions or canceling previously created
-- executions, otherwise false.
job_isConcurrent :: Lens.Lens' Job (Prelude.Maybe Prelude.Bool)
job_isConcurrent :: Lens' Job (Maybe Bool)
job_isConcurrent = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Job' {Maybe Bool
isConcurrent :: Maybe Bool
$sel:isConcurrent:Job' :: Job -> Maybe Bool
isConcurrent} -> Maybe Bool
isConcurrent) (\s :: Job
s@Job' {} Maybe Bool
a -> Job
s {$sel:isConcurrent:Job' :: Maybe Bool
isConcurrent = Maybe Bool
a} :: Job)

-- | An ARN identifying the job with format
-- \"arn:aws:iot:region:account:job\/jobId\".
job_jobArn :: Lens.Lens' Job (Prelude.Maybe Prelude.Text)
job_jobArn :: Lens' Job (Maybe Text)
job_jobArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Job' {Maybe Text
jobArn :: Maybe Text
$sel:jobArn:Job' :: Job -> Maybe Text
jobArn} -> Maybe Text
jobArn) (\s :: Job
s@Job' {} Maybe Text
a -> Job
s {$sel:jobArn:Job' :: Maybe Text
jobArn = Maybe Text
a} :: Job)

-- | The configuration for the criteria to retry the job.
job_jobExecutionsRetryConfig :: Lens.Lens' Job (Prelude.Maybe JobExecutionsRetryConfig)
job_jobExecutionsRetryConfig :: Lens' Job (Maybe JobExecutionsRetryConfig)
job_jobExecutionsRetryConfig = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Job' {Maybe JobExecutionsRetryConfig
jobExecutionsRetryConfig :: Maybe JobExecutionsRetryConfig
$sel:jobExecutionsRetryConfig:Job' :: Job -> Maybe JobExecutionsRetryConfig
jobExecutionsRetryConfig} -> Maybe JobExecutionsRetryConfig
jobExecutionsRetryConfig) (\s :: Job
s@Job' {} Maybe JobExecutionsRetryConfig
a -> Job
s {$sel:jobExecutionsRetryConfig:Job' :: Maybe JobExecutionsRetryConfig
jobExecutionsRetryConfig = Maybe JobExecutionsRetryConfig
a} :: Job)

-- | Allows you to create a staged rollout of a job.
job_jobExecutionsRolloutConfig :: Lens.Lens' Job (Prelude.Maybe JobExecutionsRolloutConfig)
job_jobExecutionsRolloutConfig :: Lens' Job (Maybe JobExecutionsRolloutConfig)
job_jobExecutionsRolloutConfig = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Job' {Maybe JobExecutionsRolloutConfig
jobExecutionsRolloutConfig :: Maybe JobExecutionsRolloutConfig
$sel:jobExecutionsRolloutConfig:Job' :: Job -> Maybe JobExecutionsRolloutConfig
jobExecutionsRolloutConfig} -> Maybe JobExecutionsRolloutConfig
jobExecutionsRolloutConfig) (\s :: Job
s@Job' {} Maybe JobExecutionsRolloutConfig
a -> Job
s {$sel:jobExecutionsRolloutConfig:Job' :: Maybe JobExecutionsRolloutConfig
jobExecutionsRolloutConfig = Maybe JobExecutionsRolloutConfig
a} :: Job)

-- | The unique identifier you assigned to this job when it was created.
job_jobId :: Lens.Lens' Job (Prelude.Maybe Prelude.Text)
job_jobId :: Lens' Job (Maybe Text)
job_jobId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Job' {Maybe Text
jobId :: Maybe Text
$sel:jobId:Job' :: Job -> Maybe Text
jobId} -> Maybe Text
jobId) (\s :: Job
s@Job' {} Maybe Text
a -> Job
s {$sel:jobId:Job' :: Maybe Text
jobId = Maybe Text
a} :: Job)

-- | Details about the job process.
job_jobProcessDetails :: Lens.Lens' Job (Prelude.Maybe JobProcessDetails)
job_jobProcessDetails :: Lens' Job (Maybe JobProcessDetails)
job_jobProcessDetails = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Job' {Maybe JobProcessDetails
jobProcessDetails :: Maybe JobProcessDetails
$sel:jobProcessDetails:Job' :: Job -> Maybe JobProcessDetails
jobProcessDetails} -> Maybe JobProcessDetails
jobProcessDetails) (\s :: Job
s@Job' {} Maybe JobProcessDetails
a -> Job
s {$sel:jobProcessDetails:Job' :: Maybe JobProcessDetails
jobProcessDetails = Maybe JobProcessDetails
a} :: Job)

-- | The ARN of the job template used to create the job.
job_jobTemplateArn :: Lens.Lens' Job (Prelude.Maybe Prelude.Text)
job_jobTemplateArn :: Lens' Job (Maybe Text)
job_jobTemplateArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Job' {Maybe Text
jobTemplateArn :: Maybe Text
$sel:jobTemplateArn:Job' :: Job -> Maybe Text
jobTemplateArn} -> Maybe Text
jobTemplateArn) (\s :: Job
s@Job' {} Maybe Text
a -> Job
s {$sel:jobTemplateArn:Job' :: Maybe Text
jobTemplateArn = Maybe Text
a} :: Job)

-- | The time, in seconds since the epoch, when the job was last updated.
job_lastUpdatedAt :: Lens.Lens' Job (Prelude.Maybe Prelude.UTCTime)
job_lastUpdatedAt :: Lens' Job (Maybe UTCTime)
job_lastUpdatedAt = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Job' {Maybe POSIX
lastUpdatedAt :: Maybe POSIX
$sel:lastUpdatedAt:Job' :: Job -> Maybe POSIX
lastUpdatedAt} -> Maybe POSIX
lastUpdatedAt) (\s :: Job
s@Job' {} Maybe POSIX
a -> Job
s {$sel:lastUpdatedAt:Job' :: Maybe POSIX
lastUpdatedAt = 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 namespace used to indicate that a job is a customer-managed job.
--
-- When you specify a value for this parameter, Amazon Web Services IoT
-- Core sends jobs notifications to MQTT topics that contain the value in
-- the following format.
--
-- @$aws\/things\/@/@THING_NAME@/@\/jobs\/@/@JOB_ID@/@\/notify-namespace-@/@NAMESPACE_ID@/@\/@
--
-- The @namespaceId@ feature is in public preview.
job_namespaceId :: Lens.Lens' Job (Prelude.Maybe Prelude.Text)
job_namespaceId :: Lens' Job (Maybe Text)
job_namespaceId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Job' {Maybe Text
namespaceId :: Maybe Text
$sel:namespaceId:Job' :: Job -> Maybe Text
namespaceId} -> Maybe Text
namespaceId) (\s :: Job
s@Job' {} Maybe Text
a -> Job
s {$sel:namespaceId:Job' :: Maybe Text
namespaceId = Maybe Text
a} :: Job)

-- | Configuration for pre-signed S3 URLs.
job_presignedUrlConfig :: Lens.Lens' Job (Prelude.Maybe PresignedUrlConfig)
job_presignedUrlConfig :: Lens' Job (Maybe PresignedUrlConfig)
job_presignedUrlConfig = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Job' {Maybe PresignedUrlConfig
presignedUrlConfig :: Maybe PresignedUrlConfig
$sel:presignedUrlConfig:Job' :: Job -> Maybe PresignedUrlConfig
presignedUrlConfig} -> Maybe PresignedUrlConfig
presignedUrlConfig) (\s :: Job
s@Job' {} Maybe PresignedUrlConfig
a -> Job
s {$sel:presignedUrlConfig:Job' :: Maybe PresignedUrlConfig
presignedUrlConfig = Maybe PresignedUrlConfig
a} :: Job)

-- | If the job was updated, provides the reason code for the update.
job_reasonCode :: Lens.Lens' Job (Prelude.Maybe Prelude.Text)
job_reasonCode :: Lens' Job (Maybe Text)
job_reasonCode = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Job' {Maybe Text
reasonCode :: Maybe Text
$sel:reasonCode:Job' :: Job -> Maybe Text
reasonCode} -> Maybe Text
reasonCode) (\s :: Job
s@Job' {} Maybe Text
a -> Job
s {$sel:reasonCode:Job' :: Maybe Text
reasonCode = Maybe Text
a} :: Job)

-- | The configuration that allows you to schedule a job for a future date
-- and time in addition to specifying the end behavior for each job
-- execution.
job_schedulingConfig :: Lens.Lens' Job (Prelude.Maybe SchedulingConfig)
job_schedulingConfig :: Lens' Job (Maybe SchedulingConfig)
job_schedulingConfig = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Job' {Maybe SchedulingConfig
schedulingConfig :: Maybe SchedulingConfig
$sel:schedulingConfig:Job' :: Job -> Maybe SchedulingConfig
schedulingConfig} -> Maybe SchedulingConfig
schedulingConfig) (\s :: Job
s@Job' {} Maybe SchedulingConfig
a -> Job
s {$sel:schedulingConfig:Job' :: Maybe SchedulingConfig
schedulingConfig = Maybe SchedulingConfig
a} :: Job)

-- | The status of the job, one of @IN_PROGRESS@, @CANCELED@,
-- @DELETION_IN_PROGRESS@ or @COMPLETED@.
job_status :: Lens.Lens' Job (Prelude.Maybe JobStatus)
job_status :: Lens' Job (Maybe JobStatus)
job_status = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Job' {Maybe JobStatus
status :: Maybe JobStatus
$sel:status:Job' :: Job -> Maybe JobStatus
status} -> Maybe JobStatus
status) (\s :: Job
s@Job' {} Maybe JobStatus
a -> Job
s {$sel:status:Job' :: Maybe JobStatus
status = Maybe JobStatus
a} :: Job)

-- | Specifies whether the job will continue to run (CONTINUOUS), or will be
-- complete after all those things specified as targets have completed the
-- job (SNAPSHOT). If continuous, the job may also be run on a thing when a
-- change is detected in a target. For example, a job will run on a device
-- when the thing representing the device is added to a target group, even
-- after the job was completed by all things originally in the group.
--
-- We recommend that you use continuous jobs instead of snapshot jobs for
-- dynamic thing group targets. By using continuous jobs, devices that join
-- the group receive the job execution even after the job has been created.
job_targetSelection :: Lens.Lens' Job (Prelude.Maybe TargetSelection)
job_targetSelection :: Lens' Job (Maybe TargetSelection)
job_targetSelection = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Job' {Maybe TargetSelection
targetSelection :: Maybe TargetSelection
$sel:targetSelection:Job' :: Job -> Maybe TargetSelection
targetSelection} -> Maybe TargetSelection
targetSelection) (\s :: Job
s@Job' {} Maybe TargetSelection
a -> Job
s {$sel:targetSelection:Job' :: Maybe TargetSelection
targetSelection = Maybe TargetSelection
a} :: Job)

-- | A list of IoT things and thing groups to which the job should be sent.
job_targets :: Lens.Lens' Job (Prelude.Maybe (Prelude.NonEmpty Prelude.Text))
job_targets :: Lens' Job (Maybe (NonEmpty Text))
job_targets = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Job' {Maybe (NonEmpty Text)
targets :: Maybe (NonEmpty Text)
$sel:targets:Job' :: Job -> Maybe (NonEmpty Text)
targets} -> Maybe (NonEmpty Text)
targets) (\s :: Job
s@Job' {} Maybe (NonEmpty Text)
a -> Job
s {$sel:targets:Job' :: Maybe (NonEmpty Text)
targets = Maybe (NonEmpty 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 the amount of time each device has to finish its execution of
-- the job. A timer is started when the job execution status is set to
-- @IN_PROGRESS@. If the job execution status is not set to another
-- terminal state before the timer expires, it will be automatically set to
-- @TIMED_OUT@.
job_timeoutConfig :: Lens.Lens' Job (Prelude.Maybe TimeoutConfig)
job_timeoutConfig :: Lens' Job (Maybe TimeoutConfig)
job_timeoutConfig = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Job' {Maybe TimeoutConfig
timeoutConfig :: Maybe TimeoutConfig
$sel:timeoutConfig:Job' :: Job -> Maybe TimeoutConfig
timeoutConfig} -> Maybe TimeoutConfig
timeoutConfig) (\s :: Job
s@Job' {} Maybe TimeoutConfig
a -> Job
s {$sel:timeoutConfig:Job' :: Maybe TimeoutConfig
timeoutConfig = Maybe TimeoutConfig
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 AbortConfig
-> Maybe Text
-> Maybe POSIX
-> Maybe POSIX
-> Maybe Text
-> Maybe (HashMap Text Text)
-> Maybe Bool
-> Maybe Bool
-> Maybe Text
-> Maybe JobExecutionsRetryConfig
-> Maybe JobExecutionsRolloutConfig
-> Maybe Text
-> Maybe JobProcessDetails
-> Maybe Text
-> Maybe POSIX
-> Maybe Text
-> Maybe PresignedUrlConfig
-> Maybe Text
-> Maybe SchedulingConfig
-> Maybe JobStatus
-> Maybe TargetSelection
-> Maybe (NonEmpty Text)
-> Maybe TimeoutConfig
-> 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
"abortConfig")
            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
"comment")
            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
"completedAt")
            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
"createdAt")
            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
"documentParameters"
                            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
"forceCanceled")
            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
"isConcurrent")
            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
"jobArn")
            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
"jobExecutionsRetryConfig")
            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
"jobExecutionsRolloutConfig")
            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
"jobId")
            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
"jobProcessDetails")
            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
"jobTemplateArn")
            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
"lastUpdatedAt")
            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
"namespaceId")
            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
"presignedUrlConfig")
            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
"reasonCode")
            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
"schedulingConfig")
            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
"status")
            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
"targetSelection")
            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
"targets")
            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
"timeoutConfig")
      )

instance Prelude.Hashable Job where
  hashWithSalt :: Int -> Job -> Int
hashWithSalt Int
_salt Job' {Maybe Bool
Maybe (NonEmpty Text)
Maybe Text
Maybe (HashMap Text Text)
Maybe POSIX
Maybe AbortConfig
Maybe JobProcessDetails
Maybe JobStatus
Maybe PresignedUrlConfig
Maybe JobExecutionsRolloutConfig
Maybe JobExecutionsRetryConfig
Maybe SchedulingConfig
Maybe TargetSelection
Maybe TimeoutConfig
timeoutConfig :: Maybe TimeoutConfig
targets :: Maybe (NonEmpty Text)
targetSelection :: Maybe TargetSelection
status :: Maybe JobStatus
schedulingConfig :: Maybe SchedulingConfig
reasonCode :: Maybe Text
presignedUrlConfig :: Maybe PresignedUrlConfig
namespaceId :: Maybe Text
lastUpdatedAt :: Maybe POSIX
jobTemplateArn :: Maybe Text
jobProcessDetails :: Maybe JobProcessDetails
jobId :: Maybe Text
jobExecutionsRolloutConfig :: Maybe JobExecutionsRolloutConfig
jobExecutionsRetryConfig :: Maybe JobExecutionsRetryConfig
jobArn :: Maybe Text
isConcurrent :: Maybe Bool
forceCanceled :: Maybe Bool
documentParameters :: Maybe (HashMap Text Text)
description :: Maybe Text
createdAt :: Maybe POSIX
completedAt :: Maybe POSIX
comment :: Maybe Text
abortConfig :: Maybe AbortConfig
$sel:timeoutConfig:Job' :: Job -> Maybe TimeoutConfig
$sel:targets:Job' :: Job -> Maybe (NonEmpty Text)
$sel:targetSelection:Job' :: Job -> Maybe TargetSelection
$sel:status:Job' :: Job -> Maybe JobStatus
$sel:schedulingConfig:Job' :: Job -> Maybe SchedulingConfig
$sel:reasonCode:Job' :: Job -> Maybe Text
$sel:presignedUrlConfig:Job' :: Job -> Maybe PresignedUrlConfig
$sel:namespaceId:Job' :: Job -> Maybe Text
$sel:lastUpdatedAt:Job' :: Job -> Maybe POSIX
$sel:jobTemplateArn:Job' :: Job -> Maybe Text
$sel:jobProcessDetails:Job' :: Job -> Maybe JobProcessDetails
$sel:jobId:Job' :: Job -> Maybe Text
$sel:jobExecutionsRolloutConfig:Job' :: Job -> Maybe JobExecutionsRolloutConfig
$sel:jobExecutionsRetryConfig:Job' :: Job -> Maybe JobExecutionsRetryConfig
$sel:jobArn:Job' :: Job -> Maybe Text
$sel:isConcurrent:Job' :: Job -> Maybe Bool
$sel:forceCanceled:Job' :: Job -> Maybe Bool
$sel:documentParameters:Job' :: Job -> Maybe (HashMap Text Text)
$sel:description:Job' :: Job -> Maybe Text
$sel:createdAt:Job' :: Job -> Maybe POSIX
$sel:completedAt:Job' :: Job -> Maybe POSIX
$sel:comment:Job' :: Job -> Maybe Text
$sel:abortConfig:Job' :: Job -> Maybe AbortConfig
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe AbortConfig
abortConfig
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
comment
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe POSIX
completedAt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe POSIX
createdAt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
description
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe (HashMap Text Text)
documentParameters
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
forceCanceled
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
isConcurrent
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
jobArn
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe JobExecutionsRetryConfig
jobExecutionsRetryConfig
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe JobExecutionsRolloutConfig
jobExecutionsRolloutConfig
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
jobId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe JobProcessDetails
jobProcessDetails
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
jobTemplateArn
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe POSIX
lastUpdatedAt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
namespaceId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe PresignedUrlConfig
presignedUrlConfig
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
reasonCode
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe SchedulingConfig
schedulingConfig
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe JobStatus
status
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe TargetSelection
targetSelection
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe (NonEmpty Text)
targets
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe TimeoutConfig
timeoutConfig

instance Prelude.NFData Job where
  rnf :: Job -> ()
rnf Job' {Maybe Bool
Maybe (NonEmpty Text)
Maybe Text
Maybe (HashMap Text Text)
Maybe POSIX
Maybe AbortConfig
Maybe JobProcessDetails
Maybe JobStatus
Maybe PresignedUrlConfig
Maybe JobExecutionsRolloutConfig
Maybe JobExecutionsRetryConfig
Maybe SchedulingConfig
Maybe TargetSelection
Maybe TimeoutConfig
timeoutConfig :: Maybe TimeoutConfig
targets :: Maybe (NonEmpty Text)
targetSelection :: Maybe TargetSelection
status :: Maybe JobStatus
schedulingConfig :: Maybe SchedulingConfig
reasonCode :: Maybe Text
presignedUrlConfig :: Maybe PresignedUrlConfig
namespaceId :: Maybe Text
lastUpdatedAt :: Maybe POSIX
jobTemplateArn :: Maybe Text
jobProcessDetails :: Maybe JobProcessDetails
jobId :: Maybe Text
jobExecutionsRolloutConfig :: Maybe JobExecutionsRolloutConfig
jobExecutionsRetryConfig :: Maybe JobExecutionsRetryConfig
jobArn :: Maybe Text
isConcurrent :: Maybe Bool
forceCanceled :: Maybe Bool
documentParameters :: Maybe (HashMap Text Text)
description :: Maybe Text
createdAt :: Maybe POSIX
completedAt :: Maybe POSIX
comment :: Maybe Text
abortConfig :: Maybe AbortConfig
$sel:timeoutConfig:Job' :: Job -> Maybe TimeoutConfig
$sel:targets:Job' :: Job -> Maybe (NonEmpty Text)
$sel:targetSelection:Job' :: Job -> Maybe TargetSelection
$sel:status:Job' :: Job -> Maybe JobStatus
$sel:schedulingConfig:Job' :: Job -> Maybe SchedulingConfig
$sel:reasonCode:Job' :: Job -> Maybe Text
$sel:presignedUrlConfig:Job' :: Job -> Maybe PresignedUrlConfig
$sel:namespaceId:Job' :: Job -> Maybe Text
$sel:lastUpdatedAt:Job' :: Job -> Maybe POSIX
$sel:jobTemplateArn:Job' :: Job -> Maybe Text
$sel:jobProcessDetails:Job' :: Job -> Maybe JobProcessDetails
$sel:jobId:Job' :: Job -> Maybe Text
$sel:jobExecutionsRolloutConfig:Job' :: Job -> Maybe JobExecutionsRolloutConfig
$sel:jobExecutionsRetryConfig:Job' :: Job -> Maybe JobExecutionsRetryConfig
$sel:jobArn:Job' :: Job -> Maybe Text
$sel:isConcurrent:Job' :: Job -> Maybe Bool
$sel:forceCanceled:Job' :: Job -> Maybe Bool
$sel:documentParameters:Job' :: Job -> Maybe (HashMap Text Text)
$sel:description:Job' :: Job -> Maybe Text
$sel:createdAt:Job' :: Job -> Maybe POSIX
$sel:completedAt:Job' :: Job -> Maybe POSIX
$sel:comment:Job' :: Job -> Maybe Text
$sel:abortConfig:Job' :: Job -> Maybe AbortConfig
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe AbortConfig
abortConfig
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
comment
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe POSIX
completedAt
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe POSIX
createdAt
      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 (HashMap Text Text)
documentParameters
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Bool
forceCanceled
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Bool
isConcurrent
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
jobArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe JobExecutionsRetryConfig
jobExecutionsRetryConfig
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe JobExecutionsRolloutConfig
jobExecutionsRolloutConfig
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
jobId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe JobProcessDetails
jobProcessDetails
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
jobTemplateArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe POSIX
lastUpdatedAt
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
namespaceId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe PresignedUrlConfig
presignedUrlConfig
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
reasonCode
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe SchedulingConfig
schedulingConfig
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe JobStatus
status
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe TargetSelection
targetSelection
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe (NonEmpty Text)
targets
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Maybe TimeoutConfig
timeoutConfig