{-# 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.Batch.Types.JobSummary
-- 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.Batch.Types.JobSummary where

import Amazonka.Batch.Types.ArrayPropertiesSummary
import Amazonka.Batch.Types.ContainerSummary
import Amazonka.Batch.Types.JobStatus
import Amazonka.Batch.Types.NodePropertiesSummary
import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import qualified Amazonka.Prelude as Prelude

-- | An object that represents summary details of a job.
--
-- /See:/ 'newJobSummary' smart constructor.
data JobSummary = JobSummary'
  { -- | The array properties of the job, if it\'s an array job.
    JobSummary -> Maybe ArrayPropertiesSummary
arrayProperties :: Prelude.Maybe ArrayPropertiesSummary,
    -- | An object that represents the details of the container that\'s
    -- associated with the job.
    JobSummary -> Maybe ContainerSummary
container :: Prelude.Maybe ContainerSummary,
    -- | The Unix timestamp (in milliseconds) for when the job was created. For
    -- non-array jobs and parent array jobs, this is when the job entered the
    -- @SUBMITTED@ state (at the time SubmitJob was called). For array child
    -- jobs, this is when the child job was spawned by its parent and entered
    -- the @PENDING@ state.
    JobSummary -> Maybe Integer
createdAt :: Prelude.Maybe Prelude.Integer,
    -- | The Amazon Resource Name (ARN) of the job.
    JobSummary -> Maybe Text
jobArn :: Prelude.Maybe Prelude.Text,
    -- | The Amazon Resource Name (ARN) of the job definition.
    JobSummary -> Maybe Text
jobDefinition :: Prelude.Maybe Prelude.Text,
    -- | The node properties for a single node in a job summary list.
    --
    -- This isn\'t applicable to jobs that are running on Fargate resources.
    JobSummary -> Maybe NodePropertiesSummary
nodeProperties :: Prelude.Maybe NodePropertiesSummary,
    -- | The Unix timestamp for when the job was started. More specifically,
    -- it\'s when the job transitioned from the @STARTING@ state to the
    -- @RUNNING@ state.
    JobSummary -> Maybe Integer
startedAt :: Prelude.Maybe Prelude.Integer,
    -- | The current status for the job.
    JobSummary -> Maybe JobStatus
status :: Prelude.Maybe JobStatus,
    -- | A short, human-readable string to provide more details for the current
    -- status of the job.
    JobSummary -> Maybe Text
statusReason :: Prelude.Maybe Prelude.Text,
    -- | The Unix timestamp for when the job was stopped. More specifically,
    -- it\'s when the job transitioned from the @RUNNING@ state to a terminal
    -- state, such as @SUCCEEDED@ or @FAILED@.
    JobSummary -> Maybe Integer
stoppedAt :: Prelude.Maybe Prelude.Integer,
    -- | The job ID.
    JobSummary -> Text
jobId :: Prelude.Text,
    -- | The job name.
    JobSummary -> Text
jobName :: Prelude.Text
  }
  deriving (JobSummary -> JobSummary -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: JobSummary -> JobSummary -> Bool
$c/= :: JobSummary -> JobSummary -> Bool
== :: JobSummary -> JobSummary -> Bool
$c== :: JobSummary -> JobSummary -> Bool
Prelude.Eq, ReadPrec [JobSummary]
ReadPrec JobSummary
Int -> ReadS JobSummary
ReadS [JobSummary]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [JobSummary]
$creadListPrec :: ReadPrec [JobSummary]
readPrec :: ReadPrec JobSummary
$creadPrec :: ReadPrec JobSummary
readList :: ReadS [JobSummary]
$creadList :: ReadS [JobSummary]
readsPrec :: Int -> ReadS JobSummary
$creadsPrec :: Int -> ReadS JobSummary
Prelude.Read, Int -> JobSummary -> ShowS
[JobSummary] -> ShowS
JobSummary -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [JobSummary] -> ShowS
$cshowList :: [JobSummary] -> ShowS
show :: JobSummary -> String
$cshow :: JobSummary -> String
showsPrec :: Int -> JobSummary -> ShowS
$cshowsPrec :: Int -> JobSummary -> ShowS
Prelude.Show, forall x. Rep JobSummary x -> JobSummary
forall x. JobSummary -> Rep JobSummary x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep JobSummary x -> JobSummary
$cfrom :: forall x. JobSummary -> Rep JobSummary x
Prelude.Generic)

-- |
-- Create a value of 'JobSummary' 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:
--
-- 'arrayProperties', 'jobSummary_arrayProperties' - The array properties of the job, if it\'s an array job.
--
-- 'container', 'jobSummary_container' - An object that represents the details of the container that\'s
-- associated with the job.
--
-- 'createdAt', 'jobSummary_createdAt' - The Unix timestamp (in milliseconds) for when the job was created. For
-- non-array jobs and parent array jobs, this is when the job entered the
-- @SUBMITTED@ state (at the time SubmitJob was called). For array child
-- jobs, this is when the child job was spawned by its parent and entered
-- the @PENDING@ state.
--
-- 'jobArn', 'jobSummary_jobArn' - The Amazon Resource Name (ARN) of the job.
--
-- 'jobDefinition', 'jobSummary_jobDefinition' - The Amazon Resource Name (ARN) of the job definition.
--
-- 'nodeProperties', 'jobSummary_nodeProperties' - The node properties for a single node in a job summary list.
--
-- This isn\'t applicable to jobs that are running on Fargate resources.
--
-- 'startedAt', 'jobSummary_startedAt' - The Unix timestamp for when the job was started. More specifically,
-- it\'s when the job transitioned from the @STARTING@ state to the
-- @RUNNING@ state.
--
-- 'status', 'jobSummary_status' - The current status for the job.
--
-- 'statusReason', 'jobSummary_statusReason' - A short, human-readable string to provide more details for the current
-- status of the job.
--
-- 'stoppedAt', 'jobSummary_stoppedAt' - The Unix timestamp for when the job was stopped. More specifically,
-- it\'s when the job transitioned from the @RUNNING@ state to a terminal
-- state, such as @SUCCEEDED@ or @FAILED@.
--
-- 'jobId', 'jobSummary_jobId' - The job ID.
--
-- 'jobName', 'jobSummary_jobName' - The job name.
newJobSummary ::
  -- | 'jobId'
  Prelude.Text ->
  -- | 'jobName'
  Prelude.Text ->
  JobSummary
newJobSummary :: Text -> Text -> JobSummary
newJobSummary Text
pJobId_ Text
pJobName_ =
  JobSummary'
    { $sel:arrayProperties:JobSummary' :: Maybe ArrayPropertiesSummary
arrayProperties = forall a. Maybe a
Prelude.Nothing,
      $sel:container:JobSummary' :: Maybe ContainerSummary
container = forall a. Maybe a
Prelude.Nothing,
      $sel:createdAt:JobSummary' :: Maybe Integer
createdAt = forall a. Maybe a
Prelude.Nothing,
      $sel:jobArn:JobSummary' :: Maybe Text
jobArn = forall a. Maybe a
Prelude.Nothing,
      $sel:jobDefinition:JobSummary' :: Maybe Text
jobDefinition = forall a. Maybe a
Prelude.Nothing,
      $sel:nodeProperties:JobSummary' :: Maybe NodePropertiesSummary
nodeProperties = forall a. Maybe a
Prelude.Nothing,
      $sel:startedAt:JobSummary' :: Maybe Integer
startedAt = forall a. Maybe a
Prelude.Nothing,
      $sel:status:JobSummary' :: Maybe JobStatus
status = forall a. Maybe a
Prelude.Nothing,
      $sel:statusReason:JobSummary' :: Maybe Text
statusReason = forall a. Maybe a
Prelude.Nothing,
      $sel:stoppedAt:JobSummary' :: Maybe Integer
stoppedAt = forall a. Maybe a
Prelude.Nothing,
      $sel:jobId:JobSummary' :: Text
jobId = Text
pJobId_,
      $sel:jobName:JobSummary' :: Text
jobName = Text
pJobName_
    }

-- | The array properties of the job, if it\'s an array job.
jobSummary_arrayProperties :: Lens.Lens' JobSummary (Prelude.Maybe ArrayPropertiesSummary)
jobSummary_arrayProperties :: Lens' JobSummary (Maybe ArrayPropertiesSummary)
jobSummary_arrayProperties = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\JobSummary' {Maybe ArrayPropertiesSummary
arrayProperties :: Maybe ArrayPropertiesSummary
$sel:arrayProperties:JobSummary' :: JobSummary -> Maybe ArrayPropertiesSummary
arrayProperties} -> Maybe ArrayPropertiesSummary
arrayProperties) (\s :: JobSummary
s@JobSummary' {} Maybe ArrayPropertiesSummary
a -> JobSummary
s {$sel:arrayProperties:JobSummary' :: Maybe ArrayPropertiesSummary
arrayProperties = Maybe ArrayPropertiesSummary
a} :: JobSummary)

