module Stratosphere.QuickSight.Dashboard.GeospatialCategoricalColorProperty (
module Exports, GeospatialCategoricalColorProperty(..),
mkGeospatialCategoricalColorProperty
) where
import qualified Data.Aeson as JSON
import qualified Stratosphere.Prelude as Prelude
import Stratosphere.Property
import {-# SOURCE #-} Stratosphere.QuickSight.Dashboard.GeospatialCategoricalDataColorProperty as Exports
import {-# SOURCE #-} Stratosphere.QuickSight.Dashboard.GeospatialNullDataSettingsProperty as Exports
import Stratosphere.ResourceProperties
import Stratosphere.Value
data GeospatialCategoricalColorProperty
=
GeospatialCategoricalColorProperty {GeospatialCategoricalColorProperty -> ()
haddock_workaround_ :: (),
GeospatialCategoricalColorProperty
-> [GeospatialCategoricalDataColorProperty]
categoryDataColors :: [GeospatialCategoricalDataColorProperty],
GeospatialCategoricalColorProperty -> Maybe (Value Double)
defaultOpacity :: (Prelude.Maybe (Value Prelude.Double)),
GeospatialCategoricalColorProperty
-> Maybe GeospatialNullDataSettingsProperty
nullDataSettings :: (Prelude.Maybe GeospatialNullDataSettingsProperty),
GeospatialCategoricalColorProperty -> Maybe (Value Text)
nullDataVisibility :: (Prelude.Maybe (Value Prelude.Text))}
deriving stock (GeospatialCategoricalColorProperty
-> GeospatialCategoricalColorProperty -> Bool
(GeospatialCategoricalColorProperty
-> GeospatialCategoricalColorProperty -> Bool)
-> (GeospatialCategoricalColorProperty
-> GeospatialCategoricalColorProperty -> Bool)
-> Eq GeospatialCategoricalColorProperty
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: GeospatialCategoricalColorProperty
-> GeospatialCategoricalColorProperty -> Bool
== :: GeospatialCategoricalColorProperty
-> GeospatialCategoricalColorProperty -> Bool
$c/= :: GeospatialCategoricalColorProperty
-> GeospatialCategoricalColorProperty -> Bool
/= :: GeospatialCategoricalColorProperty
-> GeospatialCategoricalColorProperty -> Bool
Prelude.Eq, Int -> GeospatialCategoricalColorProperty -> ShowS
[GeospatialCategoricalColorProperty] -> ShowS
GeospatialCategoricalColorProperty -> String
(Int -> GeospatialCategoricalColorProperty -> ShowS)
-> (GeospatialCategoricalColorProperty -> String)
-> ([GeospatialCategoricalColorProperty] -> ShowS)
-> Show GeospatialCategoricalColorProperty
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> GeospatialCategoricalColorProperty -> ShowS
showsPrec :: Int -> GeospatialCategoricalColorProperty -> ShowS
$cshow :: GeospatialCategoricalColorProperty -> String
show :: GeospatialCategoricalColorProperty -> String
$cshowList :: [GeospatialCategoricalColorProperty] -> ShowS
showList :: [GeospatialCategoricalColorProperty] -> ShowS
Prelude.Show)
mkGeospatialCategoricalColorProperty ::
[GeospatialCategoricalDataColorProperty]
-> GeospatialCategoricalColorProperty
mkGeospatialCategoricalColorProperty :: [GeospatialCategoricalDataColorProperty]
-> GeospatialCategoricalColorProperty
mkGeospatialCategoricalColorProperty [GeospatialCategoricalDataColorProperty]
categoryDataColors
= GeospatialCategoricalColorProperty
{haddock_workaround_ :: ()
haddock_workaround_ = (), categoryDataColors :: [GeospatialCategoricalDataColorProperty]
categoryDataColors = [GeospatialCategoricalDataColorProperty]
categoryDataColors,
defaultOpacity :: Maybe (Value Double)
defaultOpacity = Maybe (Value Double)
forall a. Maybe a
Prelude.Nothing,
nullDataSettings :: Maybe GeospatialNullDataSettingsProperty
nullDataSettings = Maybe GeospatialNullDataSettingsProperty
forall a. Maybe a
Prelude.Nothing,
nullDataVisibility :: Maybe (Value Text)
nullDataVisibility = Maybe (Value Text)
forall a. Maybe a
Prelude.Nothing}
instance ToResourceProperties GeospatialCategoricalColorProperty where
toResourceProperties :: GeospatialCategoricalColorProperty -> ResourceProperties
toResourceProperties GeospatialCategoricalColorProperty {[GeospatialCategoricalDataColorProperty]
Maybe (Value Double)
Maybe (Value Text)
Maybe GeospatialNullDataSettingsProperty
()
haddock_workaround_ :: GeospatialCategoricalColorProperty -> ()
categoryDataColors :: GeospatialCategoricalColorProperty
-> [GeospatialCategoricalDataColorProperty]
defaultOpacity :: GeospatialCategoricalColorProperty -> Maybe (Value Double)
nullDataSettings :: GeospatialCategoricalColorProperty
-> Maybe GeospatialNullDataSettingsProperty
nullDataVisibility :: GeospatialCategoricalColorProperty -> Maybe (Value Text)
haddock_workaround_ :: ()
categoryDataColors :: [GeospatialCategoricalDataColorProperty]
defaultOpacity :: Maybe (Value Double)
nullDataSettings :: Maybe GeospatialNullDataSettingsProperty
nullDataVisibility :: Maybe (Value Text)
..}
= ResourceProperties
{awsType :: Text
awsType = Text
"AWS::QuickSight::Dashboard.GeospatialCategoricalColor",
supportsTags :: Bool
supportsTags = Bool
Prelude.False,
properties :: Object
properties = [Item Object] -> Object
forall l. IsList l => [Item l] -> l
Prelude.fromList
([(Key, Value)] -> [(Key, Value)] -> [(Key, Value)]
forall a. Semigroup a => a -> a -> a
(Prelude.<>)
[Key
"CategoryDataColors" Key -> [GeospatialCategoricalDataColorProperty] -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
JSON..= [GeospatialCategoricalDataColorProperty]
categoryDataColors]
([Maybe (Key, Value)] -> [(Key, Value)]
forall a. [Maybe a] -> [a]
Prelude.catMaybes
[Key -> Value Double -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"DefaultOpacity" (Value Double -> (Key, Value))
-> Maybe (Value Double) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Double)
defaultOpacity,
Key -> GeospatialNullDataSettingsProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"NullDataSettings" (GeospatialNullDataSettingsProperty -> (Key, Value))
-> Maybe GeospatialNullDataSettingsProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe GeospatialNullDataSettingsProperty
nullDataSettings,
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
"NullDataVisibility" (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)
nullDataVisibility]))}
instance JSON.ToJSON GeospatialCategoricalColorProperty where
toJSON :: GeospatialCategoricalColorProperty -> Value
toJSON GeospatialCategoricalColorProperty {[GeospatialCategoricalDataColorProperty]
Maybe (Value Double)
Maybe (Value Text)
Maybe GeospatialNullDataSettingsProperty
()
haddock_workaround_ :: GeospatialCategoricalColorProperty -> ()
categoryDataColors :: GeospatialCategoricalColorProperty
-> [GeospatialCategoricalDataColorProperty]
defaultOpacity :: GeospatialCategoricalColorProperty -> Maybe (Value Double)
nullDataSettings :: GeospatialCategoricalColorProperty
-> Maybe GeospatialNullDataSettingsProperty
nullDataVisibility :: GeospatialCategoricalColorProperty -> Maybe (Value Text)
haddock_workaround_ :: ()
categoryDataColors :: [GeospatialCategoricalDataColorProperty]
defaultOpacity :: Maybe (Value Double)
nullDataSettings :: Maybe GeospatialNullDataSettingsProperty
nullDataVisibility :: Maybe (Value Text)
..}
= [(Key, Value)] -> Value
JSON.object
([Item [(Key, Value)]] -> [(Key, Value)]
forall l. IsList l => [Item l] -> l
Prelude.fromList
([(Key, Value)] -> [(Key, Value)] -> [(Key, Value)]
forall a. Semigroup a => a -> a -> a
(Prelude.<>)
[Key
"CategoryDataColors" Key -> [GeospatialCategoricalDataColorProperty] -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
JSON..= [GeospatialCategoricalDataColorProperty]
categoryDataColors]
([Maybe (Key, Value)] -> [(Key, Value)]
forall a. [Maybe a] -> [a]
Prelude.catMaybes
[Key -> Value Double -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"DefaultOpacity" (Value Double -> (Key, Value))
-> Maybe (Value Double) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Double)
defaultOpacity,
Key -> GeospatialNullDataSettingsProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"NullDataSettings" (GeospatialNullDataSettingsProperty -> (Key, Value))
-> Maybe GeospatialNullDataSettingsProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe GeospatialNullDataSettingsProperty
nullDataSettings,
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
"NullDataVisibility" (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)
nullDataVisibility])))
instance Property "CategoryDataColors" GeospatialCategoricalColorProperty where
type PropertyType "CategoryDataColors" GeospatialCategoricalColorProperty = [GeospatialCategoricalDataColorProperty]
set :: PropertyType
"CategoryDataColors" GeospatialCategoricalColorProperty
-> GeospatialCategoricalColorProperty
-> GeospatialCategoricalColorProperty
set PropertyType
"CategoryDataColors" GeospatialCategoricalColorProperty
newValue GeospatialCategoricalColorProperty {[GeospatialCategoricalDataColorProperty]
Maybe (Value Double)
Maybe (Value Text)
Maybe GeospatialNullDataSettingsProperty
()
haddock_workaround_ :: GeospatialCategoricalColorProperty -> ()
categoryDataColors :: GeospatialCategoricalColorProperty
-> [GeospatialCategoricalDataColorProperty]
defaultOpacity :: GeospatialCategoricalColorProperty -> Maybe (Value Double)
nullDataSettings :: GeospatialCategoricalColorProperty
-> Maybe GeospatialNullDataSettingsProperty
nullDataVisibility :: GeospatialCategoricalColorProperty -> Maybe (Value Text)
haddock_workaround_ :: ()
categoryDataColors :: [GeospatialCategoricalDataColorProperty]
defaultOpacity :: Maybe (Value Double)
nullDataSettings :: Maybe GeospatialNullDataSettingsProperty
nullDataVisibility :: Maybe (Value Text)
..}
= GeospatialCategoricalColorProperty
{categoryDataColors :: [GeospatialCategoricalDataColorProperty]
categoryDataColors = [GeospatialCategoricalDataColorProperty]
PropertyType
"CategoryDataColors" GeospatialCategoricalColorProperty
newValue, Maybe (Value Double)
Maybe (Value Text)
Maybe GeospatialNullDataSettingsProperty
()
haddock_workaround_ :: ()
defaultOpacity :: Maybe (Value Double)
nullDataSettings :: Maybe GeospatialNullDataSettingsProperty
nullDataVisibility :: Maybe (Value Text)
haddock_workaround_ :: ()
defaultOpacity :: Maybe (Value Double)
nullDataSettings :: Maybe GeospatialNullDataSettingsProperty
nullDataVisibility :: Maybe (Value Text)
..}
instance Property "DefaultOpacity" GeospatialCategoricalColorProperty where
type PropertyType "DefaultOpacity" GeospatialCategoricalColorProperty = Value Prelude.Double
set :: PropertyType "DefaultOpacity" GeospatialCategoricalColorProperty
-> GeospatialCategoricalColorProperty
-> GeospatialCategoricalColorProperty
set PropertyType "DefaultOpacity" GeospatialCategoricalColorProperty
newValue GeospatialCategoricalColorProperty {[GeospatialCategoricalDataColorProperty]
Maybe (Value Double)
Maybe (Value Text)
Maybe GeospatialNullDataSettingsProperty
()
haddock_workaround_ :: GeospatialCategoricalColorProperty -> ()
categoryDataColors :: GeospatialCategoricalColorProperty
-> [GeospatialCategoricalDataColorProperty]
defaultOpacity :: GeospatialCategoricalColorProperty -> Maybe (Value Double)
nullDataSettings :: GeospatialCategoricalColorProperty
-> Maybe GeospatialNullDataSettingsProperty
nullDataVisibility :: GeospatialCategoricalColorProperty -> Maybe (Value Text)
haddock_workaround_ :: ()
categoryDataColors :: [GeospatialCategoricalDataColorProperty]
defaultOpacity :: Maybe (Value Double)
nullDataSettings :: Maybe GeospatialNullDataSettingsProperty
nullDataVisibility :: Maybe (Value Text)
..}
= GeospatialCategoricalColorProperty
{defaultOpacity :: Maybe (Value Double)
defaultOpacity = Value Double -> Maybe (Value Double)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "DefaultOpacity" GeospatialCategoricalColorProperty
Value Double
newValue, [GeospatialCategoricalDataColorProperty]
Maybe (Value Text)
Maybe GeospatialNullDataSettingsProperty
()
haddock_workaround_ :: ()
categoryDataColors :: [GeospatialCategoricalDataColorProperty]
nullDataSettings :: Maybe GeospatialNullDataSettingsProperty
nullDataVisibility :: Maybe (Value Text)
haddock_workaround_ :: ()
categoryDataColors :: [GeospatialCategoricalDataColorProperty]
nullDataSettings :: Maybe GeospatialNullDataSettingsProperty
nullDataVisibility :: Maybe (Value Text)
..}
instance Property "NullDataSettings" GeospatialCategoricalColorProperty where
type PropertyType "NullDataSettings" GeospatialCategoricalColorProperty = GeospatialNullDataSettingsProperty
set :: PropertyType "NullDataSettings" GeospatialCategoricalColorProperty
-> GeospatialCategoricalColorProperty
-> GeospatialCategoricalColorProperty
set PropertyType "NullDataSettings" GeospatialCategoricalColorProperty
newValue GeospatialCategoricalColorProperty {[GeospatialCategoricalDataColorProperty]
Maybe (Value Double)
Maybe (Value Text)
Maybe GeospatialNullDataSettingsProperty
()
haddock_workaround_ :: GeospatialCategoricalColorProperty -> ()
categoryDataColors :: GeospatialCategoricalColorProperty
-> [GeospatialCategoricalDataColorProperty]
defaultOpacity :: GeospatialCategoricalColorProperty -> Maybe (Value Double)
nullDataSettings :: GeospatialCategoricalColorProperty
-> Maybe GeospatialNullDataSettingsProperty
nullDataVisibility :: GeospatialCategoricalColorProperty -> Maybe (Value Text)
haddock_workaround_ :: ()
categoryDataColors :: [GeospatialCategoricalDataColorProperty]
defaultOpacity :: Maybe (Value Double)
nullDataSettings :: Maybe GeospatialNullDataSettingsProperty
nullDataVisibility :: Maybe (Value Text)
..}
= GeospatialCategoricalColorProperty
{nullDataSettings :: Maybe GeospatialNullDataSettingsProperty
nullDataSettings = GeospatialNullDataSettingsProperty
-> Maybe GeospatialNullDataSettingsProperty
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "NullDataSettings" GeospatialCategoricalColorProperty
GeospatialNullDataSettingsProperty
newValue, [GeospatialCategoricalDataColorProperty]
Maybe (Value Double)
Maybe (Value Text)
()
haddock_workaround_ :: ()
categoryDataColors :: [GeospatialCategoricalDataColorProperty]
defaultOpacity :: Maybe (Value Double)
nullDataVisibility :: Maybe (Value Text)
haddock_workaround_ :: ()
categoryDataColors :: [GeospatialCategoricalDataColorProperty]
defaultOpacity :: Maybe (Value Double)
nullDataVisibility :: Maybe (Value Text)
..}
instance Property "NullDataVisibility" GeospatialCategoricalColorProperty where
type PropertyType "NullDataVisibility" GeospatialCategoricalColorProperty = Value Prelude.Text
set :: PropertyType
"NullDataVisibility" GeospatialCategoricalColorProperty
-> GeospatialCategoricalColorProperty
-> GeospatialCategoricalColorProperty
set PropertyType
"NullDataVisibility" GeospatialCategoricalColorProperty
newValue GeospatialCategoricalColorProperty {[GeospatialCategoricalDataColorProperty]
Maybe (Value Double)
Maybe (Value Text)
Maybe GeospatialNullDataSettingsProperty
()
haddock_workaround_ :: GeospatialCategoricalColorProperty -> ()
categoryDataColors :: GeospatialCategoricalColorProperty
-> [GeospatialCategoricalDataColorProperty]
defaultOpacity :: GeospatialCategoricalColorProperty -> Maybe (Value Double)
nullDataSettings :: GeospatialCategoricalColorProperty
-> Maybe GeospatialNullDataSettingsProperty
nullDataVisibility :: GeospatialCategoricalColorProperty -> Maybe (Value Text)
haddock_workaround_ :: ()
categoryDataColors :: [GeospatialCategoricalDataColorProperty]
defaultOpacity :: Maybe (Value Double)
nullDataSettings :: Maybe GeospatialNullDataSettingsProperty
nullDataVisibility :: Maybe (Value Text)
..}
= GeospatialCategoricalColorProperty
{nullDataVisibility :: Maybe (Value Text)
nullDataVisibility = Value Text -> Maybe (Value Text)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType
"NullDataVisibility" GeospatialCategoricalColorProperty
Value Text
newValue, [GeospatialCategoricalDataColorProperty]
Maybe (Value Double)
Maybe GeospatialNullDataSettingsProperty
()
haddock_workaround_ :: ()
categoryDataColors :: [GeospatialCategoricalDataColorProperty]
defaultOpacity :: Maybe (Value Double)
nullDataSettings :: Maybe GeospatialNullDataSettingsProperty
haddock_workaround_ :: ()
categoryDataColors :: [GeospatialCategoricalDataColorProperty]
defaultOpacity :: Maybe (Value Double)
nullDataSettings :: Maybe GeospatialNullDataSettingsProperty
..}