eventlog-live-0.2.0.1: Live processing of eventlog data.
Stabilityexperimental
Portabilityportable
Safe HaskellNone
LanguageHaskell2010

GHC.Eventlog.Live.Machine

Description

 
Synopsis

Event processing

Capability Usage

Capability Usage Metrics

processCapabilityUsageMetrics :: forall (m :: Type -> Type). MonadIO m => ProcessT m (WithStartTime CapabilityUsageSpan) (Metric Timestamp) Source #

This machine processes CapabilityUsageSpan spans and produces metrics that contain the duration and category of each such span and each idle period in between.

Capability Usage Spans

data CapabilityUser Source #

The type of process using a capability, which is either a mutator thread or garbage collection.

Constructors

GC 
Mutator 

Fields

processCapabilityUsageSpans :: forall (m :: Type -> Type). MonadIO m => Verbosity -> ProcessT m (WithStartTime Event) (WithStartTime CapabilityUsageSpan) Source #

This machine runs processGCSpans and processMutatorSpans in parallel and combines their output.

This is effectively a fanout of processGCSpans and processMutatorSpans, the latter of which runs processThreadStateSpans internally. If you are running processThreadStateSpans as well, then using asMutatorSpans and constructing the fanout yourself is more efficient.

processCapabilityUsageSpans' :: forall (m :: Type -> Type) s t1 t2. MonadIO m => (s -> Maybe Timestamp) -> (s -> Event) -> (s -> GCSpan -> t1) -> (s -> MutatorSpan -> t2) -> Verbosity -> ProcessT m s (Either t1 t2) Source #

Generalised version of processCapabilityUsageSpans that can be adapted to work on arbitrary types using a getter and a pair of lenses.

GC Spans

data GCSpan Source #

A GCSpan represents a segment of time during which the specified capability ran GC.

Instances

Instances details
Show GCSpan Source # 
Instance details

Defined in GHC.Eventlog.Live.Machine

HasField "cap" CapabilityUsageSpan Int Source # 
Instance details

Defined in GHC.Eventlog.Live.Machine

HasField "endTimeUnixNano" CapabilityUsageSpan Timestamp Source # 
Instance details

Defined in GHC.Eventlog.Live.Machine

HasField "startTimeUnixNano" CapabilityUsageSpan Timestamp Source # 
Instance details

Defined in GHC.Eventlog.Live.Machine

processGCSpans :: forall (m :: Type -> Type). MonadIO m => Verbosity -> ProcessT m (WithStartTime Event) (WithStartTime GCSpan) Source #

This machine processes StartGC and EndGC events to produce GCSpan values that represent the segments of time a capability spent in GC.

This processor uses the following finite-state automaton:

      ┌─(EndGC)───┐
      │           ↓
    ┌→[   Idle    ]─┐
    │               │
(EndGC)         (StartGC)
    │               │
    └─[    GC     ]←┘
      ↑           │
      └─(StartGC)─┘

The transition from GC to Idle yields a GC span.

processGCSpans' :: forall (m :: Type -> Type) s t. MonadIO m => (s -> Maybe Timestamp) -> (s -> Event) -> (s -> GCSpan -> t) -> Verbosity -> ProcessT m s t Source #

Generalised version of processGCSpans that can be adapted to work on arbitrary types using a getter and a lens.

Mutator Spans

data MutatorSpan Source #

A MutatorSpan represents a segment of time during which the specified capability ran the specified mutator thread.

Instances

Instances details
Show MutatorSpan Source # 
Instance details

Defined in GHC.Eventlog.Live.Machine

HasField "cap" CapabilityUsageSpan Int Source # 
Instance details

Defined in GHC.Eventlog.Live.Machine

HasField "endTimeUnixNano" CapabilityUsageSpan Timestamp Source # 
Instance details

Defined in GHC.Eventlog.Live.Machine

HasField "startTimeUnixNano" CapabilityUsageSpan Timestamp Source # 
Instance details

Defined in GHC.Eventlog.Live.Machine

asMutatorSpans :: forall (m :: Type -> Type). MonadIO m => ProcessT m ThreadStateSpan MutatorSpan Source #

This machine converts any Running ThreadStateSpan to a MutatorSpan.

asMutatorSpans' :: forall (m :: Type -> Type) s t. MonadIO m => (s -> ThreadStateSpan) -> (s -> MutatorSpan -> t) -> ProcessT m s t Source #

Generalised version of asMutatorSpans that can be adapted to work on arbitrary types using a getter and a lens.

processMutatorSpans :: forall (m :: Type -> Type). MonadIO m => Verbosity -> ProcessT m (WithStartTime Event) (WithStartTime MutatorSpan) Source #

This machine processes RunThread and StopThread events to produce tMutatorSpan values that represent the segments of time a capability spent executating a mutator.

This processor uses the following finite-state automaton:

      ┌─(StopThread[X])─┐
      │                 ↓
    ┌→[      Idle       ]─┐
    │                     │
(StopThread[X])       (RunThread[X])
    │                     │
    └─[   Mutator[X]    ]←┘
      ↑                 │
      └─(RunThread[X])──┘

The transition from Mutator[X] to Idle yields a MutatorSpan. While in the Mutator[X] state, any RunThread[Y] or StopThread[Y] events result in an error. Furthermore, when a StopThread[X] event with the ThreadFinished status is processed, the thread X is added to a set of finished threads, and any further RunThread[X] events for that thread are ignored. This is done because the GHC RTS frequently emits a RunThread[X] event immediately after a StopThread[X] event with the ThreadFinished status.

This runs processThreadStateSpans internally. If you are also running processThreadStateSpans, then post-composing it with asMutatorSpans is more efficient.

