{-# 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.SSM.Types.AutomationExecutionMetadata
-- 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.SSM.Types.AutomationExecutionMetadata 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.SSM.Types.AlarmConfiguration
import Amazonka.SSM.Types.AlarmStateInformation
import Amazonka.SSM.Types.AutomationExecutionStatus
import Amazonka.SSM.Types.AutomationSubtype
import Amazonka.SSM.Types.AutomationType
import Amazonka.SSM.Types.ExecutionMode
import Amazonka.SSM.Types.ResolvedTargets
import Amazonka.SSM.Types.Runbook
import Amazonka.SSM.Types.Target

-- | Details about a specific Automation execution.
--
-- /See:/ 'newAutomationExecutionMetadata' smart constructor.
data AutomationExecutionMetadata = AutomationExecutionMetadata'
  { -- | The details for the CloudWatch alarm applied to your automation.
    AutomationExecutionMetadata -> Maybe AlarmConfiguration
alarmConfiguration :: Prelude.Maybe AlarmConfiguration,
    -- | The ID of a State Manager association used in the Automation operation.
    AutomationExecutionMetadata -> Maybe Text
associationId :: Prelude.Maybe Prelude.Text,
    -- | The execution ID.
    AutomationExecutionMetadata -> Maybe Text
automationExecutionId :: Prelude.Maybe Prelude.Text,
    -- | The status of the execution.
    AutomationExecutionMetadata -> Maybe AutomationExecutionStatus
automationExecutionStatus :: Prelude.Maybe AutomationExecutionStatus,
    -- | The subtype of the Automation operation. Currently, the only supported
    -- value is @ChangeRequest@.
    AutomationExecutionMetadata -> Maybe AutomationSubtype
automationSubtype :: Prelude.Maybe AutomationSubtype,
    -- | Use this filter with DescribeAutomationExecutions. Specify either Local
    -- or CrossAccount. CrossAccount is an Automation that runs in multiple
    -- Amazon Web Services Regions and Amazon Web Services accounts. For more
    -- information, see
    -- <https://docs.aws.amazon.com/systems-manager/latest/userguide/systems-manager-automation-multiple-accounts-and-regions.html Running Automation workflows in multiple Amazon Web Services Regions and accounts>
    -- in the /Amazon Web Services Systems Manager User Guide/.
    AutomationExecutionMetadata -> Maybe AutomationType
automationType :: Prelude.Maybe AutomationType,
    -- | The name of the Change Manager change request.
    AutomationExecutionMetadata -> Maybe Text
changeRequestName :: Prelude.Maybe Prelude.Text,
    -- | The action of the step that is currently running.
    AutomationExecutionMetadata -> Maybe Text
currentAction :: Prelude.Maybe Prelude.Text,
    -- | The name of the step that is currently running.
    AutomationExecutionMetadata -> Maybe Text
currentStepName :: Prelude.Maybe Prelude.Text,
    -- | The name of the Automation runbook used during execution.
    AutomationExecutionMetadata -> Maybe Text
documentName :: Prelude.Maybe Prelude.Text,
    -- | The document version used during the execution.
    AutomationExecutionMetadata -> Maybe Text
documentVersion :: Prelude.Maybe Prelude.Text,
    -- | The IAM role ARN of the user who ran the automation.
    AutomationExecutionMetadata -> Maybe Text
executedBy :: Prelude.Maybe Prelude.Text,
    -- | The time the execution finished. This isn\'t populated if the execution
    -- is still in progress.
    AutomationExecutionMetadata -> Maybe POSIX
executionEndTime :: Prelude.Maybe Data.POSIX,
    -- | The time the execution started.
    AutomationExecutionMetadata -> Maybe POSIX
executionStartTime :: Prelude.Maybe Data.POSIX,
    -- | The list of execution outputs as defined in the Automation runbook.
    AutomationExecutionMetadata -> Maybe Text
failureMessage :: Prelude.Maybe Prelude.Text,
    -- | An S3 bucket where execution information is stored.
    AutomationExecutionMetadata -> Maybe Text
logFile :: Prelude.Maybe Prelude.Text,
    -- | The @MaxConcurrency@ value specified by the user when starting the
    -- automation.
    AutomationExecutionMetadata -> Maybe Text
maxConcurrency :: Prelude.Maybe Prelude.Text,
    -- | The @MaxErrors@ value specified by the user when starting the
    -- automation.
    AutomationExecutionMetadata -> Maybe Text
maxErrors :: Prelude.Maybe Prelude.Text,
    -- | The Automation execution mode.
    AutomationExecutionMetadata -> Maybe ExecutionMode
mode :: Prelude.Maybe ExecutionMode,
    -- | The ID of an OpsItem that is created to represent a Change Manager
    -- change request.
    AutomationExecutionMetadata -> Maybe Text
opsItemId :: Prelude.Maybe Prelude.Text,
    -- | The list of execution outputs as defined in the Automation runbook.
    AutomationExecutionMetadata -> Maybe (HashMap Text [Text])
outputs :: Prelude.Maybe (Prelude.HashMap Prelude.Text [Prelude.Text]),
    -- | The execution ID of the parent automation.
    AutomationExecutionMetadata -> Maybe Text
parentAutomationExecutionId :: Prelude.Maybe Prelude.Text,
    -- | A list of targets that resolved during the execution.
    AutomationExecutionMetadata -> Maybe ResolvedTargets
resolvedTargets :: Prelude.Maybe ResolvedTargets,
    -- | Information about the Automation runbooks that are run during a runbook
    -- workflow in Change Manager.
    --
    -- The Automation runbooks specified for the runbook workflow can\'t run
    -- until all required approvals for the change request have been received.
    AutomationExecutionMetadata -> Maybe (NonEmpty Runbook)
runbooks :: Prelude.Maybe (Prelude.NonEmpty Runbook),
    -- | The date and time the Automation operation is scheduled to start.
    AutomationExecutionMetadata -> Maybe POSIX
scheduledTime :: Prelude.Maybe Data.POSIX,
    -- | The list of execution outputs as defined in the Automation runbook.
    AutomationExecutionMetadata -> Maybe Text
target :: Prelude.Maybe Prelude.Text,
    -- | The specified key-value mapping of document parameters to target
    -- resources.
    AutomationExecutionMetadata -> Maybe [HashMap Text [Text]]
targetMaps :: Prelude.Maybe [Prelude.HashMap Prelude.Text [Prelude.Text]],
    -- | The list of execution outputs as defined in the Automation runbook.
    AutomationExecutionMetadata -> Maybe Text
targetParameterName :: Prelude.Maybe Prelude.Text,
    -- | The targets defined by the user when starting the automation.
    AutomationExecutionMetadata -> Maybe [Target]
targets :: Prelude.Maybe [Target],
    -- | The CloudWatch alarm that was invoked by the automation.
    AutomationExecutionMetadata
-> Maybe (NonEmpty AlarmStateInformation)
triggeredAlarms :: Prelude.Maybe (Prelude.NonEmpty AlarmStateInformation)
  }
  deriving (AutomationExecutionMetadata -> AutomationExecutionMetadata -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AutomationExecutionMetadata -> AutomationExecutionMetadata -> Bool
$c/= :: AutomationExecutionMetadata -> AutomationExecutionMetadata -> Bool
== :: AutomationExecutionMetadata -> AutomationExecutionMetadata -> Bool
$c== :: AutomationExecutionMetadata -> AutomationExecutionMetadata -> Bool
Prelude.Eq, ReadPrec [AutomationExecutionMetadata]
ReadPrec AutomationExecutionMetadata
Int -> ReadS AutomationExecutionMetadata
ReadS [AutomationExecutionMetadata]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [AutomationExecutionMetadata]
$creadListPrec :: ReadPrec [AutomationExecutionMetadata]
readPrec :: ReadPrec AutomationExecutionMetadata
$creadPrec :: ReadPrec AutomationExecutionMetadata
readList :: ReadS [AutomationExecutionMetadata]
$creadList :: ReadS [AutomationExecutionMetadata]
readsPrec :: Int -> ReadS AutomationExecutionMetadata
$creadsPrec :: Int -> ReadS AutomationExecutionMetadata
Prelude.Read, Int -> AutomationExecutionMetadata -> ShowS
[AutomationExecutionMetadata] -> ShowS
AutomationExecutionMetadata -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [AutomationExecutionMetadata] -> ShowS
$cshowList :: [AutomationExecutionMetadata] -> ShowS
show :: AutomationExecutionMetadata -> String
$cshow :: AutomationExecutionMetadata -> String
showsPrec :: Int -> AutomationExecutionMetadata -> ShowS
$cshowsPrec :: Int -> AutomationExecutionMetadata -> ShowS
Prelude.Show, forall x.
Rep AutomationExecutionMetadata x -> AutomationExecutionMetadata
forall x.
AutomationExecutionMetadata -> Rep AutomationExecutionMetadata x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep AutomationExecutionMetadata x -> AutomationExecutionMetadata
$cfrom :: forall x.
AutomationExecutionMetadata -> Rep AutomationExecutionMetadata x
Prelude.Generic)

-- |
-- Create a value of 'AutomationExecutionMetadata' 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:
--
-- 'alarmConfiguration', 'automationExecutionMetadata_alarmConfiguration' - The details for the CloudWatch alarm applied to your automation.
--
-- 'associationId', 'automationExecutionMetadata_associationId' - The ID of a State Manager association used in the Automation operation.
--
-- 'automationExecutionId', 'automationExecutionMetadata_automationExecutionId' - The execution ID.
--
-- 'automationExecutionStatus', 'automationExecutionMetadata_automationExecutionStatus' - The status of the execution.
--
-- 'automationSubtype', 'automationExecutionMetadata_automationSubtype' - The subtype of the Automation operation. Currently, the only supported
-- value is @ChangeRequest@.
--
-- 'automationType', 'automationExecutionMetadata_automationType' - Use this filter with DescribeAutomationExecutions. Specify either Local
-- or CrossAccount. CrossAccount is an Automation that runs in multiple
-- Amazon Web Services Regions and Amazon Web Services accounts. For more
-- information, see
-- <https://docs.aws.amazon.com/systems-manager/latest/userguide/systems-manager-automation-multiple-accounts-and-regions.html Running Automation workflows in multiple Amazon Web Services Regions and accounts>
-- in the /Amazon Web Services Systems Manager User Guide/.
--
-- 'changeRequestName', 'automationExecutionMetadata_changeRequestName' - The name of the Change Manager change request.
--
-- 'currentAction', 'automationExecutionMetadata_currentAction' - The action of the step that is currently running.
--
-- 'currentStepName', 'automationExecutionMetadata_currentStepName' - The name of the step that is currently running.
--
-- 'documentName', 'automationExecutionMetadata_documentName' - The name of the Automation runbook used during execution.
--
-- 'documentVersion', 'automationExecutionMetadata_documentVersion' - The document version used during the execution.
--
-- 'executedBy', 'automationExecutionMetadata_executedBy' - The IAM role ARN of the user who ran the automation.
--
-- 'executionEndTime', 'automationExecutionMetadata_executionEndTime' - The time the execution finished. This isn\'t populated if the execution
-- is still in progress.
--
-- 'executionStartTime', 'automationExecutionMetadata_executionStartTime' - The time the execution started.
--
-- 'failureMessage', 'automationExecutionMetadata_failureMessage' - The list of execution outputs as defined in the Automation runbook.
--
-- 'logFile', 'automationExecutionMetadata_logFile' - An S3 bucket where execution information is stored.
--
-- 'maxConcurrency', 'automationExecutionMetadata_maxConcurrency' - The @MaxConcurrency@ value specified by the user when starting the
-- automation.
--
-- 'maxErrors', 'automationExecutionMetadata_maxErrors' - The @MaxErrors@ value specified by the user when starting the
-- automation.
--
-- 'mode', 'automationExecutionMetadata_mode' - The Automation execution mode.
--
-- 'opsItemId', 'automationExecutionMetadata_opsItemId' - The ID of an OpsItem that is created to represent a Change Manager
-- change request.
--
-- 'outputs', 'automationExecutionMetadata_outputs' - The list of execution outputs as defined in the Automation runbook.
--
-- 'parentAutomationExecutionId', 'automationExecutionMetadata_parentAutomationExecutionId' - The execution ID of the parent automation.
--
-- 'resolvedTargets', 'automationExecutionMetadata_resolvedTargets' - A list of targets that resolved during the execution.
--
-- 'runbooks', 'automationExecutionMetadata_runbooks' - Information about the Automation runbooks that are run during a runbook
-- workflow in Change Manager.
--
-- The Automation runbooks specified for the runbook workflow can\'t run
-- until all required approvals for the change request have been received.
--
-- 'scheduledTime', 'automationExecutionMetadata_scheduledTime' - The date and time the Automation operation is scheduled to start.
--
-- 'target', 'automationExecutionMetadata_target' - The list of execution outputs as defined in the Automation runbook.
--
-- 'targetMaps', 'automationExecutionMetadata_targetMaps' - The specified key-value mapping of document parameters to target
-- resources.
--
-- 'targetParameterName', 'automationExecutionMetadata_targetParameterName' - The list of execution outputs as defined in the Automation runbook.
--
-- 'targets', 'automationExecutionMetadata_targets' - The targets defined by the user when starting the automation.
--
-- 'triggeredAlarms', 'automationExecutionMetadata_triggeredAlarms' - The CloudWatch alarm that was invoked by the automation.
newAutomationExecutionMetadata ::
  AutomationExecutionMetadata
newAutomationExecutionMetadata :: AutomationExecutionMetadata
newAutomationExecutionMetadata =
  AutomationExecutionMetadata'
    { $sel:alarmConfiguration:AutomationExecutionMetadata' :: Maybe AlarmConfiguration
alarmConfiguration =
        forall a. Maybe a
Prelude.Nothing,
      $sel:associationId:AutomationExecutionMetadata' :: Maybe Text
associationId = forall a. Maybe a
Prelude.Nothing,
      $sel:automationExecutionId:AutomationExecutionMetadata' :: Maybe Text
automationExecutionId = forall a. Maybe a
Prelude.Nothing,
      $sel:automationExecutionStatus:AutomationExecutionMetadata' :: Maybe AutomationExecutionStatus
automationExecutionStatus = forall a. Maybe a
Prelude.Nothing,
      $sel:automationSubtype:AutomationExecutionMetadata' :: Maybe AutomationSubtype
automationSubtype = forall a. Maybe a
Prelude.Nothing,
      $sel:automationType:AutomationExecutionMetadata' :: Maybe AutomationType
automationType = forall a. Maybe a
Prelude.Nothing,
      $sel:changeRequestName:AutomationExecutionMetadata' :: Maybe Text
changeRequestName = forall a. Maybe a
Prelude.Nothing,
      $sel:currentAction:AutomationExecutionMetadata' :: Maybe Text
currentAction = forall a. Maybe a
Prelude.Nothing,
      $sel:currentStepName:AutomationExecutionMetadata' :: Maybe Text
currentStepName = forall a. Maybe a
Prelude.Nothing,
      $sel:documentName:AutomationExecutionMetadata' :: Maybe Text
documentName = forall a. Maybe a
Prelude.Nothing,
      $sel:documentVersion:AutomationExecutionMetadata' :: Maybe Text
documentVersion = forall a. Maybe a
Prelude.Nothing,
      $sel:executedBy:AutomationExecutionMetadata' :: Maybe Text
executedBy = forall a. Maybe a
Prelude.Nothing,
      $sel:executionEndTime:AutomationExecutionMetadata' :: Maybe POSIX
executionEndTime = forall a. Maybe a
Prelude.Nothing,
      $sel:executionStartTime:AutomationExecutionMetadata' :: Maybe POSIX
executionStartTime = forall a. Maybe a
Prelude.Nothing,
      $sel:failureMessage:AutomationExecutionMetadata' :: Maybe Text
failureMessage = forall a. Maybe a
Prelude.Nothing,
      $sel:logFile:AutomationExecutionMetadata' :: Maybe Text
logFile = forall a. Maybe a
Prelude.Nothing,
      $sel:maxConcurrency:AutomationExecutionMetadata' :: Maybe Text
maxConcurrency = forall a. Maybe a
Prelude.Nothing,
      $sel:maxErrors:AutomationExecutionMetadata' :: Maybe Text
maxErrors = forall a. Maybe a
Prelude.Nothing,
      $sel:mode:AutomationExecutionMetadata' :: Maybe ExecutionMode
mode = forall a. Maybe a
Prelude.Nothing,
      $sel:opsItemId:AutomationExecutionMetadata' :: Maybe Text
opsItemId = forall a. Maybe a
Prelude.Nothing,
      $sel:outputs:AutomationExecutionMetadata' :: Maybe (HashMap Text [Text])
outputs = forall a. Maybe a
Prelude.Nothing,
      $sel:parentAutomationExecutionId:AutomationExecutionMetadata' :: Maybe Text
parentAutomationExecutionId = forall a. Maybe a
Prelude.Nothing,
      $sel:resolvedTargets:AutomationExecutionMetadata' :: Maybe ResolvedTargets
resolvedTargets = forall a. Maybe a
Prelude.Nothing,
      $sel:runbooks:AutomationExecutionMetadata' :: Maybe (NonEmpty Runbook)
runbooks = forall a. Maybe a
Prelude.Nothing,
      $sel:scheduledTime:AutomationExecutionMetadata' :: Maybe POSIX
scheduledTime = forall a. Maybe a
Prelude.Nothing,
      $sel:target:AutomationExecutionMetadata' :: Maybe Text
target = forall a. Maybe a
Prelude.Nothing,
      $sel:targetMaps:AutomationExecutionMetadata' :: Maybe [HashMap Text [Text]]
targetMaps = forall a. Maybe a
Prelude.Nothing,
      $sel:targetParameterName:AutomationExecutionMetadata' :: Maybe Text
targetParameterName = forall a. Maybe a
Prelude.Nothing,
      $sel:targets:AutomationExecutionMetadata' :: Maybe [Target]
targets = forall a. Maybe a
Prelude.Nothing,
      $sel:triggeredAlarms:AutomationExecutionMetadata' :: Maybe (NonEmpty AlarmStateInformation)
triggeredAlarms = forall a. Maybe a
Prelude.Nothing
    }

-- | The details for the CloudWatch alarm applied to your automation.
automationExecutionMetadata_alarmConfiguration :: Lens.Lens' AutomationExecutionMetadata (Prelude.Maybe AlarmConfiguration)
automationExecutionMetadata_alarmConfiguration :: Lens' AutomationExecutionMetadata (Maybe AlarmConfiguration)
automationExecutionMetadata_alarmConfiguration = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AutomationExecutionMetadata' {Maybe AlarmConfiguration
alarmConfiguration :: Maybe AlarmConfiguration
$sel:alarmConfiguration:AutomationExecutionMetadata' :: AutomationExecutionMetadata -> Maybe AlarmConfiguration
alarmConfiguration} -> Maybe AlarmConfiguration
alarmConfiguration) (\s :: AutomationExecutionMetadata
s@AutomationExecutionMetadata' {} Maybe AlarmConfiguration
a -> AutomationExecutionMetadata
s {$sel:alarmConfiguration:AutomationExecutionMetadata' :: Maybe AlarmConfiguration
alarmConfiguration = Maybe AlarmConfiguration
a} :: AutomationExecutionMetadata)

