{-# 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.StepFunctions.Types.HistoryEvent
-- 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.StepFunctions.Types.HistoryEvent 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.StepFunctions.Types.ActivityFailedEventDetails
import Amazonka.StepFunctions.Types.ActivityScheduleFailedEventDetails
import Amazonka.StepFunctions.Types.ActivityScheduledEventDetails
import Amazonka.StepFunctions.Types.ActivityStartedEventDetails
import Amazonka.StepFunctions.Types.ActivitySucceededEventDetails
import Amazonka.StepFunctions.Types.ActivityTimedOutEventDetails
import Amazonka.StepFunctions.Types.ExecutionAbortedEventDetails
import Amazonka.StepFunctions.Types.ExecutionFailedEventDetails
import Amazonka.StepFunctions.Types.ExecutionStartedEventDetails
import Amazonka.StepFunctions.Types.ExecutionSucceededEventDetails
import Amazonka.StepFunctions.Types.ExecutionTimedOutEventDetails
import Amazonka.StepFunctions.Types.HistoryEventType
import Amazonka.StepFunctions.Types.LambdaFunctionFailedEventDetails
import Amazonka.StepFunctions.Types.LambdaFunctionScheduleFailedEventDetails
import Amazonka.StepFunctions.Types.LambdaFunctionScheduledEventDetails
import Amazonka.StepFunctions.Types.LambdaFunctionStartFailedEventDetails
import Amazonka.StepFunctions.Types.LambdaFunctionSucceededEventDetails
import Amazonka.StepFunctions.Types.LambdaFunctionTimedOutEventDetails
import Amazonka.StepFunctions.Types.MapIterationEventDetails
import Amazonka.StepFunctions.Types.MapRunFailedEventDetails
import Amazonka.StepFunctions.Types.MapRunStartedEventDetails
import Amazonka.StepFunctions.Types.MapStateStartedEventDetails
import Amazonka.StepFunctions.Types.StateEnteredEventDetails
import Amazonka.StepFunctions.Types.StateExitedEventDetails
import Amazonka.StepFunctions.Types.TaskFailedEventDetails
import Amazonka.StepFunctions.Types.TaskScheduledEventDetails
import Amazonka.StepFunctions.Types.TaskStartFailedEventDetails
import Amazonka.StepFunctions.Types.TaskStartedEventDetails
import Amazonka.StepFunctions.Types.TaskSubmitFailedEventDetails
import Amazonka.StepFunctions.Types.TaskSubmittedEventDetails
import Amazonka.StepFunctions.Types.TaskSucceededEventDetails
import Amazonka.StepFunctions.Types.TaskTimedOutEventDetails

-- | Contains details about the events of an execution.
--
-- /See:/ 'newHistoryEvent' smart constructor.
data HistoryEvent = HistoryEvent'
  { HistoryEvent -> Maybe ActivityFailedEventDetails
activityFailedEventDetails :: Prelude.Maybe ActivityFailedEventDetails,
    -- | Contains details about an activity schedule event that failed during an
    -- execution.
    HistoryEvent -> Maybe ActivityScheduleFailedEventDetails
activityScheduleFailedEventDetails :: Prelude.Maybe ActivityScheduleFailedEventDetails,
    HistoryEvent -> Maybe ActivityScheduledEventDetails
activityScheduledEventDetails :: Prelude.Maybe ActivityScheduledEventDetails,
    HistoryEvent -> Maybe ActivityStartedEventDetails
activityStartedEventDetails :: Prelude.Maybe ActivityStartedEventDetails,
    HistoryEvent -> Maybe ActivitySucceededEventDetails
activitySucceededEventDetails :: Prelude.Maybe ActivitySucceededEventDetails,
    HistoryEvent -> Maybe ActivityTimedOutEventDetails
activityTimedOutEventDetails :: Prelude.Maybe ActivityTimedOutEventDetails,
    HistoryEvent -> Maybe ExecutionAbortedEventDetails
executionAbortedEventDetails :: Prelude.Maybe ExecutionAbortedEventDetails,
    HistoryEvent -> Maybe ExecutionFailedEventDetails
executionFailedEventDetails :: Prelude.Maybe ExecutionFailedEventDetails,
    HistoryEvent -> Maybe ExecutionStartedEventDetails
executionStartedEventDetails :: Prelude.Maybe ExecutionStartedEventDetails,
    HistoryEvent -> Maybe ExecutionSucceededEventDetails
executionSucceededEventDetails :: Prelude.Maybe ExecutionSucceededEventDetails,
    HistoryEvent -> Maybe ExecutionTimedOutEventDetails
executionTimedOutEventDetails :: Prelude.Maybe ExecutionTimedOutEventDetails,
    HistoryEvent -> Maybe LambdaFunctionFailedEventDetails
lambdaFunctionFailedEventDetails :: Prelude.Maybe LambdaFunctionFailedEventDetails,
    HistoryEvent -> Maybe LambdaFunctionScheduleFailedEventDetails
lambdaFunctionScheduleFailedEventDetails :: Prelude.Maybe LambdaFunctionScheduleFailedEventDetails,
    HistoryEvent -> Maybe LambdaFunctionScheduledEventDetails
lambdaFunctionScheduledEventDetails :: Prelude.Maybe LambdaFunctionScheduledEventDetails,
    -- | Contains details about a lambda function that failed to start during an
    -- execution.
    HistoryEvent -> Maybe LambdaFunctionStartFailedEventDetails
lambdaFunctionStartFailedEventDetails :: Prelude.Maybe LambdaFunctionStartFailedEventDetails,
    -- | Contains details about a Lambda function that terminated successfully
    -- during an execution.
    HistoryEvent -> Maybe LambdaFunctionSucceededEventDetails
lambdaFunctionSucceededEventDetails :: Prelude.Maybe LambdaFunctionSucceededEventDetails,
    HistoryEvent -> Maybe LambdaFunctionTimedOutEventDetails
lambdaFunctionTimedOutEventDetails :: Prelude.Maybe LambdaFunctionTimedOutEventDetails,
    -- | Contains details about an iteration of a Map state that was aborted.
    HistoryEvent -> Maybe MapIterationEventDetails
mapIterationAbortedEventDetails :: Prelude.Maybe MapIterationEventDetails,
    -- | Contains details about an iteration of a Map state that failed.
    HistoryEvent -> Maybe MapIterationEventDetails
mapIterationFailedEventDetails :: Prelude.Maybe MapIterationEventDetails,
    -- | Contains details about an iteration of a Map state that was started.
    HistoryEvent -> Maybe MapIterationEventDetails
mapIterationStartedEventDetails :: Prelude.Maybe MapIterationEventDetails,
    -- | Contains details about an iteration of a Map state that succeeded.
    HistoryEvent -> Maybe MapIterationEventDetails
mapIterationSucceededEventDetails :: Prelude.Maybe MapIterationEventDetails,
    -- | Contains error and cause details about a Map Run that failed.
    HistoryEvent -> Maybe MapRunFailedEventDetails
mapRunFailedEventDetails :: Prelude.Maybe MapRunFailedEventDetails,
    -- | Contains details, such as @mapRunArn@, and the start date and time of a
    -- Map Run. @mapRunArn@ is the Amazon Resource Name (ARN) of the Map Run
    -- that was started.
    HistoryEvent -> Maybe MapRunStartedEventDetails
mapRunStartedEventDetails :: Prelude.Maybe MapRunStartedEventDetails,
    -- | Contains details about Map state that was started.
    HistoryEvent -> Maybe MapStateStartedEventDetails
mapStateStartedEventDetails :: Prelude.Maybe MapStateStartedEventDetails,
    -- | The id of the previous event.
    HistoryEvent -> Maybe Integer
previousEventId :: Prelude.Maybe Prelude.Integer,
    HistoryEvent -> Maybe StateEnteredEventDetails
stateEnteredEventDetails :: Prelude.Maybe StateEnteredEventDetails,
    HistoryEvent -> Maybe StateExitedEventDetails
stateExitedEventDetails :: Prelude.Maybe StateExitedEventDetails,
    -- | Contains details about the failure of a task.
    HistoryEvent -> Maybe TaskFailedEventDetails
taskFailedEventDetails :: Prelude.Maybe TaskFailedEventDetails,
    -- | Contains details about a task that was scheduled.
    HistoryEvent -> Maybe TaskScheduledEventDetails
taskScheduledEventDetails :: Prelude.Maybe TaskScheduledEventDetails,
    -- | Contains details about a task that failed to start.
    HistoryEvent -> Maybe TaskStartFailedEventDetails
taskStartFailedEventDetails :: Prelude.Maybe TaskStartFailedEventDetails,
    -- | Contains details about a task that was started.
    HistoryEvent -> Maybe TaskStartedEventDetails
taskStartedEventDetails :: Prelude.Maybe TaskStartedEventDetails,
    -- | Contains details about a task that where the submit failed.
    HistoryEvent -> Maybe TaskSubmitFailedEventDetails
taskSubmitFailedEventDetails :: Prelude.Maybe TaskSubmitFailedEventDetails,
    -- | Contains details about a submitted task.
    HistoryEvent -> Maybe TaskSubmittedEventDetails
taskSubmittedEventDetails :: Prelude.Maybe TaskSubmittedEventDetails,
    -- | Contains details about a task that succeeded.
    HistoryEvent -> Maybe TaskSucceededEventDetails
taskSucceededEventDetails :: Prelude.Maybe TaskSucceededEventDetails,
    -- | Contains details about a task that timed out.
    HistoryEvent -> Maybe TaskTimedOutEventDetails
taskTimedOutEventDetails :: Prelude.Maybe TaskTimedOutEventDetails,
    -- | The date and time the event occurred.
    HistoryEvent -> POSIX
timestamp :: Data.POSIX,
    -- | The type of the event.
    HistoryEvent -> HistoryEventType
type' :: HistoryEventType,
    -- | The id of the event. Events are numbered sequentially, starting at one.
    HistoryEvent -> Integer
id :: Prelude.Integer
  }
  deriving (HistoryEvent -> HistoryEvent -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: HistoryEvent -> HistoryEvent -> Bool
$c/= :: HistoryEvent -> HistoryEvent -> Bool
== :: HistoryEvent -> HistoryEvent -> Bool
$c== :: HistoryEvent -> HistoryEvent -> Bool
Prelude.Eq, Int -> HistoryEvent -> ShowS
[HistoryEvent] -> ShowS
HistoryEvent -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [HistoryEvent] -> ShowS
$cshowList :: [HistoryEvent] -> ShowS
show :: HistoryEvent -> String
$cshow :: HistoryEvent -> String
showsPrec :: Int -> HistoryEvent -> ShowS
$cshowsPrec :: Int -> HistoryEvent -> ShowS
Prelude.Show, forall x. Rep HistoryEvent x -> HistoryEvent
forall x. HistoryEvent -> Rep HistoryEvent x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep HistoryEvent x -> HistoryEvent
$cfrom :: forall x. HistoryEvent -> Rep HistoryEvent x
Prelude.Generic)

-- |
-- Create a value of 'HistoryEvent' 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:
--
-- 'activityFailedEventDetails', 'historyEvent_activityFailedEventDetails' - Undocumented member.
--
-- 'activityScheduleFailedEventDetails', 'historyEvent_activityScheduleFailedEventDetails' - Contains details about an activity schedule event that failed during an
-- execution.
--
-- 'activityScheduledEventDetails', 'historyEvent_activityScheduledEventDetails' - Undocumented member.
--
-- 'activityStartedEventDetails', 'historyEvent_activityStartedEventDetails' - Undocumented member.
--
-- 'activitySucceededEventDetails', 'historyEvent_activitySucceededEventDetails' - Undocumented member.
--
-- 'activityTimedOutEventDetails', 'historyEvent_activityTimedOutEventDetails' - Undocumented member.
--
-- 'executionAbortedEventDetails', 'historyEvent_executionAbortedEventDetails' - Undocumented member.
--
-- 'executionFailedEventDetails', 'historyEvent_executionFailedEventDetails' - Undocumented member.
--
-- 'executionStartedEventDetails', 'historyEvent_executionStartedEventDetails' - Undocumented member.
--
-- 'executionSucceededEventDetails', 'historyEvent_executionSucceededEventDetails' - Undocumented member.
--
-- 'executionTimedOutEventDetails', 'historyEvent_executionTimedOutEventDetails' - Undocumented member.
--
-- 'lambdaFunctionFailedEventDetails', 'historyEvent_lambdaFunctionFailedEventDetails' - Undocumented member.
--
-- 'lambdaFunctionScheduleFailedEventDetails', 'historyEvent_lambdaFunctionScheduleFailedEventDetails' - Undocumented member.
--
-- 'lambdaFunctionScheduledEventDetails', 'historyEvent_lambdaFunctionScheduledEventDetails' - Undocumented member.
--
-- 'lambdaFunctionStartFailedEventDetails', 'historyEvent_lambdaFunctionStartFailedEventDetails' - Contains details about a lambda function that failed to start during an
-- execution.
--
-- 'lambdaFunctionSucceededEventDetails', 'historyEvent_lambdaFunctionSucceededEventDetails' - Contains details about a Lambda function that terminated successfully
-- during an execution.
--
-- 'lambdaFunctionTimedOutEventDetails', 'historyEvent_lambdaFunctionTimedOutEventDetails' - Undocumented member.
--
-- 'mapIterationAbortedEventDetails', 'historyEvent_mapIterationAbortedEventDetails' - Contains details about an iteration of a Map state that was aborted.
--
-- 'mapIterationFailedEventDetails', 'historyEvent_mapIterationFailedEventDetails' - Contains details about an iteration of a Map state that failed.
--
-- 'mapIterationStartedEventDetails', 'historyEvent_mapIterationStartedEventDetails' - Contains details about an iteration of a Map state that was started.
--
-- 'mapIterationSucceededEventDetails', 'historyEvent_mapIterationSucceededEventDetails' - Contains details about an iteration of a Map state that succeeded.
--
-- 'mapRunFailedEventDetails', 'historyEvent_mapRunFailedEventDetails' - Contains error and cause details about a Map Run that failed.
--
-- 'mapRunStartedEventDetails', 'historyEvent_mapRunStartedEventDetails' - Contains details, such as @mapRunArn@, and the start date and time of a
-- Map Run. @mapRunArn@ is the Amazon Resource Name (ARN) of the Map Run
-- that was started.
--
-- 'mapStateStartedEventDetails', 'historyEvent_mapStateStartedEventDetails' - Contains details about Map state that was started.
--
-- 'previousEventId', 'historyEvent_previousEventId' - The id of the previous event.
--
-- 'stateEnteredEventDetails', 'historyEvent_stateEnteredEventDetails' - Undocumented member.
--
-- 'stateExitedEventDetails', 'historyEvent_stateExitedEventDetails' - Undocumented member.
--
-- 'taskFailedEventDetails', 'historyEvent_taskFailedEventDetails' - Contains details about the failure of a task.
--
-- 'taskScheduledEventDetails', 'historyEvent_taskScheduledEventDetails' - Contains details about a task that was scheduled.
--
-- 'taskStartFailedEventDetails', 'historyEvent_taskStartFailedEventDetails' - Contains details about a task that failed to start.
--
-- 'taskStartedEventDetails', 'historyEvent_taskStartedEventDetails' - Contains details about a task that was started.
--
-- 'taskSubmitFailedEventDetails', 'historyEvent_taskSubmitFailedEventDetails' - Contains details about a task that where the submit failed.
--
-- 'taskSubmittedEventDetails', 'historyEvent_taskSubmittedEventDetails' - Contains details about a submitted task.
--
-- 'taskSucceededEventDetails', 'historyEvent_taskSucceededEventDetails' - Contains details about a task that succeeded.
--
-- 'taskTimedOutEventDetails', 'historyEvent_taskTimedOutEventDetails' - Contains details about a task that timed out.
--
-- 'timestamp', 'historyEvent_timestamp' - The date and time the event occurred.
--
-- 'type'', 'historyEvent_type' - The type of the event.
--
-- 'id', 'historyEvent_id' - The id of the event. Events are numbered sequentially, starting at one.
newHistoryEvent ::
  -- | 'timestamp'
  Prelude.UTCTime ->
  -- | 'type''
  HistoryEventType ->
  -- | 'id'
  Prelude.Integer ->
  HistoryEvent
newHistoryEvent :: UTCTime -> HistoryEventType -> Integer -> HistoryEvent
newHistoryEvent UTCTime
pTimestamp_ HistoryEventType
pType_ Integer
pId_ =
  HistoryEvent'
    { $sel:activityFailedEventDetails:HistoryEvent' :: Maybe ActivityFailedEventDetails
activityFailedEventDetails =
        forall a. Maybe a
Prelude.Nothing,
      $sel:activityScheduleFailedEventDetails:HistoryEvent' :: Maybe ActivityScheduleFailedEventDetails
activityScheduleFailedEventDetails = forall a. Maybe a
Prelude.Nothing,
      $sel:activityScheduledEventDetails:HistoryEvent' :: Maybe ActivityScheduledEventDetails
activityScheduledEventDetails = forall a. Maybe a
Prelude.Nothing,
      $sel:activityStartedEventDetails:HistoryEvent' :: Maybe ActivityStartedEventDetails
activityStartedEventDetails = forall a. Maybe a
Prelude.Nothing,
      $sel:activitySucceededEventDetails:HistoryEvent' :: Maybe ActivitySucceededEventDetails
activitySucceededEventDetails = forall a. Maybe a
Prelude.Nothing,
      $sel:activityTimedOutEventDetails:HistoryEvent' :: Maybe ActivityTimedOutEventDetails
activityTimedOutEventDetails = forall a. Maybe a
Prelude.Nothing,
      $sel:executionAbortedEventDetails:HistoryEvent' :: Maybe ExecutionAbortedEventDetails
executionAbortedEventDetails = forall a. Maybe a
Prelude.Nothing,
      $sel:executionFailedEventDetails:HistoryEvent' :: Maybe ExecutionFailedEventDetails
executionFailedEventDetails = forall a. Maybe a
Prelude.Nothing,
      $sel:executionStartedEventDetails:HistoryEvent' :: Maybe ExecutionStartedEventDetails
executionStartedEventDetails = forall a. Maybe a
Prelude.Nothing,
      $sel:executionSucceededEventDetails:HistoryEvent' :: Maybe ExecutionSucceededEventDetails
executionSucceededEventDetails = forall a. Maybe a
Prelude.Nothing,
      $sel:executionTimedOutEventDetails:HistoryEvent' :: Maybe ExecutionTimedOutEventDetails
executionTimedOutEventDetails = forall a. Maybe a
Prelude.Nothing,
      $sel:lambdaFunctionFailedEventDetails:HistoryEvent' :: Maybe LambdaFunctionFailedEventDetails
lambdaFunctionFailedEventDetails = forall a. Maybe a
Prelude.Nothing,
      $sel:lambdaFunctionScheduleFailedEventDetails:HistoryEvent' :: Maybe LambdaFunctionScheduleFailedEventDetails
lambdaFunctionScheduleFailedEventDetails =
        forall a. Maybe a
Prelude.Nothing,
      $sel:lambdaFunctionScheduledEventDetails:HistoryEvent' :: Maybe LambdaFunctionScheduledEventDetails
lambdaFunctionScheduledEventDetails =
        forall a. Maybe a
Prelude.Nothing,
      $sel:lambdaFunctionStartFailedEventDetails:HistoryEvent' :: Maybe LambdaFunctionStartFailedEventDetails
lambdaFunctionStartFailedEventDetails =
        forall a. Maybe a
Prelude.Nothing,
      $sel:lambdaFunctionSucceededEventDetails:HistoryEvent' :: Maybe LambdaFunctionSucceededEventDetails
lambdaFunctionSucceededEventDetails =
        forall a. Maybe a
Prelude.Nothing,
      $sel:lambdaFunctionTimedOutEventDetails:HistoryEvent' :: Maybe LambdaFunctionTimedOutEventDetails
lambdaFunctionTimedOutEventDetails = forall a. Maybe a
Prelude.Nothing,
      $sel:mapIterationAbortedEventDetails:HistoryEvent' :: Maybe MapIterationEventDetails
mapIterationAbortedEventDetails = forall a. Maybe a
Prelude.Nothing,
      $sel:mapIterationFailedEventDetails:HistoryEvent' :: Maybe MapIterationEventDetails
mapIterationFailedEventDetails = forall a. Maybe a
Prelude.Nothing,
      $sel:mapIterationStartedEventDetails:HistoryEvent' :: Maybe MapIterationEventDetails
mapIterationStartedEventDetails = forall a. Maybe a
Prelude.Nothing,
      $sel:mapIterationSucceededEventDetails:HistoryEvent' :: Maybe MapIterationEventDetails
mapIterationSucceededEventDetails = forall a. Maybe a
Prelude.Nothing,
      $sel:mapRunFailedEventDetails:HistoryEvent' :: Maybe MapRunFailedEventDetails
mapRunFailedEventDetails = forall a. Maybe a
Prelude.Nothing,
      $sel:mapRunStartedEventDetails:HistoryEvent' :: Maybe MapRunStartedEventDetails
mapRunStartedEventDetails = forall a. Maybe a
Prelude.Nothing,
      $sel:mapStateStartedEventDetails:HistoryEvent' :: Maybe MapStateStartedEventDetails
mapStateStartedEventDetails = forall a. Maybe a
Prelude.Nothing,
      $sel:previousEventId:HistoryEvent' :: Maybe Integer
previousEventId = forall a. Maybe a
Prelude.Nothing,
      $sel:stateEnteredEventDetails:HistoryEvent' :: Maybe StateEnteredEventDetails
stateEnteredEventDetails = forall a. Maybe a
Prelude.Nothing,
      $sel:stateExitedEventDetails:HistoryEvent' :: Maybe StateExitedEventDetails
stateExitedEventDetails = forall a. Maybe a
Prelude.Nothing,
      $sel:taskFailedEventDetails:HistoryEvent' :: Maybe TaskFailedEventDetails
taskFailedEventDetails = forall a. Maybe a
Prelude.Nothing,
      $sel:taskScheduledEventDetails:HistoryEvent' :: Maybe TaskScheduledEventDetails
taskScheduledEventDetails = forall a. Maybe a
Prelude.Nothing,
      $sel:taskStartFailedEventDetails:HistoryEvent' :: Maybe TaskStartFailedEventDetails
taskStartFailedEventDetails = forall a. Maybe a
Prelude.Nothing,
      $sel:taskStartedEventDetails:HistoryEvent' :: Maybe TaskStartedEventDetails
taskStartedEventDetails = forall a. Maybe a
Prelude.Nothing,
      $sel:taskSubmitFailedEventDetails:HistoryEvent' :: Maybe TaskSubmitFailedEventDetails
taskSubmitFailedEventDetails = forall a. Maybe a
Prelude.Nothing,
      $sel:taskSubmittedEventDetails:HistoryEvent' :: Maybe TaskSubmittedEventDetails
taskSubmittedEventDetails = forall a. Maybe a
Prelude.Nothing,
      $sel:taskSucceededEventDetails:HistoryEvent' :: Maybe TaskSucceededEventDetails
taskSucceededEventDetails = forall a. Maybe a
Prelude.Nothing,
      $sel:taskTimedOutEventDetails:HistoryEvent' :: Maybe TaskTimedOutEventDetails
taskTimedOutEventDetails = forall a. Maybe a
Prelude.Nothing,
      $sel:timestamp:HistoryEvent' :: POSIX
timestamp = forall (a :: Format). Iso' (Time a) UTCTime
Data._Time forall t b. AReview t b -> b -> t
Lens.# UTCTime
pTimestamp_,
      $sel:type':HistoryEvent' :: HistoryEventType
type' = HistoryEventType
pType_,
      $sel:id:HistoryEvent' :: Integer
id = Integer
pId_
    }

-- | Undocumented member.
historyEvent_activityFailedEventDetails :: Lens.Lens' HistoryEvent (Prelude.Maybe ActivityFailedEventDetails)
historyEvent_activityFailedEventDetails :: Lens' HistoryEvent (Maybe ActivityFailedEventDetails)
historyEvent_activityFailedEventDetails = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\HistoryEvent' {Maybe ActivityFailedEventDetails
activityFailedEventDetails :: Maybe ActivityFailedEventDetails
$sel:activityFailedEventDetails:HistoryEvent' :: HistoryEvent -> Maybe ActivityFailedEventDetails
activityFailedEventDetails} -> Maybe ActivityFailedEventDetails
activityFailedEventDetails) (\s :: HistoryEvent
s@HistoryEvent' {} Maybe ActivityFailedEventDetails
a -> HistoryEvent
s {$sel:activityFailedEventDetails:HistoryEvent' :: Maybe ActivityFailedEventDetails
activityFailedEventDetails = Maybe ActivityFailedEventDetails
a} :: HistoryEvent)

