{-# 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.SageMaker.Types.MonitoringAlertSummary
-- 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.SageMaker.Types.MonitoringAlertSummary 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
import Amazonka.SageMaker.Types.MonitoringAlertActions
import Amazonka.SageMaker.Types.MonitoringAlertStatus

-- | Provides summary information about a monitor alert.
--
-- /See:/ 'newMonitoringAlertSummary' smart constructor.
data MonitoringAlertSummary = MonitoringAlertSummary'
  { -- | The name of a monitoring alert.
    MonitoringAlertSummary -> Text
monitoringAlertName :: Prelude.Text,
    -- | A timestamp that indicates when a monitor alert was created.
    MonitoringAlertSummary -> POSIX
creationTime :: Data.POSIX,
    -- | A timestamp that indicates when a monitor alert was last updated.
    MonitoringAlertSummary -> POSIX
lastModifiedTime :: Data.POSIX,
    -- | The current status of an alert.
    MonitoringAlertSummary -> MonitoringAlertStatus
alertStatus :: MonitoringAlertStatus,
    -- | Within @EvaluationPeriod@, how many execution failures will raise an
    -- alert.
    MonitoringAlertSummary -> Natural
datapointsToAlert :: Prelude.Natural,
    -- | The number of most recent monitoring executions to consider when
    -- evaluating alert status.
    MonitoringAlertSummary -> Natural
evaluationPeriod :: Prelude.Natural,
    -- | A list of alert actions taken in response to an alert going into
    -- @InAlert@ status.
    MonitoringAlertSummary -> MonitoringAlertActions
actions :: MonitoringAlertActions
  }
  deriving (MonitoringAlertSummary -> MonitoringAlertSummary -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: MonitoringAlertSummary -> MonitoringAlertSummary -> Bool
$c/= :: MonitoringAlertSummary -> MonitoringAlertSummary -> Bool
== :: MonitoringAlertSummary -> MonitoringAlertSummary -> Bool
$c== :: MonitoringAlertSummary -> MonitoringAlertSummary -> Bool
Prelude.Eq, ReadPrec [MonitoringAlertSummary]
ReadPrec MonitoringAlertSummary
Int -> ReadS MonitoringAlertSummary
ReadS [MonitoringAlertSummary]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [MonitoringAlertSummary]
$creadListPrec :: ReadPrec [MonitoringAlertSummary]
readPrec :: ReadPrec MonitoringAlertSummary
$creadPrec :: ReadPrec MonitoringAlertSummary
readList :: ReadS [MonitoringAlertSummary]
$creadList :: ReadS [MonitoringAlertSummary]
readsPrec :: Int -> ReadS MonitoringAlertSummary
$creadsPrec :: Int -> ReadS MonitoringAlertSummary
Prelude.Read, Int -> MonitoringAlertSummary -> ShowS
[MonitoringAlertSummary] -> ShowS
MonitoringAlertSummary -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [MonitoringAlertSummary] -> ShowS
$cshowList :: [MonitoringAlertSummary] -> ShowS
show :: MonitoringAlertSummary -> String
$cshow :: MonitoringAlertSummary -> String
showsPrec :: Int -> MonitoringAlertSummary -> ShowS
$cshowsPrec :: Int -> MonitoringAlertSummary -> ShowS
Prelude.Show, forall x. Rep MonitoringAlertSummary x -> MonitoringAlertSummary
forall x. MonitoringAlertSummary -> Rep MonitoringAlertSummary x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep MonitoringAlertSummary x -> MonitoringAlertSummary
$cfrom :: forall x. MonitoringAlertSummary -> Rep MonitoringAlertSummary x
Prelude.Generic)

-- |
-- Create a value of 'MonitoringAlertSummary' 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:
--
-- 'monitoringAlertName', 'monitoringAlertSummary_monitoringAlertName' - The name of a monitoring alert.
--
-- 'creationTime', 'monitoringAlertSummary_creationTime' - A timestamp that indicates when a monitor alert was created.
--
-- 'lastModifiedTime', 'monitoringAlertSummary_lastModifiedTime' - A timestamp that indicates when a monitor alert was last updated.
--
-- 'alertStatus', 'monitoringAlertSummary_alertStatus' - The current status of an alert.
--
-- 'datapointsToAlert', 'monitoringAlertSummary_datapointsToAlert' - Within @EvaluationPeriod@, how many execution failures will raise an
-- alert.
--
-- 'evaluationPeriod', 'monitoringAlertSummary_evaluationPeriod' - The number of most recent monitoring executions to consider when
-- evaluating alert status.
--
-- 'actions', 'monitoringAlertSummary_actions' - A list of alert actions taken in response to an alert going into
-- @InAlert@ status.
newMonitoringAlertSummary ::
  -- | 'monitoringAlertName'
  Prelude.Text ->
  -- | 'creationTime'
  Prelude.UTCTime ->
  -- | 'lastModifiedTime'
  Prelude.UTCTime ->
  -- | 'alertStatus'
  MonitoringAlertStatus ->
  -- | 'datapointsToAlert'
  Prelude.Natural ->
  -- | 'evaluationPeriod'
  Prelude.Natural ->
  -- | 'actions'
  MonitoringAlertActions ->
  MonitoringAlertSummary
newMonitoringAlertSummary :: Text
-> UTCTime
-> UTCTime
-> MonitoringAlertStatus
-> Natural
-> Natural
-> MonitoringAlertActions
-> MonitoringAlertSummary
newMonitoringAlertSummary
  Text
pMonitoringAlertName_
  UTCTime
pCreationTime_
  UTCTime
pLastModifiedTime_
  MonitoringAlertStatus
pAlertStatus_
  Natural
pDatapointsToAlert_
  Natural
pEvaluationPeriod_
  MonitoringAlertActions
pActions_ =
    MonitoringAlertSummary'
      { $sel:monitoringAlertName:MonitoringAlertSummary' :: Text
monitoringAlertName =
          Text
pMonitoringAlertName_,
        $sel:creationTime:MonitoringAlertSummary' :: POSIX
creationTime = forall (a :: Format). Iso' (Time a) UTCTime
Data._Time forall t b. AReview t b -> b -> t
Lens.# UTCTime
pCreationTime_,
        $sel:lastModifiedTime:MonitoringAlertSummary' :: POSIX
lastModifiedTime =
          forall (a :: Format). Iso' (Time a) UTCTime
Data._Time forall t b. AReview t b -> b -> t
Lens.# UTCTime
pLastModifiedTime_,
        $sel:alertStatus:MonitoringAlertSummary' :: MonitoringAlertStatus
alertStatus = MonitoringAlertStatus
pAlertStatus_,
        $sel:datapointsToAlert:MonitoringAlertSummary' :: Natural
datapointsToAlert = Natural
pDatapointsToAlert_,
        $sel:evaluationPeriod:MonitoringAlertSummary' :: Natural
evaluationPeriod = Natural
pEvaluationPeriod_,
        $sel:actions:MonitoringAlertSummary' :: MonitoringAlertActions
actions = MonitoringAlertActions
pActions_
      }

-- | The name of a monitoring alert.
monitoringAlertSummary_monitoringAlertName :: Lens.Lens' MonitoringAlertSummary Prelude.Text
monitoringAlertSummary_monitoringAlertName :: Lens' MonitoringAlertSummary Text
monitoringAlertSummary_monitoringAlertName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\MonitoringAlertSummary' {Text
monitoringAlertName :: Text
$sel:monitoringAlertName:MonitoringAlertSummary' :: MonitoringAlertSummary -> Text
monitoringAlertName} -> Text
monitoringAlertName) (\s :: MonitoringAlertSummary
s@MonitoringAlertSummary' {} Text
a -> MonitoringAlertSummary
s {$sel:monitoringAlertName:MonitoringAlertSummary' :: Text
monitoringAlertName = Text
a} :: MonitoringAlertSummary)

