module Stratosphere.QuickSight.Dashboard.AggregationFunctionProperty (
module Exports, AggregationFunctionProperty(..),
mkAggregationFunctionProperty
) where
import qualified Data.Aeson as JSON
import qualified Stratosphere.Prelude as Prelude
import Stratosphere.Property
import {-# SOURCE #-} Stratosphere.QuickSight.Dashboard.AttributeAggregationFunctionProperty as Exports
import {-# SOURCE #-} Stratosphere.QuickSight.Dashboard.NumericalAggregationFunctionProperty as Exports
import Stratosphere.ResourceProperties
import Stratosphere.Value
data AggregationFunctionProperty
=
AggregationFunctionProperty {AggregationFunctionProperty -> ()
haddock_workaround_ :: (),
AggregationFunctionProperty
-> Maybe AttributeAggregationFunctionProperty
attributeAggregationFunction :: (Prelude.Maybe AttributeAggregationFunctionProperty),
AggregationFunctionProperty -> Maybe (Value Text)
categoricalAggregationFunction :: (Prelude.Maybe (Value Prelude.Text)),
AggregationFunctionProperty -> Maybe (Value Text)
dateAggregationFunction :: (Prelude.Maybe (Value Prelude.Text)),
AggregationFunctionProperty
-> Maybe NumericalAggregationFunctionProperty
numericalAggregationFunction :: (Prelude.Maybe NumericalAggregationFunctionProperty)}
deriving stock (AggregationFunctionProperty -> AggregationFunctionProperty -> Bool
(AggregationFunctionProperty
-> AggregationFunctionProperty -> Bool)
-> (AggregationFunctionProperty
-> AggregationFunctionProperty -> Bool)
-> Eq AggregationFunctionProperty
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: AggregationFunctionProperty -> AggregationFunctionProperty -> Bool
== :: AggregationFunctionProperty -> AggregationFunctionProperty -> Bool
$c/= :: AggregationFunctionProperty -> AggregationFunctionProperty -> Bool
/= :: AggregationFunctionProperty -> AggregationFunctionProperty -> Bool
Prelude.Eq, Int -> AggregationFunctionProperty -> ShowS
[AggregationFunctionProperty] -> ShowS
AggregationFunctionProperty -> String
(Int -> AggregationFunctionProperty -> ShowS)
-> (AggregationFunctionProperty -> String)
-> ([AggregationFunctionProperty] -> ShowS)
-> Show AggregationFunctionProperty
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> AggregationFunctionProperty -> ShowS
showsPrec :: Int -> AggregationFunctionProperty -> ShowS
$cshow :: AggregationFunctionProperty -> String
show :: AggregationFunctionProperty -> String
$cshowList :: [AggregationFunctionProperty] -> ShowS
showList :: [AggregationFunctionProperty] -> ShowS
Prelude.Show)
mkAggregationFunctionProperty :: AggregationFunctionProperty
mkAggregationFunctionProperty :: AggregationFunctionProperty
mkAggregationFunctionProperty
= AggregationFunctionProperty
{haddock_workaround_ :: ()
haddock_workaround_ = (),
attributeAggregationFunction :: Maybe AttributeAggregationFunctionProperty
attributeAggregationFunction = Maybe AttributeAggregationFunctionProperty
forall a. Maybe a
Prelude.Nothing,
categoricalAggregationFunction :: Maybe (Value Text)
categoricalAggregationFunction = Maybe (Value Text)
forall a. Maybe a
Prelude.Nothing,
dateAggregationFunction :: Maybe (Value Text)
dateAggregationFunction = Maybe (Value Text)
forall a. Maybe a
Prelude.Nothing,
numericalAggregationFunction :: Maybe NumericalAggregationFunctionProperty
numericalAggregationFunction = Maybe NumericalAggregationFunctionProperty
forall a. Maybe a
Prelude.Nothing}
instance ToResourceProperties AggregationFunctionProperty where
toResourceProperties :: AggregationFunctionProperty -> ResourceProperties
toResourceProperties AggregationFunctionProperty {Maybe (Value Text)
Maybe AttributeAggregationFunctionProperty
Maybe NumericalAggregationFunctionProperty
()
haddock_workaround_ :: AggregationFunctionProperty -> ()
attributeAggregationFunction :: AggregationFunctionProperty
-> Maybe AttributeAggregationFunctionProperty
categoricalAggregationFunction :: AggregationFunctionProperty -> Maybe (Value Text)
dateAggregationFunction :: AggregationFunctionProperty -> Maybe (Value Text)
numericalAggregationFunction :: AggregationFunctionProperty
-> Maybe NumericalAggregationFunctionProperty
haddock_workaround_ :: ()
attributeAggregationFunction :: Maybe AttributeAggregationFunctionProperty
categoricalAggregationFunction :: Maybe (Value Text)
dateAggregationFunction :: Maybe (Value Text)
numericalAggregationFunction :: Maybe NumericalAggregationFunctionProperty
..}
= ResourceProperties
{awsType :: Text
awsType = Text
"AWS::QuickSight::Dashboard.AggregationFunction",
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 -> AttributeAggregationFunctionProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"AttributeAggregationFunction"
(AttributeAggregationFunctionProperty -> (Key, Value))
-> Maybe AttributeAggregationFunctionProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe AttributeAggregationFunctionProperty
attributeAggregationFunction,
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
"CategoricalAggregationFunction"
(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)
categoricalAggregationFunction,
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
"DateAggregationFunction"
(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)
dateAggregationFunction,
Key -> NumericalAggregationFunctionProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"NumericalAggregationFunction"
(NumericalAggregationFunctionProperty -> (Key, Value))
-> Maybe NumericalAggregationFunctionProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe NumericalAggregationFunctionProperty
numericalAggregationFunction])}
instance JSON.ToJSON AggregationFunctionProperty where
toJSON :: AggregationFunctionProperty -> Value
toJSON AggregationFunctionProperty {Maybe (Value Text)
Maybe AttributeAggregationFunctionProperty
Maybe NumericalAggregationFunctionProperty
()
haddock_workaround_ :: AggregationFunctionProperty -> ()
attributeAggregationFunction :: AggregationFunctionProperty
-> Maybe AttributeAggregationFunctionProperty
categoricalAggregationFunction :: AggregationFunctionProperty -> Maybe (Value Text)
dateAggregationFunction :: AggregationFunctionProperty -> Maybe (Value Text)
numericalAggregationFunction :: AggregationFunctionProperty
-> Maybe NumericalAggregationFunctionProperty
haddock_workaround_ :: ()
attributeAggregationFunction :: Maybe AttributeAggregationFunctionProperty
categoricalAggregationFunction :: Maybe (Value Text)
dateAggregationFunction :: Maybe (Value Text)
numericalAggregationFunction :: Maybe NumericalAggregationFunctionProperty
..}
= [(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 -> AttributeAggregationFunctionProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"AttributeAggregationFunction"
(AttributeAggregationFunctionProperty -> (Key, Value))
-> Maybe AttributeAggregationFunctionProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe AttributeAggregationFunctionProperty
attributeAggregationFunction,
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
"CategoricalAggregationFunction"
(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)
categoricalAggregationFunction,
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
"DateAggregationFunction"
(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)
dateAggregationFunction,
Key -> NumericalAggregationFunctionProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"NumericalAggregationFunction"
(NumericalAggregationFunctionProperty -> (Key, Value))
-> Maybe NumericalAggregationFunctionProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe NumericalAggregationFunctionProperty
numericalAggregationFunction]))
instance Property "AttributeAggregationFunction" AggregationFunctionProperty where
type PropertyType "AttributeAggregationFunction" AggregationFunctionProperty = AttributeAggregationFunctionProperty
set :: PropertyType
"AttributeAggregationFunction" AggregationFunctionProperty
-> AggregationFunctionProperty -> AggregationFunctionProperty
set PropertyType
"AttributeAggregationFunction" AggregationFunctionProperty
newValue AggregationFunctionProperty {Maybe (Value Text)
Maybe AttributeAggregationFunctionProperty
Maybe NumericalAggregationFunctionProperty
()
haddock_workaround_ :: AggregationFunctionProperty -> ()
attributeAggregationFunction :: AggregationFunctionProperty
-> Maybe AttributeAggregationFunctionProperty
categoricalAggregationFunction :: AggregationFunctionProperty -> Maybe (Value Text)
dateAggregationFunction :: AggregationFunctionProperty -> Maybe (Value Text)
numericalAggregationFunction :: AggregationFunctionProperty
-> Maybe NumericalAggregationFunctionProperty
haddock_workaround_ :: ()
attributeAggregationFunction :: Maybe AttributeAggregationFunctionProperty
categoricalAggregationFunction :: Maybe (Value Text)
dateAggregationFunction :: Maybe (Value Text)
numericalAggregationFunction :: Maybe NumericalAggregationFunctionProperty
..}
= AggregationFunctionProperty
{attributeAggregationFunction :: Maybe AttributeAggregationFunctionProperty
attributeAggregationFunction = AttributeAggregationFunctionProperty
-> Maybe AttributeAggregationFunctionProperty
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType
"AttributeAggregationFunction" AggregationFunctionProperty
AttributeAggregationFunctionProperty
newValue, Maybe (Value Text)
Maybe NumericalAggregationFunctionProperty
()
haddock_workaround_ :: ()
categoricalAggregationFunction :: Maybe (Value Text)
dateAggregationFunction :: Maybe (Value Text)
numericalAggregationFunction :: Maybe NumericalAggregationFunctionProperty
haddock_workaround_ :: ()
categoricalAggregationFunction :: Maybe (Value Text)
dateAggregationFunction :: Maybe (Value Text)
numericalAggregationFunction :: Maybe NumericalAggregationFunctionProperty
..}
instance Property "CategoricalAggregationFunction" AggregationFunctionProperty where
type PropertyType "CategoricalAggregationFunction" AggregationFunctionProperty = Value Prelude.Text
set :: PropertyType
"CategoricalAggregationFunction" AggregationFunctionProperty
-> AggregationFunctionProperty -> AggregationFunctionProperty
set PropertyType
"CategoricalAggregationFunction" AggregationFunctionProperty
newValue AggregationFunctionProperty {Maybe (Value Text)
Maybe AttributeAggregationFunctionProperty
Maybe NumericalAggregationFunctionProperty
()
haddock_workaround_ :: AggregationFunctionProperty -> ()
attributeAggregationFunction :: AggregationFunctionProperty
-> Maybe AttributeAggregationFunctionProperty
categoricalAggregationFunction :: AggregationFunctionProperty -> Maybe (Value Text)
dateAggregationFunction :: AggregationFunctionProperty -> Maybe (Value Text)
numericalAggregationFunction :: AggregationFunctionProperty
-> Maybe NumericalAggregationFunctionProperty
haddock_workaround_ :: ()
attributeAggregationFunction :: Maybe AttributeAggregationFunctionProperty
categoricalAggregationFunction :: Maybe (Value Text)
dateAggregationFunction :: Maybe (Value Text)
numericalAggregationFunction :: Maybe NumericalAggregationFunctionProperty
..}
= AggregationFunctionProperty
{categoricalAggregationFunction :: Maybe (Value Text)
categoricalAggregationFunction = Value Text -> Maybe (Value Text)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType
"CategoricalAggregationFunction" AggregationFunctionProperty
Value Text
newValue, Maybe (Value Text)
Maybe AttributeAggregationFunctionProperty
Maybe NumericalAggregationFunctionProperty
()
haddock_workaround_ :: ()
attributeAggregationFunction :: Maybe AttributeAggregationFunctionProperty
dateAggregationFunction :: Maybe (Value Text)
numericalAggregationFunction :: Maybe NumericalAggregationFunctionProperty
haddock_workaround_ :: ()
attributeAggregationFunction :: Maybe AttributeAggregationFunctionProperty
dateAggregationFunction :: Maybe (Value Text)
numericalAggregationFunction :: Maybe NumericalAggregationFunctionProperty
..}
instance Property "DateAggregationFunction" AggregationFunctionProperty where
type PropertyType "DateAggregationFunction" AggregationFunctionProperty = Value Prelude.Text
set :: PropertyType "DateAggregationFunction" AggregationFunctionProperty
-> AggregationFunctionProperty -> AggregationFunctionProperty
set PropertyType "DateAggregationFunction" AggregationFunctionProperty
newValue AggregationFunctionProperty {Maybe (Value Text)
Maybe AttributeAggregationFunctionProperty
Maybe NumericalAggregationFunctionProperty
()
haddock_workaround_ :: AggregationFunctionProperty -> ()
attributeAggregationFunction :: AggregationFunctionProperty
-> Maybe AttributeAggregationFunctionProperty
categoricalAggregationFunction :: AggregationFunctionProperty -> Maybe (Value Text)
dateAggregationFunction :: AggregationFunctionProperty -> Maybe (Value Text)
numericalAggregationFunction :: AggregationFunctionProperty
-> Maybe NumericalAggregationFunctionProperty
haddock_workaround_ :: ()
attributeAggregationFunction :: Maybe AttributeAggregationFunctionProperty
categoricalAggregationFunction :: Maybe (Value Text)
dateAggregationFunction :: Maybe (Value Text)
numericalAggregationFunction :: Maybe NumericalAggregationFunctionProperty
..}
= AggregationFunctionProperty
{dateAggregationFunction :: Maybe (Value Text)
dateAggregationFunction = Value Text -> Maybe (Value Text)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "DateAggregationFunction" AggregationFunctionProperty
Value Text
newValue, Maybe (Value Text)
Maybe AttributeAggregationFunctionProperty
Maybe NumericalAggregationFunctionProperty
()
haddock_workaround_ :: ()
attributeAggregationFunction :: Maybe AttributeAggregationFunctionProperty
categoricalAggregationFunction :: Maybe (Value Text)
numericalAggregationFunction :: Maybe NumericalAggregationFunctionProperty
haddock_workaround_ :: ()
attributeAggregationFunction :: Maybe AttributeAggregationFunctionProperty
categoricalAggregationFunction :: Maybe (Value Text)
numericalAggregationFunction :: Maybe NumericalAggregationFunctionProperty
..}
instance Property "NumericalAggregationFunction" AggregationFunctionProperty where
type PropertyType "NumericalAggregationFunction" AggregationFunctionProperty = NumericalAggregationFunctionProperty
set :: PropertyType
"NumericalAggregationFunction" AggregationFunctionProperty
-> AggregationFunctionProperty -> AggregationFunctionProperty
set PropertyType
"NumericalAggregationFunction" AggregationFunctionProperty
newValue AggregationFunctionProperty {Maybe (Value Text)
Maybe AttributeAggregationFunctionProperty
Maybe NumericalAggregationFunctionProperty
()
haddock_workaround_ :: AggregationFunctionProperty -> ()
attributeAggregationFunction :: AggregationFunctionProperty
-> Maybe AttributeAggregationFunctionProperty
categoricalAggregationFunction :: AggregationFunctionProperty -> Maybe (Value Text)
dateAggregationFunction :: AggregationFunctionProperty -> Maybe (Value Text)
numericalAggregationFunction :: AggregationFunctionProperty
-> Maybe NumericalAggregationFunctionProperty
haddock_workaround_ :: ()
attributeAggregationFunction :: Maybe AttributeAggregationFunctionProperty
categoricalAggregationFunction :: Maybe (Value Text)
dateAggregationFunction :: Maybe (Value Text)
numericalAggregationFunction :: Maybe NumericalAggregationFunctionProperty
..}
= AggregationFunctionProperty
{numericalAggregationFunction :: Maybe NumericalAggregationFunctionProperty
numericalAggregationFunction = NumericalAggregationFunctionProperty
-> Maybe NumericalAggregationFunctionProperty
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType
"NumericalAggregationFunction" AggregationFunctionProperty
NumericalAggregationFunctionProperty
newValue, Maybe (Value Text)
Maybe AttributeAggregationFunctionProperty
()
haddock_workaround_ :: ()
attributeAggregationFunction :: Maybe AttributeAggregationFunctionProperty
categoricalAggregationFunction :: Maybe (Value Text)
dateAggregationFunction :: Maybe (Value Text)
haddock_workaround_ :: ()
attributeAggregationFunction :: Maybe AttributeAggregationFunctionProperty
categoricalAggregationFunction :: Maybe (Value Text)
dateAggregationFunction :: Maybe (Value Text)
..}