{-# 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.SageMaker.Types.CompilationJobSummary
-- 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.SageMaker.Types.CompilationJobSummary where

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
import Amazonka.SageMaker.Types.CompilationJobStatus
import Amazonka.SageMaker.Types.TargetDevice
import Amazonka.SageMaker.Types.TargetPlatformAccelerator
import Amazonka.SageMaker.Types.TargetPlatformArch
import Amazonka.SageMaker.Types.TargetPlatformOs

-- | A summary of a model compilation job.
--
-- /See:/ 'newCompilationJobSummary' smart constructor.
data CompilationJobSummary = CompilationJobSummary'
  { -- | The time when the model compilation job completed.
    CompilationJobSummary -> Maybe POSIX
compilationEndTime :: Prelude.Maybe Data.POSIX,
    -- | The time when the model compilation job started.
    CompilationJobSummary -> Maybe POSIX
compilationStartTime :: Prelude.Maybe Data.POSIX,
    -- | The type of device that the model will run on after the compilation job
    -- has completed.
    CompilationJobSummary -> Maybe TargetDevice
compilationTargetDevice :: Prelude.Maybe TargetDevice,
    -- | The type of accelerator that the model will run on after the compilation
    -- job has completed.
    CompilationJobSummary -> Maybe TargetPlatformAccelerator
compilationTargetPlatformAccelerator :: Prelude.Maybe TargetPlatformAccelerator,
    -- | The type of architecture that the model will run on after the
    -- compilation job has completed.
    CompilationJobSummary -> Maybe TargetPlatformArch
compilationTargetPlatformArch :: Prelude.Maybe TargetPlatformArch,
    -- | The type of OS that the model will run on after the compilation job has
    -- completed.
    CompilationJobSummary -> Maybe TargetPlatformOs
compilationTargetPlatformOs :: Prelude.Maybe TargetPlatformOs,
    -- | The time when the model compilation job was last modified.
    CompilationJobSummary -> Maybe POSIX
lastModifiedTime :: Prelude.Maybe Data.POSIX,
    -- | The name of the model compilation job that you want a summary for.
    CompilationJobSummary -> Text
compilationJobName :: Prelude.Text,
    -- | The Amazon Resource Name (ARN) of the model compilation job.
    CompilationJobSummary -> Text
compilationJobArn :: Prelude.Text,
    -- | The time when the model compilation job was created.
    CompilationJobSummary -> POSIX
creationTime :: Data.POSIX,
    -- | The status of the model compilation job.
    CompilationJobSummary -> CompilationJobStatus
compilationJobStatus :: CompilationJobStatus
  }
  deriving (CompilationJobSummary -> CompilationJobSummary -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CompilationJobSummary -> CompilationJobSummary -> Bool
$c/= :: CompilationJobSummary -> CompilationJobSummary -> Bool
== :: CompilationJobSummary -> CompilationJobSummary -> Bool
$c== :: CompilationJobSummary -> CompilationJobSummary -> Bool
Prelude.Eq, ReadPrec [CompilationJobSummary]
ReadPrec CompilationJobSummary
Int -> ReadS CompilationJobSummary
ReadS [CompilationJobSummary]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CompilationJobSummary]
$creadListPrec :: ReadPrec [CompilationJobSummary]
readPrec :: ReadPrec CompilationJobSummary
$creadPrec :: ReadPrec CompilationJobSummary
readList :: ReadS [CompilationJobSummary]
$creadList :: ReadS [CompilationJobSummary]
readsPrec :: Int -> ReadS CompilationJobSummary
$creadsPrec :: Int -> ReadS CompilationJobSummary
Prelude.Read, Int -> CompilationJobSummary -> ShowS
[CompilationJobSummary] -> ShowS
CompilationJobSummary -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CompilationJobSummary] -> ShowS
$cshowList :: [CompilationJobSummary] -> ShowS
show :: CompilationJobSummary -> String
$cshow :: CompilationJobSummary -> String
showsPrec :: Int -> CompilationJobSummary -> ShowS
$cshowsPrec :: Int -> CompilationJobSummary -> ShowS
Prelude.Show, forall x. Rep CompilationJobSummary x -> CompilationJobSummary
forall x. CompilationJobSummary -> Rep CompilationJobSummary x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CompilationJobSummary x -> CompilationJobSummary
$cfrom :: forall x. CompilationJobSummary -> Rep CompilationJobSummary x
Prelude.Generic)

