module Stratosphere.SageMaker.UserProfile.ResourceSpecProperty (
        ResourceSpecProperty(..), mkResourceSpecProperty
    ) where
import qualified Data.Aeson as JSON
import qualified Stratosphere.Prelude as Prelude
import Stratosphere.Property
import Stratosphere.ResourceProperties
import Stratosphere.Value
data ResourceSpecProperty
  = -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-sagemaker-userprofile-resourcespec.html>
    ResourceSpecProperty {ResourceSpecProperty -> ()
haddock_workaround_ :: (),
                          -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-sagemaker-userprofile-resourcespec.html#cfn-sagemaker-userprofile-resourcespec-instancetype>
                          ResourceSpecProperty -> Maybe (Value Text)
instanceType :: (Prelude.Maybe (Value Prelude.Text)),
                          -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-sagemaker-userprofile-resourcespec.html#cfn-sagemaker-userprofile-resourcespec-lifecycleconfigarn>
                          ResourceSpecProperty -> Maybe (Value Text)
lifecycleConfigArn :: (Prelude.Maybe (Value Prelude.Text)),
                          -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-sagemaker-userprofile-resourcespec.html#cfn-sagemaker-userprofile-resourcespec-sagemakerimagearn>
                          ResourceSpecProperty -> Maybe (Value Text)
sageMakerImageArn :: (Prelude.Maybe (Value Prelude.Text)),
                          -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-sagemaker-userprofile-resourcespec.html#cfn-sagemaker-userprofile-resourcespec-sagemakerimageversionarn>
                          ResourceSpecProperty -> Maybe (Value Text)
sageMakerImageVersionArn :: (Prelude.Maybe (Value Prelude.Text))}
  deriving stock (ResourceSpecProperty -> ResourceSpecProperty -> Bool
(ResourceSpecProperty -> ResourceSpecProperty -> Bool)
-> (ResourceSpecProperty -> ResourceSpecProperty -> Bool)
-> Eq ResourceSpecProperty
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ResourceSpecProperty -> ResourceSpecProperty -> Bool
== :: ResourceSpecProperty -> ResourceSpecProperty -> Bool
$c/= :: ResourceSpecProperty -> ResourceSpecProperty -> Bool
/= :: ResourceSpecProperty -> ResourceSpecProperty -> Bool
Prelude.Eq, Int -> ResourceSpecProperty -> ShowS
[ResourceSpecProperty] -> ShowS
ResourceSpecProperty -> String
(Int -> ResourceSpecProperty -> ShowS)
-> (ResourceSpecProperty -> String)
-> ([ResourceSpecProperty] -> ShowS)
-> Show ResourceSpecProperty
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ResourceSpecProperty -> ShowS
showsPrec :: Int -> ResourceSpecProperty -> ShowS
$cshow :: ResourceSpecProperty -> String
show :: ResourceSpecProperty -> String
$cshowList :: [ResourceSpecProperty] -> ShowS
showList :: [ResourceSpecProperty] -> ShowS
Prelude.Show)
mkResourceSpecProperty :: ResourceSpecProperty
mkResourceSpecProperty :: ResourceSpecProperty
mkResourceSpecProperty
  = ResourceSpecProperty
      {haddock_workaround_ :: ()
haddock_workaround_ = (), instanceType :: Maybe (Value Text)
instanceType = Maybe (Value Text)
forall a. Maybe a
Prelude.Nothing,
       lifecycleConfigArn :: Maybe (Value Text)
lifecycleConfigArn = Maybe (Value Text)
forall a. Maybe a
Prelude.Nothing,
       sageMakerImageArn :: Maybe (Value Text)
sageMakerImageArn = Maybe (Value Text)
forall a. Maybe a
Prelude.Nothing,
       sageMakerImageVersionArn :: Maybe (Value Text)
sageMakerImageVersionArn = Maybe (Value Text)
forall a. Maybe a
Prelude.Nothing}
instance ToResourceProperties ResourceSpecProperty where
  toResourceProperties :: ResourceSpecProperty -> ResourceProperties
