{-# 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.HyperParameterTrainingJobDefinition
-- 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.HyperParameterTrainingJobDefinition 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.Channel
import Amazonka.SageMaker.Types.CheckpointConfig
import Amazonka.SageMaker.Types.HyperParameterAlgorithmSpecification
import Amazonka.SageMaker.Types.HyperParameterTuningJobObjective
import Amazonka.SageMaker.Types.HyperParameterTuningResourceConfig
import Amazonka.SageMaker.Types.OutputDataConfig
import Amazonka.SageMaker.Types.ParameterRanges
import Amazonka.SageMaker.Types.ResourceConfig
import Amazonka.SageMaker.Types.RetryStrategy
import Amazonka.SageMaker.Types.StoppingCondition
import Amazonka.SageMaker.Types.VpcConfig

-- | Defines the training jobs launched by a hyperparameter tuning job.
--
-- /See:/ 'newHyperParameterTrainingJobDefinition' smart constructor.
data HyperParameterTrainingJobDefinition = HyperParameterTrainingJobDefinition'
  { HyperParameterTrainingJobDefinition -> Maybe CheckpointConfig
checkpointConfig :: Prelude.Maybe CheckpointConfig,
    -- | The job definition name.
    HyperParameterTrainingJobDefinition -> Maybe Text
definitionName :: Prelude.Maybe Prelude.Text,
    -- | 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.
    HyperParameterTrainingJobDefinition -> Maybe Bool
enableInterContainerTrafficEncryption :: Prelude.Maybe Prelude.Bool,
    -- | A Boolean indicating whether managed spot training is enabled (@True@)
    -- or not (@False@).
    HyperParameterTrainingJobDefinition -> Maybe Bool
enableManagedSpotTraining :: Prelude.Maybe Prelude.Bool,
    -- | Isolates the training container. No inbound or outbound network calls
    -- can be made, except for calls between peers within a training cluster
    -- for distributed training. If network isolation is used for training jobs
    -- that are configured to use a VPC, SageMaker downloads and uploads
    -- customer data and model artifacts through the specified VPC, but the
    -- training container does not have network access.
    HyperParameterTrainingJobDefinition -> Maybe Bool
enableNetworkIsolation :: Prelude.Maybe Prelude.Bool,
    HyperParameterTrainingJobDefinition -> Maybe ParameterRanges
hyperParameterRanges :: Prelude.Maybe ParameterRanges,
    -- | The configuration for the hyperparameter tuning resources, including the
    -- compute instances and storage volumes, used for training jobs launched
    -- by the tuning job. By default, storage volumes hold model artifacts and
    -- incremental states. Choose @File@ for @TrainingInputMode@ in the
    -- @AlgorithmSpecification@ parameter to additionally store training data
    -- in the storage volume (optional).
    HyperParameterTrainingJobDefinition
-> Maybe HyperParameterTuningResourceConfig
hyperParameterTuningResourceConfig :: Prelude.Maybe HyperParameterTuningResourceConfig,
    -- | An array of Channel objects that specify the input for the training jobs
    -- that the tuning job launches.
    HyperParameterTrainingJobDefinition -> Maybe (NonEmpty Channel)
inputDataConfig :: Prelude.Maybe (Prelude.NonEmpty Channel),
    -- | The resources, including the compute instances and storage volumes, to
    -- use for the training jobs that the tuning job launches.
    --
    -- Storage volumes store model artifacts and incremental states. Training
    -- algorithms might also use storage volumes for scratch space. If you want
    -- SageMaker to use the storage volume to store the training data, choose
    -- @File@ as the @TrainingInputMode@ in the algorithm specification. For
    -- distributed training algorithms, specify an instance count greater than
    -- 1.
    --
    -- If you want to use hyperparameter optimization with instance type
    -- flexibility, use @HyperParameterTuningResourceConfig@ instead.
    HyperParameterTrainingJobDefinition -> Maybe ResourceConfig
resourceConfig :: Prelude.Maybe ResourceConfig,
    -- | The number of times to retry the job when the job fails due to an
    -- @InternalServerError@.
    HyperParameterTrainingJobDefinition -> Maybe RetryStrategy
retryStrategy :: Prelude.Maybe RetryStrategy,
    -- | Specifies the values of hyperparameters that do not change for the
    -- tuning job.
    HyperParameterTrainingJobDefinition -> Maybe (HashMap Text Text)
staticHyperParameters :: Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text),
    HyperParameterTrainingJobDefinition
-> Maybe HyperParameterTuningJobObjective
tuningObjective :: Prelude.Maybe HyperParameterTuningJobObjective,
    -- | The VpcConfig object that specifies the VPC that you want the training
    -- jobs that this hyperparameter tuning job launches to connect to. Control
    -- access to and from your training container by configuring the VPC. 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>.
    HyperParameterTrainingJobDefinition -> Maybe VpcConfig
vpcConfig :: Prelude.Maybe VpcConfig,
    -- | The HyperParameterAlgorithmSpecification object that specifies the
    -- resource algorithm to use for the training jobs that the tuning job
    -- launches.
    HyperParameterTrainingJobDefinition
-> HyperParameterAlgorithmSpecification
algorithmSpecification :: HyperParameterAlgorithmSpecification,
    -- | The Amazon Resource Name (ARN) of the IAM role associated with the
    -- training jobs that the tuning job launches.
    HyperParameterTrainingJobDefinition -> Text
roleArn :: Prelude.Text,
    -- | Specifies the path to the Amazon S3 bucket where you store model
    -- artifacts from the training jobs that the tuning job launches.
    HyperParameterTrainingJobDefinition -> OutputDataConfig
outputDataConfig :: OutputDataConfig,
    -- | Specifies a limit to how long a model hyperparameter 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.
    HyperParameterTrainingJobDefinition -> StoppingCondition
stoppingCondition :: StoppingCondition
  }
  deriving (HyperParameterTrainingJobDefinition
-> HyperParameterTrainingJobDefinition -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: HyperParameterTrainingJobDefinition
-> HyperParameterTrainingJobDefinition -> Bool
$c/= :: HyperParameterTrainingJobDefinition
-> HyperParameterTrainingJobDefinition -> Bool
== :: HyperParameterTrainingJobDefinition
-> HyperParameterTrainingJobDefinition -> Bool
$c== :: HyperParameterTrainingJobDefinition
-> HyperParameterTrainingJobDefinition -> Bool
Prelude.Eq, ReadPrec [HyperParameterTrainingJobDefinition]
ReadPrec HyperParameterTrainingJobDefinition
Int -> ReadS HyperParameterTrainingJobDefinition
ReadS [HyperParameterTrainingJobDefinition]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [HyperParameterTrainingJobDefinition]
$creadListPrec :: ReadPrec [HyperParameterTrainingJobDefinition]
readPrec :: ReadPrec HyperParameterTrainingJobDefinition
$creadPrec :: ReadPrec HyperParameterTrainingJobDefinition
readList :: ReadS [HyperParameterTrainingJobDefinition]
$creadList :: ReadS [HyperParameterTrainingJobDefinition]
readsPrec :: Int -> ReadS HyperParameterTrainingJobDefinition
$creadsPrec :: Int -> ReadS HyperParameterTrainingJobDefinition
Prelude.Read, Int -> HyperParameterTrainingJobDefinition -> ShowS
[HyperParameterTrainingJobDefinition] -> ShowS
HyperParameterTrainingJobDefinition -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [HyperParameterTrainingJobDefinition] -> ShowS
$cshowList :: [HyperParameterTrainingJobDefinition] -> ShowS
show :: HyperParameterTrainingJobDefinition -> String
$cshow :: HyperParameterTrainingJobDefinition -> String
showsPrec :: Int -> HyperParameterTrainingJobDefinition -> ShowS
$cshowsPrec :: Int -> HyperParameterTrainingJobDefinition -> ShowS
Prelude.Show, forall x.
Rep HyperParameterTrainingJobDefinition x
-> HyperParameterTrainingJobDefinition
forall x.
HyperParameterTrainingJobDefinition
-> Rep HyperParameterTrainingJobDefinition x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep HyperParameterTrainingJobDefinition x
-> HyperParameterTrainingJobDefinition
$cfrom :: forall x.
HyperParameterTrainingJobDefinition
-> Rep HyperParameterTrainingJobDefinition x
Prelude.Generic)

