| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Control.Monad.Trace.Class
Description
This module exposes the generic MonadTrace class.
Synopsis
- data Span = Span {
- spanName :: !Name
- spanContext :: !Context
- spanReferences :: !(Set Reference)
- spanIsSampled :: !Bool
- spanIsDebug :: !Bool
- data Context = Context {
- contextTraceID :: !TraceID
- contextSpanID :: !SpanID
- contextBaggages :: !(Map Key ByteString)
- newtype TraceID = TraceID ByteString
- decodeTraceID :: Text -> Maybe TraceID
- encodeTraceID :: TraceID -> Text
- newtype SpanID = SpanID ByteString
- decodeSpanID :: Text -> Maybe SpanID
- encodeSpanID :: SpanID -> Text
- data Reference
- = ChildOf !SpanID
- | FollowsFrom !Context
- class Monad m => MonadTrace m where
- trace :: Builder -> m a -> m a
- activeSpan :: m (Maybe Span)
- addSpanEntry :: Key -> Value -> m ()
- data Builder = Builder {
- builderName :: !Name
- builderTraceID :: !(Maybe TraceID)
- builderSpanID :: !(Maybe SpanID)
- builderReferences :: !(Set Reference)
- builderTags :: !(Map Key Value)
- builderBaggages :: !(Map Key ByteString)
- builderSampling :: !(Maybe Sampling)
- type Name = Text
- builder :: Name -> Builder
- 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 Sampling
- alwaysSampled :: Sampling
- neverSampled :: Sampling
- sampledEvery :: Int -> Sampling
- sampledWhen :: Bool -> Sampling
- debugEnabled :: Sampling
- type Key = Text
- data Value
- tagDoubleValue :: Double -> Value
- tagInt64Value :: Integral a => a -> Value
- tagTextValue :: Text -> Value
- logValue :: ToJSON a => a -> Value
- logValueAt :: ToJSON a => POSIXTime -> a -> Value
Types
A part of a trace.
Constructors
| Span | |
Fields
| |
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.
Constructors
| Context | |
Fields
| |
A 128-bit trace identifier.
Constructors
| TraceID ByteString |
encodeTraceID :: TraceID -> Text Source #
Hex-encodes a trace ID.
A 64-bit span identifier.
Constructors
| SpanID ByteString |
encodeSpanID :: SpanID -> Text Source #
Hex-encodes a span ID.
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 |
|
| FollowsFrom !Context | If the parent does not depend on the child, we use a |
Instances
| Eq Reference Source # | |
| Ord Reference Source # | |
| Show Reference Source # | |
Generating traces
Individual spans
class Monad m => MonadTrace m where Source #
A monad capable of generating and modifying trace spans.
There are currently two instances of this monad:
Minimal complete definition
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 # | |
| 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 # | |
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
| |
builder :: Name -> Builder Source #
Returns a Builder with the given input as name and all other fields empty.
Structured traces
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: 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
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.
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).
The type of annotations' keys.
Keys starting with double underscores are reserved and should not be used.
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.