{-# 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.TrainingJob
-- 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.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

-- | Contains information about a training job.
--
-- /See:/ 'newTrainingJob' smart constructor.
data TrainingJob = TrainingJob'
  { -- | Information about the algorithm used for training, and algorithm
    -- metadata.
    TrainingJob -> Maybe AlgorithmSpecification
algorithmSpecification :: Prelude.Maybe AlgorithmSpecification,
    -- | The Amazon Resource Name (ARN) of the job.
    TrainingJob -> Maybe Text
autoMLJobArn :: Prelude.Maybe Prelude.Text,
    -- | The billable time in seconds.
    TrainingJob -> Maybe Natural
billableTimeInSeconds :: Prelude.Maybe Prelude.Natural,
    TrainingJob -> Maybe CheckpointConfig
checkpointConfig :: Prelude.Maybe CheckpointConfig,
    -- | A timestamp that indicates when the training job was created.
    TrainingJob -> Maybe POSIX
creationTime :: Prelude.Maybe Data.POSIX,
    TrainingJob -> Maybe DebugHookConfig
debugHookConfig :: Prelude.Maybe DebugHookConfig,
    -- | Information about the debug rule configuration.
    TrainingJob -> Maybe [DebugRuleConfiguration]
debugRuleConfigurations :: Prelude.Maybe [DebugRuleConfiguration],
    -- | Information about the evaluation status of the rules for the training
    -- job.
    TrainingJob -> Maybe [DebugRuleEvaluationStatus]
debugRuleEvaluationStatuses :: Prelude.Maybe [DebugRuleEvaluationStatus],
    -- | To encrypt all communications between ML compute instances in
    -- distributed training, choose @True@. Encryption provides greater
    -- security for distributed training, but training might take longer. How
    -- long it takes depends on the amount of communication between compute
    -- instances, especially if you use a deep learning algorithm in
    -- distributed training.
    TrainingJob -> Maybe Bool
enableInterContainerTrafficEncryption :: Prelude.Maybe Prelude.Bool,
    -- | When true, enables managed spot training using Amazon EC2 Spot instances
    -- to run training jobs instead of on-demand instances. For more
    -- information, see
    -- <https://docs.aws.amazon.com/sagemaker/latest/dg/model-managed-spot-training.html Managed Spot Training>.
    TrainingJob -> Maybe Bool
enableManagedSpotTraining :: Prelude.Maybe Prelude.Bool,
    -- | If the @TrainingJob@ was created with network isolation, the value is
    -- set to @true@. If network isolation is enabled, nodes can\'t communicate
    -- beyond the VPC they run in.
    TrainingJob -> Maybe Bool
enableNetworkIsolation :: Prelude.Maybe Prelude.Bool,
    -- | The environment variables to set in the Docker container.
    TrainingJob -> Maybe (HashMap Text Text)
environment :: Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text),
    TrainingJob -> Maybe ExperimentConfig
experimentConfig :: Prelude.Maybe ExperimentConfig,
    -- | If the training job failed, the reason it failed.
    TrainingJob -> Maybe Text
failureReason :: Prelude.Maybe Prelude.Text,
    -- | A list of final metric values that are set when the training job
    -- completes. Used only if the training job was configured to use metrics.
    TrainingJob -> Maybe [MetricData]
finalMetricDataList :: Prelude.Maybe [MetricData],
    -- | Algorithm-specific parameters.
    TrainingJob -> Maybe (HashMap Text Text)
hyperParameters :: Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text),
    -- | An array of @Channel@ objects that describes each data input channel.
    TrainingJob -> Maybe (NonEmpty Channel)
inputDataConfig :: Prelude.Maybe (Prelude.NonEmpty Channel),
    -- | The Amazon Resource Name (ARN) of the labeling job.
    TrainingJob -> Maybe Text
labelingJobArn :: Prelude.Maybe Prelude.Text,
    -- | A timestamp that indicates when the status of the training job was last
    -- modified.
    TrainingJob -> Maybe POSIX
lastModifiedTime :: Prelude.Maybe Data.POSIX,
    -- | Information about the Amazon S3 location that is configured for storing
    -- model artifacts.
    TrainingJob -> Maybe ModelArtifacts
