module Stratosphere.QuickSight.Template.FormatConfigurationProperty (
        module Exports, FormatConfigurationProperty(..),
        mkFormatConfigurationProperty
    ) where
import qualified Data.Aeson as JSON
import qualified Stratosphere.Prelude as Prelude
import Stratosphere.Property
import {-# SOURCE #-} Stratosphere.QuickSight.Template.DateTimeFormatConfigurationProperty as Exports
import {-# SOURCE #-} Stratosphere.QuickSight.Template.NumberFormatConfigurationProperty as Exports
import {-# SOURCE #-} Stratosphere.QuickSight.Template.StringFormatConfigurationProperty as Exports
import Stratosphere.ResourceProperties
data FormatConfigurationProperty
  = -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-quicksight-template-formatconfiguration.html>
    FormatConfigurationProperty {FormatConfigurationProperty -> ()
haddock_workaround_ :: (),
                                 -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-quicksight-template-formatconfiguration.html#cfn-quicksight-template-formatconfiguration-datetimeformatconfiguration>
                                 FormatConfigurationProperty
-> Maybe DateTimeFormatConfigurationProperty
dateTimeFormatConfiguration :: (Prelude.Maybe DateTimeFormatConfigurationProperty),
                                 -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-quicksight-template-formatconfiguration.html#cfn-quicksight-template-formatconfiguration-numberformatconfiguration>
                                 FormatConfigurationProperty
-> Maybe NumberFormatConfigurationProperty
numberFormatConfiguration :: (Prelude.Maybe NumberFormatConfigurationProperty),
                                 -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-quicksight-template-formatconfiguration.html#cfn-quicksight-template-formatconfiguration-stringformatconfiguration>
                                 FormatConfigurationProperty
-> Maybe StringFormatConfigurationProperty
stringFormatConfiguration :: (Prelude.Maybe StringFormatConfigurationProperty)}
  deriving stock (FormatConfigurationProperty -> FormatConfigurationProperty -> Bool
(FormatConfigurationProperty
 -> FormatConfigurationProperty -> Bool)
-> (FormatConfigurationProperty
    -> FormatConfigurationProperty -> Bool)
-> Eq FormatConfigurationProperty
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: FormatConfigurationProperty -> FormatConfigurationProperty -> Bool
== :: FormatConfigurationProperty -> FormatConfigurationProperty -> Bool
$c/= :: FormatConfigurationProperty -> FormatConfigurationProperty -> Bool
/= :: FormatConfigurationProperty -> FormatConfigurationProperty -> Bool
Prelude.Eq, Int -> FormatConfigurationProperty -> ShowS
[FormatConfigurationProperty] -> ShowS
FormatConfigurationProperty -> String
(Int -> FormatConfigurationProperty -> ShowS)
-> (FormatConfigurationProperty -> String)
-> ([FormatConfigurationProperty] -> ShowS)
-> Show FormatConfigurationProperty
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> FormatConfigurationProperty -> ShowS
showsPrec :: Int -> FormatConfigurationProperty -> ShowS
$cshow :: FormatConfigurationProperty -> String
show :: FormatConfigurationProperty -> String
$cshowList :: [FormatConfigurationProperty] -> ShowS
showList :: [FormatConfigurationProperty] -> ShowS
Prelude.Show)
mkFormatConfigurationProperty :: FormatConfigurationProperty
mkFormatConfigurationProperty :: FormatConfigurationProperty
mkFormatConfigurationProperty
  = FormatConfigurationProperty
      {haddock_workaround_ :: ()
haddock_workaround_ = (),
       dateTimeFormatConfiguration :: Maybe DateTimeFormatConfigurationProperty
dateTimeFormatConfiguration = Maybe DateTimeFormatConfigurationProperty
forall a. Maybe a
Prelude.Nothing,
       numberFormatConfiguration :: Maybe NumberFormatConfigurationProperty
numberFormatConfiguration = Maybe NumberFormatConfigurationProperty
forall a. Maybe a
Prelude.Nothing,
       stringFormatConfiguration :: Maybe StringFormatConfigurationProperty
stringFormatConfiguration = Maybe StringFormatConfigurationProperty
forall a. Maybe a
Prelude.Nothing}
instance ToResourceProperties FormatConfigurationProperty where
  toResourceProperties :: FormatConfigurationProperty -> ResourceProperties
toResourceProperties FormatConfigurationProperty {Maybe StringFormatConfigurationProperty
Maybe NumberFormatConfigurationProperty
Maybe DateTimeFormatConfigurationProperty
()
haddock_workaround_ :: FormatConfigurationProperty -> ()
dateTimeFormatConfiguration :: FormatConfigurationProperty
-> Maybe DateTimeFormatConfigurationProperty
numberFormatConfiguration :: FormatConfigurationProperty
-> Maybe NumberFormatConfigurationProperty
stringFormatConfiguration :: FormatConfigurationProperty
-> Maybe StringFormatConfigurationProperty
haddock_workaround_ :: ()
dateTimeFormatConfiguration :: Maybe DateTimeFormatConfigurationProperty
numberFormatConfiguration :: Maybe NumberFormatConfigurationProperty
stringFormatConfiguration :: Maybe StringFormatConfigurationProperty
..}
    = ResourceProperties
        {awsType :: Text
awsType = Text
"AWS::QuickSight::Template.FormatConfiguration",
         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 -> DateTimeFormatConfigurationProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"DateTimeFormatConfiguration"
                              (DateTimeFormatConfigurationProperty -> (Key, Value))
-> Maybe DateTimeFormatConfigurationProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe DateTimeFormatConfigurationProperty
dateTimeFormatConfiguration,
                            Key -> NumberFormatConfigurationProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"NumberFormatConfiguration"
                              (NumberFormatConfigurationProperty -> (Key, Value))
-> Maybe NumberFormatConfigurationProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe NumberFormatConfigurationProperty
numberFormatConfiguration,
                            Key -> StringFormatConfigurationProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"StringFormatConfiguration"
                              (StringFormatConfigurationProperty -> (Key, Value))
-> Maybe StringFormatConfigurationProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe StringFormatConfigurationProperty
stringFormatConfiguration])}
instance JSON.ToJSON FormatConfigurationProperty where
  toJSON :: FormatConfigurationProperty -> Value
toJSON FormatConfigurationProperty {Maybe StringFormatConfigurationProperty
Maybe NumberFormatConfigurationProperty
Maybe DateTimeFormatConfigurationProperty
()
haddock_workaround_ :: FormatConfigurationProperty -> ()
dateTimeFormatConfiguration :: FormatConfigurationProperty
-> Maybe DateTimeFormatConfigurationProperty
numberFormatConfiguration :: FormatConfigurationProperty
-> Maybe NumberFormatConfigurationProperty
stringFormatConfiguration :: FormatConfigurationProperty
-> Maybe StringFormatConfigurationProperty
haddock_workaround_ :: ()
dateTimeFormatConfiguration :: Maybe DateTimeFormatConfigurationProperty
numberFormatConfiguration :: Maybe NumberFormatConfigurationProperty
stringFormatConfiguration :: Maybe StringFormatConfigurationProperty
..}
    = [(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 -> DateTimeFormatConfigurationProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"DateTimeFormatConfiguration"
                 (DateTimeFormatConfigurationProperty -> (Key, Value))
-> Maybe DateTimeFormatConfigurationProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe DateTimeFormatConfigurationProperty
dateTimeFormatConfiguration,
               Key -> NumberFormatConfigurationProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"NumberFormatConfiguration"
                 (NumberFormatConfigurationProperty -> (Key, Value))
-> Maybe NumberFormatConfigurationProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe NumberFormatConfigurationProperty
numberFormatConfiguration,
               Key -> StringFormatConfigurationProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"StringFormatConfiguration"
                 (StringFormatConfigurationProperty -> (Key, Value))
-> Maybe StringFormatConfigurationProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe StringFormatConfigurationProperty
stringFormatConfiguration]))
instance Property "DateTimeFormatConfiguration" FormatConfigurationProperty where
  type PropertyType "DateTimeFormatConfiguration" FormatConfigurationProperty = DateTimeFormatConfigurationProperty
  set :: PropertyType
  "DateTimeFormatConfiguration" FormatConfigurationProperty
