module Stratosphere.SageMaker.ModelCard (
module Exports, ModelCard(..), mkModelCard
) where
import qualified Data.Aeson as JSON
import qualified Stratosphere.Prelude as Prelude
import Stratosphere.Property
import {-# SOURCE #-} Stratosphere.SageMaker.ModelCard.ContentProperty as Exports
import {-# SOURCE #-} Stratosphere.SageMaker.ModelCard.SecurityConfigProperty as Exports
import {-# SOURCE #-} Stratosphere.SageMaker.ModelCard.UserContextProperty as Exports
import Stratosphere.ResourceProperties
import Stratosphere.Tag
import Stratosphere.Value
data ModelCard
=
ModelCard {ModelCard -> ()
haddock_workaround_ :: (),
ModelCard -> ContentProperty
content :: ContentProperty,
ModelCard -> Maybe UserContextProperty
createdBy :: (Prelude.Maybe UserContextProperty),
ModelCard -> Maybe UserContextProperty
lastModifiedBy :: (Prelude.Maybe UserContextProperty),
ModelCard -> Value Text
modelCardName :: (Value Prelude.Text),
ModelCard -> Value Text
modelCardStatus :: (Value Prelude.Text),
ModelCard -> Maybe SecurityConfigProperty
securityConfig :: (Prelude.Maybe SecurityConfigProperty),
ModelCard -> Maybe [Tag]
tags :: (Prelude.Maybe [Tag])}
deriving stock (ModelCard -> ModelCard -> Bool
(ModelCard -> ModelCard -> Bool)
-> (ModelCard -> ModelCard -> Bool) -> Eq ModelCard
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ModelCard -> ModelCard -> Bool
== :: ModelCard -> ModelCard -> Bool
$c/= :: ModelCard -> ModelCard -> Bool
/= :: ModelCard -> ModelCard -> Bool
Prelude.Eq, Int -> ModelCard -> ShowS
[ModelCard] -> ShowS
ModelCard -> String
(Int -> ModelCard -> ShowS)
-> (ModelCard -> String)
-> ([ModelCard] -> ShowS)
-> Show ModelCard
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ModelCard -> ShowS
showsPrec :: Int -> ModelCard -> ShowS
$cshow :: ModelCard -> String
show :: ModelCard -> String
$cshowList :: [ModelCard] -> ShowS
showList :: [ModelCard] -> ShowS
Prelude.Show)
mkModelCard ::
ContentProperty
-> Value Prelude.Text -> Value Prelude.Text -> ModelCard
mkModelCard :: ContentProperty -> Value Text -> Value Text -> ModelCard
mkModelCard ContentProperty
content Value Text
modelCardName Value Text
modelCardStatus
= ModelCard
{haddock_workaround_ :: ()
haddock_workaround_ = (), content :: ContentProperty
content = ContentProperty
content,
modelCardName :: Value Text
modelCardName = Value Text
modelCardName, modelCardStatus :: Value Text
modelCardStatus = Value Text
modelCardStatus,
createdBy :: Maybe UserContextProperty
createdBy = Maybe UserContextProperty
forall a. Maybe a
Prelude.Nothing, lastModifiedBy :: Maybe UserContextProperty
lastModifiedBy = Maybe UserContextProperty
forall a. Maybe a
Prelude.Nothing,
securityConfig :: Maybe SecurityConfigProperty
securityConfig = Maybe SecurityConfigProperty
forall a. Maybe a
Prelude.Nothing, tags :: Maybe [Tag]
tags = Maybe [Tag]
forall a. Maybe a
Prelude.Nothing}
instance ToResourceProperties ModelCard where
toResourceProperties :: ModelCard -> ResourceProperties
toResourceProperties ModelCard {Maybe [Tag]
Maybe SecurityConfigProperty
Maybe UserContextProperty
()
Value Text
ContentProperty
haddock_workaround_ :: ModelCard -> ()
content :: ModelCard -> ContentProperty
createdBy :: ModelCard -> Maybe UserContextProperty
lastModifiedBy :: ModelCard -> Maybe UserContextProperty
modelCardName :: ModelCard -> Value Text
modelCardStatus :: ModelCard -> Value Text
securityConfig :: ModelCard -> Maybe SecurityConfigProperty
tags :: ModelCard -> Maybe [Tag]
haddock_workaround_ :: ()
content :: ContentProperty
createdBy :: Maybe UserContextProperty
lastModifiedBy :: Maybe UserContextProperty
modelCardName :: Value Text
modelCardStatus :: Value Text
securityConfig :: Maybe SecurityConfigProperty
tags :: Maybe [Tag]
..}
= ResourceProperties
{awsType :: Text
awsType = Text
"AWS::SageMaker::ModelCard",
supportsTags :: Bool
supportsTags = Bool
Prelude.True,
properties :: Object
properties = [Item Object] -> Object
forall l. IsList l => [Item l] -> l
Prelude.fromList
([(Key, Value)] -> [(Key, Value)] -> [(Key, Value)]
forall a. Semigroup a => a -> a -> a
(Prelude.<>)
[Key
"Content" Key -> ContentProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
JSON..= ContentProperty
content, Key
"ModelCardName" 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
modelCardName,
Key
"ModelCardStatus" 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
modelCardStatus]
([Maybe (Key, Value)] -> [(Key, Value)]
forall a. [Maybe a] -> [a]
Prelude.catMaybes
[Key -> UserContextProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"CreatedBy" (UserContextProperty -> (Key, Value))
-> Maybe UserContextProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe UserContextProperty
createdBy,
Key -> UserContextProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"LastModifiedBy" (UserContextProperty -> (Key, Value))
-> Maybe UserContextProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe UserContextProperty
lastModifiedBy,
Key -> SecurityConfigProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"SecurityConfig" (SecurityConfigProperty -> (Key, Value))
-> Maybe SecurityConfigProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe SecurityConfigProperty
securityConfig,
Key -> [Tag] -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"Tags" ([Tag] -> (Key, Value)) -> Maybe [Tag] -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [Tag]
tags]))}
instance JSON.ToJSON ModelCard where
toJSON :: ModelCard -> Value
toJSON ModelCard {Maybe [Tag]
Maybe SecurityConfigProperty
Maybe UserContextProperty
()
Value Text
ContentProperty
haddock_workaround_ :: ModelCard -> ()
content :: ModelCard -> ContentProperty
createdBy :: ModelCard -> Maybe UserContextProperty
lastModifiedBy :: ModelCard -> Maybe UserContextProperty
modelCardName :: ModelCard -> Value Text
modelCardStatus :: ModelCard -> Value Text
securityConfig :: ModelCard -> Maybe SecurityConfigProperty
tags :: ModelCard -> Maybe [Tag]
haddock_workaround_ :: ()
content :: ContentProperty
createdBy :: Maybe UserContextProperty
lastModifiedBy :: Maybe UserContextProperty
modelCardName :: Value Text
modelCardStatus :: Value Text
securityConfig :: Maybe SecurityConfigProperty
tags :: Maybe [Tag]
..}
= [(Key, Value)] -> Value
JSON.object
([Item [(Key, Value)]] -> [(Key, Value)]
forall l. IsList l => [Item l] -> l
Prelude.fromList
([(Key, Value)] -> [(Key, Value)] -> [(Key, Value)]
forall a. Semigroup a => a -> a -> a
(Prelude.<>)
[Key
"Content" Key -> ContentProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
JSON..= ContentProperty
content, Key
"ModelCardName" 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
modelCardName,
Key
"ModelCardStatus" 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
modelCardStatus]
([Maybe (Key, Value)] -> [(Key, Value)]
forall a. [Maybe a] -> [a]
Prelude.catMaybes
[Key -> UserContextProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"CreatedBy" (UserContextProperty -> (Key, Value))
-> Maybe UserContextProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe UserContextProperty
createdBy,
Key -> UserContextProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"LastModifiedBy" (UserContextProperty -> (Key, Value))
-> Maybe UserContextProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe UserContextProperty
lastModifiedBy,
Key -> SecurityConfigProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"SecurityConfig" (SecurityConfigProperty -> (Key, Value))
-> Maybe SecurityConfigProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe SecurityConfigProperty
securityConfig,
Key -> [Tag] -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"Tags" ([Tag] -> (Key, Value)) -> Maybe [Tag] -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [Tag]
tags])))
instance Property "Content" ModelCard where
type PropertyType "Content" ModelCard = ContentProperty
set :: PropertyType "Content" ModelCard -> ModelCard -> ModelCard
set PropertyType "Content" ModelCard
newValue ModelCard {Maybe [Tag]
Maybe SecurityConfigProperty
Maybe UserContextProperty
()
Value Text
ContentProperty
haddock_workaround_ :: ModelCard -> ()
content :: ModelCard -> ContentProperty
createdBy :: ModelCard -> Maybe UserContextProperty
lastModifiedBy :: ModelCard -> Maybe UserContextProperty
modelCardName :: ModelCard -> Value Text
modelCardStatus :: ModelCard -> Value Text
securityConfig :: ModelCard -> Maybe SecurityConfigProperty
tags :: ModelCard -> Maybe [Tag]
haddock_workaround_ :: ()
content :: ContentProperty
createdBy :: Maybe UserContextProperty
lastModifiedBy :: Maybe UserContextProperty
modelCardName :: Value Text
modelCardStatus :: Value Text
securityConfig :: Maybe SecurityConfigProperty
tags :: Maybe [Tag]
..} = ModelCard {content :: ContentProperty
content = PropertyType "Content" ModelCard
ContentProperty
newValue, Maybe [Tag]
Maybe SecurityConfigProperty
Maybe UserContextProperty
()
Value Text
haddock_workaround_ :: ()
createdBy :: Maybe UserContextProperty
lastModifiedBy :: Maybe UserContextProperty
modelCardName :: Value Text
modelCardStatus :: Value Text
securityConfig :: Maybe SecurityConfigProperty
tags :: Maybe [Tag]
haddock_workaround_ :: ()
createdBy :: Maybe UserContextProperty
lastModifiedBy :: Maybe UserContextProperty
modelCardName :: Value Text
modelCardStatus :: Value Text
securityConfig :: Maybe SecurityConfigProperty
tags :: Maybe [Tag]
..}
instance Property "CreatedBy" ModelCard where
type PropertyType "CreatedBy" ModelCard = UserContextProperty
set :: PropertyType "CreatedBy" ModelCard -> ModelCard -> ModelCard
set PropertyType "CreatedBy" ModelCard
newValue ModelCard {Maybe [Tag]
Maybe SecurityConfigProperty
Maybe UserContextProperty
()
Value Text
ContentProperty
haddock_workaround_ :: ModelCard -> ()
content :: ModelCard -> ContentProperty
createdBy :: ModelCard -> Maybe UserContextProperty
lastModifiedBy :: ModelCard -> Maybe UserContextProperty
modelCardName :: ModelCard -> Value Text
modelCardStatus :: ModelCard -> Value Text
securityConfig :: ModelCard -> Maybe SecurityConfigProperty
tags :: ModelCard -> Maybe [Tag]
haddock_workaround_ :: ()
content :: ContentProperty
createdBy :: Maybe UserContextProperty
lastModifiedBy :: Maybe UserContextProperty
modelCardName :: Value Text
modelCardStatus :: Value Text
securityConfig :: Maybe SecurityConfigProperty
tags :: Maybe [Tag]
..}
= ModelCard {createdBy :: Maybe UserContextProperty
createdBy = UserContextProperty -> Maybe UserContextProperty
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "CreatedBy" ModelCard
UserContextProperty
newValue, Maybe [Tag]
Maybe SecurityConfigProperty
Maybe UserContextProperty
()
Value Text
ContentProperty
haddock_workaround_ :: ()
content :: ContentProperty
lastModifiedBy :: Maybe UserContextProperty
modelCardName :: Value Text
modelCardStatus :: Value Text
securityConfig :: Maybe SecurityConfigProperty
tags :: Maybe [Tag]
haddock_workaround_ :: ()
content :: ContentProperty
lastModifiedBy :: Maybe UserContextProperty
modelCardName :: Value Text
modelCardStatus :: Value Text
securityConfig :: Maybe SecurityConfigProperty
tags :: Maybe [Tag]
..}
instance Property "LastModifiedBy" ModelCard where
type PropertyType "LastModifiedBy" ModelCard = UserContextProperty
set :: PropertyType "LastModifiedBy" ModelCard -> ModelCard -> ModelCard
set PropertyType "LastModifiedBy" ModelCard
newValue ModelCard {Maybe [Tag]
Maybe SecurityConfigProperty
Maybe UserContextProperty
()
Value Text
ContentProperty
haddock_workaround_ :: ModelCard -> ()
content :: ModelCard -> ContentProperty
createdBy :: ModelCard -> Maybe UserContextProperty
lastModifiedBy :: ModelCard -> Maybe UserContextProperty
modelCardName :: ModelCard -> Value Text
modelCardStatus :: ModelCard -> Value Text
securityConfig :: ModelCard -> Maybe SecurityConfigProperty
tags :: ModelCard -> Maybe [Tag]
haddock_workaround_ :: ()
content :: ContentProperty
createdBy :: Maybe UserContextProperty
lastModifiedBy :: Maybe UserContextProperty
modelCardName :: Value Text
modelCardStatus :: Value Text
securityConfig :: Maybe SecurityConfigProperty
tags :: Maybe [Tag]
..}
= ModelCard {lastModifiedBy :: Maybe UserContextProperty
lastModifiedBy = UserContextProperty -> Maybe UserContextProperty
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "LastModifiedBy" ModelCard
UserContextProperty
newValue, Maybe [Tag]
Maybe SecurityConfigProperty
Maybe UserContextProperty
()
Value Text
ContentProperty
haddock_workaround_ :: ()
content :: ContentProperty
createdBy :: Maybe UserContextProperty
modelCardName :: Value Text
modelCardStatus :: Value Text
securityConfig :: Maybe SecurityConfigProperty
tags :: Maybe [Tag]
haddock_workaround_ :: ()
content :: ContentProperty
createdBy :: Maybe UserContextProperty
modelCardName :: Value Text
modelCardStatus :: Value Text
securityConfig :: Maybe SecurityConfigProperty
tags :: Maybe [Tag]
..}
instance Property "ModelCardName" ModelCard where
type PropertyType "ModelCardName" ModelCard = Value Prelude.Text
set :: PropertyType "ModelCardName" ModelCard -> ModelCard -> ModelCard
set PropertyType "ModelCardName" ModelCard
newValue ModelCard {Maybe [Tag]
Maybe SecurityConfigProperty
Maybe UserContextProperty
()
Value Text
ContentProperty
haddock_workaround_ :: ModelCard -> ()
content :: ModelCard -> ContentProperty
createdBy :: ModelCard -> Maybe UserContextProperty
lastModifiedBy :: ModelCard -> Maybe UserContextProperty
modelCardName :: ModelCard -> Value Text
modelCardStatus :: ModelCard -> Value Text
securityConfig :: ModelCard -> Maybe SecurityConfigProperty
tags :: ModelCard -> Maybe [Tag]
haddock_workaround_ :: ()
content :: ContentProperty
createdBy :: Maybe UserContextProperty
lastModifiedBy :: Maybe UserContextProperty
modelCardName :: Value Text
modelCardStatus :: Value Text
securityConfig :: Maybe SecurityConfigProperty
tags :: Maybe [Tag]
..}
= ModelCard {modelCardName :: Value Text
modelCardName = PropertyType "ModelCardName" ModelCard
Value Text
newValue, Maybe [Tag]
Maybe SecurityConfigProperty
Maybe UserContextProperty
()
Value Text
ContentProperty
haddock_workaround_ :: ()
content :: ContentProperty
createdBy :: Maybe UserContextProperty
lastModifiedBy :: Maybe UserContextProperty
modelCardStatus :: Value Text
securityConfig :: Maybe SecurityConfigProperty
tags :: Maybe [Tag]
haddock_workaround_ :: ()
content :: ContentProperty
createdBy :: Maybe UserContextProperty
lastModifiedBy :: Maybe UserContextProperty
modelCardStatus :: Value Text
securityConfig :: Maybe SecurityConfigProperty
tags :: Maybe [Tag]
..}
instance Property "ModelCardStatus" ModelCard where
type PropertyType "ModelCardStatus" ModelCard = Value Prelude.Text
set :: PropertyType "ModelCardStatus" ModelCard -> ModelCard -> ModelCard
set PropertyType "ModelCardStatus" ModelCard
newValue ModelCard {Maybe [Tag]
Maybe SecurityConfigProperty
Maybe UserContextProperty
()
Value Text
ContentProperty
haddock_workaround_ :: ModelCard -> ()
content :: ModelCard -> ContentProperty
createdBy :: ModelCard -> Maybe UserContextProperty
lastModifiedBy :: ModelCard -> Maybe UserContextProperty
modelCardName :: ModelCard -> Value Text
modelCardStatus :: ModelCard -> Value Text
securityConfig :: ModelCard -> Maybe SecurityConfigProperty
tags :: ModelCard -> Maybe [Tag]
haddock_workaround_ :: ()
content :: ContentProperty
createdBy :: Maybe UserContextProperty
lastModifiedBy :: Maybe UserContextProperty
modelCardName :: Value Text
modelCardStatus :: Value Text
securityConfig :: Maybe SecurityConfigProperty
tags :: Maybe [Tag]
..}
= ModelCard {modelCardStatus :: Value Text
modelCardStatus = PropertyType "ModelCardStatus" ModelCard
Value Text
newValue, Maybe [Tag]
Maybe SecurityConfigProperty
Maybe UserContextProperty
()
Value Text
ContentProperty
haddock_workaround_ :: ()
content :: ContentProperty
createdBy :: Maybe UserContextProperty
lastModifiedBy :: Maybe UserContextProperty
modelCardName :: Value Text
securityConfig :: Maybe SecurityConfigProperty
tags :: Maybe [Tag]
haddock_workaround_ :: ()
content :: ContentProperty
createdBy :: Maybe UserContextProperty
lastModifiedBy :: Maybe UserContextProperty
modelCardName :: Value Text
securityConfig :: Maybe SecurityConfigProperty
tags :: Maybe [Tag]
..}
instance Property "SecurityConfig" ModelCard where
type PropertyType "SecurityConfig" ModelCard = SecurityConfigProperty
set :: PropertyType "SecurityConfig" ModelCard -> ModelCard -> ModelCard
set PropertyType "SecurityConfig" ModelCard
newValue ModelCard {Maybe [Tag]
Maybe SecurityConfigProperty
Maybe UserContextProperty
()
Value Text
ContentProperty
haddock_workaround_ :: ModelCard -> ()
content :: ModelCard -> ContentProperty
createdBy :: ModelCard -> Maybe UserContextProperty
lastModifiedBy :: ModelCard -> Maybe UserContextProperty
modelCardName :: ModelCard -> Value Text
modelCardStatus :: ModelCard -> Value Text
securityConfig :: ModelCard -> Maybe SecurityConfigProperty
tags :: ModelCard -> Maybe [Tag]
haddock_workaround_ :: ()
content :: ContentProperty
createdBy :: Maybe UserContextProperty
lastModifiedBy :: Maybe UserContextProperty
modelCardName :: Value Text
modelCardStatus :: Value Text
securityConfig :: Maybe SecurityConfigProperty
tags :: Maybe [Tag]
..}
= ModelCard {securityConfig :: Maybe SecurityConfigProperty
securityConfig = SecurityConfigProperty -> Maybe SecurityConfigProperty
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "SecurityConfig" ModelCard
SecurityConfigProperty
newValue, Maybe [Tag]
Maybe UserContextProperty
()
Value Text
ContentProperty
haddock_workaround_ :: ()
content :: ContentProperty
createdBy :: Maybe UserContextProperty
lastModifiedBy :: Maybe UserContextProperty
modelCardName :: Value Text
modelCardStatus :: Value Text
tags :: Maybe [Tag]
haddock_workaround_ :: ()
content :: ContentProperty
createdBy :: Maybe UserContextProperty
lastModifiedBy :: Maybe UserContextProperty
modelCardName :: Value Text
modelCardStatus :: Value Text
tags :: Maybe [Tag]
..}
instance Property "Tags" ModelCard where
type PropertyType "Tags" ModelCard = [Tag]
set :: PropertyType "Tags" ModelCard -> ModelCard -> ModelCard
set PropertyType "Tags" ModelCard
newValue ModelCard {Maybe [Tag]
Maybe SecurityConfigProperty
Maybe UserContextProperty
()
Value Text
ContentProperty
haddock_workaround_ :: ModelCard -> ()
content :: ModelCard -> ContentProperty
createdBy :: ModelCard -> Maybe UserContextProperty
lastModifiedBy :: ModelCard -> Maybe UserContextProperty
modelCardName :: ModelCard -> Value Text
modelCardStatus :: ModelCard -> Value Text
securityConfig :: ModelCard -> Maybe SecurityConfigProperty
tags :: ModelCard -> Maybe [Tag]
haddock_workaround_ :: ()
content :: ContentProperty
createdBy :: Maybe UserContextProperty
lastModifiedBy :: Maybe UserContextProperty
modelCardName :: Value Text
modelCardStatus :: Value Text
securityConfig :: Maybe SecurityConfigProperty
tags :: Maybe [Tag]
..}
= ModelCard {tags :: Maybe [Tag]
tags = [Tag] -> Maybe [Tag]
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure [Tag]
PropertyType "Tags" ModelCard
newValue, Maybe SecurityConfigProperty
Maybe UserContextProperty
()
Value Text
ContentProperty
haddock_workaround_ :: ()
content :: ContentProperty
createdBy :: Maybe UserContextProperty
lastModifiedBy :: Maybe UserContextProperty
modelCardName :: Value Text
modelCardStatus :: Value Text
securityConfig :: Maybe SecurityConfigProperty
haddock_workaround_ :: ()
content :: ContentProperty
createdBy :: Maybe UserContextProperty
lastModifiedBy :: Maybe UserContextProperty
modelCardName :: Value Text
modelCardStatus :: Value Text
securityConfig :: Maybe SecurityConfigProperty
..}