module Stratosphere.CloudWatch.MetricStream.MetricStreamStatisticsMetricProperty (
        MetricStreamStatisticsMetricProperty(..),
        mkMetricStreamStatisticsMetricProperty
    ) where
import qualified Data.Aeson as JSON
import qualified Stratosphere.Prelude as Prelude
import Stratosphere.Property
import Stratosphere.ResourceProperties
import Stratosphere.Value
data MetricStreamStatisticsMetricProperty
  = -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-cloudwatch-metricstream-metricstreamstatisticsmetric.html>
    MetricStreamStatisticsMetricProperty {MetricStreamStatisticsMetricProperty -> ()
haddock_workaround_ :: (),
                                          -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-cloudwatch-metricstream-metricstreamstatisticsmetric.html#cfn-cloudwatch-metricstream-metricstreamstatisticsmetric-metricname>
                                          MetricStreamStatisticsMetricProperty -> Value Text
metricName :: (Value Prelude.Text),
                                          -- | See: <http://docs.aws.amazon.com/AWSCloudFormation/latest/UserGuide/aws-properties-cloudwatch-metricstream-metricstreamstatisticsmetric.html#cfn-cloudwatch-metricstream-metricstreamstatisticsmetric-namespace>
                                          MetricStreamStatisticsMetricProperty -> Value Text
namespace :: (Value Prelude.Text)}
  deriving stock (MetricStreamStatisticsMetricProperty
-> MetricStreamStatisticsMetricProperty -> Bool
(MetricStreamStatisticsMetricProperty
 -> MetricStreamStatisticsMetricProperty -> Bool)
-> (MetricStreamStatisticsMetricProperty
    -> MetricStreamStatisticsMetricProperty -> Bool)
-> Eq MetricStreamStatisticsMetricProperty
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: MetricStreamStatisticsMetricProperty
-> MetricStreamStatisticsMetricProperty -> Bool
== :: MetricStreamStatisticsMetricProperty
-> MetricStreamStatisticsMetricProperty -> Bool
$c/= :: MetricStreamStatisticsMetricProperty
-> MetricStreamStatisticsMetricProperty -> Bool
/= :: MetricStreamStatisticsMetricProperty
-> MetricStreamStatisticsMetricProperty -> Bool
Prelude.Eq, Int -> MetricStreamStatisticsMetricProperty -> ShowS
[MetricStreamStatisticsMetricProperty] -> ShowS
MetricStreamStatisticsMetricProperty -> String
(Int -> MetricStreamStatisticsMetricProperty -> ShowS)
-> (MetricStreamStatisticsMetricProperty -> String)
-> ([MetricStreamStatisticsMetricProperty] -> ShowS)
-> Show MetricStreamStatisticsMetricProperty
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> MetricStreamStatisticsMetricProperty -> ShowS
showsPrec :: Int -> MetricStreamStatisticsMetricProperty -> ShowS
$cshow :: MetricStreamStatisticsMetricProperty -> String
show :: MetricStreamStatisticsMetricProperty -> String
$cshowList :: [MetricStreamStatisticsMetricProperty] -> ShowS
showList :: [MetricStreamStatisticsMetricProperty] -> ShowS
Prelude.Show)
mkMetricStreamStatisticsMetricProperty ::
  Value Prelude.Text
  -> Value Prelude.Text -> MetricStreamStatisticsMetricProperty
mkMetricStreamStatisticsMetricProperty :: Value Text -> Value Text -> MetricStreamStatisticsMetricProperty
mkMetricStreamStatisticsMetricProperty Value Text
metricName Value Text
namespace
  = MetricStreamStatisticsMetricProperty
      {haddock_workaround_ :: ()
haddock_workaround_ = (), metricName :: Value Text
metricName = Value Text
metricName,
       namespace :: Value Text
namespace = Value Text
namespace}
instance ToResourceProperties MetricStreamStatisticsMetricProperty where
  toResourceProperties :: MetricStreamStatisticsMetricProperty -> ResourceProperties
