opentracing-0.2.1: OpenTracing for Haskell
Safe HaskellNone
LanguageHaskell2010

OpenTracing.Tracer

Description

This module provides mid and high level tracing functions.

Synopsis

Documentation

data Tracer Source #

A Tracer is a set of effectful actions that define the mid-level interface to an OpenTracing tracer

Appliction code should generally construct a Tracer once and then use other higher-level functions such as traced, startSpan, finishedSpan.

Since: 0.1.0.0

Constructors

Tracer 

Fields

  • tracerStart :: forall m. MonadIO m => SpanOpts -> m Span

    Start recording a new span with the given options. This is a mid-level operation that will handle start timing and random span ID generation.

    Application code should supply this field with stdTracer.

  • tracerReport :: forall m. MonadIO m => FinishedSpan -> m ()

    Report a finished span. What reporting means for each application will depend on where this data is going. There are multiple backends that define reporters for Google Cloudtrace, Zipkin, and Jaeger, for example.

Instances

Instances details
HasTracer Tracer Source # 
Instance details

Defined in OpenTracing.Tracer

class HasTracer a where Source #

Typeclass for application environments that contain a Tracer.

Since: 0.1.0.0

Methods

tracer :: Getting r a Tracer Source #

Instances

Instances details
HasTracer Tracer Source # 
Instance details

Defined in OpenTracing.Tracer

runTracer :: HasTracer r => r -> ReaderT r m a -> m a Source #

traced Source #

Arguments

:: (HasTracer t, MonadMask m, MonadIO m) 
=> t

A tracer environment

-> SpanOpts

The options to use when creating the span. Options include:

  • Operation name
  • Tags
  • Relations to other spans
-> (ActiveSpan -> m a)

the computation to trace. The argument is the span that is created. It can be used to:

  • Add logs
  • Add child spans
-> m (Traced a) 

Trace a computation as a span. This is a high-level operation that will handle all aspects of the trace, including timing and reporting. If the traced computation throws an excpetion, traced will clean up and add logs before rethrowing the exception

        traced tracer (spanOpts "hello" mempty          ) $ parent ->
        traced tracer (spanOpts "world" (childOf parent)) $ child ->
           liftIO $ do
               putStrLn "doing some work..."
               addLogRecord child (Message "doing some work")
               threadDelay 500000

Since: 0.1.0.0

traced_ :: (HasTracer t, MonadMask m, MonadIO m) => t -> SpanOpts -> (ActiveSpan -> m a) -> m a Source #

Variant of traced that doesn't return the wrapped value.

Since: 0.1.0.0

startSpan :: (HasTracer t, MonadIO m) => t -> SpanOpts -> m ActiveSpan Source #

Start recording a span

Since: 0.1.0.0

finishSpan :: (HasTracer t, MonadIO m) => t -> ActiveSpan -> m FinishedSpan Source #

Finish recording a span

Since: 0.1.0.0