{-# 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.AutoMLJobSummary
-- 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.AutoMLJobSummary 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.AutoMLJobSecondaryStatus
import Amazonka.SageMaker.Types.AutoMLJobStatus
import Amazonka.SageMaker.Types.AutoMLPartialFailureReason

-- | Provides a summary about an AutoML job.
--
-- /See:/ 'newAutoMLJobSummary' smart constructor.
data AutoMLJobSummary = AutoMLJobSummary'
  { -- | The end time of an AutoML job.
    AutoMLJobSummary -> Maybe POSIX
endTime :: Prelude.Maybe Data.POSIX,
    -- | The failure reason of an AutoML job.
    AutoMLJobSummary -> Maybe Text
failureReason :: Prelude.Maybe Prelude.Text,
    -- | The list of reasons for partial failures within an AutoML job.
    AutoMLJobSummary -> Maybe (NonEmpty AutoMLPartialFailureReason)
partialFailureReasons :: Prelude.Maybe (Prelude.NonEmpty AutoMLPartialFailureReason),
    -- | The name of the AutoML job you are requesting.
    AutoMLJobSummary -> Text
autoMLJobName :: Prelude.Text,
    -- | The ARN of the AutoML job.
    AutoMLJobSummary -> Text
autoMLJobArn :: Prelude.Text,
    -- | The status of the AutoML job.
    AutoMLJobSummary -> AutoMLJobStatus
autoMLJobStatus :: AutoMLJobStatus,
    -- | The secondary status of the AutoML job.
    AutoMLJobSummary -> AutoMLJobSecondaryStatus
autoMLJobSecondaryStatus :: AutoMLJobSecondaryStatus,
    -- | When the AutoML job was created.
    AutoMLJobSummary -> POSIX
creationTime :: Data.POSIX,
    -- | When the AutoML job was last modified.
    AutoMLJobSummary -> POSIX
lastModifiedTime :: Data.POSIX
  }
  deriving (AutoMLJobSummary -> AutoMLJobSummary -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AutoMLJobSummary -> AutoMLJobSummary -> Bool
$c/= :: AutoMLJobSummary -> AutoMLJobSummary -> Bool
== :: AutoMLJobSummary -> AutoMLJobSummary -> Bool
$c== :: AutoMLJobSummary -> AutoMLJobSummary -> Bool
Prelude.Eq, ReadPrec [AutoMLJobSummary]
ReadPrec AutoMLJobSummary
Int -> ReadS AutoMLJobSummary
ReadS [AutoMLJobSummary]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [AutoMLJobSummary]
$creadListPrec :: ReadPrec [AutoMLJobSummary]
readPrec :: ReadPrec AutoMLJobSummary
$creadPrec :: ReadPrec AutoMLJobSummary
readList :: ReadS [AutoMLJobSummary]
$creadList :: ReadS [AutoMLJobSummary]
readsPrec :: Int -> ReadS AutoMLJobSummary
$creadsPrec :: Int -> ReadS AutoMLJobSummary
Prelude.Read, Int -> AutoMLJobSummary -> ShowS
[AutoMLJobSummary] -> ShowS
AutoMLJobSummary -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [AutoMLJobSummary] -> ShowS
$cshowList :: [AutoMLJobSummary] -> ShowS
show :: AutoMLJobSummary -> String
$cshow :: AutoMLJobSummary -> String
showsPrec :: Int -> AutoMLJobSummary -> ShowS
$cshowsPrec :: Int -> AutoMLJobSummary -> ShowS
Prelude.Show, forall x. Rep AutoMLJobSummary x -> AutoMLJobSummary
forall x. AutoMLJobSummary -> Rep AutoMLJobSummary x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep AutoMLJobSummary x -> AutoMLJobSummary
$cfrom :: forall x. AutoMLJobSummary -> Rep AutoMLJobSummary x
Prelude.Generic)

-- |
-- Create a value of 'AutoMLJobSummary' 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:
--
-- 'endTime', 'autoMLJobSummary_endTime' - The end time of an AutoML job.
--
-- 'failureReason', 'autoMLJobSummary_failureReason' - The failure reason of an AutoML job.
--
-- 'partialFailureReasons', 'autoMLJobSummary_partialFailureReasons' - The list of reasons for partial failures within an AutoML job.
--
-- 'autoMLJobName', 'autoMLJobSummary_autoMLJobName' - The name of the AutoML job you are requesting.
--
-- 'autoMLJobArn', 'autoMLJobSummary_autoMLJobArn' - The ARN of the AutoML job.
--
-- 'autoMLJobStatus', 'autoMLJobSummary_autoMLJobStatus' - The status of the AutoML job.
--
-- 'autoMLJobSecondaryStatus', 'autoMLJobSummary_autoMLJobSecondaryStatus' - The secondary status of the AutoML job.
--
-- 'creationTime', 'autoMLJobSummary_creationTime' - When the AutoML job was created.
--
-- 'lastModifiedTime', 'autoMLJobSummary_lastModifiedTime' - When the AutoML job was last modified.
newAutoMLJobSummary ::
  -- | 'autoMLJobName'
  Prelude.Text ->
  -- | 'autoMLJobArn'
  Prelude.Text ->
  -- | 'autoMLJobStatus'
  AutoMLJobStatus ->
  -- | 'autoMLJobSecondaryStatus'
  AutoMLJobSecondaryStatus ->
  -- | 'creationTime'
  Prelude.UTCTime ->
  -- | 'lastModifiedTime'
  Prelude.UTCTime ->
  AutoMLJobSummary
newAutoMLJobSummary :: Text
-> Text
-> AutoMLJobStatus
-> AutoMLJobSecondaryStatus
-> UTCTime
-> UTCTime
-> AutoMLJobSummary
newAutoMLJobSummary
  Text
pAutoMLJobName_
  Text
pAutoMLJobArn_
  AutoMLJobStatus
pAutoMLJobStatus_
  AutoMLJobSecondaryStatus
pAutoMLJobSecondaryStatus_
  UTCTime
pCreationTime_
  UTCTime
pLastModifiedTime_ =
    AutoMLJobSummary'
      { $sel:endTime:AutoMLJobSummary' :: Maybe POSIX
endTime = forall a. Maybe a
Prelude.Nothing,
        $sel:failureReason:AutoMLJobSummary' :: Maybe Text
failureReason = forall a. Maybe a
Prelude.Nothing,
        $sel:partialFailureReasons:AutoMLJobSummary' :: Maybe (NonEmpty AutoMLPartialFailureReason)
partialFailureReasons = forall a. Maybe a
Prelude.Nothing,
        $sel:autoMLJobName:AutoMLJobSummary' :: Text
autoMLJobName = Text
pAutoMLJobName_,
        $sel:autoMLJobArn:AutoMLJobSummary' :: Text
autoMLJobArn = Text
pAutoMLJobArn_,
        $sel:autoMLJobStatus:AutoMLJobSummary' :: AutoMLJobStatus
autoMLJobStatus = AutoMLJobStatus
pAutoMLJobStatus_,
        $sel:autoMLJobSecondaryStatus:AutoMLJobSummary' :: AutoMLJobSecondaryStatus
autoMLJobSecondaryStatus =
          AutoMLJobSecondaryStatus
pAutoMLJobSecondaryStatus_,
        $sel:creationTime:AutoMLJobSummary' :: POSIX
creationTime = forall (a :: Format). Iso' (Time a) UTCTime
Data._Time forall t b. AReview t b -> b -> t
Lens.# UTCTime
pCreationTime_,
        $sel:lastModifiedTime:AutoMLJobSummary' :: POSIX
lastModifiedTime =
          forall (a :: Format). Iso' (Time a) UTCTime
Data._Time forall t b. AReview t b -> b -> t
Lens.# UTCTime
pLastModifiedTime_
      }

-- | The end time of an AutoML job.
autoMLJobSummary_endTime :: Lens.Lens' AutoMLJobSummary (Prelude.Maybe Prelude.UTCTime)
autoMLJobSummary_endTime :: Lens' AutoMLJobSummary (Maybe UTCTime)
autoMLJobSummary_endTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AutoMLJobSummary' {Maybe POSIX
endTime :: Maybe POSIX
$sel:endTime:AutoMLJobSummary' :: AutoMLJobSummary -> Maybe POSIX
endTime} -> Maybe POSIX
endTime) (\s :: AutoMLJobSummary
s@AutoMLJobSummary' {} Maybe POSIX
a -> AutoMLJobSummary
s {$sel:endTime:AutoMLJobSummary' :: Maybe POSIX
endTime = Maybe POSIX
a} :: AutoMLJobSummary) 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 failure reason of an AutoML job.
autoMLJobSummary_failureReason :: Lens.Lens' AutoMLJobSummary (Prelude.Maybe Prelude.Text)
autoMLJobSummary_failureReason :: Lens' AutoMLJobSummary (Maybe Text)
autoMLJobSummary_failureReason = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AutoMLJobSummary' {Maybe Text
failureReason :: Maybe Text
$sel:failureReason:AutoMLJobSummary' :: AutoMLJobSummary -> Maybe Text
failureReason} -> Maybe Text
failureReason) (\s :: AutoMLJobSummary
s@AutoMLJobSummary' {} Maybe Text
a -> AutoMLJobSummary
s {$sel:failureReason:AutoMLJobSummary' :: Maybe Text
failureReason = Maybe Text
a} :: AutoMLJobSummary)

