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

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

-- |
-- Module      : Amazonka.LookoutMetrics.ListAnomalyGroupRelatedMetrics
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Returns a list of measures that are potential causes or effects of an
-- anomaly group.
module Amazonka.LookoutMetrics.ListAnomalyGroupRelatedMetrics
  ( -- * Creating a Request
    ListAnomalyGroupRelatedMetrics (..),
    newListAnomalyGroupRelatedMetrics,

    -- * Request Lenses
    listAnomalyGroupRelatedMetrics_maxResults,
    listAnomalyGroupRelatedMetrics_nextToken,
    listAnomalyGroupRelatedMetrics_relationshipTypeFilter,
    listAnomalyGroupRelatedMetrics_anomalyDetectorArn,
    listAnomalyGroupRelatedMetrics_anomalyGroupId,

    -- * Destructuring the Response
    ListAnomalyGroupRelatedMetricsResponse (..),
    newListAnomalyGroupRelatedMetricsResponse,

    -- * Response Lenses
    listAnomalyGroupRelatedMetricsResponse_interMetricImpactList,
    listAnomalyGroupRelatedMetricsResponse_nextToken,
    listAnomalyGroupRelatedMetricsResponse_httpStatus,
  )
where

import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import Amazonka.LookoutMetrics.Types
import qualified Amazonka.Prelude as Prelude
import qualified Amazonka.Request as Request
import qualified Amazonka.Response as Response

-- | /See:/ 'newListAnomalyGroupRelatedMetrics' smart constructor.
data ListAnomalyGroupRelatedMetrics = ListAnomalyGroupRelatedMetrics'
  { -- | The maximum number of results to return.
    ListAnomalyGroupRelatedMetrics -> Maybe Natural
maxResults :: Prelude.Maybe Prelude.Natural,
    -- | Specify the pagination token that\'s returned by a previous request to
    -- retrieve the next page of results.
    ListAnomalyGroupRelatedMetrics -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | Filter for potential causes (@CAUSE_OF_INPUT_ANOMALY_GROUP@) or
    -- downstream effects (@EFFECT_OF_INPUT_ANOMALY_GROUP@) of the anomaly
    -- group.
    ListAnomalyGroupRelatedMetrics -> Maybe RelationshipType
relationshipTypeFilter :: Prelude.Maybe RelationshipType,
    -- | The Amazon Resource Name (ARN) of the anomaly detector.
    ListAnomalyGroupRelatedMetrics -> Text
anomalyDetectorArn :: Prelude.Text,
    -- | The ID of the anomaly group.
    ListAnomalyGroupRelatedMetrics -> Text
anomalyGroupId :: Prelude.Text
  }
  deriving (ListAnomalyGroupRelatedMetrics
-> ListAnomalyGroupRelatedMetrics -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListAnomalyGroupRelatedMetrics
-> ListAnomalyGroupRelatedMetrics -> Bool
$c/= :: ListAnomalyGroupRelatedMetrics
-> ListAnomalyGroupRelatedMetrics -> Bool
== :: ListAnomalyGroupRelatedMetrics
-> ListAnomalyGroupRelatedMetrics -> Bool
$c== :: ListAnomalyGroupRelatedMetrics
-> ListAnomalyGroupRelatedMetrics -> Bool
Prelude.Eq, ReadPrec [ListAnomalyGroupRelatedMetrics]
ReadPrec ListAnomalyGroupRelatedMetrics
Int -> ReadS ListAnomalyGroupRelatedMetrics
ReadS [ListAnomalyGroupRelatedMetrics]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListAnomalyGroupRelatedMetrics]
$creadListPrec :: ReadPrec [ListAnomalyGroupRelatedMetrics]
readPrec :: ReadPrec ListAnomalyGroupRelatedMetrics
$creadPrec :: ReadPrec ListAnomalyGroupRelatedMetrics
readList :: ReadS [ListAnomalyGroupRelatedMetrics]
$creadList :: ReadS [ListAnomalyGroupRelatedMetrics]
readsPrec :: Int -> ReadS ListAnomalyGroupRelatedMetrics
$creadsPrec :: Int -> ReadS ListAnomalyGroupRelatedMetrics
Prelude.Read, Int -> ListAnomalyGroupRelatedMetrics -> ShowS
[ListAnomalyGroupRelatedMetrics] -> ShowS
ListAnomalyGroupRelatedMetrics -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListAnomalyGroupRelatedMetrics] -> ShowS
$cshowList :: [ListAnomalyGroupRelatedMetrics] -> ShowS
show :: ListAnomalyGroupRelatedMetrics -> String
$cshow :: ListAnomalyGroupRelatedMetrics -> String
showsPrec :: Int -> ListAnomalyGroupRelatedMetrics -> ShowS
$cshowsPrec :: Int -> ListAnomalyGroupRelatedMetrics -> ShowS
Prelude.Show, forall x.
Rep ListAnomalyGroupRelatedMetrics x
-> ListAnomalyGroupRelatedMetrics
forall x.
ListAnomalyGroupRelatedMetrics
-> Rep ListAnomalyGroupRelatedMetrics x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep ListAnomalyGroupRelatedMetrics x
-> ListAnomalyGroupRelatedMetrics
$cfrom :: forall x.
ListAnomalyGroupRelatedMetrics
-> Rep ListAnomalyGroupRelatedMetrics x
Prelude.Generic)