-- |
-- Create a value of 'CompilationJobSummary' 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:
--
-- 'compilationEndTime', 'compilationJobSummary_compilationEndTime' - The time when the model compilation job completed.
--
-- 'compilationStartTime', 'compilationJobSummary_compilationStartTime' - The time when the model compilation job started.
--
-- 'compilationTargetDevice', 'compilationJobSummary_compilationTargetDevice' - The type of device that the model will run on after the compilation job
-- has completed.
--
-- 'compilationTargetPlatformAccelerator', 'compilationJobSummary_compilationTargetPlatformAccelerator' - The type of accelerator that the model will run on after the compilation
-- job has completed.
--
-- 'compilationTargetPlatformArch', 'compilationJobSummary_compilationTargetPlatformArch' - The type of architecture that the model will run on after the
-- compilation job has completed.
--
-- 'compilationTargetPlatformOs', 'compilationJobSummary_compilationTargetPlatformOs' - The type of OS that the model will run on after the compilation job has
-- completed.
--
-- 'lastModifiedTime', 'compilationJobSummary_lastModifiedTime' - The time when the model compilation job was last modified.
--
-- 'compilationJobName', 'compilationJobSummary_compilationJobName' - The name of the model compilation job that you want a summary for.
--
-- 'compilationJobArn', 'compilationJobSummary_compilationJobArn' - The Amazon Resource Name (ARN) of the model compilation job.
--
-- 'creationTime', 'compilationJobSummary_creationTime' - The time when the model compilation job was created.
--
-- 'compilationJobStatus', 'compilationJobSummary_compilationJobStatus' - The status of the model compilation job.
newCompilationJobSummary ::
  -- | 'compilationJobName'
  Prelude.Text ->
  -- | 'compilationJobArn'
  Prelude.Text ->
  -- | 'creationTime'
  Prelude.UTCTime ->
  -- | 'compilationJobStatus'
  CompilationJobStatus ->
  CompilationJobSummary
newCompilationJobSummary :: Text
-> Text -> UTCTime -> CompilationJobStatus -> CompilationJobSummary
newCompilationJobSummary
  Text
pCompilationJobName_
  Text
pCompilationJobArn_
  UTCTime
pCreationTime_
  CompilationJobStatus
pCompilationJobStatus_ =
    CompilationJobSummary'
      { $sel:compilationEndTime:CompilationJobSummary' :: Maybe POSIX
compilationEndTime =
          forall a. Maybe a
Prelude.Nothing,
        $sel:compilationStartTime:CompilationJobSummary' :: Maybe POSIX
compilationStartTime = forall a. Maybe a
Prelude.Nothing,
        $sel:compilationTargetDevice:CompilationJobSummary' :: Maybe TargetDevice
compilationTargetDevice = forall a. Maybe a
Prelude.Nothing,
        $sel:compilationTargetPlatformAccelerator:CompilationJobSummary' :: Maybe TargetPlatformAccelerator
compilationTargetPlatformAccelerator =
          forall a. Maybe a
Prelude.Nothing,
        $sel:compilationTargetPlatformArch:CompilationJobSummary' :: Maybe TargetPlatformArch
compilationTargetPlatformArch = forall a. Maybe a
Prelude.Nothing,
        $sel:compilationTargetPlatformOs:CompilationJobSummary' :: Maybe TargetPlatformOs
compilationTargetPlatformOs = forall a. Maybe a
Prelude.Nothing,
        $sel:lastModifiedTime:CompilationJobSummary' :: Maybe POSIX
lastModifiedTime = forall a. Maybe a
Prelude.Nothing,
        $sel:compilationJobName:CompilationJobSummary' :: Text
compilationJobName = Text
pCompilationJobName_,
        $sel:compilationJobArn:CompilationJobSummary' :: Text
compilationJobArn = Text
pCompilationJobArn_,
        $sel:creationTime:CompilationJobSummary' :: POSIX
creationTime = forall (a :: Format). Iso' (Time a) UTCTime
Data._Time forall t b. AReview t b -> b -> t
Lens.# UTCTime
pCreationTime_,
        $sel:compilationJobStatus:CompilationJobSummary' :: CompilationJobStatus
compilationJobStatus = CompilationJobStatus
pCompilationJobStatus_
      }