-- | The list of reasons for partial failures within an AutoML job.
autoMLJobSummary_partialFailureReasons :: Lens.Lens' AutoMLJobSummary (Prelude.Maybe (Prelude.NonEmpty AutoMLPartialFailureReason))
autoMLJobSummary_partialFailureReasons :: Lens'
  AutoMLJobSummary (Maybe (NonEmpty AutoMLPartialFailureReason))
autoMLJobSummary_partialFailureReasons = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AutoMLJobSummary' {Maybe (NonEmpty AutoMLPartialFailureReason)
partialFailureReasons :: Maybe (NonEmpty AutoMLPartialFailureReason)
$sel:partialFailureReasons:AutoMLJobSummary' :: AutoMLJobSummary -> Maybe (NonEmpty AutoMLPartialFailureReason)
partialFailureReasons} -> Maybe (NonEmpty AutoMLPartialFailureReason)
partialFailureReasons) (\s :: AutoMLJobSummary
s@AutoMLJobSummary' {} Maybe (NonEmpty AutoMLPartialFailureReason)
a -> AutoMLJobSummary
s {$sel:partialFailureReasons:AutoMLJobSummary' :: Maybe (NonEmpty AutoMLPartialFailureReason)
partialFailureReasons = Maybe (NonEmpty AutoMLPartialFailureReason)
a} :: AutoMLJobSummary) 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

