module Stratosphere.SageMaker.ModelPackage.SourceAlgorithmSpecificationProperty (
module Exports, SourceAlgorithmSpecificationProperty(..),
mkSourceAlgorithmSpecificationProperty
) where
import qualified Data.Aeson as JSON
import qualified Stratosphere.Prelude as Prelude
import Stratosphere.Property
import {-# SOURCE #-} Stratosphere.SageMaker.ModelPackage.SourceAlgorithmProperty as Exports
import Stratosphere.ResourceProperties
data SourceAlgorithmSpecificationProperty
=
SourceAlgorithmSpecificationProperty {SourceAlgorithmSpecificationProperty -> ()
haddock_workaround_ :: (),
SourceAlgorithmSpecificationProperty -> [SourceAlgorithmProperty]
sourceAlgorithms :: [SourceAlgorithmProperty]}
deriving stock (SourceAlgorithmSpecificationProperty
-> SourceAlgorithmSpecificationProperty -> Bool
(SourceAlgorithmSpecificationProperty
-> SourceAlgorithmSpecificationProperty -> Bool)
-> (SourceAlgorithmSpecificationProperty
-> SourceAlgorithmSpecificationProperty -> Bool)
-> Eq SourceAlgorithmSpecificationProperty
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: SourceAlgorithmSpecificationProperty
-> SourceAlgorithmSpecificationProperty -> Bool
== :: SourceAlgorithmSpecificationProperty
-> SourceAlgorithmSpecificationProperty -> Bool
$c/= :: SourceAlgorithmSpecificationProperty
-> SourceAlgorithmSpecificationProperty -> Bool
/= :: SourceAlgorithmSpecificationProperty
-> SourceAlgorithmSpecificationProperty -> Bool
Prelude.Eq, Int -> SourceAlgorithmSpecificationProperty -> ShowS
[SourceAlgorithmSpecificationProperty] -> ShowS
SourceAlgorithmSpecificationProperty -> String
(Int -> SourceAlgorithmSpecificationProperty -> ShowS)
-> (SourceAlgorithmSpecificationProperty -> String)
-> ([SourceAlgorithmSpecificationProperty] -> ShowS)
-> Show SourceAlgorithmSpecificationProperty
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> SourceAlgorithmSpecificationProperty -> ShowS
showsPrec :: Int -> SourceAlgorithmSpecificationProperty -> ShowS
$cshow :: SourceAlgorithmSpecificationProperty -> String
show :: SourceAlgorithmSpecificationProperty -> String
$cshowList :: [SourceAlgorithmSpecificationProperty] -> ShowS
showList :: [SourceAlgorithmSpecificationProperty] -> ShowS
Prelude.Show)
mkSourceAlgorithmSpecificationProperty ::
[SourceAlgorithmProperty] -> SourceAlgorithmSpecificationProperty
mkSourceAlgorithmSpecificationProperty :: [SourceAlgorithmProperty] -> SourceAlgorithmSpecificationProperty
mkSourceAlgorithmSpecificationProperty [SourceAlgorithmProperty]
sourceAlgorithms
= SourceAlgorithmSpecificationProperty
{haddock_workaround_ :: ()
haddock_workaround_ = (), sourceAlgorithms :: [SourceAlgorithmProperty]
sourceAlgorithms = [SourceAlgorithmProperty]
sourceAlgorithms}
instance ToResourceProperties SourceAlgorithmSpecificationProperty where
toResourceProperties :: SourceAlgorithmSpecificationProperty -> ResourceProperties
toResourceProperties SourceAlgorithmSpecificationProperty {[SourceAlgorithmProperty]
()
haddock_workaround_ :: SourceAlgorithmSpecificationProperty -> ()
sourceAlgorithms :: SourceAlgorithmSpecificationProperty -> [SourceAlgorithmProperty]
haddock_workaround_ :: ()
sourceAlgorithms :: [SourceAlgorithmProperty]
..}
= ResourceProperties
{awsType :: Text
awsType = Text
"AWS::SageMaker::ModelPackage.SourceAlgorithmSpecification",
supportsTags :: Bool
supportsTags = Bool
Prelude.False,
properties :: Object
properties = [Key
"SourceAlgorithms" Key -> [SourceAlgorithmProperty] -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
JSON..= [SourceAlgorithmProperty]
sourceAlgorithms]}
instance JSON.ToJSON SourceAlgorithmSpecificationProperty where
toJSON :: SourceAlgorithmSpecificationProperty -> Value
toJSON SourceAlgorithmSpecificationProperty {[SourceAlgorithmProperty]
()
haddock_workaround_ :: SourceAlgorithmSpecificationProperty -> ()
sourceAlgorithms :: SourceAlgorithmSpecificationProperty -> [SourceAlgorithmProperty]
haddock_workaround_ :: ()
sourceAlgorithms :: [SourceAlgorithmProperty]
..}
= [(Key, Value)] -> Value
JSON.object [Key
"SourceAlgorithms" Key -> [SourceAlgorithmProperty] -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
JSON..= [SourceAlgorithmProperty]
sourceAlgorithms]
instance Property "SourceAlgorithms" SourceAlgorithmSpecificationProperty where
type PropertyType "SourceAlgorithms" SourceAlgorithmSpecificationProperty = [SourceAlgorithmProperty]
set :: PropertyType
"SourceAlgorithms" SourceAlgorithmSpecificationProperty
-> SourceAlgorithmSpecificationProperty
-> SourceAlgorithmSpecificationProperty
set PropertyType
"SourceAlgorithms" SourceAlgorithmSpecificationProperty
newValue SourceAlgorithmSpecificationProperty {[SourceAlgorithmProperty]
()
haddock_workaround_ :: SourceAlgorithmSpecificationProperty -> ()
sourceAlgorithms :: SourceAlgorithmSpecificationProperty -> [SourceAlgorithmProperty]
haddock_workaround_ :: ()
sourceAlgorithms :: [SourceAlgorithmProperty]
..}
= SourceAlgorithmSpecificationProperty
{sourceAlgorithms :: [SourceAlgorithmProperty]
sourceAlgorithms = [SourceAlgorithmProperty]
PropertyType
"SourceAlgorithms" SourceAlgorithmSpecificationProperty
newValue, ()
haddock_workaround_ :: ()
haddock_workaround_ :: ()
..}