{-# 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.DevOpsGuru.Types.ProactiveAnomaly
-- 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.DevOpsGuru.Types.ProactiveAnomaly where

import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import Amazonka.DevOpsGuru.Types.AnomalyReportedTimeRange
import Amazonka.DevOpsGuru.Types.AnomalyResource
import Amazonka.DevOpsGuru.Types.AnomalySeverity
import Amazonka.DevOpsGuru.Types.AnomalySourceDetails
import Amazonka.DevOpsGuru.Types.AnomalySourceMetadata
import Amazonka.DevOpsGuru.Types.AnomalyStatus
import Amazonka.DevOpsGuru.Types.AnomalyTimeRange
import Amazonka.DevOpsGuru.Types.PredictionTimeRange
import Amazonka.DevOpsGuru.Types.ResourceCollection
import qualified Amazonka.Prelude as Prelude

-- | Information about an anomaly. This object is returned by
-- @ListAnomalies@.
--
-- /See:/ 'newProactiveAnomaly' smart constructor.
data ProactiveAnomaly = ProactiveAnomaly'
  { -- | An @AnomalyReportedTimeRange@ object that specifies the time range
    -- between when the anomaly is opened and the time when it is closed.
    ProactiveAnomaly -> Maybe AnomalyReportedTimeRange
anomalyReportedTimeRange :: Prelude.Maybe AnomalyReportedTimeRange,
    -- | Information about a resource in which DevOps Guru detected anomalous
    -- behavior.
    ProactiveAnomaly -> Maybe [AnomalyResource]
anomalyResources :: Prelude.Maybe [AnomalyResource],
    ProactiveAnomaly -> Maybe AnomalyTimeRange
anomalyTimeRange :: Prelude.Maybe AnomalyTimeRange,
    -- | The ID of the insight that contains this anomaly. An insight is composed
    -- of related anomalies.
    ProactiveAnomaly -> Maybe Text
associatedInsightId :: Prelude.Maybe Prelude.Text,
    -- | The ID of a proactive anomaly.
    ProactiveAnomaly -> Maybe Text
id :: Prelude.Maybe Prelude.Text,
    -- | A threshold that was exceeded by behavior in analyzed resources.
    -- Exceeding this threshold is related to the anomalous behavior that
    -- generated this anomaly.
    ProactiveAnomaly -> Maybe Double
limit :: Prelude.Maybe Prelude.Double,
    ProactiveAnomaly -> Maybe PredictionTimeRange
predictionTimeRange :: Prelude.Maybe PredictionTimeRange,
    ProactiveAnomaly -> Maybe ResourceCollection
resourceCollection :: Prelude.Maybe ResourceCollection,
    -- | The severity of the anomaly. The severity of anomalies that generate an
    -- insight determine that insight\'s severity. For more information, see
    -- <https://docs.aws.amazon.com/devops-guru/latest/userguide/working-with-insights.html#understanding-insights-severities Understanding insight severities>
    -- in the /Amazon DevOps Guru User Guide/.
    ProactiveAnomaly -> Maybe AnomalySeverity
severity :: Prelude.Maybe AnomalySeverity,
    -- | Details about the source of the analyzed operational data that triggered
    -- the anomaly. The one supported source is Amazon CloudWatch metrics.
    ProactiveAnomaly -> Maybe AnomalySourceDetails
sourceDetails :: Prelude.Maybe AnomalySourceDetails,
    -- | The metadata for the anomaly.
    ProactiveAnomaly -> Maybe AnomalySourceMetadata
sourceMetadata :: Prelude.Maybe AnomalySourceMetadata,
    -- | The status of a proactive anomaly.
    ProactiveAnomaly -> Maybe AnomalyStatus
status :: Prelude.Maybe AnomalyStatus,
    -- | The time of the anomaly\'s most recent update.
    ProactiveAnomaly -> Maybe POSIX
updateTime :: Prelude.Maybe Data.POSIX
  }
  deriving (ProactiveAnomaly -> ProactiveAnomaly -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ProactiveAnomaly -> ProactiveAnomaly -> Bool
$c/= :: ProactiveAnomaly -> ProactiveAnomaly -> Bool
== :: ProactiveAnomaly -> ProactiveAnomaly -> Bool
$c== :: ProactiveAnomaly -> ProactiveAnomaly -> Bool
Prelude.Eq, ReadPrec [ProactiveAnomaly]
ReadPrec ProactiveAnomaly
Int -> ReadS ProactiveAnomaly
ReadS [ProactiveAnomaly]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ProactiveAnomaly]
$creadListPrec :: ReadPrec [ProactiveAnomaly]
readPrec :: ReadPrec ProactiveAnomaly
$creadPrec :: ReadPrec ProactiveAnomaly
readList :: ReadS [ProactiveAnomaly]
$creadList :: ReadS [ProactiveAnomaly]
readsPrec :: Int -> ReadS ProactiveAnomaly
$creadsPrec :: Int -> ReadS ProactiveAnomaly
Prelude.Read, Int -> ProactiveAnomaly -> ShowS
[ProactiveAnomaly] -> ShowS
ProactiveAnomaly -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ProactiveAnomaly] -> ShowS
$cshowList :: [ProactiveAnomaly] -> ShowS
show :: ProactiveAnomaly -> String
$cshow :: ProactiveAnomaly -> String
showsPrec :: Int -> ProactiveAnomaly -> ShowS
$cshowsPrec :: Int -> ProactiveAnomaly -> ShowS
Prelude.Show, forall x. Rep ProactiveAnomaly x -> ProactiveAnomaly
forall x. ProactiveAnomaly -> Rep ProactiveAnomaly x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ProactiveAnomaly x -> ProactiveAnomaly
$cfrom :: forall x. ProactiveAnomaly -> Rep ProactiveAnomaly x
Prelude.Generic)

