Safe Haskell | None |
---|---|
Language | Haskell2010 |
This module exposes the generic MonadTrace
class.
Synopsis
- data Span = Span {
- spanName :: !Name
- spanContext :: !Context
- spanReferences :: !(Set Reference)
- spanSamplingDecision :: !SamplingDecision
- spanIsSampled :: Span -> Bool
- spanIsDebug :: Span -> 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)
- builderSamplingPolicy :: !(Maybe SamplingPolicy)
- type Name = Text
- builder :: Name -> Builder
- rootSpan :: MonadTrace m => SamplingPolicy -> Name -> m a -> m a
- rootSpanWith :: MonadTrace m => (Builder -> Builder) -> SamplingPolicy -> Name -> m a -> m a
- childSpan :: MonadTrace m => Name -> m a -> m a
- childSpanWith :: MonadTrace m => (Builder -> Builder) -> Name -> m a -> m a
- data SamplingDecision
- type SamplingPolicy = IO SamplingDecision
- alwaysSampled :: SamplingPolicy
- neverSampled :: SamplingPolicy
- sampledWithProbability :: Double -> SamplingPolicy
- sampledWhen :: Bool -> SamplingPolicy
- debugEnabled :: SamplingPolicy
- 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.
Span | |
|
spanIsSampled :: Span -> Bool Source #
Returns whether the span is sampled.
spanIsDebug :: Span -> Bool Source #
Returns whether the span has debug enabled.
A fully qualified span identifier, containing both the ID of the trace the span belongs to and the span's ID.
Context | |
|
A 128-bit trace identifier.
encodeTraceID :: TraceID -> Text Source #
Hex-encodes a trace ID.
A 64-bit span identifier.
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.
ChildOf !SpanID |
|
FollowsFrom !Context | If the parent does not depend on the child, we use a |
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:
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
MonadTrace Identity Source # | |
(MonadIO m, MonadBaseControl IO m) => MonadTrace (TraceT m) Source # | |
MonadTrace m => MonadTrace (ExceptT e m) Source # | |
(MonadTrace m, Monoid w) => MonadTrace (WriterT w m) Source # | |
MonadTrace m => MonadTrace (StateT s m) Source # | |
MonadTrace m => MonadTrace (ReaderT r m) Source # | |
MonadTrace m => MonadTrace (StateT s m) Source # | |
(MonadTrace m, Monoid w) => MonadTrace (WriterT w m) Source # | |
(MonadTrace m, Monoid w) => MonadTrace (RWST r w s m) Source # | |
(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.
Builder | |
|
Instances
IsString Builder Source # | |
Defined in Control.Monad.Trace.Class fromString :: String -> Builder # |
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.
Instances
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).
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.