-- |
-- Create a value of 'ListAnomalyGroupRelatedMetrics' 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:
--
-- 'maxResults', 'listAnomalyGroupRelatedMetrics_maxResults' - The maximum number of results to return.
--
-- 'nextToken', 'listAnomalyGroupRelatedMetrics_nextToken' - Specify the pagination token that\'s returned by a previous request to
-- retrieve the next page of results.
--
-- 'relationshipTypeFilter', 'listAnomalyGroupRelatedMetrics_relationshipTypeFilter' - Filter for potential causes (@CAUSE_OF_INPUT_ANOMALY_GROUP@) or
-- downstream effects (@EFFECT_OF_INPUT_ANOMALY_GROUP@) of the anomaly
-- group.
--
-- 'anomalyDetectorArn', 'listAnomalyGroupRelatedMetrics_anomalyDetectorArn' - The Amazon Resource Name (ARN) of the anomaly detector.
--
-- 'anomalyGroupId', 'listAnomalyGroupRelatedMetrics_anomalyGroupId' - The ID of the anomaly group.
newListAnomalyGroupRelatedMetrics ::
  -- | 'anomalyDetectorArn'
  Prelude.Text ->
  -- | 'anomalyGroupId'
  Prelude.Text ->
  ListAnomalyGroupRelatedMetrics
newListAnomalyGroupRelatedMetrics :: Text -> Text -> ListAnomalyGroupRelatedMetrics
newListAnomalyGroupRelatedMetrics
  Text
pAnomalyDetectorArn_
  Text
pAnomalyGroupId_ =
    ListAnomalyGroupRelatedMetrics'
      { $sel:maxResults:ListAnomalyGroupRelatedMetrics' :: Maybe Natural
maxResults =
          forall a. Maybe a
Prelude.Nothing,
        $sel:nextToken:ListAnomalyGroupRelatedMetrics' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
        $sel:relationshipTypeFilter:ListAnomalyGroupRelatedMetrics' :: Maybe RelationshipType
relationshipTypeFilter = forall a. Maybe a
Prelude.Nothing,
        $sel:anomalyDetectorArn:ListAnomalyGroupRelatedMetrics' :: Text
anomalyDetectorArn = Text
pAnomalyDetectorArn_,
        $sel:anomalyGroupId:ListAnomalyGroupRelatedMetrics' :: Text
anomalyGroupId = Text
pAnomalyGroupId_
      }

-- | The maximum number of results to return.
listAnomalyGroupRelatedMetrics_maxResults :: Lens.Lens' ListAnomalyGroupRelatedMetrics (Prelude.Maybe Prelude.Natural)
listAnomalyGroupRelatedMetrics_maxResults :: Lens' ListAnomalyGroupRelatedMetrics (Maybe Natural)
listAnomalyGroupRelatedMetrics_maxResults = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListAnomalyGroupRelatedMetrics' {Maybe Natural
maxResults :: Maybe Natural
$sel:maxResults:ListAnomalyGroupRelatedMetrics' :: ListAnomalyGroupRelatedMetrics -> Maybe Natural
maxResults} -> Maybe Natural
maxResults) (\s :: ListAnomalyGroupRelatedMetrics
s@ListAnomalyGroupRelatedMetrics' {} Maybe Natural
a -> ListAnomalyGroupRelatedMetrics
s {$sel:maxResults:ListAnomalyGroupRelatedMetrics' :: Maybe Natural
maxResults = Maybe Natural
a} :: ListAnomalyGroupRelatedMetrics)