-- | Contains details about an activity schedule event that failed during an
-- execution.
historyEvent_activityScheduleFailedEventDetails :: Lens.Lens' HistoryEvent (Prelude.Maybe ActivityScheduleFailedEventDetails)
historyEvent_activityScheduleFailedEventDetails :: Lens' HistoryEvent (Maybe ActivityScheduleFailedEventDetails)
historyEvent_activityScheduleFailedEventDetails = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\HistoryEvent' {Maybe ActivityScheduleFailedEventDetails
activityScheduleFailedEventDetails :: Maybe ActivityScheduleFailedEventDetails
$sel:activityScheduleFailedEventDetails:HistoryEvent' :: HistoryEvent -> Maybe ActivityScheduleFailedEventDetails
activityScheduleFailedEventDetails} -> Maybe ActivityScheduleFailedEventDetails
activityScheduleFailedEventDetails) (\s :: HistoryEvent
s@HistoryEvent' {} Maybe ActivityScheduleFailedEventDetails
a -> HistoryEvent
s {$sel:activityScheduleFailedEventDetails:HistoryEvent' :: Maybe ActivityScheduleFailedEventDetails
activityScheduleFailedEventDetails = Maybe ActivityScheduleFailedEventDetails
a} :: HistoryEvent)

-- | Undocumented member.
historyEvent_activityScheduledEventDetails :: Lens.Lens' HistoryEvent (Prelude.Maybe ActivityScheduledEventDetails)
historyEvent_activityScheduledEventDetails :: Lens' HistoryEvent (Maybe ActivityScheduledEventDetails)
historyEvent_activityScheduledEventDetails = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\HistoryEvent' {Maybe ActivityScheduledEventDetails
activityScheduledEventDetails :: Maybe ActivityScheduledEventDetails
$sel:activityScheduledEventDetails:HistoryEvent' :: HistoryEvent -> Maybe ActivityScheduledEventDetails
activityScheduledEventDetails} -> Maybe ActivityScheduledEventDetails
activityScheduledEventDetails) (\s :: HistoryEvent
s@HistoryEvent' {} Maybe ActivityScheduledEventDetails
a -> HistoryEvent
s {$sel:activityScheduledEventDetails:HistoryEvent' :: Maybe ActivityScheduledEventDetails
activityScheduledEventDetails = Maybe ActivityScheduledEventDetails
a} :: HistoryEvent)

