{-# 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.LookoutMetrics.Types.AnomalyGroup
-- 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.LookoutMetrics.Types.AnomalyGroup 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.MetricLevelImpact
import qualified Amazonka.Prelude as Prelude

-- | A group of anomalous metrics
--
-- /See:/ 'newAnomalyGroup' smart constructor.
data AnomalyGroup = AnomalyGroup'
  { -- | The ID of the anomaly group.
    AnomalyGroup -> Maybe Text
anomalyGroupId :: Prelude.Maybe Prelude.Text,
    -- | The severity score of the group.
    AnomalyGroup -> Maybe Double
anomalyGroupScore :: Prelude.Maybe Prelude.Double,
    -- | The end time for the group.
    AnomalyGroup -> Maybe Text
endTime :: Prelude.Maybe Prelude.Text,
    -- | A list of measures affected by the anomaly.
    AnomalyGroup -> Maybe [MetricLevelImpact]
metricLevelImpactList :: Prelude.Maybe [MetricLevelImpact],
    -- | The name of the primary affected measure for the group.
    AnomalyGroup -> Maybe Text
primaryMetricName :: Prelude.Maybe Prelude.Text,
    -- | The start time for the group.
    AnomalyGroup -> Maybe Text
startTime :: Prelude.Maybe Prelude.Text
  }
  deriving (AnomalyGroup -> AnomalyGroup -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AnomalyGroup -> AnomalyGroup -> Bool
$c/= :: AnomalyGroup -> AnomalyGroup -> Bool
== :: AnomalyGroup -> AnomalyGroup -> Bool
$c== :: AnomalyGroup -> AnomalyGroup -> Bool
Prelude.Eq, ReadPrec [AnomalyGroup]
ReadPrec AnomalyGroup
Int -> ReadS AnomalyGroup
ReadS [AnomalyGroup]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [AnomalyGroup]
$creadListPrec :: ReadPrec [AnomalyGroup]
readPrec :: ReadPrec AnomalyGroup
$creadPrec :: ReadPrec AnomalyGroup
readList :: ReadS [AnomalyGroup]
$creadList :: ReadS [AnomalyGroup]
readsPrec :: Int -> ReadS AnomalyGroup
$creadsPrec :: Int -> ReadS AnomalyGroup
Prelude.Read, Int -> AnomalyGroup -> ShowS
[AnomalyGroup] -> ShowS
AnomalyGroup -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [AnomalyGroup] -> ShowS
$cshowList :: [AnomalyGroup] -> ShowS
show :: AnomalyGroup -> String
$cshow :: AnomalyGroup -> String
showsPrec :: Int -> AnomalyGroup -> ShowS
$cshowsPrec :: Int -> AnomalyGroup -> ShowS
Prelude.Show, forall x. Rep AnomalyGroup x -> AnomalyGroup
forall x. AnomalyGroup -> Rep AnomalyGroup x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep AnomalyGroup x -> AnomalyGroup
$cfrom :: forall x. AnomalyGroup -> Rep AnomalyGroup x
Prelude.Generic)

-- |
-- Create a value of 'AnomalyGroup' 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:
--
-- 'anomalyGroupId', 'anomalyGroup_anomalyGroupId' - The ID of the anomaly group.
--
-- 'anomalyGroupScore', 'anomalyGroup_anomalyGroupScore' - The severity score of the group.
--
-- 'endTime', 'anomalyGroup_endTime' - The end time for the group.
--
-- 'metricLevelImpactList', 'anomalyGroup_metricLevelImpactList' - A list of measures affected by the anomaly.
--
-- 'primaryMetricName', 'anomalyGroup_primaryMetricName' - The name of the primary affected measure for the group.
--
-- 'startTime', 'anomalyGroup_startTime' - The start time for the group.
newAnomalyGroup ::
  AnomalyGroup
newAnomalyGroup :: AnomalyGroup
newAnomalyGroup =
  AnomalyGroup'
    { $sel:anomalyGroupId:AnomalyGroup' :: Maybe Text
anomalyGroupId = forall a. Maybe a
Prelude.Nothing,
      $sel:anomalyGroupScore:AnomalyGroup' :: Maybe Double
anomalyGroupScore = forall a. Maybe a
Prelude.Nothing,
      $sel:endTime:AnomalyGroup' :: Maybe Text
endTime = forall a. Maybe a
Prelude.Nothing,
      $sel:metricLevelImpactList:AnomalyGroup' :: Maybe [MetricLevelImpact]
metricLevelImpactList = forall a. Maybe a
Prelude.Nothing,
      $sel:primaryMetricName:AnomalyGroup' :: Maybe Text
primaryMetricName = forall a. Maybe a
Prelude.Nothing,
      $sel:startTime:AnomalyGroup' :: Maybe Text
startTime = forall a. Maybe a
Prelude.Nothing
    }

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

-- | The severity score of the group.
anomalyGroup_anomalyGroupScore :: Lens.Lens' AnomalyGroup (Prelude.Maybe Prelude.Double)
anomalyGroup_anomalyGroupScore :: Lens' AnomalyGroup (Maybe Double)
anomalyGroup_anomalyGroupScore = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AnomalyGroup' {Maybe Double
anomalyGroupScore :: Maybe Double
$sel:anomalyGroupScore:AnomalyGroup' :: AnomalyGroup -> Maybe Double
anomalyGroupScore} -> Maybe Double
anomalyGroupScore) (\s :: AnomalyGroup
s@AnomalyGroup' {} Maybe Double
a -> AnomalyGroup
s {$sel:anomalyGroupScore:AnomalyGroup' :: Maybe Double
anomalyGroupScore = Maybe Double
a} :: AnomalyGroup)