-- | The ID of a State Manager association used in the Automation operation.
automationExecutionMetadata_associationId :: Lens.Lens' AutomationExecutionMetadata (Prelude.Maybe Prelude.Text)
automationExecutionMetadata_associationId :: Lens' AutomationExecutionMetadata (Maybe Text)
automationExecutionMetadata_associationId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AutomationExecutionMetadata' {Maybe Text
associationId :: Maybe Text
$sel:associationId:AutomationExecutionMetadata' :: AutomationExecutionMetadata -> Maybe Text
associationId} -> Maybe Text
associationId) (\s :: AutomationExecutionMetadata
s@AutomationExecutionMetadata' {} Maybe Text
a -> AutomationExecutionMetadata
s {$sel:associationId:AutomationExecutionMetadata' :: Maybe Text
associationId = Maybe Text
a} :: AutomationExecutionMetadata)

-- | The execution ID.
automationExecutionMetadata_automationExecutionId :: Lens.Lens' AutomationExecutionMetadata (Prelude.Maybe Prelude.Text)
automationExecutionMetadata_automationExecutionId :: Lens' AutomationExecutionMetadata (Maybe Text)
automationExecutionMetadata_automationExecutionId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AutomationExecutionMetadata' {Maybe Text
automationExecutionId :: Maybe Text
$sel:automationExecutionId:AutomationExecutionMetadata' :: AutomationExecutionMetadata -> Maybe Text
automationExecutionId} -> Maybe Text
automationExecutionId) (\s :: AutomationExecutionMetadata
s@AutomationExecutionMetadata' {} Maybe Text
a -> AutomationExecutionMetadata
s {$sel:automationExecutionId:AutomationExecutionMetadata' :: Maybe Text
automationExecutionId = Maybe Text
a} :: AutomationExecutionMetadata)