-- |
-- Create a value of 'ProactiveAnomaly' 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:
--
-- 'anomalyReportedTimeRange', 'proactiveAnomaly_anomalyReportedTimeRange' - An @AnomalyReportedTimeRange@ object that specifies the time range
-- between when the anomaly is opened and the time when it is closed.
--
-- 'anomalyResources', 'proactiveAnomaly_anomalyResources' - Information about a resource in which DevOps Guru detected anomalous
-- behavior.
--
-- 'anomalyTimeRange', 'proactiveAnomaly_anomalyTimeRange' - Undocumented member.
--
-- 'associatedInsightId', 'proactiveAnomaly_associatedInsightId' - The ID of the insight that contains this anomaly. An insight is composed
-- of related anomalies.
--
-- 'id', 'proactiveAnomaly_id' - The ID of a proactive anomaly.
--
-- 'limit', 'proactiveAnomaly_limit' - A threshold that was exceeded by behavior in analyzed resources.
-- Exceeding this threshold is related to the anomalous behavior that
-- generated this anomaly.
--
-- 'predictionTimeRange', 'proactiveAnomaly_predictionTimeRange' - Undocumented member.
--
-- 'resourceCollection', 'proactiveAnomaly_resourceCollection' - Undocumented member.
--
-- 'severity', 'proactiveAnomaly_severity' - The severity of the anomaly. The severity of anomalies that generate an
-- insight determine that insight\'s severity. For more information, see
-- <https://docs.aws.amazon.com/devops-guru/latest/userguide/working-with-insights.html#understanding-insights-severities Understanding insight severities>
-- in the /Amazon DevOps Guru User Guide/.
--
-- 'sourceDetails', 'proactiveAnomaly_sourceDetails' - Details about the source of the analyzed operational data that triggered
-- the anomaly. The one supported source is Amazon CloudWatch metrics.
--
-- 'sourceMetadata', 'proactiveAnomaly_sourceMetadata' - The metadata for the anomaly.
--
-- 'status', 'proactiveAnomaly_status' - The status of a proactive anomaly.
--
-- 'updateTime', 'proactiveAnomaly_updateTime' - The time of the anomaly\'s most recent update.
newProactiveAnomaly ::
  ProactiveAnomaly
