{-# 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.CloudWatch.Types.CompositeAlarm
-- 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.CloudWatch.Types.CompositeAlarm where

import Amazonka.CloudWatch.Types.ActionsSuppressedBy
import Amazonka.CloudWatch.Types.StateValue
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

-- | The details about a composite alarm.
--
-- /See:/ 'newCompositeAlarm' smart constructor.
data CompositeAlarm = CompositeAlarm'
  { -- | Indicates whether actions should be executed during any changes to the
    -- alarm state.
    CompositeAlarm -> Maybe Bool
actionsEnabled :: Prelude.Maybe Prelude.Bool,
    -- | When the value is @ALARM@, it means that the actions are suppressed
    -- because the suppressor alarm is in @ALARM@ When the value is
    -- @WaitPeriod@, it means that the actions are suppressed because the
    -- composite alarm is waiting for the suppressor alarm to go into into the
    -- @ALARM@ state. The maximum waiting time is as specified in
    -- @ActionsSuppressorWaitPeriod@. After this time, the composite alarm
    -- performs its actions. When the value is @ExtensionPeriod@, it means that
    -- the actions are suppressed because the composite alarm is waiting after
    -- the suppressor alarm went out of the @ALARM@ state. The maximum waiting
    -- time is as specified in @ActionsSuppressorExtensionPeriod@. After this
    -- time, the composite alarm performs its actions.
    CompositeAlarm -> Maybe ActionsSuppressedBy
actionsSuppressedBy :: Prelude.Maybe ActionsSuppressedBy,
    -- | Captures the reason for action suppression.
    CompositeAlarm -> Maybe Text
actionsSuppressedReason :: Prelude.Maybe Prelude.Text,
    -- | Actions will be suppressed if the suppressor alarm is in the @ALARM@
    -- state. @ActionsSuppressor@ can be an AlarmName or an Amazon Resource
    -- Name (ARN) from an existing alarm.
    CompositeAlarm -> Maybe Text
actionsSuppressor :: Prelude.Maybe Prelude.Text,
    -- | The maximum time in seconds that the composite alarm waits after
    -- suppressor alarm goes out of the @ALARM@ state. After this time, the
    -- composite alarm performs its actions.
    --
    -- @ExtensionPeriod@ is required only when @ActionsSuppressor@ is
    -- specified.
    CompositeAlarm -> Maybe Int
actionsSuppressorExtensionPeriod :: Prelude.Maybe Prelude.Int,
    -- | The maximum time in seconds that the composite alarm waits for the
    -- suppressor alarm to go into the @ALARM@ state. After this time, the
    -- composite alarm performs its actions.
    --
    -- @WaitPeriod@ is required only when @ActionsSuppressor@ is specified.
    CompositeAlarm -> Maybe Int
actionsSuppressorWaitPeriod :: Prelude.Maybe Prelude.Int,
    -- | The actions to execute when this alarm transitions to the ALARM state
    -- from any other state. Each action is specified as an Amazon Resource
    -- Name (ARN).
    CompositeAlarm -> Maybe [Text]
alarmActions :: Prelude.Maybe [Prelude.Text],
    -- | The Amazon Resource Name (ARN) of the alarm.
    CompositeAlarm -> Maybe Text
alarmArn :: Prelude.Maybe Prelude.Text,
    -- | The time stamp of the last update to the alarm configuration.
    CompositeAlarm -> Maybe ISO8601
alarmConfigurationUpdatedTimestamp :: Prelude.Maybe Data.ISO8601,
    -- | The description of the alarm.
    CompositeAlarm -> Maybe Text
alarmDescription :: Prelude.Maybe Prelude.Text,
    -- | The name of the alarm.
    CompositeAlarm -> Maybe Text
alarmName :: Prelude.Maybe Prelude.Text,
    -- | The rule that this alarm uses to evaluate its alarm state.
    CompositeAlarm -> Maybe Text
alarmRule :: Prelude.Maybe Prelude.Text,
    -- | The actions to execute when this alarm transitions to the
    -- INSUFFICIENT_DATA state from any other state. Each action is specified
    -- as an Amazon Resource Name (ARN).
    CompositeAlarm -> Maybe [Text]
insufficientDataActions :: Prelude.Maybe [Prelude.Text],
    -- | The actions to execute when this alarm transitions to the OK state from
    -- any other state. Each action is specified as an Amazon Resource Name
    -- (ARN).
    CompositeAlarm -> Maybe [Text]
oKActions :: Prelude.Maybe [Prelude.Text],
    -- | An explanation for the alarm state, in text format.
    CompositeAlarm -> Maybe Text
stateReason :: Prelude.Maybe Prelude.Text,
    -- | An explanation for the alarm state, in JSON format.
    CompositeAlarm -> Maybe Text
stateReasonData :: Prelude.Maybe Prelude.Text,
    -- | The timestamp of the last change to the alarm\'s @StateValue@.
    CompositeAlarm -> Maybe ISO8601
stateTransitionedTimestamp :: Prelude.Maybe Data.ISO8601,
    -- | Tracks the timestamp of any state update, even if @StateValue@ doesn\'t
    -- change.
    CompositeAlarm -> Maybe ISO8601
stateUpdatedTimestamp :: Prelude.Maybe Data.ISO8601,
    -- | The state value for the alarm.
    CompositeAlarm -> Maybe StateValue
stateValue :: Prelude.Maybe StateValue
  }
  deriving (CompositeAlarm -> CompositeAlarm -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CompositeAlarm -> CompositeAlarm -> Bool
$c/= :: CompositeAlarm -> CompositeAlarm -> Bool
== :: CompositeAlarm -> CompositeAlarm -> Bool
$c== :: CompositeAlarm -> CompositeAlarm -> Bool
Prelude.Eq, ReadPrec [CompositeAlarm]
ReadPrec CompositeAlarm
Int -> ReadS CompositeAlarm
ReadS [CompositeAlarm]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CompositeAlarm]
$creadListPrec :: ReadPrec [CompositeAlarm]
readPrec :: ReadPrec CompositeAlarm
$creadPrec :: ReadPrec CompositeAlarm
readList :: ReadS [CompositeAlarm]
$creadList :: ReadS [CompositeAlarm]
readsPrec :: Int -> ReadS CompositeAlarm
$creadsPrec :: Int -> ReadS CompositeAlarm
Prelude.Read, Int -> CompositeAlarm -> ShowS
[CompositeAlarm] -> ShowS
CompositeAlarm -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CompositeAlarm] -> ShowS
$cshowList :: [CompositeAlarm] -> ShowS
show :: CompositeAlarm -> String
$cshow :: CompositeAlarm -> String
showsPrec :: Int -> CompositeAlarm -> ShowS
$cshowsPrec :: Int -> CompositeAlarm -> ShowS
Prelude.Show, forall x. Rep CompositeAlarm x -> CompositeAlarm
forall x. CompositeAlarm -> Rep CompositeAlarm x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CompositeAlarm x -> CompositeAlarm
$cfrom :: forall x. CompositeAlarm -> Rep CompositeAlarm x
Prelude.Generic)

