| Stability | experimental |
|---|---|
| Portability | portable |
| Safe Haskell | None |
| Language | Haskell2010 |
GHC.Eventlog.Live.Machine.Analysis.Capability
Description
Synopsis
- processCapabilityUsageMetrics :: forall (m :: Type -> Type). MonadIO m => ProcessT m (WithStartTime CapabilityUsageSpan) (Metric Timestamp)
- type CapabilityUsageSpan = Either GCSpan MutatorSpan
- data CapabilityUser
- capabilityUser :: CapabilityUsageSpan -> CapabilityUser
- showCapabilityUserCategory :: CapabilityUser -> Text
- processCapabilityUsageSpans :: forall (m :: Type -> Type). MonadIO m => Verbosity -> ProcessT m (WithStartTime Event) (WithStartTime CapabilityUsageSpan)
- 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)
- data GCSpan = GCSpan {
- cap :: !Int
- startTimeUnixNano :: !Timestamp
- endTimeUnixNano :: !Timestamp
- processGCSpans :: forall (m :: Type -> Type). MonadIO m => Verbosity -> ProcessT m (WithStartTime Event) (WithStartTime GCSpan)
- processGCSpans' :: forall (m :: Type -> Type) s t. MonadIO m => (s -> Maybe Timestamp) -> (s -> Event) -> (s -> GCSpan -> t) -> Verbosity -> ProcessT m s t
- data MutatorSpan = MutatorSpan {
- cap :: !Int
- thread :: !ThreadId
- startTimeUnixNano :: !Timestamp
- endTimeUnixNano :: !Timestamp
- asMutatorSpans :: forall (m :: Type -> Type). MonadIO m => ProcessT m ThreadStateSpan MutatorSpan
- asMutatorSpans' :: forall (m :: Type -> Type) s t. MonadIO m => (s -> ThreadStateSpan) -> (s -> MutatorSpan -> t) -> ProcessT m s t
- processMutatorSpans :: forall (m :: Type -> Type). MonadIO m => Verbosity -> ProcessT m (WithStartTime Event) (WithStartTime MutatorSpan)
- processMutatorSpans' :: forall (m :: Type -> Type) s t. MonadIO m => (s -> Maybe Timestamp) -> (s -> Event) -> (s -> MutatorSpan -> t) -> Verbosity -> ProcessT m s t
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
type CapabilityUsageSpan = Either GCSpan MutatorSpan Source #
A CapabilityUsageSpan is either a GCSpan or a MutatorSpan.
data CapabilityUser Source #
The type of process using a capability, which is either a mutator thread or garbage collection.
Instances
| Show CapabilityUser Source # | |
Defined in GHC.Eventlog.Live.Machine.Analysis.Capability Methods showsPrec :: Int -> CapabilityUser -> ShowS # show :: CapabilityUser -> String # showList :: [CapabilityUser] -> ShowS # | |
| IsAttrValue CapabilityUser Source # | |
Defined in GHC.Eventlog.Live.Machine.Analysis.Capability Methods | |
capabilityUser :: CapabilityUsageSpan -> CapabilityUser Source #
Get the CapabilityUser associated with a CapabilityUsageSpan.
showCapabilityUserCategory :: CapabilityUser -> Text Source #
Show the category of a CapabilityUser as either GC or Mutator.
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
A GCSpan represents a segment of time during which the specified capability
ran GC.
Constructors
| GCSpan | |
Fields
| |
Instances
| Show GCSpan Source # | |
| HasField "cap" CapabilityUsageSpan Int Source # | |
Defined in GHC.Eventlog.Live.Machine.Analysis.Capability Methods getField :: CapabilityUsageSpan -> Int # | |
| HasField "endTimeUnixNano" CapabilityUsageSpan Timestamp Source # | |
Defined in GHC.Eventlog.Live.Machine.Analysis.Capability Methods | |
| HasField "startTimeUnixNano" CapabilityUsageSpan Timestamp Source # | |
Defined in GHC.Eventlog.Live.Machine.Analysis.Capability Methods | |
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.
Constructors
| MutatorSpan | |
Fields
| |
Instances
| Show MutatorSpan Source # | |
Defined in GHC.Eventlog.Live.Machine.Analysis.Capability Methods showsPrec :: Int -> MutatorSpan -> ShowS # show :: MutatorSpan -> String # showList :: [MutatorSpan] -> ShowS # | |
| HasField "cap" CapabilityUsageSpan Int Source # | |
Defined in GHC.Eventlog.Live.Machine.Analysis.Capability Methods getField :: CapabilityUsageSpan -> Int # | |
| HasField "endTimeUnixNano" CapabilityUsageSpan Timestamp Source # | |
Defined in GHC.Eventlog.Live.Machine.Analysis.Capability Methods | |
| HasField "startTimeUnixNano" CapabilityUsageSpan Timestamp Source # | |
Defined in GHC.Eventlog.Live.Machine.Analysis.Capability Methods | |
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.