-- | The time when the model compilation job completed.
compilationJobSummary_compilationEndTime :: Lens.Lens' CompilationJobSummary (Prelude.Maybe Prelude.UTCTime)
compilationJobSummary_compilationEndTime :: Lens' CompilationJobSummary (Maybe UTCTime)
compilationJobSummary_compilationEndTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CompilationJobSummary' {Maybe POSIX
compilationEndTime :: Maybe POSIX
$sel:compilationEndTime:CompilationJobSummary' :: CompilationJobSummary -> Maybe POSIX
compilationEndTime} -> Maybe POSIX
compilationEndTime) (\s :: CompilationJobSummary
s@CompilationJobSummary' {} Maybe POSIX
a -> CompilationJobSummary
s {$sel:compilationEndTime:CompilationJobSummary' :: Maybe POSIX
compilationEndTime = Maybe POSIX
a} :: CompilationJobSummary) 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 when the model compilation job started.
compilationJobSummary_compilationStartTime :: Lens.Lens' CompilationJobSummary (Prelude.Maybe Prelude.UTCTime)
compilationJobSummary_compilationStartTime :: Lens' CompilationJobSummary (Maybe UTCTime)
compilationJobSummary_compilationStartTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CompilationJobSummary' {Maybe POSIX
compilationStartTime :: Maybe POSIX
$sel:compilationStartTime:CompilationJobSummary' :: CompilationJobSummary -> Maybe POSIX
compilationStartTime} -> Maybe POSIX
compilationStartTime) (\s :: CompilationJobSummary
s@CompilationJobSummary' {} Maybe POSIX
a -> CompilationJobSummary
s {$sel:compilationStartTime:CompilationJobSummary' :: Maybe POSIX
compilationStartTime = Maybe POSIX
a} :: CompilationJobSummary) 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 type of device that the model will run on after the compilation job
-- has completed.
compilationJobSummary_compilationTargetDevice :: Lens.Lens' CompilationJobSummary (Prelude.Maybe TargetDevice)
compilationJobSummary_compilationTargetDevice :: Lens' CompilationJobSummary (Maybe TargetDevice)
compilationJobSummary_compilationTargetDevice = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CompilationJobSummary' {Maybe TargetDevice
compilationTargetDevice :: Maybe TargetDevice
$sel:compilationTargetDevice:CompilationJobSummary' :: CompilationJobSummary -> Maybe TargetDevice
compilationTargetDevice} -> Maybe TargetDevice
compilationTargetDevice) (\s :: CompilationJobSummary
s@CompilationJobSummary' {} Maybe TargetDevice
a -> CompilationJobSummary
s {$sel:compilationTargetDevice:CompilationJobSummary' :: Maybe TargetDevice
compilationTargetDevice = Maybe TargetDevice
a} :: CompilationJobSummary)

-- | The type of accelerator that the model will run on after the compilation
-- job has completed.
compilationJobSummary_compilationTargetPlatformAccelerator :: Lens.Lens' CompilationJobSummary (Prelude.Maybe TargetPlatformAccelerator)
compilationJobSummary_compilationTargetPlatformAccelerator :: Lens' CompilationJobSummary (Maybe TargetPlatformAccelerator)
compilationJobSummary_compilationTargetPlatformAccelerator = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CompilationJobSummary' {Maybe TargetPlatformAccelerator
compilationTargetPlatformAccelerator :: Maybe TargetPlatformAccelerator
$sel:compilationTargetPlatformAccelerator:CompilationJobSummary' :: CompilationJobSummary -> Maybe TargetPlatformAccelerator
compilationTargetPlatformAccelerator} -> Maybe TargetPlatformAccelerator
compilationTargetPlatformAccelerator) (\s :: CompilationJobSummary
s@CompilationJobSummary' {} Maybe TargetPlatformAccelerator
a -> CompilationJobSummary
s {$sel:compilationTargetPlatformAccelerator:CompilationJobSummary' :: Maybe TargetPlatformAccelerator
compilationTargetPlatformAccelerator = Maybe TargetPlatformAccelerator
a} :: CompilationJobSummary)