-- |
-- Create a value of 'CompositeAlarm' 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:
--
-- 'actionsEnabled', 'compositeAlarm_actionsEnabled' - Indicates whether actions should be executed during any changes to the
-- alarm state.
--
-- 'actionsSuppressedBy', 'compositeAlarm_actionsSuppressedBy' - When the value is @ALARM@, it means that the actions are suppressed
-- because the suppressor alarm is in @ALARM@ When the value is
-- @WaitPeriod@, it means that the actions are suppressed because the
-- composite alarm is waiting for the suppressor alarm to go into into the
-- @ALARM@ state. The maximum waiting time is as specified in
-- @ActionsSuppressorWaitPeriod@. After this time, the composite alarm
-- performs its actions. When the value is @ExtensionPeriod@, it means that
-- the actions are suppressed because the composite alarm is waiting after
-- the suppressor alarm went out of the @ALARM@ state. The maximum waiting
-- time is as specified in @ActionsSuppressorExtensionPeriod@. After this
-- time, the composite alarm performs its actions.
--
-- 'actionsSuppressedReason', 'compositeAlarm_actionsSuppressedReason' - Captures the reason for action suppression.
--
-- 'actionsSuppressor', 'compositeAlarm_actionsSuppressor' - Actions will be suppressed if the suppressor alarm is in the @ALARM@
-- state. @ActionsSuppressor@ can be an AlarmName or an Amazon Resource
-- Name (ARN) from an existing alarm.
--
-- 'actionsSuppressorExtensionPeriod', 'compositeAlarm_actionsSuppressorExtensionPeriod' - The maximum time in seconds that the composite alarm waits after
-- suppressor alarm goes out of the @ALARM@ state. After this time, the
-- composite alarm performs its actions.
--
-- @ExtensionPeriod@ is required only when @ActionsSuppressor@ is
-- specified.
--
-- 'actionsSuppressorWaitPeriod', 'compositeAlarm_actionsSuppressorWaitPeriod' - The maximum time in seconds that the composite alarm waits for the
-- suppressor alarm to go into the @ALARM@ state. After this time, the
-- composite alarm performs its actions.
--
-- @WaitPeriod@ is required only when @ActionsSuppressor@ is specified.
--
-- 'alarmActions', 'compositeAlarm_alarmActions' - The actions to execute when this alarm transitions to the ALARM state
-- from any other state. Each action is specified as an Amazon Resource
-- Name (ARN).
--
-- 'alarmArn', 'compositeAlarm_alarmArn' - The Amazon Resource Name (ARN) of the alarm.
--
-- 'alarmConfigurationUpdatedTimestamp', 'compositeAlarm_alarmConfigurationUpdatedTimestamp' - The time stamp of the last update to the alarm configuration.
--
-- 'alarmDescription', 'compositeAlarm_alarmDescription' - The description of the alarm.
--
-- 'alarmName', 'compositeAlarm_alarmName' - The name of the alarm.
--
-- 'alarmRule', 'compositeAlarm_alarmRule' - The rule that this alarm uses to evaluate its alarm state.
--
-- 'insufficientDataActions', 'compositeAlarm_insufficientDataActions' - The actions to execute when this alarm transitions to the
-- INSUFFICIENT_DATA state from any other state. Each action is specified
-- as an Amazon Resource Name (ARN).
--
-- 'oKActions', 'compositeAlarm_oKActions' - The actions to execute when this alarm transitions to the OK state from
-- any other state. Each action is specified as an Amazon Resource Name
-- (ARN).
--
-- 'stateReason', 'compositeAlarm_stateReason' - An explanation for the alarm state, in text format.
--
-- 'stateReasonData', 'compositeAlarm_stateReasonData' - An explanation for the alarm state, in JSON format.
--
-- 'stateTransitionedTimestamp', 'compositeAlarm_stateTransitionedTimestamp' - The timestamp of the last change to the alarm\'s @StateValue@.
--
-- 'stateUpdatedTimestamp', 'compositeAlarm_stateUpdatedTimestamp' - Tracks the timestamp of any state update, even if @StateValue@ doesn\'t
-- change.
--
-- 'stateValue', 'compositeAlarm_stateValue' - The state value for the alarm.
newCompositeAlarm ::
  CompositeAlarm
