{-# 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 #-}
module Amazonka.SageMaker.Types.TrainingJob 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.AlgorithmSpecification
import Amazonka.SageMaker.Types.Channel
import Amazonka.SageMaker.Types.CheckpointConfig
import Amazonka.SageMaker.Types.DebugHookConfig
import Amazonka.SageMaker.Types.DebugRuleConfiguration
import Amazonka.SageMaker.Types.DebugRuleEvaluationStatus
import Amazonka.SageMaker.Types.ExperimentConfig
import Amazonka.SageMaker.Types.MetricData
import Amazonka.SageMaker.Types.ModelArtifacts
import Amazonka.SageMaker.Types.OutputDataConfig
import Amazonka.SageMaker.Types.ResourceConfig
import Amazonka.SageMaker.Types.RetryStrategy
import Amazonka.SageMaker.Types.SecondaryStatus
import Amazonka.SageMaker.Types.SecondaryStatusTransition
import Amazonka.SageMaker.Types.StoppingCondition
import Amazonka.SageMaker.Types.Tag
import Amazonka.SageMaker.Types.TensorBoardOutputConfig
import Amazonka.SageMaker.Types.TrainingJobStatus
import Amazonka.SageMaker.Types.VpcConfig
data TrainingJob = TrainingJob'
  { 
    
    TrainingJob -> Maybe AlgorithmSpecification
algorithmSpecification :: Prelude.Maybe AlgorithmSpecification,
    
    TrainingJob -> Maybe Text
autoMLJobArn :: Prelude.Maybe Prelude.Text,
    
    TrainingJob -> Maybe Natural
billableTimeInSeconds :: Prelude.Maybe Prelude.Natural,
    TrainingJob -> Maybe CheckpointConfig
checkpointConfig :: Prelude.Maybe CheckpointConfig,
    
    TrainingJob -> Maybe POSIX
creationTime :: Prelude.Maybe Data.POSIX,
    TrainingJob -> Maybe DebugHookConfig
debugHookConfig :: Prelude.Maybe DebugHookConfig,
    
    TrainingJob -> Maybe [DebugRuleConfiguration]
debugRuleConfigurations :: Prelude.Maybe [DebugRuleConfiguration],
    
    
    TrainingJob -> Maybe [DebugRuleEvaluationStatus]
debugRuleEvaluationStatuses :: Prelude.Maybe [DebugRuleEvaluationStatus],
    
    
    
    
    
    
    TrainingJob -> Maybe Bool
enableInterContainerTrafficEncryption :: Prelude.Maybe Prelude.Bool,
    
    
    
    
    TrainingJob -> Maybe Bool
enableManagedSpotTraining :: Prelude.Maybe Prelude.Bool,
    
    
    
    TrainingJob -> Maybe Bool
enableNetworkIsolation :: Prelude.Maybe Prelude.Bool,
    
    TrainingJob -> Maybe (HashMap Text Text)
environment :: Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text),
    TrainingJob -> Maybe ExperimentConfig
experimentConfig :: Prelude.Maybe ExperimentConfig,
    
    TrainingJob -> Maybe Text
failureReason :: Prelude.Maybe Prelude.Text,
    
    
    TrainingJob -> Maybe [MetricData]
finalMetricDataList :: Prelude.Maybe [MetricData],
    
    TrainingJob -> Maybe (HashMap Text Text)
hyperParameters :: Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text),
    
    TrainingJob -> Maybe (NonEmpty Channel)
inputDataConfig :: Prelude.Maybe (Prelude.NonEmpty Channel),
    
    TrainingJob -> Maybe Text
labelingJobArn :: Prelude.Maybe Prelude.Text,
    
    
    TrainingJob -> Maybe POSIX
lastModifiedTime :: Prelude.Maybe Data.POSIX,
    
    
    TrainingJob -> Maybe ModelArtifacts
modelArtifacts :: Prelude.Maybe ModelArtifacts,
    
    
    TrainingJob -> Maybe OutputDataConfig
outputDataConfig :: Prelude.Maybe OutputDataConfig,
    
    
    TrainingJob -> Maybe ResourceConfig
resourceConfig :: Prelude.Maybe ResourceConfig,
    
    
    TrainingJob -> Maybe RetryStrategy
retryStrategy :: Prelude.Maybe RetryStrategy,
    
    
    TrainingJob -> Maybe Text
roleArn :: Prelude.Maybe Prelude.Text,
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    TrainingJob -> Maybe SecondaryStatus
secondaryStatus :: Prelude.Maybe SecondaryStatus,
    
    
    TrainingJob -> Maybe [SecondaryStatusTransition]
secondaryStatusTransitions :: Prelude.Maybe [SecondaryStatusTransition],
    
    
    
    
    
    
    
    
    
    TrainingJob -> Maybe StoppingCondition
stoppingCondition :: Prelude.Maybe StoppingCondition,
    
    
    
    
    TrainingJob -> Maybe [Tag]
tags :: Prelude.Maybe [Tag],
    TrainingJob -> Maybe TensorBoardOutputConfig
tensorBoardOutputConfig :: Prelude.Maybe TensorBoardOutputConfig,
    
    
    
    
    
    TrainingJob -> Maybe POSIX
trainingEndTime :: Prelude.Maybe Data.POSIX,
    
    TrainingJob -> Maybe Text
trainingJobArn :: Prelude.Maybe Prelude.Text,
    
    TrainingJob -> Maybe Text
trainingJobName :: Prelude.Maybe Prelude.Text,
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    TrainingJob -> Maybe TrainingJobStatus
trainingJobStatus :: Prelude.Maybe TrainingJobStatus,
    
    
    
    
    
    TrainingJob -> Maybe POSIX
trainingStartTime :: Prelude.Maybe Data.POSIX,
    
    TrainingJob -> Maybe Natural
trainingTimeInSeconds :: Prelude.Maybe Prelude.Natural,
    
    
    TrainingJob -> Maybe Text
tuningJobArn :: Prelude.Maybe Prelude.Text,
    
    
    
    TrainingJob -> Maybe VpcConfig
vpcConfig :: Prelude.Maybe VpcConfig
  }
  deriving (TrainingJob -> TrainingJob -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TrainingJob -> TrainingJob -> Bool
$c/= :: TrainingJob -> TrainingJob -> Bool
== :: TrainingJob -> TrainingJob -> Bool
$c== :: TrainingJob -> TrainingJob -> Bool
Prelude.Eq, ReadPrec [TrainingJob]
ReadPrec TrainingJob
Int -> ReadS TrainingJob
ReadS [TrainingJob]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [TrainingJob]
$creadListPrec :: ReadPrec [TrainingJob]
readPrec :: ReadPrec TrainingJob
$creadPrec :: ReadPrec TrainingJob
readList :: ReadS [TrainingJob]
$creadList :: ReadS [TrainingJob]
readsPrec :: Int -> ReadS TrainingJob
$creadsPrec :: Int -> ReadS TrainingJob
Prelude.Read, Int -> TrainingJob -> ShowS
[TrainingJob] -> ShowS
TrainingJob -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TrainingJob] -> ShowS
$cshowList :: [TrainingJob] -> ShowS
show :: TrainingJob -> String
$cshow :: TrainingJob -> String
showsPrec :: Int -> TrainingJob -> ShowS
$cshowsPrec :: Int -> TrainingJob -> ShowS
Prelude.Show, forall x. Rep TrainingJob x -> TrainingJob
forall x. TrainingJob -> Rep TrainingJob x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep TrainingJob x -> TrainingJob
$cfrom :: forall x. TrainingJob -> Rep TrainingJob x
Prelude.Generic)
newTrainingJob ::
  TrainingJob
