| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Monitor.Tracing
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
- class Monad m => MonadTrace m
- data Sampling
- alwaysSampled :: Sampling
- neverSampled :: Sampling
- sampledEvery :: Int -> Sampling
- sampledWhen :: Bool -> Sampling
- debugEnabled :: Sampling
- rootSpan :: MonadTrace m => Sampling -> Name -> m a -> m a
- rootSpanWith :: MonadTrace m => (Builder -> Builder) -> Sampling -> Name -> m a -> m a
- childSpan :: MonadTrace m => Name -> m a -> m a
- childSpanWith :: MonadTrace m => (Builder -> Builder) -> Name -> m a -> m a
- data Zipkin
Overview
class Monad m => MonadTrace m Source #
A monad capable of generating traces.
There are currently two instances of this monad:
Minimal complete definition
Instances
| MonadTrace Identity Source # | |
| MonadUnliftIO m => MonadTrace (TraceT m) Source # | |
| (Monad m, MonadTrace m) => MonadTrace (ExceptT e m) Source # | |
| (Monad m, MonadTrace m) => MonadTrace (StateT s m) Source # | |
| (Monad m, MonadTrace m) => MonadTrace (StateT s m) Source # | |
| (Monad m, MonadTrace m, Monoid w) => MonadTrace (WriterT w m) Source # | |
| (Monad m, MonadTrace m, Monoid w) => MonadTrace (WriterT w m) Source # | |
| (Monad m, MonadTrace m) => MonadTrace (ReaderT r m) Source # | |
| (Monad m, MonadTrace m, Monoid w) => MonadTrace (RWST r w s m) Source # | |
| (Monad m, MonadTrace m, Monoid w) => MonadTrace (RWST r w s m) Source # | |
Generic span creation
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 #
debugEnabled :: Sampling Source #
Returns a debug Sampling. Debug spans are always sampled.
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).