-- |
-- Create a value of 'HyperParameterTrainingJobDefinition' 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:
--
-- 'checkpointConfig', 'hyperParameterTrainingJobDefinition_checkpointConfig' - Undocumented member.
--
-- 'definitionName', 'hyperParameterTrainingJobDefinition_definitionName' - The job definition name.
--
-- 'enableInterContainerTrafficEncryption', 'hyperParameterTrainingJobDefinition_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', 'hyperParameterTrainingJobDefinition_enableManagedSpotTraining' - A Boolean indicating whether managed spot training is enabled (@True@)
-- or not (@False@).
--
-- 'enableNetworkIsolation', 'hyperParameterTrainingJobDefinition_enableNetworkIsolation' - Isolates the training container. No inbound or outbound network calls
-- can be made, except for calls between peers within a training cluster
-- for distributed training. If network isolation is used for training jobs
-- that are configured to use a VPC, SageMaker downloads and uploads
-- customer data and model artifacts through the specified VPC, but the
-- training container does not have network access.
--
-- 'hyperParameterRanges', 'hyperParameterTrainingJobDefinition_hyperParameterRanges' - Undocumented member.
--
-- 'hyperParameterTuningResourceConfig', 'hyperParameterTrainingJobDefinition_hyperParameterTuningResourceConfig' - The configuration for the hyperparameter tuning resources, including the
-- compute instances and storage volumes, used for training jobs launched
-- by the tuning job. By default, storage volumes hold model artifacts and
-- incremental states. Choose @File@ for @TrainingInputMode@ in the
-- @AlgorithmSpecification@ parameter to additionally store training data
-- in the storage volume (optional).
--
-- 'inputDataConfig', 'hyperParameterTrainingJobDefinition_inputDataConfig' - An array of Channel objects that specify the input for the training jobs
-- that the tuning job launches.
--
-- 'resourceConfig', 'hyperParameterTrainingJobDefinition_resourceConfig' - The resources, including the compute instances and storage volumes, to
-- use for the training jobs that the tuning job launches.
--
-- Storage volumes store model artifacts and incremental states. Training
-- algorithms might also use storage volumes for scratch space. If you want
-- SageMaker to use the storage volume to store the training data, choose
-- @File@ as the @TrainingInputMode@ in the algorithm specification. For
-- distributed training algorithms, specify an instance count greater than
-- 1.
--
-- If you want to use hyperparameter optimization with instance type
-- flexibility, use @HyperParameterTuningResourceConfig@ instead.
--
-- 'retryStrategy', 'hyperParameterTrainingJobDefinition_retryStrategy' - The number of times to retry the job when the job fails due to an
-- @InternalServerError@.
--
-- 'staticHyperParameters', 'hyperParameterTrainingJobDefinition_staticHyperParameters' - Specifies the values of hyperparameters that do not change for the
-- tuning job.
--
-- 'tuningObjective', 'hyperParameterTrainingJobDefinition_tuningObjective' - Undocumented member.
--
-- 'vpcConfig', 'hyperParameterTrainingJobDefinition_vpcConfig' - The VpcConfig object that specifies the VPC that you want the training
-- jobs that this hyperparameter tuning job launches to connect to. Control
-- access to and from your training container by configuring the VPC. 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>.
--
-- 'algorithmSpecification', 'hyperParameterTrainingJobDefinition_algorithmSpecification' - The HyperParameterAlgorithmSpecification object that specifies the
-- resource algorithm to use for the training jobs that the tuning job
-- launches.
--
-- 'roleArn', 'hyperParameterTrainingJobDefinition_roleArn' - The Amazon Resource Name (ARN) of the IAM role associated with the
-- training jobs that the tuning job launches.
--
-- 'outputDataConfig', 'hyperParameterTrainingJobDefinition_outputDataConfig' - Specifies the path to the Amazon S3 bucket where you store model
-- artifacts from the training jobs that the tuning job launches.
--
-- 'stoppingCondition', 'hyperParameterTrainingJobDefinition_stoppingCondition' - Specifies a limit to how long a model hyperparameter 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.
newHyperParameterTrainingJobDefinition ::
  -- | 'algorithmSpecification'
  HyperParameterAlgorithmSpecification ->
  -- | 'roleArn'
  Prelude.Text ->
  -- | 'outputDataConfig'
  OutputDataConfig ->
  -- | 'stoppingCondition'
  StoppingCondition ->
  HyperParameterTrainingJobDefinition
newHyperParameterTrainingJobDefinition :: HyperParameterAlgorithmSpecification
-> Text
-> OutputDataConfig
-> StoppingCondition
-> HyperParameterTrainingJobDefinition
newHyperParameterTrainingJobDefinition
  HyperParameterAlgorithmSpecification
pAlgorithmSpecification_
  Text
pRoleArn_
  OutputDataConfig
pOutputDataConfig_
  StoppingCondition
