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