newCompositeAlarm :: CompositeAlarm
newCompositeAlarm =
  CompositeAlarm'
    { $sel:actionsEnabled:CompositeAlarm' :: Maybe Bool
actionsEnabled = forall a. Maybe a
Prelude.Nothing,
      $sel:actionsSuppressedBy:CompositeAlarm' :: Maybe ActionsSuppressedBy
actionsSuppressedBy = forall a. Maybe a
Prelude.Nothing,
      $sel:actionsSuppressedReason:CompositeAlarm' :: Maybe Text
actionsSuppressedReason = forall a. Maybe a
Prelude.Nothing,
      $sel:actionsSuppressor:CompositeAlarm' :: Maybe Text
actionsSuppressor = forall a. Maybe a
Prelude.Nothing,
      $sel:actionsSuppressorExtensionPeriod:CompositeAlarm' :: Maybe Int
actionsSuppressorExtensionPeriod = forall a. Maybe a
Prelude.Nothing,
      $sel:actionsSuppressorWaitPeriod:CompositeAlarm' :: Maybe Int
actionsSuppressorWaitPeriod = forall a. Maybe a
Prelude.Nothing,
      $sel:alarmActions:CompositeAlarm' :: Maybe [Text]
alarmActions = forall a. Maybe a
Prelude.Nothing,
      $sel:alarmArn:CompositeAlarm' :: Maybe Text
alarmArn = forall a. Maybe a
Prelude.Nothing,
      $sel:alarmConfigurationUpdatedTimestamp:CompositeAlarm' :: Maybe ISO8601
alarmConfigurationUpdatedTimestamp = forall a. Maybe a
Prelude.Nothing,
      $sel:alarmDescription:CompositeAlarm' :: Maybe Text
alarmDescription = forall a. Maybe a
Prelude.Nothing,
      $sel:alarmName:CompositeAlarm' :: Maybe Text
alarmName = forall a. Maybe a
Prelude.Nothing,
      $sel:alarmRule:CompositeAlarm' :: Maybe Text
alarmRule = forall a. Maybe a
Prelude.Nothing,
      $sel:insufficientDataActions:CompositeAlarm' :: Maybe [Text]
insufficientDataActions = forall a. Maybe a
Prelude.Nothing,
      $sel:oKActions:CompositeAlarm' :: Maybe [Text]
oKActions = forall a. Maybe a
Prelude.Nothing,
      $sel:stateReason:CompositeAlarm' :: Maybe Text
stateReason = forall a. Maybe a
Prelude.Nothing,
      $sel:stateReasonData:CompositeAlarm' :: Maybe Text
stateReasonData = forall a. Maybe a
Prelude.Nothing,
      $sel:stateTransitionedTimestamp:CompositeAlarm' :: Maybe ISO8601
stateTransitionedTimestamp = forall a. Maybe a
Prelude.Nothing,
      $sel:stateUpdatedTimestamp:CompositeAlarm' :: Maybe ISO8601
stateUpdatedTimestamp = forall a. Maybe a
Prelude.Nothing,
      $sel:stateValue:CompositeAlarm' :: Maybe StateValue
stateValue = forall a. Maybe a
Prelude.Nothing
    }

-- | Indicates whether actions should be executed during any changes to the
-- alarm state.
compositeAlarm_actionsEnabled :: Lens.Lens' CompositeAlarm (Prelude.Maybe Prelude.Bool)
compositeAlarm_actionsEnabled :: Lens' CompositeAlarm (Maybe Bool)
compositeAlarm_actionsEnabled = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CompositeAlarm' {Maybe Bool
actionsEnabled :: Maybe Bool
$sel:actionsEnabled:CompositeAlarm' :: CompositeAlarm -> Maybe Bool
actionsEnabled} -> Maybe Bool
actionsEnabled) (\s :: CompositeAlarm
s@CompositeAlarm' {} Maybe Bool
a -> CompositeAlarm
s {$sel:actionsEnabled:CompositeAlarm' :: Maybe Bool
actionsEnabled = Maybe Bool
a} :: CompositeAlarm)

-- | When the value is @ALARM@, it means that the actions are suppressed
-- because the suppressor alarm is in @ALARM@ When the value is
-- @WaitPeriod@, it means that the actions are suppressed because the
-- composite alarm is waiting for the suppressor alarm to go into into the
-- @ALARM@ state. The maximum waiting time is as specified in
-- @ActionsSuppressorWaitPeriod@. After this time, the composite alarm
-- performs its actions. When the value is @ExtensionPeriod@, it means that
-- the actions are suppressed because the composite alarm is waiting after
-- the suppressor alarm went out of the @ALARM@ state. The maximum waiting
-- time is as specified in @ActionsSuppressorExtensionPeriod@. After this
-- time, the composite alarm performs its actions.
compositeAlarm_actionsSuppressedBy :: Lens.Lens' CompositeAlarm (Prelude.Maybe ActionsSuppressedBy)
compositeAlarm_actionsSuppressedBy :: Lens' CompositeAlarm (Maybe ActionsSuppressedBy)
compositeAlarm_actionsSuppressedBy = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CompositeAlarm' {Maybe ActionsSuppressedBy
actionsSuppressedBy :: Maybe ActionsSuppressedBy
$sel:actionsSuppressedBy:CompositeAlarm' :: CompositeAlarm -> Maybe ActionsSuppressedBy
actionsSuppressedBy} -> Maybe ActionsSuppressedBy
actionsSuppressedBy) (\s :: CompositeAlarm
s@CompositeAlarm' {} Maybe ActionsSuppressedBy
a -> CompositeAlarm
s {$sel:actionsSuppressedBy:CompositeAlarm' :: Maybe ActionsSuppressedBy
actionsSuppressedBy = Maybe ActionsSuppressedBy
a} :: CompositeAlarm)