newTrainingJob :: TrainingJob
newTrainingJob =
  TrainingJob'
    { $sel:algorithmSpecification:TrainingJob' :: Maybe AlgorithmSpecification
algorithmSpecification =
        forall a. Maybe a
Prelude.Nothing,
      $sel:autoMLJobArn:TrainingJob' :: Maybe Text
autoMLJobArn = forall a. Maybe a
Prelude.Nothing,
      $sel:billableTimeInSeconds:TrainingJob' :: Maybe Natural
billableTimeInSeconds = forall a. Maybe a
Prelude.Nothing,
      $sel:checkpointConfig:TrainingJob' :: Maybe CheckpointConfig
checkpointConfig = forall a. Maybe a
Prelude.Nothing,
      $sel:creationTime:TrainingJob' :: Maybe POSIX
creationTime = forall a. Maybe a
Prelude.Nothing,
      $sel:debugHookConfig:TrainingJob' :: Maybe DebugHookConfig
debugHookConfig = forall a. Maybe a
Prelude.Nothing,
      $sel:debugRuleConfigurations:TrainingJob' :: Maybe [DebugRuleConfiguration]
debugRuleConfigurations = forall a. Maybe a
Prelude.Nothing,
      $sel:debugRuleEvaluationStatuses:TrainingJob' :: Maybe [DebugRuleEvaluationStatus]
debugRuleEvaluationStatuses = forall a. Maybe a
Prelude.Nothing,
      $sel:enableInterContainerTrafficEncryption:TrainingJob' :: Maybe Bool
enableInterContainerTrafficEncryption =
        forall a. Maybe a
Prelude.Nothing,
      $sel:enableManagedSpotTraining:TrainingJob' :: Maybe Bool
enableManagedSpotTraining = forall a. Maybe a
Prelude.Nothing,
      $sel:enableNetworkIsolation:TrainingJob' :: Maybe Bool
enableNetworkIsolation = forall a. Maybe a
Prelude.Nothing,
      $sel:environment:TrainingJob' :: Maybe (HashMap Text Text)
environment = forall a. Maybe a
Prelude.Nothing,
      $sel:experimentConfig:TrainingJob' :: Maybe ExperimentConfig
experimentConfig = forall a. Maybe a
Prelude.Nothing,
      $sel:failureReason:TrainingJob' :: Maybe Text
failureReason = forall a. Maybe a
Prelude.Nothing,
      $sel:finalMetricDataList:TrainingJob' :: Maybe [MetricData]
finalMetricDataList = forall a. Maybe a
Prelude.Nothing,
      $sel:hyperParameters:TrainingJob' :: Maybe (HashMap Text Text)
hyperParameters = forall a. Maybe a
Prelude.Nothing,
      $sel:inputDataConfig:TrainingJob' :: Maybe (NonEmpty Channel)
inputDataConfig = forall a. Maybe a
Prelude.Nothing,
      $sel:labelingJobArn:TrainingJob' :: Maybe Text
labelingJobArn = forall a. Maybe a
Prelude.Nothing,
      $sel:lastModifiedTime:TrainingJob' :: Maybe POSIX
lastModifiedTime = forall a. Maybe a
Prelude.Nothing,
      $sel:modelArtifacts:TrainingJob' :: Maybe ModelArtifacts
modelArtifacts = forall a. Maybe a
Prelude.Nothing,
      $sel:outputDataConfig:TrainingJob' :: Maybe OutputDataConfig
outputDataConfig = forall a. Maybe a
Prelude.Nothing,
      $sel:resourceConfig:TrainingJob' :: Maybe ResourceConfig
resourceConfig = forall a. Maybe a
Prelude.Nothing,
      $sel:retryStrategy:TrainingJob' :: Maybe RetryStrategy
retryStrategy = forall a. Maybe a
Prelude.Nothing,
      $sel:roleArn:TrainingJob' :: Maybe Text
roleArn = forall a. Maybe a
Prelude.Nothing,
      $sel:secondaryStatus:TrainingJob' :: Maybe SecondaryStatus
secondaryStatus = forall a. Maybe a
Prelude.Nothing,
      $sel:secondaryStatusTransitions:TrainingJob' :: Maybe [SecondaryStatusTransition]
secondaryStatusTransitions = forall a. Maybe a
Prelude.Nothing,
      $sel:stoppingCondition:TrainingJob' :: Maybe StoppingCondition
stoppingCondition = forall a. Maybe a
Prelude.Nothing,
      $sel:tags:TrainingJob' :: Maybe [Tag]
tags = forall a. Maybe a
Prelude.Nothing,
      $sel:tensorBoardOutputConfig:TrainingJob' :: Maybe TensorBoardOutputConfig
tensorBoardOutputConfig = forall a. Maybe a
Prelude.Nothing,
      $sel:trainingEndTime:TrainingJob' :: Maybe POSIX
trainingEndTime = forall a. Maybe a
Prelude.Nothing,
      $sel:trainingJobArn:TrainingJob' :: Maybe Text
trainingJobArn = forall a. Maybe a
Prelude.Nothing,
      $sel:trainingJobName:TrainingJob' :: Maybe Text
trainingJobName = forall a. Maybe a
Prelude.Nothing,
      $sel:trainingJobStatus:TrainingJob' :: Maybe TrainingJobStatus
trainingJobStatus = forall a. Maybe a
Prelude.Nothing,
      $sel:trainingStartTime:TrainingJob' :: Maybe POSIX
trainingStartTime = forall a. Maybe a
Prelude.Nothing,
      $sel:trainingTimeInSeconds:TrainingJob' :: Maybe Natural
trainingTimeInSeconds = forall a. Maybe a
Prelude.Nothing,
      $sel:tuningJobArn:TrainingJob' :: Maybe Text
tuningJobArn = forall a. Maybe a
Prelude.Nothing,
      $sel:vpcConfig:TrainingJob' :: Maybe VpcConfig
vpcConfig = forall a. Maybe a
Prelude.Nothing
    }
