module Stratosphere.QuickSight.Dashboard.ReferenceLineStaticDataConfigurationProperty (
        ReferenceLineStaticDataConfigurationProperty(..),
        mkReferenceLineStaticDataConfigurationProperty
    ) where
import qualified Data.Aeson as JSON
import qualified Stratosphere.Prelude as Prelude
import Stratosphere.Property
import Stratosphere.ResourceProperties
import Stratosphere.Value
data ReferenceLineStaticDataConfigurationProperty
  = -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-quicksight-dashboard-referencelinestaticdataconfiguration.html>
    ReferenceLineStaticDataConfigurationProperty {ReferenceLineStaticDataConfigurationProperty -> ()
haddock_workaround_ :: (),
                                                  -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-quicksight-dashboard-referencelinestaticdataconfiguration.html#cfn-quicksight-dashboard-referencelinestaticdataconfiguration-value>
                                                  ReferenceLineStaticDataConfigurationProperty -> Value Double
value :: (Value Prelude.Double)}
  deriving stock (ReferenceLineStaticDataConfigurationProperty
-> ReferenceLineStaticDataConfigurationProperty -> Bool
(ReferenceLineStaticDataConfigurationProperty
 -> ReferenceLineStaticDataConfigurationProperty -> Bool)
-> (ReferenceLineStaticDataConfigurationProperty
    -> ReferenceLineStaticDataConfigurationProperty -> Bool)
-> Eq ReferenceLineStaticDataConfigurationProperty
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ReferenceLineStaticDataConfigurationProperty
-> ReferenceLineStaticDataConfigurationProperty -> Bool
== :: ReferenceLineStaticDataConfigurationProperty
-> ReferenceLineStaticDataConfigurationProperty -> Bool
$c/= :: ReferenceLineStaticDataConfigurationProperty
-> ReferenceLineStaticDataConfigurationProperty -> Bool
/= :: ReferenceLineStaticDataConfigurationProperty
-> ReferenceLineStaticDataConfigurationProperty -> Bool
Prelude.Eq, Int -> ReferenceLineStaticDataConfigurationProperty -> ShowS
[ReferenceLineStaticDataConfigurationProperty] -> ShowS
ReferenceLineStaticDataConfigurationProperty -> String
(Int -> ReferenceLineStaticDataConfigurationProperty -> ShowS)
-> (ReferenceLineStaticDataConfigurationProperty -> String)
-> ([ReferenceLineStaticDataConfigurationProperty] -> ShowS)
-> Show ReferenceLineStaticDataConfigurationProperty
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ReferenceLineStaticDataConfigurationProperty -> ShowS
showsPrec :: Int -> ReferenceLineStaticDataConfigurationProperty -> ShowS
$cshow :: ReferenceLineStaticDataConfigurationProperty -> String
show :: ReferenceLineStaticDataConfigurationProperty -> String
$cshowList :: [ReferenceLineStaticDataConfigurationProperty] -> ShowS
showList :: [ReferenceLineStaticDataConfigurationProperty] -> ShowS
Prelude.Show)
mkReferenceLineStaticDataConfigurationProperty ::
  Value Prelude.Double
  -> ReferenceLineStaticDataConfigurationProperty
mkReferenceLineStaticDataConfigurationProperty :: Value Double -> ReferenceLineStaticDataConfigurationProperty
mkReferenceLineStaticDataConfigurationProperty Value Double
value
  = ReferenceLineStaticDataConfigurationProperty
      {haddock_workaround_ :: ()
haddock_workaround_ = (), value :: Value Double
value = Value Double
value}
instance ToResourceProperties ReferenceLineStaticDataConfigurationProperty where
  toResourceProperties :: ReferenceLineStaticDataConfigurationProperty -> ResourceProperties
toResourceProperties
    ReferenceLineStaticDataConfigurationProperty {()
Value Double
haddock_workaround_ :: ReferenceLineStaticDataConfigurationProperty -> ()
value :: ReferenceLineStaticDataConfigurationProperty -> Value Double
haddock_workaround_ :: ()
value :: Value Double
..}
    = ResourceProperties
        {awsType :: Text
awsType = Text
"AWS::QuickSight::Dashboard.ReferenceLineStaticDataConfiguration",
         supportsTags :: Bool
supportsTags = Bool
Prelude.False, properties :: Object
properties = [Key
"Value" 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..= Value Double
value]}
instance JSON.ToJSON ReferenceLineStaticDataConfigurationProperty where
  toJSON :: ReferenceLineStaticDataConfigurationProperty -> Value
toJSON ReferenceLineStaticDataConfigurationProperty {()
Value Double
haddock_workaround_ :: ReferenceLineStaticDataConfigurationProperty -> ()
value :: ReferenceLineStaticDataConfigurationProperty -> Value Double
haddock_workaround_ :: ()
value :: Value Double
..}
    = [(Key, Value)] -> Value
JSON.object [Key
"Value" 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..= Value Double
value]
instance Property "Value" ReferenceLineStaticDataConfigurationProperty where
  type PropertyType "Value" ReferenceLineStaticDataConfigurationProperty = Value Prelude.Double
  set :: PropertyType "Value" ReferenceLineStaticDataConfigurationProperty
-> ReferenceLineStaticDataConfigurationProperty
-> ReferenceLineStaticDataConfigurationProperty
set PropertyType "Value" ReferenceLineStaticDataConfigurationProperty
newValue ReferenceLineStaticDataConfigurationProperty {()
Value Double
haddock_workaround_ :: ReferenceLineStaticDataConfigurationProperty -> ()
value :: ReferenceLineStaticDataConfigurationProperty -> Value Double
haddock_workaround_ :: ()
value :: Value Double
..}
    = ReferenceLineStaticDataConfigurationProperty
        {value :: Value Double
value = PropertyType "Value" ReferenceLineStaticDataConfigurationProperty
Value Double
newValue, ()
haddock_workaround_ :: ()
haddock_workaround_ :: ()
..}