-- | Undocumented member.
historyEvent_activityStartedEventDetails :: Lens.Lens' HistoryEvent (Prelude.Maybe ActivityStartedEventDetails)
historyEvent_activityStartedEventDetails :: Lens' HistoryEvent (Maybe ActivityStartedEventDetails)
historyEvent_activityStartedEventDetails = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\HistoryEvent' {Maybe ActivityStartedEventDetails
activityStartedEventDetails :: Maybe ActivityStartedEventDetails
$sel:activityStartedEventDetails:HistoryEvent' :: HistoryEvent -> Maybe ActivityStartedEventDetails
activityStartedEventDetails} -> Maybe ActivityStartedEventDetails
activityStartedEventDetails) (\s :: HistoryEvent
s@HistoryEvent' {} Maybe ActivityStartedEventDetails
a -> HistoryEvent
s {$sel:activityStartedEventDetails:HistoryEvent' :: Maybe ActivityStartedEventDetails
activityStartedEventDetails = Maybe ActivityStartedEventDetails
a} :: HistoryEvent)

-- | Undocumented member.
historyEvent_activitySucceededEventDetails :: Lens.Lens' HistoryEvent (Prelude.Maybe ActivitySucceededEventDetails)
historyEvent_activitySucceededEventDetails :: Lens' HistoryEvent (Maybe ActivitySucceededEventDetails)
historyEvent_activitySucceededEventDetails = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\HistoryEvent' {Maybe ActivitySucceededEventDetails
activitySucceededEventDetails :: Maybe ActivitySucceededEventDetails
$sel:activitySucceededEventDetails:HistoryEvent' :: HistoryEvent -> Maybe ActivitySucceededEventDetails
activitySucceededEventDetails} -> Maybe ActivitySucceededEventDetails
activitySucceededEventDetails) (\s :: HistoryEvent
s@HistoryEvent' {} Maybe ActivitySucceededEventDetails
a -> HistoryEvent
s {$sel:activitySucceededEventDetails:HistoryEvent' :: Maybe ActivitySucceededEventDetails
activitySucceededEventDetails = Maybe ActivitySucceededEventDetails
a} :: HistoryEvent)

-- | Undocumented member.
historyEvent_activityTimedOutEventDetails :: Lens.Lens' HistoryEvent (Prelude.Maybe ActivityTimedOutEventDetails)
historyEvent_activityTimedOutEventDetails :: Lens' HistoryEvent (Maybe ActivityTimedOutEventDetails)
historyEvent_activityTimedOutEventDetails = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\HistoryEvent' {Maybe ActivityTimedOutEventDetails
activityTimedOutEventDetails :: Maybe ActivityTimedOutEventDetails
$sel:activityTimedOutEventDetails:HistoryEvent' :: HistoryEvent -> Maybe ActivityTimedOutEventDetails
activityTimedOutEventDetails} -> Maybe ActivityTimedOutEventDetails
activityTimedOutEventDetails) (\s :: HistoryEvent
s@HistoryEvent' {} Maybe ActivityTimedOutEventDetails
a -> HistoryEvent
s {$sel:activityTimedOutEventDetails:HistoryEvent' :: Maybe ActivityTimedOutEventDetails
activityTimedOutEventDetails = Maybe ActivityTimedOutEventDetails
a} :: HistoryEvent)

-- | Undocumented member.
historyEvent_executionAbortedEventDetails :: Lens.Lens' HistoryEvent (Prelude.Maybe ExecutionAbortedEventDetails)
historyEvent_executionAbortedEventDetails :: Lens' HistoryEvent (Maybe ExecutionAbortedEventDetails)
historyEvent_executionAbortedEventDetails = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\HistoryEvent' {Maybe ExecutionAbortedEventDetails
executionAbortedEventDetails :: Maybe ExecutionAbortedEventDetails
$sel:executionAbortedEventDetails:HistoryEvent' :: HistoryEvent -> Maybe ExecutionAbortedEventDetails
executionAbortedEventDetails} -> Maybe ExecutionAbortedEventDetails
executionAbortedEventDetails) (\s :: HistoryEvent
s@HistoryEvent' {} Maybe ExecutionAbortedEventDetails
a -> HistoryEvent
s {$sel:executionAbortedEventDetails:HistoryEvent' :: Maybe ExecutionAbortedEventDetails
executionAbortedEventDetails = Maybe ExecutionAbortedEventDetails
a} :: HistoryEvent)

-- | Undocumented member.
historyEvent_executionFailedEventDetails :: Lens.Lens' HistoryEvent (Prelude.Maybe ExecutionFailedEventDetails)
historyEvent_executionFailedEventDetails :: Lens' HistoryEvent (Maybe ExecutionFailedEventDetails)
historyEvent_executionFailedEventDetails = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\HistoryEvent' {Maybe ExecutionFailedEventDetails
executionFailedEventDetails :: Maybe ExecutionFailedEventDetails
$sel:executionFailedEventDetails:HistoryEvent' :: HistoryEvent -> Maybe ExecutionFailedEventDetails
executionFailedEventDetails} -> Maybe ExecutionFailedEventDetails
executionFailedEventDetails) (\s :: HistoryEvent
s@HistoryEvent' {} Maybe ExecutionFailedEventDetails
a -> HistoryEvent
s {$sel:executionFailedEventDetails:HistoryEvent' :: Maybe ExecutionFailedEventDetails
executionFailedEventDetails = Maybe ExecutionFailedEventDetails
a} :: HistoryEvent)

-- | Undocumented member.
historyEvent_executionStartedEventDetails :: Lens.Lens' HistoryEvent (Prelude.Maybe ExecutionStartedEventDetails)
historyEvent_executionStartedEventDetails :: Lens' HistoryEvent (Maybe ExecutionStartedEventDetails)
historyEvent_executionStartedEventDetails = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\HistoryEvent' {Maybe ExecutionStartedEventDetails
executionStartedEventDetails :: Maybe ExecutionStartedEventDetails
$sel:executionStartedEventDetails:HistoryEvent' :: HistoryEvent -> Maybe ExecutionStartedEventDetails
executionStartedEventDetails} -> Maybe ExecutionStartedEventDetails
executionStartedEventDetails) (\s :: HistoryEvent
s@HistoryEvent' {} Maybe ExecutionStartedEventDetails
a -> HistoryEvent
s {$sel:executionStartedEventDetails:HistoryEvent' :: Maybe ExecutionStartedEventDetails
executionStartedEventDetails = Maybe ExecutionStartedEventDetails
a} :: HistoryEvent)

-- | Undocumented member.
historyEvent_executionSucceededEventDetails :: Lens.Lens' HistoryEvent (Prelude.Maybe ExecutionSucceededEventDetails)
historyEvent_executionSucceededEventDetails :: Lens' HistoryEvent (Maybe ExecutionSucceededEventDetails)
historyEvent_executionSucceededEventDetails = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\HistoryEvent' {Maybe ExecutionSucceededEventDetails
executionSucceededEventDetails :: Maybe ExecutionSucceededEventDetails
$sel:executionSucceededEventDetails:HistoryEvent' :: HistoryEvent -> Maybe ExecutionSucceededEventDetails
executionSucceededEventDetails} -> Maybe ExecutionSucceededEventDetails
executionSucceededEventDetails) (\s :: HistoryEvent
s@HistoryEvent' {} Maybe ExecutionSucceededEventDetails
a -> HistoryEvent
s {$sel:executionSucceededEventDetails:HistoryEvent' :: Maybe ExecutionSucceededEventDetails
executionSucceededEventDetails = Maybe ExecutionSucceededEventDetails
a} :: HistoryEvent)