toResourceProperties ResourceSpecProperty {Maybe (Value Text)
()
haddock_workaround_ :: ResourceSpecProperty -> ()
instanceType :: ResourceSpecProperty -> Maybe (Value Text)
lifecycleConfigArn :: ResourceSpecProperty -> Maybe (Value Text)
sageMakerImageArn :: ResourceSpecProperty -> Maybe (Value Text)
sageMakerImageVersionArn :: ResourceSpecProperty -> Maybe (Value Text)
haddock_workaround_ :: ()
instanceType :: Maybe (Value Text)
lifecycleConfigArn :: Maybe (Value Text)
sageMakerImageArn :: Maybe (Value Text)
sageMakerImageVersionArn :: Maybe (Value Text)
..}
    = ResourceProperties
        {awsType :: Text
awsType = Text
"AWS::SageMaker::UserProfile.ResourceSpec",
         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
"InstanceType" (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)
instanceType,
                            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
"LifecycleConfigArn" (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)
lifecycleConfigArn,
                            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
"SageMakerImageArn" (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)
sageMakerImageArn,
                            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
"SageMakerImageVersionArn"
                              (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)
sageMakerImageVersionArn])}
instance JSON.ToJSON ResourceSpecProperty where
  toJSON :: ResourceSpecProperty -> Value
toJSON ResourceSpecProperty {Maybe (Value Text)
()
haddock_workaround_ :: ResourceSpecProperty -> ()
instanceType :: ResourceSpecProperty -> Maybe (Value Text)
lifecycleConfigArn :: ResourceSpecProperty -> Maybe (Value Text)
sageMakerImageArn :: ResourceSpecProperty -> Maybe (Value Text)
sageMakerImageVersionArn :: ResourceSpecProperty -> Maybe (Value Text)
haddock_workaround_ :: ()
instanceType :: Maybe (Value Text)
lifecycleConfigArn :: Maybe (Value Text)
sageMakerImageArn :: Maybe (Value Text)
sageMakerImageVersionArn :: Maybe (Value Text)
..}
    = [(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
"InstanceType" (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)
instanceType,
               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
"LifecycleConfigArn" (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)
lifecycleConfigArn,
               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
"SageMakerImageArn" (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)
sageMakerImageArn,
               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
"SageMakerImageVersionArn"
                 (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)
sageMakerImageVersionArn]))
instance Property "InstanceType" ResourceSpecProperty where
  type PropertyType "InstanceType" ResourceSpecProperty = Value Prelude.Text
  set :: PropertyType "InstanceType" ResourceSpecProperty
-> ResourceSpecProperty -> ResourceSpecProperty
set PropertyType "InstanceType" ResourceSpecProperty
newValue ResourceSpecProperty {Maybe (Value Text)
()
haddock_workaround_ :: ResourceSpecProperty -> ()
instanceType :: ResourceSpecProperty -> Maybe (Value Text)
lifecycleConfigArn :: ResourceSpecProperty -> Maybe (Value Text)
sageMakerImageArn :: ResourceSpecProperty -> Maybe (Value Text)
sageMakerImageVersionArn :: ResourceSpecProperty -> Maybe (Value Text)
haddock_workaround_ :: ()
instanceType :: Maybe (Value Text)
lifecycleConfigArn :: Maybe (Value Text)
sageMakerImageArn :: Maybe (Value Text)
sageMakerImageVersionArn :: Maybe (Value Text)
..}
    = ResourceSpecProperty {instanceType :: Maybe (Value Text)
instanceType = Value Text -> Maybe (Value Text)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "InstanceType" ResourceSpecProperty
Value Text
newValue, Maybe (Value Text)
()
haddock_workaround_ :: ()
lifecycleConfigArn :: Maybe (Value Text)
sageMakerImageArn :: Maybe (Value Text)
sageMakerImageVersionArn :: Maybe (Value Text)
haddock_workaround_ :: ()
lifecycleConfigArn :: Maybe (Value Text)
sageMakerImageArn :: Maybe (Value Text)
sageMakerImageVersionArn :: Maybe (Value Text)
..}
instance Property "LifecycleConfigArn" ResourceSpecProperty where
  type PropertyType "LifecycleConfigArn" ResourceSpecProperty = Value Prelude.Text
  set :: PropertyType "LifecycleConfigArn" ResourceSpecProperty