-- | An object that represents the details of the container that\'s
-- associated with the job.
jobSummary_container :: Lens.Lens' JobSummary (Prelude.Maybe ContainerSummary)
jobSummary_container :: Lens' JobSummary (Maybe ContainerSummary)
jobSummary_container = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\JobSummary' {Maybe ContainerSummary
container :: Maybe ContainerSummary
$sel:container:JobSummary' :: JobSummary -> Maybe ContainerSummary
container} -> Maybe ContainerSummary
container) (\s :: JobSummary
s@JobSummary' {} Maybe ContainerSummary
a -> JobSummary
s {$sel:container:JobSummary' :: Maybe ContainerSummary
container = Maybe ContainerSummary
a} :: JobSummary)

-- | The Unix timestamp (in milliseconds) for when the job was created. For
-- non-array jobs and parent array jobs, this is when the job entered the
-- @SUBMITTED@ state (at the time SubmitJob was called). For array child
-- jobs, this is when the child job was spawned by its parent and entered
-- the @PENDING@ state.
jobSummary_createdAt :: Lens.Lens' JobSummary (Prelude.Maybe Prelude.Integer)
jobSummary_createdAt :: Lens' JobSummary (Maybe Integer)
jobSummary_createdAt = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\JobSummary' {Maybe Integer
createdAt :: Maybe Integer
$sel:createdAt:JobSummary' :: JobSummary -> Maybe Integer
createdAt} -> Maybe Integer
createdAt) (\s :: JobSummary
s@JobSummary' {} Maybe Integer
a -> JobSummary
s {$sel:createdAt:JobSummary' :: Maybe Integer
createdAt = Maybe Integer
a} :: JobSummary)