-- | Undocumented member.
historyEvent_executionTimedOutEventDetails :: Lens.Lens' HistoryEvent (Prelude.Maybe ExecutionTimedOutEventDetails)
historyEvent_executionTimedOutEventDetails :: Lens' HistoryEvent (Maybe ExecutionTimedOutEventDetails)
historyEvent_executionTimedOutEventDetails = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\HistoryEvent' {Maybe ExecutionTimedOutEventDetails
executionTimedOutEventDetails :: Maybe ExecutionTimedOutEventDetails
$sel:executionTimedOutEventDetails:HistoryEvent' :: HistoryEvent -> Maybe ExecutionTimedOutEventDetails
executionTimedOutEventDetails} -> Maybe ExecutionTimedOutEventDetails
executionTimedOutEventDetails) (\s :: HistoryEvent
s@HistoryEvent' {} Maybe ExecutionTimedOutEventDetails
a -> HistoryEvent
s {$sel:executionTimedOutEventDetails:HistoryEvent' :: Maybe ExecutionTimedOutEventDetails
executionTimedOutEventDetails = Maybe ExecutionTimedOutEventDetails
a} :: HistoryEvent)

-- | Undocumented member.
historyEvent_lambdaFunctionFailedEventDetails :: Lens.Lens' HistoryEvent (Prelude.Maybe LambdaFunctionFailedEventDetails)
historyEvent_lambdaFunctionFailedEventDetails :: Lens' HistoryEvent (Maybe LambdaFunctionFailedEventDetails)
historyEvent_lambdaFunctionFailedEventDetails = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\HistoryEvent' {Maybe LambdaFunctionFailedEventDetails
lambdaFunctionFailedEventDetails :: Maybe LambdaFunctionFailedEventDetails
$sel:lambdaFunctionFailedEventDetails:HistoryEvent' :: HistoryEvent -> Maybe LambdaFunctionFailedEventDetails
lambdaFunctionFailedEventDetails} -> Maybe LambdaFunctionFailedEventDetails
lambdaFunctionFailedEventDetails) (\s :: HistoryEvent
s@HistoryEvent' {} Maybe LambdaFunctionFailedEventDetails
a -> HistoryEvent
s {$sel:lambdaFunctionFailedEventDetails:HistoryEvent' :: Maybe LambdaFunctionFailedEventDetails
lambdaFunctionFailedEventDetails = Maybe LambdaFunctionFailedEventDetails
a} :: HistoryEvent)

-- | Undocumented member.
historyEvent_lambdaFunctionScheduleFailedEventDetails :: Lens.Lens' HistoryEvent (Prelude.Maybe LambdaFunctionScheduleFailedEventDetails)
historyEvent_lambdaFunctionScheduleFailedEventDetails :: Lens' HistoryEvent (Maybe LambdaFunctionScheduleFailedEventDetails)
historyEvent_lambdaFunctionScheduleFailedEventDetails = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\HistoryEvent' {Maybe LambdaFunctionScheduleFailedEventDetails
lambdaFunctionScheduleFailedEventDetails :: Maybe LambdaFunctionScheduleFailedEventDetails
$sel:lambdaFunctionScheduleFailedEventDetails:HistoryEvent' :: HistoryEvent -> Maybe LambdaFunctionScheduleFailedEventDetails
lambdaFunctionScheduleFailedEventDetails} -> Maybe LambdaFunctionScheduleFailedEventDetails
lambdaFunctionScheduleFailedEventDetails) (\s :: HistoryEvent
s@HistoryEvent' {} Maybe LambdaFunctionScheduleFailedEventDetails
a -> HistoryEvent
s {$sel:lambdaFunctionScheduleFailedEventDetails:HistoryEvent' :: Maybe LambdaFunctionScheduleFailedEventDetails
lambdaFunctionScheduleFailedEventDetails = Maybe LambdaFunctionScheduleFailedEventDetails
a} :: HistoryEvent)

-- | Undocumented member.
historyEvent_lambdaFunctionScheduledEventDetails :: Lens.Lens' HistoryEvent (Prelude.Maybe LambdaFunctionScheduledEventDetails)
historyEvent_lambdaFunctionScheduledEventDetails :: Lens' HistoryEvent (Maybe LambdaFunctionScheduledEventDetails)
historyEvent_lambdaFunctionScheduledEventDetails = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\HistoryEvent' {Maybe LambdaFunctionScheduledEventDetails
lambdaFunctionScheduledEventDetails :: Maybe LambdaFunctionScheduledEventDetails
$sel:lambdaFunctionScheduledEventDetails:HistoryEvent' :: HistoryEvent -> Maybe LambdaFunctionScheduledEventDetails
lambdaFunctionScheduledEventDetails} -> Maybe LambdaFunctionScheduledEventDetails
lambdaFunctionScheduledEventDetails) (\s :: HistoryEvent
s@HistoryEvent' {} Maybe LambdaFunctionScheduledEventDetails
a -> HistoryEvent
s {$sel:lambdaFunctionScheduledEventDetails:HistoryEvent' :: Maybe LambdaFunctionScheduledEventDetails
lambdaFunctionScheduledEventDetails = Maybe LambdaFunctionScheduledEventDetails
a} :: HistoryEvent)

-- | Contains details about a lambda function that failed to start during an
-- execution.
historyEvent_lambdaFunctionStartFailedEventDetails :: Lens.Lens' HistoryEvent (Prelude.Maybe LambdaFunctionStartFailedEventDetails)
historyEvent_lambdaFunctionStartFailedEventDetails :: Lens' HistoryEvent (Maybe LambdaFunctionStartFailedEventDetails)
historyEvent_lambdaFunctionStartFailedEventDetails = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\HistoryEvent' {Maybe LambdaFunctionStartFailedEventDetails
lambdaFunctionStartFailedEventDetails :: Maybe LambdaFunctionStartFailedEventDetails
$sel:lambdaFunctionStartFailedEventDetails:HistoryEvent' :: HistoryEvent -> Maybe LambdaFunctionStartFailedEventDetails
lambdaFunctionStartFailedEventDetails} -> Maybe LambdaFunctionStartFailedEventDetails
lambdaFunctionStartFailedEventDetails) (\s :: HistoryEvent
s@HistoryEvent' {} Maybe LambdaFunctionStartFailedEventDetails
a -> HistoryEvent
s {$sel:lambdaFunctionStartFailedEventDetails:HistoryEvent' :: Maybe LambdaFunctionStartFailedEventDetails
lambdaFunctionStartFailedEventDetails = Maybe LambdaFunctionStartFailedEventDetails
a} :: HistoryEvent)

-- | Contains details about a Lambda function that terminated successfully
-- during an execution.
historyEvent_lambdaFunctionSucceededEventDetails :: Lens.Lens' HistoryEvent (Prelude.Maybe LambdaFunctionSucceededEventDetails)
historyEvent_lambdaFunctionSucceededEventDetails :: Lens' HistoryEvent (Maybe LambdaFunctionSucceededEventDetails)
historyEvent_lambdaFunctionSucceededEventDetails = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\HistoryEvent' {Maybe LambdaFunctionSucceededEventDetails
lambdaFunctionSucceededEventDetails :: Maybe LambdaFunctionSucceededEventDetails
$sel:lambdaFunctionSucceededEventDetails:HistoryEvent' :: HistoryEvent -> Maybe LambdaFunctionSucceededEventDetails
lambdaFunctionSucceededEventDetails} -> Maybe LambdaFunctionSucceededEventDetails
lambdaFunctionSucceededEventDetails) (\s :: HistoryEvent
s@HistoryEvent' {} Maybe LambdaFunctionSucceededEventDetails
a -> HistoryEvent
s {$sel:lambdaFunctionSucceededEventDetails:HistoryEvent' :: Maybe LambdaFunctionSucceededEventDetails
lambdaFunctionSucceededEventDetails = Maybe LambdaFunctionSucceededEventDetails
a} :: HistoryEvent)

-- | Undocumented member.
historyEvent_lambdaFunctionTimedOutEventDetails :: Lens.Lens' HistoryEvent (Prelude.Maybe LambdaFunctionTimedOutEventDetails)
historyEvent_lambdaFunctionTimedOutEventDetails :: Lens' HistoryEvent (Maybe LambdaFunctionTimedOutEventDetails)
historyEvent_lambdaFunctionTimedOutEventDetails = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\HistoryEvent' {Maybe LambdaFunctionTimedOutEventDetails
lambdaFunctionTimedOutEventDetails :: Maybe LambdaFunctionTimedOutEventDetails
$sel:lambdaFunctionTimedOutEventDetails:HistoryEvent' :: HistoryEvent -> Maybe LambdaFunctionTimedOutEventDetails
lambdaFunctionTimedOutEventDetails} -> Maybe LambdaFunctionTimedOutEventDetails
lambdaFunctionTimedOutEventDetails) (\s :: HistoryEvent
s@HistoryEvent' {} Maybe LambdaFunctionTimedOutEventDetails
a -> HistoryEvent
s {$sel:lambdaFunctionTimedOutEventDetails:HistoryEvent' :: Maybe LambdaFunctionTimedOutEventDetails
lambdaFunctionTimedOutEventDetails = Maybe LambdaFunctionTimedOutEventDetails
a} :: HistoryEvent)

-- | Contains details about an iteration of a Map state that was aborted.
historyEvent_mapIterationAbortedEventDetails :: Lens.Lens' HistoryEvent (Prelude.Maybe MapIterationEventDetails)
historyEvent_mapIterationAbortedEventDetails :: Lens' HistoryEvent (Maybe MapIterationEventDetails)
historyEvent_mapIterationAbortedEventDetails = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\HistoryEvent' {Maybe MapIterationEventDetails
mapIterationAbortedEventDetails :: Maybe MapIterationEventDetails
$sel:mapIterationAbortedEventDetails:HistoryEvent' :: HistoryEvent -> Maybe MapIterationEventDetails
mapIterationAbortedEventDetails} -> Maybe MapIterationEventDetails
mapIterationAbortedEventDetails) (\s :: HistoryEvent
s@HistoryEvent' {} Maybe MapIterationEventDetails
a -> HistoryEvent
s {$sel:mapIterationAbortedEventDetails:HistoryEvent' :: Maybe MapIterationEventDetails
mapIterationAbortedEventDetails = Maybe MapIterationEventDetails
a} :: HistoryEvent)

-- | Contains details about an iteration of a Map state that failed.
historyEvent_mapIterationFailedEventDetails :: Lens.Lens' HistoryEvent (Prelude.Maybe MapIterationEventDetails)
historyEvent_mapIterationFailedEventDetails :: Lens' HistoryEvent (Maybe MapIterationEventDetails)
historyEvent_mapIterationFailedEventDetails = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\HistoryEvent' {Maybe MapIterationEventDetails
mapIterationFailedEventDetails :: Maybe MapIterationEventDetails
$sel:mapIterationFailedEventDetails:HistoryEvent' :: HistoryEvent -> Maybe MapIterationEventDetails
mapIterationFailedEventDetails} -> Maybe MapIterationEventDetails
mapIterationFailedEventDetails) (\s :: HistoryEvent
s@HistoryEvent' {} Maybe MapIterationEventDetails
a -> HistoryEvent
s {$sel:mapIterationFailedEventDetails:HistoryEvent' :: Maybe MapIterationEventDetails
mapIterationFailedEventDetails = Maybe MapIterationEventDetails
a} :: HistoryEvent)

