{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DuplicateRecordFields #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE StrictData #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# OPTIONS_GHC -fno-warn-unused-imports #-}
{-# OPTIONS_GHC -fno-warn-unused-matches #-}

-- Derived from AWS service descriptions, licensed under Apache 2.0.

-- |
-- Module      : Amazonka.Rum.Types.MetricDefinitionRequest
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
module Amazonka.Rum.Types.MetricDefinitionRequest where

import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import qualified Amazonka.Prelude as Prelude

-- | Use this structure to define one extended metric that RUM will send to
-- CloudWatch or CloudWatch Evidently. For more information, see
-- <https://docs.aws.amazon.com/AmazonCloudWatch/latest/monitoring/CloudWatch-RUM-vended-metrics.html Additional metrics that you can send to CloudWatch and CloudWatch Evidently>.
--
-- Only certain combinations of values for @Name@, @ValueKey@, and
-- @EventPattern@ are valid. In addition to what is displayed in the list
-- below, the @EventPattern@ can also include information used by the
-- @DimensionKeys@ field.
--
-- -   If @Name@ is @PerformanceNavigationDuration@, then @ValueKey@must be
--     @event_details.duration@ and the @EventPattern@ must include
--     @{\"event_type\":[\"com.amazon.rum.performance_navigation_event\"]}@
--
-- -   If @Name@ is @PerformanceResourceDuration@, then @ValueKey@must be
--     @event_details.duration@ and the @EventPattern@ must include
--     @{\"event_type\":[\"com.amazon.rum.performance_resource_event\"]}@
--
-- -   If @Name@ is @NavigationSatisfiedTransaction@, then @ValueKey@must
--     be null and the @EventPattern@ must include
--     @{ \"event_type\": [\"com.amazon.rum.performance_navigation_event\"], \"event_details\": { \"duration\": [{ \"numeric\": [\">\",2000] }] } }@
--
-- -   If @Name@ is @NavigationToleratedTransaction@, then @ValueKey@must
--     be null and the @EventPattern@ must include
--     @{ \"event_type\": [\"com.amazon.rum.performance_navigation_event\"], \"event_details\": { \"duration\": [{ \"numeric\": [\">=\",2000,\"\<\"8000] }] } }@
--
-- -   If @Name@ is @NavigationFrustratedTransaction@, then @ValueKey@must
--     be null and the @EventPattern@ must include
--     @{ \"event_type\": [\"com.amazon.rum.performance_navigation_event\"], \"event_details\": { \"duration\": [{ \"numeric\": [\">=\",8000] }] } }@
--
-- -   If @Name@ is @WebVitalsCumulativeLayoutShift@, then @ValueKey@must
--     be @event_details.value@ and the @EventPattern@ must include
--     @{\"event_type\":[\"com.amazon.rum.cumulative_layout_shift_event\"]}@
--
-- -   If @Name@ is @WebVitalsFirstInputDelay@, then @ValueKey@must be
--     @event_details.value@ and the @EventPattern@ must include
--     @{\"event_type\":[\"com.amazon.rum.first_input_delay_event\"]}@
--
-- -   If @Name@ is @WebVitalsLargestContentfulPaint@, then @ValueKey@must
--     be @event_details.value@ and the @EventPattern@ must include
--     @{\"event_type\":[\"com.amazon.rum.largest_contentful_paint_event\"]}@
--
-- -   If @Name@ is @JsErrorCount@, then @ValueKey@must be null and the
--     @EventPattern@ must include
--     @{\"event_type\":[\"com.amazon.rum.js_error_event\"]}@
--
-- -   If @Name@ is @HttpErrorCount@, then @ValueKey@must be null and the
--     @EventPattern@ must include
--     @{\"event_type\":[\"com.amazon.rum.http_event\"]}@
--
-- -   If @Name@ is @SessionCount@, then @ValueKey@must be null and the
--     @EventPattern@ must include
--     @{\"event_type\":[\"com.amazon.rum.session_start_event\"]}@
--
-- /See:/ 'newMetricDefinitionRequest' smart constructor.
data MetricDefinitionRequest = MetricDefinitionRequest'
  { -- | Use this field only if you are sending the metric to CloudWatch.
    --
    -- This field is a map of field paths to dimension names. It defines the
    -- dimensions to associate with this metric in CloudWatch. Valid values for
    -- the entries in this field are the following:
    --
    -- -   @\"metadata.pageId\": \"PageId\"@
    --
    -- -   @\"metadata.browserName\": \"BrowserName\"@
    --
    -- -   @\"metadata.deviceType\": \"DeviceType\"@
    --
    -- -   @\"metadata.osName\": \"OSName\"@
    --
    -- -   @\"metadata.countryCode\": \"CountryCode\"@
    --
    -- -   @\"event_details.fileType\": \"FileType\"@
    --
    -- All dimensions listed in this field must also be included in
    -- @EventPattern@.
    MetricDefinitionRequest -> Maybe (HashMap Text Text)
dimensionKeys :: Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text),
    -- | The pattern that defines the metric, specified as a JSON object. RUM
    -- checks events that happen in a user\'s session against the pattern, and
    -- events that match the pattern are sent to the metric destination.
    --
    -- When you define extended metrics, the metric definition is not valid if
    -- @EventPattern@ is omitted.
    --
    -- Example event patterns:
    --
    -- -   @\'{ \"event_type\": [\"com.amazon.rum.js_error_event\"], \"metadata\": { \"browserName\": [ \"Chrome\", \"Safari\" ], } }\'@
    --
    -- -   @\'{ \"event_type\": [\"com.amazon.rum.performance_navigation_event\"], \"metadata\": { \"browserName\": [ \"Chrome\", \"Firefox\" ] }, \"event_details\": { \"duration\": [{ \"numeric\": [ \"\<\", 2000 ] }] } }\'@
    --
    -- -   @\'{ \"event_type\": [\"com.amazon.rum.performance_navigation_event\"], \"metadata\": { \"browserName\": [ \"Chrome\", \"Safari\" ], \"countryCode\": [ \"US\" ] }, \"event_details\": { \"duration\": [{ \"numeric\": [ \">=\", 2000, \"\<\", 8000 ] }] } }\'@
    --
    -- If the metrics destination\' is @CloudWatch@ and the event also matches
    -- a value in @DimensionKeys@, then the metric is published with the
    -- specified dimensions.
    MetricDefinitionRequest -> Maybe Text
eventPattern :: Prelude.Maybe Prelude.Text,
    -- | The CloudWatch metric unit to use for this metric. If you omit this
    -- field, the metric is recorded with no unit.
    MetricDefinitionRequest -> Maybe Text
unitLabel :: Prelude.Maybe Prelude.Text,
    -- | The field within the event object that the metric value is sourced from.
    --
    -- If you omit this field, a hardcoded value of 1 is pushed as the metric
    -- value. This is useful if you just want to count the number of events
    -- that the filter catches.
    --
    -- If this metric is sent to CloudWatch Evidently, this field will be
    -- passed to Evidently raw and Evidently will handle data extraction from
    -- the event.
    MetricDefinitionRequest -> Maybe Text
valueKey :: Prelude.Maybe Prelude.Text,
    -- | The name for the metric that is defined in this structure. Valid values
    -- are the following:
    --
    -- -   @PerformanceNavigationDuration@
    --
    -- -   @PerformanceResourceDuration @
    --
    -- -   @NavigationSatisfiedTransaction@
    --
    -- -   @NavigationToleratedTransaction@
    --
    -- -   @NavigationFrustratedTransaction@
    --
    -- -   @WebVitalsCumulativeLayoutShift@
    --
    -- -   @WebVitalsFirstInputDelay@
    --
    -- -   @WebVitalsLargestContentfulPaint@
    --
    -- -   @JsErrorCount@
    --
    -- -   @HttpErrorCount@
    --
    -- -   @SessionCount@
    MetricDefinitionRequest -> Text
name :: Prelude.Text
  }
  deriving (MetricDefinitionRequest -> MetricDefinitionRequest -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: MetricDefinitionRequest -> MetricDefinitionRequest -> Bool
$c/= :: MetricDefinitionRequest -> MetricDefinitionRequest -> Bool
== :: MetricDefinitionRequest -> MetricDefinitionRequest -> Bool
$c== :: MetricDefinitionRequest -> MetricDefinitionRequest -> Bool
Prelude.Eq, ReadPrec [MetricDefinitionRequest]
ReadPrec MetricDefinitionRequest
Int -> ReadS MetricDefinitionRequest
ReadS [MetricDefinitionRequest]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [MetricDefinitionRequest]
$creadListPrec :: ReadPrec [MetricDefinitionRequest]
readPrec :: ReadPrec MetricDefinitionRequest
$creadPrec :: ReadPrec MetricDefinitionRequest
readList :: ReadS [MetricDefinitionRequest]
$creadList :: ReadS [MetricDefinitionRequest]
readsPrec :: Int -> ReadS MetricDefinitionRequest
$creadsPrec :: Int -> ReadS MetricDefinitionRequest
Prelude.Read, Int -> MetricDefinitionRequest -> ShowS
[MetricDefinitionRequest] -> ShowS
MetricDefinitionRequest -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [MetricDefinitionRequest] -> ShowS
$cshowList :: [MetricDefinitionRequest] -> ShowS
show :: MetricDefinitionRequest -> String
$cshow :: MetricDefinitionRequest -> String
showsPrec :: Int -> MetricDefinitionRequest -> ShowS
$cshowsPrec :: Int -> MetricDefinitionRequest -> ShowS
Prelude.Show, forall x. Rep MetricDefinitionRequest x -> MetricDefinitionRequest
forall x. MetricDefinitionRequest -> Rep MetricDefinitionRequest x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep MetricDefinitionRequest x -> MetricDefinitionRequest
$cfrom :: forall x. MetricDefinitionRequest -> Rep MetricDefinitionRequest x
Prelude.Generic)

-- |
-- Create a value of 'MetricDefinitionRequest' with all optional fields omitted.
--
-- Use <https://hackage.haskell.org/package/generic-lens generic-lens> or <https://hackage.haskell.org/package/optics optics> to modify other optional fields.
--
-- The following record fields are available, with the corresponding lenses provided
-- for backwards compatibility:
--
-- 'dimensionKeys', 'metricDefinitionRequest_dimensionKeys' - Use this field only if you are sending the metric to CloudWatch.
--
-- This field is a map of field paths to dimension names. It defines the
-- dimensions to associate with this metric in CloudWatch. Valid values for
-- the entries in this field are the following:
--
-- -   @\"metadata.pageId\": \"PageId\"@
--
-- -   @\"metadata.browserName\": \"BrowserName\"@
--
-- -   @\"metadata.deviceType\": \"DeviceType\"@
--
-- -   @\"metadata.osName\": \"OSName\"@
--
-- -   @\"metadata.countryCode\": \"CountryCode\"@
--
-- -   @\"event_details.fileType\": \"FileType\"@
--
-- All dimensions listed in this field must also be included in
-- @EventPattern@.
--
-- 'eventPattern', 'metricDefinitionRequest_eventPattern' - The pattern that defines the metric, specified as a JSON object. RUM
-- checks events that happen in a user\'s session against the pattern, and
-- events that match the pattern are sent to the metric destination.
--
-- When you define extended metrics, the metric definition is not valid if
-- @EventPattern@ is omitted.
--
-- Example event patterns:
--
-- -   @\'{ \"event_type\": [\"com.amazon.rum.js_error_event\"], \"metadata\": { \"browserName\": [ \"Chrome\", \"Safari\" ], } }\'@
--
-- -   @\'{ \"event_type\": [\"com.amazon.rum.performance_navigation_event\"], \"metadata\": { \"browserName\": [ \"Chrome\", \"Firefox\" ] }, \"event_details\": { \"duration\": [{ \"numeric\": [ \"\<\", 2000 ] }] } }\'@
--
-- -   @\'{ \"event_type\": [\"com.amazon.rum.performance_navigation_event\"], \"metadata\": { \"browserName\": [ \"Chrome\", \"Safari\" ], \"countryCode\": [ \"US\" ] }, \"event_details\": { \"duration\": [{ \"numeric\": [ \">=\", 2000, \"\<\", 8000 ] }] } }\'@
--
-- If the metrics destination\' is @CloudWatch@ and the event also matches
-- a value in @DimensionKeys@, then the metric is published with the
-- specified dimensions.
--
-- 'unitLabel', 'metricDefinitionRequest_unitLabel' - The CloudWatch metric unit to use for this metric. If you omit this
-- field, the metric is recorded with no unit.
--
-- 'valueKey', 'metricDefinitionRequest_valueKey' - The field within the event object that the metric value is sourced from.
--
-- If you omit this field, a hardcoded value of 1 is pushed as the metric
-- value. This is useful if you just want to count the number of events
-- that the filter catches.
--
-- If this metric is sent to CloudWatch Evidently, this field will be
-- passed to Evidently raw and Evidently will handle data extraction from
-- the event.
--
-- 'name', 'metricDefinitionRequest_name' - The name for the metric that is defined in this structure. Valid values
-- are the following:
--
-- -   @PerformanceNavigationDuration@
--
-- -   @PerformanceResourceDuration @
--
-- -   @NavigationSatisfiedTransaction@
--
-- -   @NavigationToleratedTransaction@
--
-- -   @NavigationFrustratedTransaction@
--
-- -   @WebVitalsCumulativeLayoutShift@
--
-- -   @WebVitalsFirstInputDelay@
--
-- -   @WebVitalsLargestContentfulPaint@
--
-- -   @JsErrorCount@
--
-- -   @HttpErrorCount@
--
-- -   @SessionCount@
newMetricDefinitionRequest ::
  -- | 'name'
  Prelude.Text ->
  MetricDefinitionRequest
newMetricDefinitionRequest :: Text -> MetricDefinitionRequest
newMetricDefinitionRequest Text
pName_ =
  MetricDefinitionRequest'
    { $sel:dimensionKeys:MetricDefinitionRequest' :: Maybe (HashMap Text Text)
dimensionKeys =
        forall a. Maybe a
Prelude.Nothing,
      $sel:eventPattern:MetricDefinitionRequest' :: Maybe Text
eventPattern = forall a. Maybe a
Prelude.Nothing,
      $sel:unitLabel:MetricDefinitionRequest' :: Maybe Text
unitLabel = forall a. Maybe a
Prelude.Nothing,
      $sel:valueKey:MetricDefinitionRequest' :: Maybe Text
valueKey = forall a. Maybe a
Prelude.Nothing,
      $sel:name:MetricDefinitionRequest' :: Text
name = Text
pName_
    }

-- | Use this field only if you are sending the metric to CloudWatch.
--
-- This field is a map of field paths to dimension names. It defines the
-- dimensions to associate with this metric in CloudWatch. Valid values for
-- the entries in this field are the following:
--
-- -   @\"metadata.pageId\": \"PageId\"@
--
-- -   @\"metadata.browserName\": \"BrowserName\"@
--
-- -   @\"metadata.deviceType\": \"DeviceType\"@
--
-- -   @\"metadata.osName\": \"OSName\"@
--
-- -   @\"metadata.countryCode\": \"CountryCode\"@
--
-- -   @\"event_details.fileType\": \"FileType\"@
--
-- All dimensions listed in this field must also be included in
-- @EventPattern@.
metricDefinitionRequest_dimensionKeys :: Lens.Lens' MetricDefinitionRequest (Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text))
metricDefinitionRequest_dimensionKeys :: Lens' MetricDefinitionRequest (Maybe (HashMap Text Text))
metricDefinitionRequest_dimensionKeys = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\MetricDefinitionRequest' {Maybe (HashMap Text Text)
dimensionKeys :: Maybe (HashMap Text Text)
$sel:dimensionKeys:MetricDefinitionRequest' :: MetricDefinitionRequest -> Maybe (HashMap Text Text)
dimensionKeys} -> Maybe (HashMap Text Text)
dimensionKeys) (\s :: MetricDefinitionRequest
s@MetricDefinitionRequest' {} Maybe (HashMap Text Text)
a -> MetricDefinitionRequest
s {$sel:dimensionKeys:MetricDefinitionRequest' :: Maybe (HashMap Text Text)
dimensionKeys = Maybe (HashMap Text Text)
a} :: MetricDefinitionRequest) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
Lens.mapping forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

-- | The pattern that defines the metric, specified as a JSON object. RUM
-- checks events that happen in a user\'s session against the pattern, and
-- events that match the pattern are sent to the metric destination.
--
-- When you define extended metrics, the metric definition is not valid if
-- @EventPattern@ is omitted.
--
-- Example event patterns:
--
-- -   @\'{ \"event_type\": [\"com.amazon.rum.js_error_event\"], \"metadata\": { \"browserName\": [ \"Chrome\", \"Safari\" ], } }\'@
--
-- -   @\'{ \"event_type\": [\"com.amazon.rum.performance_navigation_event\"], \"metadata\": { \"browserName\": [ \"Chrome\", \"Firefox\" ] }, \"event_details\": { \"duration\": [{ \"numeric\": [ \"\<\", 2000 ] }] } }\'@
--
-- -   @\'{ \"event_type\": [\"com.amazon.rum.performance_navigation_event\"], \"metadata\": { \"browserName\": [ \"Chrome\", \"Safari\" ], \"countryCode\": [ \"US\" ] }, \"event_details\": { \"duration\": [{ \"numeric\": [ \">=\", 2000, \"\<\", 8000 ] }] } }\'@
--
-- If the metrics destination\' is @CloudWatch@ and the event also matches
-- a value in @DimensionKeys@, then the metric is published with the
-- specified dimensions.
metricDefinitionRequest_eventPattern :: Lens.Lens' MetricDefinitionRequest (Prelude.Maybe Prelude.Text)
metricDefinitionRequest_eventPattern :: Lens' MetricDefinitionRequest (Maybe Text)
metricDefinitionRequest_eventPattern = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\MetricDefinitionRequest' {Maybe Text
eventPattern :: Maybe Text
$sel:eventPattern:MetricDefinitionRequest' :: MetricDefinitionRequest -> Maybe Text
eventPattern} -> Maybe Text
eventPattern) (\s :: MetricDefinitionRequest
s@MetricDefinitionRequest' {} Maybe Text
a -> MetricDefinitionRequest
s {$sel:eventPattern:MetricDefinitionRequest' :: Maybe Text
eventPattern = Maybe Text
a} :: MetricDefinitionRequest)

-- | The CloudWatch metric unit to use for this metric. If you omit this
-- field, the metric is recorded with no unit.
metricDefinitionRequest_unitLabel :: Lens.Lens' MetricDefinitionRequest (Prelude.Maybe Prelude.Text)
metricDefinitionRequest_unitLabel :: Lens' MetricDefinitionRequest (Maybe Text)
metricDefinitionRequest_unitLabel = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\MetricDefinitionRequest' {Maybe Text
unitLabel :: Maybe Text
$sel:unitLabel:MetricDefinitionRequest' :: MetricDefinitionRequest -> Maybe Text
unitLabel} -> Maybe Text
unitLabel) (\s :: MetricDefinitionRequest
s@MetricDefinitionRequest' {} Maybe Text
a -> MetricDefinitionRequest
s {$sel:unitLabel:MetricDefinitionRequest' :: Maybe Text
unitLabel = Maybe Text
a} :: MetricDefinitionRequest)

-- | The field within the event object that the metric value is sourced from.
--
-- If you omit this field, a hardcoded value of 1 is pushed as the metric
-- value. This is useful if you just want to count the number of events
-- that the filter catches.
--
-- If this metric is sent to CloudWatch Evidently, this field will be
-- passed to Evidently raw and Evidently will handle data extraction from
-- the event.
metricDefinitionRequest_valueKey :: Lens.Lens' MetricDefinitionRequest (Prelude.Maybe Prelude.Text)
metricDefinitionRequest_valueKey :: Lens' MetricDefinitionRequest (Maybe Text)
metricDefinitionRequest_valueKey = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\MetricDefinitionRequest' {Maybe Text
valueKey :: Maybe Text
$sel:valueKey:MetricDefinitionRequest' :: MetricDefinitionRequest -> Maybe Text
valueKey} -> Maybe Text
valueKey) (\s :: MetricDefinitionRequest
s@MetricDefinitionRequest' {} Maybe Text
a -> MetricDefinitionRequest
s {$sel:valueKey:MetricDefinitionRequest' :: Maybe Text
valueKey = Maybe Text
a} :: MetricDefinitionRequest)

-- | The name for the metric that is defined in this structure. Valid values
-- are the following:
--
-- -   @PerformanceNavigationDuration@
--
-- -   @PerformanceResourceDuration @
--
-- -   @NavigationSatisfiedTransaction@
--
-- -   @NavigationToleratedTransaction@
--
-- -   @NavigationFrustratedTransaction@
--
-- -   @WebVitalsCumulativeLayoutShift@
--
-- -   @WebVitalsFirstInputDelay@
--
-- -   @WebVitalsLargestContentfulPaint@
--
-- -   @JsErrorCount@
--
-- -   @HttpErrorCount@
--
-- -   @SessionCount@
metricDefinitionRequest_name :: Lens.Lens' MetricDefinitionRequest Prelude.Text
metricDefinitionRequest_name :: Lens' MetricDefinitionRequest Text
metricDefinitionRequest_name = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\MetricDefinitionRequest' {Text
name :: Text
$sel:name:MetricDefinitionRequest' :: MetricDefinitionRequest -> Text
name} -> Text
name) (\s :: MetricDefinitionRequest
s@MetricDefinitionRequest' {} Text
a -> MetricDefinitionRequest
s {$sel:name:MetricDefinitionRequest' :: Text
name = Text
a} :: MetricDefinitionRequest)

instance Data.FromJSON MetricDefinitionRequest where
  parseJSON :: Value -> Parser MetricDefinitionRequest
parseJSON =
    forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.withObject
      String
"MetricDefinitionRequest"
      ( \Object
x ->
          Maybe (HashMap Text Text)
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Text
-> MetricDefinitionRequest
MetricDefinitionRequest'
            forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"DimensionKeys" forall a. Parser (Maybe a) -> a -> Parser a
Data..!= forall a. Monoid a => a
Prelude.mempty)
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"EventPattern")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"UnitLabel")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"ValueKey")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser a
Data..: Key
"Name")
      )