newProactiveAnomaly :: ProactiveAnomaly
newProactiveAnomaly =
  ProactiveAnomaly'
    { $sel:anomalyReportedTimeRange:ProactiveAnomaly' :: Maybe AnomalyReportedTimeRange
anomalyReportedTimeRange =
        forall a. Maybe a
Prelude.Nothing,
      $sel:anomalyResources:ProactiveAnomaly' :: Maybe [AnomalyResource]
anomalyResources = forall a. Maybe a
Prelude.Nothing,
      $sel:anomalyTimeRange:ProactiveAnomaly' :: Maybe AnomalyTimeRange
anomalyTimeRange = forall a. Maybe a
Prelude.Nothing,
      $sel:associatedInsightId:ProactiveAnomaly' :: Maybe Text
associatedInsightId = forall a. Maybe a
Prelude.Nothing,
      $sel:id:ProactiveAnomaly' :: Maybe Text
id = forall a. Maybe a
Prelude.Nothing,
      $sel:limit:ProactiveAnomaly' :: Maybe Double
limit = forall a. Maybe a
Prelude.Nothing,
      $sel:predictionTimeRange:ProactiveAnomaly' :: Maybe PredictionTimeRange
predictionTimeRange = forall a. Maybe a
Prelude.Nothing,
      $sel:resourceCollection:ProactiveAnomaly' :: Maybe ResourceCollection
resourceCollection = forall a. Maybe a
Prelude.Nothing,
      $sel:severity:ProactiveAnomaly' :: Maybe AnomalySeverity
severity = forall a. Maybe a
Prelude.Nothing,
      $sel:sourceDetails:ProactiveAnomaly' :: Maybe AnomalySourceDetails
sourceDetails = forall a. Maybe a
Prelude.Nothing,
      $sel:sourceMetadata:ProactiveAnomaly' :: Maybe AnomalySourceMetadata
sourceMetadata = forall a. Maybe a
Prelude.Nothing,
      $sel:status:ProactiveAnomaly' :: Maybe AnomalyStatus
status = forall a. Maybe a
Prelude.Nothing,
      $sel:updateTime:ProactiveAnomaly' :: Maybe POSIX
updateTime = forall a. Maybe a
Prelude.Nothing
    }

-- | An @AnomalyReportedTimeRange@ object that specifies the time range
-- between when the anomaly is opened and the time when it is closed.
proactiveAnomaly_anomalyReportedTimeRange :: Lens.Lens' ProactiveAnomaly (Prelude.Maybe AnomalyReportedTimeRange)
proactiveAnomaly_anomalyReportedTimeRange :: Lens' ProactiveAnomaly (Maybe AnomalyReportedTimeRange)
proactiveAnomaly_anomalyReportedTimeRange = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ProactiveAnomaly' {Maybe AnomalyReportedTimeRange
anomalyReportedTimeRange :: Maybe AnomalyReportedTimeRange
$sel:anomalyReportedTimeRange:ProactiveAnomaly' :: ProactiveAnomaly -> Maybe AnomalyReportedTimeRange
anomalyReportedTimeRange} -> Maybe AnomalyReportedTimeRange
anomalyReportedTimeRange) (\s :: ProactiveAnomaly
s@ProactiveAnomaly' {} Maybe AnomalyReportedTimeRange
a -> ProactiveAnomaly
s {$sel:anomalyReportedTimeRange:ProactiveAnomaly' :: Maybe AnomalyReportedTimeRange
anomalyReportedTimeRange = Maybe AnomalyReportedTimeRange
a} :: ProactiveAnomaly)