trainingJob_algorithmSpecification :: Lens.Lens' TrainingJob (Prelude.Maybe AlgorithmSpecification)
trainingJob_algorithmSpecification :: Lens' TrainingJob (Maybe AlgorithmSpecification)
trainingJob_algorithmSpecification = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\TrainingJob' {Maybe AlgorithmSpecification
algorithmSpecification :: Maybe AlgorithmSpecification
$sel:algorithmSpecification:TrainingJob' :: TrainingJob -> Maybe AlgorithmSpecification
algorithmSpecification} -> Maybe AlgorithmSpecification
algorithmSpecification) (\s :: TrainingJob
s@TrainingJob' {} Maybe AlgorithmSpecification
a -> TrainingJob
s {$sel:algorithmSpecification:TrainingJob' :: Maybe AlgorithmSpecification
algorithmSpecification = Maybe AlgorithmSpecification
a} :: TrainingJob)
trainingJob_autoMLJobArn :: Lens.Lens' TrainingJob (Prelude.Maybe Prelude.Text)
trainingJob_autoMLJobArn :: Lens' TrainingJob (Maybe Text)
trainingJob_autoMLJobArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\TrainingJob' {Maybe Text
autoMLJobArn :: Maybe Text
$sel:autoMLJobArn:TrainingJob' :: TrainingJob -> Maybe Text
autoMLJobArn} -> Maybe Text
autoMLJobArn) (\s :: TrainingJob
s@TrainingJob' {} Maybe Text
a -> TrainingJob
s {$sel:autoMLJobArn:TrainingJob' :: Maybe Text
autoMLJobArn = Maybe Text
a} :: TrainingJob)
trainingJob_billableTimeInSeconds :: Lens.Lens' TrainingJob (Prelude.Maybe Prelude.Natural)
trainingJob_billableTimeInSeconds :: Lens' TrainingJob (Maybe Natural)
trainingJob_billableTimeInSeconds = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\TrainingJob' {Maybe Natural
billableTimeInSeconds :: Maybe Natural
$sel:billableTimeInSeconds:TrainingJob' :: TrainingJob -> Maybe Natural
billableTimeInSeconds} -> Maybe Natural
billableTimeInSeconds) (\s :: TrainingJob
s@TrainingJob' {} Maybe Natural
a -> TrainingJob
s {$sel:billableTimeInSeconds:TrainingJob' :: Maybe Natural
billableTimeInSeconds = Maybe Natural
a} :: TrainingJob)
trainingJob_checkpointConfig :: Lens.Lens' TrainingJob (Prelude.Maybe CheckpointConfig)
trainingJob_checkpointConfig :: Lens' TrainingJob (Maybe CheckpointConfig)
trainingJob_checkpointConfig = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\TrainingJob' {Maybe CheckpointConfig
checkpointConfig :: Maybe CheckpointConfig
$sel:checkpointConfig:TrainingJob' :: TrainingJob -> Maybe CheckpointConfig
checkpointConfig} -> Maybe CheckpointConfig
checkpointConfig) (\s :: TrainingJob
s@TrainingJob' {} Maybe CheckpointConfig
a -> TrainingJob
s {$sel:checkpointConfig:TrainingJob' :: Maybe CheckpointConfig
checkpointConfig = Maybe CheckpointConfig
a} :: TrainingJob)
trainingJob_creationTime :: Lens.Lens' TrainingJob (Prelude.Maybe Prelude.UTCTime)
trainingJob_creationTime :: Lens' TrainingJob (Maybe UTCTime)
trainingJob_creationTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\TrainingJob' {Maybe POSIX
creationTime :: Maybe POSIX
$sel:creationTime:TrainingJob' :: TrainingJob -> Maybe POSIX
creationTime} -> Maybe POSIX
creationTime) (\s :: TrainingJob
s@TrainingJob' {} Maybe POSIX
a -> TrainingJob
s {$sel:creationTime:TrainingJob' :: Maybe POSIX
creationTime = Maybe POSIX
a} :: TrainingJob) 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
trainingJob_debugHookConfig :: Lens.Lens' TrainingJob (Prelude.Maybe DebugHookConfig)
trainingJob_debugHookConfig :: Lens' TrainingJob (Maybe DebugHookConfig)
trainingJob_debugHookConfig = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\TrainingJob' {Maybe DebugHookConfig
debugHookConfig :: Maybe DebugHookConfig
$sel:debugHookConfig:TrainingJob' :: TrainingJob -> Maybe DebugHookConfig
debugHookConfig} -> Maybe DebugHookConfig
debugHookConfig) (\s :: TrainingJob
s@TrainingJob' {} Maybe DebugHookConfig
a -> TrainingJob
s {$sel:debugHookConfig:TrainingJob' :: Maybe DebugHookConfig
debugHookConfig = Maybe DebugHookConfig
a} :: TrainingJob)
trainingJob_debugRuleConfigurations :: Lens.Lens' TrainingJob (Prelude.Maybe [DebugRuleConfiguration])
trainingJob_debugRuleConfigurations :: Lens' TrainingJob (Maybe [DebugRuleConfiguration])
trainingJob_debugRuleConfigurations = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\TrainingJob' {Maybe [DebugRuleConfiguration]
debugRuleConfigurations :: Maybe [DebugRuleConfiguration]
$sel:debugRuleConfigurations:TrainingJob' :: TrainingJob -> Maybe [DebugRuleConfiguration]
debugRuleConfigurations} -> Maybe [DebugRuleConfiguration]
debugRuleConfigurations) (\s :: TrainingJob
s@TrainingJob' {} Maybe [DebugRuleConfiguration]
a -> TrainingJob
s {$sel:debugRuleConfigurations:TrainingJob' :: Maybe [DebugRuleConfiguration]
debugRuleConfigurations = Maybe [DebugRuleConfiguration]
a} :: TrainingJob) 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
trainingJob_debugRuleEvaluationStatuses :: Lens.Lens' TrainingJob (Prelude.Maybe [DebugRuleEvaluationStatus])
trainingJob_debugRuleEvaluationStatuses :: Lens' TrainingJob (Maybe [DebugRuleEvaluationStatus])
trainingJob_debugRuleEvaluationStatuses = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\TrainingJob' {Maybe [DebugRuleEvaluationStatus]
debugRuleEvaluationStatuses :: Maybe [DebugRuleEvaluationStatus]
$sel:debugRuleEvaluationStatuses:TrainingJob' :: TrainingJob -> Maybe [DebugRuleEvaluationStatus]
debugRuleEvaluationStatuses} -> Maybe [DebugRuleEvaluationStatus]
debugRuleEvaluationStatuses) (\s :: TrainingJob
s@TrainingJob' {} Maybe [DebugRuleEvaluationStatus]
a -> TrainingJob
s {$sel:debugRuleEvaluationStatuses:TrainingJob' :: Maybe [DebugRuleEvaluationStatus]
debugRuleEvaluationStatuses = Maybe [DebugRuleEvaluationStatus]
a} :: TrainingJob) 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
trainingJob_enableInterContainerTrafficEncryption :: Lens.Lens' TrainingJob (Prelude.Maybe Prelude.Bool)
trainingJob_enableInterContainerTrafficEncryption :: Lens' TrainingJob (Maybe Bool)
trainingJob_enableInterContainerTrafficEncryption = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\TrainingJob' {Maybe Bool
enableInterContainerTrafficEncryption :: Maybe Bool
$sel:enableInterContainerTrafficEncryption:TrainingJob' :: TrainingJob -> Maybe Bool
enableInterContainerTrafficEncryption} -> Maybe Bool
enableInterContainerTrafficEncryption) (\s :: TrainingJob
s@TrainingJob' {} Maybe Bool
a -> TrainingJob
s {$sel:enableInterContainerTrafficEncryption:TrainingJob' :: Maybe Bool
enableInterContainerTrafficEncryption = Maybe Bool
a} :: TrainingJob)
trainingJob_enableManagedSpotTraining :: Lens.Lens' TrainingJob (Prelude.Maybe Prelude.Bool)
trainingJob_enableManagedSpotTraining :: Lens' TrainingJob (Maybe Bool)
trainingJob_enableManagedSpotTraining = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\TrainingJob' {Maybe Bool
enableManagedSpotTraining :: Maybe Bool
$sel:enableManagedSpotTraining:TrainingJob' :: TrainingJob -> Maybe Bool
enableManagedSpotTraining} -> Maybe Bool
enableManagedSpotTraining) (\s :: TrainingJob
s@TrainingJob' {} Maybe Bool
a -> TrainingJob
s {$sel:enableManagedSpotTraining:TrainingJob' :: Maybe Bool
enableManagedSpotTraining = Maybe Bool
a} :: TrainingJob)
trainingJob_enableNetworkIsolation :: Lens.Lens' TrainingJob (Prelude.Maybe Prelude.Bool)
trainingJob_enableNetworkIsolation :: Lens' TrainingJob (Maybe Bool)
trainingJob_enableNetworkIsolation = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\TrainingJob' {Maybe Bool
enableNetworkIsolation :: Maybe Bool
$sel:enableNetworkIsolation:TrainingJob' :: TrainingJob -> Maybe Bool
enableNetworkIsolation} -> Maybe Bool
enableNetworkIsolation) (\s :: TrainingJob
s@TrainingJob' {} Maybe Bool
a -> TrainingJob
s {$sel:enableNetworkIsolation:TrainingJob' :: Maybe Bool
enableNetworkIsolation = Maybe Bool
a} :: TrainingJob)
trainingJob_environment :: Lens.Lens' TrainingJob (Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text))
trainingJob_environment :: Lens' TrainingJob (Maybe (HashMap Text Text))
trainingJob_environment = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\TrainingJob' {Maybe (HashMap Text Text)
environment :: Maybe (HashMap Text Text)
$sel:environment:TrainingJob' :: TrainingJob -> Maybe (HashMap Text Text)
environment} -> Maybe (HashMap Text Text)
environment) (\s :: TrainingJob
s@TrainingJob' {} Maybe (HashMap Text Text)
a -> TrainingJob
s {$sel:environment:TrainingJob' :: Maybe (HashMap Text Text)
environment = Maybe (HashMap Text Text)
a} :: TrainingJob) 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
trainingJob_experimentConfig :: Lens.Lens' TrainingJob (Prelude.Maybe ExperimentConfig)
trainingJob_experimentConfig :: Lens' TrainingJob (Maybe ExperimentConfig)
trainingJob_experimentConfig = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\TrainingJob' {Maybe ExperimentConfig
experimentConfig :: Maybe ExperimentConfig
$sel:experimentConfig:TrainingJob' :: TrainingJob -> Maybe ExperimentConfig
experimentConfig} -> Maybe ExperimentConfig
experimentConfig) (\s :: TrainingJob
s@TrainingJob' {} Maybe ExperimentConfig
a -> TrainingJob
s {$sel:experimentConfig:TrainingJob' :: Maybe ExperimentConfig
experimentConfig = Maybe ExperimentConfig
a} :: TrainingJob)
trainingJob_failureReason :: Lens.Lens' TrainingJob (Prelude.Maybe Prelude.Text)
trainingJob_failureReason :: Lens' TrainingJob (Maybe Text)
trainingJob_failureReason = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\TrainingJob' {Maybe Text
failureReason :: Maybe Text
$sel:failureReason:TrainingJob' :: TrainingJob -> Maybe Text
failureReason} -> Maybe Text
failureReason) (\s :: TrainingJob
s@TrainingJob' {} Maybe Text
a -> TrainingJob
s {$sel:failureReason:TrainingJob' :: Maybe Text
failureReason = Maybe Text
a} :: TrainingJob)
trainingJob_finalMetricDataList :: Lens.Lens' TrainingJob (Prelude.Maybe [MetricData])
trainingJob_finalMetricDataList :: Lens' TrainingJob (Maybe [MetricData])
trainingJob_finalMetricDataList = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\TrainingJob' {Maybe [MetricData]
finalMetricDataList :: Maybe [MetricData]
$sel:finalMetricDataList:TrainingJob' :: TrainingJob -> Maybe [MetricData]
finalMetricDataList} -> Maybe [MetricData]
finalMetricDataList) (\s :: TrainingJob
s@TrainingJob' {} Maybe [MetricData]
a -> TrainingJob
s {$sel:finalMetricDataList:TrainingJob' :: Maybe [MetricData]
finalMetricDataList = Maybe [MetricData]
a} :: TrainingJob) 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
trainingJob_hyperParameters :: Lens.Lens' TrainingJob (Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text))
trainingJob_hyperParameters :: Lens' TrainingJob (Maybe (HashMap Text Text))
trainingJob_hyperParameters = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\TrainingJob' {Maybe (HashMap Text Text)
hyperParameters :: Maybe (HashMap Text Text)
$sel:hyperParameters:TrainingJob' :: TrainingJob -> Maybe (HashMap Text Text)
hyperParameters} -> Maybe (HashMap Text Text)
hyperParameters) (\s :: TrainingJob
s@TrainingJob' {} Maybe (HashMap Text Text)
a -> TrainingJob
s {$sel:hyperParameters:TrainingJob' :: Maybe (HashMap Text Text)
hyperParameters = Maybe (HashMap Text Text)
a} :: TrainingJob) 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
trainingJob_inputDataConfig :: Lens.Lens' TrainingJob (Prelude.Maybe (Prelude.NonEmpty Channel))
trainingJob_inputDataConfig :: Lens' TrainingJob (Maybe (NonEmpty Channel))
trainingJob_inputDataConfig = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\TrainingJob' {Maybe (NonEmpty Channel)
inputDataConfig :: Maybe (NonEmpty Channel)
$sel:inputDataConfig:TrainingJob' :: TrainingJob -> Maybe (NonEmpty Channel)
inputDataConfig} -> Maybe (NonEmpty Channel)
inputDataConfig) (\s :: TrainingJob
s@TrainingJob' {} Maybe (NonEmpty Channel)
a -> TrainingJob
s {$sel:inputDataConfig:TrainingJob' :: Maybe (NonEmpty Channel)
inputDataConfig = Maybe (NonEmpty Channel)
a} :: TrainingJob) 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
trainingJob_labelingJobArn :: Lens.Lens' TrainingJob (Prelude.Maybe Prelude.Text)
trainingJob_labelingJobArn :: Lens' TrainingJob (Maybe Text)
trainingJob_labelingJobArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\TrainingJob' {Maybe Text
labelingJobArn :: Maybe Text
$sel:labelingJobArn:TrainingJob' :: TrainingJob -> Maybe Text
labelingJobArn} -> Maybe Text
labelingJobArn) (\s :: TrainingJob
s@TrainingJob' {} Maybe Text
a -> TrainingJob
s {$sel:labelingJobArn:TrainingJob' :: Maybe Text
labelingJobArn = Maybe Text
a} :: TrainingJob)
trainingJob_lastModifiedTime :: Lens.Lens' TrainingJob (Prelude.Maybe Prelude.UTCTime)
trainingJob_lastModifiedTime :: Lens' TrainingJob (Maybe UTCTime)
trainingJob_lastModifiedTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\TrainingJob' {Maybe POSIX
lastModifiedTime :: Maybe POSIX
$sel:lastModifiedTime:TrainingJob' :: TrainingJob -> Maybe POSIX
lastModifiedTime} -> Maybe POSIX
lastModifiedTime) (\s :: TrainingJob
s@TrainingJob' {} Maybe POSIX
a -> TrainingJob
s {$sel:lastModifiedTime:TrainingJob' :: Maybe POSIX
lastModifiedTime = Maybe POSIX
a} :: TrainingJob) 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
trainingJob_modelArtifacts :: Lens.Lens' TrainingJob (Prelude.Maybe ModelArtifacts)
trainingJob_modelArtifacts :: Lens' TrainingJob (Maybe ModelArtifacts)
trainingJob_modelArtifacts = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\TrainingJob' {Maybe ModelArtifacts
modelArtifacts :: Maybe ModelArtifacts
$sel:modelArtifacts:TrainingJob' :: TrainingJob -> Maybe ModelArtifacts
modelArtifacts} -> Maybe ModelArtifacts
modelArtifacts) (\s :: TrainingJob
s@TrainingJob' {} Maybe ModelArtifacts
a -> TrainingJob
s {$sel:modelArtifacts:TrainingJob' :: Maybe ModelArtifacts
modelArtifacts = Maybe ModelArtifacts
a} :: TrainingJob)
trainingJob_outputDataConfig :: Lens.Lens' TrainingJob (Prelude.Maybe OutputDataConfig)
trainingJob_outputDataConfig :: Lens' TrainingJob (Maybe OutputDataConfig)
trainingJob_outputDataConfig = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\TrainingJob' {Maybe OutputDataConfig
outputDataConfig :: Maybe OutputDataConfig
$sel:outputDataConfig:TrainingJob' :: TrainingJob -> Maybe OutputDataConfig
outputDataConfig} -> Maybe OutputDataConfig
outputDataConfig) (\s :: TrainingJob
s@TrainingJob' {} Maybe OutputDataConfig
a -> TrainingJob
s {$sel:outputDataConfig:TrainingJob' :: Maybe OutputDataConfig
outputDataConfig = Maybe OutputDataConfig
a} :: TrainingJob)
trainingJob_resourceConfig :: Lens.Lens' TrainingJob (Prelude.Maybe ResourceConfig)
trainingJob_resourceConfig :: Lens' TrainingJob (Maybe ResourceConfig)
trainingJob_resourceConfig = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\TrainingJob' {Maybe ResourceConfig
resourceConfig :: Maybe ResourceConfig
$sel:resourceConfig:TrainingJob' :: TrainingJob -> Maybe ResourceConfig
resourceConfig} -> Maybe ResourceConfig
resourceConfig) (\s :: TrainingJob
s@TrainingJob' {} Maybe ResourceConfig
a -> TrainingJob
s {$sel:resourceConfig:TrainingJob' :: Maybe ResourceConfig
resourceConfig = Maybe ResourceConfig
a} :: TrainingJob)
trainingJob_retryStrategy :: Lens.Lens' TrainingJob (Prelude.Maybe RetryStrategy)
trainingJob_retryStrategy :: Lens' TrainingJob (Maybe RetryStrategy)
trainingJob_retryStrategy = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\TrainingJob' {Maybe RetryStrategy
retryStrategy :: Maybe RetryStrategy
$sel:retryStrategy:TrainingJob' :: TrainingJob -> Maybe RetryStrategy
retryStrategy} -> Maybe RetryStrategy
retryStrategy) (\s :: TrainingJob
s@TrainingJob' {} Maybe RetryStrategy
a -> TrainingJob
s {$sel:retryStrategy:TrainingJob' :: Maybe RetryStrategy
retryStrategy = Maybe RetryStrategy
a} :: TrainingJob)
trainingJob_roleArn :: Lens.Lens' TrainingJob (Prelude.Maybe Prelude.Text)
trainingJob_roleArn :: Lens' TrainingJob (Maybe Text)
trainingJob_roleArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\TrainingJob' {Maybe Text
roleArn :: Maybe Text
$sel:roleArn:TrainingJob' :: TrainingJob -> Maybe Text
roleArn} -> Maybe Text
roleArn) (\s :: TrainingJob
s@TrainingJob' {} Maybe Text
a -> TrainingJob
s {$sel:roleArn:TrainingJob' :: Maybe Text
roleArn = Maybe Text
a} :: TrainingJob)
trainingJob_secondaryStatus :: Lens.Lens' TrainingJob (Prelude.Maybe SecondaryStatus)
trainingJob_secondaryStatus :: Lens' TrainingJob (Maybe SecondaryStatus)
trainingJob_secondaryStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\TrainingJob' {Maybe SecondaryStatus
secondaryStatus :: Maybe SecondaryStatus
$sel:secondaryStatus:TrainingJob' :: TrainingJob -> Maybe SecondaryStatus
secondaryStatus} -> Maybe SecondaryStatus
secondaryStatus) (\s :: TrainingJob
s@TrainingJob' {} Maybe SecondaryStatus
a -> TrainingJob
s {$sel:secondaryStatus:TrainingJob' :: Maybe SecondaryStatus
secondaryStatus = Maybe SecondaryStatus
a} :: TrainingJob)
trainingJob_secondaryStatusTransitions :: Lens.Lens' TrainingJob (Prelude.Maybe [SecondaryStatusTransition])
trainingJob_secondaryStatusTransitions :: Lens' TrainingJob (Maybe [SecondaryStatusTransition])
trainingJob_secondaryStatusTransitions = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\TrainingJob' {Maybe [SecondaryStatusTransition]
secondaryStatusTransitions :: Maybe [SecondaryStatusTransition]
$sel:secondaryStatusTransitions:TrainingJob' :: TrainingJob -> Maybe [SecondaryStatusTransition]
secondaryStatusTransitions} -> Maybe [SecondaryStatusTransition]
secondaryStatusTransitions) (\s :: TrainingJob
s@TrainingJob' {} Maybe [SecondaryStatusTransition]
a -> TrainingJob
s {$sel:secondaryStatusTransitions:TrainingJob' :: Maybe [SecondaryStatusTransition]
secondaryStatusTransitions = Maybe [SecondaryStatusTransition]
a} :: TrainingJob) 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
trainingJob_stoppingCondition :: Lens.Lens' TrainingJob (Prelude.Maybe StoppingCondition)
trainingJob_stoppingCondition :: Lens' TrainingJob (Maybe StoppingCondition)
trainingJob_stoppingCondition = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\TrainingJob' {Maybe StoppingCondition
stoppingCondition :: Maybe StoppingCondition
$sel:stoppingCondition:TrainingJob' :: TrainingJob -> Maybe StoppingCondition
stoppingCondition} -> Maybe StoppingCondition
stoppingCondition) (\s :: TrainingJob
s@TrainingJob' {} Maybe StoppingCondition
a -> TrainingJob
s {$sel:stoppingCondition:TrainingJob' :: Maybe StoppingCondition
stoppingCondition = Maybe StoppingCondition
a} :: TrainingJob)
trainingJob_tags :: Lens.Lens' TrainingJob (Prelude.Maybe [Tag])
trainingJob_tags :: Lens' TrainingJob (Maybe [Tag])
trainingJob_tags = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\TrainingJob' {Maybe [Tag]
tags :: Maybe [Tag]
$sel:tags:TrainingJob' :: TrainingJob -> Maybe [Tag]
tags} -> Maybe [Tag]
tags) (\s :: TrainingJob
s@TrainingJob' {} Maybe [Tag]
a -> TrainingJob
s {$sel:tags:TrainingJob' :: Maybe [Tag]
tags = Maybe [Tag]
a} :: TrainingJob) 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
trainingJob_tensorBoardOutputConfig :: Lens.Lens' TrainingJob (Prelude.Maybe TensorBoardOutputConfig)
trainingJob_tensorBoardOutputConfig :: Lens' TrainingJob (Maybe TensorBoardOutputConfig)
trainingJob_tensorBoardOutputConfig = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\TrainingJob' {Maybe TensorBoardOutputConfig
tensorBoardOutputConfig :: Maybe TensorBoardOutputConfig
$sel:tensorBoardOutputConfig:TrainingJob' :: TrainingJob -> Maybe TensorBoardOutputConfig
tensorBoardOutputConfig} -> Maybe TensorBoardOutputConfig
tensorBoardOutputConfig) (\s :: TrainingJob
s@TrainingJob' {} Maybe TensorBoardOutputConfig
a -> TrainingJob
s {$sel:tensorBoardOutputConfig:TrainingJob' :: Maybe TensorBoardOutputConfig
tensorBoardOutputConfig = Maybe TensorBoardOutputConfig
a} :: TrainingJob)
trainingJob_trainingEndTime :: Lens.Lens' TrainingJob (Prelude.Maybe Prelude.UTCTime)
trainingJob_trainingEndTime :: Lens' TrainingJob (Maybe UTCTime)
trainingJob_trainingEndTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\TrainingJob' {Maybe POSIX
trainingEndTime :: Maybe POSIX
$sel:trainingEndTime:TrainingJob' :: TrainingJob -> Maybe POSIX
trainingEndTime} -> Maybe POSIX
trainingEndTime) (\s :: TrainingJob
s@TrainingJob' {} Maybe POSIX
a -> TrainingJob
s {$sel:trainingEndTime:TrainingJob' :: Maybe POSIX
trainingEndTime = Maybe POSIX
a} :: TrainingJob) 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
trainingJob_trainingJobArn :: Lens.Lens' TrainingJob (Prelude.Maybe Prelude.Text)
trainingJob_trainingJobArn :: Lens' TrainingJob (Maybe Text)
trainingJob_trainingJobArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\TrainingJob' {Maybe Text
trainingJobArn :: Maybe Text
$sel:trainingJobArn:TrainingJob' :: TrainingJob -> Maybe Text
trainingJobArn} -> Maybe Text
trainingJobArn) (\s :: TrainingJob
s@TrainingJob' {} Maybe Text
a -> TrainingJob
s {$sel:trainingJobArn:TrainingJob' :: Maybe Text
trainingJobArn = Maybe Text
a} :: TrainingJob)
trainingJob_trainingJobName :: Lens.Lens' TrainingJob (Prelude.Maybe Prelude.Text)
trainingJob_trainingJobName :: Lens' TrainingJob (Maybe Text)
trainingJob_trainingJobName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\TrainingJob' {Maybe Text
trainingJobName :: Maybe Text
$sel:trainingJobName:TrainingJob' :: TrainingJob -> Maybe Text
trainingJobName} -> Maybe Text
trainingJobName) (\s :: TrainingJob
s@TrainingJob' {} Maybe Text
a -> TrainingJob
s {$sel:trainingJobName:TrainingJob' :: Maybe Text
trainingJobName = Maybe Text
a} :: TrainingJob)
trainingJob_trainingJobStatus :: Lens.Lens' TrainingJob (Prelude.Maybe TrainingJobStatus)
trainingJob_trainingJobStatus :: Lens' TrainingJob (Maybe TrainingJobStatus)
trainingJob_trainingJobStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\TrainingJob' {Maybe TrainingJobStatus
trainingJobStatus :: Maybe TrainingJobStatus
$sel:trainingJobStatus:TrainingJob' :: TrainingJob -> Maybe TrainingJobStatus
trainingJobStatus} -> Maybe TrainingJobStatus
trainingJobStatus) (\s :: TrainingJob
s@TrainingJob' {} Maybe TrainingJobStatus
a -> TrainingJob
s {$sel:trainingJobStatus:TrainingJob' :: Maybe TrainingJobStatus
trainingJobStatus = Maybe TrainingJobStatus
a} :: TrainingJob)
trainingJob_trainingStartTime :: Lens.Lens' TrainingJob (Prelude.Maybe Prelude.UTCTime)
trainingJob_trainingStartTime :: Lens' TrainingJob (Maybe UTCTime)
trainingJob_trainingStartTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\TrainingJob' {Maybe POSIX
trainingStartTime :: Maybe POSIX
$sel:trainingStartTime:TrainingJob' :: TrainingJob -> Maybe POSIX
trainingStartTime} -> Maybe POSIX
trainingStartTime) (\s :: TrainingJob
s@TrainingJob' {} Maybe POSIX
a -> TrainingJob
s {$sel:trainingStartTime:TrainingJob' :: Maybe POSIX
trainingStartTime = Maybe POSIX
a} :: TrainingJob) 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
trainingJob_trainingTimeInSeconds :: Lens.Lens' TrainingJob (Prelude.Maybe Prelude.Natural)
trainingJob_trainingTimeInSeconds :: Lens' TrainingJob (Maybe Natural)
trainingJob_trainingTimeInSeconds = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\TrainingJob' {Maybe Natural
trainingTimeInSeconds :: Maybe Natural
$sel:trainingTimeInSeconds:TrainingJob' :: TrainingJob -> Maybe Natural
trainingTimeInSeconds} -> Maybe Natural
trainingTimeInSeconds) (\s :: TrainingJob
s@TrainingJob' {} Maybe Natural
a -> TrainingJob
s {$sel:trainingTimeInSeconds:TrainingJob' :: Maybe Natural
trainingTimeInSeconds = Maybe Natural
a} :: TrainingJob)
trainingJob_tuningJobArn :: Lens.Lens' TrainingJob (Prelude.Maybe Prelude.Text)
trainingJob_tuningJobArn :: Lens' TrainingJob (Maybe Text)
trainingJob_tuningJobArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\TrainingJob' {Maybe Text
tuningJobArn :: Maybe Text
$sel:tuningJobArn:TrainingJob' :: TrainingJob -> Maybe Text
tuningJobArn} -> Maybe Text
tuningJobArn) (\s :: TrainingJob
s@TrainingJob' {} Maybe Text
a -> TrainingJob
s {$sel:tuningJobArn:TrainingJob' :: Maybe Text
tuningJobArn = Maybe Text
a} :: TrainingJob)
trainingJob_vpcConfig :: Lens.Lens' TrainingJob (Prelude.Maybe VpcConfig)
trainingJob_vpcConfig :: Lens' TrainingJob (Maybe VpcConfig)
trainingJob_vpcConfig = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\TrainingJob' {Maybe VpcConfig
vpcConfig :: Maybe VpcConfig
$sel:vpcConfig:TrainingJob' :: TrainingJob -> Maybe VpcConfig
vpcConfig} -> Maybe VpcConfig
vpcConfig) (\s :: TrainingJob
s@TrainingJob' {} Maybe VpcConfig
a -> TrainingJob
s {$sel:vpcConfig:TrainingJob' :: Maybe VpcConfig
vpcConfig = Maybe VpcConfig
a} :: TrainingJob)
instance Data.FromJSON TrainingJob where
  parseJSON :: Value -> Parser TrainingJob