instance Prelude.Hashable MetricDefinitionRequest where
  hashWithSalt :: Int -> MetricDefinitionRequest -> Int
hashWithSalt Int
_salt MetricDefinitionRequest' {Maybe Text
Maybe (HashMap Text Text)
Text
name :: Text
valueKey :: Maybe Text
unitLabel :: Maybe Text
eventPattern :: Maybe Text
dimensionKeys :: Maybe (HashMap Text Text)
$sel:name:MetricDefinitionRequest' :: MetricDefinitionRequest -> Text
$sel:valueKey:MetricDefinitionRequest' :: MetricDefinitionRequest -> Maybe Text
$sel:unitLabel:MetricDefinitionRequest' :: MetricDefinitionRequest -> Maybe Text
$sel:eventPattern:MetricDefinitionRequest' :: MetricDefinitionRequest -> Maybe Text
$sel:dimensionKeys:MetricDefinitionRequest' :: MetricDefinitionRequest -> Maybe (HashMap Text Text)
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe (HashMap Text Text)
dimensionKeys
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
eventPattern
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
unitLabel
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
valueKey
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
name

instance Prelude.NFData MetricDefinitionRequest where
  rnf :: MetricDefinitionRequest -> ()
rnf MetricDefinitionRequest' {Maybe Text
Maybe (HashMap Text Text)
Text
name :: Text
valueKey :: Maybe Text
unitLabel :: Maybe Text
eventPattern :: Maybe Text
dimensionKeys :: Maybe (HashMap Text Text)
$sel:name:MetricDefinitionRequest' :: MetricDefinitionRequest -> Text
$sel:valueKey:MetricDefinitionRequest' :: MetricDefinitionRequest -> Maybe Text
$sel:unitLabel:MetricDefinitionRequest' :: MetricDefinitionRequest -> Maybe Text
$sel:eventPattern:MetricDefinitionRequest' :: MetricDefinitionRequest -> Maybe Text
$sel:dimensionKeys:MetricDefinitionRequest' :: MetricDefinitionRequest -> Maybe (HashMap Text Text)
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe (HashMap Text Text)
dimensionKeys
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
eventPattern
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
unitLabel
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
valueKey
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
name

