{-# 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.JobExecution
-- 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.JobExecution 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.JobExecutionStatus
import Amazonka.IoT.Types.JobExecutionStatusDetails
import qualified Amazonka.Prelude as Prelude

-- | The job execution object represents the execution of a job on a
-- particular device.
--
-- /See:/ 'newJobExecution' smart constructor.
data JobExecution = JobExecution'
  { -- | The estimated number of seconds that remain before the job execution
    -- status will be changed to @TIMED_OUT@. The timeout interval can be
    -- anywhere between 1 minute and 7 days (1 to 10080 minutes). The actual
    -- job execution timeout can occur up to 60 seconds later than the
    -- estimated duration. This value will not be included if the job execution
    -- has reached a terminal status.
    JobExecution -> Maybe Integer
approximateSecondsBeforeTimedOut :: Prelude.Maybe Prelude.Integer,
    -- | A string (consisting of the digits \"0\" through \"9\") which identifies
    -- this particular job execution on this particular device. It can be used
    -- in commands which return or update job execution information.
    JobExecution -> Maybe Integer
executionNumber :: Prelude.Maybe Prelude.Integer,
    -- | Will be @true@ if the job execution was canceled with the optional
    -- @force@ parameter set to @true@.
    JobExecution -> Maybe Bool
forceCanceled :: Prelude.Maybe Prelude.Bool,
    -- | The unique identifier you assigned to the job when it was created.
    JobExecution -> Maybe Text
jobId :: Prelude.Maybe Prelude.Text,
    -- | The time, in seconds since the epoch, when the job execution was last
    -- updated.
    JobExecution -> Maybe POSIX
lastUpdatedAt :: Prelude.Maybe Data.POSIX,
    -- | The time, in seconds since the epoch, when the job execution was queued.
    JobExecution -> Maybe POSIX
queuedAt :: Prelude.Maybe Data.POSIX,
    -- | The time, in seconds since the epoch, when the job execution started.
    JobExecution -> Maybe POSIX
startedAt :: Prelude.Maybe Data.POSIX,
    -- | The status of the job execution (IN_PROGRESS, QUEUED, FAILED, SUCCEEDED,
    -- TIMED_OUT, CANCELED, or REJECTED).
    JobExecution -> Maybe JobExecutionStatus
status :: Prelude.Maybe JobExecutionStatus,
    -- | A collection of name\/value pairs that describe the status of the job
    -- execution.
    JobExecution -> Maybe JobExecutionStatusDetails
statusDetails :: Prelude.Maybe JobExecutionStatusDetails,
    -- | The ARN of the thing on which the job execution is running.
    JobExecution -> Maybe Text
thingArn :: Prelude.Maybe Prelude.Text,
    -- | The version of the job execution. Job execution versions are incremented
    -- each time they are updated by a device.
    JobExecution -> Maybe Integer
versionNumber :: Prelude.Maybe Prelude.Integer
  }
  deriving (JobExecution -> JobExecution -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: JobExecution -> JobExecution -> Bool
$c/= :: JobExecution -> JobExecution -> Bool
== :: JobExecution -> JobExecution -> Bool
$c== :: JobExecution -> JobExecution -> Bool
Prelude.Eq, ReadPrec [JobExecution]
ReadPrec JobExecution
Int -> ReadS JobExecution
ReadS [JobExecution]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [JobExecution]
$creadListPrec :: ReadPrec [JobExecution]
readPrec :: ReadPrec JobExecution
$creadPrec :: ReadPrec JobExecution
readList :: ReadS [JobExecution]
$creadList :: ReadS [JobExecution]
readsPrec :: Int -> ReadS JobExecution
$creadsPrec :: Int -> ReadS JobExecution
Prelude.Read, Int -> JobExecution -> ShowS
[JobExecution] -> ShowS
JobExecution -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [JobExecution] -> ShowS
$cshowList :: [JobExecution] -> ShowS
show :: JobExecution -> String
$cshow :: JobExecution -> String
showsPrec :: Int -> JobExecution -> ShowS
$cshowsPrec :: Int -> JobExecution -> ShowS
Prelude.Show, forall x. Rep JobExecution x -> JobExecution
forall x. JobExecution -> Rep JobExecution x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep JobExecution x -> JobExecution
$cfrom :: forall x. JobExecution -> Rep JobExecution x
Prelude.Generic)

-- |
-- Create a value of 'JobExecution' 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:
--
-- 'approximateSecondsBeforeTimedOut', 'jobExecution_approximateSecondsBeforeTimedOut' - The estimated number of seconds that remain before the job execution
-- status will be changed to @TIMED_OUT@. The timeout interval can be
-- anywhere between 1 minute and 7 days (1 to 10080 minutes). The actual
-- job execution timeout can occur up to 60 seconds later than the
-- estimated duration. This value will not be included if the job execution
-- has reached a terminal status.
--
-- 'executionNumber', 'jobExecution_executionNumber' - A string (consisting of the digits \"0\" through \"9\") which identifies
-- this particular job execution on this particular device. It can be used
-- in commands which return or update job execution information.
--
-- 'forceCanceled', 'jobExecution_forceCanceled' - Will be @true@ if the job execution was canceled with the optional
-- @force@ parameter set to @true@.
--
-- 'jobId', 'jobExecution_jobId' - The unique identifier you assigned to the job when it was created.
--
-- 'lastUpdatedAt', 'jobExecution_lastUpdatedAt' - The time, in seconds since the epoch, when the job execution was last
-- updated.
--
-- 'queuedAt', 'jobExecution_queuedAt' - The time, in seconds since the epoch, when the job execution was queued.
--
-- 'startedAt', 'jobExecution_startedAt' - The time, in seconds since the epoch, when the job execution started.
--
-- 'status', 'jobExecution_status' - The status of the job execution (IN_PROGRESS, QUEUED, FAILED, SUCCEEDED,
-- TIMED_OUT, CANCELED, or REJECTED).
--
-- 'statusDetails', 'jobExecution_statusDetails' - A collection of name\/value pairs that describe the status of the job
-- execution.
--
-- 'thingArn', 'jobExecution_thingArn' - The ARN of the thing on which the job execution is running.
--
-- 'versionNumber', 'jobExecution_versionNumber' - The version of the job execution. Job execution versions are incremented
-- each time they are updated by a device.
newJobExecution ::
  JobExecution
newJobExecution :: JobExecution
newJobExecution =
  JobExecution'
    { $sel:approximateSecondsBeforeTimedOut:JobExecution' :: Maybe Integer
approximateSecondsBeforeTimedOut =
        forall a. Maybe a
Prelude.Nothing,
      $sel:executionNumber:JobExecution' :: Maybe Integer
executionNumber = forall a. Maybe a
Prelude.Nothing,
      $sel:forceCanceled:JobExecution' :: Maybe Bool
forceCanceled = forall a. Maybe a
Prelude.Nothing,
      $sel:jobId:JobExecution' :: Maybe Text
jobId = forall a. Maybe a
Prelude.Nothing,
      $sel:lastUpdatedAt:JobExecution' :: Maybe POSIX
lastUpdatedAt = forall a. Maybe a
Prelude.Nothing,
      $sel:queuedAt:JobExecution' :: Maybe POSIX
queuedAt = forall a. Maybe a
Prelude.Nothing,
      $sel:startedAt:JobExecution' :: Maybe POSIX
startedAt = forall a. Maybe a
Prelude.Nothing,
      $sel:status:JobExecution' :: Maybe JobExecutionStatus
status = forall a. Maybe a
Prelude.Nothing,
      $sel:statusDetails:JobExecution' :: Maybe JobExecutionStatusDetails
statusDetails = forall a. Maybe a
Prelude.Nothing,
      $sel:thingArn:JobExecution' :: Maybe Text
thingArn = forall a. Maybe a
Prelude.Nothing,
      $sel:versionNumber:JobExecution' :: Maybe Integer
versionNumber = forall a. Maybe a
Prelude.Nothing
    }

-- | The estimated number of seconds that remain before the job execution
-- status will be changed to @TIMED_OUT@. The timeout interval can be
-- anywhere between 1 minute and 7 days (1 to 10080 minutes). The actual
-- job execution timeout can occur up to 60 seconds later than the
-- estimated duration. This value will not be included if the job execution
-- has reached a terminal status.
jobExecution_approximateSecondsBeforeTimedOut :: Lens.Lens' JobExecution (Prelude.Maybe Prelude.Integer)
jobExecution_approximateSecondsBeforeTimedOut :: Lens' JobExecution (Maybe Integer)
jobExecution_approximateSecondsBeforeTimedOut = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\JobExecution' {Maybe Integer
approximateSecondsBeforeTimedOut :: Maybe Integer
$sel:approximateSecondsBeforeTimedOut:JobExecution' :: JobExecution -> Maybe Integer
approximateSecondsBeforeTimedOut} -> Maybe Integer
approximateSecondsBeforeTimedOut) (\s :: JobExecution
s@JobExecution' {} Maybe Integer
a -> JobExecution
s {$sel:approximateSecondsBeforeTimedOut:JobExecution' :: Maybe Integer
approximateSecondsBeforeTimedOut = Maybe Integer
a} :: JobExecution)

-- | A string (consisting of the digits \"0\" through \"9\") which identifies
-- this particular job execution on this particular device. It can be used
-- in commands which return or update job execution information.
jobExecution_executionNumber :: Lens.Lens' JobExecution (Prelude.Maybe Prelude.Integer)
jobExecution_executionNumber :: Lens' JobExecution (Maybe Integer)
jobExecution_executionNumber = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\JobExecution' {Maybe Integer
executionNumber :: Maybe Integer
$sel:executionNumber:JobExecution' :: JobExecution -> Maybe Integer
executionNumber} -> Maybe Integer
executionNumber) (\s :: JobExecution
s@JobExecution' {} Maybe Integer
a -> JobExecution
s {$sel:executionNumber:JobExecution' :: Maybe Integer
executionNumber = Maybe Integer
a} :: JobExecution)

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

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

