module Stratosphere.AmplifyUIBuilder.Form.FieldConfigProperty (
module Exports, FieldConfigProperty(..), mkFieldConfigProperty
) where
import qualified Data.Aeson as JSON
import qualified Stratosphere.Prelude as Prelude
import Stratosphere.Property
import {-# SOURCE #-} Stratosphere.AmplifyUIBuilder.Form.FieldInputConfigProperty as Exports
import {-# SOURCE #-} Stratosphere.AmplifyUIBuilder.Form.FieldPositionProperty as Exports
import {-# SOURCE #-} Stratosphere.AmplifyUIBuilder.Form.FieldValidationConfigurationProperty as Exports
import Stratosphere.ResourceProperties
import Stratosphere.Value
data FieldConfigProperty
=
FieldConfigProperty {FieldConfigProperty -> ()
haddock_workaround_ :: (),
FieldConfigProperty -> Maybe (Value Bool)
excluded :: (Prelude.Maybe (Value Prelude.Bool)),
FieldConfigProperty -> Maybe FieldInputConfigProperty
inputType :: (Prelude.Maybe FieldInputConfigProperty),
FieldConfigProperty -> Maybe (Value Text)
label :: (Prelude.Maybe (Value Prelude.Text)),
FieldConfigProperty -> Maybe FieldPositionProperty
position :: (Prelude.Maybe FieldPositionProperty),
FieldConfigProperty -> Maybe [FieldValidationConfigurationProperty]
validations :: (Prelude.Maybe [FieldValidationConfigurationProperty])}
deriving stock (FieldConfigProperty -> FieldConfigProperty -> Bool
(FieldConfigProperty -> FieldConfigProperty -> Bool)
-> (FieldConfigProperty -> FieldConfigProperty -> Bool)
-> Eq FieldConfigProperty
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: FieldConfigProperty -> FieldConfigProperty -> Bool
== :: FieldConfigProperty -> FieldConfigProperty -> Bool
$c/= :: FieldConfigProperty -> FieldConfigProperty -> Bool
/= :: FieldConfigProperty -> FieldConfigProperty -> Bool
Prelude.Eq, Int -> FieldConfigProperty -> ShowS
[FieldConfigProperty] -> ShowS
FieldConfigProperty -> String
(Int -> FieldConfigProperty -> ShowS)
-> (FieldConfigProperty -> String)
-> ([FieldConfigProperty] -> ShowS)
-> Show FieldConfigProperty
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> FieldConfigProperty -> ShowS
showsPrec :: Int -> FieldConfigProperty -> ShowS
$cshow :: FieldConfigProperty -> String
show :: FieldConfigProperty -> String
$cshowList :: [FieldConfigProperty] -> ShowS
showList :: [FieldConfigProperty] -> ShowS
Prelude.Show)
mkFieldConfigProperty :: FieldConfigProperty
mkFieldConfigProperty :: FieldConfigProperty
mkFieldConfigProperty
= FieldConfigProperty
{haddock_workaround_ :: ()
haddock_workaround_ = (), excluded :: Maybe (Value Bool)
excluded = Maybe (Value Bool)
forall a. Maybe a
Prelude.Nothing,
inputType :: Maybe FieldInputConfigProperty
inputType = Maybe FieldInputConfigProperty
forall a. Maybe a
Prelude.Nothing, label :: Maybe (Value Text)
label = Maybe (Value Text)
forall a. Maybe a
Prelude.Nothing,
position :: Maybe FieldPositionProperty
position = Maybe FieldPositionProperty
forall a. Maybe a
Prelude.Nothing, validations :: Maybe [FieldValidationConfigurationProperty]
validations = Maybe [FieldValidationConfigurationProperty]
forall a. Maybe a
Prelude.Nothing}
instance ToResourceProperties FieldConfigProperty where
toResourceProperties :: FieldConfigProperty -> ResourceProperties
toResourceProperties FieldConfigProperty {Maybe [FieldValidationConfigurationProperty]
Maybe (Value Bool)
Maybe (Value Text)
Maybe FieldPositionProperty
Maybe FieldInputConfigProperty
()
haddock_workaround_ :: FieldConfigProperty -> ()
excluded :: FieldConfigProperty -> Maybe (Value Bool)
inputType :: FieldConfigProperty -> Maybe FieldInputConfigProperty
label :: FieldConfigProperty -> Maybe (Value Text)
position :: FieldConfigProperty -> Maybe FieldPositionProperty
validations :: FieldConfigProperty -> Maybe [FieldValidationConfigurationProperty]
haddock_workaround_ :: ()
excluded :: Maybe (Value Bool)
inputType :: Maybe FieldInputConfigProperty
label :: Maybe (Value Text)
position :: Maybe FieldPositionProperty
validations :: Maybe [FieldValidationConfigurationProperty]
..}
= ResourceProperties
{awsType :: Text
awsType = Text
"AWS::AmplifyUIBuilder::Form.FieldConfig",
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 -> 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
"Excluded" (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)
excluded,
Key -> FieldInputConfigProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"InputType" (FieldInputConfigProperty -> (Key, Value))
-> Maybe FieldInputConfigProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe FieldInputConfigProperty
inputType,
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
"Label" (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)
label,
Key -> FieldPositionProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"Position" (FieldPositionProperty -> (Key, Value))
-> Maybe FieldPositionProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe FieldPositionProperty
position,
Key -> [FieldValidationConfigurationProperty] -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"Validations" ([FieldValidationConfigurationProperty] -> (Key, Value))
-> Maybe [FieldValidationConfigurationProperty]
-> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [FieldValidationConfigurationProperty]
validations])}
instance JSON.ToJSON FieldConfigProperty where
toJSON :: FieldConfigProperty -> Value
toJSON FieldConfigProperty {Maybe [FieldValidationConfigurationProperty]
Maybe (Value Bool)
Maybe (Value Text)
Maybe FieldPositionProperty
Maybe FieldInputConfigProperty
()
haddock_workaround_ :: FieldConfigProperty -> ()
excluded :: FieldConfigProperty -> Maybe (Value Bool)
inputType :: FieldConfigProperty -> Maybe FieldInputConfigProperty
label :: FieldConfigProperty -> Maybe (Value Text)
position :: FieldConfigProperty -> Maybe FieldPositionProperty
validations :: FieldConfigProperty -> Maybe [FieldValidationConfigurationProperty]
haddock_workaround_ :: ()
excluded :: Maybe (Value Bool)
inputType :: Maybe FieldInputConfigProperty
label :: Maybe (Value Text)
position :: Maybe FieldPositionProperty
validations :: Maybe [FieldValidationConfigurationProperty]
..}
= [(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 -> 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
"Excluded" (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)
excluded,
Key -> FieldInputConfigProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"InputType" (FieldInputConfigProperty -> (Key, Value))
-> Maybe FieldInputConfigProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe FieldInputConfigProperty
inputType,
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
"Label" (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)
label,
Key -> FieldPositionProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"Position" (FieldPositionProperty -> (Key, Value))
-> Maybe FieldPositionProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe FieldPositionProperty
position,
Key -> [FieldValidationConfigurationProperty] -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"Validations" ([FieldValidationConfigurationProperty] -> (Key, Value))
-> Maybe [FieldValidationConfigurationProperty]
-> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [FieldValidationConfigurationProperty]
validations]))
instance Property "Excluded" FieldConfigProperty where
type PropertyType "Excluded" FieldConfigProperty = Value Prelude.Bool
set :: PropertyType "Excluded" FieldConfigProperty
-> FieldConfigProperty -> FieldConfigProperty
set PropertyType "Excluded" FieldConfigProperty
newValue FieldConfigProperty {Maybe [FieldValidationConfigurationProperty]
Maybe (Value Bool)
Maybe (Value Text)
Maybe FieldPositionProperty
Maybe FieldInputConfigProperty
()
haddock_workaround_ :: FieldConfigProperty -> ()
excluded :: FieldConfigProperty -> Maybe (Value Bool)
inputType :: FieldConfigProperty -> Maybe FieldInputConfigProperty
label :: FieldConfigProperty -> Maybe (Value Text)
position :: FieldConfigProperty -> Maybe FieldPositionProperty
validations :: FieldConfigProperty -> Maybe [FieldValidationConfigurationProperty]
haddock_workaround_ :: ()
excluded :: Maybe (Value Bool)
inputType :: Maybe FieldInputConfigProperty
label :: Maybe (Value Text)
position :: Maybe FieldPositionProperty
validations :: Maybe [FieldValidationConfigurationProperty]
..}
= FieldConfigProperty {excluded :: Maybe (Value Bool)
excluded = Value Bool -> Maybe (Value Bool)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "Excluded" FieldConfigProperty
Value Bool
newValue, Maybe [FieldValidationConfigurationProperty]
Maybe (Value Text)
Maybe FieldPositionProperty
Maybe FieldInputConfigProperty
()
haddock_workaround_ :: ()
inputType :: Maybe FieldInputConfigProperty
label :: Maybe (Value Text)
position :: Maybe FieldPositionProperty
validations :: Maybe [FieldValidationConfigurationProperty]
haddock_workaround_ :: ()
inputType :: Maybe FieldInputConfigProperty
label :: Maybe (Value Text)
position :: Maybe FieldPositionProperty
validations :: Maybe [FieldValidationConfigurationProperty]
..}
instance Property "InputType" FieldConfigProperty where
type PropertyType "InputType" FieldConfigProperty = FieldInputConfigProperty
set :: PropertyType "InputType" FieldConfigProperty
-> FieldConfigProperty -> FieldConfigProperty
set PropertyType "InputType" FieldConfigProperty
newValue FieldConfigProperty {Maybe [FieldValidationConfigurationProperty]
Maybe (Value Bool)
Maybe (Value Text)
Maybe FieldPositionProperty
Maybe FieldInputConfigProperty
()
haddock_workaround_ :: FieldConfigProperty -> ()
excluded :: FieldConfigProperty -> Maybe (Value Bool)
inputType :: FieldConfigProperty -> Maybe FieldInputConfigProperty
label :: FieldConfigProperty -> Maybe (Value Text)
position :: FieldConfigProperty -> Maybe FieldPositionProperty
validations :: FieldConfigProperty -> Maybe [FieldValidationConfigurationProperty]
haddock_workaround_ :: ()
excluded :: Maybe (Value Bool)
inputType :: Maybe FieldInputConfigProperty
label :: Maybe (Value Text)
position :: Maybe FieldPositionProperty
validations :: Maybe [FieldValidationConfigurationProperty]
..}
= FieldConfigProperty {inputType :: Maybe FieldInputConfigProperty
inputType = FieldInputConfigProperty -> Maybe FieldInputConfigProperty
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "InputType" FieldConfigProperty
FieldInputConfigProperty
newValue, Maybe [FieldValidationConfigurationProperty]
Maybe (Value Bool)
Maybe (Value Text)
Maybe FieldPositionProperty
()
haddock_workaround_ :: ()
excluded :: Maybe (Value Bool)
label :: Maybe (Value Text)
position :: Maybe FieldPositionProperty
validations :: Maybe [FieldValidationConfigurationProperty]
haddock_workaround_ :: ()
excluded :: Maybe (Value Bool)
label :: Maybe (Value Text)
position :: Maybe FieldPositionProperty
validations :: Maybe [FieldValidationConfigurationProperty]
..}
instance Property "Label" FieldConfigProperty where
type PropertyType "Label" FieldConfigProperty = Value Prelude.Text
set :: PropertyType "Label" FieldConfigProperty
-> FieldConfigProperty -> FieldConfigProperty
set PropertyType "Label" FieldConfigProperty
newValue FieldConfigProperty {Maybe [FieldValidationConfigurationProperty]
Maybe (Value Bool)
Maybe (Value Text)
Maybe FieldPositionProperty
Maybe FieldInputConfigProperty
()
haddock_workaround_ :: FieldConfigProperty -> ()
excluded :: FieldConfigProperty -> Maybe (Value Bool)
inputType :: FieldConfigProperty -> Maybe FieldInputConfigProperty
label :: FieldConfigProperty -> Maybe (Value Text)
position :: FieldConfigProperty -> Maybe FieldPositionProperty
validations :: FieldConfigProperty -> Maybe [FieldValidationConfigurationProperty]
haddock_workaround_ :: ()
excluded :: Maybe (Value Bool)
inputType :: Maybe FieldInputConfigProperty
label :: Maybe (Value Text)
position :: Maybe FieldPositionProperty
validations :: Maybe [FieldValidationConfigurationProperty]
..}
= FieldConfigProperty {label :: Maybe (Value Text)
label = Value Text -> Maybe (Value Text)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "Label" FieldConfigProperty
Value Text
newValue, Maybe [FieldValidationConfigurationProperty]
Maybe (Value Bool)
Maybe FieldPositionProperty
Maybe FieldInputConfigProperty
()
haddock_workaround_ :: ()
excluded :: Maybe (Value Bool)
inputType :: Maybe FieldInputConfigProperty
position :: Maybe FieldPositionProperty
validations :: Maybe [FieldValidationConfigurationProperty]
haddock_workaround_ :: ()
excluded :: Maybe (Value Bool)
inputType :: Maybe FieldInputConfigProperty
position :: Maybe FieldPositionProperty
validations :: Maybe [FieldValidationConfigurationProperty]
..}
instance Property "Position" FieldConfigProperty where
type PropertyType "Position" FieldConfigProperty = FieldPositionProperty
set :: PropertyType "Position" FieldConfigProperty
-> FieldConfigProperty -> FieldConfigProperty
set PropertyType "Position" FieldConfigProperty
newValue FieldConfigProperty {Maybe [FieldValidationConfigurationProperty]
Maybe (Value Bool)
Maybe (Value Text)
Maybe FieldPositionProperty
Maybe FieldInputConfigProperty
()
haddock_workaround_ :: FieldConfigProperty -> ()
excluded :: FieldConfigProperty -> Maybe (Value Bool)
inputType :: FieldConfigProperty -> Maybe FieldInputConfigProperty
label :: FieldConfigProperty -> Maybe (Value Text)
position :: FieldConfigProperty -> Maybe FieldPositionProperty
validations :: FieldConfigProperty -> Maybe [FieldValidationConfigurationProperty]
haddock_workaround_ :: ()
excluded :: Maybe (Value Bool)
inputType :: Maybe FieldInputConfigProperty
label :: Maybe (Value Text)
position :: Maybe FieldPositionProperty
validations :: Maybe [FieldValidationConfigurationProperty]
..}
= FieldConfigProperty {position :: Maybe FieldPositionProperty
position = FieldPositionProperty -> Maybe FieldPositionProperty
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "Position" FieldConfigProperty
FieldPositionProperty
newValue, Maybe [FieldValidationConfigurationProperty]
Maybe (Value Bool)
Maybe (Value Text)
Maybe FieldInputConfigProperty
()
haddock_workaround_ :: ()
excluded :: Maybe (Value Bool)
inputType :: Maybe FieldInputConfigProperty
label :: Maybe (Value Text)
validations :: Maybe [FieldValidationConfigurationProperty]
haddock_workaround_ :: ()
excluded :: Maybe (Value Bool)
inputType :: Maybe FieldInputConfigProperty
label :: Maybe (Value Text)
validations :: Maybe [FieldValidationConfigurationProperty]
..}
instance Property "Validations" FieldConfigProperty where
type PropertyType "Validations" FieldConfigProperty = [FieldValidationConfigurationProperty]
set :: PropertyType "Validations" FieldConfigProperty
-> FieldConfigProperty -> FieldConfigProperty
set PropertyType "Validations" FieldConfigProperty
newValue FieldConfigProperty {Maybe [FieldValidationConfigurationProperty]
Maybe (Value Bool)
Maybe (Value Text)
Maybe FieldPositionProperty
Maybe FieldInputConfigProperty
()
haddock_workaround_ :: FieldConfigProperty -> ()
excluded :: FieldConfigProperty -> Maybe (Value Bool)
inputType :: FieldConfigProperty -> Maybe FieldInputConfigProperty
label :: FieldConfigProperty -> Maybe (Value Text)
position :: FieldConfigProperty -> Maybe FieldPositionProperty
validations :: FieldConfigProperty -> Maybe [FieldValidationConfigurationProperty]
haddock_workaround_ :: ()
excluded :: Maybe (Value Bool)
inputType :: Maybe FieldInputConfigProperty
label :: Maybe (Value Text)
position :: Maybe FieldPositionProperty
validations :: Maybe [FieldValidationConfigurationProperty]
..}
= FieldConfigProperty {validations :: Maybe [FieldValidationConfigurationProperty]
validations = [FieldValidationConfigurationProperty]
-> Maybe [FieldValidationConfigurationProperty]
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure [FieldValidationConfigurationProperty]
PropertyType "Validations" FieldConfigProperty
newValue, Maybe (Value Bool)
Maybe (Value Text)
Maybe FieldPositionProperty
Maybe FieldInputConfigProperty
()
haddock_workaround_ :: ()
excluded :: Maybe (Value Bool)
inputType :: Maybe FieldInputConfigProperty
label :: Maybe (Value Text)
position :: Maybe FieldPositionProperty
haddock_workaround_ :: ()
excluded :: Maybe (Value Bool)
inputType :: Maybe FieldInputConfigProperty
label :: Maybe (Value Text)
position :: Maybe FieldPositionProperty
..}