-- | The Amazon Resource Name (ARN) of the job.
jobSummary_jobArn :: Lens.Lens' JobSummary (Prelude.Maybe Prelude.Text)
jobSummary_jobArn :: Lens' JobSummary (Maybe Text)
jobSummary_jobArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\JobSummary' {Maybe Text
jobArn :: Maybe Text
$sel:jobArn:JobSummary' :: JobSummary -> Maybe Text
jobArn} -> Maybe Text
jobArn) (\s :: JobSummary
s@JobSummary' {} Maybe Text
a -> JobSummary
s {$sel:jobArn:JobSummary' :: Maybe Text
jobArn = Maybe Text
a} :: JobSummary)

-- | The Amazon Resource Name (ARN) of the job definition.
jobSummary_jobDefinition :: Lens.Lens' JobSummary (Prelude.Maybe Prelude.Text)
jobSummary_jobDefinition :: Lens' JobSummary (Maybe Text)
jobSummary_jobDefinition = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\JobSummary' {Maybe Text
jobDefinition :: Maybe Text
$sel:jobDefinition:JobSummary' :: JobSummary -> Maybe Text
jobDefinition} -> Maybe Text
jobDefinition) (\s :: JobSummary
s@JobSummary' {} Maybe Text
a -> JobSummary
s {$sel:jobDefinition:JobSummary' :: Maybe Text
jobDefinition = Maybe Text
a} :: JobSummary)

-- | The node properties for a single node in a job summary list.
--
-- This isn\'t applicable to jobs that are running on Fargate resources.
jobSummary_nodeProperties :: Lens.Lens' JobSummary (Prelude.Maybe NodePropertiesSummary)
jobSummary_nodeProperties :: Lens' JobSummary (Maybe NodePropertiesSummary)
jobSummary_nodeProperties = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\JobSummary' {Maybe NodePropertiesSummary
nodeProperties :: Maybe NodePropertiesSummary
$sel:nodeProperties:JobSummary' :: JobSummary -> Maybe NodePropertiesSummary
nodeProperties} -> Maybe NodePropertiesSummary
nodeProperties) (\s :: JobSummary
s@JobSummary' {} Maybe NodePropertiesSummary
a -> JobSummary
s {$sel:nodeProperties:JobSummary' :: Maybe NodePropertiesSummary
nodeProperties = Maybe NodePropertiesSummary
a} :: JobSummary)