pStoppingCondition_ =
    HyperParameterTrainingJobDefinition'
      { $sel:checkpointConfig:HyperParameterTrainingJobDefinition' :: Maybe CheckpointConfig
checkpointConfig =
          forall a. Maybe a
Prelude.Nothing,
        $sel:definitionName:HyperParameterTrainingJobDefinition' :: Maybe Text
definitionName = forall a. Maybe a
Prelude.Nothing,
        $sel:enableInterContainerTrafficEncryption:HyperParameterTrainingJobDefinition' :: Maybe Bool
enableInterContainerTrafficEncryption =
          forall a. Maybe a
Prelude.Nothing,
        $sel:enableManagedSpotTraining:HyperParameterTrainingJobDefinition' :: Maybe Bool
enableManagedSpotTraining =
          forall a. Maybe a
Prelude.Nothing,
        $sel:enableNetworkIsolation:HyperParameterTrainingJobDefinition' :: Maybe Bool
enableNetworkIsolation =
          forall a. Maybe a
Prelude.Nothing,
        $sel:hyperParameterRanges:HyperParameterTrainingJobDefinition' :: Maybe ParameterRanges
hyperParameterRanges = forall a. Maybe a
Prelude.Nothing,
        $sel:hyperParameterTuningResourceConfig:HyperParameterTrainingJobDefinition' :: Maybe HyperParameterTuningResourceConfig
hyperParameterTuningResourceConfig =
          forall a. Maybe a
Prelude.Nothing,
        $sel:inputDataConfig:HyperParameterTrainingJobDefinition' :: Maybe (NonEmpty Channel)
inputDataConfig = forall a. Maybe a
Prelude.Nothing,
        $sel:resourceConfig:HyperParameterTrainingJobDefinition' :: Maybe ResourceConfig
resourceConfig = forall a. Maybe a
Prelude.Nothing,
        $sel:retryStrategy:HyperParameterTrainingJobDefinition' :: Maybe RetryStrategy
retryStrategy = forall a. Maybe a
Prelude.Nothing,
        $sel:staticHyperParameters:HyperParameterTrainingJobDefinition' :: Maybe (HashMap Text Text)
staticHyperParameters =
          forall a. Maybe a
Prelude.Nothing,
        $sel:tuningObjective:HyperParameterTrainingJobDefinition' :: Maybe HyperParameterTuningJobObjective
tuningObjective = forall a. Maybe a
Prelude.Nothing,
        $sel:vpcConfig:HyperParameterTrainingJobDefinition' :: Maybe VpcConfig
vpcConfig = forall a. Maybe a
Prelude.Nothing,
        $sel:algorithmSpecification:HyperParameterTrainingJobDefinition' :: HyperParameterAlgorithmSpecification
algorithmSpecification =
          HyperParameterAlgorithmSpecification
pAlgorithmSpecification_,
        $sel:roleArn:HyperParameterTrainingJobDefinition' :: Text
roleArn = Text
pRoleArn_,
        $sel:outputDataConfig:HyperParameterTrainingJobDefinition' :: OutputDataConfig
outputDataConfig = OutputDataConfig
pOutputDataConfig_,
        $sel:stoppingCondition:HyperParameterTrainingJobDefinition' :: StoppingCondition
stoppingCondition =
          StoppingCondition
pStoppingCondition_
      }

-- | Undocumented member.
hyperParameterTrainingJobDefinition_checkpointConfig :: Lens.Lens' HyperParameterTrainingJobDefinition (Prelude.Maybe CheckpointConfig)
hyperParameterTrainingJobDefinition_checkpointConfig :: Lens' HyperParameterTrainingJobDefinition (Maybe CheckpointConfig)
hyperParameterTrainingJobDefinition_checkpointConfig = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\HyperParameterTrainingJobDefinition' {Maybe CheckpointConfig
checkpointConfig :: Maybe CheckpointConfig
$sel:checkpointConfig:HyperParameterTrainingJobDefinition' :: HyperParameterTrainingJobDefinition -> Maybe CheckpointConfig
checkpointConfig} -> Maybe CheckpointConfig
checkpointConfig) (\s :: HyperParameterTrainingJobDefinition
s@HyperParameterTrainingJobDefinition' {} Maybe CheckpointConfig
a -> HyperParameterTrainingJobDefinition
s {$sel:checkpointConfig:HyperParameterTrainingJobDefinition' :: Maybe CheckpointConfig
checkpointConfig = Maybe CheckpointConfig
a} :: HyperParameterTrainingJobDefinition)

-- | The job definition name.
hyperParameterTrainingJobDefinition_definitionName :: Lens.Lens' HyperParameterTrainingJobDefinition (Prelude.Maybe Prelude.Text)
hyperParameterTrainingJobDefinition_definitionName :: Lens' HyperParameterTrainingJobDefinition (Maybe Text)
hyperParameterTrainingJobDefinition_definitionName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\HyperParameterTrainingJobDefinition' {Maybe Text
definitionName :: Maybe Text
$sel:definitionName:HyperParameterTrainingJobDefinition' :: HyperParameterTrainingJobDefinition -> Maybe Text
definitionName} -> Maybe Text
definitionName) (\s :: HyperParameterTrainingJobDefinition
s@HyperParameterTrainingJobDefinition' {} Maybe Text
a -> HyperParameterTrainingJobDefinition
s {$sel:definitionName:HyperParameterTrainingJobDefinition' :: Maybe Text
definitionName = Maybe Text
a} :: HyperParameterTrainingJobDefinition)

-- | 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.
hyperParameterTrainingJobDefinition_enableInterContainerTrafficEncryption :: Lens.Lens' HyperParameterTrainingJobDefinition (Prelude.Maybe Prelude.Bool)
hyperParameterTrainingJobDefinition_enableInterContainerTrafficEncryption :: Lens' HyperParameterTrainingJobDefinition (Maybe Bool)
hyperParameterTrainingJobDefinition_enableInterContainerTrafficEncryption = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\HyperParameterTrainingJobDefinition' {Maybe Bool
enableInterContainerTrafficEncryption :: Maybe Bool
$sel:enableInterContainerTrafficEncryption:HyperParameterTrainingJobDefinition' :: HyperParameterTrainingJobDefinition -> Maybe Bool
enableInterContainerTrafficEncryption} -> Maybe Bool
enableInterContainerTrafficEncryption) (\s :: HyperParameterTrainingJobDefinition
s@HyperParameterTrainingJobDefinition' {} Maybe Bool
a -> HyperParameterTrainingJobDefinition
s {$sel:enableInterContainerTrafficEncryption:HyperParameterTrainingJobDefinition' :: Maybe Bool
enableInterContainerTrafficEncryption = Maybe Bool
a} :: HyperParameterTrainingJobDefinition)

-- | A Boolean indicating whether managed spot training is enabled (@True@)
-- or not (@False@).
hyperParameterTrainingJobDefinition_enableManagedSpotTraining :: Lens.Lens' HyperParameterTrainingJobDefinition (Prelude.Maybe Prelude.Bool)
hyperParameterTrainingJobDefinition_enableManagedSpotTraining :: Lens' HyperParameterTrainingJobDefinition (Maybe Bool)
hyperParameterTrainingJobDefinition_enableManagedSpotTraining = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\HyperParameterTrainingJobDefinition' {Maybe Bool
enableManagedSpotTraining :: Maybe Bool
$sel:enableManagedSpotTraining:HyperParameterTrainingJobDefinition' :: HyperParameterTrainingJobDefinition -> Maybe Bool
enableManagedSpotTraining} -> Maybe Bool
enableManagedSpotTraining) (\s :: HyperParameterTrainingJobDefinition
s@HyperParameterTrainingJobDefinition' {} Maybe Bool
a -> HyperParameterTrainingJobDefinition
s {$sel:enableManagedSpotTraining:HyperParameterTrainingJobDefinition' :: Maybe Bool
enableManagedSpotTraining = Maybe Bool
a} :: HyperParameterTrainingJobDefinition)