-- | Specify the pagination token that\'s returned by a previous request to
-- retrieve the next page of results.
listAnomalyGroupRelatedMetrics_nextToken :: Lens.Lens' ListAnomalyGroupRelatedMetrics (Prelude.Maybe Prelude.Text)
listAnomalyGroupRelatedMetrics_nextToken :: Lens' ListAnomalyGroupRelatedMetrics (Maybe Text)
listAnomalyGroupRelatedMetrics_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListAnomalyGroupRelatedMetrics' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:ListAnomalyGroupRelatedMetrics' :: ListAnomalyGroupRelatedMetrics -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: ListAnomalyGroupRelatedMetrics
s@ListAnomalyGroupRelatedMetrics' {} Maybe Text
a -> ListAnomalyGroupRelatedMetrics
s {$sel:nextToken:ListAnomalyGroupRelatedMetrics' :: Maybe Text
nextToken = Maybe Text
a} :: ListAnomalyGroupRelatedMetrics)

-- | Filter for potential causes (@CAUSE_OF_INPUT_ANOMALY_GROUP@) or
-- downstream effects (@EFFECT_OF_INPUT_ANOMALY_GROUP@) of the anomaly
-- group.
listAnomalyGroupRelatedMetrics_relationshipTypeFilter :: Lens.Lens' ListAnomalyGroupRelatedMetrics (Prelude.Maybe RelationshipType)
listAnomalyGroupRelatedMetrics_relationshipTypeFilter :: Lens' ListAnomalyGroupRelatedMetrics (Maybe RelationshipType)
listAnomalyGroupRelatedMetrics_relationshipTypeFilter = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListAnomalyGroupRelatedMetrics' {Maybe RelationshipType
relationshipTypeFilter :: Maybe RelationshipType
$sel:relationshipTypeFilter:ListAnomalyGroupRelatedMetrics' :: ListAnomalyGroupRelatedMetrics -> Maybe RelationshipType
relationshipTypeFilter} -> Maybe RelationshipType
relationshipTypeFilter) (\s :: ListAnomalyGroupRelatedMetrics
s@ListAnomalyGroupRelatedMetrics' {} Maybe RelationshipType
a -> ListAnomalyGroupRelatedMetrics
s {$sel:relationshipTypeFilter:ListAnomalyGroupRelatedMetrics' :: Maybe RelationshipType
relationshipTypeFilter = Maybe RelationshipType
a} :: ListAnomalyGroupRelatedMetrics)

-- | The Amazon Resource Name (ARN) of the anomaly detector.
listAnomalyGroupRelatedMetrics_anomalyDetectorArn :: Lens.Lens' ListAnomalyGroupRelatedMetrics Prelude.Text
listAnomalyGroupRelatedMetrics_anomalyDetectorArn :: Lens' ListAnomalyGroupRelatedMetrics Text
listAnomalyGroupRelatedMetrics_anomalyDetectorArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListAnomalyGroupRelatedMetrics' {Text
anomalyDetectorArn :: Text
$sel:anomalyDetectorArn:ListAnomalyGroupRelatedMetrics' :: ListAnomalyGroupRelatedMetrics -> Text
anomalyDetectorArn} -> Text
anomalyDetectorArn) (\s :: ListAnomalyGroupRelatedMetrics
s@ListAnomalyGroupRelatedMetrics' {} Text
a -> ListAnomalyGroupRelatedMetrics
s {$sel:anomalyDetectorArn:ListAnomalyGroupRelatedMetrics' :: Text
anomalyDetectorArn = Text
a} :: ListAnomalyGroupRelatedMetrics)