-- | The time, in seconds since the epoch, when the job execution was last
-- updated.
jobExecution_lastUpdatedAt :: Lens.Lens' JobExecution (Prelude.Maybe Prelude.UTCTime)
jobExecution_lastUpdatedAt :: Lens' JobExecution (Maybe UTCTime)
jobExecution_lastUpdatedAt = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\JobExecution' {Maybe POSIX
lastUpdatedAt :: Maybe POSIX
$sel:lastUpdatedAt:JobExecution' :: JobExecution -> Maybe POSIX
lastUpdatedAt} -> Maybe POSIX
lastUpdatedAt) (\s :: JobExecution
s@JobExecution' {} Maybe POSIX
a -> JobExecution
s {$sel:lastUpdatedAt:JobExecution' :: Maybe POSIX
lastUpdatedAt = Maybe POSIX
a} :: JobExecution) 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 execution was queued.
jobExecution_queuedAt :: Lens.Lens' JobExecution (Prelude.Maybe Prelude.UTCTime)
jobExecution_queuedAt :: Lens' JobExecution (Maybe UTCTime)
jobExecution_queuedAt = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\JobExecution' {Maybe POSIX
queuedAt :: Maybe POSIX
$sel:queuedAt:JobExecution' :: JobExecution -> Maybe POSIX
queuedAt} -> Maybe POSIX
queuedAt) (\s :: JobExecution
s@JobExecution' {} Maybe POSIX
a -> JobExecution
s {$sel:queuedAt:JobExecution' :: Maybe POSIX
queuedAt = Maybe POSIX
a} :: JobExecution) 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 execution started.
jobExecution_startedAt :: Lens.Lens' JobExecution (Prelude.Maybe Prelude.UTCTime)
jobExecution_startedAt :: Lens' JobExecution (Maybe UTCTime)
jobExecution_startedAt = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\JobExecution' {Maybe POSIX
startedAt :: Maybe POSIX
$sel:startedAt:JobExecution' :: JobExecution -> Maybe POSIX
startedAt} -> Maybe POSIX
startedAt) (\s :: JobExecution
s@JobExecution' {} Maybe POSIX
a -> JobExecution
s {$sel:startedAt:JobExecution' :: Maybe POSIX
startedAt = Maybe POSIX
a} :: JobExecution) 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 status of the job execution (IN_PROGRESS, QUEUED, FAILED, SUCCEEDED,
-- TIMED_OUT, CANCELED, or REJECTED).
jobExecution_status :: Lens.Lens' JobExecution (Prelude.Maybe JobExecutionStatus)
jobExecution_status :: Lens' JobExecution (Maybe JobExecutionStatus)
jobExecution_status = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\JobExecution' {Maybe JobExecutionStatus
status :: Maybe JobExecutionStatus
$sel:status:JobExecution' :: JobExecution -> Maybe JobExecutionStatus
status} -> Maybe JobExecutionStatus
status) (\s :: JobExecution
s@JobExecution' {} Maybe JobExecutionStatus
a -> JobExecution
s {$sel:status:JobExecution' :: Maybe JobExecutionStatus
status = Maybe JobExecutionStatus
a} :: JobExecution)