-- | The type of architecture that the model will run on after the
-- compilation job has completed.
compilationJobSummary_compilationTargetPlatformArch :: Lens.Lens' CompilationJobSummary (Prelude.Maybe TargetPlatformArch)
compilationJobSummary_compilationTargetPlatformArch :: Lens' CompilationJobSummary (Maybe TargetPlatformArch)
compilationJobSummary_compilationTargetPlatformArch = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CompilationJobSummary' {Maybe TargetPlatformArch
compilationTargetPlatformArch :: Maybe TargetPlatformArch
$sel:compilationTargetPlatformArch:CompilationJobSummary' :: CompilationJobSummary -> Maybe TargetPlatformArch
compilationTargetPlatformArch} -> Maybe TargetPlatformArch
compilationTargetPlatformArch) (\s :: CompilationJobSummary
s@CompilationJobSummary' {} Maybe TargetPlatformArch
a -> CompilationJobSummary
s {$sel:compilationTargetPlatformArch:CompilationJobSummary' :: Maybe TargetPlatformArch
compilationTargetPlatformArch = Maybe TargetPlatformArch
a} :: CompilationJobSummary)

-- | The type of OS that the model will run on after the compilation job has
-- completed.
compilationJobSummary_compilationTargetPlatformOs :: Lens.Lens' CompilationJobSummary (Prelude.Maybe TargetPlatformOs)
compilationJobSummary_compilationTargetPlatformOs :: Lens' CompilationJobSummary (Maybe TargetPlatformOs)
compilationJobSummary_compilationTargetPlatformOs = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CompilationJobSummary' {Maybe TargetPlatformOs
compilationTargetPlatformOs :: Maybe TargetPlatformOs
$sel:compilationTargetPlatformOs:CompilationJobSummary' :: CompilationJobSummary -> Maybe TargetPlatformOs
compilationTargetPlatformOs} -> Maybe TargetPlatformOs
compilationTargetPlatformOs) (\s :: CompilationJobSummary
s@CompilationJobSummary' {} Maybe TargetPlatformOs
a -> CompilationJobSummary
s {$sel:compilationTargetPlatformOs:CompilationJobSummary' :: Maybe TargetPlatformOs
compilationTargetPlatformOs = Maybe TargetPlatformOs
a} :: CompilationJobSummary)

-- | The time when the model compilation job was last modified.
compilationJobSummary_lastModifiedTime :: Lens.Lens' CompilationJobSummary (Prelude.Maybe Prelude.UTCTime)
compilationJobSummary_lastModifiedTime :: Lens' CompilationJobSummary (Maybe UTCTime)
compilationJobSummary_lastModifiedTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CompilationJobSummary' {Maybe POSIX
lastModifiedTime :: Maybe POSIX
$sel:lastModifiedTime:CompilationJobSummary' :: CompilationJobSummary -> Maybe POSIX
lastModifiedTime} -> Maybe POSIX
lastModifiedTime) (\s :: CompilationJobSummary
s@CompilationJobSummary' {} Maybe POSIX
a -> CompilationJobSummary
s {$sel:lastModifiedTime:CompilationJobSummary' :: Maybe POSIX
lastModifiedTime = Maybe POSIX
a} :: CompilationJobSummary) 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 name of the model compilation job that you want a summary for.
compilationJobSummary_compilationJobName :: Lens.Lens' CompilationJobSummary Prelude.Text
compilationJobSummary_compilationJobName :: Lens' CompilationJobSummary Text
compilationJobSummary_compilationJobName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CompilationJobSummary' {Text
compilationJobName :: Text
$sel:compilationJobName:CompilationJobSummary' :: CompilationJobSummary -> Text
compilationJobName} -> Text
compilationJobName) (\s :: CompilationJobSummary
s@CompilationJobSummary' {} Text
a -> CompilationJobSummary
s {$sel:compilationJobName:CompilationJobSummary' :: Text
compilationJobName = Text
a} :: CompilationJobSummary)