-- | Captures the reason for action suppression.
compositeAlarm_actionsSuppressedReason :: Lens.Lens' CompositeAlarm (Prelude.Maybe Prelude.Text)
compositeAlarm_actionsSuppressedReason :: Lens' CompositeAlarm (Maybe Text)
compositeAlarm_actionsSuppressedReason = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CompositeAlarm' {Maybe Text
actionsSuppressedReason :: Maybe Text
$sel:actionsSuppressedReason:CompositeAlarm' :: CompositeAlarm -> Maybe Text
actionsSuppressedReason} -> Maybe Text
actionsSuppressedReason) (\s :: CompositeAlarm
s@CompositeAlarm' {} Maybe Text
a -> CompositeAlarm
s {$sel:actionsSuppressedReason:CompositeAlarm' :: Maybe Text
actionsSuppressedReason = Maybe Text
a} :: CompositeAlarm)

-- | Actions will be suppressed if the suppressor alarm is in the @ALARM@
-- state. @ActionsSuppressor@ can be an AlarmName or an Amazon Resource
-- Name (ARN) from an existing alarm.
compositeAlarm_actionsSuppressor :: Lens.Lens' CompositeAlarm (Prelude.Maybe Prelude.Text)
compositeAlarm_actionsSuppressor :: Lens' CompositeAlarm (Maybe Text)
compositeAlarm_actionsSuppressor = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CompositeAlarm' {Maybe Text
actionsSuppressor :: Maybe Text
$sel:actionsSuppressor:CompositeAlarm' :: CompositeAlarm -> Maybe Text
actionsSuppressor} -> Maybe Text
actionsSuppressor) (\s :: CompositeAlarm
s@CompositeAlarm' {} Maybe Text
a -> CompositeAlarm
s {$sel:actionsSuppressor:CompositeAlarm' :: Maybe Text
actionsSuppressor = Maybe Text
a} :: CompositeAlarm)

-- | The maximum time in seconds that the composite alarm waits after
-- suppressor alarm goes out of the @ALARM@ state. After this time, the
-- composite alarm performs its actions.
--
-- @ExtensionPeriod@ is required only when @ActionsSuppressor@ is
-- specified.
compositeAlarm_actionsSuppressorExtensionPeriod :: Lens.Lens' CompositeAlarm (Prelude.Maybe Prelude.Int)
compositeAlarm_actionsSuppressorExtensionPeriod :: Lens' CompositeAlarm (Maybe Int)
compositeAlarm_actionsSuppressorExtensionPeriod = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CompositeAlarm' {Maybe Int
actionsSuppressorExtensionPeriod :: Maybe Int
$sel:actionsSuppressorExtensionPeriod:CompositeAlarm' :: CompositeAlarm -> Maybe Int
actionsSuppressorExtensionPeriod} -> Maybe Int
actionsSuppressorExtensionPeriod) (\s :: CompositeAlarm
s@CompositeAlarm' {} Maybe Int
a -> CompositeAlarm
s {$sel:actionsSuppressorExtensionPeriod:CompositeAlarm' :: Maybe Int
actionsSuppressorExtensionPeriod = Maybe Int
a} :: CompositeAlarm)

-- | The maximum time in seconds that the composite alarm waits for the
-- suppressor alarm to go into the @ALARM@ state. After this time, the
-- composite alarm performs its actions.
--
-- @WaitPeriod@ is required only when @ActionsSuppressor@ is specified.
compositeAlarm_actionsSuppressorWaitPeriod :: Lens.Lens' CompositeAlarm (Prelude.Maybe Prelude.Int)
compositeAlarm_actionsSuppressorWaitPeriod :: Lens' CompositeAlarm (Maybe Int)
compositeAlarm_actionsSuppressorWaitPeriod = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CompositeAlarm' {Maybe Int
actionsSuppressorWaitPeriod :: Maybe Int
$sel:actionsSuppressorWaitPeriod:CompositeAlarm' :: CompositeAlarm -> Maybe Int
actionsSuppressorWaitPeriod} -> Maybe Int
actionsSuppressorWaitPeriod) (\s :: CompositeAlarm
s@CompositeAlarm' {} Maybe Int
a -> CompositeAlarm
s {$sel:actionsSuppressorWaitPeriod:CompositeAlarm' :: Maybe Int
actionsSuppressorWaitPeriod = Maybe Int
a} :: CompositeAlarm)