instance Data.ToJSON MetricDefinitionRequest where
  toJSON :: MetricDefinitionRequest -> Value
toJSON MetricDefinitionRequest' {Maybe Text
Maybe (HashMap Text Text)
Text
name :: Text
valueKey :: Maybe Text
unitLabel :: Maybe Text
eventPattern :: Maybe Text
dimensionKeys :: Maybe (HashMap Text Text)
$sel:name:MetricDefinitionRequest' :: MetricDefinitionRequest -> Text
$sel:valueKey:MetricDefinitionRequest' :: MetricDefinitionRequest -> Maybe Text
$sel:unitLabel:MetricDefinitionRequest' :: MetricDefinitionRequest -> Maybe Text
$sel:eventPattern:MetricDefinitionRequest' :: MetricDefinitionRequest -> Maybe Text
$sel:dimensionKeys:MetricDefinitionRequest' :: MetricDefinitionRequest -> Maybe (HashMap Text Text)
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"DimensionKeys" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (HashMap Text Text)
dimensionKeys,
            (Key
"EventPattern" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Text
eventPattern,
            (Key
"UnitLabel" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Text
unitLabel,
            (Key
"ValueKey" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Text
valueKey,
            forall a. a -> Maybe a
Prelude.Just (Key
"Name" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
name)
          ]
      )