-- | Contains details about an iteration of a Map state that was started.
historyEvent_mapIterationStartedEventDetails :: Lens.Lens' HistoryEvent (Prelude.Maybe MapIterationEventDetails)
historyEvent_mapIterationStartedEventDetails :: Lens' HistoryEvent (Maybe MapIterationEventDetails)
historyEvent_mapIterationStartedEventDetails = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\HistoryEvent' {Maybe MapIterationEventDetails
mapIterationStartedEventDetails :: Maybe MapIterationEventDetails
$sel:mapIterationStartedEventDetails:HistoryEvent' :: HistoryEvent -> Maybe MapIterationEventDetails
mapIterationStartedEventDetails} -> Maybe MapIterationEventDetails
mapIterationStartedEventDetails) (\s :: HistoryEvent
s@HistoryEvent' {} Maybe MapIterationEventDetails
a -> HistoryEvent
s {$sel:mapIterationStartedEventDetails:HistoryEvent' :: Maybe MapIterationEventDetails
mapIterationStartedEventDetails = Maybe MapIterationEventDetails
a} :: HistoryEvent)

-- | Contains details about an iteration of a Map state that succeeded.
historyEvent_mapIterationSucceededEventDetails :: Lens.Lens' HistoryEvent (Prelude.Maybe MapIterationEventDetails)
historyEvent_mapIterationSucceededEventDetails :: Lens' HistoryEvent (Maybe MapIterationEventDetails)
historyEvent_mapIterationSucceededEventDetails = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\HistoryEvent' {Maybe MapIterationEventDetails
mapIterationSucceededEventDetails :: Maybe MapIterationEventDetails
$sel:mapIterationSucceededEventDetails:HistoryEvent' :: HistoryEvent -> Maybe MapIterationEventDetails
mapIterationSucceededEventDetails} -> Maybe MapIterationEventDetails
mapIterationSucceededEventDetails) (\s :: HistoryEvent
s@HistoryEvent' {} Maybe MapIterationEventDetails
a -> HistoryEvent
s {$sel:mapIterationSucceededEventDetails:HistoryEvent' :: Maybe MapIterationEventDetails
mapIterationSucceededEventDetails = Maybe MapIterationEventDetails
a} :: HistoryEvent)

-- | Contains error and cause details about a Map Run that failed.
historyEvent_mapRunFailedEventDetails :: Lens.Lens' HistoryEvent (Prelude.Maybe MapRunFailedEventDetails)
historyEvent_mapRunFailedEventDetails :: Lens' HistoryEvent (Maybe MapRunFailedEventDetails)
historyEvent_mapRunFailedEventDetails = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\HistoryEvent' {Maybe MapRunFailedEventDetails
mapRunFailedEventDetails :: Maybe MapRunFailedEventDetails
$sel:mapRunFailedEventDetails:HistoryEvent' :: HistoryEvent -> Maybe MapRunFailedEventDetails
mapRunFailedEventDetails} -> Maybe MapRunFailedEventDetails
mapRunFailedEventDetails) (\s :: HistoryEvent
s@HistoryEvent' {} Maybe MapRunFailedEventDetails
a -> HistoryEvent
s {$sel:mapRunFailedEventDetails:HistoryEvent' :: Maybe MapRunFailedEventDetails
mapRunFailedEventDetails = Maybe MapRunFailedEventDetails
a} :: HistoryEvent)

-- | Contains details, such as @mapRunArn@, and the start date and time of a
-- Map Run. @mapRunArn@ is the Amazon Resource Name (ARN) of the Map Run
-- that was started.
historyEvent_mapRunStartedEventDetails :: Lens.Lens' HistoryEvent (Prelude.Maybe MapRunStartedEventDetails)
historyEvent_mapRunStartedEventDetails :: Lens' HistoryEvent (Maybe MapRunStartedEventDetails)
historyEvent_mapRunStartedEventDetails = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\HistoryEvent' {Maybe MapRunStartedEventDetails
mapRunStartedEventDetails :: Maybe MapRunStartedEventDetails
$sel:mapRunStartedEventDetails:HistoryEvent' :: HistoryEvent -> Maybe MapRunStartedEventDetails
mapRunStartedEventDetails} -> Maybe MapRunStartedEventDetails
mapRunStartedEventDetails) (\s :: HistoryEvent
s@HistoryEvent' {} Maybe MapRunStartedEventDetails
a -> HistoryEvent
s {$sel:mapRunStartedEventDetails:HistoryEvent' :: Maybe MapRunStartedEventDetails
mapRunStartedEventDetails = Maybe MapRunStartedEventDetails
a} :: HistoryEvent)

-- | Contains details about Map state that was started.
historyEvent_mapStateStartedEventDetails :: Lens.Lens' HistoryEvent (Prelude.Maybe MapStateStartedEventDetails)
historyEvent_mapStateStartedEventDetails :: Lens' HistoryEvent (Maybe MapStateStartedEventDetails)
historyEvent_mapStateStartedEventDetails = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\HistoryEvent' {Maybe MapStateStartedEventDetails
mapStateStartedEventDetails :: Maybe MapStateStartedEventDetails
$sel:mapStateStartedEventDetails:HistoryEvent' :: HistoryEvent -> Maybe MapStateStartedEventDetails
mapStateStartedEventDetails} -> Maybe MapStateStartedEventDetails
mapStateStartedEventDetails) (\s :: HistoryEvent
s@HistoryEvent' {} Maybe MapStateStartedEventDetails
a -> HistoryEvent
s {$sel:mapStateStartedEventDetails:HistoryEvent' :: Maybe MapStateStartedEventDetails
mapStateStartedEventDetails = Maybe MapStateStartedEventDetails
a} :: HistoryEvent)

-- | The id of the previous event.
historyEvent_previousEventId :: Lens.Lens' HistoryEvent (Prelude.Maybe Prelude.Integer)
historyEvent_previousEventId :: Lens' HistoryEvent (Maybe Integer)
historyEvent_previousEventId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\HistoryEvent' {Maybe Integer
previousEventId :: Maybe Integer
$sel:previousEventId:HistoryEvent' :: HistoryEvent -> Maybe Integer
previousEventId} -> Maybe Integer
previousEventId) (\s :: HistoryEvent
s@HistoryEvent' {} Maybe Integer
a -> HistoryEvent
s {$sel:previousEventId:HistoryEvent' :: Maybe Integer
previousEventId = Maybe Integer
a} :: HistoryEvent)

-- | Undocumented member.
historyEvent_stateEnteredEventDetails :: Lens.Lens' HistoryEvent (Prelude.Maybe StateEnteredEventDetails)
historyEvent_stateEnteredEventDetails :: Lens' HistoryEvent (Maybe StateEnteredEventDetails)
historyEvent_stateEnteredEventDetails = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\HistoryEvent' {Maybe StateEnteredEventDetails
stateEnteredEventDetails :: Maybe StateEnteredEventDetails
$sel:stateEnteredEventDetails:HistoryEvent' :: HistoryEvent -> Maybe StateEnteredEventDetails
stateEnteredEventDetails} -> Maybe StateEnteredEventDetails
stateEnteredEventDetails) (\s :: HistoryEvent
s@HistoryEvent' {} Maybe StateEnteredEventDetails
a -> HistoryEvent
s {$sel:stateEnteredEventDetails:HistoryEvent' :: Maybe StateEnteredEventDetails
stateEnteredEventDetails = Maybe StateEnteredEventDetails
a} :: HistoryEvent)

-- | Undocumented member.
historyEvent_stateExitedEventDetails :: Lens.Lens' HistoryEvent (Prelude.Maybe StateExitedEventDetails)
historyEvent_stateExitedEventDetails :: Lens' HistoryEvent (Maybe StateExitedEventDetails)
historyEvent_stateExitedEventDetails = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\HistoryEvent' {Maybe StateExitedEventDetails
stateExitedEventDetails :: Maybe StateExitedEventDetails
$sel:stateExitedEventDetails:HistoryEvent' :: HistoryEvent -> Maybe StateExitedEventDetails
stateExitedEventDetails} -> Maybe StateExitedEventDetails
stateExitedEventDetails) (\s :: HistoryEvent
s@HistoryEvent' {} Maybe StateExitedEventDetails
a -> HistoryEvent
s {$sel:stateExitedEventDetails:HistoryEvent' :: Maybe StateExitedEventDetails
stateExitedEventDetails = Maybe StateExitedEventDetails
a} :: HistoryEvent)

-- | Contains details about the failure of a task.
historyEvent_taskFailedEventDetails :: Lens.Lens' HistoryEvent (Prelude.Maybe TaskFailedEventDetails)
historyEvent_taskFailedEventDetails :: Lens' HistoryEvent (Maybe TaskFailedEventDetails)
historyEvent_taskFailedEventDetails = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\HistoryEvent' {Maybe TaskFailedEventDetails
taskFailedEventDetails :: Maybe TaskFailedEventDetails
$sel:taskFailedEventDetails:HistoryEvent' :: HistoryEvent -> Maybe TaskFailedEventDetails
taskFailedEventDetails} -> Maybe TaskFailedEventDetails
taskFailedEventDetails) (\s :: HistoryEvent
s@HistoryEvent' {} Maybe TaskFailedEventDetails
a -> HistoryEvent
s {$sel:taskFailedEventDetails:HistoryEvent' :: Maybe TaskFailedEventDetails
taskFailedEventDetails = Maybe TaskFailedEventDetails
a} :: HistoryEvent)

-- | Contains details about a task that was scheduled.
historyEvent_taskScheduledEventDetails :: Lens.Lens' HistoryEvent (Prelude.Maybe TaskScheduledEventDetails)
historyEvent_taskScheduledEventDetails :: Lens' HistoryEvent (Maybe TaskScheduledEventDetails)
historyEvent_taskScheduledEventDetails = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\HistoryEvent' {Maybe TaskScheduledEventDetails
taskScheduledEventDetails :: Maybe TaskScheduledEventDetails
$sel:taskScheduledEventDetails:HistoryEvent' :: HistoryEvent -> Maybe TaskScheduledEventDetails
taskScheduledEventDetails} -> Maybe TaskScheduledEventDetails
taskScheduledEventDetails) (\s :: HistoryEvent
s@HistoryEvent' {} Maybe TaskScheduledEventDetails
a -> HistoryEvent
s {$sel:taskScheduledEventDetails:HistoryEvent' :: Maybe TaskScheduledEventDetails
taskScheduledEventDetails = Maybe TaskScheduledEventDetails
a} :: HistoryEvent)

-- | Contains details about a task that failed to start.
historyEvent_taskStartFailedEventDetails :: Lens.Lens' HistoryEvent (Prelude.Maybe TaskStartFailedEventDetails)
historyEvent_taskStartFailedEventDetails :: Lens' HistoryEvent (Maybe TaskStartFailedEventDetails)
historyEvent_taskStartFailedEventDetails = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\HistoryEvent' {Maybe TaskStartFailedEventDetails
taskStartFailedEventDetails :: Maybe TaskStartFailedEventDetails
$sel:taskStartFailedEventDetails:HistoryEvent' :: HistoryEvent -> Maybe TaskStartFailedEventDetails
taskStartFailedEventDetails} -> Maybe TaskStartFailedEventDetails
taskStartFailedEventDetails) (\s :: HistoryEvent
s@HistoryEvent' {} Maybe TaskStartFailedEventDetails
a -> HistoryEvent
s {$sel:taskStartFailedEventDetails:HistoryEvent' :: Maybe TaskStartFailedEventDetails
taskStartFailedEventDetails = Maybe TaskStartFailedEventDetails
a} :: HistoryEvent)