-- | The actions to execute when this alarm transitions to the ALARM state
-- from any other state. Each action is specified as an Amazon Resource
-- Name (ARN).
compositeAlarm_alarmActions :: Lens.Lens' CompositeAlarm (Prelude.Maybe [Prelude.Text])
compositeAlarm_alarmActions :: Lens' CompositeAlarm (Maybe [Text])
compositeAlarm_alarmActions = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CompositeAlarm' {Maybe [Text]
alarmActions :: Maybe [Text]
$sel:alarmActions:CompositeAlarm' :: CompositeAlarm -> Maybe [Text]
alarmActions} -> Maybe [Text]
alarmActions) (\s :: CompositeAlarm
s@CompositeAlarm' {} Maybe [Text]
a -> CompositeAlarm
s {$sel:alarmActions:CompositeAlarm' :: Maybe [Text]
alarmActions = Maybe [Text]
a} :: CompositeAlarm) 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 Amazon Resource Name (ARN) of the alarm.
compositeAlarm_alarmArn :: Lens.Lens' CompositeAlarm (Prelude.Maybe Prelude.Text)
compositeAlarm_alarmArn :: Lens' CompositeAlarm (Maybe Text)
compositeAlarm_alarmArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CompositeAlarm' {Maybe Text
alarmArn :: Maybe Text
$sel:alarmArn:CompositeAlarm' :: CompositeAlarm -> Maybe Text
alarmArn} -> Maybe Text
alarmArn) (\s :: CompositeAlarm
s@CompositeAlarm' {} Maybe Text
a -> CompositeAlarm
s {$sel:alarmArn:CompositeAlarm' :: Maybe Text
alarmArn = Maybe Text
a} :: CompositeAlarm)

-- | The time stamp of the last update to the alarm configuration.
compositeAlarm_alarmConfigurationUpdatedTimestamp :: Lens.Lens' CompositeAlarm (Prelude.Maybe Prelude.UTCTime)
compositeAlarm_alarmConfigurationUpdatedTimestamp :: Lens' CompositeAlarm (Maybe UTCTime)
compositeAlarm_alarmConfigurationUpdatedTimestamp = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CompositeAlarm' {Maybe ISO8601
alarmConfigurationUpdatedTimestamp :: Maybe ISO8601
$sel:alarmConfigurationUpdatedTimestamp:CompositeAlarm' :: CompositeAlarm -> Maybe ISO8601
alarmConfigurationUpdatedTimestamp} -> Maybe ISO8601
alarmConfigurationUpdatedTimestamp) (\s :: CompositeAlarm
s@CompositeAlarm' {} Maybe ISO8601
a -> CompositeAlarm
s {$sel:alarmConfigurationUpdatedTimestamp:CompositeAlarm' :: Maybe ISO8601
alarmConfigurationUpdatedTimestamp = Maybe ISO8601
a} :: CompositeAlarm) 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

-- | The description of the alarm.
compositeAlarm_alarmDescription :: Lens.Lens' CompositeAlarm (Prelude.Maybe Prelude.Text)
compositeAlarm_alarmDescription :: Lens' CompositeAlarm (Maybe Text)
compositeAlarm_alarmDescription = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CompositeAlarm' {Maybe Text
alarmDescription :: Maybe Text
$sel:alarmDescription:CompositeAlarm' :: CompositeAlarm -> Maybe Text
alarmDescription} -> Maybe Text
alarmDescription) (\s :: CompositeAlarm
s@CompositeAlarm' {} Maybe Text
a -> CompositeAlarm
s {$sel:alarmDescription:CompositeAlarm' :: Maybe Text
alarmDescription = Maybe Text
a} :: CompositeAlarm)

-- | The name of the alarm.
compositeAlarm_alarmName :: Lens.Lens' CompositeAlarm (Prelude.Maybe Prelude.Text)
compositeAlarm_alarmName :: Lens' CompositeAlarm (Maybe Text)
compositeAlarm_alarmName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CompositeAlarm' {Maybe Text
alarmName :: Maybe Text
$sel:alarmName:CompositeAlarm' :: CompositeAlarm -> Maybe Text
alarmName} -> Maybe Text
alarmName) (\s :: CompositeAlarm
s@CompositeAlarm' {} Maybe Text
a -> CompositeAlarm
s {$sel:alarmName:CompositeAlarm' :: Maybe Text
alarmName = Maybe Text
a} :: CompositeAlarm)

-- | The rule that this alarm uses to evaluate its alarm state.
compositeAlarm_alarmRule :: Lens.Lens' CompositeAlarm (Prelude.Maybe Prelude.Text)
compositeAlarm_alarmRule :: Lens' CompositeAlarm (Maybe Text)
compositeAlarm_alarmRule = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CompositeAlarm' {Maybe Text
alarmRule :: Maybe Text
$sel:alarmRule:CompositeAlarm' :: CompositeAlarm -> Maybe Text
alarmRule} -> Maybe Text
alarmRule) (\s :: CompositeAlarm
s@CompositeAlarm' {} Maybe Text
a -> CompositeAlarm
s {$sel:alarmRule:CompositeAlarm' :: Maybe Text
alarmRule = Maybe Text
a} :: CompositeAlarm)