-- | The end time for the group.
anomalyGroup_endTime :: Lens.Lens' AnomalyGroup (Prelude.Maybe Prelude.Text)
anomalyGroup_endTime :: Lens' AnomalyGroup (Maybe Text)
anomalyGroup_endTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AnomalyGroup' {Maybe Text
endTime :: Maybe Text
$sel:endTime:AnomalyGroup' :: AnomalyGroup -> Maybe Text
endTime} -> Maybe Text
endTime) (\s :: AnomalyGroup
s@AnomalyGroup' {} Maybe Text
a -> AnomalyGroup
s {$sel:endTime:AnomalyGroup' :: Maybe Text
endTime = Maybe Text
a} :: AnomalyGroup)

-- | A list of measures affected by the anomaly.
anomalyGroup_metricLevelImpactList :: Lens.Lens' AnomalyGroup (Prelude.Maybe [MetricLevelImpact])
anomalyGroup_metricLevelImpactList :: Lens' AnomalyGroup (Maybe [MetricLevelImpact])
anomalyGroup_metricLevelImpactList = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AnomalyGroup' {Maybe [MetricLevelImpact]
metricLevelImpactList :: Maybe [MetricLevelImpact]
$sel:metricLevelImpactList:AnomalyGroup' :: AnomalyGroup -> Maybe [MetricLevelImpact]
metricLevelImpactList} -> Maybe [MetricLevelImpact]
metricLevelImpactList) (\s :: AnomalyGroup
s@AnomalyGroup' {} Maybe [MetricLevelImpact]
a -> AnomalyGroup
s {$sel:metricLevelImpactList:AnomalyGroup' :: Maybe [MetricLevelImpact]
metricLevelImpactList = Maybe [MetricLevelImpact]
a} :: AnomalyGroup) 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 name of the primary affected measure for the group.
anomalyGroup_primaryMetricName :: Lens.Lens' AnomalyGroup (Prelude.Maybe Prelude.Text)
anomalyGroup_primaryMetricName :: Lens' AnomalyGroup (Maybe Text)
anomalyGroup_primaryMetricName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AnomalyGroup' {Maybe Text
primaryMetricName :: Maybe Text
$sel:primaryMetricName:AnomalyGroup' :: AnomalyGroup -> Maybe Text
primaryMetricName} -> Maybe Text
primaryMetricName) (\s :: AnomalyGroup
s@AnomalyGroup' {} Maybe Text
a -> AnomalyGroup
s {$sel:primaryMetricName:AnomalyGroup' :: Maybe Text
primaryMetricName = Maybe Text
a} :: AnomalyGroup)