-- | Isolates the training container. No inbound or outbound network calls
-- can be made, except for calls between peers within a training cluster
-- for distributed training. If network isolation is used for training jobs
-- that are configured to use a VPC, SageMaker downloads and uploads
-- customer data and model artifacts through the specified VPC, but the
-- training container does not have network access.
hyperParameterTrainingJobDefinition_enableNetworkIsolation :: Lens.Lens' HyperParameterTrainingJobDefinition (Prelude.Maybe Prelude.Bool)
hyperParameterTrainingJobDefinition_enableNetworkIsolation :: Lens' HyperParameterTrainingJobDefinition (Maybe Bool)
hyperParameterTrainingJobDefinition_enableNetworkIsolation = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\HyperParameterTrainingJobDefinition' {Maybe Bool
enableNetworkIsolation :: Maybe Bool
$sel:enableNetworkIsolation:HyperParameterTrainingJobDefinition' :: HyperParameterTrainingJobDefinition -> Maybe Bool
enableNetworkIsolation} -> Maybe Bool
enableNetworkIsolation) (\s :: HyperParameterTrainingJobDefinition
s@HyperParameterTrainingJobDefinition' {} Maybe Bool
a -> HyperParameterTrainingJobDefinition
s {$sel:enableNetworkIsolation:HyperParameterTrainingJobDefinition' :: Maybe Bool
enableNetworkIsolation = Maybe Bool
a} :: HyperParameterTrainingJobDefinition)

-- | Undocumented member.
hyperParameterTrainingJobDefinition_hyperParameterRanges :: Lens.Lens' HyperParameterTrainingJobDefinition (Prelude.Maybe ParameterRanges)
hyperParameterTrainingJobDefinition_hyperParameterRanges :: Lens' HyperParameterTrainingJobDefinition (Maybe ParameterRanges)
hyperParameterTrainingJobDefinition_hyperParameterRanges = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\HyperParameterTrainingJobDefinition' {Maybe ParameterRanges
hyperParameterRanges :: Maybe ParameterRanges
$sel:hyperParameterRanges:HyperParameterTrainingJobDefinition' :: HyperParameterTrainingJobDefinition -> Maybe ParameterRanges
hyperParameterRanges} -> Maybe ParameterRanges
hyperParameterRanges) (\s :: HyperParameterTrainingJobDefinition
s@HyperParameterTrainingJobDefinition' {} Maybe ParameterRanges
a -> HyperParameterTrainingJobDefinition
s {$sel:hyperParameterRanges:HyperParameterTrainingJobDefinition' :: Maybe ParameterRanges
hyperParameterRanges = Maybe ParameterRanges
a} :: HyperParameterTrainingJobDefinition)

-- | The configuration for the hyperparameter tuning resources, including the
-- compute instances and storage volumes, used for training jobs launched
-- by the tuning job. By default, storage volumes hold model artifacts and
-- incremental states. Choose @File@ for @TrainingInputMode@ in the
-- @AlgorithmSpecification@ parameter to additionally store training data
-- in the storage volume (optional).
hyperParameterTrainingJobDefinition_hyperParameterTuningResourceConfig :: Lens.Lens' HyperParameterTrainingJobDefinition (Prelude.Maybe HyperParameterTuningResourceConfig)
hyperParameterTrainingJobDefinition_hyperParameterTuningResourceConfig :: Lens'
  HyperParameterTrainingJobDefinition
  (Maybe HyperParameterTuningResourceConfig)
hyperParameterTrainingJobDefinition_hyperParameterTuningResourceConfig = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\HyperParameterTrainingJobDefinition' {Maybe HyperParameterTuningResourceConfig
hyperParameterTuningResourceConfig :: Maybe HyperParameterTuningResourceConfig
$sel:hyperParameterTuningResourceConfig:HyperParameterTrainingJobDefinition' :: HyperParameterTrainingJobDefinition
-> Maybe HyperParameterTuningResourceConfig
hyperParameterTuningResourceConfig} -> Maybe HyperParameterTuningResourceConfig
hyperParameterTuningResourceConfig) (\s :: HyperParameterTrainingJobDefinition
s@HyperParameterTrainingJobDefinition' {} Maybe HyperParameterTuningResourceConfig
a -> HyperParameterTrainingJobDefinition
s {$sel:hyperParameterTuningResourceConfig:HyperParameterTrainingJobDefinition' :: Maybe HyperParameterTuningResourceConfig
hyperParameterTuningResourceConfig = Maybe HyperParameterTuningResourceConfig
a} :: HyperParameterTrainingJobDefinition)

-- | An array of Channel objects that specify the input for the training jobs
-- that the tuning job launches.
hyperParameterTrainingJobDefinition_inputDataConfig :: Lens.Lens' HyperParameterTrainingJobDefinition (Prelude.Maybe (Prelude.NonEmpty Channel))
hyperParameterTrainingJobDefinition_inputDataConfig :: Lens'
  HyperParameterTrainingJobDefinition (Maybe (NonEmpty Channel))
hyperParameterTrainingJobDefinition_inputDataConfig = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\HyperParameterTrainingJobDefinition' {Maybe (NonEmpty Channel)
inputDataConfig :: Maybe (NonEmpty Channel)
$sel:inputDataConfig:HyperParameterTrainingJobDefinition' :: HyperParameterTrainingJobDefinition -> Maybe (NonEmpty Channel)
inputDataConfig} -> Maybe (NonEmpty Channel)
inputDataConfig) (\s :: HyperParameterTrainingJobDefinition
s@HyperParameterTrainingJobDefinition' {} Maybe (NonEmpty Channel)
a -> HyperParameterTrainingJobDefinition
s {$sel:inputDataConfig:HyperParameterTrainingJobDefinition' :: Maybe (NonEmpty Channel)
inputDataConfig = Maybe (NonEmpty Channel)
a} :: HyperParameterTrainingJobDefinition) 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 resources, including the compute instances and storage volumes, to
-- use for the training jobs that the tuning job launches.
--
-- Storage volumes store model artifacts and incremental states. Training
-- algorithms might also use storage volumes for scratch space. If you want
-- SageMaker to use the storage volume to store the training data, choose
-- @File@ as the @TrainingInputMode@ in the algorithm specification. For
-- distributed training algorithms, specify an instance count greater than
-- 1.
--
-- If you want to use hyperparameter optimization with instance type
-- flexibility, use @HyperParameterTuningResourceConfig@ instead.
hyperParameterTrainingJobDefinition_resourceConfig :: Lens.Lens' HyperParameterTrainingJobDefinition (Prelude.Maybe ResourceConfig)
hyperParameterTrainingJobDefinition_resourceConfig :: Lens' HyperParameterTrainingJobDefinition (Maybe ResourceConfig)
hyperParameterTrainingJobDefinition_resourceConfig = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\HyperParameterTrainingJobDefinition' {Maybe ResourceConfig
resourceConfig :: Maybe ResourceConfig
$sel:resourceConfig:HyperParameterTrainingJobDefinition' :: HyperParameterTrainingJobDefinition -> Maybe ResourceConfig
resourceConfig} -> Maybe ResourceConfig
resourceConfig) (\s :: HyperParameterTrainingJobDefinition
s@HyperParameterTrainingJobDefinition' {} Maybe ResourceConfig
a -> HyperParameterTrainingJobDefinition
s {$sel:resourceConfig:HyperParameterTrainingJobDefinition' :: Maybe ResourceConfig
resourceConfig = Maybe ResourceConfig
a} :: HyperParameterTrainingJobDefinition)