-- | The actions to execute when this alarm transitions to the
-- INSUFFICIENT_DATA state from any other state. Each action is specified
-- as an Amazon Resource Name (ARN).
compositeAlarm_insufficientDataActions :: Lens.Lens' CompositeAlarm (Prelude.Maybe [Prelude.Text])
compositeAlarm_insufficientDataActions :: Lens' CompositeAlarm (Maybe [Text])
compositeAlarm_insufficientDataActions = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CompositeAlarm' {Maybe [Text]
insufficientDataActions :: Maybe [Text]
$sel:insufficientDataActions:CompositeAlarm' :: CompositeAlarm -> Maybe [Text]
insufficientDataActions} -> Maybe [Text]
insufficientDataActions) (\s :: CompositeAlarm
s@CompositeAlarm' {} Maybe [Text]
a -> CompositeAlarm
s {$sel:insufficientDataActions:CompositeAlarm' :: Maybe [Text]
insufficientDataActions = Maybe [Text]
a} :: CompositeAlarm) 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 actions to execute when this alarm transitions to the OK state from
-- any other state. Each action is specified as an Amazon Resource Name
-- (ARN).
compositeAlarm_oKActions :: Lens.Lens' CompositeAlarm (Prelude.Maybe [Prelude.Text])
compositeAlarm_oKActions :: Lens' CompositeAlarm (Maybe [Text])
compositeAlarm_oKActions = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CompositeAlarm' {Maybe [Text]
oKActions :: Maybe [Text]
$sel:oKActions:CompositeAlarm' :: CompositeAlarm -> Maybe [Text]
oKActions} -> Maybe [Text]
oKActions) (\s :: CompositeAlarm
s@CompositeAlarm' {} Maybe [Text]
a -> CompositeAlarm
s {$sel:oKActions:CompositeAlarm' :: Maybe [Text]
oKActions = Maybe [Text]
a} :: CompositeAlarm) 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

-- | An explanation for the alarm state, in text format.
compositeAlarm_stateReason :: Lens.Lens' CompositeAlarm (Prelude.Maybe Prelude.Text)
compositeAlarm_stateReason :: Lens' CompositeAlarm (Maybe Text)
compositeAlarm_stateReason = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CompositeAlarm' {Maybe Text
stateReason :: Maybe Text
$sel:stateReason:CompositeAlarm' :: CompositeAlarm -> Maybe Text
stateReason} -> Maybe Text
stateReason) (\s :: CompositeAlarm
s@CompositeAlarm' {} Maybe Text
a -> CompositeAlarm
s {$sel:stateReason:CompositeAlarm' :: Maybe Text
stateReason = Maybe Text
a} :: CompositeAlarm)

-- | An explanation for the alarm state, in JSON format.
compositeAlarm_stateReasonData :: Lens.Lens' CompositeAlarm (Prelude.Maybe Prelude.Text)
compositeAlarm_stateReasonData :: Lens' CompositeAlarm (Maybe Text)
compositeAlarm_stateReasonData = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CompositeAlarm' {Maybe Text
stateReasonData :: Maybe Text
$sel:stateReasonData:CompositeAlarm' :: CompositeAlarm -> Maybe Text
stateReasonData} -> Maybe Text
stateReasonData) (\s :: CompositeAlarm
s@CompositeAlarm' {} Maybe Text
a -> CompositeAlarm
s {$sel:stateReasonData:CompositeAlarm' :: Maybe Text
stateReasonData = Maybe Text
a} :: CompositeAlarm)

-- | The timestamp of the last change to the alarm\'s @StateValue@.
compositeAlarm_stateTransitionedTimestamp :: Lens.Lens' CompositeAlarm (Prelude.Maybe Prelude.UTCTime)
compositeAlarm_stateTransitionedTimestamp :: Lens' CompositeAlarm (Maybe UTCTime)
compositeAlarm_stateTransitionedTimestamp = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CompositeAlarm' {Maybe ISO8601
stateTransitionedTimestamp :: Maybe ISO8601
$sel:stateTransitionedTimestamp:CompositeAlarm' :: CompositeAlarm -> Maybe ISO8601
stateTransitionedTimestamp} -> Maybe ISO8601
stateTransitionedTimestamp) (\s :: CompositeAlarm
s@CompositeAlarm' {} Maybe ISO8601
a -> CompositeAlarm
s {$sel:stateTransitionedTimestamp:CompositeAlarm' :: Maybe ISO8601
stateTransitionedTimestamp = Maybe ISO8601
a} :: CompositeAlarm) 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

-- | Tracks the timestamp of any state update, even if @StateValue@ doesn\'t
-- change.
compositeAlarm_stateUpdatedTimestamp :: Lens.Lens' CompositeAlarm (Prelude.Maybe Prelude.UTCTime)
compositeAlarm_stateUpdatedTimestamp :: Lens' CompositeAlarm (Maybe UTCTime)
compositeAlarm_stateUpdatedTimestamp = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CompositeAlarm' {Maybe ISO8601
stateUpdatedTimestamp :: Maybe ISO8601
$sel:stateUpdatedTimestamp:CompositeAlarm' :: CompositeAlarm -> Maybe ISO8601
stateUpdatedTimestamp} -> Maybe ISO8601
stateUpdatedTimestamp) (\s :: CompositeAlarm
s@CompositeAlarm' {} Maybe ISO8601
a -> CompositeAlarm
s {$sel:stateUpdatedTimestamp:CompositeAlarm' :: Maybe ISO8601
stateUpdatedTimestamp = Maybe ISO8601
a} :: CompositeAlarm) 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