-- | The status of the execution.
automationExecutionMetadata_automationExecutionStatus :: Lens.Lens' AutomationExecutionMetadata (Prelude.Maybe AutomationExecutionStatus)
automationExecutionMetadata_automationExecutionStatus :: Lens' AutomationExecutionMetadata (Maybe AutomationExecutionStatus)
automationExecutionMetadata_automationExecutionStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AutomationExecutionMetadata' {Maybe AutomationExecutionStatus
automationExecutionStatus :: Maybe AutomationExecutionStatus
$sel:automationExecutionStatus:AutomationExecutionMetadata' :: AutomationExecutionMetadata -> Maybe AutomationExecutionStatus
automationExecutionStatus} -> Maybe AutomationExecutionStatus
automationExecutionStatus) (\s :: AutomationExecutionMetadata
s@AutomationExecutionMetadata' {} Maybe AutomationExecutionStatus
a -> AutomationExecutionMetadata
s {$sel:automationExecutionStatus:AutomationExecutionMetadata' :: Maybe AutomationExecutionStatus
automationExecutionStatus = Maybe AutomationExecutionStatus
a} :: AutomationExecutionMetadata)

-- | The subtype of the Automation operation. Currently, the only supported
-- value is @ChangeRequest@.
automationExecutionMetadata_automationSubtype :: Lens.Lens' AutomationExecutionMetadata (Prelude.Maybe AutomationSubtype)
automationExecutionMetadata_automationSubtype :: Lens' AutomationExecutionMetadata (Maybe AutomationSubtype)
automationExecutionMetadata_automationSubtype = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AutomationExecutionMetadata' {Maybe AutomationSubtype
automationSubtype :: Maybe AutomationSubtype
$sel:automationSubtype:AutomationExecutionMetadata' :: AutomationExecutionMetadata -> Maybe AutomationSubtype
automationSubtype} -> Maybe AutomationSubtype
automationSubtype) (\s :: AutomationExecutionMetadata
s@AutomationExecutionMetadata' {} Maybe AutomationSubtype
a -> AutomationExecutionMetadata
s {$sel:automationSubtype:AutomationExecutionMetadata' :: Maybe AutomationSubtype
automationSubtype = Maybe AutomationSubtype
a} :: AutomationExecutionMetadata)