parseJSON =
    forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.withObject
      String
"TrainingJob"
      ( \Object
x ->
          Maybe AlgorithmSpecification
-> Maybe Text
-> Maybe Natural
-> Maybe CheckpointConfig
-> Maybe POSIX
-> Maybe DebugHookConfig
-> Maybe [DebugRuleConfiguration]
-> Maybe [DebugRuleEvaluationStatus]
-> Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Maybe (HashMap Text Text)
-> Maybe ExperimentConfig
-> Maybe Text
-> Maybe [MetricData]
-> Maybe (HashMap Text Text)
-> Maybe (NonEmpty Channel)
-> Maybe Text
-> Maybe POSIX
-> Maybe ModelArtifacts
-> Maybe OutputDataConfig
-> Maybe ResourceConfig
-> Maybe RetryStrategy
-> Maybe Text
-> Maybe SecondaryStatus
-> Maybe [SecondaryStatusTransition]
-> Maybe StoppingCondition
-> Maybe [Tag]
-> Maybe TensorBoardOutputConfig
-> Maybe POSIX
-> Maybe Text
-> Maybe Text
-> Maybe TrainingJobStatus
-> Maybe POSIX
-> Maybe Natural
-> Maybe Text
-> Maybe VpcConfig
-> TrainingJob
TrainingJob'
            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
"AlgorithmSpecification")
            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