-- | The state value for the alarm.
compositeAlarm_stateValue :: Lens.Lens' CompositeAlarm (Prelude.Maybe StateValue)
compositeAlarm_stateValue :: Lens' CompositeAlarm (Maybe StateValue)
compositeAlarm_stateValue = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CompositeAlarm' {Maybe StateValue
stateValue :: Maybe StateValue
$sel:stateValue:CompositeAlarm' :: CompositeAlarm -> Maybe StateValue
stateValue} -> Maybe StateValue
stateValue) (\s :: CompositeAlarm
s@CompositeAlarm' {} Maybe StateValue
a -> CompositeAlarm
s {$sel:stateValue:CompositeAlarm' :: Maybe StateValue
stateValue = Maybe StateValue
a} :: CompositeAlarm)

instance Data.FromXML CompositeAlarm where
  parseXML :: [Node] -> Either String CompositeAlarm
parseXML [Node]
x =
    Maybe Bool
-> Maybe ActionsSuppressedBy
-> Maybe Text
-> Maybe Text
-> Maybe Int
-> Maybe Int
-> Maybe [Text]
-> Maybe Text
-> Maybe ISO8601
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe [Text]
-> Maybe [Text]
-> Maybe Text
-> Maybe Text
-> Maybe ISO8601
-> Maybe ISO8601
-> Maybe StateValue
-> CompositeAlarm
CompositeAlarm'
      forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"ActionsEnabled")
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"ActionsSuppressedBy")
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"ActionsSuppressedReason")
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"ActionsSuppressor")
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"ActionsSuppressorExtensionPeriod")
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"ActionsSuppressorWaitPeriod")
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ( [Node]
x
                      forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"AlarmActions"
                      forall (f :: * -> *) a. Functor f => f (Maybe a) -> a -> f a
Core..!@ forall a. Monoid a => a
Prelude.mempty
                      forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
Prelude.>>= forall (f :: * -> *) a b.
Applicative f =>
([a] -> f b) -> [a] -> f (Maybe b)
Core.may (forall a. FromXML a => Text -> [Node] -> Either String [a]
Data.parseXMLList Text
"member")
                  )
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"AlarmArn")
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"AlarmConfigurationUpdatedTimestamp")
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"AlarmDescription")
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"AlarmName")
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"AlarmRule")
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ( [Node]
x
                      forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"InsufficientDataActions"
                      forall (f :: * -> *) a. Functor f => f (Maybe a) -> a -> f a
Core..!@ forall a. Monoid a => a
Prelude.mempty
                      forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
Prelude.>>= forall (f :: * -> *) a b.
Applicative f =>
([a] -> f b) -> [a] -> f (Maybe b)
Core.may (forall a. FromXML a => Text -> [Node] -> Either String [a]
Data.parseXMLList Text
"member")
                  )
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ( [Node]
x
                      forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"OKActions"
                      forall (f :: * -> *) a. Functor f => f (Maybe a) -> a -> f a
Core..!@ forall a. Monoid a => a
Prelude.mempty
                      forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
Prelude.>>= forall (f :: * -> *) a b.
Applicative f =>
([a] -> f b) -> [a] -> f (Maybe b)
Core.may (forall a. FromXML a => Text -> [Node] -> Either String [a]
Data.parseXMLList Text
"member")
                  )
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"StateReason")
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"StateReasonData")
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"StateTransitionedTimestamp")
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"StateUpdatedTimestamp")
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"StateValue")

instance Prelude.Hashable CompositeAlarm where
  hashWithSalt :: Int -> CompositeAlarm -> Int
hashWithSalt Int
_salt CompositeAlarm' {Maybe Bool
Maybe Int
Maybe [Text]
Maybe Text
Maybe ISO8601
Maybe ActionsSuppressedBy
Maybe StateValue
stateValue :: Maybe StateValue
stateUpdatedTimestamp :: Maybe ISO8601
stateTransitionedTimestamp :: Maybe ISO8601
stateReasonData :: Maybe Text
stateReason :: Maybe Text
oKActions :: Maybe [Text]
insufficientDataActions :: Maybe [Text]
alarmRule :: Maybe Text
alarmName :: Maybe Text
alarmDescription :: Maybe Text
alarmConfigurationUpdatedTimestamp :: Maybe ISO8601
alarmArn :: Maybe Text
alarmActions :: Maybe [Text]
actionsSuppressorWaitPeriod :: Maybe Int
actionsSuppressorExtensionPeriod :: Maybe Int
actionsSuppressor :: Maybe Text
actionsSuppressedReason :: Maybe Text
actionsSuppressedBy :: Maybe ActionsSuppressedBy
actionsEnabled :: Maybe Bool
$sel:stateValue:CompositeAlarm' :: CompositeAlarm -> Maybe StateValue
$sel:stateUpdatedTimestamp:CompositeAlarm' :: CompositeAlarm -> Maybe ISO8601
$sel:stateTransitionedTimestamp:CompositeAlarm' :: CompositeAlarm -> Maybe ISO8601
$sel:stateReasonData:CompositeAlarm' :: CompositeAlarm -> Maybe Text
$sel:stateReason:CompositeAlarm' :: CompositeAlarm -> Maybe Text
$sel:oKActions:CompositeAlarm' :: CompositeAlarm -> Maybe [Text]
$sel:insufficientDataActions:CompositeAlarm' :: CompositeAlarm -> Maybe [Text]
$sel:alarmRule:CompositeAlarm' :: CompositeAlarm -> Maybe Text
$sel:alarmName:CompositeAlarm' :: CompositeAlarm -> Maybe Text
$sel:alarmDescription:CompositeAlarm' :: CompositeAlarm -> Maybe Text
$sel:alarmConfigurationUpdatedTimestamp:CompositeAlarm' :: CompositeAlarm -> Maybe ISO8601
$sel:alarmArn:CompositeAlarm' :: CompositeAlarm -> Maybe Text
$sel:alarmActions:CompositeAlarm' :: CompositeAlarm -> Maybe [Text]
$sel:actionsSuppressorWaitPeriod:CompositeAlarm' :: CompositeAlarm -> Maybe Int
$sel:actionsSuppressorExtensionPeriod:CompositeAlarm' :: CompositeAlarm -> Maybe Int
$sel:actionsSuppressor:CompositeAlarm' :: CompositeAlarm -> Maybe Text
$sel:actionsSuppressedReason:CompositeAlarm' :: CompositeAlarm -> Maybe Text
$sel:actionsSuppressedBy:CompositeAlarm' :: CompositeAlarm -> Maybe ActionsSuppressedBy
$sel:actionsEnabled:CompositeAlarm' :: CompositeAlarm -> Maybe Bool
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
actionsEnabled
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ActionsSuppressedBy
actionsSuppressedBy
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
actionsSuppressedReason
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
actionsSuppressor
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Int
actionsSuppressorExtensionPeriod
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Int
actionsSuppressorWaitPeriod
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [Text]
alarmActions
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
alarmArn
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ISO8601
alarmConfigurationUpdatedTimestamp
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
alarmDescription
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
alarmName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
alarmRule
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [Text]
insufficientDataActions
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [Text]
oKActions
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
stateReason
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
stateReasonData
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ISO8601
stateTransitionedTimestamp
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ISO8601
stateUpdatedTimestamp
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe StateValue
stateValue