-> FormatConfigurationProperty -> FormatConfigurationProperty
set PropertyType
  "DateTimeFormatConfiguration" FormatConfigurationProperty
newValue FormatConfigurationProperty {Maybe StringFormatConfigurationProperty
Maybe NumberFormatConfigurationProperty
Maybe DateTimeFormatConfigurationProperty
()
haddock_workaround_ :: FormatConfigurationProperty -> ()
dateTimeFormatConfiguration :: FormatConfigurationProperty
-> Maybe DateTimeFormatConfigurationProperty
numberFormatConfiguration :: FormatConfigurationProperty
-> Maybe NumberFormatConfigurationProperty
stringFormatConfiguration :: FormatConfigurationProperty
-> Maybe StringFormatConfigurationProperty
haddock_workaround_ :: ()
dateTimeFormatConfiguration :: Maybe DateTimeFormatConfigurationProperty
numberFormatConfiguration :: Maybe NumberFormatConfigurationProperty
stringFormatConfiguration :: Maybe StringFormatConfigurationProperty
..}
    = FormatConfigurationProperty
        {dateTimeFormatConfiguration :: Maybe DateTimeFormatConfigurationProperty
dateTimeFormatConfiguration = DateTimeFormatConfigurationProperty
-> Maybe DateTimeFormatConfigurationProperty
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType
  "DateTimeFormatConfiguration" FormatConfigurationProperty
DateTimeFormatConfigurationProperty
newValue, Maybe StringFormatConfigurationProperty
Maybe NumberFormatConfigurationProperty
()
haddock_workaround_ :: ()
numberFormatConfiguration :: Maybe NumberFormatConfigurationProperty
stringFormatConfiguration :: Maybe StringFormatConfigurationProperty
haddock_workaround_ :: ()
numberFormatConfiguration :: Maybe NumberFormatConfigurationProperty
stringFormatConfiguration :: Maybe StringFormatConfigurationProperty
..}
instance Property "NumberFormatConfiguration" FormatConfigurationProperty where
  type PropertyType "NumberFormatConfiguration" FormatConfigurationProperty = NumberFormatConfigurationProperty
  set :: PropertyType
  "NumberFormatConfiguration" FormatConfigurationProperty