"AutoMLJobArn")
            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
"BillableTimeInSeconds")
            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
"CheckpointConfig")
            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
"CreationTime")
            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
"DebugHookConfig")
            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
"DebugRuleConfigurations"
                            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 (Maybe a)
Data..:? Key
"DebugRuleEvaluationStatuses"
                            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 (Maybe a)
Data..:? Key
"EnableInterContainerTrafficEncryption")
            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
"EnableManagedSpotTraining")
            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
"EnableNetworkIsolation")
            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
"Environment" 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 (Maybe a)
Data..:? Key
"ExperimentConfig")
            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
"FinalMetricDataList"
                            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 (Maybe a)
Data..:? Key
"HyperParameters"
                            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 (Maybe a)
Data..:? Key
"InputDataConfig")
            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
"LabelingJobArn")
            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 (Maybe a)
Data..:? Key
"ModelArtifacts")
            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
"OutputDataConfig")
            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
"ResourceConfig")
            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
"RetryStrategy")
            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
"RoleArn")
            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
"SecondaryStatus")
            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
"SecondaryStatusTransitions"
                            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 (Maybe a)
Data..:? Key
"StoppingCondition")
            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
"Tags" 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 (Maybe a)
Data..:? Key
"TensorBoardOutputConfig")
            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
"TrainingEndTime")
            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
