module Stratosphere.QuickSight.Template.ContributionAnalysisDefaultProperty (
        module Exports, ContributionAnalysisDefaultProperty(..),
        mkContributionAnalysisDefaultProperty
    ) where
import qualified Data.Aeson as JSON
import qualified Stratosphere.Prelude as Prelude
import Stratosphere.Property
import {-# SOURCE #-} Stratosphere.QuickSight.Template.ColumnIdentifierProperty as Exports
import Stratosphere.ResourceProperties
import Stratosphere.Value
data ContributionAnalysisDefaultProperty
  = -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-quicksight-template-contributionanalysisdefault.html>
    ContributionAnalysisDefaultProperty {ContributionAnalysisDefaultProperty -> ()
haddock_workaround_ :: (),
                                         -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-quicksight-template-contributionanalysisdefault.html#cfn-quicksight-template-contributionanalysisdefault-contributordimensions>
                                         ContributionAnalysisDefaultProperty -> [ColumnIdentifierProperty]
contributorDimensions :: [ColumnIdentifierProperty],
                                         -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-quicksight-template-contributionanalysisdefault.html#cfn-quicksight-template-contributionanalysisdefault-measurefieldid>
                                         ContributionAnalysisDefaultProperty -> Value Text
measureFieldId :: (Value Prelude.Text)}
  deriving stock (ContributionAnalysisDefaultProperty
-> ContributionAnalysisDefaultProperty -> Bool
(ContributionAnalysisDefaultProperty
 -> ContributionAnalysisDefaultProperty -> Bool)
-> (ContributionAnalysisDefaultProperty
    -> ContributionAnalysisDefaultProperty -> Bool)
-> Eq ContributionAnalysisDefaultProperty
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ContributionAnalysisDefaultProperty
-> ContributionAnalysisDefaultProperty -> Bool
== :: ContributionAnalysisDefaultProperty
-> ContributionAnalysisDefaultProperty -> Bool
$c/= :: ContributionAnalysisDefaultProperty
-> ContributionAnalysisDefaultProperty -> Bool
/= :: ContributionAnalysisDefaultProperty
-> ContributionAnalysisDefaultProperty -> Bool
Prelude.Eq, Int -> ContributionAnalysisDefaultProperty -> ShowS
[ContributionAnalysisDefaultProperty] -> ShowS
ContributionAnalysisDefaultProperty -> String
(Int -> ContributionAnalysisDefaultProperty -> ShowS)
-> (ContributionAnalysisDefaultProperty -> String)
-> ([ContributionAnalysisDefaultProperty] -> ShowS)
-> Show ContributionAnalysisDefaultProperty
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ContributionAnalysisDefaultProperty -> ShowS
showsPrec :: Int -> ContributionAnalysisDefaultProperty -> ShowS
$cshow :: ContributionAnalysisDefaultProperty -> String
show :: ContributionAnalysisDefaultProperty -> String
$cshowList :: [ContributionAnalysisDefaultProperty] -> ShowS
showList :: [ContributionAnalysisDefaultProperty] -> ShowS
Prelude.Show)
mkContributionAnalysisDefaultProperty ::
  [ColumnIdentifierProperty]
  -> Value Prelude.Text -> ContributionAnalysisDefaultProperty
mkContributionAnalysisDefaultProperty :: [ColumnIdentifierProperty]
-> Value Text -> ContributionAnalysisDefaultProperty
mkContributionAnalysisDefaultProperty
  [ColumnIdentifierProperty]
contributorDimensions
  Value Text
measureFieldId
  = ContributionAnalysisDefaultProperty
      {haddock_workaround_ :: ()
haddock_workaround_ = (),
       contributorDimensions :: [ColumnIdentifierProperty]
contributorDimensions = [ColumnIdentifierProperty]
contributorDimensions,
       measureFieldId :: Value Text
measureFieldId = Value Text
measureFieldId}
instance ToResourceProperties ContributionAnalysisDefaultProperty where
  toResourceProperties :: ContributionAnalysisDefaultProperty -> ResourceProperties
toResourceProperties ContributionAnalysisDefaultProperty {[ColumnIdentifierProperty]
()
Value Text
haddock_workaround_ :: ContributionAnalysisDefaultProperty -> ()
contributorDimensions :: ContributionAnalysisDefaultProperty -> [ColumnIdentifierProperty]
measureFieldId :: ContributionAnalysisDefaultProperty -> Value Text
haddock_workaround_ :: ()
contributorDimensions :: [ColumnIdentifierProperty]
measureFieldId :: Value Text
..}
    = ResourceProperties
        {awsType :: Text
awsType = Text
"AWS::QuickSight::Template.ContributionAnalysisDefault",
         supportsTags :: Bool
supportsTags = Bool
Prelude.False,
         properties :: Object
properties = [Key
"ContributorDimensions"
                         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]
contributorDimensions,
                       Key
"MeasureFieldId" 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
measureFieldId]}
instance JSON.ToJSON ContributionAnalysisDefaultProperty where
  toJSON :: ContributionAnalysisDefaultProperty -> Value