-> FormatConfigurationProperty -> FormatConfigurationProperty
set PropertyType
  "NumberFormatConfiguration" FormatConfigurationProperty
newValue FormatConfigurationProperty {Maybe StringFormatConfigurationProperty
Maybe NumberFormatConfigurationProperty
Maybe DateTimeFormatConfigurationProperty
()
haddock_workaround_ :: FormatConfigurationProperty -> ()
dateTimeFormatConfiguration :: FormatConfigurationProperty
-> Maybe DateTimeFormatConfigurationProperty
numberFormatConfiguration :: FormatConfigurationProperty
-> Maybe NumberFormatConfigurationProperty
stringFormatConfiguration :: FormatConfigurationProperty
-> Maybe StringFormatConfigurationProperty
haddock_workaround_ :: ()
dateTimeFormatConfiguration :: Maybe DateTimeFormatConfigurationProperty
numberFormatConfiguration :: Maybe NumberFormatConfigurationProperty
stringFormatConfiguration :: Maybe StringFormatConfigurationProperty
..}
    = FormatConfigurationProperty
        {numberFormatConfiguration :: Maybe NumberFormatConfigurationProperty
numberFormatConfiguration = NumberFormatConfigurationProperty
-> Maybe NumberFormatConfigurationProperty
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType
  "NumberFormatConfiguration" FormatConfigurationProperty
NumberFormatConfigurationProperty
newValue, Maybe StringFormatConfigurationProperty
Maybe DateTimeFormatConfigurationProperty
()
haddock_workaround_ :: ()
dateTimeFormatConfiguration :: Maybe DateTimeFormatConfigurationProperty
stringFormatConfiguration :: Maybe StringFormatConfigurationProperty
haddock_workaround_ :: ()
dateTimeFormatConfiguration :: Maybe DateTimeFormatConfigurationProperty
stringFormatConfiguration :: Maybe StringFormatConfigurationProperty
..}
instance Property "StringFormatConfiguration" FormatConfigurationProperty where
  type PropertyType "StringFormatConfiguration" FormatConfigurationProperty = StringFormatConfigurationProperty
  set :: PropertyType
  "StringFormatConfiguration" FormatConfigurationProperty
-> FormatConfigurationProperty -> FormatConfigurationProperty
set PropertyType
  "StringFormatConfiguration" FormatConfigurationProperty
newValue FormatConfigurationProperty {Maybe StringFormatConfigurationProperty
Maybe NumberFormatConfigurationProperty
Maybe DateTimeFormatConfigurationProperty
()
haddock_workaround_ :: FormatConfigurationProperty -> ()
dateTimeFormatConfiguration :: FormatConfigurationProperty
-> Maybe DateTimeFormatConfigurationProperty
numberFormatConfiguration :: FormatConfigurationProperty
-> Maybe NumberFormatConfigurationProperty
stringFormatConfiguration :: FormatConfigurationProperty
-> Maybe StringFormatConfigurationProperty
haddock_workaround_ :: ()
dateTimeFormatConfiguration :: Maybe DateTimeFormatConfigurationProperty
numberFormatConfiguration :: Maybe NumberFormatConfigurationProperty
stringFormatConfiguration :: Maybe StringFormatConfigurationProperty
..}
    = FormatConfigurationProperty
        {stringFormatConfiguration :: Maybe StringFormatConfigurationProperty
stringFormatConfiguration = StringFormatConfigurationProperty
-> Maybe StringFormatConfigurationProperty
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType
  "StringFormatConfiguration" FormatConfigurationProperty
StringFormatConfigurationProperty
newValue, Maybe NumberFormatConfigurationProperty
Maybe DateTimeFormatConfigurationProperty
()
haddock_workaround_ :: ()
dateTimeFormatConfiguration :: Maybe DateTimeFormatConfigurationProperty
numberFormatConfiguration :: Maybe NumberFormatConfigurationProperty
haddock_workaround_ :: ()
dateTimeFormatConfiguration :: Maybe DateTimeFormatConfigurationProperty
numberFormatConfiguration :: Maybe NumberFormatConfigurationProperty
..}