module Stratosphere.AmplifyUIBuilder.Component.ComponentPropertyProperty (
module Exports, ComponentPropertyProperty(..),
mkComponentPropertyProperty
) where
import qualified Data.Aeson as JSON
import qualified Stratosphere.Prelude as Prelude
import Stratosphere.Property
import {-# SOURCE #-} Stratosphere.AmplifyUIBuilder.Component.ComponentConditionPropertyProperty as Exports
import {-# SOURCE #-} Stratosphere.AmplifyUIBuilder.Component.ComponentPropertyBindingPropertiesProperty as Exports
import {-# SOURCE #-} Stratosphere.AmplifyUIBuilder.Component.FormBindingElementProperty as Exports
import Stratosphere.ResourceProperties
import Stratosphere.Value
data ComponentPropertyProperty
=
ComponentPropertyProperty {ComponentPropertyProperty -> ()
haddock_workaround_ :: (),
ComponentPropertyProperty
-> Maybe ComponentPropertyBindingPropertiesProperty
bindingProperties :: (Prelude.Maybe ComponentPropertyBindingPropertiesProperty),
ComponentPropertyProperty
-> Maybe (Map Text FormBindingElementProperty)
bindings :: (Prelude.Maybe (Prelude.Map Prelude.Text FormBindingElementProperty)),
ComponentPropertyProperty
-> Maybe ComponentPropertyBindingPropertiesProperty
collectionBindingProperties :: (Prelude.Maybe ComponentPropertyBindingPropertiesProperty),
ComponentPropertyProperty -> Maybe (Value Text)
componentName :: (Prelude.Maybe (Value Prelude.Text)),
ComponentPropertyProperty -> Maybe [ComponentPropertyProperty]
concat :: (Prelude.Maybe [ComponentPropertyProperty]),
ComponentPropertyProperty
-> Maybe ComponentConditionPropertyProperty
condition :: (Prelude.Maybe ComponentConditionPropertyProperty),
ComponentPropertyProperty -> Maybe (Value Bool)
configured :: (Prelude.Maybe (Value Prelude.Bool)),
ComponentPropertyProperty -> Maybe (Value Text)
defaultValue :: (Prelude.Maybe (Value Prelude.Text)),
ComponentPropertyProperty -> Maybe (Value Text)
event :: (Prelude.Maybe (Value Prelude.Text)),
ComponentPropertyProperty -> Maybe (Value Text)
importedValue :: (Prelude.Maybe (Value Prelude.Text)),
ComponentPropertyProperty -> Maybe (Value Text)
model :: (Prelude.Maybe (Value Prelude.Text)),
ComponentPropertyProperty -> Maybe (Value Text)
property :: (Prelude.Maybe (Value Prelude.Text)),
ComponentPropertyProperty -> Maybe (Value Text)
type' :: (Prelude.Maybe (Value Prelude.Text)),
ComponentPropertyProperty -> Maybe (Value Text)
userAttribute :: (Prelude.Maybe (Value Prelude.Text)),
ComponentPropertyProperty -> Maybe (Value Text)
value :: (Prelude.Maybe (Value Prelude.Text))}
deriving stock (ComponentPropertyProperty -> ComponentPropertyProperty -> Bool
(ComponentPropertyProperty -> ComponentPropertyProperty -> Bool)
-> (ComponentPropertyProperty -> ComponentPropertyProperty -> Bool)
-> Eq ComponentPropertyProperty
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ComponentPropertyProperty -> ComponentPropertyProperty -> Bool
== :: ComponentPropertyProperty -> ComponentPropertyProperty -> Bool
$c/= :: ComponentPropertyProperty -> ComponentPropertyProperty -> Bool
/= :: ComponentPropertyProperty -> ComponentPropertyProperty -> Bool
Prelude.Eq, Int -> ComponentPropertyProperty -> ShowS
[ComponentPropertyProperty] -> ShowS
ComponentPropertyProperty -> String
(Int -> ComponentPropertyProperty -> ShowS)
-> (ComponentPropertyProperty -> String)
-> ([ComponentPropertyProperty] -> ShowS)
-> Show ComponentPropertyProperty
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ComponentPropertyProperty -> ShowS
showsPrec :: Int -> ComponentPropertyProperty -> ShowS
$cshow :: ComponentPropertyProperty -> String
show :: ComponentPropertyProperty -> String
$cshowList :: [ComponentPropertyProperty] -> ShowS
showList :: [ComponentPropertyProperty] -> ShowS
Prelude.Show)
mkComponentPropertyProperty :: ComponentPropertyProperty
mkComponentPropertyProperty :: ComponentPropertyProperty
mkComponentPropertyProperty
= ComponentPropertyProperty
{haddock_workaround_ :: ()
haddock_workaround_ = (), bindingProperties :: Maybe ComponentPropertyBindingPropertiesProperty
bindingProperties = Maybe ComponentPropertyBindingPropertiesProperty
forall a. Maybe a
Prelude.Nothing,
bindings :: Maybe (Map Text FormBindingElementProperty)
bindings = Maybe (Map Text FormBindingElementProperty)
forall a. Maybe a
Prelude.Nothing,
collectionBindingProperties :: Maybe ComponentPropertyBindingPropertiesProperty
collectionBindingProperties = Maybe ComponentPropertyBindingPropertiesProperty
forall a. Maybe a
Prelude.Nothing,
componentName :: Maybe (Value Text)
componentName = Maybe (Value Text)
forall a. Maybe a
Prelude.Nothing, concat :: Maybe [ComponentPropertyProperty]
concat = Maybe [ComponentPropertyProperty]
forall a. Maybe a
Prelude.Nothing,
condition :: Maybe ComponentConditionPropertyProperty
condition = Maybe ComponentConditionPropertyProperty
forall a. Maybe a
Prelude.Nothing, configured :: Maybe (Value Bool)
configured = Maybe (Value Bool)
forall a. Maybe a
Prelude.Nothing,
defaultValue :: Maybe (Value Text)
defaultValue = Maybe (Value Text)
forall a. Maybe a
Prelude.Nothing, event :: Maybe (Value Text)
event = Maybe (Value Text)
forall a. Maybe a
Prelude.Nothing,
importedValue :: Maybe (Value Text)
importedValue = Maybe (Value Text)
forall a. Maybe a
Prelude.Nothing, model :: Maybe (Value Text)
model = Maybe (Value Text)
forall a. Maybe a
Prelude.Nothing,
property :: Maybe (Value Text)
property = Maybe (Value Text)
forall a. Maybe a
Prelude.Nothing, type' :: Maybe (Value Text)
type' = Maybe (Value Text)
forall a. Maybe a
Prelude.Nothing,
userAttribute :: Maybe (Value Text)
userAttribute = Maybe (Value Text)
forall a. Maybe a
Prelude.Nothing, value :: Maybe (Value Text)
value = Maybe (Value Text)
forall a. Maybe a
Prelude.Nothing}
instance ToResourceProperties ComponentPropertyProperty where
toResourceProperties :: ComponentPropertyProperty -> ResourceProperties
toResourceProperties ComponentPropertyProperty {Maybe [ComponentPropertyProperty]
Maybe (Map Text FormBindingElementProperty)
Maybe (Value Bool)
Maybe (Value Text)
Maybe ComponentPropertyBindingPropertiesProperty
Maybe ComponentConditionPropertyProperty
()
haddock_workaround_ :: ComponentPropertyProperty -> ()
bindingProperties :: ComponentPropertyProperty
-> Maybe ComponentPropertyBindingPropertiesProperty
bindings :: ComponentPropertyProperty
-> Maybe (Map Text FormBindingElementProperty)
collectionBindingProperties :: ComponentPropertyProperty
-> Maybe ComponentPropertyBindingPropertiesProperty
componentName :: ComponentPropertyProperty -> Maybe (Value Text)
concat :: ComponentPropertyProperty -> Maybe [ComponentPropertyProperty]
condition :: ComponentPropertyProperty
-> Maybe ComponentConditionPropertyProperty
configured :: ComponentPropertyProperty -> Maybe (Value Bool)
defaultValue :: ComponentPropertyProperty -> Maybe (Value Text)
event :: ComponentPropertyProperty -> Maybe (Value Text)
importedValue :: ComponentPropertyProperty -> Maybe (Value Text)
model :: ComponentPropertyProperty -> Maybe (Value Text)
property :: ComponentPropertyProperty -> Maybe (Value Text)
type' :: ComponentPropertyProperty -> Maybe (Value Text)
userAttribute :: ComponentPropertyProperty -> Maybe (Value Text)
value :: ComponentPropertyProperty -> Maybe (Value Text)
haddock_workaround_ :: ()
bindingProperties :: Maybe ComponentPropertyBindingPropertiesProperty
bindings :: Maybe (Map Text FormBindingElementProperty)
collectionBindingProperties :: Maybe ComponentPropertyBindingPropertiesProperty
componentName :: Maybe (Value Text)
concat :: Maybe [ComponentPropertyProperty]
condition :: Maybe ComponentConditionPropertyProperty
configured :: Maybe (Value Bool)
defaultValue :: Maybe (Value Text)
event :: Maybe (Value Text)
importedValue :: Maybe (Value Text)
model :: Maybe (Value Text)
property :: Maybe (Value Text)
type' :: Maybe (Value Text)
userAttribute :: Maybe (Value Text)
value :: Maybe (Value Text)
..}
= ResourceProperties
{awsType :: Text
awsType = Text
"AWS::AmplifyUIBuilder::Component.ComponentProperty",
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 -> ComponentPropertyBindingPropertiesProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"BindingProperties" (ComponentPropertyBindingPropertiesProperty -> (Key, Value))
-> Maybe ComponentPropertyBindingPropertiesProperty
-> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe ComponentPropertyBindingPropertiesProperty
bindingProperties,
Key -> Map Text FormBindingElementProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"Bindings" (Map Text FormBindingElementProperty -> (Key, Value))
-> Maybe (Map Text FormBindingElementProperty)
-> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Map Text FormBindingElementProperty)
bindings,
Key -> ComponentPropertyBindingPropertiesProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"CollectionBindingProperties"
(ComponentPropertyBindingPropertiesProperty -> (Key, Value))
-> Maybe ComponentPropertyBindingPropertiesProperty
-> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe ComponentPropertyBindingPropertiesProperty
collectionBindingProperties,
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
"ComponentName" (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)
componentName,
Key -> [ComponentPropertyProperty] -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"Concat" ([ComponentPropertyProperty] -> (Key, Value))
-> Maybe [ComponentPropertyProperty] -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [ComponentPropertyProperty]
concat,
Key -> ComponentConditionPropertyProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"Condition" (ComponentConditionPropertyProperty -> (Key, Value))
-> Maybe ComponentConditionPropertyProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe ComponentConditionPropertyProperty
condition,
Key -> Value Bool -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"Configured" (Value Bool -> (Key, Value))
-> Maybe (Value Bool) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Bool)
configured,
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
"DefaultValue" (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)
defaultValue,
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
"Event" (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)
event,
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
"ImportedValue" (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)
importedValue,
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
"Model" (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)
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..=) Key
"Property" (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)
property,
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
"Type" (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)
type',
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
"UserAttribute" (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)
userAttribute,
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
"Value" (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)
value])}
instance JSON.ToJSON ComponentPropertyProperty where
toJSON :: ComponentPropertyProperty -> Value
toJSON ComponentPropertyProperty {Maybe [ComponentPropertyProperty]
Maybe (Map Text FormBindingElementProperty)
Maybe (Value Bool)
Maybe (Value Text)
Maybe ComponentPropertyBindingPropertiesProperty
Maybe ComponentConditionPropertyProperty
()
haddock_workaround_ :: ComponentPropertyProperty -> ()
bindingProperties :: ComponentPropertyProperty
-> Maybe ComponentPropertyBindingPropertiesProperty
bindings :: ComponentPropertyProperty
-> Maybe (Map Text FormBindingElementProperty)
collectionBindingProperties :: ComponentPropertyProperty
-> Maybe ComponentPropertyBindingPropertiesProperty
componentName :: ComponentPropertyProperty -> Maybe (Value Text)
concat :: ComponentPropertyProperty -> Maybe [ComponentPropertyProperty]
condition :: ComponentPropertyProperty
-> Maybe ComponentConditionPropertyProperty
configured :: ComponentPropertyProperty -> Maybe (Value Bool)
defaultValue :: ComponentPropertyProperty -> Maybe (Value Text)
event :: ComponentPropertyProperty -> Maybe (Value Text)
importedValue :: ComponentPropertyProperty -> Maybe (Value Text)
model :: ComponentPropertyProperty -> Maybe (Value Text)
property :: ComponentPropertyProperty -> Maybe (Value Text)
type' :: ComponentPropertyProperty -> Maybe (Value Text)
userAttribute :: ComponentPropertyProperty -> Maybe (Value Text)
value :: ComponentPropertyProperty -> Maybe (Value Text)
haddock_workaround_ :: ()
bindingProperties :: Maybe ComponentPropertyBindingPropertiesProperty
bindings :: Maybe (Map Text FormBindingElementProperty)
collectionBindingProperties :: Maybe ComponentPropertyBindingPropertiesProperty
componentName :: Maybe (Value Text)
concat :: Maybe [ComponentPropertyProperty]
condition :: Maybe ComponentConditionPropertyProperty
configured :: Maybe (Value Bool)
defaultValue :: Maybe (Value Text)
event :: Maybe (Value Text)
importedValue :: Maybe (Value Text)
model :: Maybe (Value Text)
property :: Maybe (Value Text)
type' :: Maybe (Value Text)
userAttribute :: Maybe (Value Text)
value :: 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 -> ComponentPropertyBindingPropertiesProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"BindingProperties" (ComponentPropertyBindingPropertiesProperty -> (Key, Value))
-> Maybe ComponentPropertyBindingPropertiesProperty
-> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe ComponentPropertyBindingPropertiesProperty
bindingProperties,
Key -> Map Text FormBindingElementProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"Bindings" (Map Text FormBindingElementProperty -> (Key, Value))
-> Maybe (Map Text FormBindingElementProperty)
-> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Map Text FormBindingElementProperty)
bindings,
Key -> ComponentPropertyBindingPropertiesProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"CollectionBindingProperties"
(ComponentPropertyBindingPropertiesProperty -> (Key, Value))
-> Maybe ComponentPropertyBindingPropertiesProperty
-> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe ComponentPropertyBindingPropertiesProperty
collectionBindingProperties,
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
"ComponentName" (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)
componentName,
Key -> [ComponentPropertyProperty] -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"Concat" ([ComponentPropertyProperty] -> (Key, Value))
-> Maybe [ComponentPropertyProperty] -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [ComponentPropertyProperty]
concat,
Key -> ComponentConditionPropertyProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"Condition" (ComponentConditionPropertyProperty -> (Key, Value))
-> Maybe ComponentConditionPropertyProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe ComponentConditionPropertyProperty
condition,
Key -> Value Bool -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"Configured" (Value Bool -> (Key, Value))
-> Maybe (Value Bool) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Bool)
configured,
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
"DefaultValue" (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)
defaultValue,
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
"Event" (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)
event,
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
"ImportedValue" (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)
importedValue,
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
"Model" (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)
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..=) Key
"Property" (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)
property,
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
"Type" (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)
type',
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
"UserAttribute" (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)
userAttribute,
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
"Value" (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)
value]))
instance Property "BindingProperties" ComponentPropertyProperty where
type PropertyType "BindingProperties" ComponentPropertyProperty = ComponentPropertyBindingPropertiesProperty
set :: PropertyType "BindingProperties" ComponentPropertyProperty
-> ComponentPropertyProperty -> ComponentPropertyProperty
set PropertyType "BindingProperties" ComponentPropertyProperty
newValue ComponentPropertyProperty {Maybe [ComponentPropertyProperty]
Maybe (Map Text FormBindingElementProperty)
Maybe (Value Bool)
Maybe (Value Text)
Maybe ComponentPropertyBindingPropertiesProperty
Maybe ComponentConditionPropertyProperty
()
haddock_workaround_ :: ComponentPropertyProperty -> ()
bindingProperties :: ComponentPropertyProperty
-> Maybe ComponentPropertyBindingPropertiesProperty
bindings :: ComponentPropertyProperty
-> Maybe (Map Text FormBindingElementProperty)
collectionBindingProperties :: ComponentPropertyProperty
-> Maybe ComponentPropertyBindingPropertiesProperty
componentName :: ComponentPropertyProperty -> Maybe (Value Text)
concat :: ComponentPropertyProperty -> Maybe [ComponentPropertyProperty]
condition :: ComponentPropertyProperty
-> Maybe ComponentConditionPropertyProperty
configured :: ComponentPropertyProperty -> Maybe (Value Bool)
defaultValue :: ComponentPropertyProperty -> Maybe (Value Text)
event :: ComponentPropertyProperty -> Maybe (Value Text)
importedValue :: ComponentPropertyProperty -> Maybe (Value Text)
model :: ComponentPropertyProperty -> Maybe (Value Text)
property :: ComponentPropertyProperty -> Maybe (Value Text)
type' :: ComponentPropertyProperty -> Maybe (Value Text)
userAttribute :: ComponentPropertyProperty -> Maybe (Value Text)
value :: ComponentPropertyProperty -> Maybe (Value Text)
haddock_workaround_ :: ()
bindingProperties :: Maybe ComponentPropertyBindingPropertiesProperty
bindings :: Maybe (Map Text FormBindingElementProperty)
collectionBindingProperties :: Maybe ComponentPropertyBindingPropertiesProperty
componentName :: Maybe (Value Text)
concat :: Maybe [ComponentPropertyProperty]
condition :: Maybe ComponentConditionPropertyProperty
configured :: Maybe (Value Bool)
defaultValue :: Maybe (Value Text)
event :: Maybe (Value Text)
importedValue :: Maybe (Value Text)
model :: Maybe (Value Text)
property :: Maybe (Value Text)
type' :: Maybe (Value Text)
userAttribute :: Maybe (Value Text)
value :: Maybe (Value Text)
..}
= ComponentPropertyProperty
{bindingProperties :: Maybe ComponentPropertyBindingPropertiesProperty
bindingProperties = ComponentPropertyBindingPropertiesProperty
-> Maybe ComponentPropertyBindingPropertiesProperty
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "BindingProperties" ComponentPropertyProperty
ComponentPropertyBindingPropertiesProperty
newValue, Maybe [ComponentPropertyProperty]
Maybe (Map Text FormBindingElementProperty)
Maybe (Value Bool)
Maybe (Value Text)
Maybe ComponentPropertyBindingPropertiesProperty
Maybe ComponentConditionPropertyProperty
()
haddock_workaround_ :: ()
bindings :: Maybe (Map Text FormBindingElementProperty)
collectionBindingProperties :: Maybe ComponentPropertyBindingPropertiesProperty
componentName :: Maybe (Value Text)
concat :: Maybe [ComponentPropertyProperty]
condition :: Maybe ComponentConditionPropertyProperty
configured :: Maybe (Value Bool)
defaultValue :: Maybe (Value Text)
event :: Maybe (Value Text)
importedValue :: Maybe (Value Text)
model :: Maybe (Value Text)
property :: Maybe (Value Text)
type' :: Maybe (Value Text)
userAttribute :: Maybe (Value Text)
value :: Maybe (Value Text)
haddock_workaround_ :: ()
bindings :: Maybe (Map Text FormBindingElementProperty)
collectionBindingProperties :: Maybe ComponentPropertyBindingPropertiesProperty
componentName :: Maybe (Value Text)
concat :: Maybe [ComponentPropertyProperty]
condition :: Maybe ComponentConditionPropertyProperty
configured :: Maybe (Value Bool)
defaultValue :: Maybe (Value Text)
event :: Maybe (Value Text)
importedValue :: Maybe (Value Text)
model :: Maybe (Value Text)
property :: Maybe (Value Text)
type' :: Maybe (Value Text)
userAttribute :: Maybe (Value Text)
value :: Maybe (Value Text)
..}
instance Property "Bindings" ComponentPropertyProperty where
type PropertyType "Bindings" ComponentPropertyProperty = Prelude.Map Prelude.Text FormBindingElementProperty
set :: PropertyType "Bindings" ComponentPropertyProperty
-> ComponentPropertyProperty -> ComponentPropertyProperty
set PropertyType "Bindings" ComponentPropertyProperty
newValue ComponentPropertyProperty {Maybe [ComponentPropertyProperty]
Maybe (Map Text FormBindingElementProperty)
Maybe (Value Bool)
Maybe (Value Text)
Maybe ComponentPropertyBindingPropertiesProperty
Maybe ComponentConditionPropertyProperty
()
haddock_workaround_ :: ComponentPropertyProperty -> ()
bindingProperties :: ComponentPropertyProperty
-> Maybe ComponentPropertyBindingPropertiesProperty
bindings :: ComponentPropertyProperty
-> Maybe (Map Text FormBindingElementProperty)
collectionBindingProperties :: ComponentPropertyProperty
-> Maybe ComponentPropertyBindingPropertiesProperty
componentName :: ComponentPropertyProperty -> Maybe (Value Text)
concat :: ComponentPropertyProperty -> Maybe [ComponentPropertyProperty]
condition :: ComponentPropertyProperty
-> Maybe ComponentConditionPropertyProperty
configured :: ComponentPropertyProperty -> Maybe (Value Bool)
defaultValue :: ComponentPropertyProperty -> Maybe (Value Text)
event :: ComponentPropertyProperty -> Maybe (Value Text)
importedValue :: ComponentPropertyProperty -> Maybe (Value Text)
model :: ComponentPropertyProperty -> Maybe (Value Text)
property :: ComponentPropertyProperty -> Maybe (Value Text)
type' :: ComponentPropertyProperty -> Maybe (Value Text)
userAttribute :: ComponentPropertyProperty -> Maybe (Value Text)
value :: ComponentPropertyProperty -> Maybe (Value Text)
haddock_workaround_ :: ()
bindingProperties :: Maybe ComponentPropertyBindingPropertiesProperty
bindings :: Maybe (Map Text FormBindingElementProperty)
collectionBindingProperties :: Maybe ComponentPropertyBindingPropertiesProperty
componentName :: Maybe (Value Text)
concat :: Maybe [ComponentPropertyProperty]
condition :: Maybe ComponentConditionPropertyProperty
configured :: Maybe (Value Bool)
defaultValue :: Maybe (Value Text)
event :: Maybe (Value Text)
importedValue :: Maybe (Value Text)
model :: Maybe (Value Text)
property :: Maybe (Value Text)
type' :: Maybe (Value Text)
userAttribute :: Maybe (Value Text)
value :: Maybe (Value Text)
..}
= ComponentPropertyProperty {bindings :: Maybe (Map Text FormBindingElementProperty)
bindings = Map Text FormBindingElementProperty
-> Maybe (Map Text FormBindingElementProperty)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure Map Text FormBindingElementProperty
PropertyType "Bindings" ComponentPropertyProperty
newValue, Maybe [ComponentPropertyProperty]
Maybe (Value Bool)
Maybe (Value Text)
Maybe ComponentPropertyBindingPropertiesProperty
Maybe ComponentConditionPropertyProperty
()
haddock_workaround_ :: ()
bindingProperties :: Maybe ComponentPropertyBindingPropertiesProperty
collectionBindingProperties :: Maybe ComponentPropertyBindingPropertiesProperty
componentName :: Maybe (Value Text)
concat :: Maybe [ComponentPropertyProperty]
condition :: Maybe ComponentConditionPropertyProperty
configured :: Maybe (Value Bool)
defaultValue :: Maybe (Value Text)
event :: Maybe (Value Text)
importedValue :: Maybe (Value Text)
model :: Maybe (Value Text)
property :: Maybe (Value Text)
type' :: Maybe (Value Text)
userAttribute :: Maybe (Value Text)
value :: Maybe (Value Text)
haddock_workaround_ :: ()
bindingProperties :: Maybe ComponentPropertyBindingPropertiesProperty
collectionBindingProperties :: Maybe ComponentPropertyBindingPropertiesProperty
componentName :: Maybe (Value Text)
concat :: Maybe [ComponentPropertyProperty]
condition :: Maybe ComponentConditionPropertyProperty
configured :: Maybe (Value Bool)
defaultValue :: Maybe (Value Text)
event :: Maybe (Value Text)
importedValue :: Maybe (Value Text)
model :: Maybe (Value Text)
property :: Maybe (Value Text)
type' :: Maybe (Value Text)
userAttribute :: Maybe (Value Text)
value :: Maybe (Value Text)
..}
instance Property "CollectionBindingProperties" ComponentPropertyProperty where
type PropertyType "CollectionBindingProperties" ComponentPropertyProperty = ComponentPropertyBindingPropertiesProperty
set :: PropertyType
"CollectionBindingProperties" ComponentPropertyProperty
-> ComponentPropertyProperty -> ComponentPropertyProperty
set PropertyType
"CollectionBindingProperties" ComponentPropertyProperty
newValue ComponentPropertyProperty {Maybe [ComponentPropertyProperty]
Maybe (Map Text FormBindingElementProperty)
Maybe (Value Bool)
Maybe (Value Text)
Maybe ComponentPropertyBindingPropertiesProperty
Maybe ComponentConditionPropertyProperty
()
haddock_workaround_ :: ComponentPropertyProperty -> ()
bindingProperties :: ComponentPropertyProperty
-> Maybe ComponentPropertyBindingPropertiesProperty
bindings :: ComponentPropertyProperty
-> Maybe (Map Text FormBindingElementProperty)
collectionBindingProperties :: ComponentPropertyProperty
-> Maybe ComponentPropertyBindingPropertiesProperty
componentName :: ComponentPropertyProperty -> Maybe (Value Text)
concat :: ComponentPropertyProperty -> Maybe [ComponentPropertyProperty]
condition :: ComponentPropertyProperty
-> Maybe ComponentConditionPropertyProperty
configured :: ComponentPropertyProperty -> Maybe (Value Bool)
defaultValue :: ComponentPropertyProperty -> Maybe (Value Text)
event :: ComponentPropertyProperty -> Maybe (Value Text)
importedValue :: ComponentPropertyProperty -> Maybe (Value Text)
model :: ComponentPropertyProperty -> Maybe (Value Text)
property :: ComponentPropertyProperty -> Maybe (Value Text)
type' :: ComponentPropertyProperty -> Maybe (Value Text)
userAttribute :: ComponentPropertyProperty -> Maybe (Value Text)
value :: ComponentPropertyProperty -> Maybe (Value Text)
haddock_workaround_ :: ()
bindingProperties :: Maybe ComponentPropertyBindingPropertiesProperty
bindings :: Maybe (Map Text FormBindingElementProperty)
collectionBindingProperties :: Maybe ComponentPropertyBindingPropertiesProperty
componentName :: Maybe (Value Text)
concat :: Maybe [ComponentPropertyProperty]
condition :: Maybe ComponentConditionPropertyProperty
configured :: Maybe (Value Bool)
defaultValue :: Maybe (Value Text)
event :: Maybe (Value Text)
importedValue :: Maybe (Value Text)
model :: Maybe (Value Text)
property :: Maybe (Value Text)
type' :: Maybe (Value Text)
userAttribute :: Maybe (Value Text)
value :: Maybe (Value Text)
..}
= ComponentPropertyProperty
{collectionBindingProperties :: Maybe ComponentPropertyBindingPropertiesProperty
collectionBindingProperties = ComponentPropertyBindingPropertiesProperty
-> Maybe ComponentPropertyBindingPropertiesProperty
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType
"CollectionBindingProperties" ComponentPropertyProperty
ComponentPropertyBindingPropertiesProperty
newValue, Maybe [ComponentPropertyProperty]
Maybe (Map Text FormBindingElementProperty)
Maybe (Value Bool)
Maybe (Value Text)
Maybe ComponentPropertyBindingPropertiesProperty
Maybe ComponentConditionPropertyProperty
()
haddock_workaround_ :: ()
bindingProperties :: Maybe ComponentPropertyBindingPropertiesProperty
bindings :: Maybe (Map Text FormBindingElementProperty)
componentName :: Maybe (Value Text)
concat :: Maybe [ComponentPropertyProperty]
condition :: Maybe ComponentConditionPropertyProperty
configured :: Maybe (Value Bool)
defaultValue :: Maybe (Value Text)
event :: Maybe (Value Text)
importedValue :: Maybe (Value Text)
model :: Maybe (Value Text)
property :: Maybe (Value Text)
type' :: Maybe (Value Text)
userAttribute :: Maybe (Value Text)
value :: Maybe (Value Text)
haddock_workaround_ :: ()
bindingProperties :: Maybe ComponentPropertyBindingPropertiesProperty
bindings :: Maybe (Map Text FormBindingElementProperty)
componentName :: Maybe (Value Text)
concat :: Maybe [ComponentPropertyProperty]
condition :: Maybe ComponentConditionPropertyProperty
configured :: Maybe (Value Bool)
defaultValue :: Maybe (Value Text)
event :: Maybe (Value Text)
importedValue :: Maybe (Value Text)
model :: Maybe (Value Text)
property :: Maybe (Value Text)
type' :: Maybe (Value Text)
userAttribute :: Maybe (Value Text)
value :: Maybe (Value Text)
..}
instance Property "ComponentName" ComponentPropertyProperty where
type PropertyType "ComponentName" ComponentPropertyProperty = Value Prelude.Text
set :: PropertyType "ComponentName" ComponentPropertyProperty
-> ComponentPropertyProperty -> ComponentPropertyProperty
set PropertyType "ComponentName" ComponentPropertyProperty
newValue ComponentPropertyProperty {Maybe [ComponentPropertyProperty]
Maybe (Map Text FormBindingElementProperty)
Maybe (Value Bool)
Maybe (Value Text)
Maybe ComponentPropertyBindingPropertiesProperty
Maybe ComponentConditionPropertyProperty
()
haddock_workaround_ :: ComponentPropertyProperty -> ()
bindingProperties :: ComponentPropertyProperty
-> Maybe ComponentPropertyBindingPropertiesProperty
bindings :: ComponentPropertyProperty
-> Maybe (Map Text FormBindingElementProperty)
collectionBindingProperties :: ComponentPropertyProperty
-> Maybe ComponentPropertyBindingPropertiesProperty
componentName :: ComponentPropertyProperty -> Maybe (Value Text)
concat :: ComponentPropertyProperty -> Maybe [ComponentPropertyProperty]
condition :: ComponentPropertyProperty
-> Maybe ComponentConditionPropertyProperty
configured :: ComponentPropertyProperty -> Maybe (Value Bool)
defaultValue :: ComponentPropertyProperty -> Maybe (Value Text)
event :: ComponentPropertyProperty -> Maybe (Value Text)
importedValue :: ComponentPropertyProperty -> Maybe (Value Text)
model :: ComponentPropertyProperty -> Maybe (Value Text)
property :: ComponentPropertyProperty -> Maybe (Value Text)
type' :: ComponentPropertyProperty -> Maybe (Value Text)
userAttribute :: ComponentPropertyProperty -> Maybe (Value Text)
value :: ComponentPropertyProperty -> Maybe (Value Text)
haddock_workaround_ :: ()
bindingProperties :: Maybe ComponentPropertyBindingPropertiesProperty
bindings :: Maybe (Map Text FormBindingElementProperty)
collectionBindingProperties :: Maybe ComponentPropertyBindingPropertiesProperty
componentName :: Maybe (Value Text)
concat :: Maybe [ComponentPropertyProperty]
condition :: Maybe ComponentConditionPropertyProperty
configured :: Maybe (Value Bool)
defaultValue :: Maybe (Value Text)
event :: Maybe (Value Text)
importedValue :: Maybe (Value Text)
model :: Maybe (Value Text)
property :: Maybe (Value Text)
type' :: Maybe (Value Text)
userAttribute :: Maybe (Value Text)
value :: Maybe (Value Text)
..}
= ComponentPropertyProperty
{componentName :: Maybe (Value Text)
componentName = Value Text -> Maybe (Value Text)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "ComponentName" ComponentPropertyProperty
Value Text
newValue, Maybe [ComponentPropertyProperty]
Maybe (Map Text FormBindingElementProperty)
Maybe (Value Bool)
Maybe (Value Text)
Maybe ComponentPropertyBindingPropertiesProperty
Maybe ComponentConditionPropertyProperty
()
haddock_workaround_ :: ()
bindingProperties :: Maybe ComponentPropertyBindingPropertiesProperty
bindings :: Maybe (Map Text FormBindingElementProperty)
collectionBindingProperties :: Maybe ComponentPropertyBindingPropertiesProperty
concat :: Maybe [ComponentPropertyProperty]
condition :: Maybe ComponentConditionPropertyProperty
configured :: Maybe (Value Bool)
defaultValue :: Maybe (Value Text)
event :: Maybe (Value Text)
importedValue :: Maybe (Value Text)
model :: Maybe (Value Text)
property :: Maybe (Value Text)
type' :: Maybe (Value Text)
userAttribute :: Maybe (Value Text)
value :: Maybe (Value Text)
haddock_workaround_ :: ()
bindingProperties :: Maybe ComponentPropertyBindingPropertiesProperty
bindings :: Maybe (Map Text FormBindingElementProperty)
collectionBindingProperties :: Maybe ComponentPropertyBindingPropertiesProperty
concat :: Maybe [ComponentPropertyProperty]
condition :: Maybe ComponentConditionPropertyProperty
configured :: Maybe (Value Bool)
defaultValue :: Maybe (Value Text)
event :: Maybe (Value Text)
importedValue :: Maybe (Value Text)
model :: Maybe (Value Text)
property :: Maybe (Value Text)
type' :: Maybe (Value Text)
userAttribute :: Maybe (Value Text)
value :: Maybe (Value Text)
..}
instance Property "Concat" ComponentPropertyProperty where
type PropertyType "Concat" ComponentPropertyProperty = [ComponentPropertyProperty]
set :: PropertyType "Concat" ComponentPropertyProperty
-> ComponentPropertyProperty -> ComponentPropertyProperty
set PropertyType "Concat" ComponentPropertyProperty
newValue ComponentPropertyProperty {Maybe [ComponentPropertyProperty]
Maybe (Map Text FormBindingElementProperty)
Maybe (Value Bool)
Maybe (Value Text)
Maybe ComponentPropertyBindingPropertiesProperty
Maybe ComponentConditionPropertyProperty
()
haddock_workaround_ :: ComponentPropertyProperty -> ()
bindingProperties :: ComponentPropertyProperty
-> Maybe ComponentPropertyBindingPropertiesProperty
bindings :: ComponentPropertyProperty
-> Maybe (Map Text FormBindingElementProperty)
collectionBindingProperties :: ComponentPropertyProperty
-> Maybe ComponentPropertyBindingPropertiesProperty
componentName :: ComponentPropertyProperty -> Maybe (Value Text)
concat :: ComponentPropertyProperty -> Maybe [ComponentPropertyProperty]
condition :: ComponentPropertyProperty
-> Maybe ComponentConditionPropertyProperty
configured :: ComponentPropertyProperty -> Maybe (Value Bool)
defaultValue :: ComponentPropertyProperty -> Maybe (Value Text)
event :: ComponentPropertyProperty -> Maybe (Value Text)
importedValue :: ComponentPropertyProperty -> Maybe (Value Text)
model :: ComponentPropertyProperty -> Maybe (Value Text)
property :: ComponentPropertyProperty -> Maybe (Value Text)
type' :: ComponentPropertyProperty -> Maybe (Value Text)
userAttribute :: ComponentPropertyProperty -> Maybe (Value Text)
value :: ComponentPropertyProperty -> Maybe (Value Text)
haddock_workaround_ :: ()
bindingProperties :: Maybe ComponentPropertyBindingPropertiesProperty
bindings :: Maybe (Map Text FormBindingElementProperty)
collectionBindingProperties :: Maybe ComponentPropertyBindingPropertiesProperty
componentName :: Maybe (Value Text)
concat :: Maybe [ComponentPropertyProperty]
condition :: Maybe ComponentConditionPropertyProperty
configured :: Maybe (Value Bool)
defaultValue :: Maybe (Value Text)
event :: Maybe (Value Text)
importedValue :: Maybe (Value Text)
model :: Maybe (Value Text)
property :: Maybe (Value Text)
type' :: Maybe (Value Text)
userAttribute :: Maybe (Value Text)
value :: Maybe (Value Text)
..}
= ComponentPropertyProperty {concat :: Maybe [ComponentPropertyProperty]
concat = [ComponentPropertyProperty] -> Maybe [ComponentPropertyProperty]
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure [ComponentPropertyProperty]
PropertyType "Concat" ComponentPropertyProperty
newValue, Maybe (Map Text FormBindingElementProperty)
Maybe (Value Bool)
Maybe (Value Text)
Maybe ComponentPropertyBindingPropertiesProperty
Maybe ComponentConditionPropertyProperty
()
haddock_workaround_ :: ()
bindingProperties :: Maybe ComponentPropertyBindingPropertiesProperty
bindings :: Maybe (Map Text FormBindingElementProperty)
collectionBindingProperties :: Maybe ComponentPropertyBindingPropertiesProperty
componentName :: Maybe (Value Text)
condition :: Maybe ComponentConditionPropertyProperty
configured :: Maybe (Value Bool)
defaultValue :: Maybe (Value Text)
event :: Maybe (Value Text)
importedValue :: Maybe (Value Text)
model :: Maybe (Value Text)
property :: Maybe (Value Text)
type' :: Maybe (Value Text)
userAttribute :: Maybe (Value Text)
value :: Maybe (Value Text)
haddock_workaround_ :: ()
bindingProperties :: Maybe ComponentPropertyBindingPropertiesProperty
bindings :: Maybe (Map Text FormBindingElementProperty)
collectionBindingProperties :: Maybe ComponentPropertyBindingPropertiesProperty
componentName :: Maybe (Value Text)
condition :: Maybe ComponentConditionPropertyProperty
configured :: Maybe (Value Bool)
defaultValue :: Maybe (Value Text)
event :: Maybe (Value Text)
importedValue :: Maybe (Value Text)
model :: Maybe (Value Text)
property :: Maybe (Value Text)
type' :: Maybe (Value Text)
userAttribute :: Maybe (Value Text)
value :: Maybe (Value Text)
..}
instance Property "Condition" ComponentPropertyProperty where
type PropertyType "Condition" ComponentPropertyProperty = ComponentConditionPropertyProperty
set :: PropertyType "Condition" ComponentPropertyProperty
-> ComponentPropertyProperty -> ComponentPropertyProperty
set PropertyType "Condition" ComponentPropertyProperty
newValue ComponentPropertyProperty {Maybe [ComponentPropertyProperty]
Maybe (Map Text FormBindingElementProperty)
Maybe (Value Bool)
Maybe (Value Text)
Maybe ComponentPropertyBindingPropertiesProperty
Maybe ComponentConditionPropertyProperty
()
haddock_workaround_ :: ComponentPropertyProperty -> ()
bindingProperties :: ComponentPropertyProperty
-> Maybe ComponentPropertyBindingPropertiesProperty
bindings :: ComponentPropertyProperty
-> Maybe (Map Text FormBindingElementProperty)
collectionBindingProperties :: ComponentPropertyProperty
-> Maybe ComponentPropertyBindingPropertiesProperty
componentName :: ComponentPropertyProperty -> Maybe (Value Text)
concat :: ComponentPropertyProperty -> Maybe [ComponentPropertyProperty]
condition :: ComponentPropertyProperty
-> Maybe ComponentConditionPropertyProperty
configured :: ComponentPropertyProperty -> Maybe (Value Bool)
defaultValue :: ComponentPropertyProperty -> Maybe (Value Text)
event :: ComponentPropertyProperty -> Maybe (Value Text)
importedValue :: ComponentPropertyProperty -> Maybe (Value Text)
model :: ComponentPropertyProperty -> Maybe (Value Text)
property :: ComponentPropertyProperty -> Maybe (Value Text)
type' :: ComponentPropertyProperty -> Maybe (Value Text)
userAttribute :: ComponentPropertyProperty -> Maybe (Value Text)
value :: ComponentPropertyProperty -> Maybe (Value Text)
haddock_workaround_ :: ()
bindingProperties :: Maybe ComponentPropertyBindingPropertiesProperty
bindings :: Maybe (Map Text FormBindingElementProperty)
collectionBindingProperties :: Maybe ComponentPropertyBindingPropertiesProperty
componentName :: Maybe (Value Text)
concat :: Maybe [ComponentPropertyProperty]
condition :: Maybe ComponentConditionPropertyProperty
configured :: Maybe (Value Bool)
defaultValue :: Maybe (Value Text)
event :: Maybe (Value Text)
importedValue :: Maybe (Value Text)
model :: Maybe (Value Text)
property :: Maybe (Value Text)
type' :: Maybe (Value Text)
userAttribute :: Maybe (Value Text)
value :: Maybe (Value Text)
..}
= ComponentPropertyProperty {condition :: Maybe ComponentConditionPropertyProperty
condition = ComponentConditionPropertyProperty
-> Maybe ComponentConditionPropertyProperty
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "Condition" ComponentPropertyProperty
ComponentConditionPropertyProperty
newValue, Maybe [ComponentPropertyProperty]
Maybe (Map Text FormBindingElementProperty)
Maybe (Value Bool)
Maybe (Value Text)
Maybe ComponentPropertyBindingPropertiesProperty
()
haddock_workaround_ :: ()
bindingProperties :: Maybe ComponentPropertyBindingPropertiesProperty
bindings :: Maybe (Map Text FormBindingElementProperty)
collectionBindingProperties :: Maybe ComponentPropertyBindingPropertiesProperty
componentName :: Maybe (Value Text)
concat :: Maybe [ComponentPropertyProperty]
configured :: Maybe (Value Bool)
defaultValue :: Maybe (Value Text)
event :: Maybe (Value Text)
importedValue :: Maybe (Value Text)
model :: Maybe (Value Text)
property :: Maybe (Value Text)
type' :: Maybe (Value Text)
userAttribute :: Maybe (Value Text)
value :: Maybe (Value Text)
haddock_workaround_ :: ()
bindingProperties :: Maybe ComponentPropertyBindingPropertiesProperty
bindings :: Maybe (Map Text FormBindingElementProperty)
collectionBindingProperties :: Maybe ComponentPropertyBindingPropertiesProperty
componentName :: Maybe (Value Text)
concat :: Maybe [ComponentPropertyProperty]
configured :: Maybe (Value Bool)
defaultValue :: Maybe (Value Text)
event :: Maybe (Value Text)
importedValue :: Maybe (Value Text)
model :: Maybe (Value Text)
property :: Maybe (Value Text)
type' :: Maybe (Value Text)
userAttribute :: Maybe (Value Text)
value :: Maybe (Value Text)
..}
instance Property "Configured" ComponentPropertyProperty where
type PropertyType "Configured" ComponentPropertyProperty = Value Prelude.Bool
set :: PropertyType "Configured" ComponentPropertyProperty
-> ComponentPropertyProperty -> ComponentPropertyProperty
set PropertyType "Configured" ComponentPropertyProperty
newValue ComponentPropertyProperty {Maybe [ComponentPropertyProperty]
Maybe (Map Text FormBindingElementProperty)
Maybe (Value Bool)
Maybe (Value Text)
Maybe ComponentPropertyBindingPropertiesProperty
Maybe ComponentConditionPropertyProperty
()
haddock_workaround_ :: ComponentPropertyProperty -> ()
bindingProperties :: ComponentPropertyProperty
-> Maybe ComponentPropertyBindingPropertiesProperty
bindings :: ComponentPropertyProperty
-> Maybe (Map Text FormBindingElementProperty)
collectionBindingProperties :: ComponentPropertyProperty
-> Maybe ComponentPropertyBindingPropertiesProperty
componentName :: ComponentPropertyProperty -> Maybe (Value Text)
concat :: ComponentPropertyProperty -> Maybe [ComponentPropertyProperty]
condition :: ComponentPropertyProperty
-> Maybe ComponentConditionPropertyProperty
configured :: ComponentPropertyProperty -> Maybe (Value Bool)
defaultValue :: ComponentPropertyProperty -> Maybe (Value Text)
event :: ComponentPropertyProperty -> Maybe (Value Text)
importedValue :: ComponentPropertyProperty -> Maybe (Value Text)
model :: ComponentPropertyProperty -> Maybe (Value Text)
property :: ComponentPropertyProperty -> Maybe (Value Text)
type' :: ComponentPropertyProperty -> Maybe (Value Text)
userAttribute :: ComponentPropertyProperty -> Maybe (Value Text)
value :: ComponentPropertyProperty -> Maybe (Value Text)
haddock_workaround_ :: ()
bindingProperties :: Maybe ComponentPropertyBindingPropertiesProperty
bindings :: Maybe (Map Text FormBindingElementProperty)
collectionBindingProperties :: Maybe ComponentPropertyBindingPropertiesProperty
componentName :: Maybe (Value Text)
concat :: Maybe [ComponentPropertyProperty]
condition :: Maybe ComponentConditionPropertyProperty
configured :: Maybe (Value Bool)
defaultValue :: Maybe (Value Text)
event :: Maybe (Value Text)
importedValue :: Maybe (Value Text)
model :: Maybe (Value Text)
property :: Maybe (Value Text)
type' :: Maybe (Value Text)
userAttribute :: Maybe (Value Text)
value :: Maybe (Value Text)
..}
= ComponentPropertyProperty
{configured :: Maybe (Value Bool)
configured = Value Bool -> Maybe (Value Bool)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "Configured" ComponentPropertyProperty
Value Bool
newValue, Maybe [ComponentPropertyProperty]
Maybe (Map Text FormBindingElementProperty)
Maybe (Value Text)
Maybe ComponentPropertyBindingPropertiesProperty
Maybe ComponentConditionPropertyProperty
()
haddock_workaround_ :: ()
bindingProperties :: Maybe ComponentPropertyBindingPropertiesProperty
bindings :: Maybe (Map Text FormBindingElementProperty)
collectionBindingProperties :: Maybe ComponentPropertyBindingPropertiesProperty
componentName :: Maybe (Value Text)
concat :: Maybe [ComponentPropertyProperty]
condition :: Maybe ComponentConditionPropertyProperty
defaultValue :: Maybe (Value Text)
event :: Maybe (Value Text)
importedValue :: Maybe (Value Text)
model :: Maybe (Value Text)
property :: Maybe (Value Text)
type' :: Maybe (Value Text)
userAttribute :: Maybe (Value Text)
value :: Maybe (Value Text)
haddock_workaround_ :: ()
bindingProperties :: Maybe ComponentPropertyBindingPropertiesProperty
bindings :: Maybe (Map Text FormBindingElementProperty)
collectionBindingProperties :: Maybe ComponentPropertyBindingPropertiesProperty
componentName :: Maybe (Value Text)
concat :: Maybe [ComponentPropertyProperty]
condition :: Maybe ComponentConditionPropertyProperty
defaultValue :: Maybe (Value Text)
event :: Maybe (Value Text)
importedValue :: Maybe (Value Text)
model :: Maybe (Value Text)
property :: Maybe (Value Text)
type' :: Maybe (Value Text)
userAttribute :: Maybe (Value Text)
value :: Maybe (Value Text)
..}
instance Property "DefaultValue" ComponentPropertyProperty where
type PropertyType "DefaultValue" ComponentPropertyProperty = Value Prelude.Text
set :: PropertyType "DefaultValue" ComponentPropertyProperty
-> ComponentPropertyProperty -> ComponentPropertyProperty
set PropertyType "DefaultValue" ComponentPropertyProperty
newValue ComponentPropertyProperty {Maybe [ComponentPropertyProperty]
Maybe (Map Text FormBindingElementProperty)
Maybe (Value Bool)
Maybe (Value Text)
Maybe ComponentPropertyBindingPropertiesProperty
Maybe ComponentConditionPropertyProperty
()
haddock_workaround_ :: ComponentPropertyProperty -> ()
bindingProperties :: ComponentPropertyProperty
-> Maybe ComponentPropertyBindingPropertiesProperty
bindings :: ComponentPropertyProperty
-> Maybe (Map Text FormBindingElementProperty)
collectionBindingProperties :: ComponentPropertyProperty
-> Maybe ComponentPropertyBindingPropertiesProperty
componentName :: ComponentPropertyProperty -> Maybe (Value Text)
concat :: ComponentPropertyProperty -> Maybe [ComponentPropertyProperty]
condition :: ComponentPropertyProperty
-> Maybe ComponentConditionPropertyProperty
configured :: ComponentPropertyProperty -> Maybe (Value Bool)
defaultValue :: ComponentPropertyProperty -> Maybe (Value Text)
event :: ComponentPropertyProperty -> Maybe (Value Text)
importedValue :: ComponentPropertyProperty -> Maybe (Value Text)
model :: ComponentPropertyProperty -> Maybe (Value Text)
property :: ComponentPropertyProperty -> Maybe (Value Text)
type' :: ComponentPropertyProperty -> Maybe (Value Text)
userAttribute :: ComponentPropertyProperty -> Maybe (Value Text)
value :: ComponentPropertyProperty -> Maybe (Value Text)
haddock_workaround_ :: ()
bindingProperties :: Maybe ComponentPropertyBindingPropertiesProperty
bindings :: Maybe (Map Text FormBindingElementProperty)
collectionBindingProperties :: Maybe ComponentPropertyBindingPropertiesProperty
componentName :: Maybe (Value Text)
concat :: Maybe [ComponentPropertyProperty]
condition :: Maybe ComponentConditionPropertyProperty
configured :: Maybe (Value Bool)
defaultValue :: Maybe (Value Text)
event :: Maybe (Value Text)
importedValue :: Maybe (Value Text)
model :: Maybe (Value Text)
property :: Maybe (Value Text)
type' :: Maybe (Value Text)
userAttribute :: Maybe (Value Text)
value :: Maybe (Value Text)
..}
= ComponentPropertyProperty
{defaultValue :: Maybe (Value Text)
defaultValue = Value Text -> Maybe (Value Text)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "DefaultValue" ComponentPropertyProperty
Value Text
newValue, Maybe [ComponentPropertyProperty]
Maybe (Map Text FormBindingElementProperty)
Maybe (Value Bool)
Maybe (Value Text)
Maybe ComponentPropertyBindingPropertiesProperty
Maybe ComponentConditionPropertyProperty
()
haddock_workaround_ :: ()
bindingProperties :: Maybe ComponentPropertyBindingPropertiesProperty
bindings :: Maybe (Map Text FormBindingElementProperty)
collectionBindingProperties :: Maybe ComponentPropertyBindingPropertiesProperty
componentName :: Maybe (Value Text)
concat :: Maybe [ComponentPropertyProperty]
condition :: Maybe ComponentConditionPropertyProperty
configured :: Maybe (Value Bool)
event :: Maybe (Value Text)
importedValue :: Maybe (Value Text)
model :: Maybe (Value Text)
property :: Maybe (Value Text)
type' :: Maybe (Value Text)
userAttribute :: Maybe (Value Text)
value :: Maybe (Value Text)
haddock_workaround_ :: ()
bindingProperties :: Maybe ComponentPropertyBindingPropertiesProperty
bindings :: Maybe (Map Text FormBindingElementProperty)
collectionBindingProperties :: Maybe ComponentPropertyBindingPropertiesProperty
componentName :: Maybe (Value Text)
concat :: Maybe [ComponentPropertyProperty]
condition :: Maybe ComponentConditionPropertyProperty
configured :: Maybe (Value Bool)
event :: Maybe (Value Text)
importedValue :: Maybe (Value Text)
model :: Maybe (Value Text)
property :: Maybe (Value Text)
type' :: Maybe (Value Text)
userAttribute :: Maybe (Value Text)
value :: Maybe (Value Text)
..}
instance Property "Event" ComponentPropertyProperty where
type PropertyType "Event" ComponentPropertyProperty = Value Prelude.Text
set :: PropertyType "Event" ComponentPropertyProperty
-> ComponentPropertyProperty -> ComponentPropertyProperty
set PropertyType "Event" ComponentPropertyProperty
newValue ComponentPropertyProperty {Maybe [ComponentPropertyProperty]
Maybe (Map Text FormBindingElementProperty)
Maybe (Value Bool)
Maybe (Value Text)
Maybe ComponentPropertyBindingPropertiesProperty
Maybe ComponentConditionPropertyProperty
()
haddock_workaround_ :: ComponentPropertyProperty -> ()
bindingProperties :: ComponentPropertyProperty
-> Maybe ComponentPropertyBindingPropertiesProperty
bindings :: ComponentPropertyProperty
-> Maybe (Map Text FormBindingElementProperty)
collectionBindingProperties :: ComponentPropertyProperty
-> Maybe ComponentPropertyBindingPropertiesProperty
componentName :: ComponentPropertyProperty -> Maybe (Value Text)
concat :: ComponentPropertyProperty -> Maybe [ComponentPropertyProperty]
condition :: ComponentPropertyProperty
-> Maybe ComponentConditionPropertyProperty
configured :: ComponentPropertyProperty -> Maybe (Value Bool)
defaultValue :: ComponentPropertyProperty -> Maybe (Value Text)
event :: ComponentPropertyProperty -> Maybe (Value Text)
importedValue :: ComponentPropertyProperty -> Maybe (Value Text)
model :: ComponentPropertyProperty -> Maybe (Value Text)
property :: ComponentPropertyProperty -> Maybe (Value Text)
type' :: ComponentPropertyProperty -> Maybe (Value Text)
userAttribute :: ComponentPropertyProperty -> Maybe (Value Text)
value :: ComponentPropertyProperty -> Maybe (Value Text)
haddock_workaround_ :: ()
bindingProperties :: Maybe ComponentPropertyBindingPropertiesProperty
bindings :: Maybe (Map Text FormBindingElementProperty)
collectionBindingProperties :: Maybe ComponentPropertyBindingPropertiesProperty
componentName :: Maybe (Value Text)
concat :: Maybe [ComponentPropertyProperty]
condition :: Maybe ComponentConditionPropertyProperty
configured :: Maybe (Value Bool)
defaultValue :: Maybe (Value Text)
event :: Maybe (Value Text)
importedValue :: Maybe (Value Text)
model :: Maybe (Value Text)
property :: Maybe (Value Text)
type' :: Maybe (Value Text)
userAttribute :: Maybe (Value Text)
value :: Maybe (Value Text)
..}
= ComponentPropertyProperty {event :: Maybe (Value Text)
event = Value Text -> Maybe (Value Text)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "Event" ComponentPropertyProperty
Value Text
newValue, Maybe [ComponentPropertyProperty]
Maybe (Map Text FormBindingElementProperty)
Maybe (Value Bool)
Maybe (Value Text)
Maybe ComponentPropertyBindingPropertiesProperty
Maybe ComponentConditionPropertyProperty
()
haddock_workaround_ :: ()
bindingProperties :: Maybe ComponentPropertyBindingPropertiesProperty
bindings :: Maybe (Map Text FormBindingElementProperty)
collectionBindingProperties :: Maybe ComponentPropertyBindingPropertiesProperty
componentName :: Maybe (Value Text)
concat :: Maybe [ComponentPropertyProperty]
condition :: Maybe ComponentConditionPropertyProperty
configured :: Maybe (Value Bool)
defaultValue :: Maybe (Value Text)
importedValue :: Maybe (Value Text)
model :: Maybe (Value Text)
property :: Maybe (Value Text)
type' :: Maybe (Value Text)
userAttribute :: Maybe (Value Text)
value :: Maybe (Value Text)
haddock_workaround_ :: ()
bindingProperties :: Maybe ComponentPropertyBindingPropertiesProperty
bindings :: Maybe (Map Text FormBindingElementProperty)
collectionBindingProperties :: Maybe ComponentPropertyBindingPropertiesProperty
componentName :: Maybe (Value Text)
concat :: Maybe [ComponentPropertyProperty]
condition :: Maybe ComponentConditionPropertyProperty
configured :: Maybe (Value Bool)
defaultValue :: Maybe (Value Text)
importedValue :: Maybe (Value Text)
model :: Maybe (Value Text)
property :: Maybe (Value Text)
type' :: Maybe (Value Text)
userAttribute :: Maybe (Value Text)
value :: Maybe (Value Text)
..}
instance Property "ImportedValue" ComponentPropertyProperty where
type PropertyType "ImportedValue" ComponentPropertyProperty = Value Prelude.Text
set :: PropertyType "ImportedValue" ComponentPropertyProperty
-> ComponentPropertyProperty -> ComponentPropertyProperty
set PropertyType "ImportedValue" ComponentPropertyProperty
newValue ComponentPropertyProperty {Maybe [ComponentPropertyProperty]
Maybe (Map Text FormBindingElementProperty)
Maybe (Value Bool)
Maybe (Value Text)
Maybe ComponentPropertyBindingPropertiesProperty
Maybe ComponentConditionPropertyProperty
()
haddock_workaround_ :: ComponentPropertyProperty -> ()
bindingProperties :: ComponentPropertyProperty
-> Maybe ComponentPropertyBindingPropertiesProperty
bindings :: ComponentPropertyProperty
-> Maybe (Map Text FormBindingElementProperty)
collectionBindingProperties :: ComponentPropertyProperty
-> Maybe ComponentPropertyBindingPropertiesProperty
componentName :: ComponentPropertyProperty -> Maybe (Value Text)
concat :: ComponentPropertyProperty -> Maybe [ComponentPropertyProperty]
condition :: ComponentPropertyProperty
-> Maybe ComponentConditionPropertyProperty
configured :: ComponentPropertyProperty -> Maybe (Value Bool)
defaultValue :: ComponentPropertyProperty -> Maybe (Value Text)
event :: ComponentPropertyProperty -> Maybe (Value Text)
importedValue :: ComponentPropertyProperty -> Maybe (Value Text)
model :: ComponentPropertyProperty -> Maybe (Value Text)
property :: ComponentPropertyProperty -> Maybe (Value Text)
type' :: ComponentPropertyProperty -> Maybe (Value Text)
userAttribute :: ComponentPropertyProperty -> Maybe (Value Text)
value :: ComponentPropertyProperty -> Maybe (Value Text)
haddock_workaround_ :: ()
bindingProperties :: Maybe ComponentPropertyBindingPropertiesProperty
bindings :: Maybe (Map Text FormBindingElementProperty)
collectionBindingProperties :: Maybe ComponentPropertyBindingPropertiesProperty
componentName :: Maybe (Value Text)
concat :: Maybe [ComponentPropertyProperty]
condition :: Maybe ComponentConditionPropertyProperty
configured :: Maybe (Value Bool)
defaultValue :: Maybe (Value Text)
event :: Maybe (Value Text)
importedValue :: Maybe (Value Text)
model :: Maybe (Value Text)
property :: Maybe (Value Text)
type' :: Maybe (Value Text)
userAttribute :: Maybe (Value Text)
value :: Maybe (Value Text)
..}
= ComponentPropertyProperty
{importedValue :: Maybe (Value Text)
importedValue = Value Text -> Maybe (Value Text)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "ImportedValue" ComponentPropertyProperty
Value Text
newValue, Maybe [ComponentPropertyProperty]
Maybe (Map Text FormBindingElementProperty)
Maybe (Value Bool)
Maybe (Value Text)
Maybe ComponentPropertyBindingPropertiesProperty
Maybe ComponentConditionPropertyProperty
()
haddock_workaround_ :: ()
bindingProperties :: Maybe ComponentPropertyBindingPropertiesProperty
bindings :: Maybe (Map Text FormBindingElementProperty)
collectionBindingProperties :: Maybe ComponentPropertyBindingPropertiesProperty
componentName :: Maybe (Value Text)
concat :: Maybe [ComponentPropertyProperty]
condition :: Maybe ComponentConditionPropertyProperty
configured :: Maybe (Value Bool)
defaultValue :: Maybe (Value Text)
event :: Maybe (Value Text)
model :: Maybe (Value Text)
property :: Maybe (Value Text)
type' :: Maybe (Value Text)
userAttribute :: Maybe (Value Text)
value :: Maybe (Value Text)
haddock_workaround_ :: ()
bindingProperties :: Maybe ComponentPropertyBindingPropertiesProperty
bindings :: Maybe (Map Text FormBindingElementProperty)
collectionBindingProperties :: Maybe ComponentPropertyBindingPropertiesProperty
componentName :: Maybe (Value Text)
concat :: Maybe [ComponentPropertyProperty]
condition :: Maybe ComponentConditionPropertyProperty
configured :: Maybe (Value Bool)
defaultValue :: Maybe (Value Text)
event :: Maybe (Value Text)
model :: Maybe (Value Text)
property :: Maybe (Value Text)
type' :: Maybe (Value Text)
userAttribute :: Maybe (Value Text)
value :: Maybe (Value Text)
..}
instance Property "Model" ComponentPropertyProperty where
type PropertyType "Model" ComponentPropertyProperty = Value Prelude.Text
set :: PropertyType "Model" ComponentPropertyProperty
-> ComponentPropertyProperty -> ComponentPropertyProperty
set PropertyType "Model" ComponentPropertyProperty
newValue ComponentPropertyProperty {Maybe [ComponentPropertyProperty]
Maybe (Map Text FormBindingElementProperty)
Maybe (Value Bool)
Maybe (Value Text)
Maybe ComponentPropertyBindingPropertiesProperty
Maybe ComponentConditionPropertyProperty
()
haddock_workaround_ :: ComponentPropertyProperty -> ()
bindingProperties :: ComponentPropertyProperty
-> Maybe ComponentPropertyBindingPropertiesProperty
bindings :: ComponentPropertyProperty
-> Maybe (Map Text FormBindingElementProperty)
collectionBindingProperties :: ComponentPropertyProperty
-> Maybe ComponentPropertyBindingPropertiesProperty
componentName :: ComponentPropertyProperty -> Maybe (Value Text)
concat :: ComponentPropertyProperty -> Maybe [ComponentPropertyProperty]
condition :: ComponentPropertyProperty
-> Maybe ComponentConditionPropertyProperty
configured :: ComponentPropertyProperty -> Maybe (Value Bool)
defaultValue :: ComponentPropertyProperty -> Maybe (Value Text)
event :: ComponentPropertyProperty -> Maybe (Value Text)
importedValue :: ComponentPropertyProperty -> Maybe (Value Text)
model :: ComponentPropertyProperty -> Maybe (Value Text)
property :: ComponentPropertyProperty -> Maybe (Value Text)
type' :: ComponentPropertyProperty -> Maybe (Value Text)
userAttribute :: ComponentPropertyProperty -> Maybe (Value Text)
value :: ComponentPropertyProperty -> Maybe (Value Text)
haddock_workaround_ :: ()
bindingProperties :: Maybe ComponentPropertyBindingPropertiesProperty
bindings :: Maybe (Map Text FormBindingElementProperty)
collectionBindingProperties :: Maybe ComponentPropertyBindingPropertiesProperty
componentName :: Maybe (Value Text)
concat :: Maybe [ComponentPropertyProperty]
condition :: Maybe ComponentConditionPropertyProperty
configured :: Maybe (Value Bool)
defaultValue :: Maybe (Value Text)
event :: Maybe (Value Text)
importedValue :: Maybe (Value Text)
model :: Maybe (Value Text)
property :: Maybe (Value Text)
type' :: Maybe (Value Text)
userAttribute :: Maybe (Value Text)
value :: Maybe (Value Text)
..}
= ComponentPropertyProperty {model :: Maybe (Value Text)
model = Value Text -> Maybe (Value Text)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "Model" ComponentPropertyProperty
Value Text
newValue, Maybe [ComponentPropertyProperty]
Maybe (Map Text FormBindingElementProperty)
Maybe (Value Bool)
Maybe (Value Text)
Maybe ComponentPropertyBindingPropertiesProperty
Maybe ComponentConditionPropertyProperty
()
haddock_workaround_ :: ()
bindingProperties :: Maybe ComponentPropertyBindingPropertiesProperty
bindings :: Maybe (Map Text FormBindingElementProperty)
collectionBindingProperties :: Maybe ComponentPropertyBindingPropertiesProperty
componentName :: Maybe (Value Text)
concat :: Maybe [ComponentPropertyProperty]
condition :: Maybe ComponentConditionPropertyProperty
configured :: Maybe (Value Bool)
defaultValue :: Maybe (Value Text)
event :: Maybe (Value Text)
importedValue :: Maybe (Value Text)
property :: Maybe (Value Text)
type' :: Maybe (Value Text)
userAttribute :: Maybe (Value Text)
value :: Maybe (Value Text)
haddock_workaround_ :: ()
bindingProperties :: Maybe ComponentPropertyBindingPropertiesProperty
bindings :: Maybe (Map Text FormBindingElementProperty)
collectionBindingProperties :: Maybe ComponentPropertyBindingPropertiesProperty
componentName :: Maybe (Value Text)
concat :: Maybe [ComponentPropertyProperty]
condition :: Maybe ComponentConditionPropertyProperty
configured :: Maybe (Value Bool)
defaultValue :: Maybe (Value Text)
event :: Maybe (Value Text)
importedValue :: Maybe (Value Text)
property :: Maybe (Value Text)
type' :: Maybe (Value Text)
userAttribute :: Maybe (Value Text)
value :: Maybe (Value Text)
..}
instance Property "Property" ComponentPropertyProperty where
type PropertyType "Property" ComponentPropertyProperty = Value Prelude.Text
set :: PropertyType "Property" ComponentPropertyProperty
-> ComponentPropertyProperty -> ComponentPropertyProperty
set PropertyType "Property" ComponentPropertyProperty
newValue ComponentPropertyProperty {Maybe [ComponentPropertyProperty]
Maybe (Map Text FormBindingElementProperty)
Maybe (Value Bool)
Maybe (Value Text)
Maybe ComponentPropertyBindingPropertiesProperty
Maybe ComponentConditionPropertyProperty
()
haddock_workaround_ :: ComponentPropertyProperty -> ()
bindingProperties :: ComponentPropertyProperty
-> Maybe ComponentPropertyBindingPropertiesProperty
bindings :: ComponentPropertyProperty
-> Maybe (Map Text FormBindingElementProperty)
collectionBindingProperties :: ComponentPropertyProperty
-> Maybe ComponentPropertyBindingPropertiesProperty
componentName :: ComponentPropertyProperty -> Maybe (Value Text)
concat :: ComponentPropertyProperty -> Maybe [ComponentPropertyProperty]
condition :: ComponentPropertyProperty
-> Maybe ComponentConditionPropertyProperty
configured :: ComponentPropertyProperty -> Maybe (Value Bool)
defaultValue :: ComponentPropertyProperty -> Maybe (Value Text)
event :: ComponentPropertyProperty -> Maybe (Value Text)
importedValue :: ComponentPropertyProperty -> Maybe (Value Text)
model :: ComponentPropertyProperty -> Maybe (Value Text)
property :: ComponentPropertyProperty -> Maybe (Value Text)
type' :: ComponentPropertyProperty -> Maybe (Value Text)
userAttribute :: ComponentPropertyProperty -> Maybe (Value Text)
value :: ComponentPropertyProperty -> Maybe (Value Text)
haddock_workaround_ :: ()
bindingProperties :: Maybe ComponentPropertyBindingPropertiesProperty
bindings :: Maybe (Map Text FormBindingElementProperty)
collectionBindingProperties :: Maybe ComponentPropertyBindingPropertiesProperty
componentName :: Maybe (Value Text)
concat :: Maybe [ComponentPropertyProperty]
condition :: Maybe ComponentConditionPropertyProperty
configured :: Maybe (Value Bool)
defaultValue :: Maybe (Value Text)
event :: Maybe (Value Text)
importedValue :: Maybe (Value Text)
model :: Maybe (Value Text)
property :: Maybe (Value Text)
type' :: Maybe (Value Text)
userAttribute :: Maybe (Value Text)
value :: Maybe (Value Text)
..}
= ComponentPropertyProperty {property :: Maybe (Value Text)
property = Value Text -> Maybe (Value Text)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "Property" ComponentPropertyProperty
Value Text
newValue, Maybe [ComponentPropertyProperty]
Maybe (Map Text FormBindingElementProperty)
Maybe (Value Bool)
Maybe (Value Text)
Maybe ComponentPropertyBindingPropertiesProperty
Maybe ComponentConditionPropertyProperty
()
haddock_workaround_ :: ()
bindingProperties :: Maybe ComponentPropertyBindingPropertiesProperty
bindings :: Maybe (Map Text FormBindingElementProperty)
collectionBindingProperties :: Maybe ComponentPropertyBindingPropertiesProperty
componentName :: Maybe (Value Text)
concat :: Maybe [ComponentPropertyProperty]
condition :: Maybe ComponentConditionPropertyProperty
configured :: Maybe (Value Bool)
defaultValue :: Maybe (Value Text)
event :: Maybe (Value Text)
importedValue :: Maybe (Value Text)
model :: Maybe (Value Text)
type' :: Maybe (Value Text)
userAttribute :: Maybe (Value Text)
value :: Maybe (Value Text)
haddock_workaround_ :: ()
bindingProperties :: Maybe ComponentPropertyBindingPropertiesProperty
bindings :: Maybe (Map Text FormBindingElementProperty)
collectionBindingProperties :: Maybe ComponentPropertyBindingPropertiesProperty
componentName :: Maybe (Value Text)
concat :: Maybe [ComponentPropertyProperty]
condition :: Maybe ComponentConditionPropertyProperty
configured :: Maybe (Value Bool)
defaultValue :: Maybe (Value Text)
event :: Maybe (Value Text)
importedValue :: Maybe (Value Text)
model :: Maybe (Value Text)
type' :: Maybe (Value Text)
userAttribute :: Maybe (Value Text)
value :: Maybe (Value Text)
..}
instance Property "Type" ComponentPropertyProperty where
type PropertyType "Type" ComponentPropertyProperty = Value Prelude.Text
set :: PropertyType "Type" ComponentPropertyProperty
-> ComponentPropertyProperty -> ComponentPropertyProperty
set PropertyType "Type" ComponentPropertyProperty
newValue ComponentPropertyProperty {Maybe [ComponentPropertyProperty]
Maybe (Map Text FormBindingElementProperty)
Maybe (Value Bool)
Maybe (Value Text)
Maybe ComponentPropertyBindingPropertiesProperty
Maybe ComponentConditionPropertyProperty
()
haddock_workaround_ :: ComponentPropertyProperty -> ()
bindingProperties :: ComponentPropertyProperty
-> Maybe ComponentPropertyBindingPropertiesProperty
bindings :: ComponentPropertyProperty
-> Maybe (Map Text FormBindingElementProperty)
collectionBindingProperties :: ComponentPropertyProperty
-> Maybe ComponentPropertyBindingPropertiesProperty
componentName :: ComponentPropertyProperty -> Maybe (Value Text)
concat :: ComponentPropertyProperty -> Maybe [ComponentPropertyProperty]
condition :: ComponentPropertyProperty
-> Maybe ComponentConditionPropertyProperty
configured :: ComponentPropertyProperty -> Maybe (Value Bool)
defaultValue :: ComponentPropertyProperty -> Maybe (Value Text)
event :: ComponentPropertyProperty -> Maybe (Value Text)
importedValue :: ComponentPropertyProperty -> Maybe (Value Text)
model :: ComponentPropertyProperty -> Maybe (Value Text)
property :: ComponentPropertyProperty -> Maybe (Value Text)
type' :: ComponentPropertyProperty -> Maybe (Value Text)
userAttribute :: ComponentPropertyProperty -> Maybe (Value Text)
value :: ComponentPropertyProperty -> Maybe (Value Text)
haddock_workaround_ :: ()
bindingProperties :: Maybe ComponentPropertyBindingPropertiesProperty
bindings :: Maybe (Map Text FormBindingElementProperty)
collectionBindingProperties :: Maybe ComponentPropertyBindingPropertiesProperty
componentName :: Maybe (Value Text)
concat :: Maybe [ComponentPropertyProperty]
condition :: Maybe ComponentConditionPropertyProperty
configured :: Maybe (Value Bool)
defaultValue :: Maybe (Value Text)
event :: Maybe (Value Text)
importedValue :: Maybe (Value Text)
model :: Maybe (Value Text)
property :: Maybe (Value Text)
type' :: Maybe (Value Text)
userAttribute :: Maybe (Value Text)
value :: Maybe (Value Text)
..}
= ComponentPropertyProperty {type' :: Maybe (Value Text)
type' = Value Text -> Maybe (Value Text)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "Type" ComponentPropertyProperty
Value Text
newValue, Maybe [ComponentPropertyProperty]
Maybe (Map Text FormBindingElementProperty)
Maybe (Value Bool)
Maybe (Value Text)
Maybe ComponentPropertyBindingPropertiesProperty
Maybe ComponentConditionPropertyProperty
()
haddock_workaround_ :: ()
bindingProperties :: Maybe ComponentPropertyBindingPropertiesProperty
bindings :: Maybe (Map Text FormBindingElementProperty)
collectionBindingProperties :: Maybe ComponentPropertyBindingPropertiesProperty
componentName :: Maybe (Value Text)
concat :: Maybe [ComponentPropertyProperty]
condition :: Maybe ComponentConditionPropertyProperty
configured :: Maybe (Value Bool)
defaultValue :: Maybe (Value Text)
event :: Maybe (Value Text)
importedValue :: Maybe (Value Text)
model :: Maybe (Value Text)
property :: Maybe (Value Text)
userAttribute :: Maybe (Value Text)
value :: Maybe (Value Text)
haddock_workaround_ :: ()
bindingProperties :: Maybe ComponentPropertyBindingPropertiesProperty
bindings :: Maybe (Map Text FormBindingElementProperty)
collectionBindingProperties :: Maybe ComponentPropertyBindingPropertiesProperty
componentName :: Maybe (Value Text)
concat :: Maybe [ComponentPropertyProperty]
condition :: Maybe ComponentConditionPropertyProperty
configured :: Maybe (Value Bool)
defaultValue :: Maybe (Value Text)
event :: Maybe (Value Text)
importedValue :: Maybe (Value Text)
model :: Maybe (Value Text)
property :: Maybe (Value Text)
userAttribute :: Maybe (Value Text)
value :: Maybe (Value Text)
..}
instance Property "UserAttribute" ComponentPropertyProperty where
type PropertyType "UserAttribute" ComponentPropertyProperty = Value Prelude.Text
set :: PropertyType "UserAttribute" ComponentPropertyProperty
-> ComponentPropertyProperty -> ComponentPropertyProperty
set PropertyType "UserAttribute" ComponentPropertyProperty
newValue ComponentPropertyProperty {Maybe [ComponentPropertyProperty]
Maybe (Map Text FormBindingElementProperty)
Maybe (Value Bool)
Maybe (Value Text)
Maybe ComponentPropertyBindingPropertiesProperty
Maybe ComponentConditionPropertyProperty
()
haddock_workaround_ :: ComponentPropertyProperty -> ()
bindingProperties :: ComponentPropertyProperty
-> Maybe ComponentPropertyBindingPropertiesProperty
bindings :: ComponentPropertyProperty
-> Maybe (Map Text FormBindingElementProperty)
collectionBindingProperties :: ComponentPropertyProperty
-> Maybe ComponentPropertyBindingPropertiesProperty
componentName :: ComponentPropertyProperty -> Maybe (Value Text)
concat :: ComponentPropertyProperty -> Maybe [ComponentPropertyProperty]
condition :: ComponentPropertyProperty
-> Maybe ComponentConditionPropertyProperty
configured :: ComponentPropertyProperty -> Maybe (Value Bool)
defaultValue :: ComponentPropertyProperty -> Maybe (Value Text)
event :: ComponentPropertyProperty -> Maybe (Value Text)
importedValue :: ComponentPropertyProperty -> Maybe (Value Text)
model :: ComponentPropertyProperty -> Maybe (Value Text)
property :: ComponentPropertyProperty -> Maybe (Value Text)
type' :: ComponentPropertyProperty -> Maybe (Value Text)
userAttribute :: ComponentPropertyProperty -> Maybe (Value Text)
value :: ComponentPropertyProperty -> Maybe (Value Text)
haddock_workaround_ :: ()
bindingProperties :: Maybe ComponentPropertyBindingPropertiesProperty
bindings :: Maybe (Map Text FormBindingElementProperty)
collectionBindingProperties :: Maybe ComponentPropertyBindingPropertiesProperty
componentName :: Maybe (Value Text)
concat :: Maybe [ComponentPropertyProperty]
condition :: Maybe ComponentConditionPropertyProperty
configured :: Maybe (Value Bool)
defaultValue :: Maybe (Value Text)
event :: Maybe (Value Text)
importedValue :: Maybe (Value Text)
model :: Maybe (Value Text)
property :: Maybe (Value Text)
type' :: Maybe (Value Text)
userAttribute :: Maybe (Value Text)
value :: Maybe (Value Text)
..}
= ComponentPropertyProperty
{userAttribute :: Maybe (Value Text)
userAttribute = Value Text -> Maybe (Value Text)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "UserAttribute" ComponentPropertyProperty
Value Text
newValue, Maybe [ComponentPropertyProperty]
Maybe (Map Text FormBindingElementProperty)
Maybe (Value Bool)
Maybe (Value Text)
Maybe ComponentPropertyBindingPropertiesProperty
Maybe ComponentConditionPropertyProperty
()
haddock_workaround_ :: ()
bindingProperties :: Maybe ComponentPropertyBindingPropertiesProperty
bindings :: Maybe (Map Text FormBindingElementProperty)
collectionBindingProperties :: Maybe ComponentPropertyBindingPropertiesProperty
componentName :: Maybe (Value Text)
concat :: Maybe [ComponentPropertyProperty]
condition :: Maybe ComponentConditionPropertyProperty
configured :: Maybe (Value Bool)
defaultValue :: Maybe (Value Text)
event :: Maybe (Value Text)
importedValue :: Maybe (Value Text)
model :: Maybe (Value Text)
property :: Maybe (Value Text)
type' :: Maybe (Value Text)
value :: Maybe (Value Text)
haddock_workaround_ :: ()
bindingProperties :: Maybe ComponentPropertyBindingPropertiesProperty
bindings :: Maybe (Map Text FormBindingElementProperty)
collectionBindingProperties :: Maybe ComponentPropertyBindingPropertiesProperty
componentName :: Maybe (Value Text)
concat :: Maybe [ComponentPropertyProperty]
condition :: Maybe ComponentConditionPropertyProperty
configured :: Maybe (Value Bool)
defaultValue :: Maybe (Value Text)
event :: Maybe (Value Text)
importedValue :: Maybe (Value Text)
model :: Maybe (Value Text)
property :: Maybe (Value Text)
type' :: Maybe (Value Text)
value :: Maybe (Value Text)
..}
instance Property "Value" ComponentPropertyProperty where
type PropertyType "Value" ComponentPropertyProperty = Value Prelude.Text
set :: PropertyType "Value" ComponentPropertyProperty
-> ComponentPropertyProperty -> ComponentPropertyProperty
set PropertyType "Value" ComponentPropertyProperty
newValue ComponentPropertyProperty {Maybe [ComponentPropertyProperty]
Maybe (Map Text FormBindingElementProperty)
Maybe (Value Bool)
Maybe (Value Text)
Maybe ComponentPropertyBindingPropertiesProperty
Maybe ComponentConditionPropertyProperty
()
haddock_workaround_ :: ComponentPropertyProperty -> ()
bindingProperties :: ComponentPropertyProperty
-> Maybe ComponentPropertyBindingPropertiesProperty
bindings :: ComponentPropertyProperty
-> Maybe (Map Text FormBindingElementProperty)
collectionBindingProperties :: ComponentPropertyProperty
-> Maybe ComponentPropertyBindingPropertiesProperty
componentName :: ComponentPropertyProperty -> Maybe (Value Text)
concat :: ComponentPropertyProperty -> Maybe [ComponentPropertyProperty]
condition :: ComponentPropertyProperty
-> Maybe ComponentConditionPropertyProperty
configured :: ComponentPropertyProperty -> Maybe (Value Bool)
defaultValue :: ComponentPropertyProperty -> Maybe (Value Text)
event :: ComponentPropertyProperty -> Maybe (Value Text)
importedValue :: ComponentPropertyProperty -> Maybe (Value Text)
model :: ComponentPropertyProperty -> Maybe (Value Text)
property :: ComponentPropertyProperty -> Maybe (Value Text)
type' :: ComponentPropertyProperty -> Maybe (Value Text)
userAttribute :: ComponentPropertyProperty -> Maybe (Value Text)
value :: ComponentPropertyProperty -> Maybe (Value Text)
haddock_workaround_ :: ()
bindingProperties :: Maybe ComponentPropertyBindingPropertiesProperty
bindings :: Maybe (Map Text FormBindingElementProperty)
collectionBindingProperties :: Maybe ComponentPropertyBindingPropertiesProperty
componentName :: Maybe (Value Text)
concat :: Maybe [ComponentPropertyProperty]
condition :: Maybe ComponentConditionPropertyProperty
configured :: Maybe (Value Bool)
defaultValue :: Maybe (Value Text)
event :: Maybe (Value Text)
importedValue :: Maybe (Value Text)
model :: Maybe (Value Text)
property :: Maybe (Value Text)
type' :: Maybe (Value Text)
userAttribute :: Maybe (Value Text)
value :: Maybe (Value Text)
..}
= ComponentPropertyProperty {value :: Maybe (Value Text)
value = Value Text -> Maybe (Value Text)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "Value" ComponentPropertyProperty
Value Text
newValue, Maybe [ComponentPropertyProperty]
Maybe (Map Text FormBindingElementProperty)
Maybe (Value Bool)
Maybe (Value Text)
Maybe ComponentPropertyBindingPropertiesProperty
Maybe ComponentConditionPropertyProperty
()
haddock_workaround_ :: ()
bindingProperties :: Maybe ComponentPropertyBindingPropertiesProperty
bindings :: Maybe (Map Text FormBindingElementProperty)
collectionBindingProperties :: Maybe ComponentPropertyBindingPropertiesProperty
componentName :: Maybe (Value Text)
concat :: Maybe [ComponentPropertyProperty]
condition :: Maybe ComponentConditionPropertyProperty
configured :: Maybe (Value Bool)
defaultValue :: Maybe (Value Text)
event :: Maybe (Value Text)
importedValue :: Maybe (Value Text)
model :: Maybe (Value Text)
property :: Maybe (Value Text)
type' :: Maybe (Value Text)
userAttribute :: Maybe (Value Text)
haddock_workaround_ :: ()
bindingProperties :: Maybe ComponentPropertyBindingPropertiesProperty
bindings :: Maybe (Map Text FormBindingElementProperty)
collectionBindingProperties :: Maybe ComponentPropertyBindingPropertiesProperty
componentName :: Maybe (Value Text)
concat :: Maybe [ComponentPropertyProperty]
condition :: Maybe ComponentConditionPropertyProperty
configured :: Maybe (Value Bool)
defaultValue :: Maybe (Value Text)
event :: Maybe (Value Text)
importedValue :: Maybe (Value Text)
model :: Maybe (Value Text)
property :: Maybe (Value Text)
type' :: Maybe (Value Text)
userAttribute :: Maybe (Value Text)
..}