-- | The number of times to retry the job when the job fails due to an
-- @InternalServerError@.
hyperParameterTrainingJobDefinition_retryStrategy :: Lens.Lens' HyperParameterTrainingJobDefinition (Prelude.Maybe RetryStrategy)
hyperParameterTrainingJobDefinition_retryStrategy :: Lens' HyperParameterTrainingJobDefinition (Maybe RetryStrategy)
hyperParameterTrainingJobDefinition_retryStrategy = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\HyperParameterTrainingJobDefinition' {Maybe RetryStrategy
retryStrategy :: Maybe RetryStrategy
$sel:retryStrategy:HyperParameterTrainingJobDefinition' :: HyperParameterTrainingJobDefinition -> Maybe RetryStrategy
retryStrategy} -> Maybe RetryStrategy
retryStrategy) (\s :: HyperParameterTrainingJobDefinition
s@HyperParameterTrainingJobDefinition' {} Maybe RetryStrategy
a -> HyperParameterTrainingJobDefinition
s {$sel:retryStrategy:HyperParameterTrainingJobDefinition' :: Maybe RetryStrategy
retryStrategy = Maybe RetryStrategy
a} :: HyperParameterTrainingJobDefinition)

-- | Specifies the values of hyperparameters that do not change for the
-- tuning job.
hyperParameterTrainingJobDefinition_staticHyperParameters :: Lens.Lens' HyperParameterTrainingJobDefinition (Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text))
hyperParameterTrainingJobDefinition_staticHyperParameters :: Lens'
  HyperParameterTrainingJobDefinition (Maybe (HashMap Text Text))
hyperParameterTrainingJobDefinition_staticHyperParameters = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\HyperParameterTrainingJobDefinition' {Maybe (HashMap Text Text)
staticHyperParameters :: Maybe (HashMap Text Text)
$sel:staticHyperParameters:HyperParameterTrainingJobDefinition' :: HyperParameterTrainingJobDefinition -> Maybe (HashMap Text Text)
staticHyperParameters} -> Maybe (HashMap Text Text)
staticHyperParameters) (\s :: HyperParameterTrainingJobDefinition
s@HyperParameterTrainingJobDefinition' {} Maybe (HashMap Text Text)
a -> HyperParameterTrainingJobDefinition
s {$sel:staticHyperParameters:HyperParameterTrainingJobDefinition' :: Maybe (HashMap Text Text)
staticHyperParameters = Maybe (HashMap Text Text)
a} :: HyperParameterTrainingJobDefinition) 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.
hyperParameterTrainingJobDefinition_tuningObjective :: Lens.Lens' HyperParameterTrainingJobDefinition (Prelude.Maybe HyperParameterTuningJobObjective)
hyperParameterTrainingJobDefinition_tuningObjective :: Lens'
  HyperParameterTrainingJobDefinition
  (Maybe HyperParameterTuningJobObjective)
hyperParameterTrainingJobDefinition_tuningObjective = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\HyperParameterTrainingJobDefinition' {Maybe HyperParameterTuningJobObjective
tuningObjective :: Maybe HyperParameterTuningJobObjective
$sel:tuningObjective:HyperParameterTrainingJobDefinition' :: HyperParameterTrainingJobDefinition
-> Maybe HyperParameterTuningJobObjective
tuningObjective} -> Maybe HyperParameterTuningJobObjective
tuningObjective) (\s :: HyperParameterTrainingJobDefinition
s@HyperParameterTrainingJobDefinition' {} Maybe HyperParameterTuningJobObjective
a -> HyperParameterTrainingJobDefinition
s {$sel:tuningObjective:HyperParameterTrainingJobDefinition' :: Maybe HyperParameterTuningJobObjective
tuningObjective = Maybe HyperParameterTuningJobObjective
a} :: HyperParameterTrainingJobDefinition)

-- | The VpcConfig object that specifies the VPC that you want the training
-- jobs that this hyperparameter tuning job launches to connect to. Control
-- access to and from your training container by configuring the VPC. 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>.
hyperParameterTrainingJobDefinition_vpcConfig :: Lens.Lens' HyperParameterTrainingJobDefinition (Prelude.Maybe VpcConfig)
hyperParameterTrainingJobDefinition_vpcConfig :: Lens' HyperParameterTrainingJobDefinition (Maybe VpcConfig)
hyperParameterTrainingJobDefinition_vpcConfig = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\HyperParameterTrainingJobDefinition' {Maybe VpcConfig
vpcConfig :: Maybe VpcConfig
$sel:vpcConfig:HyperParameterTrainingJobDefinition' :: HyperParameterTrainingJobDefinition -> Maybe VpcConfig
vpcConfig} -> Maybe VpcConfig
vpcConfig) (\s :: HyperParameterTrainingJobDefinition
s@HyperParameterTrainingJobDefinition' {} Maybe VpcConfig
a -> HyperParameterTrainingJobDefinition
s {$sel:vpcConfig:HyperParameterTrainingJobDefinition' :: Maybe VpcConfig
vpcConfig = Maybe VpcConfig
a} :: HyperParameterTrainingJobDefinition)

-- | The HyperParameterAlgorithmSpecification object that specifies the
-- resource algorithm to use for the training jobs that the tuning job
-- launches.
hyperParameterTrainingJobDefinition_algorithmSpecification :: Lens.Lens' HyperParameterTrainingJobDefinition HyperParameterAlgorithmSpecification
hyperParameterTrainingJobDefinition_algorithmSpecification :: Lens'
  HyperParameterTrainingJobDefinition
  HyperParameterAlgorithmSpecification