-- | The Unix timestamp for when the job was started. More specifically,
-- it\'s when the job transitioned from the @STARTING@ state to the
-- @RUNNING@ state.
jobSummary_startedAt :: Lens.Lens' JobSummary (Prelude.Maybe Prelude.Integer)
jobSummary_startedAt :: Lens' JobSummary (Maybe Integer)
jobSummary_startedAt = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\JobSummary' {Maybe Integer
startedAt :: Maybe Integer
$sel:startedAt:JobSummary' :: JobSummary -> Maybe Integer
startedAt} -> Maybe Integer
startedAt) (\s :: JobSummary
s@JobSummary' {} Maybe Integer
a -> JobSummary
s {$sel:startedAt:JobSummary' :: Maybe Integer
startedAt = Maybe Integer
a} :: JobSummary)

-- | The current status for the job.
jobSummary_status :: Lens.Lens' JobSummary (Prelude.Maybe JobStatus)
jobSummary_status :: Lens' JobSummary (Maybe JobStatus)
jobSummary_status = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\JobSummary' {Maybe JobStatus
status :: Maybe JobStatus
$sel:status:JobSummary' :: JobSummary -> Maybe JobStatus
status} -> Maybe JobStatus
status) (\s :: JobSummary
s@JobSummary' {} Maybe JobStatus
a -> JobSummary
s {$sel:status:JobSummary' :: Maybe JobStatus
status = Maybe JobStatus
a} :: JobSummary)

-- | A short, human-readable string to provide more details for the current
-- status of the job.
jobSummary_statusReason :: Lens.Lens' JobSummary (Prelude.Maybe Prelude.Text)
jobSummary_statusReason :: Lens' JobSummary (Maybe Text)
jobSummary_statusReason = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\JobSummary' {Maybe Text
statusReason :: Maybe Text
$sel:statusReason:JobSummary' :: JobSummary -> Maybe Text
statusReason} -> Maybe Text
statusReason) (\s :: JobSummary
s@JobSummary' {} Maybe Text
a -> JobSummary
s {$sel:statusReason:JobSummary' :: Maybe Text
statusReason = Maybe Text
a} :: JobSummary)

-- | The Unix timestamp for when the job was stopped. More specifically,
-- it\'s when the job transitioned from the @RUNNING@ state to a terminal
-- state, such as @SUCCEEDED@ or @FAILED@.
jobSummary_stoppedAt :: Lens.Lens' JobSummary (Prelude.Maybe Prelude.Integer)
jobSummary_stoppedAt :: Lens' JobSummary (Maybe Integer)
jobSummary_stoppedAt = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\JobSummary' {Maybe Integer
stoppedAt :: Maybe Integer
$sel:stoppedAt:JobSummary' :: JobSummary -> Maybe Integer
stoppedAt} -> Maybe Integer
stoppedAt) (\s :: JobSummary
s@JobSummary' {} Maybe Integer
a -> JobSummary
s {$sel:stoppedAt:JobSummary' :: Maybe Integer
stoppedAt = Maybe Integer
a} :: JobSummary)

-- | The job ID.
jobSummary_jobId :: Lens.Lens' JobSummary Prelude.Text
jobSummary_jobId :: Lens' JobSummary Text
jobSummary_jobId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\JobSummary' {Text
jobId :: Text
$sel:jobId:JobSummary' :: JobSummary -> Text
jobId} -> Text
jobId) (\s :: JobSummary
s@JobSummary' {} Text
a -> JobSummary
s {$sel:jobId:JobSummary' :: Text
jobId = Text
a} :: JobSummary)

-- | The job name.
jobSummary_jobName :: Lens.Lens' JobSummary Prelude.Text
jobSummary_jobName :: Lens' JobSummary Text
jobSummary_jobName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\JobSummary' {Text
jobName :: Text
$sel:jobName:JobSummary' :: JobSummary -> Text
jobName} -> Text
jobName) (\s :: JobSummary
s@JobSummary' {} Text
a -> JobSummary
s {$sel:jobName:JobSummary' :: Text
jobName = Text
a} :: JobSummary)

instance Data.FromJSON JobSummary where
  parseJSON :: Value -> Parser JobSummary
parseJSON =
    forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.withObject
      String
"JobSummary"
      ( \Object
x ->
          Maybe ArrayPropertiesSummary
-> Maybe ContainerSummary
-> Maybe Integer
-> Maybe Text
-> Maybe Text
-> Maybe NodePropertiesSummary
-> Maybe Integer
-> Maybe JobStatus
-> Maybe Text
-> Maybe Integer
-> Text
-> Text
-> JobSummary
JobSummary'
            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
"arrayProperties")
            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