-- | Use this filter with DescribeAutomationExecutions. Specify either Local
-- or CrossAccount. CrossAccount is an Automation that runs in multiple
-- Amazon Web Services Regions and Amazon Web Services accounts. For more
-- information, see
-- <https://docs.aws.amazon.com/systems-manager/latest/userguide/systems-manager-automation-multiple-accounts-and-regions.html Running Automation workflows in multiple Amazon Web Services Regions and accounts>
-- in the /Amazon Web Services Systems Manager User Guide/.
automationExecutionMetadata_automationType :: Lens.Lens' AutomationExecutionMetadata (Prelude.Maybe AutomationType)
automationExecutionMetadata_automationType :: Lens' AutomationExecutionMetadata (Maybe AutomationType)
automationExecutionMetadata_automationType = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AutomationExecutionMetadata' {Maybe AutomationType
automationType :: Maybe AutomationType
$sel:automationType:AutomationExecutionMetadata' :: AutomationExecutionMetadata -> Maybe AutomationType
automationType} -> Maybe AutomationType
automationType) (\s :: AutomationExecutionMetadata
s@AutomationExecutionMetadata' {} Maybe AutomationType
a -> AutomationExecutionMetadata
s {$sel:automationType:AutomationExecutionMetadata' :: Maybe AutomationType
automationType = Maybe AutomationType
a} :: AutomationExecutionMetadata)

-- | The name of the Change Manager change request.
automationExecutionMetadata_changeRequestName :: Lens.Lens' AutomationExecutionMetadata (Prelude.Maybe Prelude.Text)
automationExecutionMetadata_changeRequestName :: Lens' AutomationExecutionMetadata (Maybe Text)
automationExecutionMetadata_changeRequestName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AutomationExecutionMetadata' {Maybe Text
changeRequestName :: Maybe Text
$sel:changeRequestName:AutomationExecutionMetadata' :: AutomationExecutionMetadata -> Maybe Text
changeRequestName} -> Maybe Text
changeRequestName) (\s :: AutomationExecutionMetadata
s@AutomationExecutionMetadata' {} Maybe Text
a -> AutomationExecutionMetadata
s {$sel:changeRequestName:AutomationExecutionMetadata' :: Maybe Text
changeRequestName = Maybe Text
a} :: AutomationExecutionMetadata)

-- | The action of the step that is currently running.
automationExecutionMetadata_currentAction :: Lens.Lens' AutomationExecutionMetadata (Prelude.Maybe Prelude.Text)
automationExecutionMetadata_currentAction :: Lens' AutomationExecutionMetadata (Maybe Text)
automationExecutionMetadata_currentAction = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AutomationExecutionMetadata' {Maybe Text
currentAction :: Maybe Text
$sel:currentAction:AutomationExecutionMetadata' :: AutomationExecutionMetadata -> Maybe Text
currentAction} -> Maybe Text
currentAction) (\s :: AutomationExecutionMetadata
s@AutomationExecutionMetadata' {} Maybe Text
a -> AutomationExecutionMetadata
s {$sel:currentAction:AutomationExecutionMetadata' :: Maybe Text
currentAction = Maybe Text
a} :: AutomationExecutionMetadata)

-- | The name of the step that is currently running.
automationExecutionMetadata_currentStepName :: Lens.Lens' AutomationExecutionMetadata (Prelude.Maybe Prelude.Text)
automationExecutionMetadata_currentStepName :: Lens' AutomationExecutionMetadata (Maybe Text)
automationExecutionMetadata_currentStepName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AutomationExecutionMetadata' {Maybe Text
currentStepName :: Maybe Text
$sel:currentStepName:AutomationExecutionMetadata' :: AutomationExecutionMetadata -> Maybe Text
currentStepName} -> Maybe Text
currentStepName) (\s :: AutomationExecutionMetadata
s@AutomationExecutionMetadata' {} Maybe Text
a -> AutomationExecutionMetadata
s {$sel:currentStepName:AutomationExecutionMetadata' :: Maybe Text
currentStepName = Maybe Text
a} :: AutomationExecutionMetadata)

-- | The name of the Automation runbook used during execution.
automationExecutionMetadata_documentName :: Lens.Lens' AutomationExecutionMetadata (Prelude.Maybe Prelude.Text)
automationExecutionMetadata_documentName :: Lens' AutomationExecutionMetadata (Maybe Text)
automationExecutionMetadata_documentName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AutomationExecutionMetadata' {Maybe Text
documentName :: Maybe Text
$sel:documentName:AutomationExecutionMetadata' :: AutomationExecutionMetadata -> Maybe Text
documentName} -> Maybe Text
documentName) (\s :: AutomationExecutionMetadata
s@AutomationExecutionMetadata' {} Maybe Text
a -> AutomationExecutionMetadata
s {$sel:documentName:AutomationExecutionMetadata' :: Maybe Text
documentName = Maybe Text
a} :: AutomationExecutionMetadata)

-- | The document version used during the execution.
automationExecutionMetadata_documentVersion :: Lens.Lens' AutomationExecutionMetadata (Prelude.Maybe Prelude.Text)
automationExecutionMetadata_documentVersion :: Lens' AutomationExecutionMetadata (Maybe Text)
automationExecutionMetadata_documentVersion = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AutomationExecutionMetadata' {Maybe Text
documentVersion :: Maybe Text
$sel:documentVersion:AutomationExecutionMetadata' :: AutomationExecutionMetadata -> Maybe Text
documentVersion} -> Maybe Text
documentVersion) (\s :: AutomationExecutionMetadata
s@AutomationExecutionMetadata' {} Maybe Text
a -> AutomationExecutionMetadata
s {$sel:documentVersion:AutomationExecutionMetadata' :: Maybe Text
documentVersion = Maybe Text
a} :: AutomationExecutionMetadata)

-- | The IAM role ARN of the user who ran the automation.
automationExecutionMetadata_executedBy :: Lens.Lens' AutomationExecutionMetadata (Prelude.Maybe Prelude.Text)
automationExecutionMetadata_executedBy :: Lens' AutomationExecutionMetadata (Maybe Text)
automationExecutionMetadata_executedBy = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AutomationExecutionMetadata' {Maybe Text
executedBy :: Maybe Text
$sel:executedBy:AutomationExecutionMetadata' :: AutomationExecutionMetadata -> Maybe Text
executedBy} -> Maybe Text
executedBy) (\s :: AutomationExecutionMetadata
s@AutomationExecutionMetadata' {} Maybe Text
a -> AutomationExecutionMetadata
s {$sel:executedBy:AutomationExecutionMetadata' :: Maybe Text
executedBy = Maybe Text
a} :: AutomationExecutionMetadata)