-- | Information about a resource in which DevOps Guru detected anomalous
-- behavior.
proactiveAnomaly_anomalyResources :: Lens.Lens' ProactiveAnomaly (Prelude.Maybe [AnomalyResource])
proactiveAnomaly_anomalyResources :: Lens' ProactiveAnomaly (Maybe [AnomalyResource])
proactiveAnomaly_anomalyResources = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ProactiveAnomaly' {Maybe [AnomalyResource]
anomalyResources :: Maybe [AnomalyResource]
$sel:anomalyResources:ProactiveAnomaly' :: ProactiveAnomaly -> Maybe [AnomalyResource]
anomalyResources} -> Maybe [AnomalyResource]
anomalyResources) (\s :: ProactiveAnomaly
s@ProactiveAnomaly' {} Maybe [AnomalyResource]
a -> ProactiveAnomaly
s {$sel:anomalyResources:ProactiveAnomaly' :: Maybe [AnomalyResource]
anomalyResources = Maybe [AnomalyResource]
a} :: ProactiveAnomaly) 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

-- | Undocumented member.
proactiveAnomaly_anomalyTimeRange :: Lens.Lens' ProactiveAnomaly (Prelude.Maybe AnomalyTimeRange)
proactiveAnomaly_anomalyTimeRange :: Lens' ProactiveAnomaly (Maybe AnomalyTimeRange)
proactiveAnomaly_anomalyTimeRange = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ProactiveAnomaly' {Maybe AnomalyTimeRange
anomalyTimeRange :: Maybe AnomalyTimeRange
$sel:anomalyTimeRange:ProactiveAnomaly' :: ProactiveAnomaly -> Maybe AnomalyTimeRange
anomalyTimeRange} -> Maybe AnomalyTimeRange
anomalyTimeRange) (\s :: ProactiveAnomaly
s@ProactiveAnomaly' {} Maybe AnomalyTimeRange
a -> ProactiveAnomaly
s {$sel:anomalyTimeRange:ProactiveAnomaly' :: Maybe AnomalyTimeRange
anomalyTimeRange = Maybe AnomalyTimeRange
a} :: ProactiveAnomaly)

-- | The ID of the insight that contains this anomaly. An insight is composed
-- of related anomalies.
proactiveAnomaly_associatedInsightId :: Lens.Lens' ProactiveAnomaly (Prelude.Maybe Prelude.Text)
proactiveAnomaly_associatedInsightId :: Lens' ProactiveAnomaly (Maybe Text)
proactiveAnomaly_associatedInsightId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ProactiveAnomaly' {Maybe Text
associatedInsightId :: Maybe Text
$sel:associatedInsightId:ProactiveAnomaly' :: ProactiveAnomaly -> Maybe Text
associatedInsightId} -> Maybe Text
associatedInsightId) (\s :: ProactiveAnomaly
s@ProactiveAnomaly' {} Maybe Text
a -> ProactiveAnomaly
s {$sel:associatedInsightId:ProactiveAnomaly' :: Maybe Text
associatedInsightId = Maybe Text
a} :: ProactiveAnomaly)

-- | The ID of a proactive anomaly.
proactiveAnomaly_id :: Lens.Lens' ProactiveAnomaly (Prelude.Maybe Prelude.Text)
proactiveAnomaly_id :: Lens' ProactiveAnomaly (Maybe Text)
proactiveAnomaly_id = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ProactiveAnomaly' {Maybe Text
id :: Maybe Text
$sel:id:ProactiveAnomaly' :: ProactiveAnomaly -> Maybe Text
id} -> Maybe Text
id) (\s :: ProactiveAnomaly
s@ProactiveAnomaly' {} Maybe Text
a -> ProactiveAnomaly
s {$sel:id:ProactiveAnomaly' :: Maybe Text
id = Maybe Text
a} :: ProactiveAnomaly)