modelArtifacts :: Prelude.Maybe ModelArtifacts,
    -- | The S3 path where model artifacts that you configured when creating the
    -- job are stored. SageMaker creates subfolders for model artifacts.
    TrainingJob -> Maybe OutputDataConfig
outputDataConfig :: Prelude.Maybe OutputDataConfig,
    -- | Resources, including ML compute instances and ML storage volumes, that
    -- are configured for model training.
    TrainingJob -> Maybe ResourceConfig
resourceConfig :: Prelude.Maybe ResourceConfig,
    -- | The number of times to retry the job when the job fails due to an
    -- @InternalServerError@.
    TrainingJob -> Maybe RetryStrategy
retryStrategy :: Prelude.Maybe RetryStrategy,
    -- | The Amazon Web Services Identity and Access Management (IAM) role
    -- configured for the training job.
    TrainingJob -> Maybe Text
roleArn :: Prelude.Maybe Prelude.Text,
    -- | Provides detailed information about the state of the training job. For
    -- detailed information about the secondary status of the training job, see
    -- @StatusMessage@ under SecondaryStatusTransition.
    --
    -- SageMaker provides primary statuses and secondary statuses that apply to
    -- each of them:
    --
    -- [InProgress]
    --     -   @Starting@ - Starting the training job.
    --
    --     -   @Downloading@ - An optional stage for algorithms that support
    --         @File@ training input mode. It indicates that data is being
    --         downloaded to the ML storage volumes.
    --
    --     -   @Training@ - Training is in progress.
    --
    --     -   @Uploading@ - Training is complete and the model artifacts are
    --         being uploaded to the S3 location.
    --
    -- [Completed]
    --     -   @Completed@ - The training job has completed.
    --
    -- [Failed]
    --     -   @Failed@ - The training job has failed. The reason for the
    --         failure is returned in the @FailureReason@ field of
    --         @DescribeTrainingJobResponse@.
    --
    -- [Stopped]
    --     -   @MaxRuntimeExceeded@ - The job stopped because it exceeded the
    --         maximum allowed runtime.
    --
    --     -   @Stopped@ - The training job has stopped.
    --
    -- [Stopping]
    --     -   @Stopping@ - Stopping the training job.
    --
    -- Valid values for @SecondaryStatus@ are subject to change.
    --
    -- We no longer support the following secondary statuses:
    --
    -- -   @LaunchingMLInstances@
    --
    -- -   @PreparingTrainingStack@
    --
    -- -   @DownloadingTrainingImage@
    TrainingJob -> Maybe SecondaryStatus
secondaryStatus :: Prelude.Maybe SecondaryStatus,
    -- | A history of all of the secondary statuses that the training job has
    -- transitioned through.
    TrainingJob -> Maybe [SecondaryStatusTransition]
secondaryStatusTransitions :: Prelude.Maybe [SecondaryStatusTransition],
    -- | Specifies a limit to how long a model training job can run. It also
    -- specifies how long a managed Spot training job has to complete. When the
    -- job reaches the time limit, SageMaker ends the training job. Use this
    -- API to cap model training costs.
    --
    -- To stop a job, SageMaker sends the algorithm the @SIGTERM@ signal, which
    -- delays job termination for 120 seconds. Algorithms can use this
    -- 120-second window to save the model artifacts, so the results of
    -- training are not lost.
    TrainingJob -> Maybe StoppingCondition
stoppingCondition :: Prelude.Maybe StoppingCondition,
    -- | An array of key-value pairs. You can use tags to categorize your Amazon
    -- Web Services resources in different ways, for example, by purpose,
    -- owner, or environment. For more information, see
    -- <https://docs.aws.amazon.com/general/latest/gr/aws_tagging.html Tagging Amazon Web Services Resources>.
    TrainingJob -> Maybe [Tag]
tags :: Prelude.Maybe [Tag],
    TrainingJob -> Maybe TensorBoardOutputConfig
tensorBoardOutputConfig :: Prelude.Maybe TensorBoardOutputConfig,
    -- | Indicates the time when the training job ends on training instances. You
    -- are billed for the time interval between the value of
    -- @TrainingStartTime@ and this time. For successful jobs and stopped jobs,
    -- this is the time after model artifacts are uploaded. For failed jobs,
    -- this is the time when SageMaker detects a job failure.
    TrainingJob -> Maybe POSIX
