tracing-0.0.7.2: Distributed tracing
Safe HaskellNone
LanguageHaskell2010

Control.Monad.Trace.Class

Description

This module exposes the generic MonadTrace class.

Synopsis

Types

data Span Source #

A part of a trace.

spanIsSampled :: Span -> Bool Source #

Returns whether the span is sampled.

spanIsDebug :: Span -> Bool Source #

Returns whether the span has debug enabled.

data Context Source #

A fully qualified span identifier, containing both the ID of the trace the span belongs to and the span's ID.

Instances

Instances details
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

newtype TraceID Source #

A 128-bit trace identifier.

Constructors

TraceID ByteString 

decodeTraceID :: Text -> Maybe TraceID Source #

Decodes a traced ID from a hex-encoded string.

encodeTraceID :: TraceID -> Text Source #

Hex-encodes a trace ID.

newtype SpanID Source #

A 64-bit span identifier.

Constructors

SpanID ByteString 

Instances

Instances details
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

decodeSpanID :: Text -> Maybe SpanID Source #

Decodes a span ID from a hex-encoded string.

encodeSpanID :: SpanID -> Text Source #

Hex-encodes a span ID.

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.

Generating traces

Individual spans

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

Methods

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

Trace an action, wrapping it inside a new span. If the action isn't currently being traced, trace should be a no-op. Otherwise, the new span should share the active span's trace ID, sampling decision, and baggages unless overridden by the input Builder.

activeSpan :: m (Maybe Span) Source #

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

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

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

Adds information to the active span, if present.

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

Instances

Instances details
MonadTrace Identity Source # 
Instance details

Defined in Control.Monad.Trace.Class

MonadUnliftIO 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 => 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 => 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, 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, 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 #

data Builder Source #

A span builder.

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

Instances details
IsString Builder Source # 
Instance details

Defined in Control.Monad.Trace.Class

Methods

fromString :: String -> Builder #

type Name = Text Source #

The name of a span.

builder :: Name -> Builder Source #

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

Structured traces

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.

rootSpanWith :: MonadTrace m => (Builder -> Builder) -> SamplingPolicy -> 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: 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.

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

Extends a trace, same as childSpan but also customizing the builder.

Sampling

data SamplingDecision Source #

A span's sampling decision.

Constructors

Always 
Never 
Debug 

Instances

Instances details
Enum SamplingDecision Source # 
Instance details

Defined in Control.Monad.Trace.Internal

Eq SamplingDecision Source # 
Instance details

Defined in Control.Monad.Trace.Internal

Ord SamplingDecision Source # 
Instance details

Defined in Control.Monad.Trace.Internal

Show SamplingDecision Source # 
Instance details

Defined in Control.Monad.Trace.Internal

type SamplingPolicy = IO SamplingDecision Source #

An action to determine how a span should be sampled.

alwaysSampled :: SamplingPolicy Source #

Returns a SamplingPolicy which always samples.

neverSampled :: SamplingPolicy Source #

Returns a SamplingPolicy which never samples.

sampledWithProbability :: Double -> SamplingPolicy Source #

Returns a SamplingPolicy which randomly samples spans.

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

debugEnabled :: SamplingPolicy Source #

Returns a debug SamplingPolicy. Debug spans are always sampled.

Annotating traces

Note that not all annotation types are supported by all backends. For example Zipkin only supports string tags (refer to Monitor.Tracing.Zipkin for the full list of supported span metadata).

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.