servant-tracing-0.2.0.0
Safe HaskellNone
LanguageHaskell2010

Tracing.Core

Synopsis

Documentation

data Span Source #

A timed section of code with a logical name and SpanContext. Individual spans will be reconstructed by an OpenTracing backend into a single trace.

Instances

Instances details
Show Span Source # 
Instance details

Defined in Tracing.Core

Methods

showsPrec :: Int -> Span -> ShowS #

show :: Span -> String #

showList :: [Span] -> ShowS #

data SpanRelation Source #

Spans may be top level, a child, or logically follow from a given span.

Instances

Instances details
Eq SpanRelation Source # 
Instance details

Defined in Tracing.Core

Show SpanRelation Source # 
Instance details

Defined in Tracing.Core

data SpanRelationTag Source #

Indicates the type of relation this span represents

Constructors

Child 
Follows 

data SpanContext Source #

Uniquely identifies a given Span & points to its encompasing trace

Constructors

SpanContext 

Fields

Instances

Instances details
Eq SpanContext Source # 
Instance details

Defined in Tracing.Core

Show SpanContext Source # 
Instance details

Defined in Tracing.Core

data SpanTag Source #

Used to embed additional information into a Span for consumption & viewing in a tracing backend

Instances

Instances details
Eq SpanTag Source # 
Instance details

Defined in Tracing.Core

Methods

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

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

Show SpanTag Source # 
Instance details

Defined in Tracing.Core

ToSpanTag SpanTag Source # 
Instance details

Defined in Tracing.Core

newtype OpName Source #

Human-readable name for the span

Constructors

OpName Text 

Instances

Instances details
Eq OpName Source # 
Instance details

Defined in Tracing.Core

Methods

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

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

Ord OpName Source # 
Instance details

Defined in Tracing.Core

Show OpName Source # 
Instance details

Defined in Tracing.Core

IsString OpName Source # 
Instance details

Defined in Tracing.Core

Methods

fromString :: String -> OpName #

newtype SpanId Source #

An opaque & unique identifier for a trace segment, called a Span

Constructors

SpanId Int64 

Instances

Instances details
Eq SpanId Source # 
Instance details

Defined in Tracing.Core

Methods

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

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

Ord SpanId Source # 
Instance details

Defined in Tracing.Core

Show SpanId Source # 
Instance details

Defined in Tracing.Core

FromHttpApiData SpanId Source # 
Instance details

Defined in Tracing.Core

newtype TraceId Source #

An opaque & unique identifier for a logical operation. Traces are composed of many Spans

Constructors

TraceId Int64 

Instances

Instances details
Eq TraceId Source # 
Instance details

Defined in Tracing.Core

Methods

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

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

Ord TraceId Source # 
Instance details

Defined in Tracing.Core

Show TraceId Source # 
Instance details

Defined in Tracing.Core

FromHttpApiData TraceId Source # 
Instance details

Defined in Tracing.Core

data Tracer Source #

Global context required for tracing. The $sel:spanBuffer:Tracer should be manually drained by library users.

Constructors

Tracer 

Fields

class (Monad m, HasSpanId r, MonadReader r m) => MonadTracer m r where Source #

Indicates that the current monad can provide a Tracer and related context. It assumes some form of environment. While this exposes some mutable state, all of it is hidden away behind the recordSpan api.

Minimal complete definition

getTracer, currentTrace, isDebug

Methods

getTracer Source #

Arguments

:: m Tracer

Tracer is global to the process

currentTrace Source #

Arguments

:: m TraceId

Set during the initial request from the outside world, this is propagated across all nodes in the call

isDebug Source #

Arguments

:: m Bool

Set during the initial request from the outside world, this is propagated across all nodes in the call

currentSpan :: m SpanId Source #

class HasSpanId a where Source #

Methods

getSpanId :: a -> SpanId Source #

setSpanId :: a -> SpanId -> a Source #

class ToSpanTag a where Source #

The type in question may be converted into a SpanTag

Methods

toSpanTag :: a -> SpanTag Source #

Instances

Instances details
ToJSON a => ToSpanTag a Source # 
Instance details

Defined in Tracing.Core

Methods

toSpanTag :: a -> SpanTag Source #

ToSpanTag SpanTag Source # 
Instance details

Defined in Tracing.Core

data Tag Source #

Allows for easily representing multiple types in a tag list

Constructors

forall a.ToSpanTag a => Tag Text a 

recordSpan :: (MonadIO m, MonadBaseControl IO m, MonadTracer m r) => Maybe SpanRelationTag -> [Tag] -> OpName -> m a -> m a Source #

Wraps a computation & writes it to the Tracer's IORef. To start a new top-level span, and therefore a new trace, call this function with *spanType* == Nothing. Otherwise, this will create a child span.

Doesn't support parallel computations yet

debugPrintSpan :: Span -> Text Source #

Dump the details of a span. Used for debugging or logging