"TrainingJobArn")
            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
"TrainingJobName")
            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
"TrainingJobStatus")
            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
"TrainingStartTime")
            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
"TrainingTimeInSeconds")
            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
"TuningJobArn")
            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
"VpcConfig")
      )
instance Prelude.Hashable TrainingJob where
  hashWithSalt :: Int -> TrainingJob -> Int
hashWithSalt Int
_salt TrainingJob' {Maybe Bool
Maybe Natural
Maybe [MetricData]
Maybe [DebugRuleConfiguration]
Maybe [DebugRuleEvaluationStatus]
Maybe [SecondaryStatusTransition]
Maybe [Tag]
Maybe (NonEmpty Channel)
Maybe Text
Maybe (HashMap Text Text)
Maybe POSIX
Maybe CheckpointConfig
Maybe DebugHookConfig
Maybe ExperimentConfig
Maybe ModelArtifacts
Maybe OutputDataConfig
Maybe RetryStrategy
Maybe SecondaryStatus
Maybe StoppingCondition
Maybe TensorBoardOutputConfig
Maybe AlgorithmSpecification
Maybe ResourceConfig
Maybe TrainingJobStatus
Maybe VpcConfig
vpcConfig :: Maybe VpcConfig
tuningJobArn :: Maybe Text
trainingTimeInSeconds :: Maybe Natural
trainingStartTime :: Maybe POSIX
trainingJobStatus :: Maybe TrainingJobStatus
trainingJobName :: Maybe Text
trainingJobArn :: Maybe Text
trainingEndTime :: Maybe POSIX
tensorBoardOutputConfig :: Maybe TensorBoardOutputConfig
tags :: Maybe [Tag]
stoppingCondition :: Maybe StoppingCondition
secondaryStatusTransitions :: Maybe [SecondaryStatusTransition]
secondaryStatus :: Maybe SecondaryStatus
roleArn :: Maybe Text
retryStrategy :: Maybe RetryStrategy
resourceConfig :: Maybe ResourceConfig
outputDataConfig :: Maybe OutputDataConfig
modelArtifacts :: Maybe ModelArtifacts
lastModifiedTime :: Maybe POSIX
labelingJobArn :: Maybe Text
inputDataConfig :: Maybe (NonEmpty Channel)
hyperParameters :: Maybe (HashMap Text Text)
finalMetricDataList :: Maybe [MetricData]
failureReason :: Maybe Text
experimentConfig :: Maybe ExperimentConfig
environment :: Maybe (HashMap Text Text)
enableNetworkIsolation :: Maybe Bool
enableManagedSpotTraining :: Maybe Bool
enableInterContainerTrafficEncryption :: Maybe Bool
debugRuleEvaluationStatuses :: Maybe [DebugRuleEvaluationStatus]
debugRuleConfigurations :: Maybe [DebugRuleConfiguration]
debugHookConfig :: Maybe DebugHookConfig
creationTime :: Maybe POSIX
checkpointConfig :: Maybe CheckpointConfig
billableTimeInSeconds :: Maybe Natural
autoMLJobArn :: Maybe Text
algorithmSpecification :: Maybe AlgorithmSpecification
$sel:vpcConfig:TrainingJob' :: TrainingJob -> Maybe VpcConfig
$sel:tuningJobArn:TrainingJob' :: TrainingJob -> Maybe Text
$sel:trainingTimeInSeconds:TrainingJob' :: TrainingJob -> Maybe Natural
$sel:trainingStartTime:TrainingJob' :: TrainingJob -> Maybe POSIX
$sel:trainingJobStatus:TrainingJob' :: TrainingJob -> Maybe TrainingJobStatus
$sel:trainingJobName:TrainingJob' :: TrainingJob -> Maybe Text
$sel:trainingJobArn:TrainingJob' :: TrainingJob -> Maybe Text
$sel:trainingEndTime:TrainingJob' :: TrainingJob -> Maybe POSIX
$sel:tensorBoardOutputConfig:TrainingJob' :: TrainingJob -> Maybe TensorBoardOutputConfig
$sel:tags:TrainingJob' :: TrainingJob -> Maybe [Tag]
$sel:stoppingCondition:TrainingJob' :: TrainingJob -> Maybe StoppingCondition
$sel:secondaryStatusTransitions:TrainingJob' :: TrainingJob -> Maybe [SecondaryStatusTransition]
$sel:secondaryStatus:TrainingJob' :: TrainingJob -> Maybe SecondaryStatus
$sel:roleArn:TrainingJob' :: TrainingJob -> Maybe Text
$sel:retryStrategy:TrainingJob' :: TrainingJob -> Maybe RetryStrategy
$sel:resourceConfig:TrainingJob' :: TrainingJob -> Maybe ResourceConfig
$sel:outputDataConfig:TrainingJob' :: TrainingJob -> Maybe OutputDataConfig
$sel:modelArtifacts:TrainingJob' :: TrainingJob -> Maybe ModelArtifacts
$sel:lastModifiedTime:TrainingJob' :: TrainingJob -> Maybe POSIX
$sel:labelingJobArn:TrainingJob' :: TrainingJob -> Maybe Text
$sel:inputDataConfig:TrainingJob' :: TrainingJob -> Maybe (NonEmpty Channel)
$sel:hyperParameters:TrainingJob' :: TrainingJob -> Maybe (HashMap Text Text)
$sel:finalMetricDataList:TrainingJob' :: TrainingJob -> Maybe [MetricData]
$sel:failureReason:TrainingJob' :: TrainingJob -> Maybe Text
$sel:experimentConfig:TrainingJob' :: TrainingJob -> Maybe ExperimentConfig
$sel:environment:TrainingJob' :: TrainingJob -> Maybe (HashMap Text Text)
$sel:enableNetworkIsolation:TrainingJob' :: TrainingJob -> Maybe Bool
$sel:enableManagedSpotTraining:TrainingJob' :: TrainingJob -> Maybe Bool
$sel:enableInterContainerTrafficEncryption:TrainingJob' :: TrainingJob -> Maybe Bool
$sel:debugRuleEvaluationStatuses:TrainingJob' :: TrainingJob -> Maybe [DebugRuleEvaluationStatus]
$sel:debugRuleConfigurations:TrainingJob' :: TrainingJob -> Maybe [DebugRuleConfiguration]
$sel:debugHookConfig:TrainingJob' :: TrainingJob -> Maybe DebugHookConfig
$sel:creationTime:TrainingJob' :: TrainingJob -> Maybe POSIX
$sel:checkpointConfig:TrainingJob' :: TrainingJob -> Maybe CheckpointConfig
$sel:billableTimeInSeconds:TrainingJob' :: TrainingJob -> Maybe Natural
$sel:autoMLJobArn:TrainingJob' :: TrainingJob -> Maybe Text
$sel:algorithmSpecification:TrainingJob' :: TrainingJob -> Maybe AlgorithmSpecification
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe AlgorithmSpecification
algorithmSpecification
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
autoMLJobArn
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Natural
billableTimeInSeconds
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe CheckpointConfig
checkpointConfig
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe POSIX
creationTime
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe DebugHookConfig
debugHookConfig
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [DebugRuleConfiguration]
debugRuleConfigurations
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [DebugRuleEvaluationStatus]
debugRuleEvaluationStatuses
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
enableInterContainerTrafficEncryption
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
enableManagedSpotTraining
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
enableNetworkIsolation
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe (HashMap Text Text)
environment
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ExperimentConfig
experimentConfig
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
failureReason
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [MetricData]
finalMetricDataList
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe (HashMap Text Text)
hyperParameters
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe (NonEmpty Channel)
inputDataConfig
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
labelingJobArn
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe POSIX
lastModifiedTime
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ModelArtifacts
modelArtifacts
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe OutputDataConfig
outputDataConfig
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ResourceConfig
resourceConfig
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe RetryStrategy
retryStrategy
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
roleArn
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe SecondaryStatus
secondaryStatus
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [SecondaryStatusTransition]
secondaryStatusTransitions
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe StoppingCondition
stoppingCondition
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [Tag]
tags
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe TensorBoardOutputConfig
tensorBoardOutputConfig
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe POSIX
trainingEndTime
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
trainingJobArn
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
trainingJobName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe TrainingJobStatus
trainingJobStatus
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe POSIX
trainingStartTime
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Natural
trainingTimeInSeconds
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
tuningJobArn
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe VpcConfig
vpcConfig
instance Prelude.NFData TrainingJob where
  rnf :: TrainingJob -> ()