-- | The time the execution finished. This isn\'t populated if the execution
-- is still in progress.
automationExecutionMetadata_executionEndTime :: Lens.Lens' AutomationExecutionMetadata (Prelude.Maybe Prelude.UTCTime)
automationExecutionMetadata_executionEndTime :: Lens' AutomationExecutionMetadata (Maybe UTCTime)
automationExecutionMetadata_executionEndTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AutomationExecutionMetadata' {Maybe POSIX
executionEndTime :: Maybe POSIX
$sel:executionEndTime:AutomationExecutionMetadata' :: AutomationExecutionMetadata -> Maybe POSIX
executionEndTime} -> Maybe POSIX
executionEndTime) (\s :: AutomationExecutionMetadata
s@AutomationExecutionMetadata' {} Maybe POSIX
a -> AutomationExecutionMetadata
s {$sel:executionEndTime:AutomationExecutionMetadata' :: Maybe POSIX
executionEndTime = Maybe POSIX
a} :: AutomationExecutionMetadata) 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 time the execution started.
automationExecutionMetadata_executionStartTime :: Lens.Lens' AutomationExecutionMetadata (Prelude.Maybe Prelude.UTCTime)
automationExecutionMetadata_executionStartTime :: Lens' AutomationExecutionMetadata (Maybe UTCTime)
automationExecutionMetadata_executionStartTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AutomationExecutionMetadata' {Maybe POSIX
executionStartTime :: Maybe POSIX
$sel:executionStartTime:AutomationExecutionMetadata' :: AutomationExecutionMetadata -> Maybe POSIX
executionStartTime} -> Maybe POSIX
executionStartTime) (\s :: AutomationExecutionMetadata
s@AutomationExecutionMetadata' {} Maybe POSIX
a -> AutomationExecutionMetadata
s {$sel:executionStartTime:AutomationExecutionMetadata' :: Maybe POSIX
executionStartTime = Maybe POSIX
a} :: AutomationExecutionMetadata) 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 list of execution outputs as defined in the Automation runbook.
automationExecutionMetadata_failureMessage :: Lens.Lens' AutomationExecutionMetadata (Prelude.Maybe Prelude.Text)
automationExecutionMetadata_failureMessage :: Lens' AutomationExecutionMetadata (Maybe Text)
automationExecutionMetadata_failureMessage = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AutomationExecutionMetadata' {Maybe Text
failureMessage :: Maybe Text
$sel:failureMessage:AutomationExecutionMetadata' :: AutomationExecutionMetadata -> Maybe Text
failureMessage} -> Maybe Text
failureMessage) (\s :: AutomationExecutionMetadata
s@AutomationExecutionMetadata' {} Maybe Text
a -> AutomationExecutionMetadata
s {$sel:failureMessage:AutomationExecutionMetadata' :: Maybe Text
failureMessage = Maybe Text
a} :: AutomationExecutionMetadata)

-- | An S3 bucket where execution information is stored.
automationExecutionMetadata_logFile :: Lens.Lens' AutomationExecutionMetadata (Prelude.Maybe Prelude.Text)
automationExecutionMetadata_logFile :: Lens' AutomationExecutionMetadata (Maybe Text)
automationExecutionMetadata_logFile = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AutomationExecutionMetadata' {Maybe Text
logFile :: Maybe Text
$sel:logFile:AutomationExecutionMetadata' :: AutomationExecutionMetadata -> Maybe Text
logFile} -> Maybe Text
logFile) (\s :: AutomationExecutionMetadata
s@AutomationExecutionMetadata' {} Maybe Text
a -> AutomationExecutionMetadata
s {$sel:logFile:AutomationExecutionMetadata' :: Maybe Text
logFile = Maybe Text
a} :: AutomationExecutionMetadata)

-- | The @MaxConcurrency@ value specified by the user when starting the
-- automation.
automationExecutionMetadata_maxConcurrency :: Lens.Lens' AutomationExecutionMetadata (Prelude.Maybe Prelude.Text)
automationExecutionMetadata_maxConcurrency :: Lens' AutomationExecutionMetadata (Maybe Text)
automationExecutionMetadata_maxConcurrency = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AutomationExecutionMetadata' {Maybe Text
maxConcurrency :: Maybe Text
$sel:maxConcurrency:AutomationExecutionMetadata' :: AutomationExecutionMetadata -> Maybe Text
maxConcurrency} -> Maybe Text
maxConcurrency) (\s :: AutomationExecutionMetadata
s@AutomationExecutionMetadata' {} Maybe Text
a -> AutomationExecutionMetadata
s {$sel:maxConcurrency:AutomationExecutionMetadata' :: Maybe Text
maxConcurrency = Maybe Text
a} :: AutomationExecutionMetadata)

-- | The @MaxErrors@ value specified by the user when starting the
-- automation.
automationExecutionMetadata_maxErrors :: Lens.Lens' AutomationExecutionMetadata (Prelude.Maybe Prelude.Text)
automationExecutionMetadata_maxErrors :: Lens' AutomationExecutionMetadata (Maybe Text)
automationExecutionMetadata_maxErrors = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AutomationExecutionMetadata' {Maybe Text
maxErrors :: Maybe Text
$sel:maxErrors:AutomationExecutionMetadata' :: AutomationExecutionMetadata -> Maybe Text
maxErrors} -> Maybe Text
maxErrors) (\s :: AutomationExecutionMetadata
s@AutomationExecutionMetadata' {} Maybe Text
a -> AutomationExecutionMetadata
s {$sel:maxErrors:AutomationExecutionMetadata' :: Maybe Text
maxErrors = Maybe Text
a} :: AutomationExecutionMetadata)

-- | The Automation execution mode.
automationExecutionMetadata_mode :: Lens.Lens' AutomationExecutionMetadata (Prelude.Maybe ExecutionMode)
automationExecutionMetadata_mode :: Lens' AutomationExecutionMetadata (Maybe ExecutionMode)
automationExecutionMetadata_mode = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AutomationExecutionMetadata' {Maybe ExecutionMode
mode :: Maybe ExecutionMode
$sel:mode:AutomationExecutionMetadata' :: AutomationExecutionMetadata -> Maybe ExecutionMode
mode} -> Maybe ExecutionMode
mode) (\s :: AutomationExecutionMetadata
s@AutomationExecutionMetadata' {} Maybe ExecutionMode
a -> AutomationExecutionMetadata
s {$sel:mode:AutomationExecutionMetadata' :: Maybe ExecutionMode
mode = Maybe ExecutionMode
a} :: AutomationExecutionMetadata)

-- | The ID of an OpsItem that is created to represent a Change Manager
-- change request.
automationExecutionMetadata_opsItemId :: Lens.Lens' AutomationExecutionMetadata (Prelude.Maybe Prelude.Text)
automationExecutionMetadata_opsItemId :: Lens' AutomationExecutionMetadata (Maybe Text)
automationExecutionMetadata_opsItemId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AutomationExecutionMetadata' {Maybe Text
opsItemId :: Maybe Text
$sel:opsItemId:AutomationExecutionMetadata' :: AutomationExecutionMetadata -> Maybe Text
opsItemId} -> Maybe Text
opsItemId) (\s :: AutomationExecutionMetadata
s@AutomationExecutionMetadata' {} Maybe Text
a -> AutomationExecutionMetadata
s {$sel:opsItemId:AutomationExecutionMetadata' :: Maybe Text
opsItemId = Maybe Text
a} :: AutomationExecutionMetadata)

-- | The list of execution outputs as defined in the Automation runbook.
automationExecutionMetadata_outputs :: Lens.Lens' AutomationExecutionMetadata (Prelude.Maybe (Prelude.HashMap Prelude.Text [Prelude.Text]))
automationExecutionMetadata_outputs :: Lens' AutomationExecutionMetadata (Maybe (HashMap Text [Text]))
automationExecutionMetadata_outputs = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AutomationExecutionMetadata' {Maybe (HashMap Text [Text])
outputs :: Maybe (HashMap Text [Text])
$sel:outputs:AutomationExecutionMetadata' :: AutomationExecutionMetadata -> Maybe (HashMap Text [Text])
outputs} -> Maybe (HashMap Text [Text])
outputs) (\s :: AutomationExecutionMetadata
s@AutomationExecutionMetadata' {} Maybe (HashMap Text [Text])
a -> AutomationExecutionMetadata
s {$sel:outputs:AutomationExecutionMetadata' :: Maybe (HashMap Text [Text])
outputs = Maybe (HashMap Text [Text])
a} :: AutomationExecutionMetadata) 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 execution ID of the parent automation.
automationExecutionMetadata_parentAutomationExecutionId :: Lens.Lens' AutomationExecutionMetadata (Prelude.Maybe Prelude.Text)
automationExecutionMetadata_parentAutomationExecutionId :: Lens' AutomationExecutionMetadata (Maybe Text)
automationExecutionMetadata_parentAutomationExecutionId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AutomationExecutionMetadata' {Maybe Text
parentAutomationExecutionId :: Maybe Text
$sel:parentAutomationExecutionId:AutomationExecutionMetadata' :: AutomationExecutionMetadata -> Maybe Text
parentAutomationExecutionId} -> Maybe Text
parentAutomationExecutionId) (\s :: AutomationExecutionMetadata
s@AutomationExecutionMetadata' {} Maybe Text
a -> AutomationExecutionMetadata
s {$sel:parentAutomationExecutionId:AutomationExecutionMetadata' :: Maybe Text
parentAutomationExecutionId = Maybe Text
a} :: AutomationExecutionMetadata)