-- | A collection of name\/value pairs that describe the status of the job
-- execution.
jobExecution_statusDetails :: Lens.Lens' JobExecution (Prelude.Maybe JobExecutionStatusDetails)
jobExecution_statusDetails :: Lens' JobExecution (Maybe JobExecutionStatusDetails)
jobExecution_statusDetails = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\JobExecution' {Maybe JobExecutionStatusDetails
statusDetails :: Maybe JobExecutionStatusDetails
$sel:statusDetails:JobExecution' :: JobExecution -> Maybe JobExecutionStatusDetails
statusDetails} -> Maybe JobExecutionStatusDetails
statusDetails) (\s :: JobExecution
s@JobExecution' {} Maybe JobExecutionStatusDetails
a -> JobExecution
s {$sel:statusDetails:JobExecution' :: Maybe JobExecutionStatusDetails
statusDetails = Maybe JobExecutionStatusDetails
a} :: JobExecution)

-- | The ARN of the thing on which the job execution is running.
jobExecution_thingArn :: Lens.Lens' JobExecution (Prelude.Maybe Prelude.Text)
jobExecution_thingArn :: Lens' JobExecution (Maybe Text)
jobExecution_thingArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\JobExecution' {Maybe Text
thingArn :: Maybe Text
$sel:thingArn:JobExecution' :: JobExecution -> Maybe Text
thingArn} -> Maybe Text
thingArn) (\s :: JobExecution
s@JobExecution' {} Maybe Text
a -> JobExecution
s {$sel:thingArn:JobExecution' :: Maybe Text
thingArn = Maybe Text
a} :: JobExecution)

