module Stratosphere.QuickSight.Dashboard.SmallMultiplesOptionsProperty (
module Exports, SmallMultiplesOptionsProperty(..),
mkSmallMultiplesOptionsProperty
) where
import qualified Data.Aeson as JSON
import qualified Stratosphere.Prelude as Prelude
import Stratosphere.Property
import {-# SOURCE #-} Stratosphere.QuickSight.Dashboard.PanelConfigurationProperty as Exports
import {-# SOURCE #-} Stratosphere.QuickSight.Dashboard.SmallMultiplesAxisPropertiesProperty as Exports
import Stratosphere.ResourceProperties
import Stratosphere.Value
data SmallMultiplesOptionsProperty
=
SmallMultiplesOptionsProperty {SmallMultiplesOptionsProperty -> ()
haddock_workaround_ :: (),
SmallMultiplesOptionsProperty -> Maybe (Value Double)
maxVisibleColumns :: (Prelude.Maybe (Value Prelude.Double)),
SmallMultiplesOptionsProperty -> Maybe (Value Double)
maxVisibleRows :: (Prelude.Maybe (Value Prelude.Double)),
SmallMultiplesOptionsProperty -> Maybe PanelConfigurationProperty
panelConfiguration :: (Prelude.Maybe PanelConfigurationProperty),
SmallMultiplesOptionsProperty
-> Maybe SmallMultiplesAxisPropertiesProperty
xAxis :: (Prelude.Maybe SmallMultiplesAxisPropertiesProperty),
SmallMultiplesOptionsProperty
-> Maybe SmallMultiplesAxisPropertiesProperty
yAxis :: (Prelude.Maybe SmallMultiplesAxisPropertiesProperty)}
deriving stock (SmallMultiplesOptionsProperty
-> SmallMultiplesOptionsProperty -> Bool
(SmallMultiplesOptionsProperty
-> SmallMultiplesOptionsProperty -> Bool)
-> (SmallMultiplesOptionsProperty
-> SmallMultiplesOptionsProperty -> Bool)
-> Eq SmallMultiplesOptionsProperty
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: SmallMultiplesOptionsProperty
-> SmallMultiplesOptionsProperty -> Bool
== :: SmallMultiplesOptionsProperty
-> SmallMultiplesOptionsProperty -> Bool
$c/= :: SmallMultiplesOptionsProperty
-> SmallMultiplesOptionsProperty -> Bool
/= :: SmallMultiplesOptionsProperty
-> SmallMultiplesOptionsProperty -> Bool
Prelude.Eq, Int -> SmallMultiplesOptionsProperty -> ShowS
[SmallMultiplesOptionsProperty] -> ShowS
SmallMultiplesOptionsProperty -> String
(Int -> SmallMultiplesOptionsProperty -> ShowS)
-> (SmallMultiplesOptionsProperty -> String)
-> ([SmallMultiplesOptionsProperty] -> ShowS)
-> Show SmallMultiplesOptionsProperty
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> SmallMultiplesOptionsProperty -> ShowS
showsPrec :: Int -> SmallMultiplesOptionsProperty -> ShowS
$cshow :: SmallMultiplesOptionsProperty -> String
show :: SmallMultiplesOptionsProperty -> String
$cshowList :: [SmallMultiplesOptionsProperty] -> ShowS
showList :: [SmallMultiplesOptionsProperty] -> ShowS
Prelude.Show)
mkSmallMultiplesOptionsProperty :: SmallMultiplesOptionsProperty
mkSmallMultiplesOptionsProperty :: SmallMultiplesOptionsProperty
mkSmallMultiplesOptionsProperty
= SmallMultiplesOptionsProperty
{haddock_workaround_ :: ()
haddock_workaround_ = (), maxVisibleColumns :: Maybe (Value Double)
maxVisibleColumns = Maybe (Value Double)
forall a. Maybe a
Prelude.Nothing,
maxVisibleRows :: Maybe (Value Double)
maxVisibleRows = Maybe (Value Double)
forall a. Maybe a
Prelude.Nothing,
panelConfiguration :: Maybe PanelConfigurationProperty
panelConfiguration = Maybe PanelConfigurationProperty
forall a. Maybe a
Prelude.Nothing, xAxis :: Maybe SmallMultiplesAxisPropertiesProperty
xAxis = Maybe SmallMultiplesAxisPropertiesProperty
forall a. Maybe a
Prelude.Nothing,
yAxis :: Maybe SmallMultiplesAxisPropertiesProperty
yAxis = Maybe SmallMultiplesAxisPropertiesProperty
forall a. Maybe a
Prelude.Nothing}
instance ToResourceProperties SmallMultiplesOptionsProperty where
toResourceProperties :: SmallMultiplesOptionsProperty -> ResourceProperties
toResourceProperties SmallMultiplesOptionsProperty {Maybe (Value Double)
Maybe PanelConfigurationProperty
Maybe SmallMultiplesAxisPropertiesProperty
()
haddock_workaround_ :: SmallMultiplesOptionsProperty -> ()
maxVisibleColumns :: SmallMultiplesOptionsProperty -> Maybe (Value Double)
maxVisibleRows :: SmallMultiplesOptionsProperty -> Maybe (Value Double)
panelConfiguration :: SmallMultiplesOptionsProperty -> Maybe PanelConfigurationProperty
xAxis :: SmallMultiplesOptionsProperty
-> Maybe SmallMultiplesAxisPropertiesProperty
yAxis :: SmallMultiplesOptionsProperty
-> Maybe SmallMultiplesAxisPropertiesProperty
haddock_workaround_ :: ()
maxVisibleColumns :: Maybe (Value Double)
maxVisibleRows :: Maybe (Value Double)
panelConfiguration :: Maybe PanelConfigurationProperty
xAxis :: Maybe SmallMultiplesAxisPropertiesProperty
yAxis :: Maybe SmallMultiplesAxisPropertiesProperty
..}
= ResourceProperties
{awsType :: Text
awsType = Text
"AWS::QuickSight::Dashboard.SmallMultiplesOptions",
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 -> 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
"MaxVisibleColumns" (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)
maxVisibleColumns,
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
"MaxVisibleRows" (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)
maxVisibleRows,
Key -> PanelConfigurationProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"PanelConfiguration" (PanelConfigurationProperty -> (Key, Value))
-> Maybe PanelConfigurationProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe PanelConfigurationProperty
panelConfiguration,
Key -> SmallMultiplesAxisPropertiesProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"XAxis" (SmallMultiplesAxisPropertiesProperty -> (Key, Value))
-> Maybe SmallMultiplesAxisPropertiesProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe SmallMultiplesAxisPropertiesProperty
xAxis,
Key -> SmallMultiplesAxisPropertiesProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"YAxis" (SmallMultiplesAxisPropertiesProperty -> (Key, Value))
-> Maybe SmallMultiplesAxisPropertiesProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe SmallMultiplesAxisPropertiesProperty
yAxis])}
instance JSON.ToJSON SmallMultiplesOptionsProperty where
toJSON :: SmallMultiplesOptionsProperty -> Value
toJSON SmallMultiplesOptionsProperty {Maybe (Value Double)
Maybe PanelConfigurationProperty
Maybe SmallMultiplesAxisPropertiesProperty
()
haddock_workaround_ :: SmallMultiplesOptionsProperty -> ()
maxVisibleColumns :: SmallMultiplesOptionsProperty -> Maybe (Value Double)
maxVisibleRows :: SmallMultiplesOptionsProperty -> Maybe (Value Double)
panelConfiguration :: SmallMultiplesOptionsProperty -> Maybe PanelConfigurationProperty
xAxis :: SmallMultiplesOptionsProperty
-> Maybe SmallMultiplesAxisPropertiesProperty
yAxis :: SmallMultiplesOptionsProperty
-> Maybe SmallMultiplesAxisPropertiesProperty
haddock_workaround_ :: ()
maxVisibleColumns :: Maybe (Value Double)
maxVisibleRows :: Maybe (Value Double)
panelConfiguration :: Maybe PanelConfigurationProperty
xAxis :: Maybe SmallMultiplesAxisPropertiesProperty
yAxis :: Maybe SmallMultiplesAxisPropertiesProperty
..}
= [(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 -> 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
"MaxVisibleColumns" (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)
maxVisibleColumns,
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
"MaxVisibleRows" (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)
maxVisibleRows,
Key -> PanelConfigurationProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"PanelConfiguration" (PanelConfigurationProperty -> (Key, Value))
-> Maybe PanelConfigurationProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe PanelConfigurationProperty
panelConfiguration,
Key -> SmallMultiplesAxisPropertiesProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"XAxis" (SmallMultiplesAxisPropertiesProperty -> (Key, Value))
-> Maybe SmallMultiplesAxisPropertiesProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe SmallMultiplesAxisPropertiesProperty
xAxis,
Key -> SmallMultiplesAxisPropertiesProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"YAxis" (SmallMultiplesAxisPropertiesProperty -> (Key, Value))
-> Maybe SmallMultiplesAxisPropertiesProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe SmallMultiplesAxisPropertiesProperty
yAxis]))
instance Property "MaxVisibleColumns" SmallMultiplesOptionsProperty where
type PropertyType "MaxVisibleColumns" SmallMultiplesOptionsProperty = Value Prelude.Double
set :: PropertyType "MaxVisibleColumns" SmallMultiplesOptionsProperty
-> SmallMultiplesOptionsProperty -> SmallMultiplesOptionsProperty
set PropertyType "MaxVisibleColumns" SmallMultiplesOptionsProperty
newValue SmallMultiplesOptionsProperty {Maybe (Value Double)
Maybe PanelConfigurationProperty
Maybe SmallMultiplesAxisPropertiesProperty
()
haddock_workaround_ :: SmallMultiplesOptionsProperty -> ()
maxVisibleColumns :: SmallMultiplesOptionsProperty -> Maybe (Value Double)
maxVisibleRows :: SmallMultiplesOptionsProperty -> Maybe (Value Double)
panelConfiguration :: SmallMultiplesOptionsProperty -> Maybe PanelConfigurationProperty
xAxis :: SmallMultiplesOptionsProperty
-> Maybe SmallMultiplesAxisPropertiesProperty
yAxis :: SmallMultiplesOptionsProperty
-> Maybe SmallMultiplesAxisPropertiesProperty
haddock_workaround_ :: ()
maxVisibleColumns :: Maybe (Value Double)
maxVisibleRows :: Maybe (Value Double)
panelConfiguration :: Maybe PanelConfigurationProperty
xAxis :: Maybe SmallMultiplesAxisPropertiesProperty
yAxis :: Maybe SmallMultiplesAxisPropertiesProperty
..}
= SmallMultiplesOptionsProperty
{maxVisibleColumns :: Maybe (Value Double)
maxVisibleColumns = Value Double -> Maybe (Value Double)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "MaxVisibleColumns" SmallMultiplesOptionsProperty
Value Double
newValue, Maybe (Value Double)
Maybe PanelConfigurationProperty
Maybe SmallMultiplesAxisPropertiesProperty
()
haddock_workaround_ :: ()
maxVisibleRows :: Maybe (Value Double)
panelConfiguration :: Maybe PanelConfigurationProperty
xAxis :: Maybe SmallMultiplesAxisPropertiesProperty
yAxis :: Maybe SmallMultiplesAxisPropertiesProperty
haddock_workaround_ :: ()
maxVisibleRows :: Maybe (Value Double)
panelConfiguration :: Maybe PanelConfigurationProperty
xAxis :: Maybe SmallMultiplesAxisPropertiesProperty
yAxis :: Maybe SmallMultiplesAxisPropertiesProperty
..}
instance Property "MaxVisibleRows" SmallMultiplesOptionsProperty where
type PropertyType "MaxVisibleRows" SmallMultiplesOptionsProperty = Value Prelude.Double
set :: PropertyType "MaxVisibleRows" SmallMultiplesOptionsProperty
-> SmallMultiplesOptionsProperty -> SmallMultiplesOptionsProperty
set PropertyType "MaxVisibleRows" SmallMultiplesOptionsProperty
newValue SmallMultiplesOptionsProperty {Maybe (Value Double)
Maybe PanelConfigurationProperty
Maybe SmallMultiplesAxisPropertiesProperty
()
haddock_workaround_ :: SmallMultiplesOptionsProperty -> ()
maxVisibleColumns :: SmallMultiplesOptionsProperty -> Maybe (Value Double)
maxVisibleRows :: SmallMultiplesOptionsProperty -> Maybe (Value Double)
panelConfiguration :: SmallMultiplesOptionsProperty -> Maybe PanelConfigurationProperty
xAxis :: SmallMultiplesOptionsProperty
-> Maybe SmallMultiplesAxisPropertiesProperty
yAxis :: SmallMultiplesOptionsProperty
-> Maybe SmallMultiplesAxisPropertiesProperty
haddock_workaround_ :: ()
maxVisibleColumns :: Maybe (Value Double)
maxVisibleRows :: Maybe (Value Double)
panelConfiguration :: Maybe PanelConfigurationProperty
xAxis :: Maybe SmallMultiplesAxisPropertiesProperty
yAxis :: Maybe SmallMultiplesAxisPropertiesProperty
..}
= SmallMultiplesOptionsProperty
{maxVisibleRows :: Maybe (Value Double)
maxVisibleRows = Value Double -> Maybe (Value Double)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "MaxVisibleRows" SmallMultiplesOptionsProperty
Value Double
newValue, Maybe (Value Double)
Maybe PanelConfigurationProperty
Maybe SmallMultiplesAxisPropertiesProperty
()
haddock_workaround_ :: ()
maxVisibleColumns :: Maybe (Value Double)
panelConfiguration :: Maybe PanelConfigurationProperty
xAxis :: Maybe SmallMultiplesAxisPropertiesProperty
yAxis :: Maybe SmallMultiplesAxisPropertiesProperty
haddock_workaround_ :: ()
maxVisibleColumns :: Maybe (Value Double)
panelConfiguration :: Maybe PanelConfigurationProperty
xAxis :: Maybe SmallMultiplesAxisPropertiesProperty
yAxis :: Maybe SmallMultiplesAxisPropertiesProperty
..}
instance Property "PanelConfiguration" SmallMultiplesOptionsProperty where
type PropertyType "PanelConfiguration" SmallMultiplesOptionsProperty = PanelConfigurationProperty
set :: PropertyType "PanelConfiguration" SmallMultiplesOptionsProperty
-> SmallMultiplesOptionsProperty -> SmallMultiplesOptionsProperty
set PropertyType "PanelConfiguration" SmallMultiplesOptionsProperty
newValue SmallMultiplesOptionsProperty {Maybe (Value Double)
Maybe PanelConfigurationProperty
Maybe SmallMultiplesAxisPropertiesProperty
()
haddock_workaround_ :: SmallMultiplesOptionsProperty -> ()
maxVisibleColumns :: SmallMultiplesOptionsProperty -> Maybe (Value Double)
maxVisibleRows :: SmallMultiplesOptionsProperty -> Maybe (Value Double)
panelConfiguration :: SmallMultiplesOptionsProperty -> Maybe PanelConfigurationProperty
xAxis :: SmallMultiplesOptionsProperty
-> Maybe SmallMultiplesAxisPropertiesProperty
yAxis :: SmallMultiplesOptionsProperty
-> Maybe SmallMultiplesAxisPropertiesProperty
haddock_workaround_ :: ()
maxVisibleColumns :: Maybe (Value Double)
maxVisibleRows :: Maybe (Value Double)
panelConfiguration :: Maybe PanelConfigurationProperty
xAxis :: Maybe SmallMultiplesAxisPropertiesProperty
yAxis :: Maybe SmallMultiplesAxisPropertiesProperty
..}
= SmallMultiplesOptionsProperty
{panelConfiguration :: Maybe PanelConfigurationProperty
panelConfiguration = PanelConfigurationProperty -> Maybe PanelConfigurationProperty
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "PanelConfiguration" SmallMultiplesOptionsProperty
PanelConfigurationProperty
newValue, Maybe (Value Double)
Maybe SmallMultiplesAxisPropertiesProperty
()
haddock_workaround_ :: ()
maxVisibleColumns :: Maybe (Value Double)
maxVisibleRows :: Maybe (Value Double)
xAxis :: Maybe SmallMultiplesAxisPropertiesProperty
yAxis :: Maybe SmallMultiplesAxisPropertiesProperty
haddock_workaround_ :: ()
maxVisibleColumns :: Maybe (Value Double)
maxVisibleRows :: Maybe (Value Double)
xAxis :: Maybe SmallMultiplesAxisPropertiesProperty
yAxis :: Maybe SmallMultiplesAxisPropertiesProperty
..}
instance Property "XAxis" SmallMultiplesOptionsProperty where
type PropertyType "XAxis" SmallMultiplesOptionsProperty = SmallMultiplesAxisPropertiesProperty
set :: PropertyType "XAxis" SmallMultiplesOptionsProperty
-> SmallMultiplesOptionsProperty -> SmallMultiplesOptionsProperty
set PropertyType "XAxis" SmallMultiplesOptionsProperty
newValue SmallMultiplesOptionsProperty {Maybe (Value Double)
Maybe PanelConfigurationProperty
Maybe SmallMultiplesAxisPropertiesProperty
()
haddock_workaround_ :: SmallMultiplesOptionsProperty -> ()
maxVisibleColumns :: SmallMultiplesOptionsProperty -> Maybe (Value Double)
maxVisibleRows :: SmallMultiplesOptionsProperty -> Maybe (Value Double)
panelConfiguration :: SmallMultiplesOptionsProperty -> Maybe PanelConfigurationProperty
xAxis :: SmallMultiplesOptionsProperty
-> Maybe SmallMultiplesAxisPropertiesProperty
yAxis :: SmallMultiplesOptionsProperty
-> Maybe SmallMultiplesAxisPropertiesProperty
haddock_workaround_ :: ()
maxVisibleColumns :: Maybe (Value Double)
maxVisibleRows :: Maybe (Value Double)
panelConfiguration :: Maybe PanelConfigurationProperty
xAxis :: Maybe SmallMultiplesAxisPropertiesProperty
yAxis :: Maybe SmallMultiplesAxisPropertiesProperty
..}
= SmallMultiplesOptionsProperty {xAxis :: Maybe SmallMultiplesAxisPropertiesProperty
xAxis = SmallMultiplesAxisPropertiesProperty
-> Maybe SmallMultiplesAxisPropertiesProperty
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "XAxis" SmallMultiplesOptionsProperty
SmallMultiplesAxisPropertiesProperty
newValue, Maybe (Value Double)
Maybe PanelConfigurationProperty
Maybe SmallMultiplesAxisPropertiesProperty
()
haddock_workaround_ :: ()
maxVisibleColumns :: Maybe (Value Double)
maxVisibleRows :: Maybe (Value Double)
panelConfiguration :: Maybe PanelConfigurationProperty
yAxis :: Maybe SmallMultiplesAxisPropertiesProperty
haddock_workaround_ :: ()
maxVisibleColumns :: Maybe (Value Double)
maxVisibleRows :: Maybe (Value Double)
panelConfiguration :: Maybe PanelConfigurationProperty
yAxis :: Maybe SmallMultiplesAxisPropertiesProperty
..}
instance Property "YAxis" SmallMultiplesOptionsProperty where
type PropertyType "YAxis" SmallMultiplesOptionsProperty = SmallMultiplesAxisPropertiesProperty
set :: PropertyType "YAxis" SmallMultiplesOptionsProperty
-> SmallMultiplesOptionsProperty -> SmallMultiplesOptionsProperty
set PropertyType "YAxis" SmallMultiplesOptionsProperty
newValue SmallMultiplesOptionsProperty {Maybe (Value Double)
Maybe PanelConfigurationProperty
Maybe SmallMultiplesAxisPropertiesProperty
()
haddock_workaround_ :: SmallMultiplesOptionsProperty -> ()
maxVisibleColumns :: SmallMultiplesOptionsProperty -> Maybe (Value Double)
maxVisibleRows :: SmallMultiplesOptionsProperty -> Maybe (Value Double)
panelConfiguration :: SmallMultiplesOptionsProperty -> Maybe PanelConfigurationProperty
xAxis :: SmallMultiplesOptionsProperty
-> Maybe SmallMultiplesAxisPropertiesProperty
yAxis :: SmallMultiplesOptionsProperty
-> Maybe SmallMultiplesAxisPropertiesProperty
haddock_workaround_ :: ()
maxVisibleColumns :: Maybe (Value Double)
maxVisibleRows :: Maybe (Value Double)
panelConfiguration :: Maybe PanelConfigurationProperty
xAxis :: Maybe SmallMultiplesAxisPropertiesProperty
yAxis :: Maybe SmallMultiplesAxisPropertiesProperty
..}
= SmallMultiplesOptionsProperty {yAxis :: Maybe SmallMultiplesAxisPropertiesProperty
yAxis = SmallMultiplesAxisPropertiesProperty
-> Maybe SmallMultiplesAxisPropertiesProperty
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "YAxis" SmallMultiplesOptionsProperty
SmallMultiplesAxisPropertiesProperty
newValue, Maybe (Value Double)
Maybe PanelConfigurationProperty
Maybe SmallMultiplesAxisPropertiesProperty
()
haddock_workaround_ :: ()
maxVisibleColumns :: Maybe (Value Double)
maxVisibleRows :: Maybe (Value Double)
panelConfiguration :: Maybe PanelConfigurationProperty
xAxis :: Maybe SmallMultiplesAxisPropertiesProperty
haddock_workaround_ :: ()
maxVisibleColumns :: Maybe (Value Double)
maxVisibleRows :: Maybe (Value Double)
panelConfiguration :: Maybe PanelConfigurationProperty
xAxis :: Maybe SmallMultiplesAxisPropertiesProperty
..}