trainingEndTime :: Prelude.Maybe Data.POSIX,
    -- | The Amazon Resource Name (ARN) of the training job.
    TrainingJob -> Maybe Text
trainingJobArn :: Prelude.Maybe Prelude.Text,
    -- | The name of the training job.
    TrainingJob -> Maybe Text
trainingJobName :: Prelude.Maybe Prelude.Text,
    -- | The status of the training job.
    --
    -- Training job statuses are:
    --
    -- -   @InProgress@ - The training is in progress.
    --
    -- -   @Completed@ - The training job has completed.
    --
    -- -   @Failed@ - The training job has failed. To see the reason for the
    --     failure, see the @FailureReason@ field in the response to a
    --     @DescribeTrainingJobResponse@ call.
    --
    -- -   @Stopping@ - The training job is stopping.
    --
    -- -   @Stopped@ - The training job has stopped.
    --
    -- For more detailed information, see @SecondaryStatus@.
    TrainingJob -> Maybe TrainingJobStatus
trainingJobStatus :: Prelude.Maybe TrainingJobStatus,
    -- | Indicates the time when the training job starts on training instances.
    -- You are billed for the time interval between this time and the value of
    -- @TrainingEndTime@. The start time in CloudWatch Logs might be later than
    -- this time. The difference is due to the time it takes to download the
    -- training data and to the size of the training container.
    TrainingJob -> Maybe POSIX
trainingStartTime :: Prelude.Maybe Data.POSIX,
    -- | The training time in seconds.
    TrainingJob -> Maybe Natural
trainingTimeInSeconds :: Prelude.Maybe Prelude.Natural,
    -- | The Amazon Resource Name (ARN) of the associated hyperparameter tuning
    -- job if the training job was launched by a hyperparameter tuning job.
    TrainingJob -> Maybe Text
tuningJobArn :: Prelude.Maybe Prelude.Text,
    -- | A VpcConfig object that specifies the VPC that this training job has
    -- access to. For more information, see
    -- <https://docs.aws.amazon.com/sagemaker/latest/dg/train-vpc.html Protect Training Jobs by Using an Amazon Virtual Private Cloud>.
    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)