-- | A timestamp that indicates when a monitor alert was created.
monitoringAlertSummary_creationTime :: Lens.Lens' MonitoringAlertSummary Prelude.UTCTime
monitoringAlertSummary_creationTime :: Lens' MonitoringAlertSummary UTCTime
monitoringAlertSummary_creationTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\MonitoringAlertSummary' {POSIX
creationTime :: POSIX
$sel:creationTime:MonitoringAlertSummary' :: MonitoringAlertSummary -> POSIX
creationTime} -> POSIX
creationTime) (\s :: MonitoringAlertSummary
s@MonitoringAlertSummary' {} POSIX
a -> MonitoringAlertSummary
s {$sel:creationTime:MonitoringAlertSummary' :: POSIX
creationTime = POSIX
a} :: MonitoringAlertSummary) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (a :: Format). Iso' (Time a) UTCTime
Data._Time

-- | A timestamp that indicates when a monitor alert was last updated.
monitoringAlertSummary_lastModifiedTime :: Lens.Lens' MonitoringAlertSummary Prelude.UTCTime
monitoringAlertSummary_lastModifiedTime :: Lens' MonitoringAlertSummary UTCTime
monitoringAlertSummary_lastModifiedTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\MonitoringAlertSummary' {POSIX
lastModifiedTime :: POSIX
$sel:lastModifiedTime:MonitoringAlertSummary' :: MonitoringAlertSummary -> POSIX
lastModifiedTime} -> POSIX
lastModifiedTime) (\s :: MonitoringAlertSummary
s@MonitoringAlertSummary' {} POSIX
a -> MonitoringAlertSummary
s {$sel:lastModifiedTime:MonitoringAlertSummary' :: POSIX
lastModifiedTime = POSIX
a} :: MonitoringAlertSummary) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (a :: Format). Iso' (Time a) UTCTime
Data._Time