-- | A threshold that was exceeded by behavior in analyzed resources.
-- Exceeding this threshold is related to the anomalous behavior that
-- generated this anomaly.
proactiveAnomaly_limit :: Lens.Lens' ProactiveAnomaly (Prelude.Maybe Prelude.Double)
proactiveAnomaly_limit :: Lens' ProactiveAnomaly (Maybe Double)
proactiveAnomaly_limit = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ProactiveAnomaly' {Maybe Double
limit :: Maybe Double
$sel:limit:ProactiveAnomaly' :: ProactiveAnomaly -> Maybe Double
limit} -> Maybe Double
limit) (\s :: ProactiveAnomaly
s@ProactiveAnomaly' {} Maybe Double
a -> ProactiveAnomaly
s {$sel:limit:ProactiveAnomaly' :: Maybe Double
limit = Maybe Double
a} :: ProactiveAnomaly)

-- | Undocumented member.
proactiveAnomaly_predictionTimeRange :: Lens.Lens' ProactiveAnomaly (Prelude.Maybe PredictionTimeRange)
proactiveAnomaly_predictionTimeRange :: Lens' ProactiveAnomaly (Maybe PredictionTimeRange)
proactiveAnomaly_predictionTimeRange = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ProactiveAnomaly' {Maybe PredictionTimeRange
predictionTimeRange :: Maybe PredictionTimeRange
$sel:predictionTimeRange:ProactiveAnomaly' :: ProactiveAnomaly -> Maybe PredictionTimeRange
predictionTimeRange} -> Maybe PredictionTimeRange
predictionTimeRange) (\s :: ProactiveAnomaly
s@ProactiveAnomaly' {} Maybe PredictionTimeRange
a -> ProactiveAnomaly
s {$sel:predictionTimeRange:ProactiveAnomaly' :: Maybe PredictionTimeRange
predictionTimeRange = Maybe PredictionTimeRange
a} :: ProactiveAnomaly)

-- | Undocumented member.
proactiveAnomaly_resourceCollection :: Lens.Lens' ProactiveAnomaly (Prelude.Maybe ResourceCollection)
proactiveAnomaly_resourceCollection :: Lens' ProactiveAnomaly (Maybe ResourceCollection)
proactiveAnomaly_resourceCollection = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ProactiveAnomaly' {Maybe ResourceCollection
resourceCollection :: Maybe ResourceCollection
$sel:resourceCollection:ProactiveAnomaly' :: ProactiveAnomaly -> Maybe ResourceCollection
resourceCollection} -> Maybe ResourceCollection
resourceCollection) (\s :: ProactiveAnomaly
s@ProactiveAnomaly' {} Maybe ResourceCollection
a -> ProactiveAnomaly
s {$sel:resourceCollection:ProactiveAnomaly' :: Maybe ResourceCollection
resourceCollection = Maybe ResourceCollection
a} :: ProactiveAnomaly)

-- | The severity of the anomaly. The severity of anomalies that generate an
-- insight determine that insight\'s severity. For more information, see
-- <https://docs.aws.amazon.com/devops-guru/latest/userguide/working-with-insights.html#understanding-insights-severities Understanding insight severities>
-- in the /Amazon DevOps Guru User Guide/.
proactiveAnomaly_severity :: Lens.Lens' ProactiveAnomaly (Prelude.Maybe AnomalySeverity)
proactiveAnomaly_severity :: Lens' ProactiveAnomaly (Maybe AnomalySeverity)
proactiveAnomaly_severity = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ProactiveAnomaly' {Maybe AnomalySeverity
severity :: Maybe AnomalySeverity
$sel:severity:ProactiveAnomaly' :: ProactiveAnomaly -> Maybe AnomalySeverity
severity} -> Maybe AnomalySeverity
severity) (\s :: ProactiveAnomaly
s@ProactiveAnomaly' {} Maybe AnomalySeverity
a -> ProactiveAnomaly
s {$sel:severity:ProactiveAnomaly' :: Maybe AnomalySeverity
severity = Maybe AnomalySeverity
a} :: ProactiveAnomaly)

