opentracing-0.1.0.0: OpenTracing for Haskell
Safe HaskellNone
LanguageHaskell2010

OpenTracing

Description

The OpenTracing spec defines a platform agnostic approach for distributed tracing. Distributed tracing gives us insights into how complex programs spread across multiple processes are performing together.

This package provides a core implementation of the OpenTracing spec. It includes functionality to

It does not provide any functionality for consuming Spans. There are platform specific backends (CloudTrace, Zipkin, Jaeger, etc) that are provided in other packages.

Synopsis

Distributed tracing

These are mtl style constraints and runners for working with tracers in a distributed environment. When traces cross process boundaries (for example in an RPC call, information about the SpanContext needs to be transmitted from one process to another, so that all Spans in the same trace can be reported in the same trace forest.

To satisfy these constraints, you have to have access to a Propagation in the application environment, which manages serialization and deserialization of SpanContexts.

runOpenTracing :: HasOpenTracing r p => r -> ReaderT r m a -> m a Source #

Local tracing

If you aren't tracing a distributed system, these simpler constraints will work. The only thing required is a Tracer in the application context. If the program execution crosses process boundaries, no serialization will be performed.

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 #

Tracing functions

Functions to trace application code

traced Source #

Arguments

:: (MonadTracer r m, MonadMask m, MonadIO m) 
=> 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 (spanOpts "hello" mempty          ) $ parent ->
        traced (spanOpts "world" (childOf parent)) $ child ->
           liftIO $ do
               putStrLn "doing some work..."
               addLogRecord child (Message "doing some work")
               threadDelay 500000

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

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

Propagation

Functions for serialization and deserialization in a distributed tracing environment

extract :: forall c r p m. (MonadPropagation r p m, HasCarrier c p) => c -> m (Maybe SpanContext) Source #

Attempt to deserialize a SpanContext from the format c using a deserializer from the application context. See Propagation for more info.

inject :: forall c r p m. (MonadPropagation r p m, HasCarrier c p) => SpanContext -> m c Source #

Serialize a SpanContext into the format c using a serializer from the application context. See Propagation for more info.

Additional modules

rcast :: forall k1 k2 (rs :: [k1]) (ss :: [k1]) (f :: k2 -> Type) record (is :: [Nat]). (RecSubset record rs ss is, RecSubsetFCtx record f) => record f ss -> record f rs #

Takes a larger record to a smaller one by forgetting fields. This is rcastC with the type arguments reordered for more convenient usage with TypeApplications.

(<+>) :: forall k (f :: k -> Type) (as :: [k]) (bs :: [k]). Rec f as -> Rec f bs -> Rec f (as ++ bs) infixr 5 #

A shorthand for rappend.

rappend :: forall k (f :: k -> Type) (as :: [k]) (bs :: [k]). Rec f as -> Rec f bs -> Rec f (as ++ bs) #

Two records may be pasted together.

data Rec (a :: u -> Type) (b :: [u]) where #

A record is parameterized by a universe u, an interpretation f and a list of rows rs. The labels or indices of the record are given by inhabitants of the kind u; the type of values at any label r :: u is given by its interpretation f r :: *.

Constructors

RNil :: forall u (a :: u -> Type). Rec a ('[] :: [u]) 
(:&) :: forall u (a :: u -> Type) (r :: u) (rs :: [u]). !(a r) -> !(Rec a rs) -> Rec a (r ': rs) infixr 7 

Instances

Instances details
RecSubset (Rec :: (k -> Type) -> [k] -> Type) ('[] :: [k]) (ss :: [k]) ('[] :: [Nat]) 
Instance details

Defined in Data.Vinyl.Lens

Associated Types

type RecSubsetFCtx Rec f #

Methods

rsubsetC :: forall g (f :: k0 -> Type). (Functor g, RecSubsetFCtx Rec f) => (Rec f '[] -> g (Rec f '[])) -> Rec f ss -> g (Rec f ss) #

rcastC :: forall (f :: k0 -> Type). RecSubsetFCtx Rec f => Rec f ss -> Rec f '[] #

rreplaceC :: forall (f :: k0 -> Type). RecSubsetFCtx Rec f => Rec f '[] -> Rec f ss -> Rec f ss #

(RElem r ss i, RSubset rs ss is) => RecSubset (Rec :: (k -> Type) -> [k] -> Type) (r ': rs :: [k]) (ss :: [k]) (i ': is) 
Instance details

Defined in Data.Vinyl.Lens

Associated Types

type RecSubsetFCtx Rec f #

Methods

rsubsetC :: forall g (f :: k0 -> Type). (Functor g, RecSubsetFCtx Rec f) => (Rec f (r ': rs) -> g (Rec f (r ': rs))) -> Rec f ss -> g (Rec f ss) #

rcastC :: forall (f :: k0 -> Type). RecSubsetFCtx Rec f => Rec f ss -> Rec f (r ': rs) #

rreplaceC :: forall (f :: k0 -> Type). RecSubsetFCtx Rec f => Rec f (r ': rs) -> Rec f ss -> Rec f ss #

RecElem (Rec :: (a -> Type) -> [a] -> Type) (r :: a) (r' :: a) (r ': rs :: [a]) (r' ': rs :: [a]) 'Z 
Instance details

Defined in Data.Vinyl.Lens

Associated Types

type RecElemFCtx Rec f #

Methods

rlensC :: (Functor g, RecElemFCtx Rec f) => (f r -> g (f r')) -> Rec f (r ': rs) -> g (Rec f (r' ': rs)) #

rgetC :: (RecElemFCtx Rec f, r ~ r') => Rec f (r ': rs) -> f r #

rputC :: RecElemFCtx Rec f => f r' -> Rec f (r ': rs) -> Rec f (r' ': rs) #

(RIndex r (s ': rs) ~ 'S i, RecElem (Rec :: (a -> Type) -> [a] -> Type) r r' rs rs' i) => RecElem (Rec :: (a -> Type) -> [a] -> Type) (r :: a) (r' :: a) (s ': rs :: [a]) (s ': rs' :: [a]) ('S i) 
Instance details

Defined in Data.Vinyl.Lens

Associated Types

type RecElemFCtx Rec f #

Methods

rlensC :: (Functor g, RecElemFCtx Rec f) => (f r -> g (f r')) -> Rec f (s ': rs) -> g (Rec f (s ': rs')) #

rgetC :: (RecElemFCtx Rec f, r ~ r') => Rec f (s ': rs) -> f r #

rputC :: RecElemFCtx Rec f => f r' -> Rec f (s ': rs) -> Rec f (s ': rs') #

HasPropagation (Propagation p) p Source # 
Instance details

Defined in OpenTracing.Propagation

TestCoercion f => TestCoercion (Rec f :: [u] -> Type) 
Instance details

Defined in Data.Vinyl.Core

Methods

testCoercion :: forall (a :: k) (b :: k). Rec f a -> Rec f b -> Maybe (Coercion a b) #

TestEquality f => TestEquality (Rec f :: [u] -> Type) 
Instance details

Defined in Data.Vinyl.Core

Methods

testEquality :: forall (a :: k) (b :: k). Rec f a -> Rec f b -> Maybe (a :~: b) #

Eq (Rec f ('[] :: [u])) 
Instance details

Defined in Data.Vinyl.Core

Methods

(==) :: Rec f '[] -> Rec f '[] -> Bool #

(/=) :: Rec f '[] -> Rec f '[] -> Bool #

(Eq (f r), Eq (Rec f rs)) => Eq (Rec f (r ': rs)) 
Instance details

Defined in Data.Vinyl.Core

Methods

(==) :: Rec f (r ': rs) -> Rec f (r ': rs) -> Bool #

(/=) :: Rec f (r ': rs) -> Rec f (r ': rs) -> Bool #

Ord (Rec f ('[] :: [u])) 
Instance details

Defined in Data.Vinyl.Core

Methods

compare :: Rec f '[] -> Rec f '[] -> Ordering #

(<) :: Rec f '[] -> Rec f '[] -> Bool #

(<=) :: Rec f '[] -> Rec f '[] -> Bool #

(>) :: Rec f '[] -> Rec f '[] -> Bool #

(>=) :: Rec f '[] -> Rec f '[] -> Bool #

max :: Rec f '[] -> Rec f '[] -> Rec f '[] #

min :: Rec f '[] -> Rec f '[] -> Rec f '[] #

(Ord (f r), Ord (Rec f rs)) => Ord (Rec f (r ': rs)) 
Instance details

Defined in Data.Vinyl.Core

Methods

compare :: Rec f (r ': rs) -> Rec f (r ': rs) -> Ordering #

(<) :: Rec f (r ': rs) -> Rec f (r ': rs) -> Bool #

(<=) :: Rec f (r ': rs) -> Rec f (r ': rs) -> Bool #

(>) :: Rec f (r ': rs) -> Rec f (r ': rs) -> Bool #

(>=) :: Rec f (r ': rs) -> Rec f (r ': rs) -> Bool #

max :: Rec f (r ': rs) -> Rec f (r ': rs) -> Rec f (r ': rs) #

min :: Rec f (r ': rs) -> Rec f (r ': rs) -> Rec f (r ': rs) #

(RMap rs, ReifyConstraint Show f rs, RecordToList rs) => Show (Rec f rs)

Records may be shown insofar as their points may be shown. reifyConstraint is used to great effect here.

Instance details

Defined in Data.Vinyl.Core

Methods

showsPrec :: Int -> Rec f rs -> ShowS #

show :: Rec f rs -> String #

showList :: [Rec f rs] -> ShowS #

Generic (Rec f ('[] :: [u])) 
Instance details

Defined in Data.Vinyl.Core

Associated Types

type Rep (Rec f '[]) :: Type -> Type #

Methods

from :: Rec f '[] -> Rep (Rec f '[]) x #

to :: Rep (Rec f '[]) x -> Rec f '[] #

Generic (Rec f rs) => Generic (Rec f (r ': rs)) 
Instance details

Defined in Data.Vinyl.Core

Associated Types

type Rep (Rec f (r ': rs)) :: Type -> Type #

Methods

from :: Rec f (r ': rs) -> Rep (Rec f (r ': rs)) x #

to :: Rep (Rec f (r ': rs)) x -> Rec f (r ': rs) #

Semigroup (Rec f ('[] :: [u])) 
Instance details

Defined in Data.Vinyl.Core

Methods

(<>) :: Rec f '[] -> Rec f '[] -> Rec f '[] #

sconcat :: NonEmpty (Rec f '[]) -> Rec f '[] #

stimes :: Integral b => b -> Rec f '[] -> Rec f '[] #

(Semigroup (f r), Semigroup (Rec f rs)) => Semigroup (Rec f (r ': rs)) 
Instance details

Defined in Data.Vinyl.Core

Methods

(<>) :: Rec f (r ': rs) -> Rec f (r ': rs) -> Rec f (r ': rs) #

sconcat :: NonEmpty (Rec f (r ': rs)) -> Rec f (r ': rs) #

stimes :: Integral b => b -> Rec f (r ': rs) -> Rec f (r ': rs) #

Monoid (Rec f ('[] :: [u])) 
Instance details

Defined in Data.Vinyl.Core

Methods

mempty :: Rec f '[] #

mappend :: Rec f '[] -> Rec f '[] -> Rec f '[] #

mconcat :: [Rec f '[]] -> Rec f '[] #

(Monoid (f r), Monoid (Rec f rs)) => Monoid (Rec f (r ': rs)) 
Instance details

Defined in Data.Vinyl.Core

Methods

mempty :: Rec f (r ': rs) #

mappend :: Rec f (r ': rs) -> Rec f (r ': rs) -> Rec f (r ': rs) #

mconcat :: [Rec f (r ': rs)] -> Rec f (r ': rs) #

Storable (Rec f ('[] :: [u])) 
Instance details

Defined in Data.Vinyl.Core

Methods

sizeOf :: Rec f '[] -> Int #

alignment :: Rec f '[] -> Int #

peekElemOff :: Ptr (Rec f '[]) -> Int -> IO (Rec f '[]) #

pokeElemOff :: Ptr (Rec f '[]) -> Int -> Rec f '[] -> IO () #

peekByteOff :: Ptr b -> Int -> IO (Rec f '[]) #

pokeByteOff :: Ptr b -> Int -> Rec f '[] -> IO () #

peek :: Ptr (Rec f '[]) -> IO (Rec f '[]) #

poke :: Ptr (Rec f '[]) -> Rec f '[] -> IO () #

(Storable (f r), Storable (Rec f rs)) => Storable (Rec f (r ': rs)) 
Instance details

Defined in Data.Vinyl.Core

Methods

sizeOf :: Rec f (r ': rs) -> Int #

alignment :: Rec f (r ': rs) -> Int #

peekElemOff :: Ptr (Rec f (r ': rs)) -> Int -> IO (Rec f (r ': rs)) #

pokeElemOff :: Ptr (Rec f (r ': rs)) -> Int -> Rec f (r ': rs) -> IO () #

peekByteOff :: Ptr b -> Int -> IO (Rec f (r ': rs)) #

pokeByteOff :: Ptr b -> Int -> Rec f (r ': rs) -> IO () #

peek :: Ptr (Rec f (r ': rs)) -> IO (Rec f (r ': rs)) #

poke :: Ptr (Rec f (r ': rs)) -> Rec f (r ': rs) -> IO () #

ReifyConstraint NFData f xs => NFData (Rec f xs) 
Instance details

Defined in Data.Vinyl.Core

Methods

rnf :: Rec f xs -> () #

type RecSubsetFCtx (Rec :: (k -> Type) -> [k] -> Type) (f :: k -> Type) 
Instance details

Defined in Data.Vinyl.Lens

type RecSubsetFCtx (Rec :: (k -> Type) -> [k] -> Type) (f :: k -> Type) = ()
type RecSubsetFCtx (Rec :: (k -> Type) -> [k] -> Type) (f :: k -> Type) 
Instance details

Defined in Data.Vinyl.Lens

type RecSubsetFCtx (Rec :: (k -> Type) -> [k] -> Type) (f :: k -> Type) = ()
type RecElemFCtx (Rec :: (a -> Type) -> [a] -> Type) (f :: a -> Type) 
Instance details

Defined in Data.Vinyl.Lens

type RecElemFCtx (Rec :: (a -> Type) -> [a] -> Type) (f :: a -> Type) = ()
type RecElemFCtx (Rec :: (a -> Type) -> [a] -> Type) (f :: a -> Type) 
Instance details

Defined in Data.Vinyl.Lens

type RecElemFCtx (Rec :: (a -> Type) -> [a] -> Type) (f :: a -> Type) = ()
type Rep (Rec f (r ': rs)) 
Instance details

Defined in Data.Vinyl.Core

type Rep (Rec f ('[] :: [u])) 
Instance details

Defined in Data.Vinyl.Core

type HasCarriers cs ds = cs ds Source #

type HasCarrier c cs = c cs Source #

newtype Carrier a Source #

`Carrier a` is a way to convert a SpanContext into or from an a.

Since: 0.1.0.0

Constructors

Carrier 

Instances

Instances details
HasPropagation (Propagation p) p Source # 
Instance details

Defined in OpenTracing.Propagation

class HasPropagation a p | a -> p where Source #

A typeclass for application environments that contain a Propagation.

Since: 0.1.0.0

Instances

Instances details
HasPropagation (Propagation p) p Source # 
Instance details

Defined in OpenTracing.Propagation

type Propagation carriers = Rec Carrier carriers Source #

A Propagation contains the different ways that a SpanContext can be serialized and deserialized. For example Propagation '[TextMap, Headers] indicates support for serializing to Header or to TextMap.

Since: 0.1.0.0

carrier Source #

Arguments

:: (HasCarrier c cs, HasPropagation r cs) 
=> proxy c

Proxy for the carrier type c.

-> r

The application context

-> Prism' c SpanContext 

Retrieve a (de)serialization lens from the application context for format c.

Since: 0.1.0.0

otPropagation :: Propagation '[TextMap, Headers] Source #

A propagation using an "ot" prefix. No parent span id is propagated in OT.

b3Propagation :: Propagation '[TextMap, Headers] Source #

A propagation using an "x-b3" prefix for use with Zipkin.

_HeadersTextMap :: Iso' Headers TextMap Source #

Convert between a TextMap and Headers

Header field values are URL-encoded when converting from TextMap to Headers, and URL-decoded when converting the other way.

Note: validity of header fields is not checked (RFC 7230, 3.2.4)