-- | Contains details about a task that was started.
historyEvent_taskStartedEventDetails :: Lens.Lens' HistoryEvent (Prelude.Maybe TaskStartedEventDetails)
historyEvent_taskStartedEventDetails :: Lens' HistoryEvent (Maybe TaskStartedEventDetails)
historyEvent_taskStartedEventDetails = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\HistoryEvent' {Maybe TaskStartedEventDetails
taskStartedEventDetails :: Maybe TaskStartedEventDetails
$sel:taskStartedEventDetails:HistoryEvent' :: HistoryEvent -> Maybe TaskStartedEventDetails
taskStartedEventDetails} -> Maybe TaskStartedEventDetails
taskStartedEventDetails) (\s :: HistoryEvent
s@HistoryEvent' {} Maybe TaskStartedEventDetails
a -> HistoryEvent
s {$sel:taskStartedEventDetails:HistoryEvent' :: Maybe TaskStartedEventDetails
taskStartedEventDetails = Maybe TaskStartedEventDetails
a} :: HistoryEvent)

-- | Contains details about a task that where the submit failed.
historyEvent_taskSubmitFailedEventDetails :: Lens.Lens' HistoryEvent (Prelude.Maybe TaskSubmitFailedEventDetails)
historyEvent_taskSubmitFailedEventDetails :: Lens' HistoryEvent (Maybe TaskSubmitFailedEventDetails)
historyEvent_taskSubmitFailedEventDetails = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\HistoryEvent' {Maybe TaskSubmitFailedEventDetails
taskSubmitFailedEventDetails :: Maybe TaskSubmitFailedEventDetails
$sel:taskSubmitFailedEventDetails:HistoryEvent' :: HistoryEvent -> Maybe TaskSubmitFailedEventDetails
taskSubmitFailedEventDetails} -> Maybe TaskSubmitFailedEventDetails
taskSubmitFailedEventDetails) (\s :: HistoryEvent
s@HistoryEvent' {} Maybe TaskSubmitFailedEventDetails
a -> HistoryEvent
s {$sel:taskSubmitFailedEventDetails:HistoryEvent' :: Maybe TaskSubmitFailedEventDetails
taskSubmitFailedEventDetails = Maybe TaskSubmitFailedEventDetails
a} :: HistoryEvent)

-- | Contains details about a submitted task.
historyEvent_taskSubmittedEventDetails :: Lens.Lens' HistoryEvent (Prelude.Maybe TaskSubmittedEventDetails)
historyEvent_taskSubmittedEventDetails :: Lens' HistoryEvent (Maybe TaskSubmittedEventDetails)
historyEvent_taskSubmittedEventDetails = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\HistoryEvent' {Maybe TaskSubmittedEventDetails
taskSubmittedEventDetails :: Maybe TaskSubmittedEventDetails
$sel:taskSubmittedEventDetails:HistoryEvent' :: HistoryEvent -> Maybe TaskSubmittedEventDetails
taskSubmittedEventDetails} -> Maybe TaskSubmittedEventDetails
taskSubmittedEventDetails) (\s :: HistoryEvent
s@HistoryEvent' {} Maybe TaskSubmittedEventDetails
a -> HistoryEvent
s {$sel:taskSubmittedEventDetails:HistoryEvent' :: Maybe TaskSubmittedEventDetails
taskSubmittedEventDetails = Maybe TaskSubmittedEventDetails
a} :: HistoryEvent)

-- | Contains details about a task that succeeded.
historyEvent_taskSucceededEventDetails :: Lens.Lens' HistoryEvent (Prelude.Maybe TaskSucceededEventDetails)
historyEvent_taskSucceededEventDetails :: Lens' HistoryEvent (Maybe TaskSucceededEventDetails)
historyEvent_taskSucceededEventDetails = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\HistoryEvent' {Maybe TaskSucceededEventDetails
taskSucceededEventDetails :: Maybe TaskSucceededEventDetails
$sel:taskSucceededEventDetails:HistoryEvent' :: HistoryEvent -> Maybe TaskSucceededEventDetails
taskSucceededEventDetails} -> Maybe TaskSucceededEventDetails
taskSucceededEventDetails) (\s :: HistoryEvent
s@HistoryEvent' {} Maybe TaskSucceededEventDetails
a -> HistoryEvent
s {$sel:taskSucceededEventDetails:HistoryEvent' :: Maybe TaskSucceededEventDetails
taskSucceededEventDetails = Maybe TaskSucceededEventDetails
a} :: HistoryEvent)

-- | Contains details about a task that timed out.
historyEvent_taskTimedOutEventDetails :: Lens.Lens' HistoryEvent (Prelude.Maybe TaskTimedOutEventDetails)
historyEvent_taskTimedOutEventDetails :: Lens' HistoryEvent (Maybe TaskTimedOutEventDetails)
historyEvent_taskTimedOutEventDetails = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\HistoryEvent' {Maybe TaskTimedOutEventDetails
taskTimedOutEventDetails :: Maybe TaskTimedOutEventDetails
$sel:taskTimedOutEventDetails:HistoryEvent' :: HistoryEvent -> Maybe TaskTimedOutEventDetails
taskTimedOutEventDetails} -> Maybe TaskTimedOutEventDetails
taskTimedOutEventDetails) (\s :: HistoryEvent
s@HistoryEvent' {} Maybe TaskTimedOutEventDetails
a -> HistoryEvent
s {$sel:taskTimedOutEventDetails:HistoryEvent' :: Maybe TaskTimedOutEventDetails
taskTimedOutEventDetails = Maybe TaskTimedOutEventDetails
a} :: HistoryEvent)

-- | The date and time the event occurred.
historyEvent_timestamp :: Lens.Lens' HistoryEvent Prelude.UTCTime
historyEvent_timestamp :: Lens' HistoryEvent UTCTime
historyEvent_timestamp = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\HistoryEvent' {POSIX
timestamp :: POSIX
$sel:timestamp:HistoryEvent' :: HistoryEvent -> POSIX
timestamp} -> POSIX
timestamp) (\s :: HistoryEvent
s@HistoryEvent' {} POSIX
a -> HistoryEvent
s {$sel:timestamp:HistoryEvent' :: POSIX
timestamp = POSIX
a} :: HistoryEvent) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (a :: Format). Iso' (Time a) UTCTime
Data._Time

-- | The type of the event.
historyEvent_type :: Lens.Lens' HistoryEvent HistoryEventType
historyEvent_type :: Lens' HistoryEvent HistoryEventType
historyEvent_type = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\HistoryEvent' {HistoryEventType
type' :: HistoryEventType
$sel:type':HistoryEvent' :: HistoryEvent -> HistoryEventType
type'} -> HistoryEventType
type') (\s :: HistoryEvent
s@HistoryEvent' {} HistoryEventType
a -> HistoryEvent
s {$sel:type':HistoryEvent' :: HistoryEventType
type' = HistoryEventType
a} :: HistoryEvent)

-- | The id of the event. Events are numbered sequentially, starting at one.
historyEvent_id :: Lens.Lens' HistoryEvent Prelude.Integer
historyEvent_id :: Lens' HistoryEvent Integer
historyEvent_id = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\HistoryEvent' {Integer
id :: Integer
$sel:id:HistoryEvent' :: HistoryEvent -> Integer
id} -> Integer
id) (\s :: HistoryEvent
s@HistoryEvent' {} Integer
a -> HistoryEvent
s {$sel:id:HistoryEvent' :: Integer
id = Integer
a} :: HistoryEvent)

instance Data.FromJSON HistoryEvent where
  parseJSON :: Value -> Parser HistoryEvent
parseJSON =
    forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.withObject
      String
"HistoryEvent"
      ( \Object
x ->
          Maybe ActivityFailedEventDetails
-> Maybe ActivityScheduleFailedEventDetails
-> Maybe ActivityScheduledEventDetails
-> Maybe ActivityStartedEventDetails
-> Maybe ActivitySucceededEventDetails
-> Maybe ActivityTimedOutEventDetails
-> Maybe ExecutionAbortedEventDetails
-> Maybe ExecutionFailedEventDetails
-> Maybe ExecutionStartedEventDetails
-> Maybe ExecutionSucceededEventDetails
-> Maybe ExecutionTimedOutEventDetails
-> Maybe LambdaFunctionFailedEventDetails
-> Maybe LambdaFunctionScheduleFailedEventDetails
-> Maybe LambdaFunctionScheduledEventDetails
-> Maybe LambdaFunctionStartFailedEventDetails
-> Maybe LambdaFunctionSucceededEventDetails
-> Maybe LambdaFunctionTimedOutEventDetails
-> Maybe MapIterationEventDetails
-> Maybe MapIterationEventDetails
-> Maybe MapIterationEventDetails
-> Maybe MapIterationEventDetails
-> Maybe MapRunFailedEventDetails
-> Maybe MapRunStartedEventDetails
-> Maybe MapStateStartedEventDetails
-> Maybe Integer
-> Maybe StateEnteredEventDetails
-> Maybe StateExitedEventDetails
-> Maybe TaskFailedEventDetails
-> Maybe TaskScheduledEventDetails
-> Maybe TaskStartFailedEventDetails
-> Maybe TaskStartedEventDetails
-> Maybe TaskSubmitFailedEventDetails
-> Maybe TaskSubmittedEventDetails
-> Maybe TaskSucceededEventDetails
-> Maybe TaskTimedOutEventDetails
-> POSIX
-> HistoryEventType
-> Integer
-> HistoryEvent
HistoryEvent'
            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
"activityFailedEventDetails")
            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
"activityScheduleFailedEventDetails")
            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
"activityScheduledEventDetails")
            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
"activityStartedEventDetails")
            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
"activitySucceededEventDetails")
            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
"activityTimedOutEventDetails")
            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
"executionAbortedEventDetails")
            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
"executionFailedEventDetails")
            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
"executionStartedEventDetails")
            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
"executionSucceededEventDetails")
            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
"executionTimedOutEventDetails")
            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
"lambdaFunctionFailedEventDetails")
            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
"lambdaFunctionScheduleFailedEventDetails"
                        )
            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
"lambdaFunctionScheduledEventDetails")
            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
"lambdaFunctionStartFailedEventDetails")
            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
"lambdaFunctionSucceededEventDetails")
            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
"lambdaFunctionTimedOutEventDetails")
            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
"mapIterationAbortedEventDetails")
            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
"mapIterationFailedEventDetails")
            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
"mapIterationStartedEventDetails")
            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
"mapIterationSucceededEventDetails")
            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
"mapRunFailedEventDetails")
            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
"mapRunStartedEventDetails")
            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
"mapStateStartedEventDetails")
            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
"previousEventId")
            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
"stateEnteredEventDetails")
            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
"stateExitedEventDetails")
            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
"taskFailedEventDetails")
            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
"taskScheduledEventDetails")
            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
"taskStartFailedEventDetails")
            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
"taskStartedEventDetails")
            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
"taskSubmitFailedEventDetails")
            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
"taskSubmittedEventDetails")
            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
"taskSucceededEventDetails")
            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
"taskTimedOutEventDetails")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser a
Data..: Key
"timestamp")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser a
Data..: Key
"type")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser a
Data..: Key
"id")
      )

instance Prelude.Hashable HistoryEvent where
  hashWithSalt :: Int -> HistoryEvent -> Int