toResourceProperties MetricStreamStatisticsMetricProperty {()
Value Text
haddock_workaround_ :: MetricStreamStatisticsMetricProperty -> ()
metricName :: MetricStreamStatisticsMetricProperty -> Value Text
namespace :: MetricStreamStatisticsMetricProperty -> Value Text
haddock_workaround_ :: ()
metricName :: Value Text
namespace :: Value Text
..}
    = ResourceProperties
        {awsType :: Text
awsType = Text
"AWS::CloudWatch::MetricStream.MetricStreamStatisticsMetric",
         supportsTags :: Bool
supportsTags = Bool
Prelude.False,
         properties :: Object
properties = [Key
"MetricName" 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
metricName,
                       Key
"Namespace" 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
namespace]}
instance JSON.ToJSON MetricStreamStatisticsMetricProperty where
  toJSON :: MetricStreamStatisticsMetricProperty -> Value
toJSON MetricStreamStatisticsMetricProperty {()
Value Text
haddock_workaround_ :: MetricStreamStatisticsMetricProperty -> ()
metricName :: MetricStreamStatisticsMetricProperty -> Value Text
namespace :: MetricStreamStatisticsMetricProperty -> Value Text
haddock_workaround_ :: ()
metricName :: Value Text
namespace :: Value Text
..}
    = [(Key, Value)] -> Value
JSON.object
        [Key
"MetricName" 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
metricName, Key
"Namespace" 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
namespace]
instance Property "MetricName" MetricStreamStatisticsMetricProperty where
  type PropertyType "MetricName" MetricStreamStatisticsMetricProperty = Value Prelude.Text
  set :: PropertyType "MetricName" MetricStreamStatisticsMetricProperty
-> MetricStreamStatisticsMetricProperty
-> MetricStreamStatisticsMetricProperty
set PropertyType "MetricName" MetricStreamStatisticsMetricProperty
newValue MetricStreamStatisticsMetricProperty {()
Value Text
haddock_workaround_ :: MetricStreamStatisticsMetricProperty -> ()
metricName :: MetricStreamStatisticsMetricProperty -> Value Text
namespace :: MetricStreamStatisticsMetricProperty -> Value Text
haddock_workaround_ :: ()
metricName :: Value Text
namespace :: Value Text
..}
    = MetricStreamStatisticsMetricProperty {metricName :: Value Text
metricName = PropertyType "MetricName" MetricStreamStatisticsMetricProperty
Value Text
newValue, ()
Value Text
haddock_workaround_ :: ()
namespace :: Value Text
haddock_workaround_ :: ()
namespace :: Value Text
..}
instance Property "Namespace" MetricStreamStatisticsMetricProperty where
  type PropertyType "Namespace" MetricStreamStatisticsMetricProperty = Value Prelude.Text
  set :: PropertyType "Namespace" MetricStreamStatisticsMetricProperty
-> MetricStreamStatisticsMetricProperty
-> MetricStreamStatisticsMetricProperty
set PropertyType "Namespace" MetricStreamStatisticsMetricProperty
newValue MetricStreamStatisticsMetricProperty {()
Value Text
haddock_workaround_ :: MetricStreamStatisticsMetricProperty -> ()
metricName :: MetricStreamStatisticsMetricProperty -> Value Text
namespace :: MetricStreamStatisticsMetricProperty -> Value Text
haddock_workaround_ :: ()
metricName :: Value Text
namespace :: Value Text
..}
    = MetricStreamStatisticsMetricProperty {namespace :: Value Text
namespace = PropertyType "Namespace" MetricStreamStatisticsMetricProperty
Value Text
newValue, ()
Value Text
haddock_workaround_ :: ()
metricName :: Value Text
haddock_workaround_ :: ()
metricName :: Value Text
..}