module Stratosphere.QuickSight.Template.SectionLayoutConfigurationProperty (
        module Exports, SectionLayoutConfigurationProperty(..),
        mkSectionLayoutConfigurationProperty
    ) where
import qualified Data.Aeson as JSON
import qualified Stratosphere.Prelude as Prelude
import Stratosphere.Property
import {-# SOURCE #-} Stratosphere.QuickSight.Template.FreeFormSectionLayoutConfigurationProperty as Exports
import Stratosphere.ResourceProperties
data SectionLayoutConfigurationProperty
  = -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-quicksight-template-sectionlayoutconfiguration.html>
    SectionLayoutConfigurationProperty {SectionLayoutConfigurationProperty -> ()
haddock_workaround_ :: (),
                                        -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-quicksight-template-sectionlayoutconfiguration.html#cfn-quicksight-template-sectionlayoutconfiguration-freeformlayout>
                                        SectionLayoutConfigurationProperty
-> FreeFormSectionLayoutConfigurationProperty
freeFormLayout :: FreeFormSectionLayoutConfigurationProperty}
  deriving stock (SectionLayoutConfigurationProperty
-> SectionLayoutConfigurationProperty -> Bool
(SectionLayoutConfigurationProperty
 -> SectionLayoutConfigurationProperty -> Bool)
-> (SectionLayoutConfigurationProperty
    -> SectionLayoutConfigurationProperty -> Bool)
-> Eq SectionLayoutConfigurationProperty
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: SectionLayoutConfigurationProperty
-> SectionLayoutConfigurationProperty -> Bool
== :: SectionLayoutConfigurationProperty
-> SectionLayoutConfigurationProperty -> Bool
$c/= :: SectionLayoutConfigurationProperty
-> SectionLayoutConfigurationProperty -> Bool
/= :: SectionLayoutConfigurationProperty
-> SectionLayoutConfigurationProperty -> Bool
Prelude.Eq, Int -> SectionLayoutConfigurationProperty -> ShowS
[SectionLayoutConfigurationProperty] -> ShowS
SectionLayoutConfigurationProperty -> String
(Int -> SectionLayoutConfigurationProperty -> ShowS)
-> (SectionLayoutConfigurationProperty -> String)
-> ([SectionLayoutConfigurationProperty] -> ShowS)
-> Show SectionLayoutConfigurationProperty
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> SectionLayoutConfigurationProperty -> ShowS
showsPrec :: Int -> SectionLayoutConfigurationProperty -> ShowS
$cshow :: SectionLayoutConfigurationProperty -> String
show :: SectionLayoutConfigurationProperty -> String
$cshowList :: [SectionLayoutConfigurationProperty] -> ShowS
showList :: [SectionLayoutConfigurationProperty] -> ShowS
Prelude.Show)
mkSectionLayoutConfigurationProperty ::
  FreeFormSectionLayoutConfigurationProperty
  -> SectionLayoutConfigurationProperty
mkSectionLayoutConfigurationProperty :: FreeFormSectionLayoutConfigurationProperty
-> SectionLayoutConfigurationProperty
mkSectionLayoutConfigurationProperty FreeFormSectionLayoutConfigurationProperty
freeFormLayout
  = SectionLayoutConfigurationProperty
      {haddock_workaround_ :: ()
haddock_workaround_ = (), freeFormLayout :: FreeFormSectionLayoutConfigurationProperty
freeFormLayout = FreeFormSectionLayoutConfigurationProperty
freeFormLayout}
instance ToResourceProperties SectionLayoutConfigurationProperty where
  toResourceProperties :: SectionLayoutConfigurationProperty -> ResourceProperties
toResourceProperties SectionLayoutConfigurationProperty {()
FreeFormSectionLayoutConfigurationProperty
haddock_workaround_ :: SectionLayoutConfigurationProperty -> ()
freeFormLayout :: SectionLayoutConfigurationProperty
-> FreeFormSectionLayoutConfigurationProperty
haddock_workaround_ :: ()
freeFormLayout :: FreeFormSectionLayoutConfigurationProperty
..}
    = ResourceProperties
        {awsType :: Text
awsType = Text
"AWS::QuickSight::Template.SectionLayoutConfiguration",
         supportsTags :: Bool
supportsTags = Bool
Prelude.False,
         properties :: Object
properties = [Key
"FreeFormLayout" Key -> FreeFormSectionLayoutConfigurationProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
JSON..= FreeFormSectionLayoutConfigurationProperty
freeFormLayout]}
instance JSON.ToJSON SectionLayoutConfigurationProperty where
  toJSON :: SectionLayoutConfigurationProperty -> Value
toJSON SectionLayoutConfigurationProperty {()
FreeFormSectionLayoutConfigurationProperty
haddock_workaround_ :: SectionLayoutConfigurationProperty -> ()
freeFormLayout :: SectionLayoutConfigurationProperty
-> FreeFormSectionLayoutConfigurationProperty
haddock_workaround_ :: ()
freeFormLayout :: FreeFormSectionLayoutConfigurationProperty
..}
    = [(Key, Value)] -> Value
JSON.object [Key
"FreeFormLayout" Key -> FreeFormSectionLayoutConfigurationProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
JSON..= FreeFormSectionLayoutConfigurationProperty
freeFormLayout]
instance Property "FreeFormLayout" SectionLayoutConfigurationProperty where
  type PropertyType "FreeFormLayout" SectionLayoutConfigurationProperty = FreeFormSectionLayoutConfigurationProperty
  set :: PropertyType "FreeFormLayout" SectionLayoutConfigurationProperty
-> SectionLayoutConfigurationProperty
-> SectionLayoutConfigurationProperty
set PropertyType "FreeFormLayout" SectionLayoutConfigurationProperty
newValue SectionLayoutConfigurationProperty {()
FreeFormSectionLayoutConfigurationProperty
haddock_workaround_ :: SectionLayoutConfigurationProperty -> ()
freeFormLayout :: SectionLayoutConfigurationProperty
-> FreeFormSectionLayoutConfigurationProperty
haddock_workaround_ :: ()
freeFormLayout :: FreeFormSectionLayoutConfigurationProperty
..}
    = SectionLayoutConfigurationProperty
        {freeFormLayout :: FreeFormSectionLayoutConfigurationProperty
freeFormLayout = PropertyType "FreeFormLayout" SectionLayoutConfigurationProperty
FreeFormSectionLayoutConfigurationProperty
newValue, ()
haddock_workaround_ :: ()
haddock_workaround_ :: ()
..}