-- | A list of targets that resolved during the execution.
automationExecutionMetadata_resolvedTargets :: Lens.Lens' AutomationExecutionMetadata (Prelude.Maybe ResolvedTargets)
automationExecutionMetadata_resolvedTargets :: Lens' AutomationExecutionMetadata (Maybe ResolvedTargets)
automationExecutionMetadata_resolvedTargets = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AutomationExecutionMetadata' {Maybe ResolvedTargets
resolvedTargets :: Maybe ResolvedTargets
$sel:resolvedTargets:AutomationExecutionMetadata' :: AutomationExecutionMetadata -> Maybe ResolvedTargets
resolvedTargets} -> Maybe ResolvedTargets
resolvedTargets) (\s :: AutomationExecutionMetadata
s@AutomationExecutionMetadata' {} Maybe ResolvedTargets
a -> AutomationExecutionMetadata
s {$sel:resolvedTargets:AutomationExecutionMetadata' :: Maybe ResolvedTargets
resolvedTargets = Maybe ResolvedTargets
a} :: AutomationExecutionMetadata)

-- | Information about the Automation runbooks that are run during a runbook
-- workflow in Change Manager.
--
-- The Automation runbooks specified for the runbook workflow can\'t run
-- until all required approvals for the change request have been received.
automationExecutionMetadata_runbooks :: Lens.Lens' AutomationExecutionMetadata (Prelude.Maybe (Prelude.NonEmpty Runbook))
automationExecutionMetadata_runbooks :: Lens' AutomationExecutionMetadata (Maybe (NonEmpty Runbook))
automationExecutionMetadata_runbooks = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AutomationExecutionMetadata' {Maybe (NonEmpty Runbook)
runbooks :: Maybe (NonEmpty Runbook)
$sel:runbooks:AutomationExecutionMetadata' :: AutomationExecutionMetadata -> Maybe (NonEmpty Runbook)
runbooks} -> Maybe (NonEmpty Runbook)
runbooks) (\s :: AutomationExecutionMetadata
s@AutomationExecutionMetadata' {} Maybe (NonEmpty Runbook)
a -> AutomationExecutionMetadata
s {$sel:runbooks:AutomationExecutionMetadata' :: Maybe (NonEmpty Runbook)
runbooks = Maybe (NonEmpty Runbook)
a} :: AutomationExecutionMetadata) 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 date and time the Automation operation is scheduled to start.
automationExecutionMetadata_scheduledTime :: Lens.Lens' AutomationExecutionMetadata (Prelude.Maybe Prelude.UTCTime)
automationExecutionMetadata_scheduledTime :: Lens' AutomationExecutionMetadata (Maybe UTCTime)
automationExecutionMetadata_scheduledTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AutomationExecutionMetadata' {Maybe POSIX
scheduledTime :: Maybe POSIX
$sel:scheduledTime:AutomationExecutionMetadata' :: AutomationExecutionMetadata -> Maybe POSIX
scheduledTime} -> Maybe POSIX
scheduledTime) (\s :: AutomationExecutionMetadata
s@AutomationExecutionMetadata' {} Maybe POSIX
a -> AutomationExecutionMetadata
s {$sel:scheduledTime:AutomationExecutionMetadata' :: Maybe POSIX
scheduledTime = Maybe POSIX
a} :: AutomationExecutionMetadata) 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 list of execution outputs as defined in the Automation runbook.
automationExecutionMetadata_target :: Lens.Lens' AutomationExecutionMetadata (Prelude.Maybe Prelude.Text)
automationExecutionMetadata_target :: Lens' AutomationExecutionMetadata (Maybe Text)
automationExecutionMetadata_target = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AutomationExecutionMetadata' {Maybe Text
target :: Maybe Text
$sel:target:AutomationExecutionMetadata' :: AutomationExecutionMetadata -> Maybe Text
target} -> Maybe Text
target) (\s :: AutomationExecutionMetadata
s@AutomationExecutionMetadata' {} Maybe Text
a -> AutomationExecutionMetadata
s {$sel:target:AutomationExecutionMetadata' :: Maybe Text
target = Maybe Text
a} :: AutomationExecutionMetadata)

-- | The specified key-value mapping of document parameters to target
-- resources.
automationExecutionMetadata_targetMaps :: Lens.Lens' AutomationExecutionMetadata (Prelude.Maybe [Prelude.HashMap Prelude.Text [Prelude.Text]])
automationExecutionMetadata_targetMaps :: Lens' AutomationExecutionMetadata (Maybe [HashMap Text [Text]])
automationExecutionMetadata_targetMaps = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AutomationExecutionMetadata' {Maybe [HashMap Text [Text]]
targetMaps :: Maybe [HashMap Text [Text]]
$sel:targetMaps:AutomationExecutionMetadata' :: AutomationExecutionMetadata -> Maybe [HashMap Text [Text]]
targetMaps} -> Maybe [HashMap Text [Text]]
targetMaps) (\s :: AutomationExecutionMetadata
s@AutomationExecutionMetadata' {} Maybe [HashMap Text [Text]]
a -> AutomationExecutionMetadata
s {$sel:targetMaps:AutomationExecutionMetadata' :: Maybe [HashMap Text [Text]]
targetMaps = Maybe [HashMap Text [Text]]
a} :: AutomationExecutionMetadata) 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 list of execution outputs as defined in the Automation runbook.
automationExecutionMetadata_targetParameterName :: Lens.Lens' AutomationExecutionMetadata (Prelude.Maybe Prelude.Text)
automationExecutionMetadata_targetParameterName :: Lens' AutomationExecutionMetadata (Maybe Text)
automationExecutionMetadata_targetParameterName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AutomationExecutionMetadata' {Maybe Text
targetParameterName :: Maybe Text
$sel:targetParameterName:AutomationExecutionMetadata' :: AutomationExecutionMetadata -> Maybe Text
targetParameterName} -> Maybe Text
targetParameterName) (\s :: AutomationExecutionMetadata
s@AutomationExecutionMetadata' {} Maybe Text
a -> AutomationExecutionMetadata
s {$sel:targetParameterName:AutomationExecutionMetadata' :: Maybe Text
targetParameterName = Maybe Text
a} :: AutomationExecutionMetadata)

-- | The targets defined by the user when starting the automation.
automationExecutionMetadata_targets :: Lens.Lens' AutomationExecutionMetadata (Prelude.Maybe [Target])
automationExecutionMetadata_targets :: Lens' AutomationExecutionMetadata (Maybe [Target])
automationExecutionMetadata_targets = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AutomationExecutionMetadata' {Maybe [Target]
targets :: Maybe [Target]
$sel:targets:AutomationExecutionMetadata' :: AutomationExecutionMetadata -> Maybe [Target]
targets} -> Maybe [Target]
targets) (\s :: AutomationExecutionMetadata
s@AutomationExecutionMetadata' {} Maybe [Target]
a -> AutomationExecutionMetadata
s {$sel:targets:AutomationExecutionMetadata' :: Maybe [Target]
targets = Maybe [Target]
a} :: AutomationExecutionMetadata) 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 CloudWatch alarm that was invoked by the automation.
automationExecutionMetadata_triggeredAlarms :: Lens.Lens' AutomationExecutionMetadata (Prelude.Maybe (Prelude.NonEmpty AlarmStateInformation))
automationExecutionMetadata_triggeredAlarms :: Lens'
  AutomationExecutionMetadata
  (Maybe (NonEmpty AlarmStateInformation))
