{-# 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.AutoMLCandidate
-- 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.AutoMLCandidate 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.AutoMLCandidateStep
import Amazonka.SageMaker.Types.AutoMLContainerDefinition
import Amazonka.SageMaker.Types.CandidateProperties
import Amazonka.SageMaker.Types.CandidateStatus
import Amazonka.SageMaker.Types.FinalAutoMLJobObjectiveMetric
import Amazonka.SageMaker.Types.ObjectiveStatus

-- | Information about a candidate produced by an AutoML training job,
-- including its status, steps, and other properties.
--
-- /See:/ 'newAutoMLCandidate' smart constructor.
data AutoMLCandidate = AutoMLCandidate'
  { -- | The properties of an AutoML candidate job.
    AutoMLCandidate -> Maybe CandidateProperties
candidateProperties :: Prelude.Maybe CandidateProperties,
    -- | The end time.
    AutoMLCandidate -> Maybe POSIX
endTime :: Prelude.Maybe Data.POSIX,
    -- | The failure reason.
    AutoMLCandidate -> Maybe Text
failureReason :: Prelude.Maybe Prelude.Text,
    AutoMLCandidate -> Maybe FinalAutoMLJobObjectiveMetric
finalAutoMLJobObjectiveMetric :: Prelude.Maybe FinalAutoMLJobObjectiveMetric,
    -- | Information about the inference container definitions.
    AutoMLCandidate -> Maybe [AutoMLContainerDefinition]
inferenceContainers :: Prelude.Maybe [AutoMLContainerDefinition],
    -- | The name of the candidate.
    AutoMLCandidate -> Text
candidateName :: Prelude.Text,
    -- | The objective\'s status.
    AutoMLCandidate -> ObjectiveStatus
objectiveStatus :: ObjectiveStatus,
    -- | Information about the candidate\'s steps.
    AutoMLCandidate -> [AutoMLCandidateStep]
candidateSteps :: [AutoMLCandidateStep],
    -- | The candidate\'s status.
    AutoMLCandidate -> CandidateStatus
candidateStatus :: CandidateStatus,
    -- | The creation time.
    AutoMLCandidate -> POSIX
creationTime :: Data.POSIX,
    -- | The last modified time.
    AutoMLCandidate -> POSIX
lastModifiedTime :: Data.POSIX
  }
  deriving (AutoMLCandidate -> AutoMLCandidate -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AutoMLCandidate -> AutoMLCandidate -> Bool
$c/= :: AutoMLCandidate -> AutoMLCandidate -> Bool
== :: AutoMLCandidate -> AutoMLCandidate -> Bool
$c== :: AutoMLCandidate -> AutoMLCandidate -> Bool
Prelude.Eq, ReadPrec [AutoMLCandidate]
ReadPrec AutoMLCandidate
Int -> ReadS AutoMLCandidate
ReadS [AutoMLCandidate]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [AutoMLCandidate]
$creadListPrec :: ReadPrec [AutoMLCandidate]
readPrec :: ReadPrec AutoMLCandidate
$creadPrec :: ReadPrec AutoMLCandidate
readList :: ReadS [AutoMLCandidate]
$creadList :: ReadS [AutoMLCandidate]
readsPrec :: Int -> ReadS AutoMLCandidate
$creadsPrec :: Int -> ReadS AutoMLCandidate
Prelude.Read, Int -> AutoMLCandidate -> ShowS
[AutoMLCandidate] -> ShowS
AutoMLCandidate -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [AutoMLCandidate] -> ShowS
$cshowList :: [AutoMLCandidate] -> ShowS
show :: AutoMLCandidate -> String
$cshow :: AutoMLCandidate -> String
showsPrec :: Int -> AutoMLCandidate -> ShowS
$cshowsPrec :: Int -> AutoMLCandidate -> ShowS
Prelude.Show, forall x. Rep AutoMLCandidate x -> AutoMLCandidate
forall x. AutoMLCandidate -> Rep AutoMLCandidate x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep AutoMLCandidate x -> AutoMLCandidate
$cfrom :: forall x. AutoMLCandidate -> Rep AutoMLCandidate x
Prelude.Generic)

-- |
-- Create a value of 'AutoMLCandidate' 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:
--
-- 'candidateProperties', 'autoMLCandidate_candidateProperties' - The properties of an AutoML candidate job.
--
-- 'endTime', 'autoMLCandidate_endTime' - The end time.
--
-- 'failureReason', 'autoMLCandidate_failureReason' - The failure reason.
--
-- 'finalAutoMLJobObjectiveMetric', 'autoMLCandidate_finalAutoMLJobObjectiveMetric' - Undocumented member.
--
-- 'inferenceContainers', 'autoMLCandidate_inferenceContainers' - Information about the inference container definitions.
--
-- 'candidateName', 'autoMLCandidate_candidateName' - The name of the candidate.
--
-- 'objectiveStatus', 'autoMLCandidate_objectiveStatus' - The objective\'s status.
--
-- 'candidateSteps', 'autoMLCandidate_candidateSteps' - Information about the candidate\'s steps.
--
-- 'candidateStatus', 'autoMLCandidate_candidateStatus' - The candidate\'s status.
--
-- 'creationTime', 'autoMLCandidate_creationTime' - The creation time.
--
-- 'lastModifiedTime', 'autoMLCandidate_lastModifiedTime' - The last modified time.
newAutoMLCandidate ::
  -- | 'candidateName'
  Prelude.Text ->
  -- | 'objectiveStatus'
  ObjectiveStatus ->
  -- | 'candidateStatus'
  CandidateStatus ->
  -- | 'creationTime'
  Prelude.UTCTime ->
  -- | 'lastModifiedTime'
  Prelude.UTCTime ->
  AutoMLCandidate
newAutoMLCandidate :: Text
-> ObjectiveStatus
-> CandidateStatus
-> UTCTime
-> UTCTime
-> AutoMLCandidate
newAutoMLCandidate
  Text
pCandidateName_
  ObjectiveStatus
pObjectiveStatus_
  CandidateStatus
pCandidateStatus_
  UTCTime
pCreationTime_
  UTCTime
pLastModifiedTime_ =
    AutoMLCandidate'
      { $sel:candidateProperties:AutoMLCandidate' :: Maybe CandidateProperties
candidateProperties =
          forall a. Maybe a
Prelude.Nothing,
        $sel:endTime:AutoMLCandidate' :: Maybe POSIX
endTime = forall a. Maybe a
Prelude.Nothing,
        $sel:failureReason:AutoMLCandidate' :: Maybe Text
failureReason = forall a. Maybe a
Prelude.Nothing,
        $sel:finalAutoMLJobObjectiveMetric:AutoMLCandidate' :: Maybe FinalAutoMLJobObjectiveMetric
finalAutoMLJobObjectiveMetric = forall a. Maybe a
Prelude.Nothing,
        $sel:inferenceContainers:AutoMLCandidate' :: Maybe [AutoMLContainerDefinition]
inferenceContainers = forall a. Maybe a
Prelude.Nothing,
        $sel:candidateName:AutoMLCandidate' :: Text
candidateName = Text
pCandidateName_,
        $sel:objectiveStatus:AutoMLCandidate' :: ObjectiveStatus
objectiveStatus = ObjectiveStatus
pObjectiveStatus_,
        $sel:candidateSteps:AutoMLCandidate' :: [AutoMLCandidateStep]
candidateSteps = forall a. Monoid a => a
Prelude.mempty,
        $sel:candidateStatus:AutoMLCandidate' :: CandidateStatus
candidateStatus = CandidateStatus
pCandidateStatus_,
        $sel:creationTime:AutoMLCandidate' :: POSIX
creationTime = forall (a :: Format). Iso' (Time a) UTCTime
Data._Time forall t b. AReview t b -> b -> t
Lens.# UTCTime
pCreationTime_,
        $sel:lastModifiedTime:AutoMLCandidate' :: POSIX
lastModifiedTime =
          forall (a :: Format). Iso' (Time a) UTCTime
Data._Time forall t b. AReview t b -> b -> t
Lens.# UTCTime
pLastModifiedTime_
      }

-- | The properties of an AutoML candidate job.
autoMLCandidate_candidateProperties :: Lens.Lens' AutoMLCandidate (Prelude.Maybe CandidateProperties)
autoMLCandidate_candidateProperties :: Lens' AutoMLCandidate (Maybe CandidateProperties)
autoMLCandidate_candidateProperties = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AutoMLCandidate' {Maybe CandidateProperties
candidateProperties :: Maybe CandidateProperties
$sel:candidateProperties:AutoMLCandidate' :: AutoMLCandidate -> Maybe CandidateProperties
candidateProperties} -> Maybe CandidateProperties
candidateProperties) (\s :: AutoMLCandidate
s@AutoMLCandidate' {} Maybe CandidateProperties
a -> AutoMLCandidate
s {$sel:candidateProperties:AutoMLCandidate' :: Maybe CandidateProperties
candidateProperties = Maybe CandidateProperties
a} :: AutoMLCandidate)

