module Stratosphere.QuickSight.Template.DefaultSectionBasedLayoutConfigurationProperty (
module Exports, DefaultSectionBasedLayoutConfigurationProperty(..),
mkDefaultSectionBasedLayoutConfigurationProperty
) where
import qualified Data.Aeson as JSON
import qualified Stratosphere.Prelude as Prelude
import Stratosphere.Property
import {-# SOURCE #-} Stratosphere.QuickSight.Template.SectionBasedLayoutCanvasSizeOptionsProperty as Exports
import Stratosphere.ResourceProperties
data DefaultSectionBasedLayoutConfigurationProperty
=
DefaultSectionBasedLayoutConfigurationProperty {DefaultSectionBasedLayoutConfigurationProperty -> ()
haddock_workaround_ :: (),
DefaultSectionBasedLayoutConfigurationProperty
-> SectionBasedLayoutCanvasSizeOptionsProperty
canvasSizeOptions :: SectionBasedLayoutCanvasSizeOptionsProperty}
deriving stock (DefaultSectionBasedLayoutConfigurationProperty
-> DefaultSectionBasedLayoutConfigurationProperty -> Bool
(DefaultSectionBasedLayoutConfigurationProperty
-> DefaultSectionBasedLayoutConfigurationProperty -> Bool)
-> (DefaultSectionBasedLayoutConfigurationProperty
-> DefaultSectionBasedLayoutConfigurationProperty -> Bool)
-> Eq DefaultSectionBasedLayoutConfigurationProperty
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: DefaultSectionBasedLayoutConfigurationProperty
-> DefaultSectionBasedLayoutConfigurationProperty -> Bool
== :: DefaultSectionBasedLayoutConfigurationProperty
-> DefaultSectionBasedLayoutConfigurationProperty -> Bool
$c/= :: DefaultSectionBasedLayoutConfigurationProperty
-> DefaultSectionBasedLayoutConfigurationProperty -> Bool
/= :: DefaultSectionBasedLayoutConfigurationProperty
-> DefaultSectionBasedLayoutConfigurationProperty -> Bool
Prelude.Eq, Int -> DefaultSectionBasedLayoutConfigurationProperty -> ShowS
[DefaultSectionBasedLayoutConfigurationProperty] -> ShowS
DefaultSectionBasedLayoutConfigurationProperty -> String
(Int -> DefaultSectionBasedLayoutConfigurationProperty -> ShowS)
-> (DefaultSectionBasedLayoutConfigurationProperty -> String)
-> ([DefaultSectionBasedLayoutConfigurationProperty] -> ShowS)
-> Show DefaultSectionBasedLayoutConfigurationProperty
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> DefaultSectionBasedLayoutConfigurationProperty -> ShowS
showsPrec :: Int -> DefaultSectionBasedLayoutConfigurationProperty -> ShowS
$cshow :: DefaultSectionBasedLayoutConfigurationProperty -> String
show :: DefaultSectionBasedLayoutConfigurationProperty -> String
$cshowList :: [DefaultSectionBasedLayoutConfigurationProperty] -> ShowS
showList :: [DefaultSectionBasedLayoutConfigurationProperty] -> ShowS
Prelude.Show)
mkDefaultSectionBasedLayoutConfigurationProperty ::
SectionBasedLayoutCanvasSizeOptionsProperty
-> DefaultSectionBasedLayoutConfigurationProperty
mkDefaultSectionBasedLayoutConfigurationProperty :: SectionBasedLayoutCanvasSizeOptionsProperty
-> DefaultSectionBasedLayoutConfigurationProperty
mkDefaultSectionBasedLayoutConfigurationProperty SectionBasedLayoutCanvasSizeOptionsProperty
canvasSizeOptions
= DefaultSectionBasedLayoutConfigurationProperty
{haddock_workaround_ :: ()
haddock_workaround_ = (), canvasSizeOptions :: SectionBasedLayoutCanvasSizeOptionsProperty
canvasSizeOptions = SectionBasedLayoutCanvasSizeOptionsProperty
canvasSizeOptions}
instance ToResourceProperties DefaultSectionBasedLayoutConfigurationProperty where
toResourceProperties :: DefaultSectionBasedLayoutConfigurationProperty
-> ResourceProperties
toResourceProperties
DefaultSectionBasedLayoutConfigurationProperty {()
SectionBasedLayoutCanvasSizeOptionsProperty
haddock_workaround_ :: DefaultSectionBasedLayoutConfigurationProperty -> ()
canvasSizeOptions :: DefaultSectionBasedLayoutConfigurationProperty
-> SectionBasedLayoutCanvasSizeOptionsProperty
haddock_workaround_ :: ()
canvasSizeOptions :: SectionBasedLayoutCanvasSizeOptionsProperty
..}
= ResourceProperties
{awsType :: Text
awsType = Text
"AWS::QuickSight::Template.DefaultSectionBasedLayoutConfiguration",
supportsTags :: Bool
supportsTags = Bool
Prelude.False,
properties :: Object
properties = [Key
"CanvasSizeOptions" Key -> SectionBasedLayoutCanvasSizeOptionsProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
JSON..= SectionBasedLayoutCanvasSizeOptionsProperty
canvasSizeOptions]}
instance JSON.ToJSON DefaultSectionBasedLayoutConfigurationProperty where
toJSON :: DefaultSectionBasedLayoutConfigurationProperty -> Value
toJSON DefaultSectionBasedLayoutConfigurationProperty {()
SectionBasedLayoutCanvasSizeOptionsProperty
haddock_workaround_ :: DefaultSectionBasedLayoutConfigurationProperty -> ()
canvasSizeOptions :: DefaultSectionBasedLayoutConfigurationProperty
-> SectionBasedLayoutCanvasSizeOptionsProperty
haddock_workaround_ :: ()
canvasSizeOptions :: SectionBasedLayoutCanvasSizeOptionsProperty
..}
= [(Key, Value)] -> Value
JSON.object [Key
"CanvasSizeOptions" Key -> SectionBasedLayoutCanvasSizeOptionsProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
JSON..= SectionBasedLayoutCanvasSizeOptionsProperty
canvasSizeOptions]
instance Property "CanvasSizeOptions" DefaultSectionBasedLayoutConfigurationProperty where
type PropertyType "CanvasSizeOptions" DefaultSectionBasedLayoutConfigurationProperty = SectionBasedLayoutCanvasSizeOptionsProperty
set :: PropertyType
"CanvasSizeOptions" DefaultSectionBasedLayoutConfigurationProperty
-> DefaultSectionBasedLayoutConfigurationProperty
-> DefaultSectionBasedLayoutConfigurationProperty
set PropertyType
"CanvasSizeOptions" DefaultSectionBasedLayoutConfigurationProperty
newValue DefaultSectionBasedLayoutConfigurationProperty {()
SectionBasedLayoutCanvasSizeOptionsProperty
haddock_workaround_ :: DefaultSectionBasedLayoutConfigurationProperty -> ()
canvasSizeOptions :: DefaultSectionBasedLayoutConfigurationProperty
-> SectionBasedLayoutCanvasSizeOptionsProperty
haddock_workaround_ :: ()
canvasSizeOptions :: SectionBasedLayoutCanvasSizeOptionsProperty
..}
= DefaultSectionBasedLayoutConfigurationProperty
{canvasSizeOptions :: SectionBasedLayoutCanvasSizeOptionsProperty
canvasSizeOptions = PropertyType
"CanvasSizeOptions" DefaultSectionBasedLayoutConfigurationProperty
SectionBasedLayoutCanvasSizeOptionsProperty
newValue, ()
haddock_workaround_ :: ()
haddock_workaround_ :: ()
..}