-- | The name of the AutoML job you are requesting.
autoMLJobSummary_autoMLJobName :: Lens.Lens' AutoMLJobSummary Prelude.Text
autoMLJobSummary_autoMLJobName :: Lens' AutoMLJobSummary Text
autoMLJobSummary_autoMLJobName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AutoMLJobSummary' {Text
autoMLJobName :: Text
$sel:autoMLJobName:AutoMLJobSummary' :: AutoMLJobSummary -> Text
autoMLJobName} -> Text
autoMLJobName) (\s :: AutoMLJobSummary
s@AutoMLJobSummary' {} Text
a -> AutoMLJobSummary
s {$sel:autoMLJobName:AutoMLJobSummary' :: Text
autoMLJobName = Text
a} :: AutoMLJobSummary)

-- | The ARN of the AutoML job.
autoMLJobSummary_autoMLJobArn :: Lens.Lens' AutoMLJobSummary Prelude.Text
autoMLJobSummary_autoMLJobArn :: Lens' AutoMLJobSummary Text
autoMLJobSummary_autoMLJobArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AutoMLJobSummary' {Text
autoMLJobArn :: Text
$sel:autoMLJobArn:AutoMLJobSummary' :: AutoMLJobSummary -> Text
autoMLJobArn} -> Text
autoMLJobArn) (\s :: AutoMLJobSummary
s@AutoMLJobSummary' {} Text
a -> AutoMLJobSummary
s {$sel:autoMLJobArn:AutoMLJobSummary' :: Text
autoMLJobArn = Text
a} :: AutoMLJobSummary)

-- | The status of the AutoML job.
autoMLJobSummary_autoMLJobStatus :: Lens.Lens' AutoMLJobSummary AutoMLJobStatus
autoMLJobSummary_autoMLJobStatus :: Lens' AutoMLJobSummary AutoMLJobStatus
autoMLJobSummary_autoMLJobStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AutoMLJobSummary' {AutoMLJobStatus
autoMLJobStatus :: AutoMLJobStatus
$sel:autoMLJobStatus:AutoMLJobSummary' :: AutoMLJobSummary -> AutoMLJobStatus
autoMLJobStatus} -> AutoMLJobStatus
autoMLJobStatus) (\s :: AutoMLJobSummary
s@AutoMLJobSummary' {} AutoMLJobStatus
a -> AutoMLJobSummary
s {$sel:autoMLJobStatus:AutoMLJobSummary' :: AutoMLJobStatus
autoMLJobStatus = AutoMLJobStatus
a} :: AutoMLJobSummary)