-- |
-- Create a value of 'TrainingJob' 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:
--
-- 'algorithmSpecification', 'trainingJob_algorithmSpecification' - Information about the algorithm used for training, and algorithm
-- metadata.
--
-- 'autoMLJobArn', 'trainingJob_autoMLJobArn' - The Amazon Resource Name (ARN) of the job.
--
-- 'billableTimeInSeconds', 'trainingJob_billableTimeInSeconds' - The billable time in seconds.
--
-- 'checkpointConfig', 'trainingJob_checkpointConfig' - Undocumented member.
--
-- 'creationTime', 'trainingJob_creationTime' - A timestamp that indicates when the training job was created.
--
-- 'debugHookConfig', 'trainingJob_debugHookConfig' - Undocumented member.
--
-- 'debugRuleConfigurations', 'trainingJob_debugRuleConfigurations' - Information about the debug rule configuration.
--
-- 'debugRuleEvaluationStatuses', 'trainingJob_debugRuleEvaluationStatuses' - Information about the evaluation status of the rules for the training
-- job.
--
-- 'enableInterContainerTrafficEncryption', 'trainingJob_enableInterContainerTrafficEncryption' - To encrypt all communications between ML compute instances in
-- distributed training, choose @True@. Encryption provides greater
-- security for distributed training, but training might take longer. How
-- long it takes depends on the amount of communication between compute
-- instances, especially if you use a deep learning algorithm in
-- distributed training.
--
-- 'enableManagedSpotTraining', 'trainingJob_enableManagedSpotTraining' - When true, enables managed spot training using Amazon EC2 Spot instances
-- to run training jobs instead of on-demand instances. For more
-- information, see
-- <https://docs.aws.amazon.com/sagemaker/latest/dg/model-managed-spot-training.html Managed Spot Training>.
--
-- 'enableNetworkIsolation', 'trainingJob_enableNetworkIsolation' - If the @TrainingJob@ was created with network isolation, the value is
-- set to @true@. If network isolation is enabled, nodes can\'t communicate
-- beyond the VPC they run in.
--
-- 'environment', 'trainingJob_environment' - The environment variables to set in the Docker container.
--
-- 'experimentConfig', 'trainingJob_experimentConfig' - Undocumented member.
--
-- 'failureReason', 'trainingJob_failureReason' - If the training job failed, the reason it failed.
--
-- 'finalMetricDataList', 'trainingJob_finalMetricDataList' - A list of final metric values that are set when the training job
-- completes. Used only if the training job was configured to use metrics.
--
-- 'hyperParameters', 'trainingJob_hyperParameters' - Algorithm-specific parameters.
--
-- 'inputDataConfig', 'trainingJob_inputDataConfig' - An array of @Channel@ objects that describes each data input channel.
--
-- 'labelingJobArn', 'trainingJob_labelingJobArn' - The Amazon Resource Name (ARN) of the labeling job.
--
-- 'lastModifiedTime', 'trainingJob_lastModifiedTime' - A timestamp that indicates when the status of the training job was last
-- modified.
--
-- 'modelArtifacts', 'trainingJob_modelArtifacts' - Information about the Amazon S3 location that is configured for storing
-- model artifacts.
--
-- 'outputDataConfig', 'trainingJob_outputDataConfig' - The S3 path where model artifacts that you configured when creating the
-- job are stored. SageMaker creates subfolders for model artifacts.
--
-- 'resourceConfig', 'trainingJob_resourceConfig' - Resources, including ML compute instances and ML storage volumes, that
-- are configured for model training.
--
-- 'retryStrategy', 'trainingJob_retryStrategy' - The number of times to retry the job when the job fails due to an
-- @InternalServerError@.
--
-- 'roleArn', 'trainingJob_roleArn' - The Amazon Web Services Identity and Access Management (IAM) role
-- configured for the training job.
--
-- 'secondaryStatus', 'trainingJob_secondaryStatus' - Provides detailed information about the state of the training job. For
-- detailed information about the secondary status of the training job, see
-- @StatusMessage@ under SecondaryStatusTransition.
--
-- SageMaker provides primary statuses and secondary statuses that apply to
-- each of them:
--
-- [InProgress]
--     -   @Starting@ - Starting the training job.
--
--     -   @Downloading@ - An optional stage for algorithms that support
--         @File@ training input mode. It indicates that data is being
--         downloaded to the ML storage volumes.
--
--     -   @Training@ - Training is in progress.
--
--     -   @Uploading@ - Training is complete and the model artifacts are
--         being uploaded to the S3 location.
--
-- [Completed]
--     -   @Completed@ - The training job has completed.
--
-- [Failed]
--     -   @Failed@ - The training job has failed. The reason for the
--         failure is returned in the @FailureReason@ field of
--         @DescribeTrainingJobResponse@.
--
-- [Stopped]
--     -   @MaxRuntimeExceeded@ - The job stopped because it exceeded the
--         maximum allowed runtime.
--
--     -   @Stopped@ - The training job has stopped.
--
-- [Stopping]
--     -   @Stopping@ - Stopping the training job.
--
-- Valid values for @SecondaryStatus@ are subject to change.
--
-- We no longer support the following secondary statuses:
--
-- -   @LaunchingMLInstances@
--
-- -   @PreparingTrainingStack@
--
-- -   @DownloadingTrainingImage@
--
-- 'secondaryStatusTransitions', 'trainingJob_secondaryStatusTransitions' - A history of all of the secondary statuses that the training job has
-- transitioned through.
--
-- 'stoppingCondition', 'trainingJob_stoppingCondition' - Specifies a limit to how long a model training job can run. It also
-- specifies how long a managed Spot training job has to complete. When the
-- job reaches the time limit, SageMaker ends the training job. Use this
-- API to cap model training costs.
--
-- To stop a job, SageMaker sends the algorithm the @SIGTERM@ signal, which
-- delays job termination for 120 seconds. Algorithms can use this
-- 120-second window to save the model artifacts, so the results of
-- training are not lost.
--
-- 'tags', 'trainingJob_tags' - An array of key-value pairs. You can use tags to categorize your Amazon
-- Web Services resources in different ways, for example, by purpose,
-- owner, or environment. For more information, see
-- <https://docs.aws.amazon.com/general/latest/gr/aws_tagging.html Tagging Amazon Web Services Resources>.
--
-- 'tensorBoardOutputConfig', 'trainingJob_tensorBoardOutputConfig' - Undocumented member.
--
-- 'trainingEndTime', 'trainingJob_trainingEndTime' - Indicates the time when the training job ends on training instances. You
-- are billed for the time interval between the value of
-- @TrainingStartTime@ and this time. For successful jobs and stopped jobs,
-- this is the time after model artifacts are uploaded. For failed jobs,
-- this is the time when SageMaker detects a job failure.
--
-- 'trainingJobArn', 'trainingJob_trainingJobArn' - The Amazon Resource Name (ARN) of the training job.
--
-- 'trainingJobName', 'trainingJob_trainingJobName' - The name of the training job.
--
-- 'trainingJobStatus', 'trainingJob_trainingJobStatus' - The status of the training job.
--
-- Training job statuses are:
--
-- -   @InProgress@ - The training is in progress.
--
-- -   @Completed@ - The training job has completed.
--
-- -   @Failed@ - The training job has failed. To see the reason for the
--     failure, see the @FailureReason@ field in the response to a
--     @DescribeTrainingJobResponse@ call.
--
-- -   @Stopping@ - The training job is stopping.
--
-- -   @Stopped@ - The training job has stopped.
--
-- For more detailed information, see @SecondaryStatus@.
--
-- 'trainingStartTime', 'trainingJob_trainingStartTime' - Indicates the time when the training job starts on training instances.
-- You are billed for the time interval between this time and the value of
-- @TrainingEndTime@. The start time in CloudWatch Logs might be later than
-- this time. The difference is due to the time it takes to download the
-- training data and to the size of the training container.
--
-- 'trainingTimeInSeconds', 'trainingJob_trainingTimeInSeconds' - The training time in seconds.
--
-- 'tuningJobArn', 'trainingJob_tuningJobArn' - The Amazon Resource Name (ARN) of the associated hyperparameter tuning
-- job if the training job was launched by a hyperparameter tuning job.
--
-- 'vpcConfig', 'trainingJob_vpcConfig' - A VpcConfig object that specifies the VPC that this training job has
-- access to. For more information, see
-- <https://docs.aws.amazon.com/sagemaker/latest/dg/train-vpc.html Protect Training Jobs by Using an Amazon Virtual Private Cloud>.
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
    }