-- | The version of the job execution. Job execution versions are incremented
-- each time they are updated by a device.
jobExecution_versionNumber :: Lens.Lens' JobExecution (Prelude.Maybe Prelude.Integer)
jobExecution_versionNumber :: Lens' JobExecution (Maybe Integer)
jobExecution_versionNumber = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\JobExecution' {Maybe Integer
versionNumber :: Maybe Integer
$sel:versionNumber:JobExecution' :: JobExecution -> Maybe Integer
versionNumber} -> Maybe Integer
versionNumber) (\s :: JobExecution
s@JobExecution' {} Maybe Integer
a -> JobExecution
s {$sel:versionNumber:JobExecution' :: Maybe Integer
versionNumber = Maybe Integer
a} :: JobExecution)

instance Data.FromJSON JobExecution where
  parseJSON :: Value -> Parser JobExecution
parseJSON =
    forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.withObject
      String
"JobExecution"
      ( \Object
x ->
          Maybe Integer
-> Maybe Integer
-> Maybe Bool
-> Maybe Text
-> Maybe POSIX
-> Maybe POSIX
-> Maybe POSIX
-> Maybe JobExecutionStatus
-> Maybe JobExecutionStatusDetails
-> Maybe Text
-> Maybe Integer
-> JobExecution
JobExecution'
            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
"approximateSecondsBeforeTimedOut")
            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
"executionNumber")
            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
"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
"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
"queuedAt")
            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
"startedAt")
            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
"statusDetails")
            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
"thingArn")
            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
"versionNumber")
      )