-- | The secondary status of the AutoML job.
autoMLJobSummary_autoMLJobSecondaryStatus :: Lens.Lens' AutoMLJobSummary AutoMLJobSecondaryStatus
autoMLJobSummary_autoMLJobSecondaryStatus :: Lens' AutoMLJobSummary AutoMLJobSecondaryStatus
autoMLJobSummary_autoMLJobSecondaryStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AutoMLJobSummary' {AutoMLJobSecondaryStatus
autoMLJobSecondaryStatus :: AutoMLJobSecondaryStatus
$sel:autoMLJobSecondaryStatus:AutoMLJobSummary' :: AutoMLJobSummary -> AutoMLJobSecondaryStatus
autoMLJobSecondaryStatus} -> AutoMLJobSecondaryStatus
autoMLJobSecondaryStatus) (\s :: AutoMLJobSummary
s@AutoMLJobSummary' {} AutoMLJobSecondaryStatus
a -> AutoMLJobSummary
s {$sel:autoMLJobSecondaryStatus:AutoMLJobSummary' :: AutoMLJobSecondaryStatus
autoMLJobSecondaryStatus = AutoMLJobSecondaryStatus
a} :: AutoMLJobSummary)

-- | When the AutoML job was created.
autoMLJobSummary_creationTime :: Lens.Lens' AutoMLJobSummary Prelude.UTCTime
autoMLJobSummary_creationTime :: Lens' AutoMLJobSummary UTCTime
autoMLJobSummary_creationTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AutoMLJobSummary' {POSIX
creationTime :: POSIX
$sel:creationTime:AutoMLJobSummary' :: AutoMLJobSummary -> POSIX
creationTime} -> POSIX
creationTime) (\s :: AutoMLJobSummary
s@AutoMLJobSummary' {} POSIX
a -> AutoMLJobSummary
s {$sel:creationTime:AutoMLJobSummary' :: POSIX
creationTime = POSIX
a} :: AutoMLJobSummary) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (a :: Format). Iso' (Time a) UTCTime
Data._Time

-- | When the AutoML job was last modified.
autoMLJobSummary_lastModifiedTime :: Lens.Lens' AutoMLJobSummary Prelude.UTCTime
autoMLJobSummary_lastModifiedTime :: Lens' AutoMLJobSummary UTCTime
autoMLJobSummary_lastModifiedTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AutoMLJobSummary' {POSIX
lastModifiedTime :: POSIX
$sel:lastModifiedTime:AutoMLJobSummary' :: AutoMLJobSummary -> POSIX
lastModifiedTime} -> POSIX
lastModifiedTime) (\s :: AutoMLJobSummary
s@AutoMLJobSummary' {} POSIX
a -> AutoMLJobSummary
s {$sel:lastModifiedTime:AutoMLJobSummary' :: POSIX
lastModifiedTime = POSIX
a} :: AutoMLJobSummary) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (a :: Format). Iso' (Time a) UTCTime
Data._Time

instance Data.FromJSON AutoMLJobSummary where
  parseJSON :: Value -> Parser AutoMLJobSummary
parseJSON =
    forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.withObject
      String
"AutoMLJobSummary"
      ( \Object
x ->
          Maybe POSIX
-> Maybe Text
-> Maybe (NonEmpty AutoMLPartialFailureReason)
-> Text
-> Text
-> AutoMLJobStatus
-> AutoMLJobSecondaryStatus
-> POSIX
-> POSIX
-> AutoMLJobSummary
AutoMLJobSummary'
            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
"EndTime")
            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
"FailureReason")
            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
"PartialFailureReasons")
            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
"AutoMLJobName")
            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
"AutoMLJobArn")
            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
"AutoMLJobStatus")
            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
"AutoMLJobSecondaryStatus")
            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
"LastModifiedTime")
      )

instance Prelude.Hashable AutoMLJobSummary where
  hashWithSalt :: Int -> AutoMLJobSummary -> Int