-- | Details about the source of the analyzed operational data that triggered
-- the anomaly. The one supported source is Amazon CloudWatch metrics.
proactiveAnomaly_sourceDetails :: Lens.Lens' ProactiveAnomaly (Prelude.Maybe AnomalySourceDetails)
proactiveAnomaly_sourceDetails :: Lens' ProactiveAnomaly (Maybe AnomalySourceDetails)
proactiveAnomaly_sourceDetails = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ProactiveAnomaly' {Maybe AnomalySourceDetails
sourceDetails :: Maybe AnomalySourceDetails
$sel:sourceDetails:ProactiveAnomaly' :: ProactiveAnomaly -> Maybe AnomalySourceDetails
sourceDetails} -> Maybe AnomalySourceDetails
sourceDetails) (\s :: ProactiveAnomaly
s@ProactiveAnomaly' {} Maybe AnomalySourceDetails
a -> ProactiveAnomaly
s {$sel:sourceDetails:ProactiveAnomaly' :: Maybe AnomalySourceDetails
sourceDetails = Maybe AnomalySourceDetails
a} :: ProactiveAnomaly)

-- | The metadata for the anomaly.
proactiveAnomaly_sourceMetadata :: Lens.Lens' ProactiveAnomaly (Prelude.Maybe AnomalySourceMetadata)
proactiveAnomaly_sourceMetadata :: Lens' ProactiveAnomaly (Maybe AnomalySourceMetadata)
proactiveAnomaly_sourceMetadata = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ProactiveAnomaly' {Maybe AnomalySourceMetadata
sourceMetadata :: Maybe AnomalySourceMetadata
$sel:sourceMetadata:ProactiveAnomaly' :: ProactiveAnomaly -> Maybe AnomalySourceMetadata
sourceMetadata} -> Maybe AnomalySourceMetadata
sourceMetadata) (\s :: ProactiveAnomaly
s@ProactiveAnomaly' {} Maybe AnomalySourceMetadata
a -> ProactiveAnomaly
s {$sel:sourceMetadata:ProactiveAnomaly' :: Maybe AnomalySourceMetadata
sourceMetadata = Maybe AnomalySourceMetadata
a} :: ProactiveAnomaly)

-- | The status of a proactive anomaly.
proactiveAnomaly_status :: Lens.Lens' ProactiveAnomaly (Prelude.Maybe AnomalyStatus)
proactiveAnomaly_status :: Lens' ProactiveAnomaly (Maybe AnomalyStatus)
proactiveAnomaly_status = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ProactiveAnomaly' {Maybe AnomalyStatus
status :: Maybe AnomalyStatus
$sel:status:ProactiveAnomaly' :: ProactiveAnomaly -> Maybe AnomalyStatus
status} -> Maybe AnomalyStatus
status) (\s :: ProactiveAnomaly
s@ProactiveAnomaly' {} Maybe AnomalyStatus
a -> ProactiveAnomaly
s {$sel:status:ProactiveAnomaly' :: Maybe AnomalyStatus
status = Maybe AnomalyStatus
a} :: ProactiveAnomaly)

-- | The time of the anomaly\'s most recent update.
proactiveAnomaly_updateTime :: Lens.Lens' ProactiveAnomaly (Prelude.Maybe Prelude.UTCTime)
proactiveAnomaly_updateTime :: Lens' ProactiveAnomaly (Maybe UTCTime)
proactiveAnomaly_updateTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ProactiveAnomaly' {Maybe POSIX
updateTime :: Maybe POSIX
$sel:updateTime:ProactiveAnomaly' :: ProactiveAnomaly -> Maybe POSIX
updateTime} -> Maybe POSIX
updateTime) (\s :: ProactiveAnomaly
s@ProactiveAnomaly' {} Maybe POSIX
a -> ProactiveAnomaly
s {$sel:updateTime:ProactiveAnomaly' :: Maybe POSIX
updateTime = Maybe POSIX
a} :: ProactiveAnomaly) 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 (a :: Format). Iso' (Time a) UTCTime
Data._Time