hyperParameterTrainingJobDefinition_algorithmSpecification = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\HyperParameterTrainingJobDefinition' {HyperParameterAlgorithmSpecification
algorithmSpecification :: HyperParameterAlgorithmSpecification
$sel:algorithmSpecification:HyperParameterTrainingJobDefinition' :: HyperParameterTrainingJobDefinition
-> HyperParameterAlgorithmSpecification
algorithmSpecification} -> HyperParameterAlgorithmSpecification
algorithmSpecification) (\s :: HyperParameterTrainingJobDefinition
s@HyperParameterTrainingJobDefinition' {} HyperParameterAlgorithmSpecification
a -> HyperParameterTrainingJobDefinition
s {$sel:algorithmSpecification:HyperParameterTrainingJobDefinition' :: HyperParameterAlgorithmSpecification
algorithmSpecification = HyperParameterAlgorithmSpecification
a} :: HyperParameterTrainingJobDefinition)

-- | The Amazon Resource Name (ARN) of the IAM role associated with the
-- training jobs that the tuning job launches.
hyperParameterTrainingJobDefinition_roleArn :: Lens.Lens' HyperParameterTrainingJobDefinition Prelude.Text
hyperParameterTrainingJobDefinition_roleArn :: Lens' HyperParameterTrainingJobDefinition Text
hyperParameterTrainingJobDefinition_roleArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\HyperParameterTrainingJobDefinition' {Text
roleArn :: Text
$sel:roleArn:HyperParameterTrainingJobDefinition' :: HyperParameterTrainingJobDefinition -> Text
roleArn} -> Text
roleArn) (\s :: HyperParameterTrainingJobDefinition
s@HyperParameterTrainingJobDefinition' {} Text
a -> HyperParameterTrainingJobDefinition
s {$sel:roleArn:HyperParameterTrainingJobDefinition' :: Text
roleArn = Text
a} :: HyperParameterTrainingJobDefinition)

-- | Specifies the path to the Amazon S3 bucket where you store model
-- artifacts from the training jobs that the tuning job launches.
hyperParameterTrainingJobDefinition_outputDataConfig :: Lens.Lens' HyperParameterTrainingJobDefinition OutputDataConfig
hyperParameterTrainingJobDefinition_outputDataConfig :: Lens' HyperParameterTrainingJobDefinition OutputDataConfig
hyperParameterTrainingJobDefinition_outputDataConfig = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\HyperParameterTrainingJobDefinition' {OutputDataConfig
outputDataConfig :: OutputDataConfig
$sel:outputDataConfig:HyperParameterTrainingJobDefinition' :: HyperParameterTrainingJobDefinition -> OutputDataConfig
outputDataConfig} -> OutputDataConfig
outputDataConfig) (\s :: HyperParameterTrainingJobDefinition
s@HyperParameterTrainingJobDefinition' {} OutputDataConfig
a -> HyperParameterTrainingJobDefinition
s {$sel:outputDataConfig:HyperParameterTrainingJobDefinition' :: OutputDataConfig
outputDataConfig = OutputDataConfig
a} :: HyperParameterTrainingJobDefinition)

-- | Specifies a limit to how long a model hyperparameter 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.
hyperParameterTrainingJobDefinition_stoppingCondition :: Lens.Lens' HyperParameterTrainingJobDefinition StoppingCondition
hyperParameterTrainingJobDefinition_stoppingCondition :: Lens' HyperParameterTrainingJobDefinition StoppingCondition
hyperParameterTrainingJobDefinition_stoppingCondition = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\HyperParameterTrainingJobDefinition' {StoppingCondition
stoppingCondition :: StoppingCondition
$sel:stoppingCondition:HyperParameterTrainingJobDefinition' :: HyperParameterTrainingJobDefinition -> StoppingCondition
stoppingCondition} -> StoppingCondition
stoppingCondition) (\s :: HyperParameterTrainingJobDefinition
s@HyperParameterTrainingJobDefinition' {} StoppingCondition
a -> HyperParameterTrainingJobDefinition
s {$sel:stoppingCondition:HyperParameterTrainingJobDefinition' :: StoppingCondition
stoppingCondition = StoppingCondition
a} :: HyperParameterTrainingJobDefinition)

instance
  Data.FromJSON
    HyperParameterTrainingJobDefinition
  where
  parseJSON :: Value -> Parser HyperParameterTrainingJobDefinition
parseJSON =
    forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.withObject
      String
"HyperParameterTrainingJobDefinition"
      ( \Object
x ->
          Maybe CheckpointConfig
-> Maybe Text
-> Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Maybe ParameterRanges
-> Maybe HyperParameterTuningResourceConfig
-> Maybe (NonEmpty Channel)
-> Maybe ResourceConfig
-> Maybe RetryStrategy
-> Maybe (HashMap Text Text)
-> Maybe HyperParameterTuningJobObjective
-> Maybe VpcConfig
-> HyperParameterAlgorithmSpecification
-> Text
-> OutputDataConfig
-> StoppingCondition
-> HyperParameterTrainingJobDefinition
HyperParameterTrainingJobDefinition'
            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
"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
"DefinitionName")
            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
"HyperParameterRanges")
            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
"HyperParameterTuningResourceConfig")
            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
"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
"StaticHyperParameters"
                            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
"TuningObjective")
            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")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser a
Data..: Key
"AlgorithmSpecification")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser a
Data..: Key
"RoleArn")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser a
Data..: Key
"OutputDataConfig")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser a
Data..: Key
"StoppingCondition")
      )

instance
  Prelude.Hashable
    HyperParameterTrainingJobDefinition
  where
  hashWithSalt :: Int -> HyperParameterTrainingJobDefinition -> Int
hashWithSalt
    Int
_salt
    HyperParameterTrainingJobDefinition' {Maybe Bool