-- | The end time.
autoMLCandidate_endTime :: Lens.Lens' AutoMLCandidate (Prelude.Maybe Prelude.UTCTime)
autoMLCandidate_endTime :: Lens' AutoMLCandidate (Maybe UTCTime)
autoMLCandidate_endTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AutoMLCandidate' {Maybe POSIX
endTime :: Maybe POSIX
$sel:endTime:AutoMLCandidate' :: AutoMLCandidate -> Maybe POSIX
endTime} -> Maybe POSIX
endTime) (\s :: AutoMLCandidate
s@AutoMLCandidate' {} Maybe POSIX
a -> AutoMLCandidate
s {$sel:endTime:AutoMLCandidate' :: Maybe POSIX
endTime = Maybe POSIX
a} :: AutoMLCandidate) 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.
autoMLCandidate_failureReason :: Lens.Lens' AutoMLCandidate (Prelude.Maybe Prelude.Text)
autoMLCandidate_failureReason :: Lens' AutoMLCandidate (Maybe Text)
autoMLCandidate_failureReason = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AutoMLCandidate' {Maybe Text
failureReason :: Maybe Text
$sel:failureReason:AutoMLCandidate' :: AutoMLCandidate -> Maybe Text
failureReason} -> Maybe Text
failureReason) (\s :: AutoMLCandidate
s@AutoMLCandidate' {} Maybe Text
a -> AutoMLCandidate
s {$sel:failureReason:AutoMLCandidate' :: Maybe Text
failureReason = Maybe Text
a} :: AutoMLCandidate)

