module Stratosphere.AmplifyUIBuilder.Form.FormInputValuePropertyProperty (
module Exports, FormInputValuePropertyProperty(..),
mkFormInputValuePropertyProperty
) where
import qualified Data.Aeson as JSON
import qualified Stratosphere.Prelude as Prelude
import Stratosphere.Property
import {-# SOURCE #-} Stratosphere.AmplifyUIBuilder.Form.FormInputValuePropertyBindingPropertiesProperty as Exports
import Stratosphere.ResourceProperties
import Stratosphere.Value
data FormInputValuePropertyProperty
=
FormInputValuePropertyProperty {FormInputValuePropertyProperty -> ()
haddock_workaround_ :: (),
FormInputValuePropertyProperty
-> Maybe FormInputValuePropertyBindingPropertiesProperty
bindingProperties :: (Prelude.Maybe FormInputValuePropertyBindingPropertiesProperty),
FormInputValuePropertyProperty
-> Maybe [FormInputValuePropertyProperty]
concat :: (Prelude.Maybe [FormInputValuePropertyProperty]),
FormInputValuePropertyProperty -> Maybe (Value Text)
value :: (Prelude.Maybe (Value Prelude.Text))}
deriving stock (FormInputValuePropertyProperty
-> FormInputValuePropertyProperty -> Bool
(FormInputValuePropertyProperty
-> FormInputValuePropertyProperty -> Bool)
-> (FormInputValuePropertyProperty
-> FormInputValuePropertyProperty -> Bool)
-> Eq FormInputValuePropertyProperty
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: FormInputValuePropertyProperty
-> FormInputValuePropertyProperty -> Bool
== :: FormInputValuePropertyProperty
-> FormInputValuePropertyProperty -> Bool
$c/= :: FormInputValuePropertyProperty
-> FormInputValuePropertyProperty -> Bool
/= :: FormInputValuePropertyProperty
-> FormInputValuePropertyProperty -> Bool
Prelude.Eq, Int -> FormInputValuePropertyProperty -> ShowS
[FormInputValuePropertyProperty] -> ShowS
FormInputValuePropertyProperty -> String
(Int -> FormInputValuePropertyProperty -> ShowS)
-> (FormInputValuePropertyProperty -> String)
-> ([FormInputValuePropertyProperty] -> ShowS)
-> Show FormInputValuePropertyProperty
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> FormInputValuePropertyProperty -> ShowS
showsPrec :: Int -> FormInputValuePropertyProperty -> ShowS
$cshow :: FormInputValuePropertyProperty -> String
show :: FormInputValuePropertyProperty -> String
$cshowList :: [FormInputValuePropertyProperty] -> ShowS
showList :: [FormInputValuePropertyProperty] -> ShowS
Prelude.Show)
mkFormInputValuePropertyProperty :: FormInputValuePropertyProperty
mkFormInputValuePropertyProperty :: FormInputValuePropertyProperty
mkFormInputValuePropertyProperty
= FormInputValuePropertyProperty
{haddock_workaround_ :: ()
haddock_workaround_ = (), bindingProperties :: Maybe FormInputValuePropertyBindingPropertiesProperty
bindingProperties = Maybe FormInputValuePropertyBindingPropertiesProperty
forall a. Maybe a
Prelude.Nothing,
concat :: Maybe [FormInputValuePropertyProperty]
concat = Maybe [FormInputValuePropertyProperty]
forall a. Maybe a
Prelude.Nothing, value :: Maybe (Value Text)
value = Maybe (Value Text)
forall a. Maybe a
Prelude.Nothing}
instance ToResourceProperties FormInputValuePropertyProperty where
toResourceProperties :: FormInputValuePropertyProperty -> ResourceProperties
toResourceProperties FormInputValuePropertyProperty {Maybe [FormInputValuePropertyProperty]
Maybe (Value Text)
Maybe FormInputValuePropertyBindingPropertiesProperty
()
haddock_workaround_ :: FormInputValuePropertyProperty -> ()
bindingProperties :: FormInputValuePropertyProperty
-> Maybe FormInputValuePropertyBindingPropertiesProperty
concat :: FormInputValuePropertyProperty
-> Maybe [FormInputValuePropertyProperty]
value :: FormInputValuePropertyProperty -> Maybe (Value Text)
haddock_workaround_ :: ()
bindingProperties :: Maybe FormInputValuePropertyBindingPropertiesProperty
concat :: Maybe [FormInputValuePropertyProperty]
value :: Maybe (Value Text)
..}
= ResourceProperties
{awsType :: Text
awsType = Text
"AWS::AmplifyUIBuilder::Form.FormInputValueProperty",
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
-> FormInputValuePropertyBindingPropertiesProperty -> (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" (FormInputValuePropertyBindingPropertiesProperty -> (Key, Value))
-> Maybe FormInputValuePropertyBindingPropertiesProperty
-> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe FormInputValuePropertyBindingPropertiesProperty
bindingProperties,
Key -> [FormInputValuePropertyProperty] -> (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" ([FormInputValuePropertyProperty] -> (Key, Value))
-> Maybe [FormInputValuePropertyProperty] -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [FormInputValuePropertyProperty]
concat,
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 FormInputValuePropertyProperty where
toJSON :: FormInputValuePropertyProperty -> Value
toJSON FormInputValuePropertyProperty {Maybe [FormInputValuePropertyProperty]
Maybe (Value Text)
Maybe FormInputValuePropertyBindingPropertiesProperty
()
haddock_workaround_ :: FormInputValuePropertyProperty -> ()
bindingProperties :: FormInputValuePropertyProperty
-> Maybe FormInputValuePropertyBindingPropertiesProperty
concat :: FormInputValuePropertyProperty
-> Maybe [FormInputValuePropertyProperty]
value :: FormInputValuePropertyProperty -> Maybe (Value Text)
haddock_workaround_ :: ()
bindingProperties :: Maybe FormInputValuePropertyBindingPropertiesProperty
concat :: Maybe [FormInputValuePropertyProperty]
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
-> FormInputValuePropertyBindingPropertiesProperty -> (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" (FormInputValuePropertyBindingPropertiesProperty -> (Key, Value))
-> Maybe FormInputValuePropertyBindingPropertiesProperty
-> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe FormInputValuePropertyBindingPropertiesProperty
bindingProperties,
Key -> [FormInputValuePropertyProperty] -> (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" ([FormInputValuePropertyProperty] -> (Key, Value))
-> Maybe [FormInputValuePropertyProperty] -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [FormInputValuePropertyProperty]
concat,
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" FormInputValuePropertyProperty where
type PropertyType "BindingProperties" FormInputValuePropertyProperty = FormInputValuePropertyBindingPropertiesProperty
set :: PropertyType "BindingProperties" FormInputValuePropertyProperty
-> FormInputValuePropertyProperty -> FormInputValuePropertyProperty
set PropertyType "BindingProperties" FormInputValuePropertyProperty
newValue FormInputValuePropertyProperty {Maybe [FormInputValuePropertyProperty]
Maybe (Value Text)
Maybe FormInputValuePropertyBindingPropertiesProperty
()
haddock_workaround_ :: FormInputValuePropertyProperty -> ()
bindingProperties :: FormInputValuePropertyProperty
-> Maybe FormInputValuePropertyBindingPropertiesProperty
concat :: FormInputValuePropertyProperty
-> Maybe [FormInputValuePropertyProperty]
value :: FormInputValuePropertyProperty -> Maybe (Value Text)
haddock_workaround_ :: ()
bindingProperties :: Maybe FormInputValuePropertyBindingPropertiesProperty
concat :: Maybe [FormInputValuePropertyProperty]
value :: Maybe (Value Text)
..}
= FormInputValuePropertyProperty
{bindingProperties :: Maybe FormInputValuePropertyBindingPropertiesProperty
bindingProperties = FormInputValuePropertyBindingPropertiesProperty
-> Maybe FormInputValuePropertyBindingPropertiesProperty
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "BindingProperties" FormInputValuePropertyProperty
FormInputValuePropertyBindingPropertiesProperty
newValue, Maybe [FormInputValuePropertyProperty]
Maybe (Value Text)
()
haddock_workaround_ :: ()
concat :: Maybe [FormInputValuePropertyProperty]
value :: Maybe (Value Text)
haddock_workaround_ :: ()
concat :: Maybe [FormInputValuePropertyProperty]
value :: Maybe (Value Text)
..}
instance Property "Concat" FormInputValuePropertyProperty where
type PropertyType "Concat" FormInputValuePropertyProperty = [FormInputValuePropertyProperty]
set :: PropertyType "Concat" FormInputValuePropertyProperty
-> FormInputValuePropertyProperty -> FormInputValuePropertyProperty
set PropertyType "Concat" FormInputValuePropertyProperty
newValue FormInputValuePropertyProperty {Maybe [FormInputValuePropertyProperty]
Maybe (Value Text)
Maybe FormInputValuePropertyBindingPropertiesProperty
()
haddock_workaround_ :: FormInputValuePropertyProperty -> ()
bindingProperties :: FormInputValuePropertyProperty
-> Maybe FormInputValuePropertyBindingPropertiesProperty
concat :: FormInputValuePropertyProperty
-> Maybe [FormInputValuePropertyProperty]
value :: FormInputValuePropertyProperty -> Maybe (Value Text)
haddock_workaround_ :: ()
bindingProperties :: Maybe FormInputValuePropertyBindingPropertiesProperty
concat :: Maybe [FormInputValuePropertyProperty]
value :: Maybe (Value Text)
..}
= FormInputValuePropertyProperty
{concat :: Maybe [FormInputValuePropertyProperty]
concat = [FormInputValuePropertyProperty]
-> Maybe [FormInputValuePropertyProperty]
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure [FormInputValuePropertyProperty]
PropertyType "Concat" FormInputValuePropertyProperty
newValue, Maybe (Value Text)
Maybe FormInputValuePropertyBindingPropertiesProperty
()
haddock_workaround_ :: ()
bindingProperties :: Maybe FormInputValuePropertyBindingPropertiesProperty
value :: Maybe (Value Text)
haddock_workaround_ :: ()
bindingProperties :: Maybe FormInputValuePropertyBindingPropertiesProperty
value :: Maybe (Value Text)
..}
instance Property "Value" FormInputValuePropertyProperty where
type PropertyType "Value" FormInputValuePropertyProperty = Value Prelude.Text
set :: PropertyType "Value" FormInputValuePropertyProperty
-> FormInputValuePropertyProperty -> FormInputValuePropertyProperty
set PropertyType "Value" FormInputValuePropertyProperty
newValue FormInputValuePropertyProperty {Maybe [FormInputValuePropertyProperty]
Maybe (Value Text)
Maybe FormInputValuePropertyBindingPropertiesProperty
()
haddock_workaround_ :: FormInputValuePropertyProperty -> ()
bindingProperties :: FormInputValuePropertyProperty
-> Maybe FormInputValuePropertyBindingPropertiesProperty
concat :: FormInputValuePropertyProperty
-> Maybe [FormInputValuePropertyProperty]
value :: FormInputValuePropertyProperty -> Maybe (Value Text)
haddock_workaround_ :: ()
bindingProperties :: Maybe FormInputValuePropertyBindingPropertiesProperty
concat :: Maybe [FormInputValuePropertyProperty]
value :: Maybe (Value Text)
..}
= FormInputValuePropertyProperty
{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" FormInputValuePropertyProperty
Value Text
newValue, Maybe [FormInputValuePropertyProperty]
Maybe FormInputValuePropertyBindingPropertiesProperty
()
haddock_workaround_ :: ()
bindingProperties :: Maybe FormInputValuePropertyBindingPropertiesProperty
concat :: Maybe [FormInputValuePropertyProperty]
haddock_workaround_ :: ()
bindingProperties :: Maybe FormInputValuePropertyBindingPropertiesProperty
concat :: Maybe [FormInputValuePropertyProperty]
..}