Maybe (NonEmpty Channel)
Maybe Text
Maybe (HashMap Text Text)
Maybe CheckpointConfig
Maybe HyperParameterTuningJobObjective
Maybe ParameterRanges
Maybe RetryStrategy
Maybe ResourceConfig
Maybe HyperParameterTuningResourceConfig
Maybe VpcConfig
Text
OutputDataConfig
StoppingCondition
HyperParameterAlgorithmSpecification
stoppingCondition :: StoppingCondition
outputDataConfig :: OutputDataConfig
roleArn :: Text
algorithmSpecification :: HyperParameterAlgorithmSpecification
vpcConfig :: Maybe VpcConfig
tuningObjective :: Maybe HyperParameterTuningJobObjective
staticHyperParameters :: Maybe (HashMap Text Text)
retryStrategy :: Maybe RetryStrategy
resourceConfig :: Maybe ResourceConfig
inputDataConfig :: Maybe (NonEmpty Channel)
hyperParameterTuningResourceConfig :: Maybe HyperParameterTuningResourceConfig
hyperParameterRanges :: Maybe ParameterRanges
enableNetworkIsolation :: Maybe Bool
enableManagedSpotTraining :: Maybe Bool
enableInterContainerTrafficEncryption :: Maybe Bool
definitionName :: Maybe Text
checkpointConfig :: Maybe CheckpointConfig
$sel:stoppingCondition:HyperParameterTrainingJobDefinition' :: HyperParameterTrainingJobDefinition -> StoppingCondition
$sel:outputDataConfig:HyperParameterTrainingJobDefinition' :: HyperParameterTrainingJobDefinition -> OutputDataConfig
$sel:roleArn:HyperParameterTrainingJobDefinition' :: HyperParameterTrainingJobDefinition -> Text
$sel:algorithmSpecification:HyperParameterTrainingJobDefinition' :: HyperParameterTrainingJobDefinition
-> HyperParameterAlgorithmSpecification
$sel:vpcConfig:HyperParameterTrainingJobDefinition' :: HyperParameterTrainingJobDefinition -> Maybe VpcConfig
$sel:tuningObjective:HyperParameterTrainingJobDefinition' :: HyperParameterTrainingJobDefinition
-> Maybe HyperParameterTuningJobObjective
$sel:staticHyperParameters:HyperParameterTrainingJobDefinition' :: HyperParameterTrainingJobDefinition -> Maybe (HashMap Text Text)
$sel:retryStrategy:HyperParameterTrainingJobDefinition' :: HyperParameterTrainingJobDefinition -> Maybe RetryStrategy
$sel:resourceConfig:HyperParameterTrainingJobDefinition' :: HyperParameterTrainingJobDefinition -> Maybe ResourceConfig
$sel:inputDataConfig:HyperParameterTrainingJobDefinition' :: HyperParameterTrainingJobDefinition -> Maybe (NonEmpty Channel)
$sel:hyperParameterTuningResourceConfig:HyperParameterTrainingJobDefinition' :: HyperParameterTrainingJobDefinition
-> Maybe HyperParameterTuningResourceConfig
$sel:hyperParameterRanges:HyperParameterTrainingJobDefinition' :: HyperParameterTrainingJobDefinition -> Maybe ParameterRanges
$sel:enableNetworkIsolation:HyperParameterTrainingJobDefinition' :: HyperParameterTrainingJobDefinition -> Maybe Bool
$sel:enableManagedSpotTraining:HyperParameterTrainingJobDefinition' :: HyperParameterTrainingJobDefinition -> Maybe Bool
$sel:enableInterContainerTrafficEncryption:HyperParameterTrainingJobDefinition' :: HyperParameterTrainingJobDefinition -> Maybe Bool
$sel:definitionName:HyperParameterTrainingJobDefinition' :: HyperParameterTrainingJobDefinition -> Maybe Text
$sel:checkpointConfig:HyperParameterTrainingJobDefinition' :: HyperParameterTrainingJobDefinition -> Maybe CheckpointConfig
..} =
      Int
_salt
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe CheckpointConfig
checkpointConfig
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
definitionName
        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 ParameterRanges
hyperParameterRanges
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe HyperParameterTuningResourceConfig
hyperParameterTuningResourceConfig
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe (NonEmpty Channel)
inputDataConfig
        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 (HashMap Text Text)
