module Stratosphere.QuickSight.Dashboard.InsightConfigurationProperty (
module Exports, InsightConfigurationProperty(..),
mkInsightConfigurationProperty
) where
import qualified Data.Aeson as JSON
import qualified Stratosphere.Prelude as Prelude
import Stratosphere.Property
import {-# SOURCE #-} Stratosphere.QuickSight.Dashboard.ComputationProperty as Exports
import {-# SOURCE #-} Stratosphere.QuickSight.Dashboard.CustomNarrativeOptionsProperty as Exports
import {-# SOURCE #-} Stratosphere.QuickSight.Dashboard.VisualInteractionOptionsProperty as Exports
import Stratosphere.ResourceProperties
data InsightConfigurationProperty
=
InsightConfigurationProperty {InsightConfigurationProperty -> ()
haddock_workaround_ :: (),
InsightConfigurationProperty -> Maybe [ComputationProperty]
computations :: (Prelude.Maybe [ComputationProperty]),
InsightConfigurationProperty
-> Maybe CustomNarrativeOptionsProperty
customNarrative :: (Prelude.Maybe CustomNarrativeOptionsProperty),
InsightConfigurationProperty
-> Maybe VisualInteractionOptionsProperty
interactions :: (Prelude.Maybe VisualInteractionOptionsProperty)}
deriving stock (InsightConfigurationProperty
-> InsightConfigurationProperty -> Bool
(InsightConfigurationProperty
-> InsightConfigurationProperty -> Bool)
-> (InsightConfigurationProperty
-> InsightConfigurationProperty -> Bool)
-> Eq InsightConfigurationProperty
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: InsightConfigurationProperty
-> InsightConfigurationProperty -> Bool
== :: InsightConfigurationProperty
-> InsightConfigurationProperty -> Bool
$c/= :: InsightConfigurationProperty
-> InsightConfigurationProperty -> Bool
/= :: InsightConfigurationProperty
-> InsightConfigurationProperty -> Bool
Prelude.Eq, Int -> InsightConfigurationProperty -> ShowS
[InsightConfigurationProperty] -> ShowS
InsightConfigurationProperty -> String
(Int -> InsightConfigurationProperty -> ShowS)
-> (InsightConfigurationProperty -> String)
-> ([InsightConfigurationProperty] -> ShowS)
-> Show InsightConfigurationProperty
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> InsightConfigurationProperty -> ShowS
showsPrec :: Int -> InsightConfigurationProperty -> ShowS
$cshow :: InsightConfigurationProperty -> String
show :: InsightConfigurationProperty -> String
$cshowList :: [InsightConfigurationProperty] -> ShowS
showList :: [InsightConfigurationProperty] -> ShowS
Prelude.Show)
mkInsightConfigurationProperty :: InsightConfigurationProperty
mkInsightConfigurationProperty :: InsightConfigurationProperty
mkInsightConfigurationProperty
= InsightConfigurationProperty
{haddock_workaround_ :: ()
haddock_workaround_ = (), computations :: Maybe [ComputationProperty]
computations = Maybe [ComputationProperty]
forall a. Maybe a
Prelude.Nothing,
customNarrative :: Maybe CustomNarrativeOptionsProperty
customNarrative = Maybe CustomNarrativeOptionsProperty
forall a. Maybe a
Prelude.Nothing, interactions :: Maybe VisualInteractionOptionsProperty
interactions = Maybe VisualInteractionOptionsProperty
forall a. Maybe a
Prelude.Nothing}
instance ToResourceProperties InsightConfigurationProperty where
toResourceProperties :: InsightConfigurationProperty -> ResourceProperties
toResourceProperties InsightConfigurationProperty {Maybe [ComputationProperty]
Maybe CustomNarrativeOptionsProperty
Maybe VisualInteractionOptionsProperty
()
haddock_workaround_ :: InsightConfigurationProperty -> ()
computations :: InsightConfigurationProperty -> Maybe [ComputationProperty]
customNarrative :: InsightConfigurationProperty
-> Maybe CustomNarrativeOptionsProperty
interactions :: InsightConfigurationProperty
-> Maybe VisualInteractionOptionsProperty
haddock_workaround_ :: ()
computations :: Maybe [ComputationProperty]
customNarrative :: Maybe CustomNarrativeOptionsProperty
interactions :: Maybe VisualInteractionOptionsProperty
..}
= ResourceProperties
{awsType :: Text
awsType = Text
"AWS::QuickSight::Dashboard.InsightConfiguration",
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 -> [ComputationProperty] -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"Computations" ([ComputationProperty] -> (Key, Value))
-> Maybe [ComputationProperty] -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [ComputationProperty]
computations,
Key -> CustomNarrativeOptionsProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"CustomNarrative" (CustomNarrativeOptionsProperty -> (Key, Value))
-> Maybe CustomNarrativeOptionsProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe CustomNarrativeOptionsProperty
customNarrative,
Key -> VisualInteractionOptionsProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"Interactions" (VisualInteractionOptionsProperty -> (Key, Value))
-> Maybe VisualInteractionOptionsProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe VisualInteractionOptionsProperty
interactions])}
instance JSON.ToJSON InsightConfigurationProperty where
toJSON :: InsightConfigurationProperty -> Value
toJSON InsightConfigurationProperty {Maybe [ComputationProperty]
Maybe CustomNarrativeOptionsProperty
Maybe VisualInteractionOptionsProperty
()
haddock_workaround_ :: InsightConfigurationProperty -> ()
computations :: InsightConfigurationProperty -> Maybe [ComputationProperty]
customNarrative :: InsightConfigurationProperty
-> Maybe CustomNarrativeOptionsProperty
interactions :: InsightConfigurationProperty
-> Maybe VisualInteractionOptionsProperty
haddock_workaround_ :: ()
computations :: Maybe [ComputationProperty]
customNarrative :: Maybe CustomNarrativeOptionsProperty
interactions :: Maybe VisualInteractionOptionsProperty
..}
= [(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 -> [ComputationProperty] -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"Computations" ([ComputationProperty] -> (Key, Value))
-> Maybe [ComputationProperty] -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [ComputationProperty]
computations,
Key -> CustomNarrativeOptionsProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"CustomNarrative" (CustomNarrativeOptionsProperty -> (Key, Value))
-> Maybe CustomNarrativeOptionsProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe CustomNarrativeOptionsProperty
customNarrative,
Key -> VisualInteractionOptionsProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"Interactions" (VisualInteractionOptionsProperty -> (Key, Value))
-> Maybe VisualInteractionOptionsProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe VisualInteractionOptionsProperty
interactions]))
instance Property "Computations" InsightConfigurationProperty where
type PropertyType "Computations" InsightConfigurationProperty = [ComputationProperty]
set :: PropertyType "Computations" InsightConfigurationProperty
-> InsightConfigurationProperty -> InsightConfigurationProperty
set PropertyType "Computations" InsightConfigurationProperty
newValue InsightConfigurationProperty {Maybe [ComputationProperty]
Maybe CustomNarrativeOptionsProperty
Maybe VisualInteractionOptionsProperty
()
haddock_workaround_ :: InsightConfigurationProperty -> ()
computations :: InsightConfigurationProperty -> Maybe [ComputationProperty]
customNarrative :: InsightConfigurationProperty
-> Maybe CustomNarrativeOptionsProperty
interactions :: InsightConfigurationProperty
-> Maybe VisualInteractionOptionsProperty
haddock_workaround_ :: ()
computations :: Maybe [ComputationProperty]
customNarrative :: Maybe CustomNarrativeOptionsProperty
interactions :: Maybe VisualInteractionOptionsProperty
..}
= InsightConfigurationProperty
{computations :: Maybe [ComputationProperty]
computations = [ComputationProperty] -> Maybe [ComputationProperty]
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure [ComputationProperty]
PropertyType "Computations" InsightConfigurationProperty
newValue, Maybe CustomNarrativeOptionsProperty
Maybe VisualInteractionOptionsProperty
()
haddock_workaround_ :: ()
customNarrative :: Maybe CustomNarrativeOptionsProperty
interactions :: Maybe VisualInteractionOptionsProperty
haddock_workaround_ :: ()
customNarrative :: Maybe CustomNarrativeOptionsProperty
interactions :: Maybe VisualInteractionOptionsProperty
..}
instance Property "CustomNarrative" InsightConfigurationProperty where
type PropertyType "CustomNarrative" InsightConfigurationProperty = CustomNarrativeOptionsProperty
set :: PropertyType "CustomNarrative" InsightConfigurationProperty
-> InsightConfigurationProperty -> InsightConfigurationProperty
set PropertyType "CustomNarrative" InsightConfigurationProperty
newValue InsightConfigurationProperty {Maybe [ComputationProperty]
Maybe CustomNarrativeOptionsProperty
Maybe VisualInteractionOptionsProperty
()
haddock_workaround_ :: InsightConfigurationProperty -> ()
computations :: InsightConfigurationProperty -> Maybe [ComputationProperty]
customNarrative :: InsightConfigurationProperty
-> Maybe CustomNarrativeOptionsProperty
interactions :: InsightConfigurationProperty
-> Maybe VisualInteractionOptionsProperty
haddock_workaround_ :: ()
computations :: Maybe [ComputationProperty]
customNarrative :: Maybe CustomNarrativeOptionsProperty
interactions :: Maybe VisualInteractionOptionsProperty
..}
= InsightConfigurationProperty
{customNarrative :: Maybe CustomNarrativeOptionsProperty
customNarrative = CustomNarrativeOptionsProperty
-> Maybe CustomNarrativeOptionsProperty
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "CustomNarrative" InsightConfigurationProperty
CustomNarrativeOptionsProperty
newValue, Maybe [ComputationProperty]
Maybe VisualInteractionOptionsProperty
()
haddock_workaround_ :: ()
computations :: Maybe [ComputationProperty]
interactions :: Maybe VisualInteractionOptionsProperty
haddock_workaround_ :: ()
computations :: Maybe [ComputationProperty]
interactions :: Maybe VisualInteractionOptionsProperty
..}
instance Property "Interactions" InsightConfigurationProperty where
type PropertyType "Interactions" InsightConfigurationProperty = VisualInteractionOptionsProperty
set :: PropertyType "Interactions" InsightConfigurationProperty
-> InsightConfigurationProperty -> InsightConfigurationProperty
set PropertyType "Interactions" InsightConfigurationProperty
newValue InsightConfigurationProperty {Maybe [ComputationProperty]
Maybe CustomNarrativeOptionsProperty
Maybe VisualInteractionOptionsProperty
()
haddock_workaround_ :: InsightConfigurationProperty -> ()
computations :: InsightConfigurationProperty -> Maybe [ComputationProperty]
customNarrative :: InsightConfigurationProperty
-> Maybe CustomNarrativeOptionsProperty
interactions :: InsightConfigurationProperty
-> Maybe VisualInteractionOptionsProperty
haddock_workaround_ :: ()
computations :: Maybe [ComputationProperty]
customNarrative :: Maybe CustomNarrativeOptionsProperty
interactions :: Maybe VisualInteractionOptionsProperty
..}
= InsightConfigurationProperty
{interactions :: Maybe VisualInteractionOptionsProperty
interactions = VisualInteractionOptionsProperty
-> Maybe VisualInteractionOptionsProperty
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "Interactions" InsightConfigurationProperty
VisualInteractionOptionsProperty
newValue, Maybe [ComputationProperty]
Maybe CustomNarrativeOptionsProperty
()
haddock_workaround_ :: ()
computations :: Maybe [ComputationProperty]
customNarrative :: Maybe CustomNarrativeOptionsProperty
haddock_workaround_ :: ()
computations :: Maybe [ComputationProperty]
customNarrative :: Maybe CustomNarrativeOptionsProperty
..}