processMutatorSpans' :: forall (m :: Type -> Type) s t. MonadIO m => (s -> Maybe Timestamp) -> (s -> Event) -> (s -> MutatorSpan -> t) -> Verbosity -> ProcessT m s t Source #

Generalised version of processMutatorSpans that can be adapted to work on arbitrary types using a getter and a lens.

Thread labels

data ThreadLabel Source #

The ThreadLabel type represents the association of a label with a thread starting at a given time.

processThreadLabels :: Process (WithStartTime Event) ThreadLabel Source #

This machine processes ThreadLabel events and yields ThreadLabel values.

Thread State Spans

data ThreadState Source #

The execution states of a mutator thread.

Constructors

Running 

Fields

Blocked 
Finished 

Instances

Instances details
Show ThreadState Source # 
Instance details

Defined in GHC.Eventlog.Live.Machine

showThreadStateCategory :: ThreadState -> Text Source #

Pretty-print a thread state as Running, Blocked, or Finished.

data ThreadStateSpan Source #

A span representing the state of a mutator thread.

Instances

Instances details
Show ThreadStateSpan Source # 
Instance details

Defined in GHC.Eventlog.Live.Machine

processThreadStateSpans :: forall (m :: Type -> Type). MonadIO m => Verbosity -> ProcessT m (WithStartTime Event) ThreadStateSpan Source #

This machine processes RunThread and StopThread events to produce tThreadStateSpan values that represent segments of time where a thread is running, blocked, or finished.

This processor uses the following finite-state automaton:

      ┌─(StopThread)─┐
      │              ↓
    ┌→[   Blocked    ]─┐
    │                  │
(StopThread)       (RunThread)
    │                  │
    └─[   Running    ]←┘
      ↑              │
      └─(RunThread)──┘

The transitions from Blocked to Blocked, Blocked to Running, and Running to Running yield a ThreadStateSpan. There are additional transitions (not pictured) from either state to the final Finished state with a StopThread event with the ThreadFinished status.

processThreadStateSpans' :: forall (m :: Type -> Type) s t. MonadIO m => (s -> Maybe Timestamp) -> (s -> Event) -> (s -> ThreadStateSpan -> t) -> Verbosity -> ProcessT m s t Source #

Generalised version of processThreadStateSpans that can be adapted to work on arbitrary types using a getter and a lens.

Heap events

processHeapAllocatedData :: Process (WithStartTime Event) (Metric Word64) Source #

This machine processes HeapAllocated events into metrics.

processHeapSizeData :: Process (WithStartTime Event) (Metric Word64) Source #

This machine processes HeapSize events into metrics.

processBlocksSizeData :: Process (WithStartTime Event) (Metric Word64) Source #

This machine processes BlocksSize events into metrics.

processHeapLiveData :: Process (WithStartTime Event) (Metric Word64) Source #

This machine processes HeapLive events into metrics.

data MemReturnData Source #

The type of data associated with a MemReturn event.

Constructors

MemReturnData 

Fields

  • current :: !Word32

    The number of megablocks currently allocated.

  • needed :: !Word32

    The number of megablocks currently needed.

  • returned :: !Word32

    The number of megablocks currently being returned to the OS.

processMemReturnData :: Process (WithStartTime Event) (Metric MemReturnData) Source #

This machine processes MemReturn events into metrics.

processHeapProfSampleData :: forall (m :: Type -> Type). MonadIO m => Verbosity -> Maybe HeapProfBreakdown -> ProcessT m (WithStartTime Event) (Metric Word64) Source #

This machine processes HeapProfSampleString events into metrics. Furthermore, it processes the HeapProfBegin and ProgramArgs events to determine the heap profile breakdown, processes InfoTableProv events to build an info table map, if necessary, and processes HeapProfSampleBegin and HeapProfSampleEnd events to maintain an era stack.

Heap profile breakdown

heapProfBreakdownEitherReader :: String -> Either String HeapProfBreakdown Source #

Parses the HeapProfBreakdown command-line arguments:

heapProfBreakdownEitherReader "T" == Left HeapProfBreakdownClosureType
heapProfBreakdownEitherReader "c" == Left HeapProfBreakdownCostCentre
heapProfBreakdownEitherReader "m" == Left HeapProfBreakdownModule
heapProfBreakdownEitherReader "d" == Left HeapProfBreakdownClosureDescr
heapProfBreakdownEitherReader "y" == Left HeapProfBreakdownTypeDescr
heapProfBreakdownEitherReader "e" == Left HeapProfBreakdownEra
heapProfBreakdownEitherReader "r" == Left HeapProfBreakdownRetainer
heapProfBreakdownEitherReader "b" == Left HeapProfBreakdownBiography
heapProfBreakdownEitherReader "i" == Left HeapProfBreakdownInfoTable

heapProfBreakdownShow :: HeapProfBreakdown -> String Source #

Shows a HeapProfBreakdown as its corresponding command-line flag:

heapProfBreakdownShow HeapProfBreakdownClosureType == "-hT"
heapProfBreakdownShow HeapProfBreakdownCostCentre == "-hc"
heapProfBreakdownShow HeapProfBreakdownModule == "-hm"
heapProfBreakdownShow HeapProfBreakdownClosureDescr == "-hd"
heapProfBreakdownShow HeapProfBreakdownTypeDescr == "-hy"
heapProfBreakdownShow HeapProfBreakdownEra == "-he"
heapProfBreakdownShow HeapProfBreakdownRetainer == "-hr"
heapProfBreakdownShow HeapProfBreakdownBiography == "-hb"
heapProfBreakdownShow HeapProfBreakdownInfoTable == "-hi"