tracing-control-0.0.6: Distributed tracing

Safe HaskellNone
LanguageHaskell2010

Monitor.Tracing

Contents

Description

This module is where you should start if you are interested in adding tracing to an application. It provides backend-agnostic utilities to generate traces. Trace publication and other backend-specific features are available in the modules below Monitor.Tracing (e.g. Monitor.Tracing.Zipkin). The additional functionality exposed under Control.Monad in this package is useful if you wish to implement a new tracing backend.

Synopsis

Overview

Let's assume we are interested in tracing the two following functions:

listTaskIDs' :: MonadIO m => m [Int] -- Returns a list of all task IDs.
fetchTasks' :: MonadIO m => [Int] -> m [Task] -- Resolves IDs into tasks.

We can do so simply by wrapping them inside childSpan calls and adding a MonadTrace constraint:

import Monitor.Tracing

listTaskIDs :: (MonadIO m, MonadTrace m) => m [Int]
listTaskIDs = childSpan "list-task-ids" listTaskIDs'

fetchTasks :: (MonadIO m, MonadTrace m) => [Int] -> m [Task]
fetchTasks = childSpan "fetch-tasks" . fetchTasks'

Spans will now automatically get generated any time these actions are run! Each span will be associated with various useful pieces of metadata, including lineage. For example, if we wrap the two above functions in a rootSpan, the spans will correctly be nested:

printTasks :: (MonadIO m, MonadTrace m) => m ()
printTasks = rootSpan alwaysSampled "list-tasks" $ listTaskIDs >>= fetchTasks >>= print

Spans can then be published to various backends. For example, to run the above action and publish its spans using Zipkin:

import qualified Monitor.Tracing.Zipkin as ZPK

main :: IO ()
main = ZPK.with ZPK.defaultSettings $ ZPK.run printTasks

Trace creation

class Monad m => MonadTrace m Source #

A monad capable of generating and modifying trace spans.

This package currently provides two instances of this class:

  • TraceT, which emits spans for each trace in IO and is meant to be used in production.
  • Identity, where tracing is a no-op and allows testing traced functions without any overhead or complex setup.

Minimal complete definition

trace

Instances
MonadTrace Identity Source # 
Instance details

Defined in Control.Monad.Trace.Class

(MonadIO m, MonadBaseControl IO m) => MonadTrace (TraceT m) Source # 
Instance details

Defined in Control.Monad.Trace

MonadTrace m => MonadTrace (ExceptT e m) Source # 
Instance details

Defined in Control.Monad.Trace.Class

Methods

trace :: Builder -> ExceptT e m a -> ExceptT e m a Source #

activeSpan :: ExceptT e m (Maybe Span) Source #

addSpanEntry :: Key -> Value -> ExceptT e m () Source #

(MonadTrace m, Monoid w) => MonadTrace (WriterT w m) Source # 
Instance details

Defined in Control.Monad.Trace.Class

Methods

trace :: Builder -> WriterT w m a -> WriterT w m a Source #

activeSpan :: WriterT w m (Maybe Span) Source #

addSpanEntry :: Key -> Value -> WriterT w m () Source #

MonadTrace m => MonadTrace (StateT s m) Source # 
Instance details

Defined in Control.Monad.Trace.Class

Methods

trace :: Builder -> StateT s m a -> StateT s m a Source #

activeSpan :: StateT s m (Maybe Span) Source #

addSpanEntry :: Key -> Value -> StateT s m () Source #

MonadTrace m => MonadTrace (StateT s m) Source # 
Instance details

Defined in Control.Monad.Trace.Class

Methods

trace :: Builder -> StateT s m a -> StateT s m a Source #

activeSpan :: StateT s m (Maybe Span) Source #

addSpanEntry :: Key -> Value -> StateT s m () Source #

(MonadTrace m, Monoid w) => MonadTrace (WriterT w m) Source # 
Instance details

Defined in Control.Monad.Trace.Class

Methods

trace :: Builder -> WriterT w m a -> WriterT w m a Source #

activeSpan :: WriterT w m (Maybe Span) Source #

addSpanEntry :: Key -> Value -> WriterT w m () Source #

MonadTrace m => MonadTrace (ReaderT r m) Source # 
Instance details

Defined in Control.Monad.Trace.Class

Methods

trace :: Builder -> ReaderT r m a -> ReaderT r m a Source #

activeSpan :: ReaderT r m (Maybe Span) Source #

addSpanEntry :: Key -> Value -> ReaderT r m () Source #

(MonadTrace m, Monoid w) => MonadTrace (RWST r w s m) Source # 
Instance details

Defined in Control.Monad.Trace.Class

Methods

trace :: Builder -> RWST r w s m a -> RWST r w s m a Source #

activeSpan :: RWST r w s m (Maybe Span) Source #

addSpanEntry :: Key -> Value -> RWST r w s m () Source #

(MonadTrace m, Monoid w) => MonadTrace (RWST r w s m) Source # 
Instance details

Defined in Control.Monad.Trace.Class

Methods

trace :: Builder -> RWST r w s m a -> RWST r w s m a Source #

activeSpan :: RWST r w s m (Maybe Span) Source #

addSpanEntry :: Key -> Value -> RWST r w s m () Source #

Starting a new trace

By default, traces created by trace are independent from each other. However, we can get a lot more value out of tracing by organizing a trace's spans. The simplest and most common approach is to build a tree of spans, with a single root span and zero or more children for each span. rootSpan and childSpan below set up spans such that lineage information is automatically propagated.

rootSpan :: MonadTrace m => SamplingPolicy -> Name -> m a -> m a Source #

Starts a new trace. For performance reasons, it is possible to customize how frequently tracing information is collected. This allows fine-grain control on the overhead induced by tracing. For example, you might only want to sample 1% of a very actively used call-path with sampledWithProbability 0.01.

alwaysSampled :: SamplingPolicy Source #

Returns a SamplingPolicy which always samples.

neverSampled :: SamplingPolicy Source #

Returns a SamplingPolicy which never samples.

sampledWhen :: Bool -> SamplingPolicy Source #

Returns a SamplingPolicy which samples a span iff the input is True. It is equivalent to:

sampledWhen b = if b then alwaysSampled else neverSampled

sampledWithProbability :: Double -> SamplingPolicy Source #

Returns a SamplingPolicy which randomly samples spans.

debugEnabled :: SamplingPolicy Source #

Returns a debug SamplingPolicy. Debug spans are always sampled.

Extending a trace

childSpan :: MonadTrace m => Name -> m a -> m a Source #

Extends a trace: the active span's ID will be added as a reference to a newly created span and both spans will share the same trace ID. If no span is active, childSpan is a no-op.

Backends

As a convenience, the top-level type for each backend is exported here.

data Zipkin Source #

A Zipkin trace publisher.

All publisher functionality is thread-safe. In particular it is safe to publish concurrently with run, and/or run multiple actions concurrently. Note also that all sampled spans are retained in memory until they are published.