-- | The ID of the anomaly group.
listAnomalyGroupRelatedMetrics_anomalyGroupId :: Lens.Lens' ListAnomalyGroupRelatedMetrics Prelude.Text
listAnomalyGroupRelatedMetrics_anomalyGroupId :: Lens' ListAnomalyGroupRelatedMetrics Text
listAnomalyGroupRelatedMetrics_anomalyGroupId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListAnomalyGroupRelatedMetrics' {Text
anomalyGroupId :: Text
$sel:anomalyGroupId:ListAnomalyGroupRelatedMetrics' :: ListAnomalyGroupRelatedMetrics -> Text
anomalyGroupId} -> Text
anomalyGroupId) (\s :: ListAnomalyGroupRelatedMetrics
s@ListAnomalyGroupRelatedMetrics' {} Text
a -> ListAnomalyGroupRelatedMetrics
s {$sel:anomalyGroupId:ListAnomalyGroupRelatedMetrics' :: Text
anomalyGroupId = Text
a} :: ListAnomalyGroupRelatedMetrics)

instance
  Core.AWSRequest
    ListAnomalyGroupRelatedMetrics
  where
  type
    AWSResponse ListAnomalyGroupRelatedMetrics =
      ListAnomalyGroupRelatedMetricsResponse
  request :: (Service -> Service)
-> ListAnomalyGroupRelatedMetrics
-> Request ListAnomalyGroupRelatedMetrics
request Service -> Service
overrides =
    forall a. (ToRequest a, ToJSON a) => Service -> a -> Request a