instance Prelude.NFData CompositeAlarm where
  rnf :: CompositeAlarm -> ()
rnf CompositeAlarm' {Maybe Bool
Maybe Int
Maybe [Text]
Maybe Text
Maybe ISO8601
Maybe ActionsSuppressedBy
Maybe StateValue
stateValue :: Maybe StateValue
stateUpdatedTimestamp :: Maybe ISO8601
stateTransitionedTimestamp :: Maybe ISO8601
stateReasonData :: Maybe Text
stateReason :: Maybe Text
oKActions :: Maybe [Text]
insufficientDataActions :: Maybe [Text]
alarmRule :: Maybe Text
alarmName :: Maybe Text
alarmDescription :: Maybe Text
alarmConfigurationUpdatedTimestamp :: Maybe ISO8601
alarmArn :: Maybe Text
alarmActions :: Maybe [Text]
actionsSuppressorWaitPeriod :: Maybe Int
actionsSuppressorExtensionPeriod :: Maybe Int
actionsSuppressor :: Maybe Text
actionsSuppressedReason :: Maybe Text
actionsSuppressedBy :: Maybe ActionsSuppressedBy
actionsEnabled :: Maybe Bool
$sel:stateValue:CompositeAlarm' :: CompositeAlarm -> Maybe StateValue
$sel:stateUpdatedTimestamp:CompositeAlarm' :: CompositeAlarm -> Maybe ISO8601
$sel:stateTransitionedTimestamp:CompositeAlarm' :: CompositeAlarm -> Maybe ISO8601
$sel:stateReasonData:CompositeAlarm' :: CompositeAlarm -> Maybe Text
$sel:stateReason:CompositeAlarm' :: CompositeAlarm -> Maybe Text
$sel:oKActions:CompositeAlarm' :: CompositeAlarm -> Maybe [Text]
$sel:insufficientDataActions:CompositeAlarm' :: CompositeAlarm -> Maybe [Text]
$sel:alarmRule:CompositeAlarm' :: CompositeAlarm -> Maybe Text
$sel:alarmName:CompositeAlarm' :: CompositeAlarm -> Maybe Text
$sel:alarmDescription:CompositeAlarm' :: CompositeAlarm -> Maybe Text
$sel:alarmConfigurationUpdatedTimestamp:CompositeAlarm' :: CompositeAlarm -> Maybe ISO8601
$sel:alarmArn:CompositeAlarm' :: CompositeAlarm -> Maybe Text
$sel:alarmActions:CompositeAlarm' :: CompositeAlarm -> Maybe [Text]
$sel:actionsSuppressorWaitPeriod:CompositeAlarm' :: CompositeAlarm -> Maybe Int
$sel:actionsSuppressorExtensionPeriod:CompositeAlarm' :: CompositeAlarm -> Maybe Int
$sel:actionsSuppressor:CompositeAlarm' :: CompositeAlarm -> Maybe Text
$sel:actionsSuppressedReason:CompositeAlarm' :: CompositeAlarm -> Maybe Text
$sel:actionsSuppressedBy:CompositeAlarm' :: CompositeAlarm -> Maybe ActionsSuppressedBy
$sel:actionsEnabled:CompositeAlarm' :: CompositeAlarm -> Maybe Bool
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Bool
actionsEnabled
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ActionsSuppressedBy
actionsSuppressedBy
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
actionsSuppressedReason
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
actionsSuppressor
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Int
actionsSuppressorExtensionPeriod
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Int
actionsSuppressorWaitPeriod
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [Text]
alarmActions
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
alarmArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ISO8601
alarmConfigurationUpdatedTimestamp
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
alarmDescription
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
alarmName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
alarmRule
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [Text]
insufficientDataActions
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [Text]
oKActions
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
stateReason
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
stateReasonData
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Maybe ISO8601
stateTransitionedTimestamp
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ISO8601
stateUpdatedTimestamp
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe StateValue
stateValue