"container")
            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
"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
"jobDefinition")
            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
"nodeProperties")
            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
"statusReason")
            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
"stoppedAt")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser a
Data..: Key
"jobId")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser a
Data..: Key
"jobName")
      )

instance Prelude.Hashable JobSummary where
  hashWithSalt :: Int -> JobSummary -> Int
hashWithSalt Int
_salt JobSummary' {Maybe Integer
Maybe Text
Maybe ArrayPropertiesSummary
Maybe ContainerSummary
Maybe JobStatus
Maybe NodePropertiesSummary
Text
jobName :: Text
jobId :: Text
stoppedAt :: Maybe Integer
statusReason :: Maybe Text
status :: Maybe JobStatus
startedAt :: Maybe Integer
nodeProperties :: Maybe NodePropertiesSummary
jobDefinition :: Maybe Text
jobArn :: Maybe Text
createdAt :: Maybe Integer
container :: Maybe ContainerSummary
arrayProperties :: Maybe ArrayPropertiesSummary
$sel:jobName:JobSummary' :: JobSummary -> Text
$sel:jobId:JobSummary' :: JobSummary -> Text
$sel:stoppedAt:JobSummary' :: JobSummary -> Maybe Integer
$sel:statusReason:JobSummary' :: JobSummary -> Maybe Text
$sel:status:JobSummary' :: JobSummary -> Maybe JobStatus
$sel:startedAt:JobSummary' :: JobSummary -> Maybe Integer
$sel:nodeProperties:JobSummary' :: JobSummary -> Maybe NodePropertiesSummary
$sel:jobDefinition:JobSummary' :: JobSummary -> Maybe Text
$sel:jobArn:JobSummary' :: JobSummary -> Maybe Text
$sel:createdAt:JobSummary' :: JobSummary -> Maybe Integer
$sel:container:JobSummary' :: JobSummary -> Maybe ContainerSummary
$sel:arrayProperties:JobSummary' :: JobSummary -> Maybe ArrayPropertiesSummary
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ArrayPropertiesSummary
arrayProperties
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ContainerSummary
container
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Integer
createdAt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
jobArn
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
jobDefinition
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe NodePropertiesSummary
nodeProperties
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Integer
startedAt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe JobStatus
status
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
statusReason
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Integer
stoppedAt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
jobId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
jobName

instance Prelude.NFData JobSummary where
  rnf :: JobSummary -> ()
rnf JobSummary' {Maybe Integer
Maybe Text
Maybe ArrayPropertiesSummary
Maybe ContainerSummary
Maybe JobStatus
Maybe NodePropertiesSummary
Text
jobName :: Text
jobId :: Text
stoppedAt :: Maybe Integer
statusReason :: Maybe Text
status :: Maybe JobStatus
startedAt :: Maybe Integer
nodeProperties :: Maybe NodePropertiesSummary
jobDefinition :: Maybe Text
jobArn :: Maybe Text
createdAt :: Maybe Integer
container :: Maybe ContainerSummary
arrayProperties :: Maybe ArrayPropertiesSummary
$sel:jobName:JobSummary' :: JobSummary -> Text
$sel:jobId:JobSummary' :: JobSummary -> Text
$sel:stoppedAt:JobSummary' :: JobSummary -> Maybe Integer
$sel:statusReason:JobSummary' :: JobSummary -> Maybe Text
$sel:status:JobSummary' :: JobSummary -> Maybe JobStatus
$sel:startedAt:JobSummary' :: JobSummary -> Maybe Integer
$sel:nodeProperties:JobSummary' :: JobSummary -> Maybe NodePropertiesSummary
$sel:jobDefinition:JobSummary' :: JobSummary -> Maybe Text
$sel:jobArn:JobSummary' :: JobSummary -> Maybe Text
$sel:createdAt:JobSummary' :: JobSummary -> Maybe Integer
$sel:container:JobSummary' :: JobSummary -> Maybe ContainerSummary
$sel:arrayProperties:JobSummary' :: JobSummary -> Maybe ArrayPropertiesSummary
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe ArrayPropertiesSummary
arrayProperties
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ContainerSummary
container
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Integer
createdAt
      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 Text
jobDefinition
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe NodePropertiesSummary
nodeProperties
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Integer
startedAt
      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 Text
statusReason
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Integer
stoppedAt
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
jobId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
jobName