instance Data.FromJSON ProactiveAnomaly where
  parseJSON :: Value -> Parser ProactiveAnomaly
parseJSON =
    forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.withObject
      String
"ProactiveAnomaly"
      ( \Object
x ->
          Maybe AnomalyReportedTimeRange
-> Maybe [AnomalyResource]
-> Maybe AnomalyTimeRange
-> Maybe Text
-> Maybe Text
-> Maybe Double
-> Maybe PredictionTimeRange
-> Maybe ResourceCollection
-> Maybe AnomalySeverity
-> Maybe AnomalySourceDetails
-> Maybe AnomalySourceMetadata
-> Maybe AnomalyStatus
-> Maybe POSIX
-> ProactiveAnomaly
ProactiveAnomaly'
            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
"AnomalyReportedTimeRange")
            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
"AnomalyResources"
                            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
"AnomalyTimeRange")
            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
"AssociatedInsightId")
            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
"Id")
            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
"Limit")
            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
"PredictionTimeRange")
            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
"ResourceCollection")
            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
"Severity")
            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
"SourceDetails")
            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
"SourceMetadata")
            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
"Status")
            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
"UpdateTime")
      )

instance Prelude.Hashable ProactiveAnomaly where
  hashWithSalt :: Int -> ProactiveAnomaly -> Int
hashWithSalt Int
_salt ProactiveAnomaly' {Maybe Double
Maybe [AnomalyResource]
Maybe Text
Maybe POSIX
Maybe AnomalyReportedTimeRange
Maybe AnomalySeverity
Maybe AnomalySourceMetadata
Maybe AnomalyStatus
Maybe AnomalyTimeRange
Maybe PredictionTimeRange
Maybe ResourceCollection
Maybe AnomalySourceDetails
updateTime :: Maybe POSIX
status :: Maybe AnomalyStatus
sourceMetadata :: Maybe AnomalySourceMetadata
sourceDetails :: Maybe AnomalySourceDetails
severity :: Maybe AnomalySeverity
resourceCollection :: Maybe ResourceCollection
predictionTimeRange :: Maybe PredictionTimeRange
limit :: Maybe Double
id :: Maybe Text
associatedInsightId :: Maybe Text
anomalyTimeRange :: Maybe AnomalyTimeRange
anomalyResources :: Maybe [AnomalyResource]
anomalyReportedTimeRange :: Maybe AnomalyReportedTimeRange
$sel:updateTime:ProactiveAnomaly' :: ProactiveAnomaly -> Maybe POSIX
$sel:status:ProactiveAnomaly' :: ProactiveAnomaly -> Maybe AnomalyStatus
$sel:sourceMetadata:ProactiveAnomaly' :: ProactiveAnomaly -> Maybe AnomalySourceMetadata
$sel:sourceDetails:ProactiveAnomaly' :: ProactiveAnomaly -> Maybe AnomalySourceDetails
$sel:severity:ProactiveAnomaly' :: ProactiveAnomaly -> Maybe AnomalySeverity
$sel:resourceCollection:ProactiveAnomaly' :: ProactiveAnomaly -> Maybe ResourceCollection
$sel:predictionTimeRange:ProactiveAnomaly' :: ProactiveAnomaly -> Maybe PredictionTimeRange
$sel:limit:ProactiveAnomaly' :: ProactiveAnomaly -> Maybe Double
$sel:id:ProactiveAnomaly' :: ProactiveAnomaly -> Maybe Text
$sel:associatedInsightId:ProactiveAnomaly' :: ProactiveAnomaly -> Maybe Text
$sel:anomalyTimeRange:ProactiveAnomaly' :: ProactiveAnomaly -> Maybe AnomalyTimeRange
$sel:anomalyResources:ProactiveAnomaly' :: ProactiveAnomaly -> Maybe [AnomalyResource]
$sel:anomalyReportedTimeRange:ProactiveAnomaly' :: ProactiveAnomaly -> Maybe AnomalyReportedTimeRange
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe AnomalyReportedTimeRange
anomalyReportedTimeRange
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [AnomalyResource]
anomalyResources
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe AnomalyTimeRange
anomalyTimeRange
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
associatedInsightId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
id
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Double
limit
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe PredictionTimeRange
predictionTimeRange
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ResourceCollection
resourceCollection
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe AnomalySeverity
severity
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe AnomalySourceDetails
sourceDetails
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe AnomalySourceMetadata
sourceMetadata
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe AnomalyStatus
status
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe POSIX
updateTime