hashWithSalt Int
_salt AutoMLJobSummary' {Maybe (NonEmpty AutoMLPartialFailureReason)
Maybe Text
Maybe POSIX
Text
POSIX
AutoMLJobSecondaryStatus
AutoMLJobStatus
lastModifiedTime :: POSIX
creationTime :: POSIX
autoMLJobSecondaryStatus :: AutoMLJobSecondaryStatus
autoMLJobStatus :: AutoMLJobStatus
autoMLJobArn :: Text
autoMLJobName :: Text
partialFailureReasons :: Maybe (NonEmpty AutoMLPartialFailureReason)
failureReason :: Maybe Text
endTime :: Maybe POSIX
$sel:lastModifiedTime:AutoMLJobSummary' :: AutoMLJobSummary -> POSIX
$sel:creationTime:AutoMLJobSummary' :: AutoMLJobSummary -> POSIX
$sel:autoMLJobSecondaryStatus:AutoMLJobSummary' :: AutoMLJobSummary -> AutoMLJobSecondaryStatus
$sel:autoMLJobStatus:AutoMLJobSummary' :: AutoMLJobSummary -> AutoMLJobStatus
$sel:autoMLJobArn:AutoMLJobSummary' :: AutoMLJobSummary -> Text
$sel:autoMLJobName:AutoMLJobSummary' :: AutoMLJobSummary -> Text
$sel:partialFailureReasons:AutoMLJobSummary' :: AutoMLJobSummary -> Maybe (NonEmpty AutoMLPartialFailureReason)
$sel:failureReason:AutoMLJobSummary' :: AutoMLJobSummary -> Maybe Text
$sel:endTime:AutoMLJobSummary' :: AutoMLJobSummary -> Maybe POSIX
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe POSIX
endTime
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
failureReason
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe (NonEmpty AutoMLPartialFailureReason)
partialFailureReasons
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
autoMLJobName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
autoMLJobArn
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` AutoMLJobStatus
autoMLJobStatus
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` AutoMLJobSecondaryStatus
autoMLJobSecondaryStatus
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` POSIX
creationTime
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` POSIX
lastModifiedTime

instance Prelude.NFData AutoMLJobSummary where
  rnf :: AutoMLJobSummary -> ()
rnf AutoMLJobSummary' {Maybe (NonEmpty AutoMLPartialFailureReason)
Maybe Text
Maybe POSIX
Text
POSIX
AutoMLJobSecondaryStatus
AutoMLJobStatus
lastModifiedTime :: POSIX
creationTime :: POSIX
autoMLJobSecondaryStatus :: AutoMLJobSecondaryStatus
autoMLJobStatus :: AutoMLJobStatus
autoMLJobArn :: Text
autoMLJobName :: Text
partialFailureReasons :: Maybe (NonEmpty AutoMLPartialFailureReason)
failureReason :: Maybe Text
endTime :: Maybe POSIX
$sel:lastModifiedTime:AutoMLJobSummary' :: AutoMLJobSummary -> POSIX
$sel:creationTime:AutoMLJobSummary' :: AutoMLJobSummary -> POSIX
$sel:autoMLJobSecondaryStatus:AutoMLJobSummary' :: AutoMLJobSummary -> AutoMLJobSecondaryStatus
$sel:autoMLJobStatus:AutoMLJobSummary' :: AutoMLJobSummary -> AutoMLJobStatus
$sel:autoMLJobArn:AutoMLJobSummary' :: AutoMLJobSummary -> Text
$sel:autoMLJobName:AutoMLJobSummary' :: AutoMLJobSummary -> Text
$sel:partialFailureReasons:AutoMLJobSummary' :: AutoMLJobSummary -> Maybe (NonEmpty AutoMLPartialFailureReason)
$sel:failureReason:AutoMLJobSummary' :: AutoMLJobSummary -> Maybe Text
$sel:endTime:AutoMLJobSummary' :: AutoMLJobSummary -> Maybe POSIX
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe POSIX
endTime
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
failureReason
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe (NonEmpty AutoMLPartialFailureReason)
partialFailureReasons
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
autoMLJobName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
autoMLJobArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf AutoMLJobStatus
autoMLJobStatus
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf AutoMLJobSecondaryStatus
autoMLJobSecondaryStatus
      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 POSIX
lastModifiedTime