-- | Undocumented member.
autoMLCandidate_finalAutoMLJobObjectiveMetric :: Lens.Lens' AutoMLCandidate (Prelude.Maybe FinalAutoMLJobObjectiveMetric)
autoMLCandidate_finalAutoMLJobObjectiveMetric :: Lens' AutoMLCandidate (Maybe FinalAutoMLJobObjectiveMetric)
autoMLCandidate_finalAutoMLJobObjectiveMetric = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AutoMLCandidate' {Maybe FinalAutoMLJobObjectiveMetric
finalAutoMLJobObjectiveMetric :: Maybe FinalAutoMLJobObjectiveMetric
$sel:finalAutoMLJobObjectiveMetric:AutoMLCandidate' :: AutoMLCandidate -> Maybe FinalAutoMLJobObjectiveMetric
finalAutoMLJobObjectiveMetric} -> Maybe FinalAutoMLJobObjectiveMetric
finalAutoMLJobObjectiveMetric) (\s :: AutoMLCandidate
s@AutoMLCandidate' {} Maybe FinalAutoMLJobObjectiveMetric
a -> AutoMLCandidate
s {$sel:finalAutoMLJobObjectiveMetric:AutoMLCandidate' :: Maybe FinalAutoMLJobObjectiveMetric
finalAutoMLJobObjectiveMetric = Maybe FinalAutoMLJobObjectiveMetric
a} :: AutoMLCandidate)