rnf TrainingJob' {Maybe Bool
Maybe Natural
Maybe [MetricData]
Maybe [DebugRuleConfiguration]
Maybe [DebugRuleEvaluationStatus]
Maybe [SecondaryStatusTransition]
Maybe [Tag]
Maybe (NonEmpty Channel)
Maybe Text
Maybe (HashMap Text Text)
Maybe POSIX
Maybe CheckpointConfig
Maybe DebugHookConfig
Maybe ExperimentConfig
Maybe ModelArtifacts
Maybe OutputDataConfig
Maybe RetryStrategy
Maybe SecondaryStatus
Maybe StoppingCondition
Maybe TensorBoardOutputConfig
Maybe AlgorithmSpecification
Maybe ResourceConfig
Maybe TrainingJobStatus
Maybe VpcConfig
vpcConfig :: Maybe VpcConfig
tuningJobArn :: Maybe Text
trainingTimeInSeconds :: Maybe Natural
trainingStartTime :: Maybe POSIX
trainingJobStatus :: Maybe TrainingJobStatus
trainingJobName :: Maybe Text
trainingJobArn :: Maybe Text
trainingEndTime :: Maybe POSIX
tensorBoardOutputConfig :: Maybe TensorBoardOutputConfig
tags :: Maybe [Tag]
stoppingCondition :: Maybe StoppingCondition
secondaryStatusTransitions :: Maybe [SecondaryStatusTransition]
secondaryStatus :: Maybe SecondaryStatus
roleArn :: Maybe Text
retryStrategy :: Maybe RetryStrategy
resourceConfig :: Maybe ResourceConfig
outputDataConfig :: Maybe OutputDataConfig
modelArtifacts :: Maybe ModelArtifacts
lastModifiedTime :: Maybe POSIX
labelingJobArn :: Maybe Text
inputDataConfig :: Maybe (NonEmpty Channel)
hyperParameters :: Maybe (HashMap Text Text)
finalMetricDataList :: Maybe [MetricData]
failureReason :: Maybe Text
experimentConfig :: Maybe ExperimentConfig
environment :: Maybe (HashMap Text Text)
enableNetworkIsolation :: Maybe Bool
enableManagedSpotTraining :: Maybe Bool
enableInterContainerTrafficEncryption :: Maybe Bool
debugRuleEvaluationStatuses :: Maybe [DebugRuleEvaluationStatus]
debugRuleConfigurations :: Maybe [DebugRuleConfiguration]
debugHookConfig :: Maybe DebugHookConfig
creationTime :: Maybe POSIX
checkpointConfig :: Maybe CheckpointConfig
billableTimeInSeconds :: Maybe Natural
autoMLJobArn :: Maybe Text
algorithmSpecification :: Maybe AlgorithmSpecification
$sel:vpcConfig:TrainingJob' :: TrainingJob -> Maybe VpcConfig
$sel:tuningJobArn:TrainingJob' :: TrainingJob -> Maybe Text
$sel:trainingTimeInSeconds:TrainingJob' :: TrainingJob -> Maybe Natural
$sel:trainingStartTime:TrainingJob' :: TrainingJob -> Maybe POSIX
$sel:trainingJobStatus:TrainingJob' :: TrainingJob -> Maybe TrainingJobStatus
$sel:trainingJobName:TrainingJob' :: TrainingJob -> Maybe Text
$sel:trainingJobArn:TrainingJob' :: TrainingJob -> Maybe Text
$sel:trainingEndTime:TrainingJob' :: TrainingJob -> Maybe POSIX
$sel:tensorBoardOutputConfig:TrainingJob' :: TrainingJob -> Maybe TensorBoardOutputConfig
$sel:tags:TrainingJob' :: TrainingJob -> Maybe [Tag]
$sel:stoppingCondition:TrainingJob' :: TrainingJob -> Maybe StoppingCondition
$sel:secondaryStatusTransitions:TrainingJob' :: TrainingJob -> Maybe [SecondaryStatusTransition]
$sel:secondaryStatus:TrainingJob' :: TrainingJob -> Maybe SecondaryStatus
$sel:roleArn:TrainingJob' :: TrainingJob -> Maybe Text
$sel:retryStrategy:TrainingJob' :: TrainingJob -> Maybe RetryStrategy
$sel:resourceConfig:TrainingJob' :: TrainingJob -> Maybe ResourceConfig
$sel:outputDataConfig:TrainingJob' :: TrainingJob -> Maybe OutputDataConfig
$sel:modelArtifacts:TrainingJob' :: TrainingJob -> Maybe ModelArtifacts
$sel:lastModifiedTime:TrainingJob' :: TrainingJob -> Maybe POSIX
$sel:labelingJobArn:TrainingJob' :: TrainingJob -> Maybe Text
$sel:inputDataConfig:TrainingJob' :: TrainingJob -> Maybe (NonEmpty Channel)
$sel:hyperParameters:TrainingJob' :: TrainingJob -> Maybe (HashMap Text Text)
$sel:finalMetricDataList:TrainingJob' :: TrainingJob -> Maybe [MetricData]
$sel:failureReason:TrainingJob' :: TrainingJob -> Maybe Text
$sel:experimentConfig:TrainingJob' :: TrainingJob -> Maybe ExperimentConfig
$sel:environment:TrainingJob' :: TrainingJob -> Maybe (HashMap Text Text)
$sel:enableNetworkIsolation:TrainingJob' :: TrainingJob -> Maybe Bool
$sel:enableManagedSpotTraining:TrainingJob' :: TrainingJob -> Maybe Bool
$sel:enableInterContainerTrafficEncryption:TrainingJob' :: TrainingJob -> Maybe Bool
$sel:debugRuleEvaluationStatuses:TrainingJob' :: TrainingJob -> Maybe [DebugRuleEvaluationStatus]
$sel:debugRuleConfigurations:TrainingJob' :: TrainingJob -> Maybe [DebugRuleConfiguration]
$sel:debugHookConfig:TrainingJob' :: TrainingJob -> Maybe DebugHookConfig
$sel:creationTime:TrainingJob' :: TrainingJob -> Maybe POSIX
$sel:checkpointConfig:TrainingJob' :: TrainingJob -> Maybe CheckpointConfig
$sel:billableTimeInSeconds:TrainingJob' :: TrainingJob -> Maybe Natural
$sel:autoMLJobArn:TrainingJob' :: TrainingJob -> Maybe Text
$sel:algorithmSpecification:TrainingJob' :: TrainingJob -> Maybe AlgorithmSpecification
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe AlgorithmSpecification
algorithmSpecification
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
autoMLJobArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Natural
billableTimeInSeconds
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe CheckpointConfig
checkpointConfig
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe POSIX
creationTime
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe DebugHookConfig
debugHookConfig
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [DebugRuleConfiguration]
debugRuleConfigurations
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [DebugRuleEvaluationStatus]
debugRuleEvaluationStatuses
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Bool
enableInterContainerTrafficEncryption
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Bool
enableManagedSpotTraining
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Bool
enableNetworkIsolation
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe (HashMap Text Text)
environment
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ExperimentConfig
experimentConfig
      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 [MetricData]
finalMetricDataList
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe (HashMap Text Text)
hyperParameters
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe (NonEmpty Channel)
inputDataConfig
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
labelingJobArn
      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 Maybe ModelArtifacts
modelArtifacts
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe OutputDataConfig
outputDataConfig
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ResourceConfig
resourceConfig
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Maybe RetryStrategy
retryStrategy
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
roleArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Maybe SecondaryStatus
secondaryStatus
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Maybe [SecondaryStatusTransition]
secondaryStatusTransitions
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Maybe StoppingCondition
stoppingCondition
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Maybe [Tag]
tags
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Maybe TensorBoardOutputConfig
tensorBoardOutputConfig
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Maybe POSIX
trainingEndTime
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Maybe Text
trainingJobArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Maybe Text
trainingJobName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Maybe TrainingJobStatus
trainingJobStatus
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Maybe POSIX
trainingStartTime
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Maybe Natural
trainingTimeInSeconds
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Maybe Text
tuningJobArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Maybe VpcConfig
vpcConfig