-- | The start time for the group.
anomalyGroup_startTime :: Lens.Lens' AnomalyGroup (Prelude.Maybe Prelude.Text)
anomalyGroup_startTime :: Lens' AnomalyGroup (Maybe Text)
anomalyGroup_startTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AnomalyGroup' {Maybe Text
startTime :: Maybe Text
$sel:startTime:AnomalyGroup' :: AnomalyGroup -> Maybe Text
startTime} -> Maybe Text
startTime) (\s :: AnomalyGroup
s@AnomalyGroup' {} Maybe Text
a -> AnomalyGroup
s {$sel:startTime:AnomalyGroup' :: Maybe Text
startTime = Maybe Text
a} :: AnomalyGroup)

instance Data.FromJSON AnomalyGroup where
  parseJSON :: Value -> Parser AnomalyGroup
parseJSON =
    forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.withObject
      String
"AnomalyGroup"
      ( \Object
x ->
          Maybe Text
-> Maybe Double
-> Maybe Text
-> Maybe [MetricLevelImpact]
-> Maybe Text
-> Maybe Text
-> AnomalyGroup
AnomalyGroup'
            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
"AnomalyGroupId")
            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
"AnomalyGroupScore")
            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
"EndTime")
            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
"MetricLevelImpactList"
                            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
"PrimaryMetricName")
            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
"StartTime")
      )

instance Prelude.Hashable AnomalyGroup where
  hashWithSalt :: Int -> AnomalyGroup -> Int
hashWithSalt Int
_salt AnomalyGroup' {Maybe Double
Maybe [MetricLevelImpact]
Maybe Text
startTime :: Maybe Text
primaryMetricName :: Maybe Text
metricLevelImpactList :: Maybe [MetricLevelImpact]
endTime :: Maybe Text
anomalyGroupScore :: Maybe Double
anomalyGroupId :: Maybe Text
$sel:startTime:AnomalyGroup' :: AnomalyGroup -> Maybe Text
$sel:primaryMetricName:AnomalyGroup' :: AnomalyGroup -> Maybe Text
$sel:metricLevelImpactList:AnomalyGroup' :: AnomalyGroup -> Maybe [MetricLevelImpact]
$sel:endTime:AnomalyGroup' :: AnomalyGroup -> Maybe Text
$sel:anomalyGroupScore:AnomalyGroup' :: AnomalyGroup -> Maybe Double
$sel:anomalyGroupId:AnomalyGroup' :: AnomalyGroup -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
anomalyGroupId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Double
anomalyGroupScore
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
endTime
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [MetricLevelImpact]
metricLevelImpactList
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
primaryMetricName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
startTime

instance Prelude.NFData AnomalyGroup where
  rnf :: AnomalyGroup -> ()
rnf AnomalyGroup' {Maybe Double
Maybe [MetricLevelImpact]
Maybe Text
startTime :: Maybe Text
primaryMetricName :: Maybe Text
metricLevelImpactList :: Maybe [MetricLevelImpact]
endTime :: Maybe Text
anomalyGroupScore :: Maybe Double
anomalyGroupId :: Maybe Text
$sel:startTime:AnomalyGroup' :: AnomalyGroup -> Maybe Text
$sel:primaryMetricName:AnomalyGroup' :: AnomalyGroup -> Maybe Text
$sel:metricLevelImpactList:AnomalyGroup' :: AnomalyGroup -> Maybe [MetricLevelImpact]
$sel:endTime:AnomalyGroup' :: AnomalyGroup -> Maybe Text
$sel:anomalyGroupScore:AnomalyGroup' :: AnomalyGroup -> Maybe Double
$sel:anomalyGroupId:AnomalyGroup' :: AnomalyGroup -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
anomalyGroupId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Double
anomalyGroupScore
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
endTime
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [MetricLevelImpact]
metricLevelImpactList
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
primaryMetricName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
startTime