toJSON ContributionAnalysisDefaultProperty {[ColumnIdentifierProperty]
()
Value Text
haddock_workaround_ :: ContributionAnalysisDefaultProperty -> ()
contributorDimensions :: ContributionAnalysisDefaultProperty -> [ColumnIdentifierProperty]
measureFieldId :: ContributionAnalysisDefaultProperty -> Value Text
haddock_workaround_ :: ()
contributorDimensions :: [ColumnIdentifierProperty]
measureFieldId :: Value Text
..}
    = [(Key, Value)] -> Value
JSON.object
        [Key
"ContributorDimensions" 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]
contributorDimensions,
         Key
"MeasureFieldId" 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
measureFieldId]
instance Property "ContributorDimensions" ContributionAnalysisDefaultProperty where
  type PropertyType "ContributorDimensions" ContributionAnalysisDefaultProperty = [ColumnIdentifierProperty]
  set :: PropertyType
  "ContributorDimensions" ContributionAnalysisDefaultProperty
-> ContributionAnalysisDefaultProperty
-> ContributionAnalysisDefaultProperty
set PropertyType
  "ContributorDimensions" ContributionAnalysisDefaultProperty
newValue ContributionAnalysisDefaultProperty {[ColumnIdentifierProperty]
()
Value Text
haddock_workaround_ :: ContributionAnalysisDefaultProperty -> ()
contributorDimensions :: ContributionAnalysisDefaultProperty -> [ColumnIdentifierProperty]
measureFieldId :: ContributionAnalysisDefaultProperty -> Value Text
haddock_workaround_ :: ()
contributorDimensions :: [ColumnIdentifierProperty]
measureFieldId :: Value Text
..}
    = ContributionAnalysisDefaultProperty
        {contributorDimensions :: [ColumnIdentifierProperty]
contributorDimensions = [ColumnIdentifierProperty]
PropertyType
  "ContributorDimensions" ContributionAnalysisDefaultProperty
newValue, ()
Value Text
haddock_workaround_ :: ()
measureFieldId :: Value Text
haddock_workaround_ :: ()
measureFieldId :: Value Text
..}
instance Property "MeasureFieldId" ContributionAnalysisDefaultProperty where
  type PropertyType "MeasureFieldId" ContributionAnalysisDefaultProperty = Value Prelude.Text
  set :: PropertyType "MeasureFieldId" ContributionAnalysisDefaultProperty
-> ContributionAnalysisDefaultProperty
-> ContributionAnalysisDefaultProperty
set PropertyType "MeasureFieldId" ContributionAnalysisDefaultProperty
newValue ContributionAnalysisDefaultProperty {[ColumnIdentifierProperty]
()
Value Text
haddock_workaround_ :: ContributionAnalysisDefaultProperty -> ()
contributorDimensions :: ContributionAnalysisDefaultProperty -> [ColumnIdentifierProperty]
measureFieldId :: ContributionAnalysisDefaultProperty -> Value Text
haddock_workaround_ :: ()
contributorDimensions :: [ColumnIdentifierProperty]
measureFieldId :: Value Text
..}
    = ContributionAnalysisDefaultProperty
        {measureFieldId :: Value Text
measureFieldId = PropertyType "MeasureFieldId" ContributionAnalysisDefaultProperty
Value Text
newValue, [ColumnIdentifierProperty]
()
haddock_workaround_ :: ()
contributorDimensions :: [ColumnIdentifierProperty]
haddock_workaround_ :: ()
contributorDimensions :: [ColumnIdentifierProperty]
..}