hashWithSalt Int
_salt HistoryEvent' {Integer
Maybe Integer
Maybe ActivityFailedEventDetails
Maybe ActivityScheduleFailedEventDetails
Maybe ActivityStartedEventDetails
Maybe ActivityTimedOutEventDetails
Maybe ExecutionAbortedEventDetails
Maybe ExecutionFailedEventDetails
Maybe ExecutionTimedOutEventDetails
Maybe ExecutionSucceededEventDetails
Maybe ExecutionStartedEventDetails
Maybe ActivitySucceededEventDetails
Maybe ActivityScheduledEventDetails
Maybe LambdaFunctionFailedEventDetails
Maybe LambdaFunctionScheduleFailedEventDetails
Maybe LambdaFunctionStartFailedEventDetails
Maybe LambdaFunctionSucceededEventDetails
Maybe LambdaFunctionTimedOutEventDetails
Maybe MapIterationEventDetails
Maybe MapRunFailedEventDetails
Maybe MapRunStartedEventDetails
Maybe MapStateStartedEventDetails
Maybe StateEnteredEventDetails
Maybe StateExitedEventDetails
Maybe LambdaFunctionScheduledEventDetails
Maybe TaskFailedEventDetails
Maybe TaskScheduledEventDetails
Maybe TaskStartFailedEventDetails
Maybe TaskStartedEventDetails
Maybe TaskSubmitFailedEventDetails
Maybe TaskSubmittedEventDetails
Maybe TaskSucceededEventDetails
Maybe TaskTimedOutEventDetails
POSIX
HistoryEventType
id :: Integer
type' :: HistoryEventType
timestamp :: POSIX
taskTimedOutEventDetails :: Maybe TaskTimedOutEventDetails
taskSucceededEventDetails :: Maybe TaskSucceededEventDetails
taskSubmittedEventDetails :: Maybe TaskSubmittedEventDetails
taskSubmitFailedEventDetails :: Maybe TaskSubmitFailedEventDetails
taskStartedEventDetails :: Maybe TaskStartedEventDetails
taskStartFailedEventDetails :: Maybe TaskStartFailedEventDetails
taskScheduledEventDetails :: Maybe TaskScheduledEventDetails
taskFailedEventDetails :: Maybe TaskFailedEventDetails
stateExitedEventDetails :: Maybe StateExitedEventDetails
stateEnteredEventDetails :: Maybe StateEnteredEventDetails
previousEventId :: Maybe Integer
mapStateStartedEventDetails :: Maybe MapStateStartedEventDetails
mapRunStartedEventDetails :: Maybe MapRunStartedEventDetails
mapRunFailedEventDetails :: Maybe MapRunFailedEventDetails
mapIterationSucceededEventDetails :: Maybe MapIterationEventDetails
mapIterationStartedEventDetails :: Maybe MapIterationEventDetails
mapIterationFailedEventDetails :: Maybe MapIterationEventDetails
mapIterationAbortedEventDetails :: Maybe MapIterationEventDetails
lambdaFunctionTimedOutEventDetails :: Maybe LambdaFunctionTimedOutEventDetails
lambdaFunctionSucceededEventDetails :: Maybe LambdaFunctionSucceededEventDetails
lambdaFunctionStartFailedEventDetails :: Maybe LambdaFunctionStartFailedEventDetails
lambdaFunctionScheduledEventDetails :: Maybe LambdaFunctionScheduledEventDetails
lambdaFunctionScheduleFailedEventDetails :: Maybe LambdaFunctionScheduleFailedEventDetails
lambdaFunctionFailedEventDetails :: Maybe LambdaFunctionFailedEventDetails
executionTimedOutEventDetails :: Maybe ExecutionTimedOutEventDetails
executionSucceededEventDetails :: Maybe ExecutionSucceededEventDetails
executionStartedEventDetails :: Maybe ExecutionStartedEventDetails
executionFailedEventDetails :: Maybe ExecutionFailedEventDetails
executionAbortedEventDetails :: Maybe ExecutionAbortedEventDetails
activityTimedOutEventDetails :: Maybe ActivityTimedOutEventDetails
activitySucceededEventDetails :: Maybe ActivitySucceededEventDetails
activityStartedEventDetails :: Maybe ActivityStartedEventDetails
activityScheduledEventDetails :: Maybe ActivityScheduledEventDetails
activityScheduleFailedEventDetails :: Maybe ActivityScheduleFailedEventDetails
activityFailedEventDetails :: Maybe ActivityFailedEventDetails
$sel:id:HistoryEvent' :: HistoryEvent -> Integer
$sel:type':HistoryEvent' :: HistoryEvent -> HistoryEventType
$sel:timestamp:HistoryEvent' :: HistoryEvent -> POSIX
$sel:taskTimedOutEventDetails:HistoryEvent' :: HistoryEvent -> Maybe TaskTimedOutEventDetails
$sel:taskSucceededEventDetails:HistoryEvent' :: HistoryEvent -> Maybe TaskSucceededEventDetails
$sel:taskSubmittedEventDetails:HistoryEvent' :: HistoryEvent -> Maybe TaskSubmittedEventDetails
$sel:taskSubmitFailedEventDetails:HistoryEvent' :: HistoryEvent -> Maybe TaskSubmitFailedEventDetails
$sel:taskStartedEventDetails:HistoryEvent' :: HistoryEvent -> Maybe TaskStartedEventDetails
$sel:taskStartFailedEventDetails:HistoryEvent' :: HistoryEvent -> Maybe TaskStartFailedEventDetails
$sel:taskScheduledEventDetails:HistoryEvent' :: HistoryEvent -> Maybe TaskScheduledEventDetails
$sel:taskFailedEventDetails:HistoryEvent' :: HistoryEvent -> Maybe TaskFailedEventDetails
$sel:stateExitedEventDetails:HistoryEvent' :: HistoryEvent -> Maybe StateExitedEventDetails
$sel:stateEnteredEventDetails:HistoryEvent' :: HistoryEvent -> Maybe StateEnteredEventDetails
$sel:previousEventId:HistoryEvent' :: HistoryEvent -> Maybe Integer
$sel:mapStateStartedEventDetails:HistoryEvent' :: HistoryEvent -> Maybe MapStateStartedEventDetails
$sel:mapRunStartedEventDetails:HistoryEvent' :: HistoryEvent -> Maybe MapRunStartedEventDetails
$sel:mapRunFailedEventDetails:HistoryEvent' :: HistoryEvent -> Maybe MapRunFailedEventDetails
$sel:mapIterationSucceededEventDetails:HistoryEvent' :: HistoryEvent -> Maybe MapIterationEventDetails
$sel:mapIterationStartedEventDetails:HistoryEvent' :: HistoryEvent -> Maybe MapIterationEventDetails
$sel:mapIterationFailedEventDetails:HistoryEvent' :: HistoryEvent -> Maybe MapIterationEventDetails
$sel:mapIterationAbortedEventDetails:HistoryEvent' :: HistoryEvent -> Maybe MapIterationEventDetails
$sel:lambdaFunctionTimedOutEventDetails:HistoryEvent' :: HistoryEvent -> Maybe LambdaFunctionTimedOutEventDetails
$sel:lambdaFunctionSucceededEventDetails:HistoryEvent' :: HistoryEvent -> Maybe LambdaFunctionSucceededEventDetails
$sel:lambdaFunctionStartFailedEventDetails:HistoryEvent' :: HistoryEvent -> Maybe LambdaFunctionStartFailedEventDetails
$sel:lambdaFunctionScheduledEventDetails:HistoryEvent' :: HistoryEvent -> Maybe LambdaFunctionScheduledEventDetails
$sel:lambdaFunctionScheduleFailedEventDetails:HistoryEvent' :: HistoryEvent -> Maybe LambdaFunctionScheduleFailedEventDetails
$sel:lambdaFunctionFailedEventDetails:HistoryEvent' :: HistoryEvent -> Maybe LambdaFunctionFailedEventDetails
$sel:executionTimedOutEventDetails:HistoryEvent' :: HistoryEvent -> Maybe ExecutionTimedOutEventDetails
$sel:executionSucceededEventDetails:HistoryEvent' :: HistoryEvent -> Maybe ExecutionSucceededEventDetails
$sel:executionStartedEventDetails:HistoryEvent' :: HistoryEvent -> Maybe ExecutionStartedEventDetails
$sel:executionFailedEventDetails:HistoryEvent' :: HistoryEvent -> Maybe ExecutionFailedEventDetails
$sel:executionAbortedEventDetails:HistoryEvent' :: HistoryEvent -> Maybe ExecutionAbortedEventDetails
$sel:activityTimedOutEventDetails:HistoryEvent' :: HistoryEvent -> Maybe ActivityTimedOutEventDetails
$sel:activitySucceededEventDetails:HistoryEvent' :: HistoryEvent -> Maybe ActivitySucceededEventDetails
$sel:activityStartedEventDetails:HistoryEvent' :: HistoryEvent -> Maybe ActivityStartedEventDetails
$sel:activityScheduledEventDetails:HistoryEvent' :: HistoryEvent -> Maybe ActivityScheduledEventDetails
$sel:activityScheduleFailedEventDetails:HistoryEvent' :: HistoryEvent -> Maybe ActivityScheduleFailedEventDetails
$sel:activityFailedEventDetails:HistoryEvent' :: HistoryEvent -> Maybe ActivityFailedEventDetails
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ActivityFailedEventDetails
activityFailedEventDetails
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ActivityScheduleFailedEventDetails
activityScheduleFailedEventDetails
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ActivityScheduledEventDetails
activityScheduledEventDetails
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ActivityStartedEventDetails
activityStartedEventDetails
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ActivitySucceededEventDetails
activitySucceededEventDetails
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ActivityTimedOutEventDetails
activityTimedOutEventDetails
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ExecutionAbortedEventDetails
executionAbortedEventDetails
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ExecutionFailedEventDetails
executionFailedEventDetails
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ExecutionStartedEventDetails
executionStartedEventDetails
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ExecutionSucceededEventDetails
executionSucceededEventDetails
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ExecutionTimedOutEventDetails
executionTimedOutEventDetails
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe LambdaFunctionFailedEventDetails
lambdaFunctionFailedEventDetails
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe LambdaFunctionScheduleFailedEventDetails
lambdaFunctionScheduleFailedEventDetails
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe LambdaFunctionScheduledEventDetails
lambdaFunctionScheduledEventDetails
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe LambdaFunctionStartFailedEventDetails
lambdaFunctionStartFailedEventDetails
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe LambdaFunctionSucceededEventDetails
lambdaFunctionSucceededEventDetails
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe LambdaFunctionTimedOutEventDetails
lambdaFunctionTimedOutEventDetails
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe MapIterationEventDetails
mapIterationAbortedEventDetails
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe MapIterationEventDetails
mapIterationFailedEventDetails
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe MapIterationEventDetails
mapIterationStartedEventDetails
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe MapIterationEventDetails
mapIterationSucceededEventDetails
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe MapRunFailedEventDetails
mapRunFailedEventDetails
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe MapRunStartedEventDetails
mapRunStartedEventDetails
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe MapStateStartedEventDetails
mapStateStartedEventDetails
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Integer
previousEventId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe StateEnteredEventDetails
stateEnteredEventDetails
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe StateExitedEventDetails
stateExitedEventDetails
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe TaskFailedEventDetails
taskFailedEventDetails
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe TaskScheduledEventDetails
taskScheduledEventDetails
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe TaskStartFailedEventDetails
taskStartFailedEventDetails
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe TaskStartedEventDetails
taskStartedEventDetails
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe TaskSubmitFailedEventDetails
taskSubmitFailedEventDetails
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe TaskSubmittedEventDetails
taskSubmittedEventDetails
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe TaskSucceededEventDetails
taskSucceededEventDetails
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe TaskTimedOutEventDetails
taskTimedOutEventDetails
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` POSIX
timestamp
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` HistoryEventType
type'
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Integer
id

instance Prelude.NFData HistoryEvent where
  rnf :: HistoryEvent -> ()
