module Stratosphere.AmplifyUIBuilder.Component.ComponentDataConfigurationProperty (
module Exports, ComponentDataConfigurationProperty(..),
mkComponentDataConfigurationProperty
) where
import qualified Data.Aeson as JSON
import qualified Stratosphere.Prelude as Prelude
import Stratosphere.Property
import {-# SOURCE #-} Stratosphere.AmplifyUIBuilder.Component.PredicateProperty as Exports
import {-# SOURCE #-} Stratosphere.AmplifyUIBuilder.Component.SortPropertyProperty as Exports
import Stratosphere.ResourceProperties
import Stratosphere.Value
data ComponentDataConfigurationProperty
=
ComponentDataConfigurationProperty {ComponentDataConfigurationProperty -> ()
haddock_workaround_ :: (),
ComponentDataConfigurationProperty -> Maybe (ValueList Text)
identifiers :: (Prelude.Maybe (ValueList Prelude.Text)),
ComponentDataConfigurationProperty -> Value Text
model :: (Value Prelude.Text),
ComponentDataConfigurationProperty -> Maybe PredicateProperty
predicate :: (Prelude.Maybe PredicateProperty),
ComponentDataConfigurationProperty -> Maybe [SortPropertyProperty]
sort :: (Prelude.Maybe [SortPropertyProperty])}
deriving stock (ComponentDataConfigurationProperty
-> ComponentDataConfigurationProperty -> Bool
(ComponentDataConfigurationProperty
-> ComponentDataConfigurationProperty -> Bool)
-> (ComponentDataConfigurationProperty
-> ComponentDataConfigurationProperty -> Bool)
-> Eq ComponentDataConfigurationProperty
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ComponentDataConfigurationProperty
-> ComponentDataConfigurationProperty -> Bool
== :: ComponentDataConfigurationProperty
-> ComponentDataConfigurationProperty -> Bool
$c/= :: ComponentDataConfigurationProperty
-> ComponentDataConfigurationProperty -> Bool
/= :: ComponentDataConfigurationProperty
-> ComponentDataConfigurationProperty -> Bool
Prelude.Eq, Int -> ComponentDataConfigurationProperty -> ShowS
[ComponentDataConfigurationProperty] -> ShowS
ComponentDataConfigurationProperty -> String
(Int -> ComponentDataConfigurationProperty -> ShowS)
-> (ComponentDataConfigurationProperty -> String)
-> ([ComponentDataConfigurationProperty] -> ShowS)
-> Show ComponentDataConfigurationProperty
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ComponentDataConfigurationProperty -> ShowS
showsPrec :: Int -> ComponentDataConfigurationProperty -> ShowS
$cshow :: ComponentDataConfigurationProperty -> String
show :: ComponentDataConfigurationProperty -> String
$cshowList :: [ComponentDataConfigurationProperty] -> ShowS
showList :: [ComponentDataConfigurationProperty] -> ShowS
Prelude.Show)
mkComponentDataConfigurationProperty ::
Value Prelude.Text -> ComponentDataConfigurationProperty
mkComponentDataConfigurationProperty :: Value Text -> ComponentDataConfigurationProperty
mkComponentDataConfigurationProperty Value Text
model
= ComponentDataConfigurationProperty
{haddock_workaround_ :: ()
haddock_workaround_ = (), model :: Value Text
model = Value Text
model,
identifiers :: Maybe (ValueList Text)
identifiers = Maybe (ValueList Text)
forall a. Maybe a
Prelude.Nothing, predicate :: Maybe PredicateProperty
predicate = Maybe PredicateProperty
forall a. Maybe a
Prelude.Nothing,
sort :: Maybe [SortPropertyProperty]
sort = Maybe [SortPropertyProperty]
forall a. Maybe a
Prelude.Nothing}
instance ToResourceProperties ComponentDataConfigurationProperty where
toResourceProperties :: ComponentDataConfigurationProperty -> ResourceProperties
toResourceProperties ComponentDataConfigurationProperty {Maybe [SortPropertyProperty]
Maybe (ValueList Text)
Maybe PredicateProperty
()
Value Text
haddock_workaround_ :: ComponentDataConfigurationProperty -> ()
identifiers :: ComponentDataConfigurationProperty -> Maybe (ValueList Text)
model :: ComponentDataConfigurationProperty -> Value Text
predicate :: ComponentDataConfigurationProperty -> Maybe PredicateProperty
sort :: ComponentDataConfigurationProperty -> Maybe [SortPropertyProperty]
haddock_workaround_ :: ()
identifiers :: Maybe (ValueList Text)
model :: Value Text
predicate :: Maybe PredicateProperty
sort :: Maybe [SortPropertyProperty]
..}
= ResourceProperties
{awsType :: Text
awsType = Text
"AWS::AmplifyUIBuilder::Component.ComponentDataConfiguration",
supportsTags :: Bool
supportsTags = Bool
Prelude.False,
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
"Model" 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
model]
([Maybe (Key, Value)] -> [(Key, Value)]
forall a. [Maybe a] -> [a]
Prelude.catMaybes
[Key -> ValueList 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
"Identifiers" (ValueList Text -> (Key, Value))
-> Maybe (ValueList Text) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (ValueList Text)
identifiers,
Key -> PredicateProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"Predicate" (PredicateProperty -> (Key, Value))
-> Maybe PredicateProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe PredicateProperty
predicate,
Key -> [SortPropertyProperty] -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"Sort" ([SortPropertyProperty] -> (Key, Value))
-> Maybe [SortPropertyProperty] -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [SortPropertyProperty]
sort]))}
instance JSON.ToJSON ComponentDataConfigurationProperty where
toJSON :: ComponentDataConfigurationProperty -> Value
toJSON ComponentDataConfigurationProperty {Maybe [SortPropertyProperty]
Maybe (ValueList Text)
Maybe PredicateProperty
()
Value Text
haddock_workaround_ :: ComponentDataConfigurationProperty -> ()
identifiers :: ComponentDataConfigurationProperty -> Maybe (ValueList Text)
model :: ComponentDataConfigurationProperty -> Value Text
predicate :: ComponentDataConfigurationProperty -> Maybe PredicateProperty
sort :: ComponentDataConfigurationProperty -> Maybe [SortPropertyProperty]
haddock_workaround_ :: ()
identifiers :: Maybe (ValueList Text)
model :: Value Text
predicate :: Maybe PredicateProperty
sort :: Maybe [SortPropertyProperty]
..}
= [(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
"Model" 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
model]
([Maybe (Key, Value)] -> [(Key, Value)]
forall a. [Maybe a] -> [a]
Prelude.catMaybes
[Key -> ValueList 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
"Identifiers" (ValueList Text -> (Key, Value))
-> Maybe (ValueList Text) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (ValueList Text)
identifiers,
Key -> PredicateProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"Predicate" (PredicateProperty -> (Key, Value))
-> Maybe PredicateProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe PredicateProperty
predicate,
Key -> [SortPropertyProperty] -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"Sort" ([SortPropertyProperty] -> (Key, Value))
-> Maybe [SortPropertyProperty] -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [SortPropertyProperty]
sort])))
instance Property "Identifiers" ComponentDataConfigurationProperty where
type PropertyType "Identifiers" ComponentDataConfigurationProperty = ValueList Prelude.Text
set :: PropertyType "Identifiers" ComponentDataConfigurationProperty
-> ComponentDataConfigurationProperty
-> ComponentDataConfigurationProperty
set PropertyType "Identifiers" ComponentDataConfigurationProperty
newValue ComponentDataConfigurationProperty {Maybe [SortPropertyProperty]
Maybe (ValueList Text)
Maybe PredicateProperty
()
Value Text
haddock_workaround_ :: ComponentDataConfigurationProperty -> ()
identifiers :: ComponentDataConfigurationProperty -> Maybe (ValueList Text)
model :: ComponentDataConfigurationProperty -> Value Text
predicate :: ComponentDataConfigurationProperty -> Maybe PredicateProperty
sort :: ComponentDataConfigurationProperty -> Maybe [SortPropertyProperty]
haddock_workaround_ :: ()
identifiers :: Maybe (ValueList Text)
model :: Value Text
predicate :: Maybe PredicateProperty
sort :: Maybe [SortPropertyProperty]
..}
= ComponentDataConfigurationProperty
{identifiers :: Maybe (ValueList Text)
identifiers = ValueList Text -> Maybe (ValueList Text)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "Identifiers" ComponentDataConfigurationProperty
ValueList Text
newValue, Maybe [SortPropertyProperty]
Maybe PredicateProperty
()
Value Text
haddock_workaround_ :: ()
model :: Value Text
predicate :: Maybe PredicateProperty
sort :: Maybe [SortPropertyProperty]
haddock_workaround_ :: ()
model :: Value Text
predicate :: Maybe PredicateProperty
sort :: Maybe [SortPropertyProperty]
..}
instance Property "Model" ComponentDataConfigurationProperty where
type PropertyType "Model" ComponentDataConfigurationProperty = Value Prelude.Text
set :: PropertyType "Model" ComponentDataConfigurationProperty
-> ComponentDataConfigurationProperty
-> ComponentDataConfigurationProperty
set PropertyType "Model" ComponentDataConfigurationProperty
newValue ComponentDataConfigurationProperty {Maybe [SortPropertyProperty]
Maybe (ValueList Text)
Maybe PredicateProperty
()
Value Text
haddock_workaround_ :: ComponentDataConfigurationProperty -> ()
identifiers :: ComponentDataConfigurationProperty -> Maybe (ValueList Text)
model :: ComponentDataConfigurationProperty -> Value Text
predicate :: ComponentDataConfigurationProperty -> Maybe PredicateProperty
sort :: ComponentDataConfigurationProperty -> Maybe [SortPropertyProperty]
haddock_workaround_ :: ()
identifiers :: Maybe (ValueList Text)
model :: Value Text
predicate :: Maybe PredicateProperty
sort :: Maybe [SortPropertyProperty]
..}
= ComponentDataConfigurationProperty {model :: Value Text
model = PropertyType "Model" ComponentDataConfigurationProperty
Value Text
newValue, Maybe [SortPropertyProperty]
Maybe (ValueList Text)
Maybe PredicateProperty
()
haddock_workaround_ :: ()
identifiers :: Maybe (ValueList Text)
predicate :: Maybe PredicateProperty
sort :: Maybe [SortPropertyProperty]
haddock_workaround_ :: ()
identifiers :: Maybe (ValueList Text)
predicate :: Maybe PredicateProperty
sort :: Maybe [SortPropertyProperty]
..}
instance Property "Predicate" ComponentDataConfigurationProperty where
type PropertyType "Predicate" ComponentDataConfigurationProperty = PredicateProperty
set :: PropertyType "Predicate" ComponentDataConfigurationProperty
-> ComponentDataConfigurationProperty
-> ComponentDataConfigurationProperty
set PropertyType "Predicate" ComponentDataConfigurationProperty
newValue ComponentDataConfigurationProperty {Maybe [SortPropertyProperty]
Maybe (ValueList Text)
Maybe PredicateProperty
()
Value Text
haddock_workaround_ :: ComponentDataConfigurationProperty -> ()
identifiers :: ComponentDataConfigurationProperty -> Maybe (ValueList Text)
model :: ComponentDataConfigurationProperty -> Value Text
predicate :: ComponentDataConfigurationProperty -> Maybe PredicateProperty
sort :: ComponentDataConfigurationProperty -> Maybe [SortPropertyProperty]
haddock_workaround_ :: ()
identifiers :: Maybe (ValueList Text)
model :: Value Text
predicate :: Maybe PredicateProperty
sort :: Maybe [SortPropertyProperty]
..}
= ComponentDataConfigurationProperty
{predicate :: Maybe PredicateProperty
predicate = PredicateProperty -> Maybe PredicateProperty
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "Predicate" ComponentDataConfigurationProperty
PredicateProperty
newValue, Maybe [SortPropertyProperty]
Maybe (ValueList Text)
()
Value Text
haddock_workaround_ :: ()
identifiers :: Maybe (ValueList Text)
model :: Value Text
sort :: Maybe [SortPropertyProperty]
haddock_workaround_ :: ()
identifiers :: Maybe (ValueList Text)
model :: Value Text
sort :: Maybe [SortPropertyProperty]
..}
instance Property "Sort" ComponentDataConfigurationProperty where
type PropertyType "Sort" ComponentDataConfigurationProperty = [SortPropertyProperty]
set :: PropertyType "Sort" ComponentDataConfigurationProperty
-> ComponentDataConfigurationProperty
-> ComponentDataConfigurationProperty
set PropertyType "Sort" ComponentDataConfigurationProperty
newValue ComponentDataConfigurationProperty {Maybe [SortPropertyProperty]
Maybe (ValueList Text)
Maybe PredicateProperty
()
Value Text
haddock_workaround_ :: ComponentDataConfigurationProperty -> ()
identifiers :: ComponentDataConfigurationProperty -> Maybe (ValueList Text)
model :: ComponentDataConfigurationProperty -> Value Text
predicate :: ComponentDataConfigurationProperty -> Maybe PredicateProperty
sort :: ComponentDataConfigurationProperty -> Maybe [SortPropertyProperty]
haddock_workaround_ :: ()
identifiers :: Maybe (ValueList Text)
model :: Value Text
predicate :: Maybe PredicateProperty
sort :: Maybe [SortPropertyProperty]
..}
= ComponentDataConfigurationProperty
{sort :: Maybe [SortPropertyProperty]
sort = [SortPropertyProperty] -> Maybe [SortPropertyProperty]
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure [SortPropertyProperty]
PropertyType "Sort" ComponentDataConfigurationProperty
newValue, Maybe (ValueList Text)
Maybe PredicateProperty
()
Value Text
haddock_workaround_ :: ()
identifiers :: Maybe (ValueList Text)
model :: Value Text
predicate :: Maybe PredicateProperty
haddock_workaround_ :: ()
identifiers :: Maybe (ValueList Text)
model :: Value Text
predicate :: Maybe PredicateProperty
..}