-- | The current status of an alert.
monitoringAlertSummary_alertStatus :: Lens.Lens' MonitoringAlertSummary MonitoringAlertStatus
monitoringAlertSummary_alertStatus :: Lens' MonitoringAlertSummary MonitoringAlertStatus
monitoringAlertSummary_alertStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\MonitoringAlertSummary' {MonitoringAlertStatus
alertStatus :: MonitoringAlertStatus
$sel:alertStatus:MonitoringAlertSummary' :: MonitoringAlertSummary -> MonitoringAlertStatus
alertStatus} -> MonitoringAlertStatus
alertStatus) (\s :: MonitoringAlertSummary
s@MonitoringAlertSummary' {} MonitoringAlertStatus
a -> MonitoringAlertSummary
s {$sel:alertStatus:MonitoringAlertSummary' :: MonitoringAlertStatus
alertStatus = MonitoringAlertStatus
a} :: MonitoringAlertSummary)

-- | Within @EvaluationPeriod@, how many execution failures will raise an
-- alert.
monitoringAlertSummary_datapointsToAlert :: Lens.Lens' MonitoringAlertSummary Prelude.Natural
monitoringAlertSummary_datapointsToAlert :: Lens' MonitoringAlertSummary Natural
monitoringAlertSummary_datapointsToAlert = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\MonitoringAlertSummary' {Natural
datapointsToAlert :: Natural
$sel:datapointsToAlert:MonitoringAlertSummary' :: MonitoringAlertSummary -> Natural
datapointsToAlert} -> Natural
datapointsToAlert) (\s :: MonitoringAlertSummary
s@MonitoringAlertSummary' {} Natural
a -> MonitoringAlertSummary
s {$sel:datapointsToAlert:MonitoringAlertSummary' :: Natural
datapointsToAlert = Natural
a} :: MonitoringAlertSummary)

-- | The number of most recent monitoring executions to consider when
-- evaluating alert status.
monitoringAlertSummary_evaluationPeriod :: Lens.Lens' MonitoringAlertSummary Prelude.Natural
monitoringAlertSummary_evaluationPeriod :: Lens' MonitoringAlertSummary Natural
monitoringAlertSummary_evaluationPeriod = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\MonitoringAlertSummary' {Natural
evaluationPeriod :: Natural
$sel:evaluationPeriod:MonitoringAlertSummary' :: MonitoringAlertSummary -> Natural
evaluationPeriod} -> Natural
evaluationPeriod) (\s :: MonitoringAlertSummary
s@MonitoringAlertSummary' {} Natural
a -> MonitoringAlertSummary
s {$sel:evaluationPeriod:MonitoringAlertSummary' :: Natural
evaluationPeriod = Natural
a} :: MonitoringAlertSummary)

