Safe Haskell | None |
---|---|
Language | Haskell2010 |
This module is useful mostly for tracing backend implementors. If you are only interested in adding tracing to an application, start at Monitor.Tracing.
Synopsis
- data Tracer
- newTracer :: MonadIO m => m Tracer
- runTraceT :: TraceT m a -> Tracer -> m a
- runTraceT' :: TraceT m a -> Maybe Tracer -> m a
- newtype TraceT m a = TraceT {
- traceTReader :: ReaderT (Maybe Scope) m a
- spanSamples :: Tracer -> TChan Sample
- data Sample = Sample {
- sampleSpan :: !Span
- sampleTags :: !Tags
- sampleLogs :: !Logs
- sampleStart :: !POSIXTime
- sampleDuration :: !NominalDiffTime
- type Tags = Map Key Value
- type Logs = [(POSIXTime, Key, Value)]
- pendingSpanCount :: Tracer -> TVar Int
Tracers
A tracer is a producer of spans.
More specifically, a tracer:
- runs
MonadTrace
actions viarunTraceT
, - transparently collects their generated spans,
- and outputs them to a channel (available via
spanSamples
).
These samples can then be consumed independently, decoupling downstream span processing from their production.
runTraceT :: TraceT m a -> Tracer -> m a Source #
Trace an action, sampling its generated spans. This method is thread-safe and can be used to trace multiple actions concurrently.
Unless you are implementing a custom span publication backend, you should not need to call this
method explicitly. Instead, prefer to use the backend's functionality directly (e.g.
run
for Zipkin). To ease debugging in certain cases,
collectSpanSamples
is also available.
See runTraceT'
for a variant which allows discarding spans.
runTraceT' :: TraceT m a -> Maybe Tracer -> m a Source #
Maybe trace an action. If the tracer is Nothing
, no spans will be published.
A span generation monad.
TraceT | |
|
Instances
MonadTrans TraceT Source # | |
Defined in Control.Monad.Trace | |
MonadBase b m => MonadBase b (TraceT m) Source # | |
Defined in Control.Monad.Trace | |
MonadBaseControl b m => MonadBaseControl b (TraceT m) Source # | |
MonadWriter w m => MonadWriter w (TraceT m) Source # | |
MonadState s m => MonadState s (TraceT m) Source # | |
MonadReader r m => MonadReader r (TraceT m) Source # | |
MonadError e m => MonadError e (TraceT m) Source # | |
Defined in Control.Monad.Trace throwError :: e -> TraceT m a # catchError :: TraceT m a -> (e -> TraceT m a) -> TraceT m a # | |
Monad m => Monad (TraceT m) Source # | |
Functor m => Functor (TraceT m) Source # | |
Applicative m => Applicative (TraceT m) Source # | |
MonadIO m => MonadIO (TraceT m) Source # | |
Defined in Control.Monad.Trace | |
(MonadIO m, MonadBaseControl IO m) => MonadTrace (TraceT m) Source # | |
type StM (TraceT m) a Source # | |
Defined in Control.Monad.Trace |
Collected data
Tracers currently expose two pieces of data: completed spans and pending span count. Note
that only sampled spans are eligible: spans which are neverSampled
appear in neither.
Completed spans
spanSamples :: Tracer -> TChan Sample Source #
Returns all newly completed spans' samples. The samples become available in the same order they are completed.
A sampled span and its associated metadata.
Sample | |
|