-- | Information about the inference container definitions.
autoMLCandidate_inferenceContainers :: Lens.Lens' AutoMLCandidate (Prelude.Maybe [AutoMLContainerDefinition])
autoMLCandidate_inferenceContainers :: Lens' AutoMLCandidate (Maybe [AutoMLContainerDefinition])
autoMLCandidate_inferenceContainers = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AutoMLCandidate' {Maybe [AutoMLContainerDefinition]
inferenceContainers :: Maybe [AutoMLContainerDefinition]
$sel:inferenceContainers:AutoMLCandidate' :: AutoMLCandidate -> Maybe [AutoMLContainerDefinition]
inferenceContainers} -> Maybe [AutoMLContainerDefinition]
inferenceContainers) (\s :: AutoMLCandidate
s@AutoMLCandidate' {} Maybe [AutoMLContainerDefinition]
a -> AutoMLCandidate
s {$sel:inferenceContainers:AutoMLCandidate' :: Maybe [AutoMLContainerDefinition]
inferenceContainers = Maybe [AutoMLContainerDefinition]
a} :: AutoMLCandidate) 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 candidate.
autoMLCandidate_candidateName :: Lens.Lens' AutoMLCandidate Prelude.Text
autoMLCandidate_candidateName :: Lens' AutoMLCandidate Text
autoMLCandidate_candidateName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AutoMLCandidate' {Text
candidateName :: Text
$sel:candidateName:AutoMLCandidate' :: AutoMLCandidate -> Text
candidateName} -> Text
candidateName) (\s :: AutoMLCandidate
s@AutoMLCandidate' {} Text
a -> AutoMLCandidate
s {$sel:candidateName:AutoMLCandidate' :: Text
candidateName = Text
a} :: AutoMLCandidate)

-- | The objective\'s status.
autoMLCandidate_objectiveStatus :: Lens.Lens' AutoMLCandidate ObjectiveStatus
autoMLCandidate_objectiveStatus :: Lens' AutoMLCandidate ObjectiveStatus
autoMLCandidate_objectiveStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AutoMLCandidate' {ObjectiveStatus
objectiveStatus :: ObjectiveStatus
$sel:objectiveStatus:AutoMLCandidate' :: AutoMLCandidate -> ObjectiveStatus
objectiveStatus} -> ObjectiveStatus
objectiveStatus) (\s :: AutoMLCandidate
s@AutoMLCandidate' {} ObjectiveStatus
a -> AutoMLCandidate
s {$sel:objectiveStatus:AutoMLCandidate' :: ObjectiveStatus
objectiveStatus = ObjectiveStatus
a} :: AutoMLCandidate)

-- | Information about the candidate\'s steps.
autoMLCandidate_candidateSteps :: Lens.Lens' AutoMLCandidate [AutoMLCandidateStep]
autoMLCandidate_candidateSteps :: Lens' AutoMLCandidate [AutoMLCandidateStep]
autoMLCandidate_candidateSteps = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AutoMLCandidate' {[AutoMLCandidateStep]
candidateSteps :: [AutoMLCandidateStep]
$sel:candidateSteps:AutoMLCandidate' :: AutoMLCandidate -> [AutoMLCandidateStep]
candidateSteps} -> [AutoMLCandidateStep]
candidateSteps) (\s :: AutoMLCandidate
s@AutoMLCandidate' {} [AutoMLCandidateStep]
a -> AutoMLCandidate
s {$sel:candidateSteps:AutoMLCandidate' :: [AutoMLCandidateStep]
candidateSteps = [AutoMLCandidateStep]
a} :: AutoMLCandidate) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

-- | The candidate\'s status.
autoMLCandidate_candidateStatus :: Lens.Lens' AutoMLCandidate CandidateStatus
autoMLCandidate_candidateStatus :: Lens' AutoMLCandidate CandidateStatus
autoMLCandidate_candidateStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AutoMLCandidate' {CandidateStatus
candidateStatus :: CandidateStatus
$sel:candidateStatus:AutoMLCandidate' :: AutoMLCandidate -> CandidateStatus
candidateStatus} -> CandidateStatus
candidateStatus) (\s :: AutoMLCandidate
s@AutoMLCandidate' {} CandidateStatus
a -> AutoMLCandidate
s {$sel:candidateStatus:AutoMLCandidate' :: CandidateStatus
candidateStatus = CandidateStatus
a} :: AutoMLCandidate)