automationExecutionMetadata_triggeredAlarms = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AutomationExecutionMetadata' {Maybe (NonEmpty AlarmStateInformation)
triggeredAlarms :: Maybe (NonEmpty AlarmStateInformation)
$sel:triggeredAlarms:AutomationExecutionMetadata' :: AutomationExecutionMetadata
-> Maybe (NonEmpty AlarmStateInformation)
triggeredAlarms} -> Maybe (NonEmpty AlarmStateInformation)
triggeredAlarms) (\s :: AutomationExecutionMetadata
s@AutomationExecutionMetadata' {} Maybe (NonEmpty AlarmStateInformation)
a -> AutomationExecutionMetadata
s {$sel:triggeredAlarms:AutomationExecutionMetadata' :: Maybe (NonEmpty AlarmStateInformation)
triggeredAlarms = Maybe (NonEmpty AlarmStateInformation)
a} :: AutomationExecutionMetadata) 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

instance Data.FromJSON AutomationExecutionMetadata where
  parseJSON :: Value -> Parser AutomationExecutionMetadata
parseJSON =
    forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.withObject
      String
"AutomationExecutionMetadata"
      ( \Object
x ->
          Maybe AlarmConfiguration
-> Maybe Text
-> Maybe Text
-> Maybe AutomationExecutionStatus
-> Maybe AutomationSubtype
-> Maybe AutomationType
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe POSIX
-> Maybe POSIX
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe ExecutionMode
-> Maybe Text
-> Maybe (HashMap Text [Text])
-> Maybe Text
-> Maybe ResolvedTargets
-> Maybe (NonEmpty Runbook)
-> Maybe POSIX
-> Maybe Text
-> Maybe [HashMap Text [Text]]
-> Maybe Text
-> Maybe [Target]
-> Maybe (NonEmpty AlarmStateInformation)
-> AutomationExecutionMetadata
AutomationExecutionMetadata'
            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
"AlarmConfiguration")
            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
"AssociationId")
            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
"AutomationExecutionId")
            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
"AutomationExecutionStatus")
            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
"AutomationSubtype")
            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
"AutomationType")
            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
"ChangeRequestName")
            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
"CurrentAction")
            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
"CurrentStepName")
            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
"DocumentName")
            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
"DocumentVersion")
            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
"ExecutedBy")
            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
"ExecutionEndTime")
            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
"ExecutionStartTime")
            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
"FailureMessage")
            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
"LogFile")
            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
"MaxConcurrency")
            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
"MaxErrors")
            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
"Mode")
            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
"OpsItemId")
            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
"Outputs" 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
"ParentAutomationExecutionId")
            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
"ResolvedTargets")
            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
"Runbooks")
            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
"ScheduledTime")
            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
"Target")
            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
"TargetMaps" 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
"TargetParameterName")
            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
"Targets" 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
"TriggeredAlarms")
      )

instance Prelude.Hashable AutomationExecutionMetadata where
  hashWithSalt :: Int -> AutomationExecutionMetadata -> Int
hashWithSalt Int
_salt AutomationExecutionMetadata' {Maybe [HashMap Text [Text]]
Maybe [Target]
Maybe (NonEmpty AlarmStateInformation)
Maybe (NonEmpty Runbook)
Maybe Text
Maybe (HashMap Text [Text])
Maybe POSIX
Maybe AlarmConfiguration
Maybe AutomationExecutionStatus
Maybe AutomationSubtype
Maybe AutomationType
Maybe ExecutionMode
Maybe ResolvedTargets
triggeredAlarms :: Maybe (NonEmpty AlarmStateInformation)
targets :: Maybe [Target]
targetParameterName :: Maybe Text
targetMaps :: Maybe [HashMap Text [Text]]
target :: Maybe Text
scheduledTime :: Maybe POSIX
runbooks :: Maybe (NonEmpty Runbook)
resolvedTargets :: Maybe ResolvedTargets
parentAutomationExecutionId :: Maybe Text
outputs :: Maybe (HashMap Text [Text])
opsItemId :: Maybe Text
mode :: Maybe ExecutionMode
maxErrors :: Maybe Text
maxConcurrency :: Maybe Text
logFile :: Maybe Text
failureMessage :: Maybe Text
executionStartTime :: Maybe POSIX
executionEndTime :: Maybe POSIX
executedBy :: Maybe Text
documentVersion :: Maybe Text
documentName :: Maybe Text
currentStepName :: Maybe Text
currentAction :: Maybe Text
changeRequestName :: Maybe Text
automationType :: Maybe AutomationType
automationSubtype :: Maybe AutomationSubtype
automationExecutionStatus :: Maybe AutomationExecutionStatus
automationExecutionId :: Maybe Text
associationId :: Maybe Text
alarmConfiguration :: Maybe AlarmConfiguration
$sel:triggeredAlarms:AutomationExecutionMetadata' :: AutomationExecutionMetadata
-> Maybe (NonEmpty AlarmStateInformation)
$sel:targets:AutomationExecutionMetadata' :: AutomationExecutionMetadata -> Maybe [Target]
$sel:targetParameterName:AutomationExecutionMetadata' :: AutomationExecutionMetadata -> Maybe Text
$sel:targetMaps:AutomationExecutionMetadata' :: AutomationExecutionMetadata -> Maybe [HashMap Text [Text]]
$sel:target:AutomationExecutionMetadata' :: AutomationExecutionMetadata -> Maybe Text
$sel:scheduledTime:AutomationExecutionMetadata' :: AutomationExecutionMetadata -> Maybe POSIX
$sel:runbooks:AutomationExecutionMetadata' :: AutomationExecutionMetadata -> Maybe (NonEmpty Runbook)
$sel:resolvedTargets:AutomationExecutionMetadata' :: AutomationExecutionMetadata -> Maybe ResolvedTargets
$sel:parentAutomationExecutionId:AutomationExecutionMetadata' :: AutomationExecutionMetadata -> Maybe Text
$sel:outputs:AutomationExecutionMetadata' :: AutomationExecutionMetadata -> Maybe (HashMap Text [Text])
$sel:opsItemId:AutomationExecutionMetadata' :: AutomationExecutionMetadata -> Maybe Text
$sel:mode:AutomationExecutionMetadata' :: AutomationExecutionMetadata -> Maybe ExecutionMode
$sel:maxErrors:AutomationExecutionMetadata' :: AutomationExecutionMetadata -> Maybe Text
$sel:maxConcurrency:AutomationExecutionMetadata' :: AutomationExecutionMetadata -> Maybe Text
$sel:logFile:AutomationExecutionMetadata' :: AutomationExecutionMetadata -> Maybe Text
$sel:failureMessage:AutomationExecutionMetadata' :: AutomationExecutionMetadata -> Maybe Text
$sel:executionStartTime:AutomationExecutionMetadata' :: AutomationExecutionMetadata -> Maybe POSIX
$sel:executionEndTime:AutomationExecutionMetadata' :: AutomationExecutionMetadata -> Maybe POSIX
$sel:executedBy:AutomationExecutionMetadata' :: AutomationExecutionMetadata -> Maybe Text
$sel:documentVersion:AutomationExecutionMetadata' :: AutomationExecutionMetadata -> Maybe Text
$sel:documentName:AutomationExecutionMetadata' :: AutomationExecutionMetadata -> Maybe Text
$sel:currentStepName:AutomationExecutionMetadata' :: AutomationExecutionMetadata -> Maybe Text
$sel:currentAction:AutomationExecutionMetadata' :: AutomationExecutionMetadata -> Maybe Text
$sel:changeRequestName:AutomationExecutionMetadata' :: AutomationExecutionMetadata -> Maybe Text
$sel:automationType:AutomationExecutionMetadata' :: AutomationExecutionMetadata -> Maybe AutomationType
$sel:automationSubtype:AutomationExecutionMetadata' :: AutomationExecutionMetadata -> Maybe AutomationSubtype
$sel:automationExecutionStatus:AutomationExecutionMetadata' :: AutomationExecutionMetadata -> Maybe AutomationExecutionStatus
$sel:automationExecutionId:AutomationExecutionMetadata' :: AutomationExecutionMetadata -> Maybe Text
$sel:associationId:AutomationExecutionMetadata' :: AutomationExecutionMetadata -> Maybe Text
$sel:alarmConfiguration:AutomationExecutionMetadata' :: AutomationExecutionMetadata -> Maybe AlarmConfiguration
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe AlarmConfiguration
alarmConfiguration
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
associationId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
automationExecutionId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe AutomationExecutionStatus
automationExecutionStatus
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe AutomationSubtype
automationSubtype
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe AutomationType
automationType
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
changeRequestName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
currentAction
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
currentStepName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
documentName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
documentVersion
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
executedBy
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe POSIX
executionEndTime
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe POSIX
executionStartTime
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
failureMessage
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
logFile
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
maxConcurrency
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
maxErrors
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ExecutionMode
mode
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
opsItemId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe (HashMap Text [Text])
outputs
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
parentAutomationExecutionId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ResolvedTargets
resolvedTargets
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe (NonEmpty Runbook)
runbooks
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe POSIX
scheduledTime
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
target
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [HashMap Text [Text]]
targetMaps
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
targetParameterName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [Target]
targets
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe (NonEmpty AlarmStateInformation)
triggeredAlarms

