module Stratosphere.SageMaker.InferenceExperiment.ModelVariantConfigProperty (
        module Exports, ModelVariantConfigProperty(..),
        mkModelVariantConfigProperty
    ) where
import qualified Data.Aeson as JSON
import qualified Stratosphere.Prelude as Prelude
import Stratosphere.Property
import {-# SOURCE #-} Stratosphere.SageMaker.InferenceExperiment.ModelInfrastructureConfigProperty as Exports
import Stratosphere.ResourceProperties
import Stratosphere.Value
data ModelVariantConfigProperty
  = -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-sagemaker-inferenceexperiment-modelvariantconfig.html>
    ModelVariantConfigProperty {ModelVariantConfigProperty -> ()
haddock_workaround_ :: (),
                                -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-sagemaker-inferenceexperiment-modelvariantconfig.html#cfn-sagemaker-inferenceexperiment-modelvariantconfig-infrastructureconfig>
                                ModelVariantConfigProperty -> ModelInfrastructureConfigProperty
infrastructureConfig :: ModelInfrastructureConfigProperty,
                                -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-sagemaker-inferenceexperiment-modelvariantconfig.html#cfn-sagemaker-inferenceexperiment-modelvariantconfig-modelname>
                                ModelVariantConfigProperty -> Value Text
modelName :: (Value Prelude.Text),
                                -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-sagemaker-inferenceexperiment-modelvariantconfig.html#cfn-sagemaker-inferenceexperiment-modelvariantconfig-variantname>
                                ModelVariantConfigProperty -> Value Text
variantName :: (Value Prelude.Text)}
  deriving stock (ModelVariantConfigProperty -> ModelVariantConfigProperty -> Bool
(ModelVariantConfigProperty -> ModelVariantConfigProperty -> Bool)
-> (ModelVariantConfigProperty
    -> ModelVariantConfigProperty -> Bool)
-> Eq ModelVariantConfigProperty
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ModelVariantConfigProperty -> ModelVariantConfigProperty -> Bool
== :: ModelVariantConfigProperty -> ModelVariantConfigProperty -> Bool
$c/= :: ModelVariantConfigProperty -> ModelVariantConfigProperty -> Bool
/= :: ModelVariantConfigProperty -> ModelVariantConfigProperty -> Bool
Prelude.Eq, Int -> ModelVariantConfigProperty -> ShowS
[ModelVariantConfigProperty] -> ShowS
ModelVariantConfigProperty -> String
(Int -> ModelVariantConfigProperty -> ShowS)
-> (ModelVariantConfigProperty -> String)
-> ([ModelVariantConfigProperty] -> ShowS)
-> Show ModelVariantConfigProperty
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ModelVariantConfigProperty -> ShowS
showsPrec :: Int -> ModelVariantConfigProperty -> ShowS
$cshow :: ModelVariantConfigProperty -> String
show :: ModelVariantConfigProperty -> String
$cshowList :: [ModelVariantConfigProperty] -> ShowS
showList :: [ModelVariantConfigProperty] -> ShowS
Prelude.Show)
mkModelVariantConfigProperty ::
  ModelInfrastructureConfigProperty
  -> Value Prelude.Text
     -> Value Prelude.Text -> ModelVariantConfigProperty
mkModelVariantConfigProperty :: ModelInfrastructureConfigProperty
-> Value Text -> Value Text -> ModelVariantConfigProperty
mkModelVariantConfigProperty
  ModelInfrastructureConfigProperty
infrastructureConfig
  Value Text
modelName
  Value Text
variantName
  = ModelVariantConfigProperty
      {haddock_workaround_ :: ()
haddock_workaround_ = (),
       infrastructureConfig :: ModelInfrastructureConfigProperty
infrastructureConfig = ModelInfrastructureConfigProperty
infrastructureConfig, modelName :: Value Text
modelName = Value Text
modelName,
       variantName :: Value Text
variantName = Value Text
variantName}
instance ToResourceProperties ModelVariantConfigProperty where
  toResourceProperties :: ModelVariantConfigProperty -> ResourceProperties
toResourceProperties ModelVariantConfigProperty {()
Value Text
ModelInfrastructureConfigProperty
haddock_workaround_ :: ModelVariantConfigProperty -> ()
infrastructureConfig :: ModelVariantConfigProperty -> ModelInfrastructureConfigProperty
modelName :: ModelVariantConfigProperty -> Value Text
variantName :: ModelVariantConfigProperty -> Value Text
haddock_workaround_ :: ()
infrastructureConfig :: ModelInfrastructureConfigProperty
modelName :: Value Text
variantName :: Value Text
..}
    = ResourceProperties
        {awsType :: Text
awsType = Text
"AWS::SageMaker::InferenceExperiment.ModelVariantConfig",
         supportsTags :: Bool
supportsTags = Bool
Prelude.False,
         properties :: Object
properties = [Key
"InfrastructureConfig" Key -> ModelInfrastructureConfigProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
JSON..= ModelInfrastructureConfigProperty
infrastructureConfig,
                       Key
"ModelName" 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..= Value Text
modelName, Key
"VariantName" 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..= Value Text
variantName]}
instance JSON.ToJSON ModelVariantConfigProperty where
  toJSON :: ModelVariantConfigProperty -> Value
toJSON ModelVariantConfigProperty {()
Value Text
ModelInfrastructureConfigProperty
haddock_workaround_ :: ModelVariantConfigProperty -> ()
infrastructureConfig :: ModelVariantConfigProperty -> ModelInfrastructureConfigProperty
modelName :: ModelVariantConfigProperty -> Value Text
variantName :: ModelVariantConfigProperty -> Value Text
haddock_workaround_ :: ()
infrastructureConfig :: ModelInfrastructureConfigProperty
modelName :: Value Text
variantName :: Value Text
..}
    = [(Key, Value)] -> Value
JSON.object
        [Key
"InfrastructureConfig" Key -> ModelInfrastructureConfigProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
JSON..= ModelInfrastructureConfigProperty
infrastructureConfig,
         Key
"ModelName" 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..= Value Text
modelName, Key
"VariantName" 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..= Value Text
variantName]
instance Property "InfrastructureConfig" ModelVariantConfigProperty where
  type PropertyType "InfrastructureConfig" ModelVariantConfigProperty = ModelInfrastructureConfigProperty
  set :: PropertyType "InfrastructureConfig" ModelVariantConfigProperty
-> ModelVariantConfigProperty -> ModelVariantConfigProperty
set PropertyType "InfrastructureConfig" ModelVariantConfigProperty
newValue ModelVariantConfigProperty {()
Value Text
ModelInfrastructureConfigProperty
haddock_workaround_ :: ModelVariantConfigProperty -> ()
infrastructureConfig :: ModelVariantConfigProperty -> ModelInfrastructureConfigProperty
modelName :: ModelVariantConfigProperty -> Value Text
variantName :: ModelVariantConfigProperty -> Value Text
haddock_workaround_ :: ()
infrastructureConfig :: ModelInfrastructureConfigProperty
modelName :: Value Text
variantName :: Value Text
..}
    = ModelVariantConfigProperty {infrastructureConfig :: ModelInfrastructureConfigProperty
infrastructureConfig = PropertyType "InfrastructureConfig" ModelVariantConfigProperty
ModelInfrastructureConfigProperty
newValue, ()
Value Text
haddock_workaround_ :: ()
modelName :: Value Text
variantName :: Value Text
haddock_workaround_ :: ()
modelName :: Value Text
variantName :: Value Text
..}
instance Property "ModelName" ModelVariantConfigProperty where
  type PropertyType "ModelName" ModelVariantConfigProperty = Value Prelude.Text
  set :: PropertyType "ModelName" ModelVariantConfigProperty
-> ModelVariantConfigProperty -> ModelVariantConfigProperty
set PropertyType "ModelName" ModelVariantConfigProperty
newValue ModelVariantConfigProperty {()
Value Text
ModelInfrastructureConfigProperty
haddock_workaround_ :: ModelVariantConfigProperty -> ()
infrastructureConfig :: ModelVariantConfigProperty -> ModelInfrastructureConfigProperty
modelName :: ModelVariantConfigProperty -> Value Text
variantName :: ModelVariantConfigProperty -> Value Text
haddock_workaround_ :: ()
infrastructureConfig :: ModelInfrastructureConfigProperty
modelName :: Value Text
variantName :: Value Text
..}
    = ModelVariantConfigProperty {modelName :: Value Text
modelName = PropertyType "ModelName" ModelVariantConfigProperty
Value Text
newValue, ()
Value Text
ModelInfrastructureConfigProperty
haddock_workaround_ :: ()
infrastructureConfig :: ModelInfrastructureConfigProperty
variantName :: Value Text
haddock_workaround_ :: ()
infrastructureConfig :: ModelInfrastructureConfigProperty
variantName :: Value Text
..}
instance Property "VariantName" ModelVariantConfigProperty where
  type PropertyType "VariantName" ModelVariantConfigProperty = Value Prelude.Text
  set :: PropertyType "VariantName" ModelVariantConfigProperty
-> ModelVariantConfigProperty -> ModelVariantConfigProperty
set PropertyType "VariantName" ModelVariantConfigProperty
newValue ModelVariantConfigProperty {()
Value Text
ModelInfrastructureConfigProperty
haddock_workaround_ :: ModelVariantConfigProperty -> ()
infrastructureConfig :: ModelVariantConfigProperty -> ModelInfrastructureConfigProperty
modelName :: ModelVariantConfigProperty -> Value Text
variantName :: ModelVariantConfigProperty -> Value Text
haddock_workaround_ :: ()
infrastructureConfig :: ModelInfrastructureConfigProperty
modelName :: Value Text
variantName :: Value Text
..}
    = ModelVariantConfigProperty {variantName :: Value Text
variantName = PropertyType "VariantName" ModelVariantConfigProperty
Value Text
newValue, ()
Value Text
ModelInfrastructureConfigProperty
haddock_workaround_ :: ()
infrastructureConfig :: ModelInfrastructureConfigProperty
modelName :: Value Text
haddock_workaround_ :: ()
infrastructureConfig :: ModelInfrastructureConfigProperty
modelName :: Value Text
..}