staticHyperParameters
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe HyperParameterTuningJobObjective
tuningObjective
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe VpcConfig
vpcConfig
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` HyperParameterAlgorithmSpecification
algorithmSpecification
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
roleArn
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` OutputDataConfig
outputDataConfig
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` StoppingCondition
stoppingCondition

instance
  Prelude.NFData
    HyperParameterTrainingJobDefinition
  where
  rnf :: HyperParameterTrainingJobDefinition -> ()
rnf HyperParameterTrainingJobDefinition' {Maybe Bool
Maybe (NonEmpty Channel)
Maybe Text
Maybe (HashMap Text Text)
Maybe CheckpointConfig
Maybe HyperParameterTuningJobObjective
Maybe ParameterRanges
Maybe RetryStrategy
Maybe ResourceConfig
Maybe HyperParameterTuningResourceConfig
Maybe VpcConfig
Text
OutputDataConfig
StoppingCondition
HyperParameterAlgorithmSpecification
stoppingCondition :: StoppingCondition
outputDataConfig :: OutputDataConfig
roleArn :: Text
algorithmSpecification :: HyperParameterAlgorithmSpecification
vpcConfig :: Maybe VpcConfig
tuningObjective :: Maybe HyperParameterTuningJobObjective
staticHyperParameters :: Maybe (HashMap Text Text)
retryStrategy :: Maybe RetryStrategy
resourceConfig :: Maybe ResourceConfig
inputDataConfig :: Maybe (NonEmpty Channel)
hyperParameterTuningResourceConfig :: Maybe HyperParameterTuningResourceConfig
hyperParameterRanges :: Maybe ParameterRanges
enableNetworkIsolation :: Maybe Bool
enableManagedSpotTraining :: Maybe Bool
enableInterContainerTrafficEncryption :: Maybe Bool
definitionName :: Maybe Text
checkpointConfig :: Maybe CheckpointConfig
$sel:stoppingCondition:HyperParameterTrainingJobDefinition' :: HyperParameterTrainingJobDefinition -> StoppingCondition
$sel:outputDataConfig:HyperParameterTrainingJobDefinition' :: HyperParameterTrainingJobDefinition -> OutputDataConfig
$sel:roleArn:HyperParameterTrainingJobDefinition' :: HyperParameterTrainingJobDefinition -> Text
$sel:algorithmSpecification:HyperParameterTrainingJobDefinition' :: HyperParameterTrainingJobDefinition
-> HyperParameterAlgorithmSpecification
$sel:vpcConfig:HyperParameterTrainingJobDefinition' :: HyperParameterTrainingJobDefinition -> Maybe VpcConfig
$sel:tuningObjective:HyperParameterTrainingJobDefinition' :: HyperParameterTrainingJobDefinition
-> Maybe HyperParameterTuningJobObjective
$sel:staticHyperParameters:HyperParameterTrainingJobDefinition' :: HyperParameterTrainingJobDefinition -> Maybe (HashMap Text Text)
$sel:retryStrategy:HyperParameterTrainingJobDefinition' :: HyperParameterTrainingJobDefinition -> Maybe RetryStrategy
$sel:resourceConfig:HyperParameterTrainingJobDefinition' :: HyperParameterTrainingJobDefinition -> Maybe ResourceConfig
$sel:inputDataConfig:HyperParameterTrainingJobDefinition' :: HyperParameterTrainingJobDefinition -> Maybe (NonEmpty Channel)
$sel:hyperParameterTuningResourceConfig:HyperParameterTrainingJobDefinition' :: HyperParameterTrainingJobDefinition
-> Maybe HyperParameterTuningResourceConfig
$sel:hyperParameterRanges:HyperParameterTrainingJobDefinition' :: HyperParameterTrainingJobDefinition -> Maybe ParameterRanges
$sel:enableNetworkIsolation:HyperParameterTrainingJobDefinition' :: HyperParameterTrainingJobDefinition -> Maybe Bool
$sel:enableManagedSpotTraining:HyperParameterTrainingJobDefinition' :: HyperParameterTrainingJobDefinition -> Maybe Bool
$sel:enableInterContainerTrafficEncryption:HyperParameterTrainingJobDefinition' :: HyperParameterTrainingJobDefinition -> Maybe Bool
$sel:definitionName:HyperParameterTrainingJobDefinition' :: HyperParameterTrainingJobDefinition -> Maybe Text
$sel:checkpointConfig:HyperParameterTrainingJobDefinition' :: HyperParameterTrainingJobDefinition -> Maybe CheckpointConfig
..} =
    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 Text
definitionName
      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 ParameterRanges
hyperParameterRanges
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe HyperParameterTuningResourceConfig
hyperParameterTuningResourceConfig
      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 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 (HashMap Text Text)
staticHyperParameters
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe HyperParameterTuningJobObjective
tuningObjective
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe VpcConfig
vpcConfig
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf HyperParameterAlgorithmSpecification
algorithmSpecification
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
roleArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf OutputDataConfig
outputDataConfig
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf StoppingCondition
stoppingCondition

instance
  Data.ToJSON
    HyperParameterTrainingJobDefinition
  where
  toJSON :: HyperParameterTrainingJobDefinition -> Value
toJSON HyperParameterTrainingJobDefinition' {Maybe Bool
Maybe (NonEmpty Channel)
Maybe Text
Maybe (HashMap Text Text)
Maybe CheckpointConfig
Maybe HyperParameterTuningJobObjective
Maybe ParameterRanges
Maybe RetryStrategy
Maybe ResourceConfig
Maybe HyperParameterTuningResourceConfig
Maybe VpcConfig
Text
OutputDataConfig
StoppingCondition
HyperParameterAlgorithmSpecification
stoppingCondition :: StoppingCondition
outputDataConfig :: OutputDataConfig
roleArn :: Text
algorithmSpecification :: HyperParameterAlgorithmSpecification
vpcConfig :: Maybe VpcConfig
tuningObjective :: Maybe HyperParameterTuningJobObjective
staticHyperParameters :: Maybe (HashMap Text Text)
retryStrategy :: Maybe RetryStrategy
resourceConfig :: Maybe ResourceConfig
inputDataConfig :: Maybe (NonEmpty Channel)
hyperParameterTuningResourceConfig :: Maybe HyperParameterTuningResourceConfig
hyperParameterRanges :: Maybe ParameterRanges
enableNetworkIsolation :: Maybe Bool
enableManagedSpotTraining :: Maybe Bool
enableInterContainerTrafficEncryption :: Maybe Bool
definitionName :: Maybe Text
checkpointConfig :: Maybe CheckpointConfig
$sel:stoppingCondition:HyperParameterTrainingJobDefinition' :: HyperParameterTrainingJobDefinition -> StoppingCondition
$sel:outputDataConfig:HyperParameterTrainingJobDefinition' :: HyperParameterTrainingJobDefinition -> OutputDataConfig
$sel:roleArn:HyperParameterTrainingJobDefinition' :: HyperParameterTrainingJobDefinition -> Text
$sel:algorithmSpecification:HyperParameterTrainingJobDefinition' :: HyperParameterTrainingJobDefinition
-> HyperParameterAlgorithmSpecification
$sel:vpcConfig:HyperParameterTrainingJobDefinition' :: HyperParameterTrainingJobDefinition -> Maybe VpcConfig
$sel:tuningObjective:HyperParameterTrainingJobDefinition' :: HyperParameterTrainingJobDefinition
-> Maybe HyperParameterTuningJobObjective
$sel:staticHyperParameters:HyperParameterTrainingJobDefinition' :: HyperParameterTrainingJobDefinition -> Maybe (HashMap Text Text)
$sel:retryStrategy:HyperParameterTrainingJobDefinition' :: HyperParameterTrainingJobDefinition -> Maybe RetryStrategy
$sel:resourceConfig:HyperParameterTrainingJobDefinition' :: HyperParameterTrainingJobDefinition -> Maybe ResourceConfig
$sel:inputDataConfig:HyperParameterTrainingJobDefinition' :: HyperParameterTrainingJobDefinition -> Maybe (NonEmpty Channel)
$sel:hyperParameterTuningResourceConfig:HyperParameterTrainingJobDefinition' :: HyperParameterTrainingJobDefinition
-> Maybe HyperParameterTuningResourceConfig
$sel:hyperParameterRanges:HyperParameterTrainingJobDefinition' :: HyperParameterTrainingJobDefinition -> Maybe ParameterRanges
$sel:enableNetworkIsolation:HyperParameterTrainingJobDefinition' :: HyperParameterTrainingJobDefinition -> Maybe Bool
$sel:enableManagedSpotTraining:HyperParameterTrainingJobDefinition' :: HyperParameterTrainingJobDefinition -> Maybe Bool
$sel:enableInterContainerTrafficEncryption:HyperParameterTrainingJobDefinition' :: HyperParameterTrainingJobDefinition -> Maybe Bool
$sel:definitionName:HyperParameterTrainingJobDefinition' :: HyperParameterTrainingJobDefinition -> Maybe Text
$sel:checkpointConfig:HyperParameterTrainingJobDefinition' :: HyperParameterTrainingJobDefinition -> Maybe CheckpointConfig
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"CheckpointConfig" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=)
              forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe CheckpointConfig
checkpointConfig,
            (Key
"DefinitionName" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=)
              forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Text
definitionName,
            (Key
"EnableInterContainerTrafficEncryption" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=)
              forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Bool
enableInterContainerTrafficEncryption,
            (Key
"EnableManagedSpotTraining" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=)
              forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Bool
enableManagedSpotTraining,
            (Key
"EnableNetworkIsolation" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=)
              forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Bool
enableNetworkIsolation,
            (Key
"HyperParameterRanges" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=)
              forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe ParameterRanges
hyperParameterRanges,
            (Key
"HyperParameterTuningResourceConfig" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=)
              forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe HyperParameterTuningResourceConfig
hyperParameterTuningResourceConfig,
            (Key
"InputDataConfig" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=)
              forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (NonEmpty Channel)
inputDataConfig,
            (Key
"ResourceConfig" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=)
              forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe ResourceConfig
resourceConfig,
            (Key
"RetryStrategy" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe RetryStrategy
retryStrategy,
            (Key
"StaticHyperParameters" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=)
              forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (HashMap Text Text)
staticHyperParameters,
            (Key
"TuningObjective" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=)
              forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe HyperParameterTuningJobObjective
tuningObjective,
            (Key
"VpcConfig" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe VpcConfig
vpcConfig,
            forall a. a -> Maybe a
Prelude.Just
              ( Key
"AlgorithmSpecification"
                  forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= HyperParameterAlgorithmSpecification
algorithmSpecification
              ),
            forall a. a -> Maybe a
Prelude.Just (Key
"RoleArn" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
roleArn),
            forall a. a -> Maybe a
Prelude.Just
              (Key
"OutputDataConfig" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= OutputDataConfig
outputDataConfig),
            forall a. a -> Maybe a
Prelude.Just
              (Key
"StoppingCondition" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= StoppingCondition
stoppingCondition)
          ]
      )