-- | The creation time.
autoMLCandidate_creationTime :: Lens.Lens' AutoMLCandidate Prelude.UTCTime
autoMLCandidate_creationTime :: Lens' AutoMLCandidate UTCTime
autoMLCandidate_creationTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AutoMLCandidate' {POSIX
creationTime :: POSIX
$sel:creationTime:AutoMLCandidate' :: AutoMLCandidate -> POSIX
creationTime} -> POSIX
creationTime) (\s :: AutoMLCandidate
s@AutoMLCandidate' {} POSIX
a -> AutoMLCandidate
s {$sel:creationTime:AutoMLCandidate' :: POSIX
creationTime = POSIX
a} :: AutoMLCandidate) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (a :: Format). Iso' (Time a) UTCTime
Data._Time

-- | The last modified time.
autoMLCandidate_lastModifiedTime :: Lens.Lens' AutoMLCandidate Prelude.UTCTime
autoMLCandidate_lastModifiedTime :: Lens' AutoMLCandidate UTCTime
autoMLCandidate_lastModifiedTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AutoMLCandidate' {POSIX
lastModifiedTime :: POSIX
$sel:lastModifiedTime:AutoMLCandidate' :: AutoMLCandidate -> POSIX
lastModifiedTime} -> POSIX
lastModifiedTime) (\s :: AutoMLCandidate
s@AutoMLCandidate' {} POSIX
a -> AutoMLCandidate
s {$sel:lastModifiedTime:AutoMLCandidate' :: POSIX
lastModifiedTime = POSIX
a} :: AutoMLCandidate) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (a :: Format). Iso' (Time a) UTCTime
Data._Time

instance Data.FromJSON AutoMLCandidate where
  parseJSON :: Value -> Parser AutoMLCandidate
parseJSON =
    forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.withObject
      String
"AutoMLCandidate"
      ( \Object
x ->
          Maybe CandidateProperties
-> Maybe POSIX
-> Maybe Text
-> Maybe FinalAutoMLJobObjectiveMetric
-> Maybe [AutoMLContainerDefinition]
-> Text
-> ObjectiveStatus
-> [AutoMLCandidateStep]
-> CandidateStatus
-> POSIX
-> POSIX
-> AutoMLCandidate
AutoMLCandidate'
            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
"CandidateProperties")
            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
"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
"FinalAutoMLJobObjectiveMetric")
            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
"InferenceContainers"
                            forall a. Parser (Maybe a) -> a -> Parser a
Data..!= forall a. Monoid a => a
Prelude.mempty
                        )
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser a
Data..: Key
"CandidateName")
            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
"ObjectiveStatus")
            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
"CandidateSteps" forall a. Parser (Maybe a) -> a -> Parser a
Data..!= forall a. Monoid a => a
Prelude.mempty)
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser a
Data..: Key
"CandidateStatus")
            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 AutoMLCandidate where
  hashWithSalt :: Int -> AutoMLCandidate -> Int