instance Prelude.NFData AutomationExecutionMetadata where
  rnf :: AutomationExecutionMetadata -> ()
rnf AutomationExecutionMetadata' {Maybe [HashMap Text [Text]]
Maybe [Target]
Maybe (NonEmpty AlarmStateInformation)
Maybe (NonEmpty Runbook)
Maybe Text
Maybe (HashMap Text [Text])
Maybe POSIX
Maybe AlarmConfiguration
Maybe AutomationExecutionStatus
Maybe AutomationSubtype
Maybe AutomationType
Maybe ExecutionMode
Maybe ResolvedTargets
triggeredAlarms :: Maybe (NonEmpty AlarmStateInformation)
targets :: Maybe [Target]
targetParameterName :: Maybe Text
targetMaps :: Maybe [HashMap Text [Text]]
target :: Maybe Text
scheduledTime :: Maybe POSIX
runbooks :: Maybe (NonEmpty Runbook)
resolvedTargets :: Maybe ResolvedTargets
parentAutomationExecutionId :: Maybe Text
outputs :: Maybe (HashMap Text [Text])
opsItemId :: Maybe Text
mode :: Maybe ExecutionMode
maxErrors :: Maybe Text
maxConcurrency :: Maybe Text
logFile :: Maybe Text
failureMessage :: Maybe Text
executionStartTime :: Maybe POSIX
executionEndTime :: Maybe POSIX
executedBy :: Maybe Text
documentVersion :: Maybe Text
documentName :: Maybe Text
currentStepName :: Maybe Text
currentAction :: Maybe Text
changeRequestName :: Maybe Text
automationType :: Maybe AutomationType
automationSubtype :: Maybe AutomationSubtype
automationExecutionStatus :: Maybe AutomationExecutionStatus
automationExecutionId :: Maybe Text
associationId :: Maybe Text
alarmConfiguration :: Maybe AlarmConfiguration
$sel:triggeredAlarms:AutomationExecutionMetadata' :: AutomationExecutionMetadata
-> Maybe (NonEmpty AlarmStateInformation)
$sel:targets:AutomationExecutionMetadata' :: AutomationExecutionMetadata -> Maybe [Target]
$sel:targetParameterName:AutomationExecutionMetadata' :: AutomationExecutionMetadata -> Maybe Text
$sel:targetMaps:AutomationExecutionMetadata' :: AutomationExecutionMetadata -> Maybe [HashMap Text [Text]]
$sel:target:AutomationExecutionMetadata' :: AutomationExecutionMetadata -> Maybe Text
$sel:scheduledTime:AutomationExecutionMetadata' :: AutomationExecutionMetadata -> Maybe POSIX
$sel:runbooks:AutomationExecutionMetadata' :: AutomationExecutionMetadata -> Maybe (NonEmpty Runbook)
$sel:resolvedTargets:AutomationExecutionMetadata' :: AutomationExecutionMetadata -> Maybe ResolvedTargets
$sel:parentAutomationExecutionId:AutomationExecutionMetadata' :: AutomationExecutionMetadata -> Maybe Text
$sel:outputs:AutomationExecutionMetadata' :: AutomationExecutionMetadata -> Maybe (HashMap Text [Text])
$sel:opsItemId:AutomationExecutionMetadata' :: AutomationExecutionMetadata -> Maybe Text
$sel:mode:AutomationExecutionMetadata' :: AutomationExecutionMetadata -> Maybe ExecutionMode
$sel:maxErrors:AutomationExecutionMetadata' :: AutomationExecutionMetadata -> Maybe Text
$sel:maxConcurrency:AutomationExecutionMetadata' :: AutomationExecutionMetadata -> Maybe Text
$sel:logFile:AutomationExecutionMetadata' :: AutomationExecutionMetadata -> Maybe Text
$sel:failureMessage:AutomationExecutionMetadata' :: AutomationExecutionMetadata -> Maybe Text
$sel:executionStartTime:AutomationExecutionMetadata' :: AutomationExecutionMetadata -> Maybe POSIX
$sel:executionEndTime:AutomationExecutionMetadata' :: AutomationExecutionMetadata -> Maybe POSIX
$sel:executedBy:AutomationExecutionMetadata' :: AutomationExecutionMetadata -> Maybe Text
$sel:documentVersion:AutomationExecutionMetadata' :: AutomationExecutionMetadata -> Maybe Text
$sel:documentName:AutomationExecutionMetadata' :: AutomationExecutionMetadata -> Maybe Text
$sel:currentStepName:AutomationExecutionMetadata' :: AutomationExecutionMetadata -> Maybe Text
$sel:currentAction:AutomationExecutionMetadata' :: AutomationExecutionMetadata -> Maybe Text
$sel:changeRequestName:AutomationExecutionMetadata' :: AutomationExecutionMetadata -> Maybe Text
$sel:automationType:AutomationExecutionMetadata' :: AutomationExecutionMetadata -> Maybe AutomationType
$sel:automationSubtype:AutomationExecutionMetadata' :: AutomationExecutionMetadata -> Maybe AutomationSubtype
$sel:automationExecutionStatus:AutomationExecutionMetadata' :: AutomationExecutionMetadata -> Maybe AutomationExecutionStatus
$sel:automationExecutionId:AutomationExecutionMetadata' :: AutomationExecutionMetadata -> Maybe Text
$sel:associationId:AutomationExecutionMetadata' :: AutomationExecutionMetadata -> Maybe Text
$sel:alarmConfiguration:AutomationExecutionMetadata' :: AutomationExecutionMetadata -> Maybe AlarmConfiguration
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe AlarmConfiguration
alarmConfiguration
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
associationId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
automationExecutionId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe AutomationExecutionStatus
automationExecutionStatus
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe AutomationSubtype
automationSubtype
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe AutomationType
automationType
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
changeRequestName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
currentAction
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
currentStepName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
documentName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
documentVersion
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
executedBy
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe POSIX
executionEndTime
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe POSIX
executionStartTime
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
failureMessage
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
logFile
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
maxConcurrency
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
maxErrors
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ExecutionMode
mode
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
opsItemId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe (HashMap Text [Text])
outputs
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Maybe Text
parentAutomationExecutionId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Maybe ResolvedTargets
resolvedTargets
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe (NonEmpty Runbook)
runbooks
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Maybe POSIX
scheduledTime
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
target
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Maybe [HashMap Text [Text]]
targetMaps
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Maybe Text
targetParameterName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Maybe [Target]
targets
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Maybe (NonEmpty AlarmStateInformation)
triggeredAlarms