Request.postJSON (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy ListAnomalyGroupRelatedMetrics
-> ClientResponse ClientBody
-> m (Either
        Error
        (ClientResponse (AWSResponse ListAnomalyGroupRelatedMetrics)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
(Int -> ResponseHeaders -> Object -> Either String (AWSResponse a))
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveJSON
      ( \Int
s ResponseHeaders
h Object
x ->
          Maybe [InterMetricImpactDetails]
-> Maybe Text -> Int -> ListAnomalyGroupRelatedMetricsResponse
ListAnomalyGroupRelatedMetricsResponse'
            forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> ( Object
x
                            forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"InterMetricImpactList"
                            forall (f :: * -> *) a. Functor f => f (Maybe a) -> a -> f a
Core..!@ 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 -> Either String (Maybe a)
Data..?> Key
"NextToken")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure (forall a. Enum a => a -> Int
Prelude.fromEnum Int
s))
      )

instance
  Prelude.Hashable
    ListAnomalyGroupRelatedMetrics
  where
  hashWithSalt :: Int -> ListAnomalyGroupRelatedMetrics -> Int
hashWithSalt
    Int
_salt
    ListAnomalyGroupRelatedMetrics' {Maybe Natural
Maybe Text
Maybe RelationshipType
Text
anomalyGroupId :: Text
anomalyDetectorArn :: Text
relationshipTypeFilter :: Maybe RelationshipType
nextToken :: Maybe Text
maxResults :: Maybe Natural
$sel:anomalyGroupId:ListAnomalyGroupRelatedMetrics' :: ListAnomalyGroupRelatedMetrics -> Text
$sel:anomalyDetectorArn:ListAnomalyGroupRelatedMetrics' :: ListAnomalyGroupRelatedMetrics -> Text
$sel:relationshipTypeFilter:ListAnomalyGroupRelatedMetrics' :: ListAnomalyGroupRelatedMetrics -> Maybe RelationshipType
$sel:nextToken:ListAnomalyGroupRelatedMetrics' :: ListAnomalyGroupRelatedMetrics -> Maybe Text
$sel:maxResults:ListAnomalyGroupRelatedMetrics' :: ListAnomalyGroupRelatedMetrics -> Maybe Natural
..} =
      Int
_salt
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Natural
maxResults
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
nextToken
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe RelationshipType
relationshipTypeFilter
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
anomalyDetectorArn
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
anomalyGroupId

instance
  Prelude.NFData
    ListAnomalyGroupRelatedMetrics
  where
  rnf :: ListAnomalyGroupRelatedMetrics -> ()
rnf ListAnomalyGroupRelatedMetrics' {Maybe Natural
Maybe Text
Maybe RelationshipType
Text
anomalyGroupId :: Text
anomalyDetectorArn :: Text
relationshipTypeFilter :: Maybe RelationshipType
nextToken :: Maybe Text
maxResults :: Maybe Natural
$sel:anomalyGroupId:ListAnomalyGroupRelatedMetrics' :: ListAnomalyGroupRelatedMetrics -> Text
$sel:anomalyDetectorArn:ListAnomalyGroupRelatedMetrics' :: ListAnomalyGroupRelatedMetrics -> Text
$sel:relationshipTypeFilter:ListAnomalyGroupRelatedMetrics' :: ListAnomalyGroupRelatedMetrics -> Maybe RelationshipType
$sel:nextToken:ListAnomalyGroupRelatedMetrics' :: ListAnomalyGroupRelatedMetrics -> Maybe Text
$sel:maxResults:ListAnomalyGroupRelatedMetrics' :: ListAnomalyGroupRelatedMetrics -> Maybe Natural
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Natural
maxResults
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
nextToken
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe RelationshipType
relationshipTypeFilter
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
anomalyDetectorArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
anomalyGroupId

instance
  Data.ToHeaders
    ListAnomalyGroupRelatedMetrics
  where
  toHeaders :: ListAnomalyGroupRelatedMetrics -> ResponseHeaders
toHeaders =
    forall a b. a -> b -> a
Prelude.const
      ( forall a. Monoid a => [a] -> a
Prelude.mconcat
          [ HeaderName
"Content-Type"
              forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ( ByteString
"application/x-amz-json-1.1" ::
                          Prelude.ByteString
                      )
          ]
      )

instance Data.ToJSON ListAnomalyGroupRelatedMetrics where
  toJSON :: ListAnomalyGroupRelatedMetrics -> Value
toJSON ListAnomalyGroupRelatedMetrics' {Maybe Natural
Maybe Text
Maybe RelationshipType
Text
anomalyGroupId :: Text
anomalyDetectorArn :: Text
relationshipTypeFilter :: Maybe RelationshipType
nextToken :: Maybe Text
maxResults :: Maybe Natural
$sel:anomalyGroupId:ListAnomalyGroupRelatedMetrics' :: ListAnomalyGroupRelatedMetrics -> Text
$sel:anomalyDetectorArn:ListAnomalyGroupRelatedMetrics' :: ListAnomalyGroupRelatedMetrics -> Text
$sel:relationshipTypeFilter:ListAnomalyGroupRelatedMetrics' :: ListAnomalyGroupRelatedMetrics -> Maybe RelationshipType
$sel:nextToken:ListAnomalyGroupRelatedMetrics' :: ListAnomalyGroupRelatedMetrics -> Maybe Text
$sel:maxResults:ListAnomalyGroupRelatedMetrics' :: ListAnomalyGroupRelatedMetrics -> Maybe Natural
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"MaxResults" 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 Natural
maxResults,
            (Key
"NextToken" 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
nextToken,
            (Key
"RelationshipTypeFilter" 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 RelationshipType
relationshipTypeFilter,
            forall a. a -> Maybe a
Prelude.Just
              (Key
"AnomalyDetectorArn" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
anomalyDetectorArn),
            forall a. a -> Maybe a
Prelude.Just
              (Key
"AnomalyGroupId" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
anomalyGroupId)
          ]
      )

instance Data.ToPath ListAnomalyGroupRelatedMetrics where
  toPath :: ListAnomalyGroupRelatedMetrics -> ByteString
toPath =
    forall a b. a -> b -> a
Prelude.const ByteString
"/ListAnomalyGroupRelatedMetrics"

instance Data.ToQuery ListAnomalyGroupRelatedMetrics where
  toQuery :: ListAnomalyGroupRelatedMetrics -> QueryString
toQuery = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty

-- | /See:/ 'newListAnomalyGroupRelatedMetricsResponse' smart constructor.
data ListAnomalyGroupRelatedMetricsResponse = ListAnomalyGroupRelatedMetricsResponse'
  { -- | Aggregated details about the measures contributing to the anomaly group,
    -- and the measures potentially impacted by the anomaly group.
    ListAnomalyGroupRelatedMetricsResponse
-> Maybe [InterMetricImpactDetails]
interMetricImpactList :: Prelude.Maybe [InterMetricImpactDetails],
    -- | The pagination token that\'s included if more results are available.
    ListAnomalyGroupRelatedMetricsResponse -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    ListAnomalyGroupRelatedMetricsResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (ListAnomalyGroupRelatedMetricsResponse
-> ListAnomalyGroupRelatedMetricsResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListAnomalyGroupRelatedMetricsResponse
-> ListAnomalyGroupRelatedMetricsResponse -> Bool
$c/= :: ListAnomalyGroupRelatedMetricsResponse
-> ListAnomalyGroupRelatedMetricsResponse -> Bool
== :: ListAnomalyGroupRelatedMetricsResponse
-> ListAnomalyGroupRelatedMetricsResponse -> Bool
$c== :: ListAnomalyGroupRelatedMetricsResponse
-> ListAnomalyGroupRelatedMetricsResponse -> Bool
Prelude.Eq, ReadPrec [ListAnomalyGroupRelatedMetricsResponse]
ReadPrec ListAnomalyGroupRelatedMetricsResponse
Int -> ReadS ListAnomalyGroupRelatedMetricsResponse
ReadS [ListAnomalyGroupRelatedMetricsResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListAnomalyGroupRelatedMetricsResponse]
$creadListPrec :: ReadPrec [ListAnomalyGroupRelatedMetricsResponse]
readPrec :: ReadPrec ListAnomalyGroupRelatedMetricsResponse
$creadPrec :: ReadPrec ListAnomalyGroupRelatedMetricsResponse
readList :: ReadS [ListAnomalyGroupRelatedMetricsResponse]
$creadList :: ReadS [ListAnomalyGroupRelatedMetricsResponse]
readsPrec :: Int -> ReadS ListAnomalyGroupRelatedMetricsResponse
$creadsPrec :: Int -> ReadS ListAnomalyGroupRelatedMetricsResponse
Prelude.Read, Int -> ListAnomalyGroupRelatedMetricsResponse -> ShowS
[ListAnomalyGroupRelatedMetricsResponse] -> ShowS
ListAnomalyGroupRelatedMetricsResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListAnomalyGroupRelatedMetricsResponse] -> ShowS
$cshowList :: [ListAnomalyGroupRelatedMetricsResponse] -> ShowS
show :: ListAnomalyGroupRelatedMetricsResponse -> String
$cshow :: ListAnomalyGroupRelatedMetricsResponse -> String
showsPrec :: Int -> ListAnomalyGroupRelatedMetricsResponse -> ShowS
$cshowsPrec :: Int -> ListAnomalyGroupRelatedMetricsResponse -> ShowS
Prelude.Show, forall x.
Rep ListAnomalyGroupRelatedMetricsResponse x
-> ListAnomalyGroupRelatedMetricsResponse
forall x.
ListAnomalyGroupRelatedMetricsResponse
-> Rep ListAnomalyGroupRelatedMetricsResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep ListAnomalyGroupRelatedMetricsResponse x
-> ListAnomalyGroupRelatedMetricsResponse
$cfrom :: forall x.
ListAnomalyGroupRelatedMetricsResponse
-> Rep ListAnomalyGroupRelatedMetricsResponse x
Prelude.Generic)

-- |
-- Create a value of 'ListAnomalyGroupRelatedMetricsResponse' 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:
--
-- 'interMetricImpactList', 'listAnomalyGroupRelatedMetricsResponse_interMetricImpactList' - Aggregated details about the measures contributing to the anomaly group,
-- and the measures potentially impacted by the anomaly group.
--
-- 'nextToken', 'listAnomalyGroupRelatedMetricsResponse_nextToken' - The pagination token that\'s included if more results are available.
--
-- 'httpStatus', 'listAnomalyGroupRelatedMetricsResponse_httpStatus' - The response's http status code.
newListAnomalyGroupRelatedMetricsResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  ListAnomalyGroupRelatedMetricsResponse
newListAnomalyGroupRelatedMetricsResponse :: Int -> ListAnomalyGroupRelatedMetricsResponse
newListAnomalyGroupRelatedMetricsResponse
  Int
pHttpStatus_ =
    ListAnomalyGroupRelatedMetricsResponse'
      { $sel:interMetricImpactList:ListAnomalyGroupRelatedMetricsResponse' :: Maybe [InterMetricImpactDetails]
interMetricImpactList =
          forall a. Maybe a
Prelude.Nothing,
        $sel:nextToken:ListAnomalyGroupRelatedMetricsResponse' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
        $sel:httpStatus:ListAnomalyGroupRelatedMetricsResponse' :: Int
httpStatus = Int
pHttpStatus_
      }

-- | Aggregated details about the measures contributing to the anomaly group,
-- and the measures potentially impacted by the anomaly group.
listAnomalyGroupRelatedMetricsResponse_interMetricImpactList :: Lens.Lens' ListAnomalyGroupRelatedMetricsResponse (Prelude.Maybe [InterMetricImpactDetails])
listAnomalyGroupRelatedMetricsResponse_interMetricImpactList :: Lens'
  ListAnomalyGroupRelatedMetricsResponse
  (Maybe [InterMetricImpactDetails])
listAnomalyGroupRelatedMetricsResponse_interMetricImpactList = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListAnomalyGroupRelatedMetricsResponse' {Maybe [InterMetricImpactDetails]
interMetricImpactList :: Maybe [InterMetricImpactDetails]
$sel:interMetricImpactList:ListAnomalyGroupRelatedMetricsResponse' :: ListAnomalyGroupRelatedMetricsResponse
-> Maybe [InterMetricImpactDetails]
interMetricImpactList} -> Maybe [InterMetricImpactDetails]
interMetricImpactList) (\s :: ListAnomalyGroupRelatedMetricsResponse
s@ListAnomalyGroupRelatedMetricsResponse' {} Maybe [InterMetricImpactDetails]
a -> ListAnomalyGroupRelatedMetricsResponse
s {$sel:interMetricImpactList:ListAnomalyGroupRelatedMetricsResponse' :: Maybe [InterMetricImpactDetails]
interMetricImpactList = Maybe [InterMetricImpactDetails]
a} :: ListAnomalyGroupRelatedMetricsResponse) 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 pagination token that\'s included if more results are available.
listAnomalyGroupRelatedMetricsResponse_nextToken :: Lens.Lens' ListAnomalyGroupRelatedMetricsResponse (Prelude.Maybe Prelude.Text)
listAnomalyGroupRelatedMetricsResponse_nextToken :: Lens' ListAnomalyGroupRelatedMetricsResponse (Maybe Text)
listAnomalyGroupRelatedMetricsResponse_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListAnomalyGroupRelatedMetricsResponse' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:ListAnomalyGroupRelatedMetricsResponse' :: ListAnomalyGroupRelatedMetricsResponse -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: ListAnomalyGroupRelatedMetricsResponse
s@ListAnomalyGroupRelatedMetricsResponse' {} Maybe Text
a -> ListAnomalyGroupRelatedMetricsResponse
s {$sel:nextToken:ListAnomalyGroupRelatedMetricsResponse' :: Maybe Text
nextToken = Maybe Text
a} :: ListAnomalyGroupRelatedMetricsResponse)

