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