instance Prelude.NFData ProactiveAnomaly where
  rnf :: ProactiveAnomaly -> ()
rnf ProactiveAnomaly' {Maybe Double
Maybe [AnomalyResource]
Maybe Text
Maybe POSIX
Maybe AnomalyReportedTimeRange
Maybe AnomalySeverity
Maybe AnomalySourceMetadata
Maybe AnomalyStatus
Maybe AnomalyTimeRange
Maybe PredictionTimeRange
Maybe ResourceCollection
Maybe AnomalySourceDetails
updateTime :: Maybe POSIX
status :: Maybe AnomalyStatus
sourceMetadata :: Maybe AnomalySourceMetadata
sourceDetails :: Maybe AnomalySourceDetails
severity :: Maybe AnomalySeverity
resourceCollection :: Maybe ResourceCollection
predictionTimeRange :: Maybe PredictionTimeRange
limit :: Maybe Double
id :: Maybe Text
associatedInsightId :: Maybe Text
anomalyTimeRange :: Maybe AnomalyTimeRange
anomalyResources :: Maybe [AnomalyResource]
anomalyReportedTimeRange :: Maybe AnomalyReportedTimeRange
$sel:updateTime:ProactiveAnomaly' :: ProactiveAnomaly -> Maybe POSIX
$sel:status:ProactiveAnomaly' :: ProactiveAnomaly -> Maybe AnomalyStatus
$sel:sourceMetadata:ProactiveAnomaly' :: ProactiveAnomaly -> Maybe AnomalySourceMetadata
$sel:sourceDetails:ProactiveAnomaly' :: ProactiveAnomaly -> Maybe AnomalySourceDetails
$sel:severity:ProactiveAnomaly' :: ProactiveAnomaly -> Maybe AnomalySeverity
$sel:resourceCollection:ProactiveAnomaly' :: ProactiveAnomaly -> Maybe ResourceCollection
$sel:predictionTimeRange:ProactiveAnomaly' :: ProactiveAnomaly -> Maybe PredictionTimeRange
$sel:limit:ProactiveAnomaly' :: ProactiveAnomaly -> Maybe Double
$sel:id:ProactiveAnomaly' :: ProactiveAnomaly -> Maybe Text
$sel:associatedInsightId:ProactiveAnomaly' :: ProactiveAnomaly -> Maybe Text
$sel:anomalyTimeRange:ProactiveAnomaly' :: ProactiveAnomaly -> Maybe AnomalyTimeRange
$sel:anomalyResources:ProactiveAnomaly' :: ProactiveAnomaly -> Maybe [AnomalyResource]
$sel:anomalyReportedTimeRange:ProactiveAnomaly' :: ProactiveAnomaly -> Maybe AnomalyReportedTimeRange
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe AnomalyReportedTimeRange
anomalyReportedTimeRange
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [AnomalyResource]
anomalyResources
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe AnomalyTimeRange
anomalyTimeRange
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
associatedInsightId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
id
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Double
limit
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe PredictionTimeRange
predictionTimeRange
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ResourceCollection
resourceCollection
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe AnomalySeverity
severity
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe AnomalySourceDetails
sourceDetails
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe AnomalySourceMetadata
sourceMetadata
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe AnomalyStatus
status
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe POSIX
updateTime