rnf HistoryEvent' {Integer
Maybe Integer
Maybe ActivityFailedEventDetails
Maybe ActivityScheduleFailedEventDetails
Maybe ActivityStartedEventDetails
Maybe ActivityTimedOutEventDetails
Maybe ExecutionAbortedEventDetails
Maybe ExecutionFailedEventDetails
Maybe ExecutionTimedOutEventDetails
Maybe ExecutionSucceededEventDetails
Maybe ExecutionStartedEventDetails
Maybe ActivitySucceededEventDetails
Maybe ActivityScheduledEventDetails
Maybe LambdaFunctionFailedEventDetails
Maybe LambdaFunctionScheduleFailedEventDetails
Maybe LambdaFunctionStartFailedEventDetails
Maybe LambdaFunctionSucceededEventDetails
Maybe LambdaFunctionTimedOutEventDetails
Maybe MapIterationEventDetails
Maybe MapRunFailedEventDetails
Maybe MapRunStartedEventDetails
Maybe MapStateStartedEventDetails
Maybe StateEnteredEventDetails
Maybe StateExitedEventDetails
Maybe LambdaFunctionScheduledEventDetails
Maybe TaskFailedEventDetails
Maybe TaskScheduledEventDetails
Maybe TaskStartFailedEventDetails
Maybe TaskStartedEventDetails
Maybe TaskSubmitFailedEventDetails
Maybe TaskSubmittedEventDetails
Maybe TaskSucceededEventDetails
Maybe TaskTimedOutEventDetails
POSIX
HistoryEventType
id :: Integer
type' :: HistoryEventType
timestamp :: POSIX
taskTimedOutEventDetails :: Maybe TaskTimedOutEventDetails
taskSucceededEventDetails :: Maybe TaskSucceededEventDetails
taskSubmittedEventDetails :: Maybe TaskSubmittedEventDetails
taskSubmitFailedEventDetails :: Maybe TaskSubmitFailedEventDetails
taskStartedEventDetails :: Maybe TaskStartedEventDetails
taskStartFailedEventDetails :: Maybe TaskStartFailedEventDetails
taskScheduledEventDetails :: Maybe TaskScheduledEventDetails
taskFailedEventDetails :: Maybe TaskFailedEventDetails
stateExitedEventDetails :: Maybe StateExitedEventDetails
stateEnteredEventDetails :: Maybe StateEnteredEventDetails
previousEventId :: Maybe Integer
mapStateStartedEventDetails :: Maybe MapStateStartedEventDetails
mapRunStartedEventDetails :: Maybe MapRunStartedEventDetails
mapRunFailedEventDetails :: Maybe MapRunFailedEventDetails
mapIterationSucceededEventDetails :: Maybe MapIterationEventDetails
mapIterationStartedEventDetails :: Maybe MapIterationEventDetails
mapIterationFailedEventDetails :: Maybe MapIterationEventDetails
mapIterationAbortedEventDetails :: Maybe MapIterationEventDetails
lambdaFunctionTimedOutEventDetails :: Maybe LambdaFunctionTimedOutEventDetails
lambdaFunctionSucceededEventDetails :: Maybe LambdaFunctionSucceededEventDetails
lambdaFunctionStartFailedEventDetails :: Maybe LambdaFunctionStartFailedEventDetails
lambdaFunctionScheduledEventDetails :: Maybe LambdaFunctionScheduledEventDetails
lambdaFunctionScheduleFailedEventDetails :: Maybe LambdaFunctionScheduleFailedEventDetails
lambdaFunctionFailedEventDetails :: Maybe LambdaFunctionFailedEventDetails
executionTimedOutEventDetails :: Maybe ExecutionTimedOutEventDetails
executionSucceededEventDetails :: Maybe ExecutionSucceededEventDetails
executionStartedEventDetails :: Maybe ExecutionStartedEventDetails
executionFailedEventDetails :: Maybe ExecutionFailedEventDetails
executionAbortedEventDetails :: Maybe ExecutionAbortedEventDetails
activityTimedOutEventDetails :: Maybe ActivityTimedOutEventDetails
activitySucceededEventDetails :: Maybe ActivitySucceededEventDetails
activityStartedEventDetails :: Maybe ActivityStartedEventDetails
activityScheduledEventDetails :: Maybe ActivityScheduledEventDetails
activityScheduleFailedEventDetails :: Maybe ActivityScheduleFailedEventDetails
activityFailedEventDetails :: Maybe ActivityFailedEventDetails
$sel:id:HistoryEvent' :: HistoryEvent -> Integer
$sel:type':HistoryEvent' :: HistoryEvent -> HistoryEventType
$sel:timestamp:HistoryEvent' :: HistoryEvent -> POSIX
$sel:taskTimedOutEventDetails:HistoryEvent' :: HistoryEvent -> Maybe TaskTimedOutEventDetails
$sel:taskSucceededEventDetails:HistoryEvent' :: HistoryEvent -> Maybe TaskSucceededEventDetails
$sel:taskSubmittedEventDetails:HistoryEvent' :: HistoryEvent -> Maybe TaskSubmittedEventDetails
$sel:taskSubmitFailedEventDetails:HistoryEvent' :: HistoryEvent -> Maybe TaskSubmitFailedEventDetails
$sel:taskStartedEventDetails:HistoryEvent' :: HistoryEvent -> Maybe TaskStartedEventDetails
$sel:taskStartFailedEventDetails:HistoryEvent' :: HistoryEvent -> Maybe TaskStartFailedEventDetails
$sel:taskScheduledEventDetails:HistoryEvent' :: HistoryEvent -> Maybe TaskScheduledEventDetails
$sel:taskFailedEventDetails:HistoryEvent' :: HistoryEvent -> Maybe TaskFailedEventDetails
$sel:stateExitedEventDetails:HistoryEvent' :: HistoryEvent -> Maybe StateExitedEventDetails
$sel:stateEnteredEventDetails:HistoryEvent' :: HistoryEvent -> Maybe StateEnteredEventDetails
$sel:previousEventId:HistoryEvent' :: HistoryEvent -> Maybe Integer
$sel:mapStateStartedEventDetails:HistoryEvent' :: HistoryEvent -> Maybe MapStateStartedEventDetails
$sel:mapRunStartedEventDetails:HistoryEvent' :: HistoryEvent -> Maybe MapRunStartedEventDetails
$sel:mapRunFailedEventDetails:HistoryEvent' :: HistoryEvent -> Maybe MapRunFailedEventDetails
$sel:mapIterationSucceededEventDetails:HistoryEvent' :: HistoryEvent -> Maybe MapIterationEventDetails
$sel:mapIterationStartedEventDetails:HistoryEvent' :: HistoryEvent -> Maybe MapIterationEventDetails
$sel:mapIterationFailedEventDetails:HistoryEvent' :: HistoryEvent -> Maybe MapIterationEventDetails
$sel:mapIterationAbortedEventDetails:HistoryEvent' :: HistoryEvent -> Maybe MapIterationEventDetails
$sel:lambdaFunctionTimedOutEventDetails:HistoryEvent' :: HistoryEvent -> Maybe LambdaFunctionTimedOutEventDetails
$sel:lambdaFunctionSucceededEventDetails:HistoryEvent' :: HistoryEvent -> Maybe LambdaFunctionSucceededEventDetails
$sel:lambdaFunctionStartFailedEventDetails:HistoryEvent' :: HistoryEvent -> Maybe LambdaFunctionStartFailedEventDetails
$sel:lambdaFunctionScheduledEventDetails:HistoryEvent' :: HistoryEvent -> Maybe LambdaFunctionScheduledEventDetails
$sel:lambdaFunctionScheduleFailedEventDetails:HistoryEvent' :: HistoryEvent -> Maybe LambdaFunctionScheduleFailedEventDetails
$sel:lambdaFunctionFailedEventDetails:HistoryEvent' :: HistoryEvent -> Maybe LambdaFunctionFailedEventDetails
$sel:executionTimedOutEventDetails:HistoryEvent' :: HistoryEvent -> Maybe ExecutionTimedOutEventDetails
$sel:executionSucceededEventDetails:HistoryEvent' :: HistoryEvent -> Maybe ExecutionSucceededEventDetails
$sel:executionStartedEventDetails:HistoryEvent' :: HistoryEvent -> Maybe ExecutionStartedEventDetails
$sel:executionFailedEventDetails:HistoryEvent' :: HistoryEvent -> Maybe ExecutionFailedEventDetails
$sel:executionAbortedEventDetails:HistoryEvent' :: HistoryEvent -> Maybe ExecutionAbortedEventDetails
$sel:activityTimedOutEventDetails:HistoryEvent' :: HistoryEvent -> Maybe ActivityTimedOutEventDetails
$sel:activitySucceededEventDetails:HistoryEvent' :: HistoryEvent -> Maybe ActivitySucceededEventDetails
$sel:activityStartedEventDetails:HistoryEvent' :: HistoryEvent -> Maybe ActivityStartedEventDetails
$sel:activityScheduledEventDetails:HistoryEvent' :: HistoryEvent -> Maybe ActivityScheduledEventDetails
$sel:activityScheduleFailedEventDetails:HistoryEvent' :: HistoryEvent -> Maybe ActivityScheduleFailedEventDetails
$sel:activityFailedEventDetails:HistoryEvent' :: HistoryEvent -> Maybe ActivityFailedEventDetails
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe ActivityFailedEventDetails
activityFailedEventDetails
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ActivityScheduleFailedEventDetails
activityScheduleFailedEventDetails
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ActivityScheduledEventDetails
activityScheduledEventDetails
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ActivityStartedEventDetails
activityStartedEventDetails
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ActivitySucceededEventDetails
activitySucceededEventDetails
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ActivityTimedOutEventDetails
activityTimedOutEventDetails
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ExecutionAbortedEventDetails
executionAbortedEventDetails
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ExecutionFailedEventDetails
executionFailedEventDetails
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ExecutionStartedEventDetails
executionStartedEventDetails
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ExecutionSucceededEventDetails
executionSucceededEventDetails
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ExecutionTimedOutEventDetails
executionTimedOutEventDetails
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe LambdaFunctionFailedEventDetails
lambdaFunctionFailedEventDetails
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Maybe LambdaFunctionScheduleFailedEventDetails
lambdaFunctionScheduleFailedEventDetails
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Maybe LambdaFunctionScheduledEventDetails
lambdaFunctionScheduledEventDetails
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Maybe LambdaFunctionStartFailedEventDetails
lambdaFunctionStartFailedEventDetails
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Maybe LambdaFunctionSucceededEventDetails
lambdaFunctionSucceededEventDetails
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Maybe LambdaFunctionTimedOutEventDetails
lambdaFunctionTimedOutEventDetails
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Maybe MapIterationEventDetails
mapIterationAbortedEventDetails
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Maybe MapIterationEventDetails
mapIterationFailedEventDetails
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Maybe MapIterationEventDetails
mapIterationStartedEventDetails
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Maybe MapIterationEventDetails
mapIterationSucceededEventDetails
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Maybe MapRunFailedEventDetails
mapRunFailedEventDetails
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Maybe MapRunStartedEventDetails
mapRunStartedEventDetails
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Maybe MapStateStartedEventDetails
mapStateStartedEventDetails
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Maybe Integer
previousEventId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Maybe StateEnteredEventDetails
stateEnteredEventDetails
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Maybe StateExitedEventDetails
stateExitedEventDetails
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Maybe TaskFailedEventDetails
taskFailedEventDetails
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Maybe TaskScheduledEventDetails
taskScheduledEventDetails
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Maybe TaskStartFailedEventDetails
taskStartFailedEventDetails
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Maybe TaskStartedEventDetails
taskStartedEventDetails
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Maybe TaskSubmitFailedEventDetails
taskSubmitFailedEventDetails
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Maybe TaskSubmittedEventDetails
taskSubmittedEventDetails
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Maybe TaskSucceededEventDetails
taskSucceededEventDetails
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Maybe TaskTimedOutEventDetails
taskTimedOutEventDetails
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        POSIX
timestamp
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        HistoryEventType
type'
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Integer
id