-- | The Amazon Resource Name (ARN) of the model compilation job.
compilationJobSummary_compilationJobArn :: Lens.Lens' CompilationJobSummary Prelude.Text
compilationJobSummary_compilationJobArn :: Lens' CompilationJobSummary Text
compilationJobSummary_compilationJobArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CompilationJobSummary' {Text
compilationJobArn :: Text
$sel:compilationJobArn:CompilationJobSummary' :: CompilationJobSummary -> Text
compilationJobArn} -> Text
compilationJobArn) (\s :: CompilationJobSummary
s@CompilationJobSummary' {} Text
a -> CompilationJobSummary
s {$sel:compilationJobArn:CompilationJobSummary' :: Text
compilationJobArn = Text
a} :: CompilationJobSummary)

-- | The time when the model compilation job was created.
compilationJobSummary_creationTime :: Lens.Lens' CompilationJobSummary Prelude.UTCTime
compilationJobSummary_creationTime :: Lens' CompilationJobSummary UTCTime
compilationJobSummary_creationTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CompilationJobSummary' {POSIX
creationTime :: POSIX
$sel:creationTime:CompilationJobSummary' :: CompilationJobSummary -> POSIX
creationTime} -> POSIX
creationTime) (\s :: CompilationJobSummary
s@CompilationJobSummary' {} POSIX
a -> CompilationJobSummary
s {$sel:creationTime:CompilationJobSummary' :: POSIX
creationTime = POSIX
a} :: CompilationJobSummary) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (a :: Format). Iso' (Time a) UTCTime
Data._Time

-- | The status of the model compilation job.
compilationJobSummary_compilationJobStatus :: Lens.Lens' CompilationJobSummary CompilationJobStatus
compilationJobSummary_compilationJobStatus :: Lens' CompilationJobSummary CompilationJobStatus
compilationJobSummary_compilationJobStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CompilationJobSummary' {CompilationJobStatus
compilationJobStatus :: CompilationJobStatus
$sel:compilationJobStatus:CompilationJobSummary' :: CompilationJobSummary -> CompilationJobStatus
compilationJobStatus} -> CompilationJobStatus
compilationJobStatus) (\s :: CompilationJobSummary
s@CompilationJobSummary' {} CompilationJobStatus
a -> CompilationJobSummary
s {$sel:compilationJobStatus:CompilationJobSummary' :: CompilationJobStatus
compilationJobStatus = CompilationJobStatus
a} :: CompilationJobSummary)

instance Data.FromJSON CompilationJobSummary where
  parseJSON :: Value -> Parser CompilationJobSummary
parseJSON =
    forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.withObject
      String
"CompilationJobSummary"
      ( \Object
x ->
          Maybe POSIX
-> Maybe POSIX
-> Maybe TargetDevice
-> Maybe TargetPlatformAccelerator
-> Maybe TargetPlatformArch
-> Maybe TargetPlatformOs
-> Maybe POSIX
-> Text
-> Text
-> POSIX
-> CompilationJobStatus
-> CompilationJobSummary
CompilationJobSummary'
            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
"CompilationEndTime")
            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
"CompilationStartTime")
            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
"CompilationTargetDevice")
            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
"CompilationTargetPlatformAccelerator")
            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
"CompilationTargetPlatformArch")
            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
"CompilationTargetPlatformOs")
            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
"LastModifiedTime")
            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
"CompilationJobName")
            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
"CompilationJobArn")
            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
"CreationTime")
            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
"CompilationJobStatus")
      )

instance Prelude.Hashable CompilationJobSummary where
  hashWithSalt :: Int -> CompilationJobSummary -> Int
