module Stratosphere.SageMaker.Cluster.ClusterOrchestratorEksConfigProperty (
        ClusterOrchestratorEksConfigProperty(..),
        mkClusterOrchestratorEksConfigProperty
    ) where
import qualified Data.Aeson as JSON
import qualified Stratosphere.Prelude as Prelude
import Stratosphere.Property
import Stratosphere.ResourceProperties
import Stratosphere.Value
data ClusterOrchestratorEksConfigProperty
  = -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-sagemaker-cluster-clusterorchestratoreksconfig.html>
    ClusterOrchestratorEksConfigProperty {ClusterOrchestratorEksConfigProperty -> ()
haddock_workaround_ :: (),
                                          -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-sagemaker-cluster-clusterorchestratoreksconfig.html#cfn-sagemaker-cluster-clusterorchestratoreksconfig-clusterarn>
                                          ClusterOrchestratorEksConfigProperty -> Value Text
clusterArn :: (Value Prelude.Text)}
  deriving stock (ClusterOrchestratorEksConfigProperty
-> ClusterOrchestratorEksConfigProperty -> Bool
(ClusterOrchestratorEksConfigProperty
 -> ClusterOrchestratorEksConfigProperty -> Bool)
-> (ClusterOrchestratorEksConfigProperty
    -> ClusterOrchestratorEksConfigProperty -> Bool)
-> Eq ClusterOrchestratorEksConfigProperty
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ClusterOrchestratorEksConfigProperty
-> ClusterOrchestratorEksConfigProperty -> Bool
== :: ClusterOrchestratorEksConfigProperty
-> ClusterOrchestratorEksConfigProperty -> Bool
$c/= :: ClusterOrchestratorEksConfigProperty
-> ClusterOrchestratorEksConfigProperty -> Bool
/= :: ClusterOrchestratorEksConfigProperty
-> ClusterOrchestratorEksConfigProperty -> Bool
Prelude.Eq, Int -> ClusterOrchestratorEksConfigProperty -> ShowS
[ClusterOrchestratorEksConfigProperty] -> ShowS
ClusterOrchestratorEksConfigProperty -> String
(Int -> ClusterOrchestratorEksConfigProperty -> ShowS)
-> (ClusterOrchestratorEksConfigProperty -> String)
-> ([ClusterOrchestratorEksConfigProperty] -> ShowS)
-> Show ClusterOrchestratorEksConfigProperty
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ClusterOrchestratorEksConfigProperty -> ShowS
showsPrec :: Int -> ClusterOrchestratorEksConfigProperty -> ShowS
$cshow :: ClusterOrchestratorEksConfigProperty -> String
show :: ClusterOrchestratorEksConfigProperty -> String
$cshowList :: [ClusterOrchestratorEksConfigProperty] -> ShowS
showList :: [ClusterOrchestratorEksConfigProperty] -> ShowS
Prelude.Show)
mkClusterOrchestratorEksConfigProperty ::
  Value Prelude.Text -> ClusterOrchestratorEksConfigProperty
mkClusterOrchestratorEksConfigProperty :: Value Text -> ClusterOrchestratorEksConfigProperty
mkClusterOrchestratorEksConfigProperty Value Text
clusterArn
  = ClusterOrchestratorEksConfigProperty
      {haddock_workaround_ :: ()
haddock_workaround_ = (), clusterArn :: Value Text
clusterArn = Value Text
clusterArn}
instance ToResourceProperties ClusterOrchestratorEksConfigProperty where
  toResourceProperties :: ClusterOrchestratorEksConfigProperty -> ResourceProperties
toResourceProperties ClusterOrchestratorEksConfigProperty {()
Value Text
haddock_workaround_ :: ClusterOrchestratorEksConfigProperty -> ()
clusterArn :: ClusterOrchestratorEksConfigProperty -> Value Text
haddock_workaround_ :: ()
clusterArn :: Value Text
..}
    = ResourceProperties
        {awsType :: Text
awsType = Text
"AWS::SageMaker::Cluster.ClusterOrchestratorEksConfig",
         supportsTags :: Bool
supportsTags = Bool
Prelude.False,
         properties :: Object
properties = [Key
"ClusterArn" 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
clusterArn]}
instance JSON.ToJSON ClusterOrchestratorEksConfigProperty where
  toJSON :: ClusterOrchestratorEksConfigProperty -> Value
toJSON ClusterOrchestratorEksConfigProperty {()
Value Text
haddock_workaround_ :: ClusterOrchestratorEksConfigProperty -> ()
clusterArn :: ClusterOrchestratorEksConfigProperty -> Value Text
haddock_workaround_ :: ()
clusterArn :: Value Text
..}
    = [(Key, Value)] -> Value
JSON.object [Key
"ClusterArn" 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
clusterArn]
instance Property "ClusterArn" ClusterOrchestratorEksConfigProperty where
  type PropertyType "ClusterArn" ClusterOrchestratorEksConfigProperty = Value Prelude.Text
  set :: PropertyType "ClusterArn" ClusterOrchestratorEksConfigProperty
-> ClusterOrchestratorEksConfigProperty
-> ClusterOrchestratorEksConfigProperty
set PropertyType "ClusterArn" ClusterOrchestratorEksConfigProperty
newValue ClusterOrchestratorEksConfigProperty {()
Value Text
haddock_workaround_ :: ClusterOrchestratorEksConfigProperty -> ()
clusterArn :: ClusterOrchestratorEksConfigProperty -> Value Text
haddock_workaround_ :: ()
clusterArn :: Value Text
..}
    = ClusterOrchestratorEksConfigProperty {clusterArn :: Value Text
clusterArn = PropertyType "ClusterArn" ClusterOrchestratorEksConfigProperty
Value Text
newValue, ()
haddock_workaround_ :: ()
haddock_workaround_ :: ()
..}