| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
OpenTracing.Span
Description
Data types and functions for manipulating spans
Synopsis
- data SpanContext = SpanContext {}
- ctxSampled :: Lens' SpanContext Sampled
- ctxBaggage :: Lens' SpanContext (HashMap Text Text)
- data Span
- newSpan :: (MonadIO m, Foldable t) => SpanContext -> Text -> SpanRefs -> t Tag -> m Span
- class HasSpanFields a
- data ActiveSpan
- mkActive :: MonadIO m => Span -> m ActiveSpan
- modifyActiveSpan :: MonadIO m => ActiveSpan -> (Span -> Span) -> m ()
- readActiveSpan :: MonadIO m => ActiveSpan -> m Span
- addTag :: MonadIO m => ActiveSpan -> Tag -> m ()
- addLogRecord :: MonadIO m => ActiveSpan -> LogField -> m ()
- addLogRecord' :: MonadIO m => ActiveSpan -> LogField -> [LogField] -> m ()
- setBaggageItem :: MonadIO m => ActiveSpan -> Text -> Text -> m ()
- getBaggageItem :: MonadIO m => ActiveSpan -> Text -> m (Maybe Text)
- data FinishedSpan
- spanFinish :: MonadIO m => Span -> m FinishedSpan
- spanContext :: HasSpanFields a => Lens' a SpanContext
- spanOperation :: HasSpanFields a => Lens' a Text
- spanStart :: HasSpanFields a => Lens' a UTCTime
- spanTags :: HasSpanFields a => Lens' a Tags
- spanRefs :: HasRefs s a => Lens' s a
- spanLogs :: HasSpanFields a => Lens' a [LogRecord]
- spanDuration :: Lens' FinishedSpan NominalDiffTime
- data SpanOpts
- spanOpts :: Text -> SpanRefs -> SpanOpts
- spanOptOperation :: Lens' SpanOpts Text
- spanOptRefs :: Lens' SpanOpts SpanRefs
- spanOptTags :: Lens' SpanOpts [Tag]
- spanOptSampled :: Lens' SpanOpts (Maybe Sampled)
- data Reference- = ChildOf { }
- | FollowsFrom { }
 
- findParent :: Foldable t => t Reference -> Maybe Reference
- data SpanRefs
- refActiveParents :: Lens' SpanRefs [ActiveSpan]
- refPredecessors :: Lens' SpanRefs [FinishedSpan]
- refPropagated :: Lens' SpanRefs [Reference]
- childOf :: ActiveSpan -> SpanRefs
- followsFrom :: FinishedSpan -> SpanRefs
- freezeRefs :: SpanRefs -> IO [Reference]
- data Sampled
- _IsSampled :: Iso' Bool Sampled
- sampled :: HasSampled a => Lens' a Sampled
- data Traced a = Traced {- tracedResult :: a
- tracedSpan :: ~FinishedSpan
 
Documentation
data SpanContext Source #
A SpanContext is the data that uniquely identifies a span
 and the context in which it occurs. Spans occur in traces, which form
 complete pictures of a computation, potentially across multiple machines.
Since: 0.1.0.0
Constructors
| SpanContext | |
| Fields 
 | |
Instances
| ToJSON SpanContext Source # | |
| Defined in OpenTracing.Span Methods toJSON :: SpanContext -> Value # toEncoding :: SpanContext -> Encoding # toJSONList :: [SpanContext] -> Value # toEncodingList :: [SpanContext] -> Encoding # | |
ctxBaggage :: Lens' SpanContext (HashMap Text Text) Source #
Span is a span that has been started (but not finished). See the OpenTracing spec for
 more info
Since: 0.1.0.0
class HasSpanFields a Source #
Minimal complete definition
Instances
| HasSpanFields FinishedSpan Source # | |
| Defined in OpenTracing.Span | |
| HasSpanFields Span Source # | |
data ActiveSpan Source #
A mutable Span that is currently being recorded.
Since: 0.1.0.0
modifyActiveSpan :: MonadIO m => ActiveSpan -> (Span -> Span) -> m () Source #
Since: 0.1.0.0
readActiveSpan :: MonadIO m => ActiveSpan -> m Span Source #
Since: 0.1.0.0
addLogRecord :: MonadIO m => ActiveSpan -> LogField -> m () Source #
Log structured data to an ActiveSpan. More info in the OpenTracing spec
Since: 0.1.0.0
addLogRecord' :: MonadIO m => ActiveSpan -> LogField -> [LogField] -> m () Source #
setBaggageItem :: MonadIO m => ActiveSpan -> Text -> Text -> m () Source #
getBaggageItem :: MonadIO m => ActiveSpan -> Text -> m (Maybe Text) Source #
data FinishedSpan Source #
A span that has finished executing.
Since: 0.1.0.0
Instances
| HasSpanFields FinishedSpan Source # | |
| Defined in OpenTracing.Span | |
spanFinish :: MonadIO m => Span -> m FinishedSpan Source #
Convert an unfinished Span into a FinishedSpan
Since: 0.1.0.0
spanContext :: HasSpanFields a => Lens' a SpanContext Source #
spanOperation :: HasSpanFields a => Lens' a Text Source #
SpanOpts is the metadata information about a span needed in order to start
 measuring a span. This is the information that application code will provide in
 order to indicate what a span is doing and how it related to other spans. More info
 in the OpenTracing spec
Since: 0.1.0.0
spanOpts :: Text -> SpanRefs -> SpanOpts Source #
Create a new SpanOpts with the minimal amount of required information.
Since: 0.1.0.0
A reference from one span to another. Spans can be related in two ways:
- ChildOfindicates that the parent span is dependent on the child span in order to produce its own result.
- FollowsFromindicates that there is no dependence relation, perhaps the parent span spawned an asynchronous task.
More info in the OpenTracing spec
Since: 0.1.0.0
Constructors
| ChildOf | |
| Fields | |
| FollowsFrom | |
| Fields | |
The different references that a span can hold to other spans.
Since: 0.1.0.0
childOf :: ActiveSpan -> SpanRefs Source #
Create a SpanRefs containing the single refrence to a parent span.
Since: 0.1.0.0
followsFrom :: FinishedSpan -> SpanRefs Source #
Create a SpanRefs containing the single refrence to a predecessor span.
Since: 0.1.0.0
freezeRefs :: SpanRefs -> IO [Reference] Source #
Convert SpanRefs (which may include the mutable ActiveSpans) into
 an immutable list of References
Since: 0.1.0.0
A datatype indicating whether a recorded span was sampled, i.e. whether or not it will be reported. Traces are often sampled in high volume environments to keep the amount of data generated manageable.
Since: 0.1.0.0
Constructors
| NotSampled | |
| Sampled | 
Instances
| Bounded Sampled Source # | |
| Enum Sampled Source # | |
| Eq Sampled Source # | |
| Read Sampled Source # | |
| Show Sampled Source # | |
| ToJSON Sampled Source # | |
| Defined in OpenTracing.Span | |
A wrapper for a value that was produced by a traced computation.
Since: 0.1.0.0
Constructors
| Traced | |
| Fields 
 | |