-- | Information about the algorithm used for training, and algorithm
-- metadata.
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)

-- | The Amazon Resource Name (ARN) of the job.
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)

-- | The billable time in seconds.
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)

-- | Undocumented member.
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)

-- | A timestamp that indicates when the training job was created.
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

-- | Undocumented member.
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)

-- | Information about the debug rule configuration.
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

-- | Information about the evaluation status of the rules for the training
-- job.
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

-- | To encrypt all communications between ML compute instances in
-- distributed training, choose @True@. Encryption provides greater
-- security for distributed training, but training might take longer. How
-- long it takes depends on the amount of communication between compute
-- instances, especially if you use a deep learning algorithm in
-- distributed training.
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)

-- | When true, enables managed spot training using Amazon EC2 Spot instances
-- to run training jobs instead of on-demand instances. For more
-- information, see
-- <https://docs.aws.amazon.com/sagemaker/latest/dg/model-managed-spot-training.html Managed Spot Training>.
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)

-- | If the @TrainingJob@ was created with network isolation, the value is
-- set to @true@. If network isolation is enabled, nodes can\'t communicate
-- beyond the VPC they run in.
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)

-- | The environment variables to set in the Docker container.
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

-- | Undocumented member.
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)

-- | If the training job failed, the reason it failed.
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)

-- | A list of final metric values that are set when the training job
-- completes. Used only if the training job was configured to use metrics.
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

-- | Algorithm-specific parameters.
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

-- | An array of @Channel@ objects that describes each data input channel.
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

-- | The Amazon Resource Name (ARN) of the labeling job.
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)

-- | A timestamp that indicates when the status of the training job was last
-- modified.
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

-- | Information about the Amazon S3 location that is configured for storing
-- model artifacts.
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)

-- | The S3 path where model artifacts that you configured when creating the
-- job are stored. SageMaker creates subfolders for model artifacts.
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)

