module Stratosphere.SageMaker.ModelCard.TrainingJobDetailsProperty (
module Exports, TrainingJobDetailsProperty(..),
mkTrainingJobDetailsProperty
) where
import qualified Data.Aeson as JSON
import qualified Stratosphere.Prelude as Prelude
import Stratosphere.Property
import {-# SOURCE #-} Stratosphere.SageMaker.ModelCard.TrainingEnvironmentProperty as Exports
import {-# SOURCE #-} Stratosphere.SageMaker.ModelCard.TrainingHyperParameterProperty as Exports
import {-# SOURCE #-} Stratosphere.SageMaker.ModelCard.TrainingMetricProperty as Exports
import Stratosphere.ResourceProperties
import Stratosphere.Value
data TrainingJobDetailsProperty
=
TrainingJobDetailsProperty {TrainingJobDetailsProperty -> ()
haddock_workaround_ :: (),
TrainingJobDetailsProperty
-> Maybe [TrainingHyperParameterProperty]
hyperParameters :: (Prelude.Maybe [TrainingHyperParameterProperty]),
TrainingJobDetailsProperty -> Maybe (Value Text)
trainingArn :: (Prelude.Maybe (Value Prelude.Text)),
TrainingJobDetailsProperty -> Maybe (ValueList Text)
trainingDatasets :: (Prelude.Maybe (ValueList Prelude.Text)),
TrainingJobDetailsProperty -> Maybe TrainingEnvironmentProperty
trainingEnvironment :: (Prelude.Maybe TrainingEnvironmentProperty),
TrainingJobDetailsProperty -> Maybe [TrainingMetricProperty]
trainingMetrics :: (Prelude.Maybe [TrainingMetricProperty]),
TrainingJobDetailsProperty
-> Maybe [TrainingHyperParameterProperty]
userProvidedHyperParameters :: (Prelude.Maybe [TrainingHyperParameterProperty]),
TrainingJobDetailsProperty -> Maybe [TrainingMetricProperty]
userProvidedTrainingMetrics :: (Prelude.Maybe [TrainingMetricProperty])}
deriving stock (TrainingJobDetailsProperty -> TrainingJobDetailsProperty -> Bool
(TrainingJobDetailsProperty -> TrainingJobDetailsProperty -> Bool)
-> (TrainingJobDetailsProperty
-> TrainingJobDetailsProperty -> Bool)
-> Eq TrainingJobDetailsProperty
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: TrainingJobDetailsProperty -> TrainingJobDetailsProperty -> Bool
== :: TrainingJobDetailsProperty -> TrainingJobDetailsProperty -> Bool
$c/= :: TrainingJobDetailsProperty -> TrainingJobDetailsProperty -> Bool
/= :: TrainingJobDetailsProperty -> TrainingJobDetailsProperty -> Bool
Prelude.Eq, Int -> TrainingJobDetailsProperty -> ShowS
[TrainingJobDetailsProperty] -> ShowS
TrainingJobDetailsProperty -> String
(Int -> TrainingJobDetailsProperty -> ShowS)
-> (TrainingJobDetailsProperty -> String)
-> ([TrainingJobDetailsProperty] -> ShowS)
-> Show TrainingJobDetailsProperty
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> TrainingJobDetailsProperty -> ShowS
showsPrec :: Int -> TrainingJobDetailsProperty -> ShowS
$cshow :: TrainingJobDetailsProperty -> String
show :: TrainingJobDetailsProperty -> String
$cshowList :: [TrainingJobDetailsProperty] -> ShowS
showList :: [TrainingJobDetailsProperty] -> ShowS
Prelude.Show)
mkTrainingJobDetailsProperty :: TrainingJobDetailsProperty
mkTrainingJobDetailsProperty :: TrainingJobDetailsProperty
mkTrainingJobDetailsProperty
= TrainingJobDetailsProperty
{haddock_workaround_ :: ()
haddock_workaround_ = (), hyperParameters :: Maybe [TrainingHyperParameterProperty]
hyperParameters = Maybe [TrainingHyperParameterProperty]
forall a. Maybe a
Prelude.Nothing,
trainingArn :: Maybe (Value Text)
trainingArn = Maybe (Value Text)
forall a. Maybe a
Prelude.Nothing, trainingDatasets :: Maybe (ValueList Text)
trainingDatasets = Maybe (ValueList Text)
forall a. Maybe a
Prelude.Nothing,
trainingEnvironment :: Maybe TrainingEnvironmentProperty
trainingEnvironment = Maybe TrainingEnvironmentProperty
forall a. Maybe a
Prelude.Nothing,
trainingMetrics :: Maybe [TrainingMetricProperty]
trainingMetrics = Maybe [TrainingMetricProperty]
forall a. Maybe a
Prelude.Nothing,
userProvidedHyperParameters :: Maybe [TrainingHyperParameterProperty]
userProvidedHyperParameters = Maybe [TrainingHyperParameterProperty]
forall a. Maybe a
Prelude.Nothing,
userProvidedTrainingMetrics :: Maybe [TrainingMetricProperty]
userProvidedTrainingMetrics = Maybe [TrainingMetricProperty]
forall a. Maybe a
Prelude.Nothing}
instance ToResourceProperties TrainingJobDetailsProperty where
toResourceProperties :: TrainingJobDetailsProperty -> ResourceProperties
toResourceProperties TrainingJobDetailsProperty {Maybe [TrainingHyperParameterProperty]
Maybe [TrainingMetricProperty]
Maybe (ValueList Text)
Maybe (Value Text)
Maybe TrainingEnvironmentProperty
()
haddock_workaround_ :: TrainingJobDetailsProperty -> ()
hyperParameters :: TrainingJobDetailsProperty
-> Maybe [TrainingHyperParameterProperty]
trainingArn :: TrainingJobDetailsProperty -> Maybe (Value Text)
trainingDatasets :: TrainingJobDetailsProperty -> Maybe (ValueList Text)
trainingEnvironment :: TrainingJobDetailsProperty -> Maybe TrainingEnvironmentProperty
trainingMetrics :: TrainingJobDetailsProperty -> Maybe [TrainingMetricProperty]
userProvidedHyperParameters :: TrainingJobDetailsProperty
-> Maybe [TrainingHyperParameterProperty]
userProvidedTrainingMetrics :: TrainingJobDetailsProperty -> Maybe [TrainingMetricProperty]
haddock_workaround_ :: ()
hyperParameters :: Maybe [TrainingHyperParameterProperty]
trainingArn :: Maybe (Value Text)
trainingDatasets :: Maybe (ValueList Text)
trainingEnvironment :: Maybe TrainingEnvironmentProperty
trainingMetrics :: Maybe [TrainingMetricProperty]
userProvidedHyperParameters :: Maybe [TrainingHyperParameterProperty]
userProvidedTrainingMetrics :: Maybe [TrainingMetricProperty]
..}
= ResourceProperties
{awsType :: Text
awsType = Text
"AWS::SageMaker::ModelCard.TrainingJobDetails",
supportsTags :: Bool
supportsTags = Bool
Prelude.False,
properties :: Object
properties = [Item Object] -> Object
forall l. IsList l => [Item l] -> l
Prelude.fromList
([Maybe (Key, Value)] -> [(Key, Value)]
forall a. [Maybe a] -> [a]
Prelude.catMaybes
[Key -> [TrainingHyperParameterProperty] -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"HyperParameters" ([TrainingHyperParameterProperty] -> (Key, Value))
-> Maybe [TrainingHyperParameterProperty] -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [TrainingHyperParameterProperty]
hyperParameters,
Key -> Value Text -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"TrainingArn" (Value Text -> (Key, Value))
-> Maybe (Value Text) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Text)
trainingArn,
Key -> ValueList Text -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"TrainingDatasets" (ValueList Text -> (Key, Value))
-> Maybe (ValueList Text) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (ValueList Text)
trainingDatasets,
Key -> TrainingEnvironmentProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"TrainingEnvironment" (TrainingEnvironmentProperty -> (Key, Value))
-> Maybe TrainingEnvironmentProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe TrainingEnvironmentProperty
trainingEnvironment,
Key -> [TrainingMetricProperty] -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"TrainingMetrics" ([TrainingMetricProperty] -> (Key, Value))
-> Maybe [TrainingMetricProperty] -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [TrainingMetricProperty]
trainingMetrics,
Key -> [TrainingHyperParameterProperty] -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"UserProvidedHyperParameters"
([TrainingHyperParameterProperty] -> (Key, Value))
-> Maybe [TrainingHyperParameterProperty] -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [TrainingHyperParameterProperty]
userProvidedHyperParameters,
Key -> [TrainingMetricProperty] -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"UserProvidedTrainingMetrics"
([TrainingMetricProperty] -> (Key, Value))
-> Maybe [TrainingMetricProperty] -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [TrainingMetricProperty]
userProvidedTrainingMetrics])}
instance JSON.ToJSON TrainingJobDetailsProperty where
toJSON :: TrainingJobDetailsProperty -> Value
toJSON TrainingJobDetailsProperty {Maybe [TrainingHyperParameterProperty]
Maybe [TrainingMetricProperty]
Maybe (ValueList Text)
Maybe (Value Text)
Maybe TrainingEnvironmentProperty
()
haddock_workaround_ :: TrainingJobDetailsProperty -> ()
hyperParameters :: TrainingJobDetailsProperty
-> Maybe [TrainingHyperParameterProperty]
trainingArn :: TrainingJobDetailsProperty -> Maybe (Value Text)
trainingDatasets :: TrainingJobDetailsProperty -> Maybe (ValueList Text)
trainingEnvironment :: TrainingJobDetailsProperty -> Maybe TrainingEnvironmentProperty
trainingMetrics :: TrainingJobDetailsProperty -> Maybe [TrainingMetricProperty]
userProvidedHyperParameters :: TrainingJobDetailsProperty
-> Maybe [TrainingHyperParameterProperty]
userProvidedTrainingMetrics :: TrainingJobDetailsProperty -> Maybe [TrainingMetricProperty]
haddock_workaround_ :: ()
hyperParameters :: Maybe [TrainingHyperParameterProperty]
trainingArn :: Maybe (Value Text)
trainingDatasets :: Maybe (ValueList Text)
trainingEnvironment :: Maybe TrainingEnvironmentProperty
trainingMetrics :: Maybe [TrainingMetricProperty]
userProvidedHyperParameters :: Maybe [TrainingHyperParameterProperty]
userProvidedTrainingMetrics :: Maybe [TrainingMetricProperty]
..}
= [(Key, Value)] -> Value
JSON.object
([Item [(Key, Value)]] -> [(Key, Value)]
forall l. IsList l => [Item l] -> l
Prelude.fromList
([Maybe (Key, Value)] -> [(Key, Value)]
forall a. [Maybe a] -> [a]
Prelude.catMaybes
[Key -> [TrainingHyperParameterProperty] -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"HyperParameters" ([TrainingHyperParameterProperty] -> (Key, Value))
-> Maybe [TrainingHyperParameterProperty] -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [TrainingHyperParameterProperty]
hyperParameters,
Key -> Value Text -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"TrainingArn" (Value Text -> (Key, Value))
-> Maybe (Value Text) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Text)
trainingArn,
Key -> ValueList Text -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"TrainingDatasets" (ValueList Text -> (Key, Value))
-> Maybe (ValueList Text) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (ValueList Text)
trainingDatasets,
Key -> TrainingEnvironmentProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"TrainingEnvironment" (TrainingEnvironmentProperty -> (Key, Value))
-> Maybe TrainingEnvironmentProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe TrainingEnvironmentProperty
trainingEnvironment,
Key -> [TrainingMetricProperty] -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"TrainingMetrics" ([TrainingMetricProperty] -> (Key, Value))
-> Maybe [TrainingMetricProperty] -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [TrainingMetricProperty]
trainingMetrics,
Key -> [TrainingHyperParameterProperty] -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"UserProvidedHyperParameters"
([TrainingHyperParameterProperty] -> (Key, Value))
-> Maybe [TrainingHyperParameterProperty] -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [TrainingHyperParameterProperty]
userProvidedHyperParameters,
Key -> [TrainingMetricProperty] -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"UserProvidedTrainingMetrics"
([TrainingMetricProperty] -> (Key, Value))
-> Maybe [TrainingMetricProperty] -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [TrainingMetricProperty]
userProvidedTrainingMetrics]))
instance Property "HyperParameters" TrainingJobDetailsProperty where
type PropertyType "HyperParameters" TrainingJobDetailsProperty = [TrainingHyperParameterProperty]
set :: PropertyType "HyperParameters" TrainingJobDetailsProperty
-> TrainingJobDetailsProperty -> TrainingJobDetailsProperty
set PropertyType "HyperParameters" TrainingJobDetailsProperty
newValue TrainingJobDetailsProperty {Maybe [TrainingHyperParameterProperty]
Maybe [TrainingMetricProperty]
Maybe (ValueList Text)
Maybe (Value Text)
Maybe TrainingEnvironmentProperty
()
haddock_workaround_ :: TrainingJobDetailsProperty -> ()
hyperParameters :: TrainingJobDetailsProperty
-> Maybe [TrainingHyperParameterProperty]
trainingArn :: TrainingJobDetailsProperty -> Maybe (Value Text)
trainingDatasets :: TrainingJobDetailsProperty -> Maybe (ValueList Text)
trainingEnvironment :: TrainingJobDetailsProperty -> Maybe TrainingEnvironmentProperty
trainingMetrics :: TrainingJobDetailsProperty -> Maybe [TrainingMetricProperty]
userProvidedHyperParameters :: TrainingJobDetailsProperty
-> Maybe [TrainingHyperParameterProperty]
userProvidedTrainingMetrics :: TrainingJobDetailsProperty -> Maybe [TrainingMetricProperty]
haddock_workaround_ :: ()
hyperParameters :: Maybe [TrainingHyperParameterProperty]
trainingArn :: Maybe (Value Text)
trainingDatasets :: Maybe (ValueList Text)
trainingEnvironment :: Maybe TrainingEnvironmentProperty
trainingMetrics :: Maybe [TrainingMetricProperty]
userProvidedHyperParameters :: Maybe [TrainingHyperParameterProperty]
userProvidedTrainingMetrics :: Maybe [TrainingMetricProperty]
..}
= TrainingJobDetailsProperty
{hyperParameters :: Maybe [TrainingHyperParameterProperty]
hyperParameters = [TrainingHyperParameterProperty]
-> Maybe [TrainingHyperParameterProperty]
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure [TrainingHyperParameterProperty]
PropertyType "HyperParameters" TrainingJobDetailsProperty
newValue, Maybe [TrainingHyperParameterProperty]
Maybe [TrainingMetricProperty]
Maybe (ValueList Text)
Maybe (Value Text)
Maybe TrainingEnvironmentProperty
()
haddock_workaround_ :: ()
trainingArn :: Maybe (Value Text)
trainingDatasets :: Maybe (ValueList Text)
trainingEnvironment :: Maybe TrainingEnvironmentProperty
trainingMetrics :: Maybe [TrainingMetricProperty]
userProvidedHyperParameters :: Maybe [TrainingHyperParameterProperty]
userProvidedTrainingMetrics :: Maybe [TrainingMetricProperty]
haddock_workaround_ :: ()
trainingArn :: Maybe (Value Text)
trainingDatasets :: Maybe (ValueList Text)
trainingEnvironment :: Maybe TrainingEnvironmentProperty
trainingMetrics :: Maybe [TrainingMetricProperty]
userProvidedHyperParameters :: Maybe [TrainingHyperParameterProperty]
userProvidedTrainingMetrics :: Maybe [TrainingMetricProperty]
..}
instance Property "TrainingArn" TrainingJobDetailsProperty where
type PropertyType "TrainingArn" TrainingJobDetailsProperty = Value Prelude.Text
set :: PropertyType "TrainingArn" TrainingJobDetailsProperty
-> TrainingJobDetailsProperty -> TrainingJobDetailsProperty
set PropertyType "TrainingArn" TrainingJobDetailsProperty
newValue TrainingJobDetailsProperty {Maybe [TrainingHyperParameterProperty]
Maybe [TrainingMetricProperty]
Maybe (ValueList Text)
Maybe (Value Text)
Maybe TrainingEnvironmentProperty
()
haddock_workaround_ :: TrainingJobDetailsProperty -> ()
hyperParameters :: TrainingJobDetailsProperty
-> Maybe [TrainingHyperParameterProperty]
trainingArn :: TrainingJobDetailsProperty -> Maybe (Value Text)
trainingDatasets :: TrainingJobDetailsProperty -> Maybe (ValueList Text)
trainingEnvironment :: TrainingJobDetailsProperty -> Maybe TrainingEnvironmentProperty
trainingMetrics :: TrainingJobDetailsProperty -> Maybe [TrainingMetricProperty]
userProvidedHyperParameters :: TrainingJobDetailsProperty
-> Maybe [TrainingHyperParameterProperty]
userProvidedTrainingMetrics :: TrainingJobDetailsProperty -> Maybe [TrainingMetricProperty]
haddock_workaround_ :: ()
hyperParameters :: Maybe [TrainingHyperParameterProperty]
trainingArn :: Maybe (Value Text)
trainingDatasets :: Maybe (ValueList Text)
trainingEnvironment :: Maybe TrainingEnvironmentProperty
trainingMetrics :: Maybe [TrainingMetricProperty]
userProvidedHyperParameters :: Maybe [TrainingHyperParameterProperty]
userProvidedTrainingMetrics :: Maybe [TrainingMetricProperty]
..}
= TrainingJobDetailsProperty
{trainingArn :: Maybe (Value Text)
trainingArn = Value Text -> Maybe (Value Text)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "TrainingArn" TrainingJobDetailsProperty
Value Text
newValue, Maybe [TrainingHyperParameterProperty]
Maybe [TrainingMetricProperty]
Maybe (ValueList Text)
Maybe TrainingEnvironmentProperty
()
haddock_workaround_ :: ()
hyperParameters :: Maybe [TrainingHyperParameterProperty]
trainingDatasets :: Maybe (ValueList Text)
trainingEnvironment :: Maybe TrainingEnvironmentProperty
trainingMetrics :: Maybe [TrainingMetricProperty]
userProvidedHyperParameters :: Maybe [TrainingHyperParameterProperty]
userProvidedTrainingMetrics :: Maybe [TrainingMetricProperty]
haddock_workaround_ :: ()
hyperParameters :: Maybe [TrainingHyperParameterProperty]
trainingDatasets :: Maybe (ValueList Text)
trainingEnvironment :: Maybe TrainingEnvironmentProperty
trainingMetrics :: Maybe [TrainingMetricProperty]
userProvidedHyperParameters :: Maybe [TrainingHyperParameterProperty]
userProvidedTrainingMetrics :: Maybe [TrainingMetricProperty]
..}
instance Property "TrainingDatasets" TrainingJobDetailsProperty where
type PropertyType "TrainingDatasets" TrainingJobDetailsProperty = ValueList Prelude.Text
set :: PropertyType "TrainingDatasets" TrainingJobDetailsProperty
-> TrainingJobDetailsProperty -> TrainingJobDetailsProperty
set PropertyType "TrainingDatasets" TrainingJobDetailsProperty
newValue TrainingJobDetailsProperty {Maybe [TrainingHyperParameterProperty]
Maybe [TrainingMetricProperty]
Maybe (ValueList Text)
Maybe (Value Text)
Maybe TrainingEnvironmentProperty
()
haddock_workaround_ :: TrainingJobDetailsProperty -> ()
hyperParameters :: TrainingJobDetailsProperty
-> Maybe [TrainingHyperParameterProperty]
trainingArn :: TrainingJobDetailsProperty -> Maybe (Value Text)
trainingDatasets :: TrainingJobDetailsProperty -> Maybe (ValueList Text)
trainingEnvironment :: TrainingJobDetailsProperty -> Maybe TrainingEnvironmentProperty
trainingMetrics :: TrainingJobDetailsProperty -> Maybe [TrainingMetricProperty]
userProvidedHyperParameters :: TrainingJobDetailsProperty
-> Maybe [TrainingHyperParameterProperty]
userProvidedTrainingMetrics :: TrainingJobDetailsProperty -> Maybe [TrainingMetricProperty]
haddock_workaround_ :: ()
hyperParameters :: Maybe [TrainingHyperParameterProperty]
trainingArn :: Maybe (Value Text)
trainingDatasets :: Maybe (ValueList Text)
trainingEnvironment :: Maybe TrainingEnvironmentProperty
trainingMetrics :: Maybe [TrainingMetricProperty]
userProvidedHyperParameters :: Maybe [TrainingHyperParameterProperty]
userProvidedTrainingMetrics :: Maybe [TrainingMetricProperty]
..}
= TrainingJobDetailsProperty
{trainingDatasets :: Maybe (ValueList Text)
trainingDatasets = ValueList Text -> Maybe (ValueList Text)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "TrainingDatasets" TrainingJobDetailsProperty
ValueList Text
newValue, Maybe [TrainingHyperParameterProperty]
Maybe [TrainingMetricProperty]
Maybe (Value Text)
Maybe TrainingEnvironmentProperty
()
haddock_workaround_ :: ()
hyperParameters :: Maybe [TrainingHyperParameterProperty]
trainingArn :: Maybe (Value Text)
trainingEnvironment :: Maybe TrainingEnvironmentProperty
trainingMetrics :: Maybe [TrainingMetricProperty]
userProvidedHyperParameters :: Maybe [TrainingHyperParameterProperty]
userProvidedTrainingMetrics :: Maybe [TrainingMetricProperty]
haddock_workaround_ :: ()
hyperParameters :: Maybe [TrainingHyperParameterProperty]
trainingArn :: Maybe (Value Text)
trainingEnvironment :: Maybe TrainingEnvironmentProperty
trainingMetrics :: Maybe [TrainingMetricProperty]
userProvidedHyperParameters :: Maybe [TrainingHyperParameterProperty]
userProvidedTrainingMetrics :: Maybe [TrainingMetricProperty]
..}
instance Property "TrainingEnvironment" TrainingJobDetailsProperty where
type PropertyType "TrainingEnvironment" TrainingJobDetailsProperty = TrainingEnvironmentProperty
set :: PropertyType "TrainingEnvironment" TrainingJobDetailsProperty
-> TrainingJobDetailsProperty -> TrainingJobDetailsProperty
set PropertyType "TrainingEnvironment" TrainingJobDetailsProperty
newValue TrainingJobDetailsProperty {Maybe [TrainingHyperParameterProperty]
Maybe [TrainingMetricProperty]
Maybe (ValueList Text)
Maybe (Value Text)
Maybe TrainingEnvironmentProperty
()
haddock_workaround_ :: TrainingJobDetailsProperty -> ()
hyperParameters :: TrainingJobDetailsProperty
-> Maybe [TrainingHyperParameterProperty]
trainingArn :: TrainingJobDetailsProperty -> Maybe (Value Text)
trainingDatasets :: TrainingJobDetailsProperty -> Maybe (ValueList Text)
trainingEnvironment :: TrainingJobDetailsProperty -> Maybe TrainingEnvironmentProperty
trainingMetrics :: TrainingJobDetailsProperty -> Maybe [TrainingMetricProperty]
userProvidedHyperParameters :: TrainingJobDetailsProperty
-> Maybe [TrainingHyperParameterProperty]
userProvidedTrainingMetrics :: TrainingJobDetailsProperty -> Maybe [TrainingMetricProperty]
haddock_workaround_ :: ()
hyperParameters :: Maybe [TrainingHyperParameterProperty]
trainingArn :: Maybe (Value Text)
trainingDatasets :: Maybe (ValueList Text)
trainingEnvironment :: Maybe TrainingEnvironmentProperty
trainingMetrics :: Maybe [TrainingMetricProperty]
userProvidedHyperParameters :: Maybe [TrainingHyperParameterProperty]
userProvidedTrainingMetrics :: Maybe [TrainingMetricProperty]
..}
= TrainingJobDetailsProperty
{trainingEnvironment :: Maybe TrainingEnvironmentProperty
trainingEnvironment = TrainingEnvironmentProperty -> Maybe TrainingEnvironmentProperty
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "TrainingEnvironment" TrainingJobDetailsProperty
TrainingEnvironmentProperty
newValue, Maybe [TrainingHyperParameterProperty]
Maybe [TrainingMetricProperty]
Maybe (ValueList Text)
Maybe (Value Text)
()
haddock_workaround_ :: ()
hyperParameters :: Maybe [TrainingHyperParameterProperty]
trainingArn :: Maybe (Value Text)
trainingDatasets :: Maybe (ValueList Text)
trainingMetrics :: Maybe [TrainingMetricProperty]
userProvidedHyperParameters :: Maybe [TrainingHyperParameterProperty]
userProvidedTrainingMetrics :: Maybe [TrainingMetricProperty]
haddock_workaround_ :: ()
hyperParameters :: Maybe [TrainingHyperParameterProperty]
trainingArn :: Maybe (Value Text)
trainingDatasets :: Maybe (ValueList Text)
trainingMetrics :: Maybe [TrainingMetricProperty]
userProvidedHyperParameters :: Maybe [TrainingHyperParameterProperty]
userProvidedTrainingMetrics :: Maybe [TrainingMetricProperty]
..}
instance Property "TrainingMetrics" TrainingJobDetailsProperty where
type PropertyType "TrainingMetrics" TrainingJobDetailsProperty = [TrainingMetricProperty]
set :: PropertyType "TrainingMetrics" TrainingJobDetailsProperty
-> TrainingJobDetailsProperty -> TrainingJobDetailsProperty
set PropertyType "TrainingMetrics" TrainingJobDetailsProperty
newValue TrainingJobDetailsProperty {Maybe [TrainingHyperParameterProperty]
Maybe [TrainingMetricProperty]
Maybe (ValueList Text)
Maybe (Value Text)
Maybe TrainingEnvironmentProperty
()
haddock_workaround_ :: TrainingJobDetailsProperty -> ()
hyperParameters :: TrainingJobDetailsProperty
-> Maybe [TrainingHyperParameterProperty]
trainingArn :: TrainingJobDetailsProperty -> Maybe (Value Text)
trainingDatasets :: TrainingJobDetailsProperty -> Maybe (ValueList Text)
trainingEnvironment :: TrainingJobDetailsProperty -> Maybe TrainingEnvironmentProperty
trainingMetrics :: TrainingJobDetailsProperty -> Maybe [TrainingMetricProperty]
userProvidedHyperParameters :: TrainingJobDetailsProperty
-> Maybe [TrainingHyperParameterProperty]
userProvidedTrainingMetrics :: TrainingJobDetailsProperty -> Maybe [TrainingMetricProperty]
haddock_workaround_ :: ()
hyperParameters :: Maybe [TrainingHyperParameterProperty]
trainingArn :: Maybe (Value Text)
trainingDatasets :: Maybe (ValueList Text)
trainingEnvironment :: Maybe TrainingEnvironmentProperty
trainingMetrics :: Maybe [TrainingMetricProperty]
userProvidedHyperParameters :: Maybe [TrainingHyperParameterProperty]
userProvidedTrainingMetrics :: Maybe [TrainingMetricProperty]
..}
= TrainingJobDetailsProperty
{trainingMetrics :: Maybe [TrainingMetricProperty]
trainingMetrics = [TrainingMetricProperty] -> Maybe [TrainingMetricProperty]
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure [TrainingMetricProperty]
PropertyType "TrainingMetrics" TrainingJobDetailsProperty
newValue, Maybe [TrainingHyperParameterProperty]
Maybe [TrainingMetricProperty]
Maybe (ValueList Text)
Maybe (Value Text)
Maybe TrainingEnvironmentProperty
()
haddock_workaround_ :: ()
hyperParameters :: Maybe [TrainingHyperParameterProperty]
trainingArn :: Maybe (Value Text)
trainingDatasets :: Maybe (ValueList Text)
trainingEnvironment :: Maybe TrainingEnvironmentProperty
userProvidedHyperParameters :: Maybe [TrainingHyperParameterProperty]
userProvidedTrainingMetrics :: Maybe [TrainingMetricProperty]
haddock_workaround_ :: ()
hyperParameters :: Maybe [TrainingHyperParameterProperty]
trainingArn :: Maybe (Value Text)
trainingDatasets :: Maybe (ValueList Text)
trainingEnvironment :: Maybe TrainingEnvironmentProperty
userProvidedHyperParameters :: Maybe [TrainingHyperParameterProperty]
userProvidedTrainingMetrics :: Maybe [TrainingMetricProperty]
..}
instance Property "UserProvidedHyperParameters" TrainingJobDetailsProperty where
type PropertyType "UserProvidedHyperParameters" TrainingJobDetailsProperty = [TrainingHyperParameterProperty]
set :: PropertyType
"UserProvidedHyperParameters" TrainingJobDetailsProperty
-> TrainingJobDetailsProperty -> TrainingJobDetailsProperty
set PropertyType
"UserProvidedHyperParameters" TrainingJobDetailsProperty
newValue TrainingJobDetailsProperty {Maybe [TrainingHyperParameterProperty]
Maybe [TrainingMetricProperty]
Maybe (ValueList Text)
Maybe (Value Text)
Maybe TrainingEnvironmentProperty
()
haddock_workaround_ :: TrainingJobDetailsProperty -> ()
hyperParameters :: TrainingJobDetailsProperty
-> Maybe [TrainingHyperParameterProperty]
trainingArn :: TrainingJobDetailsProperty -> Maybe (Value Text)
trainingDatasets :: TrainingJobDetailsProperty -> Maybe (ValueList Text)
trainingEnvironment :: TrainingJobDetailsProperty -> Maybe TrainingEnvironmentProperty
trainingMetrics :: TrainingJobDetailsProperty -> Maybe [TrainingMetricProperty]
userProvidedHyperParameters :: TrainingJobDetailsProperty
-> Maybe [TrainingHyperParameterProperty]
userProvidedTrainingMetrics :: TrainingJobDetailsProperty -> Maybe [TrainingMetricProperty]
haddock_workaround_ :: ()
hyperParameters :: Maybe [TrainingHyperParameterProperty]
trainingArn :: Maybe (Value Text)
trainingDatasets :: Maybe (ValueList Text)
trainingEnvironment :: Maybe TrainingEnvironmentProperty
trainingMetrics :: Maybe [TrainingMetricProperty]
userProvidedHyperParameters :: Maybe [TrainingHyperParameterProperty]
userProvidedTrainingMetrics :: Maybe [TrainingMetricProperty]
..}
= TrainingJobDetailsProperty
{userProvidedHyperParameters :: Maybe [TrainingHyperParameterProperty]
userProvidedHyperParameters = [TrainingHyperParameterProperty]
-> Maybe [TrainingHyperParameterProperty]
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure [TrainingHyperParameterProperty]
PropertyType
"UserProvidedHyperParameters" TrainingJobDetailsProperty
newValue, Maybe [TrainingHyperParameterProperty]
Maybe [TrainingMetricProperty]
Maybe (ValueList Text)
Maybe (Value Text)
Maybe TrainingEnvironmentProperty
()
haddock_workaround_ :: ()
hyperParameters :: Maybe [TrainingHyperParameterProperty]
trainingArn :: Maybe (Value Text)
trainingDatasets :: Maybe (ValueList Text)
trainingEnvironment :: Maybe TrainingEnvironmentProperty
trainingMetrics :: Maybe [TrainingMetricProperty]
userProvidedTrainingMetrics :: Maybe [TrainingMetricProperty]
haddock_workaround_ :: ()
hyperParameters :: Maybe [TrainingHyperParameterProperty]
trainingArn :: Maybe (Value Text)
trainingDatasets :: Maybe (ValueList Text)
trainingEnvironment :: Maybe TrainingEnvironmentProperty
trainingMetrics :: Maybe [TrainingMetricProperty]
userProvidedTrainingMetrics :: Maybe [TrainingMetricProperty]
..}
instance Property "UserProvidedTrainingMetrics" TrainingJobDetailsProperty where
type PropertyType "UserProvidedTrainingMetrics" TrainingJobDetailsProperty = [TrainingMetricProperty]
set :: PropertyType
"UserProvidedTrainingMetrics" TrainingJobDetailsProperty
-> TrainingJobDetailsProperty -> TrainingJobDetailsProperty
set PropertyType
"UserProvidedTrainingMetrics" TrainingJobDetailsProperty
newValue TrainingJobDetailsProperty {Maybe [TrainingHyperParameterProperty]
Maybe [TrainingMetricProperty]
Maybe (ValueList Text)
Maybe (Value Text)
Maybe TrainingEnvironmentProperty
()
haddock_workaround_ :: TrainingJobDetailsProperty -> ()
hyperParameters :: TrainingJobDetailsProperty
-> Maybe [TrainingHyperParameterProperty]
trainingArn :: TrainingJobDetailsProperty -> Maybe (Value Text)
trainingDatasets :: TrainingJobDetailsProperty -> Maybe (ValueList Text)
trainingEnvironment :: TrainingJobDetailsProperty -> Maybe TrainingEnvironmentProperty
trainingMetrics :: TrainingJobDetailsProperty -> Maybe [TrainingMetricProperty]
userProvidedHyperParameters :: TrainingJobDetailsProperty
-> Maybe [TrainingHyperParameterProperty]
userProvidedTrainingMetrics :: TrainingJobDetailsProperty -> Maybe [TrainingMetricProperty]
haddock_workaround_ :: ()
hyperParameters :: Maybe [TrainingHyperParameterProperty]
trainingArn :: Maybe (Value Text)
trainingDatasets :: Maybe (ValueList Text)
trainingEnvironment :: Maybe TrainingEnvironmentProperty
trainingMetrics :: Maybe [TrainingMetricProperty]
userProvidedHyperParameters :: Maybe [TrainingHyperParameterProperty]
userProvidedTrainingMetrics :: Maybe [TrainingMetricProperty]
..}
= TrainingJobDetailsProperty
{userProvidedTrainingMetrics :: Maybe [TrainingMetricProperty]
userProvidedTrainingMetrics = [TrainingMetricProperty] -> Maybe [TrainingMetricProperty]
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure [TrainingMetricProperty]
PropertyType
"UserProvidedTrainingMetrics" TrainingJobDetailsProperty
newValue, Maybe [TrainingHyperParameterProperty]
Maybe [TrainingMetricProperty]
Maybe (ValueList Text)
Maybe (Value Text)
Maybe TrainingEnvironmentProperty
()
haddock_workaround_ :: ()
hyperParameters :: Maybe [TrainingHyperParameterProperty]
trainingArn :: Maybe (Value Text)
trainingDatasets :: Maybe (ValueList Text)
trainingEnvironment :: Maybe TrainingEnvironmentProperty
trainingMetrics :: Maybe [TrainingMetricProperty]
userProvidedHyperParameters :: Maybe [TrainingHyperParameterProperty]
haddock_workaround_ :: ()
hyperParameters :: Maybe [TrainingHyperParameterProperty]
trainingArn :: Maybe (Value Text)
trainingDatasets :: Maybe (ValueList Text)
trainingEnvironment :: Maybe TrainingEnvironmentProperty
trainingMetrics :: Maybe [TrainingMetricProperty]
userProvidedHyperParameters :: Maybe [TrainingHyperParameterProperty]
..}