instance Prelude.Hashable JobExecution where
  hashWithSalt :: Int -> JobExecution -> Int
hashWithSalt Int
_salt JobExecution' {Maybe Bool
Maybe Integer
Maybe Text
Maybe POSIX
Maybe JobExecutionStatus
Maybe JobExecutionStatusDetails
versionNumber :: Maybe Integer
thingArn :: Maybe Text
statusDetails :: Maybe JobExecutionStatusDetails
status :: Maybe JobExecutionStatus
startedAt :: Maybe POSIX
queuedAt :: Maybe POSIX
lastUpdatedAt :: Maybe POSIX
jobId :: Maybe Text
forceCanceled :: Maybe Bool
executionNumber :: Maybe Integer
approximateSecondsBeforeTimedOut :: Maybe Integer
$sel:versionNumber:JobExecution' :: JobExecution -> Maybe Integer
$sel:thingArn:JobExecution' :: JobExecution -> Maybe Text
$sel:statusDetails:JobExecution' :: JobExecution -> Maybe JobExecutionStatusDetails
$sel:status:JobExecution' :: JobExecution -> Maybe JobExecutionStatus
$sel:startedAt:JobExecution' :: JobExecution -> Maybe POSIX
$sel:queuedAt:JobExecution' :: JobExecution -> Maybe POSIX
$sel:lastUpdatedAt:JobExecution' :: JobExecution -> Maybe POSIX
$sel:jobId:JobExecution' :: JobExecution -> Maybe Text
$sel:forceCanceled:JobExecution' :: JobExecution -> Maybe Bool
$sel:executionNumber:JobExecution' :: JobExecution -> Maybe Integer
$sel:approximateSecondsBeforeTimedOut:JobExecution' :: JobExecution -> Maybe Integer
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Integer
approximateSecondsBeforeTimedOut
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Integer
executionNumber
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
forceCanceled
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
jobId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe POSIX
lastUpdatedAt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe POSIX
queuedAt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe POSIX
startedAt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe JobExecutionStatus
status
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe JobExecutionStatusDetails
statusDetails
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
thingArn
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Integer
versionNumber

instance Prelude.NFData JobExecution where
  rnf :: JobExecution -> ()
rnf JobExecution' {Maybe Bool
Maybe Integer
Maybe Text
Maybe POSIX
Maybe JobExecutionStatus
Maybe JobExecutionStatusDetails
versionNumber :: Maybe Integer
thingArn :: Maybe Text
statusDetails :: Maybe JobExecutionStatusDetails
status :: Maybe JobExecutionStatus
startedAt :: Maybe POSIX
queuedAt :: Maybe POSIX
lastUpdatedAt :: Maybe POSIX
jobId :: Maybe Text
forceCanceled :: Maybe Bool
executionNumber :: Maybe Integer
approximateSecondsBeforeTimedOut :: Maybe Integer
$sel:versionNumber:JobExecution' :: JobExecution -> Maybe Integer
$sel:thingArn:JobExecution' :: JobExecution -> Maybe Text
$sel:statusDetails:JobExecution' :: JobExecution -> Maybe JobExecutionStatusDetails
$sel:status:JobExecution' :: JobExecution -> Maybe JobExecutionStatus
$sel:startedAt:JobExecution' :: JobExecution -> Maybe POSIX
$sel:queuedAt:JobExecution' :: JobExecution -> Maybe POSIX
$sel:lastUpdatedAt:JobExecution' :: JobExecution -> Maybe POSIX
$sel:jobId:JobExecution' :: JobExecution -> Maybe Text
$sel:forceCanceled:JobExecution' :: JobExecution -> Maybe Bool
$sel:executionNumber:JobExecution' :: JobExecution -> Maybe Integer
$sel:approximateSecondsBeforeTimedOut:JobExecution' :: JobExecution -> Maybe Integer
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Integer
approximateSecondsBeforeTimedOut
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Integer
executionNumber
      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 Text
jobId
      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 POSIX
queuedAt
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe POSIX
startedAt
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe JobExecutionStatus
status
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe JobExecutionStatusDetails
statusDetails
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
thingArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Integer
versionNumber