-- | Resources, including ML compute instances and ML storage volumes, that
-- are configured for model training.
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)

-- | The number of times to retry the job when the job fails due to an
-- @InternalServerError@.
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)

-- | The Amazon Web Services Identity and Access Management (IAM) role
-- configured for the training job.
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)

-- | Provides detailed information about the state of the training job. For
-- detailed information about the secondary status of the training job, see
-- @StatusMessage@ under SecondaryStatusTransition.
--
-- SageMaker provides primary statuses and secondary statuses that apply to
-- each of them:
--
-- [InProgress]
--     -   @Starting@ - Starting the training job.
--
--     -   @Downloading@ - An optional stage for algorithms that support
--         @File@ training input mode. It indicates that data is being
--         downloaded to the ML storage volumes.
--
--     -   @Training@ - Training is in progress.
--
--     -   @Uploading@ - Training is complete and the model artifacts are
--         being uploaded to the S3 location.
--
-- [Completed]
--     -   @Completed@ - The training job has completed.
--
-- [Failed]
--     -   @Failed@ - The training job has failed. The reason for the
--         failure is returned in the @FailureReason@ field of
--         @DescribeTrainingJobResponse@.
--
-- [Stopped]
--     -   @MaxRuntimeExceeded@ - The job stopped because it exceeded the
--         maximum allowed runtime.
--
--     -   @Stopped@ - The training job has stopped.
--
-- [Stopping]
--     -   @Stopping@ - Stopping the training job.
--
-- Valid values for @SecondaryStatus@ are subject to change.
--
-- We no longer support the following secondary statuses:
--
-- -   @LaunchingMLInstances@
--
-- -   @PreparingTrainingStack@
--
-- -   @DownloadingTrainingImage@
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)

-- | A history of all of the secondary statuses that the training job has
-- transitioned through.
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

-- | Specifies a limit to how long a model training job can run. It also
-- specifies how long a managed Spot training job has to complete. When the
-- job reaches the time limit, SageMaker ends the training job. Use this
-- API to cap model training costs.
--
-- To stop a job, SageMaker sends the algorithm the @SIGTERM@ signal, which
-- delays job termination for 120 seconds. Algorithms can use this
-- 120-second window to save the model artifacts, so the results of
-- training are not lost.
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)

-- | An array of key-value pairs. You can use tags to categorize your Amazon
-- Web Services resources in different ways, for example, by purpose,
-- owner, or environment. For more information, see
-- <https://docs.aws.amazon.com/general/latest/gr/aws_tagging.html Tagging Amazon Web Services Resources>.
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

-- | Undocumented member.
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)

-- | Indicates the time when the training job ends on training instances. You
-- are billed for the time interval between the value of
-- @TrainingStartTime@ and this time. For successful jobs and stopped jobs,
-- this is the time after model artifacts are uploaded. For failed jobs,
-- this is the time when SageMaker detects a job failure.
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

-- | The Amazon Resource Name (ARN) of the training job.
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)

-- | The name of the training job.
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)

-- | The status of the training job.
--
-- Training job statuses are:
--
-- -   @InProgress@ - The training is in progress.
--
-- -   @Completed@ - The training job has completed.
--
-- -   @Failed@ - The training job has failed. To see the reason for the
--     failure, see the @FailureReason@ field in the response to a
--     @DescribeTrainingJobResponse@ call.
--
-- -   @Stopping@ - The training job is stopping.
--
-- -   @Stopped@ - The training job has stopped.
--
-- For more detailed information, see @SecondaryStatus@.
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)

-- | Indicates the time when the training job starts on training instances.
-- You are billed for the time interval between this time and the value of
-- @TrainingEndTime@. The start time in CloudWatch Logs might be later than
-- this time. The difference is due to the time it takes to download the
-- training data and to the size of the training container.
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

-- | The training time in seconds.
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)

-- | The Amazon Resource Name (ARN) of the associated hyperparameter tuning
-- job if the training job was launched by a hyperparameter tuning job.
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)

-- | A VpcConfig object that specifies the VPC that this training job has
-- access to. For more information, see
-- <https://docs.aws.amazon.com/sagemaker/latest/dg/train-vpc.html Protect Training Jobs by Using an Amazon Virtual Private Cloud>.
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