hashWithSalt Int
_salt CompilationJobSummary' {Maybe POSIX
Maybe TargetDevice
Maybe TargetPlatformAccelerator
Maybe TargetPlatformArch
Maybe TargetPlatformOs
Text
POSIX
CompilationJobStatus
compilationJobStatus :: CompilationJobStatus
creationTime :: POSIX
compilationJobArn :: Text
compilationJobName :: Text
lastModifiedTime :: Maybe POSIX
compilationTargetPlatformOs :: Maybe TargetPlatformOs
compilationTargetPlatformArch :: Maybe TargetPlatformArch
compilationTargetPlatformAccelerator :: Maybe TargetPlatformAccelerator
compilationTargetDevice :: Maybe TargetDevice
compilationStartTime :: Maybe POSIX
compilationEndTime :: Maybe POSIX
$sel:compilationJobStatus:CompilationJobSummary' :: CompilationJobSummary -> CompilationJobStatus
$sel:creationTime:CompilationJobSummary' :: CompilationJobSummary -> POSIX
$sel:compilationJobArn:CompilationJobSummary' :: CompilationJobSummary -> Text
$sel:compilationJobName:CompilationJobSummary' :: CompilationJobSummary -> Text
$sel:lastModifiedTime:CompilationJobSummary' :: CompilationJobSummary -> Maybe POSIX
$sel:compilationTargetPlatformOs:CompilationJobSummary' :: CompilationJobSummary -> Maybe TargetPlatformOs
$sel:compilationTargetPlatformArch:CompilationJobSummary' :: CompilationJobSummary -> Maybe TargetPlatformArch
$sel:compilationTargetPlatformAccelerator:CompilationJobSummary' :: CompilationJobSummary -> Maybe TargetPlatformAccelerator
$sel:compilationTargetDevice:CompilationJobSummary' :: CompilationJobSummary -> Maybe TargetDevice
$sel:compilationStartTime:CompilationJobSummary' :: CompilationJobSummary -> Maybe POSIX
$sel:compilationEndTime:CompilationJobSummary' :: CompilationJobSummary -> Maybe POSIX
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe POSIX
compilationEndTime
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe POSIX
compilationStartTime
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe TargetDevice
compilationTargetDevice
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe TargetPlatformAccelerator
compilationTargetPlatformAccelerator
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe TargetPlatformArch
compilationTargetPlatformArch
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe TargetPlatformOs
compilationTargetPlatformOs
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe POSIX
lastModifiedTime
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
compilationJobName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
compilationJobArn
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` POSIX
creationTime
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` CompilationJobStatus
compilationJobStatus

instance Prelude.NFData CompilationJobSummary where
  rnf :: CompilationJobSummary -> ()
rnf CompilationJobSummary' {Maybe POSIX
Maybe TargetDevice
Maybe TargetPlatformAccelerator
Maybe TargetPlatformArch
Maybe TargetPlatformOs
Text
POSIX
CompilationJobStatus
compilationJobStatus :: CompilationJobStatus
creationTime :: POSIX
compilationJobArn :: Text
compilationJobName :: Text
lastModifiedTime :: Maybe POSIX
compilationTargetPlatformOs :: Maybe TargetPlatformOs
compilationTargetPlatformArch :: Maybe TargetPlatformArch
compilationTargetPlatformAccelerator :: Maybe TargetPlatformAccelerator
compilationTargetDevice :: Maybe TargetDevice
compilationStartTime :: Maybe POSIX
compilationEndTime :: Maybe POSIX
$sel:compilationJobStatus:CompilationJobSummary' :: CompilationJobSummary -> CompilationJobStatus
$sel:creationTime:CompilationJobSummary' :: CompilationJobSummary -> POSIX
$sel:compilationJobArn:CompilationJobSummary' :: CompilationJobSummary -> Text
$sel:compilationJobName:CompilationJobSummary' :: CompilationJobSummary -> Text
$sel:lastModifiedTime:CompilationJobSummary' :: CompilationJobSummary -> Maybe POSIX
$sel:compilationTargetPlatformOs:CompilationJobSummary' :: CompilationJobSummary -> Maybe TargetPlatformOs
$sel:compilationTargetPlatformArch:CompilationJobSummary' :: CompilationJobSummary -> Maybe TargetPlatformArch
$sel:compilationTargetPlatformAccelerator:CompilationJobSummary' :: CompilationJobSummary -> Maybe TargetPlatformAccelerator
$sel:compilationTargetDevice:CompilationJobSummary' :: CompilationJobSummary -> Maybe TargetDevice
$sel:compilationStartTime:CompilationJobSummary' :: CompilationJobSummary -> Maybe POSIX
$sel:compilationEndTime:CompilationJobSummary' :: CompilationJobSummary -> Maybe POSIX
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe POSIX
compilationEndTime
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe POSIX
compilationStartTime
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe TargetDevice
compilationTargetDevice
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe TargetPlatformAccelerator
compilationTargetPlatformAccelerator
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe TargetPlatformArch
compilationTargetPlatformArch
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe TargetPlatformOs
compilationTargetPlatformOs
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe POSIX
lastModifiedTime
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
compilationJobName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
compilationJobArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf POSIX
creationTime
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf CompilationJobStatus
compilationJobStatus