-- | A list of alert actions taken in response to an alert going into
-- @InAlert@ status.
monitoringAlertSummary_actions :: Lens.Lens' MonitoringAlertSummary MonitoringAlertActions
monitoringAlertSummary_actions :: Lens' MonitoringAlertSummary MonitoringAlertActions
monitoringAlertSummary_actions = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\MonitoringAlertSummary' {MonitoringAlertActions
actions :: MonitoringAlertActions
$sel:actions:MonitoringAlertSummary' :: MonitoringAlertSummary -> MonitoringAlertActions
actions} -> MonitoringAlertActions
actions) (\s :: MonitoringAlertSummary
s@MonitoringAlertSummary' {} MonitoringAlertActions
a -> MonitoringAlertSummary
s {$sel:actions:MonitoringAlertSummary' :: MonitoringAlertActions
actions = MonitoringAlertActions
a} :: MonitoringAlertSummary)

instance Data.FromJSON MonitoringAlertSummary where
  parseJSON :: Value -> Parser MonitoringAlertSummary
parseJSON =
    forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.withObject
      String
"MonitoringAlertSummary"
      ( \Object
x ->
          Text
-> POSIX
-> POSIX
-> MonitoringAlertStatus
-> Natural
-> Natural
-> MonitoringAlertActions
-> MonitoringAlertSummary
MonitoringAlertSummary'
            forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> (Object
x forall a. FromJSON a => Object -> Key -> Parser a
Data..: Key
"MonitoringAlertName")
            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
"CreationTime")
            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
"LastModifiedTime")
            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
"AlertStatus")
            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
"DatapointsToAlert")
            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
"EvaluationPeriod")
            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
"Actions")
      )

instance Prelude.Hashable MonitoringAlertSummary where
  hashWithSalt :: Int -> MonitoringAlertSummary -> Int
hashWithSalt Int
_salt MonitoringAlertSummary' {Natural
Text
POSIX
MonitoringAlertActions
MonitoringAlertStatus
actions :: MonitoringAlertActions
evaluationPeriod :: Natural
datapointsToAlert :: Natural
alertStatus :: MonitoringAlertStatus
lastModifiedTime :: POSIX
creationTime :: POSIX
monitoringAlertName :: Text
$sel:actions:MonitoringAlertSummary' :: MonitoringAlertSummary -> MonitoringAlertActions
$sel:evaluationPeriod:MonitoringAlertSummary' :: MonitoringAlertSummary -> Natural
$sel:datapointsToAlert:MonitoringAlertSummary' :: MonitoringAlertSummary -> Natural
$sel:alertStatus:MonitoringAlertSummary' :: MonitoringAlertSummary -> MonitoringAlertStatus
$sel:lastModifiedTime:MonitoringAlertSummary' :: MonitoringAlertSummary -> POSIX
$sel:creationTime:MonitoringAlertSummary' :: MonitoringAlertSummary -> POSIX
$sel:monitoringAlertName:MonitoringAlertSummary' :: MonitoringAlertSummary -> Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
monitoringAlertName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` POSIX
creationTime
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` POSIX
lastModifiedTime
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` MonitoringAlertStatus
alertStatus
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Natural
datapointsToAlert
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Natural
evaluationPeriod
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` MonitoringAlertActions
actions

instance Prelude.NFData MonitoringAlertSummary where
  rnf :: MonitoringAlertSummary -> ()
rnf MonitoringAlertSummary' {Natural
Text
POSIX
MonitoringAlertActions
MonitoringAlertStatus
actions :: MonitoringAlertActions
evaluationPeriod :: Natural
datapointsToAlert :: Natural
alertStatus :: MonitoringAlertStatus
lastModifiedTime :: POSIX
creationTime :: POSIX
monitoringAlertName :: Text
$sel:actions:MonitoringAlertSummary' :: MonitoringAlertSummary -> MonitoringAlertActions
$sel:evaluationPeriod:MonitoringAlertSummary' :: MonitoringAlertSummary -> Natural
$sel:datapointsToAlert:MonitoringAlertSummary' :: MonitoringAlertSummary -> Natural
$sel:alertStatus:MonitoringAlertSummary' :: MonitoringAlertSummary -> MonitoringAlertStatus
$sel:lastModifiedTime:MonitoringAlertSummary' :: MonitoringAlertSummary -> POSIX
$sel:creationTime:MonitoringAlertSummary' :: MonitoringAlertSummary -> POSIX
$sel:monitoringAlertName:MonitoringAlertSummary' :: MonitoringAlertSummary -> Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Text
monitoringAlertName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf POSIX
creationTime
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf POSIX
lastModifiedTime
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf MonitoringAlertStatus
alertStatus
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Natural
datapointsToAlert
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Natural
evaluationPeriod
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf MonitoringAlertActions
actions