Safe Haskell | None |
---|---|
Language | Haskell2010 |
Tracing.Core
Synopsis
- data Span = Span {
- operationName :: !OpName
- context :: !SpanContext
- timestamp :: !POSIXTime
- duration :: !NominalDiffTime
- relations :: ![SpanRelation]
- tags :: !(Map Text SpanTag)
- baggage :: !(Map Text Text)
- debug :: !Bool
- serviceName :: !Text
- data SpanRelation
- data SpanRelationTag
- data SpanContext = SpanContext {}
- data SpanTag
- newtype OpName = OpName Text
- newtype SpanId = SpanId Int64
- newtype TraceId = TraceId Int64
- data Tracer = Tracer {
- spanBuffer :: IORef [Span]
- svcName :: Text
- data TracingInstructions = TracingInstructions {}
- class (Monad m, HasSpanId r, MonadReader r m) => MonadTracer m r where
- getTracer :: m Tracer
- currentTrace :: m TraceId
- isDebug :: m Bool
- currentSpan :: m SpanId
- class HasSpanId a where
- class ToSpanTag a where
- data Tag = forall a.ToSpanTag a => Tag Text a
- recordSpan :: (MonadIO m, MonadBaseControl IO m, MonadTracer m r) => Maybe SpanRelationTag -> [Tag] -> OpName -> m a -> m a
- debugPrintSpan :: Span -> Text
Documentation
A timed section of code with a logical name and SpanContext
. Individual spans will be reconstructed by an
OpenTracing backend into a single trace.
Constructors
Span | |
Fields
|
data SpanRelation Source #
Spans may be top level, a child, or logically follow from a given span.
Constructors
ChildOf !SpanContext | |
FollowsFrom !SpanContext |
Instances
Eq SpanRelation Source # | |
Defined in Tracing.Core | |
Show SpanRelation Source # | |
Defined in Tracing.Core Methods showsPrec :: Int -> SpanRelation -> ShowS # show :: SpanRelation -> String # showList :: [SpanRelation] -> ShowS # |
data SpanRelationTag Source #
Indicates the type of relation this span represents
data SpanContext Source #
Uniquely identifies a given Span
& points to its encompasing trace
Constructors
SpanContext | |
Instances
Eq SpanContext Source # | |
Defined in Tracing.Core | |
Show SpanContext Source # | |
Defined in Tracing.Core Methods showsPrec :: Int -> SpanContext -> ShowS # show :: SpanContext -> String # showList :: [SpanContext] -> ShowS # |
Used to embed additional information into a Span for consumption & viewing in a tracing backend
Human-readable name for the span
An opaque & unique identifier for a trace segment, called a Span
An opaque & unique identifier for a logical operation. Traces are composed of many Span
s
Global context required for tracing. The $sel:spanBuffer:Tracer
should be manually drained by library users.
data TracingInstructions Source #
Instructions that are specific to a single trace
Constructors
TracingInstructions | |
Instances
Eq TracingInstructions Source # | |
Defined in Tracing.Core Methods (==) :: TracingInstructions -> TracingInstructions -> Bool # (/=) :: TracingInstructions -> TracingInstructions -> Bool # | |
Show TracingInstructions Source # | |
Defined in Tracing.Core Methods showsPrec :: Int -> TracingInstructions -> ShowS # show :: TracingInstructions -> String # showList :: [TracingInstructions] -> ShowS # | |
FromHttpApiData TracingInstructions Source # | |
Defined in Servant.Tracing Methods parseUrlPiece :: Text -> Either Text TracingInstructions # parseHeader :: ByteString -> Either Text TracingInstructions # parseQueryParam :: Text -> Either Text TracingInstructions # |
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
Allows for easily representing multiple types in a tag list
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