-> ResourceSpecProperty -> ResourceSpecProperty
set PropertyType "LifecycleConfigArn" ResourceSpecProperty
newValue ResourceSpecProperty {Maybe (Value Text)
()
haddock_workaround_ :: ResourceSpecProperty -> ()
instanceType :: ResourceSpecProperty -> Maybe (Value Text)
lifecycleConfigArn :: ResourceSpecProperty -> Maybe (Value Text)
sageMakerImageArn :: ResourceSpecProperty -> Maybe (Value Text)
sageMakerImageVersionArn :: ResourceSpecProperty -> Maybe (Value Text)
haddock_workaround_ :: ()
instanceType :: Maybe (Value Text)
lifecycleConfigArn :: Maybe (Value Text)
sageMakerImageArn :: Maybe (Value Text)
sageMakerImageVersionArn :: Maybe (Value Text)
..}
    = ResourceSpecProperty
        {lifecycleConfigArn :: Maybe (Value Text)
lifecycleConfigArn = Value Text -> Maybe (Value Text)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "LifecycleConfigArn" ResourceSpecProperty
Value Text
newValue, Maybe (Value Text)
()
haddock_workaround_ :: ()
instanceType :: Maybe (Value Text)
sageMakerImageArn :: Maybe (Value Text)
sageMakerImageVersionArn :: Maybe (Value Text)
haddock_workaround_ :: ()
instanceType :: Maybe (Value Text)
sageMakerImageArn :: Maybe (Value Text)
sageMakerImageVersionArn :: Maybe (Value Text)
..}
instance Property "SageMakerImageArn" ResourceSpecProperty where
  type PropertyType "SageMakerImageArn" ResourceSpecProperty = Value Prelude.Text
  set :: PropertyType "SageMakerImageArn" ResourceSpecProperty
-> ResourceSpecProperty -> ResourceSpecProperty
set PropertyType "SageMakerImageArn" ResourceSpecProperty
newValue ResourceSpecProperty {Maybe (Value Text)
()
haddock_workaround_ :: ResourceSpecProperty -> ()
instanceType :: ResourceSpecProperty -> Maybe (Value Text)
lifecycleConfigArn :: ResourceSpecProperty -> Maybe (Value Text)
sageMakerImageArn :: ResourceSpecProperty -> Maybe (Value Text)
sageMakerImageVersionArn :: ResourceSpecProperty -> Maybe (Value Text)
haddock_workaround_ :: ()
instanceType :: Maybe (Value Text)
lifecycleConfigArn :: Maybe (Value Text)
sageMakerImageArn :: Maybe (Value Text)
sageMakerImageVersionArn :: Maybe (Value Text)
..}
    = ResourceSpecProperty
        {sageMakerImageArn :: Maybe (Value Text)
sageMakerImageArn = Value Text -> Maybe (Value Text)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "SageMakerImageArn" ResourceSpecProperty
Value Text
newValue, Maybe (Value Text)
()
haddock_workaround_ :: ()
instanceType :: Maybe (Value Text)
lifecycleConfigArn :: Maybe (Value Text)
sageMakerImageVersionArn :: Maybe (Value Text)
haddock_workaround_ :: ()
instanceType :: Maybe (Value Text)
lifecycleConfigArn :: Maybe (Value Text)
sageMakerImageVersionArn :: Maybe (Value Text)
..}
instance Property "SageMakerImageVersionArn" ResourceSpecProperty where
  type PropertyType "SageMakerImageVersionArn" ResourceSpecProperty = Value Prelude.Text
  set :: PropertyType "SageMakerImageVersionArn" ResourceSpecProperty
-> ResourceSpecProperty -> ResourceSpecProperty
set PropertyType "SageMakerImageVersionArn" ResourceSpecProperty
newValue ResourceSpecProperty {Maybe (Value Text)
()
haddock_workaround_ :: ResourceSpecProperty -> ()
instanceType :: ResourceSpecProperty -> Maybe (Value Text)
lifecycleConfigArn :: ResourceSpecProperty -> Maybe (Value Text)
sageMakerImageArn :: ResourceSpecProperty -> Maybe (Value Text)
sageMakerImageVersionArn :: ResourceSpecProperty -> Maybe (Value Text)
haddock_workaround_ :: ()
instanceType :: Maybe (Value Text)
lifecycleConfigArn :: Maybe (Value Text)
sageMakerImageArn :: Maybe (Value Text)
sageMakerImageVersionArn :: Maybe (Value Text)
..}
    = ResourceSpecProperty
        {sageMakerImageVersionArn :: Maybe (Value Text)
sageMakerImageVersionArn = Value Text -> Maybe (Value Text)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "SageMakerImageVersionArn" ResourceSpecProperty
Value Text
newValue, Maybe (Value Text)
()
haddock_workaround_ :: ()
instanceType :: Maybe (Value Text)
lifecycleConfigArn :: Maybe (Value Text)
sageMakerImageArn :: Maybe (Value Text)
haddock_workaround_ :: ()
instanceType :: Maybe (Value Text)
lifecycleConfigArn :: Maybe (Value Text)
sageMakerImageArn :: Maybe (Value Text)
..}