tracing-0.0.2.0: Distributed tracing

Safe HaskellNone
LanguageHaskell2010

Monitor.Tracing

Contents

Description

Non-intrusive distributed tracing

Let's assume for example 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 a childSpan call 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
Synopsis

Overview

class Monad m => MonadTrace m Source #

A monad capable of generating traces.

There are currently two instances of this monad:

  • 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

MonadUnliftIO m => MonadTrace (TraceT m) Source # 
Instance details

Defined in Control.Monad.Trace

(Monad m, 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 #

(Monad m, 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 #

(Monad m, 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 #

(Monad m, 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 #

(Monad m, 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 #

(Monad m, 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 #

(Monad m, 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 #

(Monad m, 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 #

Generic span creation

data Sampling Source #

A trace sampling strategy.

Instances
Eq Sampling Source # 
Instance details

Defined in Control.Monad.Trace.Internal

Show Sampling Source # 
Instance details

Defined in Control.Monad.Trace.Internal

alwaysSampled :: Sampling Source #

Returns a Sampling which always samples.

neverSampled :: Sampling Source #

Returns a Sampling which never samples.

sampledEvery :: Int -> Sampling Source #

Returns a Sampling which randomly samples one in every n spans.

sampledWhen :: Bool -> Sampling Source #

Returns a Sampling which samples a span iff the input is True.

debugEnabled :: Sampling Source #

Returns a debug Sampling. Debug spans are always sampled.

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

Starts a new trace.

rootSpanWith :: MonadTrace m => (Builder -> Builder) -> Sampling -> Name -> m a -> m a Source #

Starts a new trace, customizing the span builder. Note that the sampling input will override any sampling customization set on the builder.

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

Extends a trace if it is active, otherwise do nothing.

childSpanWith :: MonadTrace m => (Builder -> Builder) -> Name -> m a -> m a Source #

Extends a trace if it is active, otherwise do nothing. The active span's ID will be added as a reference to the new span and it will share the same trace ID (overriding any customization done to the builder).

Backends

data Zipkin Source #

A Zipkin trace publisher.