module Stratosphere.SageMaker.InferenceComponent.InferenceComponentSpecificationProperty (
module Exports, InferenceComponentSpecificationProperty(..),
mkInferenceComponentSpecificationProperty
) where
import qualified Data.Aeson as JSON
import qualified Stratosphere.Prelude as Prelude
import Stratosphere.Property
import {-# SOURCE #-} Stratosphere.SageMaker.InferenceComponent.InferenceComponentComputeResourceRequirementsProperty as Exports
import {-# SOURCE #-} Stratosphere.SageMaker.InferenceComponent.InferenceComponentContainerSpecificationProperty as Exports
import {-# SOURCE #-} Stratosphere.SageMaker.InferenceComponent.InferenceComponentStartupParametersProperty as Exports
import Stratosphere.ResourceProperties
import Stratosphere.Value
data InferenceComponentSpecificationProperty
=
InferenceComponentSpecificationProperty {InferenceComponentSpecificationProperty -> ()
haddock_workaround_ :: (),
InferenceComponentSpecificationProperty -> Maybe (Value Text)
baseInferenceComponentName :: (Prelude.Maybe (Value Prelude.Text)),
InferenceComponentSpecificationProperty
-> Maybe InferenceComponentComputeResourceRequirementsProperty
computeResourceRequirements :: (Prelude.Maybe InferenceComponentComputeResourceRequirementsProperty),
InferenceComponentSpecificationProperty
-> Maybe InferenceComponentContainerSpecificationProperty
container :: (Prelude.Maybe InferenceComponentContainerSpecificationProperty),
InferenceComponentSpecificationProperty -> Maybe (Value Text)
modelName :: (Prelude.Maybe (Value Prelude.Text)),
InferenceComponentSpecificationProperty
-> Maybe InferenceComponentStartupParametersProperty
startupParameters :: (Prelude.Maybe InferenceComponentStartupParametersProperty)}
deriving stock (InferenceComponentSpecificationProperty
-> InferenceComponentSpecificationProperty -> Bool
(InferenceComponentSpecificationProperty
-> InferenceComponentSpecificationProperty -> Bool)
-> (InferenceComponentSpecificationProperty
-> InferenceComponentSpecificationProperty -> Bool)
-> Eq InferenceComponentSpecificationProperty
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: InferenceComponentSpecificationProperty
-> InferenceComponentSpecificationProperty -> Bool
== :: InferenceComponentSpecificationProperty
-> InferenceComponentSpecificationProperty -> Bool
$c/= :: InferenceComponentSpecificationProperty
-> InferenceComponentSpecificationProperty -> Bool
/= :: InferenceComponentSpecificationProperty
-> InferenceComponentSpecificationProperty -> Bool
Prelude.Eq, Int -> InferenceComponentSpecificationProperty -> ShowS
[InferenceComponentSpecificationProperty] -> ShowS
InferenceComponentSpecificationProperty -> String
(Int -> InferenceComponentSpecificationProperty -> ShowS)
-> (InferenceComponentSpecificationProperty -> String)
-> ([InferenceComponentSpecificationProperty] -> ShowS)
-> Show InferenceComponentSpecificationProperty
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> InferenceComponentSpecificationProperty -> ShowS
showsPrec :: Int -> InferenceComponentSpecificationProperty -> ShowS
$cshow :: InferenceComponentSpecificationProperty -> String
show :: InferenceComponentSpecificationProperty -> String
$cshowList :: [InferenceComponentSpecificationProperty] -> ShowS
showList :: [InferenceComponentSpecificationProperty] -> ShowS
Prelude.Show)
mkInferenceComponentSpecificationProperty ::
InferenceComponentSpecificationProperty
mkInferenceComponentSpecificationProperty :: InferenceComponentSpecificationProperty
mkInferenceComponentSpecificationProperty
= InferenceComponentSpecificationProperty
{haddock_workaround_ :: ()
haddock_workaround_ = (),
baseInferenceComponentName :: Maybe (Value Text)
baseInferenceComponentName = Maybe (Value Text)
forall a. Maybe a
Prelude.Nothing,
computeResourceRequirements :: Maybe InferenceComponentComputeResourceRequirementsProperty
computeResourceRequirements = Maybe InferenceComponentComputeResourceRequirementsProperty
forall a. Maybe a
Prelude.Nothing,
container :: Maybe InferenceComponentContainerSpecificationProperty
container = Maybe InferenceComponentContainerSpecificationProperty
forall a. Maybe a
Prelude.Nothing, modelName :: Maybe (Value Text)
modelName = Maybe (Value Text)
forall a. Maybe a
Prelude.Nothing,
startupParameters :: Maybe InferenceComponentStartupParametersProperty
startupParameters = Maybe InferenceComponentStartupParametersProperty
forall a. Maybe a
Prelude.Nothing}
instance ToResourceProperties InferenceComponentSpecificationProperty where
toResourceProperties :: InferenceComponentSpecificationProperty -> ResourceProperties
toResourceProperties InferenceComponentSpecificationProperty {Maybe (Value Text)
Maybe InferenceComponentComputeResourceRequirementsProperty
Maybe InferenceComponentContainerSpecificationProperty
Maybe InferenceComponentStartupParametersProperty
()
haddock_workaround_ :: InferenceComponentSpecificationProperty -> ()
baseInferenceComponentName :: InferenceComponentSpecificationProperty -> Maybe (Value Text)
computeResourceRequirements :: InferenceComponentSpecificationProperty
-> Maybe InferenceComponentComputeResourceRequirementsProperty
container :: InferenceComponentSpecificationProperty
-> Maybe InferenceComponentContainerSpecificationProperty
modelName :: InferenceComponentSpecificationProperty -> Maybe (Value Text)
startupParameters :: InferenceComponentSpecificationProperty
-> Maybe InferenceComponentStartupParametersProperty
haddock_workaround_ :: ()
baseInferenceComponentName :: Maybe (Value Text)
computeResourceRequirements :: Maybe InferenceComponentComputeResourceRequirementsProperty
container :: Maybe InferenceComponentContainerSpecificationProperty
modelName :: Maybe (Value Text)
startupParameters :: Maybe InferenceComponentStartupParametersProperty
..}
= ResourceProperties
{awsType :: Text
awsType = Text
"AWS::SageMaker::InferenceComponent.InferenceComponentSpecification",
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 -> 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
"BaseInferenceComponentName"
(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)
baseInferenceComponentName,
Key
-> InferenceComponentComputeResourceRequirementsProperty
-> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"ComputeResourceRequirements"
(InferenceComponentComputeResourceRequirementsProperty
-> (Key, Value))
-> Maybe InferenceComponentComputeResourceRequirementsProperty
-> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe InferenceComponentComputeResourceRequirementsProperty
computeResourceRequirements,
Key
-> InferenceComponentContainerSpecificationProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"Container" (InferenceComponentContainerSpecificationProperty -> (Key, Value))
-> Maybe InferenceComponentContainerSpecificationProperty
-> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe InferenceComponentContainerSpecificationProperty
container,
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
"ModelName" (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)
modelName,
Key -> InferenceComponentStartupParametersProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"StartupParameters" (InferenceComponentStartupParametersProperty -> (Key, Value))
-> Maybe InferenceComponentStartupParametersProperty
-> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe InferenceComponentStartupParametersProperty
startupParameters])}
instance JSON.ToJSON InferenceComponentSpecificationProperty where
toJSON :: InferenceComponentSpecificationProperty -> Value
toJSON InferenceComponentSpecificationProperty {Maybe (Value Text)
Maybe InferenceComponentComputeResourceRequirementsProperty
Maybe InferenceComponentContainerSpecificationProperty
Maybe InferenceComponentStartupParametersProperty
()
haddock_workaround_ :: InferenceComponentSpecificationProperty -> ()
baseInferenceComponentName :: InferenceComponentSpecificationProperty -> Maybe (Value Text)
computeResourceRequirements :: InferenceComponentSpecificationProperty
-> Maybe InferenceComponentComputeResourceRequirementsProperty
container :: InferenceComponentSpecificationProperty
-> Maybe InferenceComponentContainerSpecificationProperty
modelName :: InferenceComponentSpecificationProperty -> Maybe (Value Text)
startupParameters :: InferenceComponentSpecificationProperty
-> Maybe InferenceComponentStartupParametersProperty
haddock_workaround_ :: ()
baseInferenceComponentName :: Maybe (Value Text)
computeResourceRequirements :: Maybe InferenceComponentComputeResourceRequirementsProperty
container :: Maybe InferenceComponentContainerSpecificationProperty
modelName :: Maybe (Value Text)
startupParameters :: Maybe InferenceComponentStartupParametersProperty
..}
= [(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 -> 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
"BaseInferenceComponentName"
(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)
baseInferenceComponentName,
Key
-> InferenceComponentComputeResourceRequirementsProperty
-> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"ComputeResourceRequirements"
(InferenceComponentComputeResourceRequirementsProperty
-> (Key, Value))
-> Maybe InferenceComponentComputeResourceRequirementsProperty
-> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe InferenceComponentComputeResourceRequirementsProperty
computeResourceRequirements,
Key
-> InferenceComponentContainerSpecificationProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"Container" (InferenceComponentContainerSpecificationProperty -> (Key, Value))
-> Maybe InferenceComponentContainerSpecificationProperty
-> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe InferenceComponentContainerSpecificationProperty
container,
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
"ModelName" (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)
modelName,
Key -> InferenceComponentStartupParametersProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"StartupParameters" (InferenceComponentStartupParametersProperty -> (Key, Value))
-> Maybe InferenceComponentStartupParametersProperty
-> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe InferenceComponentStartupParametersProperty
startupParameters]))
instance Property "BaseInferenceComponentName" InferenceComponentSpecificationProperty where
type PropertyType "BaseInferenceComponentName" InferenceComponentSpecificationProperty = Value Prelude.Text
set :: PropertyType
"BaseInferenceComponentName"
InferenceComponentSpecificationProperty
-> InferenceComponentSpecificationProperty
-> InferenceComponentSpecificationProperty
set PropertyType
"BaseInferenceComponentName"
InferenceComponentSpecificationProperty
newValue InferenceComponentSpecificationProperty {Maybe (Value Text)
Maybe InferenceComponentComputeResourceRequirementsProperty
Maybe InferenceComponentContainerSpecificationProperty
Maybe InferenceComponentStartupParametersProperty
()
haddock_workaround_ :: InferenceComponentSpecificationProperty -> ()
baseInferenceComponentName :: InferenceComponentSpecificationProperty -> Maybe (Value Text)
computeResourceRequirements :: InferenceComponentSpecificationProperty
-> Maybe InferenceComponentComputeResourceRequirementsProperty
container :: InferenceComponentSpecificationProperty
-> Maybe InferenceComponentContainerSpecificationProperty
modelName :: InferenceComponentSpecificationProperty -> Maybe (Value Text)
startupParameters :: InferenceComponentSpecificationProperty
-> Maybe InferenceComponentStartupParametersProperty
haddock_workaround_ :: ()
baseInferenceComponentName :: Maybe (Value Text)
computeResourceRequirements :: Maybe InferenceComponentComputeResourceRequirementsProperty
container :: Maybe InferenceComponentContainerSpecificationProperty
modelName :: Maybe (Value Text)
startupParameters :: Maybe InferenceComponentStartupParametersProperty
..}
= InferenceComponentSpecificationProperty
{baseInferenceComponentName :: Maybe (Value Text)
baseInferenceComponentName = Value Text -> Maybe (Value Text)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType
"BaseInferenceComponentName"
InferenceComponentSpecificationProperty
Value Text
newValue, Maybe (Value Text)
Maybe InferenceComponentComputeResourceRequirementsProperty
Maybe InferenceComponentContainerSpecificationProperty
Maybe InferenceComponentStartupParametersProperty
()
haddock_workaround_ :: ()
computeResourceRequirements :: Maybe InferenceComponentComputeResourceRequirementsProperty
container :: Maybe InferenceComponentContainerSpecificationProperty
modelName :: Maybe (Value Text)
startupParameters :: Maybe InferenceComponentStartupParametersProperty
haddock_workaround_ :: ()
computeResourceRequirements :: Maybe InferenceComponentComputeResourceRequirementsProperty
container :: Maybe InferenceComponentContainerSpecificationProperty
modelName :: Maybe (Value Text)
startupParameters :: Maybe InferenceComponentStartupParametersProperty
..}
instance Property "ComputeResourceRequirements" InferenceComponentSpecificationProperty where
type PropertyType "ComputeResourceRequirements" InferenceComponentSpecificationProperty = InferenceComponentComputeResourceRequirementsProperty
set :: PropertyType
"ComputeResourceRequirements"
InferenceComponentSpecificationProperty
-> InferenceComponentSpecificationProperty
-> InferenceComponentSpecificationProperty
set PropertyType
"ComputeResourceRequirements"
InferenceComponentSpecificationProperty
newValue InferenceComponentSpecificationProperty {Maybe (Value Text)
Maybe InferenceComponentComputeResourceRequirementsProperty
Maybe InferenceComponentContainerSpecificationProperty
Maybe InferenceComponentStartupParametersProperty
()
haddock_workaround_ :: InferenceComponentSpecificationProperty -> ()
baseInferenceComponentName :: InferenceComponentSpecificationProperty -> Maybe (Value Text)
computeResourceRequirements :: InferenceComponentSpecificationProperty
-> Maybe InferenceComponentComputeResourceRequirementsProperty
container :: InferenceComponentSpecificationProperty
-> Maybe InferenceComponentContainerSpecificationProperty
modelName :: InferenceComponentSpecificationProperty -> Maybe (Value Text)
startupParameters :: InferenceComponentSpecificationProperty
-> Maybe InferenceComponentStartupParametersProperty
haddock_workaround_ :: ()
baseInferenceComponentName :: Maybe (Value Text)
computeResourceRequirements :: Maybe InferenceComponentComputeResourceRequirementsProperty
container :: Maybe InferenceComponentContainerSpecificationProperty
modelName :: Maybe (Value Text)
startupParameters :: Maybe InferenceComponentStartupParametersProperty
..}
= InferenceComponentSpecificationProperty
{computeResourceRequirements :: Maybe InferenceComponentComputeResourceRequirementsProperty
computeResourceRequirements = InferenceComponentComputeResourceRequirementsProperty
-> Maybe InferenceComponentComputeResourceRequirementsProperty
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType
"ComputeResourceRequirements"
InferenceComponentSpecificationProperty
InferenceComponentComputeResourceRequirementsProperty
newValue, Maybe (Value Text)
Maybe InferenceComponentContainerSpecificationProperty
Maybe InferenceComponentStartupParametersProperty
()
haddock_workaround_ :: ()
baseInferenceComponentName :: Maybe (Value Text)
container :: Maybe InferenceComponentContainerSpecificationProperty
modelName :: Maybe (Value Text)
startupParameters :: Maybe InferenceComponentStartupParametersProperty
haddock_workaround_ :: ()
baseInferenceComponentName :: Maybe (Value Text)
container :: Maybe InferenceComponentContainerSpecificationProperty
modelName :: Maybe (Value Text)
startupParameters :: Maybe InferenceComponentStartupParametersProperty
..}
instance Property "Container" InferenceComponentSpecificationProperty where
type PropertyType "Container" InferenceComponentSpecificationProperty = InferenceComponentContainerSpecificationProperty
set :: PropertyType "Container" InferenceComponentSpecificationProperty
-> InferenceComponentSpecificationProperty
-> InferenceComponentSpecificationProperty
set PropertyType "Container" InferenceComponentSpecificationProperty
newValue InferenceComponentSpecificationProperty {Maybe (Value Text)
Maybe InferenceComponentComputeResourceRequirementsProperty
Maybe InferenceComponentContainerSpecificationProperty
Maybe InferenceComponentStartupParametersProperty
()
haddock_workaround_ :: InferenceComponentSpecificationProperty -> ()
baseInferenceComponentName :: InferenceComponentSpecificationProperty -> Maybe (Value Text)
computeResourceRequirements :: InferenceComponentSpecificationProperty
-> Maybe InferenceComponentComputeResourceRequirementsProperty
container :: InferenceComponentSpecificationProperty
-> Maybe InferenceComponentContainerSpecificationProperty
modelName :: InferenceComponentSpecificationProperty -> Maybe (Value Text)
startupParameters :: InferenceComponentSpecificationProperty
-> Maybe InferenceComponentStartupParametersProperty
haddock_workaround_ :: ()
baseInferenceComponentName :: Maybe (Value Text)
computeResourceRequirements :: Maybe InferenceComponentComputeResourceRequirementsProperty
container :: Maybe InferenceComponentContainerSpecificationProperty
modelName :: Maybe (Value Text)
startupParameters :: Maybe InferenceComponentStartupParametersProperty
..}
= InferenceComponentSpecificationProperty
{container :: Maybe InferenceComponentContainerSpecificationProperty
container = InferenceComponentContainerSpecificationProperty
-> Maybe InferenceComponentContainerSpecificationProperty
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "Container" InferenceComponentSpecificationProperty
InferenceComponentContainerSpecificationProperty
newValue, Maybe (Value Text)
Maybe InferenceComponentComputeResourceRequirementsProperty
Maybe InferenceComponentStartupParametersProperty
()
haddock_workaround_ :: ()
baseInferenceComponentName :: Maybe (Value Text)
computeResourceRequirements :: Maybe InferenceComponentComputeResourceRequirementsProperty
modelName :: Maybe (Value Text)
startupParameters :: Maybe InferenceComponentStartupParametersProperty
haddock_workaround_ :: ()
baseInferenceComponentName :: Maybe (Value Text)
computeResourceRequirements :: Maybe InferenceComponentComputeResourceRequirementsProperty
modelName :: Maybe (Value Text)
startupParameters :: Maybe InferenceComponentStartupParametersProperty
..}
instance Property "ModelName" InferenceComponentSpecificationProperty where
type PropertyType "ModelName" InferenceComponentSpecificationProperty = Value Prelude.Text
set :: PropertyType "ModelName" InferenceComponentSpecificationProperty
-> InferenceComponentSpecificationProperty
-> InferenceComponentSpecificationProperty
set PropertyType "ModelName" InferenceComponentSpecificationProperty
newValue InferenceComponentSpecificationProperty {Maybe (Value Text)
Maybe InferenceComponentComputeResourceRequirementsProperty
Maybe InferenceComponentContainerSpecificationProperty
Maybe InferenceComponentStartupParametersProperty
()
haddock_workaround_ :: InferenceComponentSpecificationProperty -> ()
baseInferenceComponentName :: InferenceComponentSpecificationProperty -> Maybe (Value Text)
computeResourceRequirements :: InferenceComponentSpecificationProperty
-> Maybe InferenceComponentComputeResourceRequirementsProperty
container :: InferenceComponentSpecificationProperty
-> Maybe InferenceComponentContainerSpecificationProperty
modelName :: InferenceComponentSpecificationProperty -> Maybe (Value Text)
startupParameters :: InferenceComponentSpecificationProperty
-> Maybe InferenceComponentStartupParametersProperty
haddock_workaround_ :: ()
baseInferenceComponentName :: Maybe (Value Text)
computeResourceRequirements :: Maybe InferenceComponentComputeResourceRequirementsProperty
container :: Maybe InferenceComponentContainerSpecificationProperty
modelName :: Maybe (Value Text)
startupParameters :: Maybe InferenceComponentStartupParametersProperty
..}
= InferenceComponentSpecificationProperty
{modelName :: Maybe (Value Text)
modelName = Value Text -> Maybe (Value Text)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "ModelName" InferenceComponentSpecificationProperty
Value Text
newValue, Maybe (Value Text)
Maybe InferenceComponentComputeResourceRequirementsProperty
Maybe InferenceComponentContainerSpecificationProperty
Maybe InferenceComponentStartupParametersProperty
()
haddock_workaround_ :: ()
baseInferenceComponentName :: Maybe (Value Text)
computeResourceRequirements :: Maybe InferenceComponentComputeResourceRequirementsProperty
container :: Maybe InferenceComponentContainerSpecificationProperty
startupParameters :: Maybe InferenceComponentStartupParametersProperty
haddock_workaround_ :: ()
baseInferenceComponentName :: Maybe (Value Text)
computeResourceRequirements :: Maybe InferenceComponentComputeResourceRequirementsProperty
container :: Maybe InferenceComponentContainerSpecificationProperty
startupParameters :: Maybe InferenceComponentStartupParametersProperty
..}
instance Property "StartupParameters" InferenceComponentSpecificationProperty where
type PropertyType "StartupParameters" InferenceComponentSpecificationProperty = InferenceComponentStartupParametersProperty
set :: PropertyType
"StartupParameters" InferenceComponentSpecificationProperty
-> InferenceComponentSpecificationProperty
-> InferenceComponentSpecificationProperty
set PropertyType
"StartupParameters" InferenceComponentSpecificationProperty
newValue InferenceComponentSpecificationProperty {Maybe (Value Text)
Maybe InferenceComponentComputeResourceRequirementsProperty
Maybe InferenceComponentContainerSpecificationProperty
Maybe InferenceComponentStartupParametersProperty
()
haddock_workaround_ :: InferenceComponentSpecificationProperty -> ()
baseInferenceComponentName :: InferenceComponentSpecificationProperty -> Maybe (Value Text)
computeResourceRequirements :: InferenceComponentSpecificationProperty
-> Maybe InferenceComponentComputeResourceRequirementsProperty
container :: InferenceComponentSpecificationProperty
-> Maybe InferenceComponentContainerSpecificationProperty
modelName :: InferenceComponentSpecificationProperty -> Maybe (Value Text)
startupParameters :: InferenceComponentSpecificationProperty
-> Maybe InferenceComponentStartupParametersProperty
haddock_workaround_ :: ()
baseInferenceComponentName :: Maybe (Value Text)
computeResourceRequirements :: Maybe InferenceComponentComputeResourceRequirementsProperty
container :: Maybe InferenceComponentContainerSpecificationProperty
modelName :: Maybe (Value Text)
startupParameters :: Maybe InferenceComponentStartupParametersProperty
..}
= InferenceComponentSpecificationProperty
{startupParameters :: Maybe InferenceComponentStartupParametersProperty
startupParameters = InferenceComponentStartupParametersProperty
-> Maybe InferenceComponentStartupParametersProperty
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType
"StartupParameters" InferenceComponentSpecificationProperty
InferenceComponentStartupParametersProperty
newValue, Maybe (Value Text)
Maybe InferenceComponentComputeResourceRequirementsProperty
Maybe InferenceComponentContainerSpecificationProperty
()
haddock_workaround_ :: ()
baseInferenceComponentName :: Maybe (Value Text)
computeResourceRequirements :: Maybe InferenceComponentComputeResourceRequirementsProperty
container :: Maybe InferenceComponentContainerSpecificationProperty
modelName :: Maybe (Value Text)
haddock_workaround_ :: ()
baseInferenceComponentName :: Maybe (Value Text)
computeResourceRequirements :: Maybe InferenceComponentComputeResourceRequirementsProperty
container :: Maybe InferenceComponentContainerSpecificationProperty
modelName :: Maybe (Value Text)
..}