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