tracing-0.0.1.2: Distributed tracing

Safe HaskellNone
LanguageHaskell2010

Control.Monad.Trace.Class

Description

The MonadTrace class

Synopsis

Documentation

class Monad m => MonadTrace m where 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

Methods

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

Trace an action, wrapping it inside a new span.

activeSpan :: m (Maybe Span) Source #

Extracts the currently active span, or Nothing if the action is not being traced.

activeSpan :: (MonadTrace n, MonadTrans t, m ~ t n) => m (Maybe Span) Source #

Extracts the currently active span, or Nothing if the action is not being traced.

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

Adds information to the active span, if present.

addSpanEntry :: (MonadTrace n, MonadTrans t, m ~ t n) => Key -> Value -> m () Source #

Adds information to the active span, if present.

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 #

data Builder Source #

A trace builder.

Note that Builder has an IsString instance, producing a span with the given string as name, no additional references, tags, or baggages. This allows convenient creation of spans via the OverloadedStrings pragma.

Constructors

Builder 

Fields

Instances
Show Builder Source # 
Instance details

Defined in Control.Monad.Trace.Class

IsString Builder Source # 
Instance details

Defined in Control.Monad.Trace.Class

Methods

fromString :: String -> Builder #

type Name = Text Source #

The name of a span.

data SpanID Source #

A 64-bit span identifier.

Instances
Eq SpanID Source # 
Instance details

Defined in Control.Monad.Trace.Internal

Methods

(==) :: SpanID -> SpanID -> Bool #

(/=) :: SpanID -> SpanID -> Bool #

Ord SpanID Source # 
Instance details

Defined in Control.Monad.Trace.Internal

Show SpanID Source # 
Instance details

Defined in Control.Monad.Trace.Internal

ToJSON SpanID Source # 
Instance details

Defined in Control.Monad.Trace.Internal

FromJSON SpanID Source # 
Instance details

Defined in Control.Monad.Trace.Internal

data TraceID Source #

A 128-bit trace identifier.

data Reference Source #

A relationship between spans.

There are currently two types of references, both of which model direct causal relationships between a child and a parent. More background on references is available in the opentracing specification: https://github.com/opentracing/specification/blob/master/specification.md.

Constructors

ChildOf !SpanID

ChildOf references imply that the parent span depends on the child span in some capacity. Note that this reference type is only valid within a single trace.

FollowsFrom !Context

If the parent does not depend on the child, we use a FollowsFrom reference.

builder :: Name -> Builder Source #

Returns a Builder with the given input as name and all other fields empty.

data Span Source #

A part of a trace.

Constructors

Span 

data Context Source #

A fully qualified span identifier, containing both the ID of the trace the span belongs to and the span's ID. Span contexts can be exported (resp. imported) via their toJSON (resp. fromJSON) instance.

Instances
Eq Context Source # 
Instance details

Defined in Control.Monad.Trace.Internal

Methods

(==) :: Context -> Context -> Bool #

(/=) :: Context -> Context -> Bool #

Ord Context Source # 
Instance details

Defined in Control.Monad.Trace.Internal

Show Context Source # 
Instance details

Defined in Control.Monad.Trace.Internal

type Key = Text Source #

The type of annotations' keys.

Keys starting with double underscores are reserved and should not be used.

data Value Source #

Metadata attached to a span.

tagDoubleValue :: Double -> Value Source #

Generates a tag value from a double.

tagInt64Value :: Integral a => a -> Value Source #

Generates a 64-bit integer tag value from any integer.

tagTextValue :: Text -> Value Source #

Generates a Unicode text tag value.

logValue :: ToJSON a => a -> Value Source #

Generates a log value with the time of writing as timestamp. Note that the value may be written later than it is created. For more control on the timestamp, use logValueAt.

logValueAt :: ToJSON a => POSIXTime -> a -> Value Source #

Generates a log value with a custom time.