module Stratosphere.SageMaker.ProcessingJob.FeatureStoreOutputProperty (
FeatureStoreOutputProperty(..), mkFeatureStoreOutputProperty
) where
import qualified Data.Aeson as JSON
import qualified Stratosphere.Prelude as Prelude
import Stratosphere.Property
import Stratosphere.ResourceProperties
import Stratosphere.Value
data FeatureStoreOutputProperty
=
FeatureStoreOutputProperty {FeatureStoreOutputProperty -> ()
haddock_workaround_ :: (),
FeatureStoreOutputProperty -> Value Text
featureGroupName :: (Value Prelude.Text)}
deriving stock (FeatureStoreOutputProperty -> FeatureStoreOutputProperty -> Bool
(FeatureStoreOutputProperty -> FeatureStoreOutputProperty -> Bool)
-> (FeatureStoreOutputProperty
-> FeatureStoreOutputProperty -> Bool)
-> Eq FeatureStoreOutputProperty
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: FeatureStoreOutputProperty -> FeatureStoreOutputProperty -> Bool
== :: FeatureStoreOutputProperty -> FeatureStoreOutputProperty -> Bool
$c/= :: FeatureStoreOutputProperty -> FeatureStoreOutputProperty -> Bool
/= :: FeatureStoreOutputProperty -> FeatureStoreOutputProperty -> Bool
Prelude.Eq, Int -> FeatureStoreOutputProperty -> ShowS
[FeatureStoreOutputProperty] -> ShowS
FeatureStoreOutputProperty -> String
(Int -> FeatureStoreOutputProperty -> ShowS)
-> (FeatureStoreOutputProperty -> String)
-> ([FeatureStoreOutputProperty] -> ShowS)
-> Show FeatureStoreOutputProperty
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> FeatureStoreOutputProperty -> ShowS
showsPrec :: Int -> FeatureStoreOutputProperty -> ShowS
$cshow :: FeatureStoreOutputProperty -> String
show :: FeatureStoreOutputProperty -> String
$cshowList :: [FeatureStoreOutputProperty] -> ShowS
showList :: [FeatureStoreOutputProperty] -> ShowS
Prelude.Show)
mkFeatureStoreOutputProperty ::
Value Prelude.Text -> FeatureStoreOutputProperty
mkFeatureStoreOutputProperty :: Value Text -> FeatureStoreOutputProperty
mkFeatureStoreOutputProperty Value Text
featureGroupName
= FeatureStoreOutputProperty
{haddock_workaround_ :: ()
haddock_workaround_ = (), featureGroupName :: Value Text
featureGroupName = Value Text
featureGroupName}
instance ToResourceProperties FeatureStoreOutputProperty where
toResourceProperties :: FeatureStoreOutputProperty -> ResourceProperties
toResourceProperties FeatureStoreOutputProperty {()
Value Text
haddock_workaround_ :: FeatureStoreOutputProperty -> ()
featureGroupName :: FeatureStoreOutputProperty -> Value Text
haddock_workaround_ :: ()
featureGroupName :: Value Text
..}
= ResourceProperties
{awsType :: Text
awsType = Text
"AWS::SageMaker::ProcessingJob.FeatureStoreOutput",
supportsTags :: Bool
supportsTags = Bool
Prelude.False,
properties :: Object
properties = [Key
"FeatureGroupName" 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
featureGroupName]}
instance JSON.ToJSON FeatureStoreOutputProperty where
toJSON :: FeatureStoreOutputProperty -> Value
toJSON FeatureStoreOutputProperty {()
Value Text
haddock_workaround_ :: FeatureStoreOutputProperty -> ()
featureGroupName :: FeatureStoreOutputProperty -> Value Text
haddock_workaround_ :: ()
featureGroupName :: Value Text
..}
= [(Key, Value)] -> Value
JSON.object [Key
"FeatureGroupName" 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
featureGroupName]
instance Property "FeatureGroupName" FeatureStoreOutputProperty where
type PropertyType "FeatureGroupName" FeatureStoreOutputProperty = Value Prelude.Text
set :: PropertyType "FeatureGroupName" FeatureStoreOutputProperty
-> FeatureStoreOutputProperty -> FeatureStoreOutputProperty
set PropertyType "FeatureGroupName" FeatureStoreOutputProperty
newValue FeatureStoreOutputProperty {()
Value Text
haddock_workaround_ :: FeatureStoreOutputProperty -> ()
featureGroupName :: FeatureStoreOutputProperty -> Value Text
haddock_workaround_ :: ()
featureGroupName :: Value Text
..}
= FeatureStoreOutputProperty {featureGroupName :: Value Text
featureGroupName = PropertyType "FeatureGroupName" FeatureStoreOutputProperty
Value Text
newValue, ()
haddock_workaround_ :: ()
haddock_workaround_ :: ()
..}