hashWithSalt Int
_salt AutoMLCandidate' {[AutoMLCandidateStep]
Maybe [AutoMLContainerDefinition]
Maybe Text
Maybe POSIX
Maybe FinalAutoMLJobObjectiveMetric
Maybe CandidateProperties
Text
POSIX
CandidateStatus
ObjectiveStatus
lastModifiedTime :: POSIX
creationTime :: POSIX
candidateStatus :: CandidateStatus
candidateSteps :: [AutoMLCandidateStep]
objectiveStatus :: ObjectiveStatus
candidateName :: Text
inferenceContainers :: Maybe [AutoMLContainerDefinition]
finalAutoMLJobObjectiveMetric :: Maybe FinalAutoMLJobObjectiveMetric
failureReason :: Maybe Text
endTime :: Maybe POSIX
candidateProperties :: Maybe CandidateProperties
$sel:lastModifiedTime:AutoMLCandidate' :: AutoMLCandidate -> POSIX
$sel:creationTime:AutoMLCandidate' :: AutoMLCandidate -> POSIX
$sel:candidateStatus:AutoMLCandidate' :: AutoMLCandidate -> CandidateStatus
$sel:candidateSteps:AutoMLCandidate' :: AutoMLCandidate -> [AutoMLCandidateStep]
$sel:objectiveStatus:AutoMLCandidate' :: AutoMLCandidate -> ObjectiveStatus
$sel:candidateName:AutoMLCandidate' :: AutoMLCandidate -> Text
$sel:inferenceContainers:AutoMLCandidate' :: AutoMLCandidate -> Maybe [AutoMLContainerDefinition]
$sel:finalAutoMLJobObjectiveMetric:AutoMLCandidate' :: AutoMLCandidate -> Maybe FinalAutoMLJobObjectiveMetric
$sel:failureReason:AutoMLCandidate' :: AutoMLCandidate -> Maybe Text
$sel:endTime:AutoMLCandidate' :: AutoMLCandidate -> Maybe POSIX
$sel:candidateProperties:AutoMLCandidate' :: AutoMLCandidate -> Maybe CandidateProperties
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe CandidateProperties
candidateProperties
      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 FinalAutoMLJobObjectiveMetric
finalAutoMLJobObjectiveMetric
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [AutoMLContainerDefinition]
inferenceContainers
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
candidateName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` ObjectiveStatus
objectiveStatus
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` [AutoMLCandidateStep]
candidateSteps
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` CandidateStatus
candidateStatus
      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 AutoMLCandidate where
  rnf :: AutoMLCandidate -> ()
rnf AutoMLCandidate' {[AutoMLCandidateStep]
Maybe [AutoMLContainerDefinition]
Maybe Text
Maybe POSIX
Maybe FinalAutoMLJobObjectiveMetric
Maybe CandidateProperties
Text
POSIX
CandidateStatus
ObjectiveStatus
lastModifiedTime :: POSIX
creationTime :: POSIX
candidateStatus :: CandidateStatus
candidateSteps :: [AutoMLCandidateStep]
objectiveStatus :: ObjectiveStatus
candidateName :: Text
inferenceContainers :: Maybe [AutoMLContainerDefinition]
finalAutoMLJobObjectiveMetric :: Maybe FinalAutoMLJobObjectiveMetric
failureReason :: Maybe Text
endTime :: Maybe POSIX
candidateProperties :: Maybe CandidateProperties
$sel:lastModifiedTime:AutoMLCandidate' :: AutoMLCandidate -> POSIX
$sel:creationTime:AutoMLCandidate' :: AutoMLCandidate -> POSIX
$sel:candidateStatus:AutoMLCandidate' :: AutoMLCandidate -> CandidateStatus
$sel:candidateSteps:AutoMLCandidate' :: AutoMLCandidate -> [AutoMLCandidateStep]
$sel:objectiveStatus:AutoMLCandidate' :: AutoMLCandidate -> ObjectiveStatus
$sel:candidateName:AutoMLCandidate' :: AutoMLCandidate -> Text
$sel:inferenceContainers:AutoMLCandidate' :: AutoMLCandidate -> Maybe [AutoMLContainerDefinition]
$sel:finalAutoMLJobObjectiveMetric:AutoMLCandidate' :: AutoMLCandidate -> Maybe FinalAutoMLJobObjectiveMetric
$sel:failureReason:AutoMLCandidate' :: AutoMLCandidate -> Maybe Text
$sel:endTime:AutoMLCandidate' :: AutoMLCandidate -> Maybe POSIX
$sel:candidateProperties:AutoMLCandidate' :: AutoMLCandidate -> Maybe CandidateProperties
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe CandidateProperties
candidateProperties
      seq :: forall a b. a -> b -> b
`Prelude.seq` 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 FinalAutoMLJobObjectiveMetric
finalAutoMLJobObjectiveMetric
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [AutoMLContainerDefinition]
inferenceContainers
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
candidateName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf ObjectiveStatus
objectiveStatus
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf [AutoMLCandidateStep]
candidateSteps
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf CandidateStatus
candidateStatus
      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