-- | The response's http status code.
listAnomalyGroupRelatedMetricsResponse_httpStatus :: Lens.Lens' ListAnomalyGroupRelatedMetricsResponse Prelude.Int
listAnomalyGroupRelatedMetricsResponse_httpStatus :: Lens' ListAnomalyGroupRelatedMetricsResponse Int
listAnomalyGroupRelatedMetricsResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListAnomalyGroupRelatedMetricsResponse' {Int
httpStatus :: Int
$sel:httpStatus:ListAnomalyGroupRelatedMetricsResponse' :: ListAnomalyGroupRelatedMetricsResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: ListAnomalyGroupRelatedMetricsResponse
s@ListAnomalyGroupRelatedMetricsResponse' {} Int
a -> ListAnomalyGroupRelatedMetricsResponse
s {$sel:httpStatus:ListAnomalyGroupRelatedMetricsResponse' :: Int
httpStatus = Int
a} :: ListAnomalyGroupRelatedMetricsResponse)

instance
  Prelude.NFData
    ListAnomalyGroupRelatedMetricsResponse
  where
  rnf :: ListAnomalyGroupRelatedMetricsResponse -> ()
rnf ListAnomalyGroupRelatedMetricsResponse' {Int
Maybe [InterMetricImpactDetails]
Maybe Text
httpStatus :: Int
nextToken :: Maybe Text
interMetricImpactList :: Maybe [InterMetricImpactDetails]
$sel:httpStatus:ListAnomalyGroupRelatedMetricsResponse' :: ListAnomalyGroupRelatedMetricsResponse -> Int
$sel:nextToken:ListAnomalyGroupRelatedMetricsResponse' :: ListAnomalyGroupRelatedMetricsResponse -> Maybe Text
$sel:interMetricImpactList:ListAnomalyGroupRelatedMetricsResponse' :: ListAnomalyGroupRelatedMetricsResponse
-> Maybe [InterMetricImpactDetails]
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe [InterMetricImpactDetails]
interMetricImpactList
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
nextToken
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus