Safe Haskell | None |
---|---|
Language | Haskell2010 |
Instana.SDK.Span.Span
Description
Synopsis
- data Span
- data SpanKind
- addAnnotation :: Annotation -> Span -> Span
- addAnnotationAt :: Text -> Annotation -> Span -> Span
- addAnnotationValueAt :: Text -> AnnotationValue -> Span -> Span
- addJsonValueAt :: ToJSON a => Text -> a -> Span -> Span
- addToErrorCount :: Int -> Span -> Span
- correlationId :: Span -> Maybe Text
- correlationType :: Span -> Maybe Text
- errorCount :: Span -> Int
- initialData :: SpanKind -> SpanType -> SpanData
- parentId :: Span -> Maybe Id
- serviceName :: Span -> Maybe Text
- setCorrelationId :: Text -> Span -> Span
- setCorrelationType :: Text -> Span -> Span
- setServiceName :: Text -> Span -> Span
- setSynthetic :: Bool -> Span -> Span
- setTpFlag :: Span -> Span
- setW3cTraceContext :: W3CTraceContext -> Span -> Span
- spanData :: Span -> SpanData
- spanId :: Span -> Id
- spanKind :: Span -> SpanKind
- spanName :: Span -> Text
- spanType :: Span -> SpanType
- synthetic :: Span -> Bool
- timestamp :: Span -> Int
- tpFlag :: Span -> Bool
- traceId :: Span -> Id
- w3cTraceContext :: Span -> Maybe W3CTraceContext
Documentation
A span.
Instances
Eq Span Source # | |
Show Span Source # | |
Generic Span Source # | |
type Rep Span Source # | |
Defined in Instana.SDK.Span.Span type Rep Span = D1 ('MetaData "Span" "Instana.SDK.Span.Span" "instana-haskell-trace-sdk-0.10.2.0-inplace" 'False) (C1 ('MetaCons "Entry" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 EntrySpan)) :+: C1 ('MetaCons "Exit" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ExitSpan))) |
The span kind (entry, exit or intermediate).
Constructors
EntryKind | The monitored componenent receives a call. |
ExitKind | The monitored componenent calls something else. |
IntermediateKind | An additional annotation that is added to the trace while a traced call is being processed. |
Instances
Eq SpanKind Source # | |
Show SpanKind Source # | |
Generic SpanKind Source # | |
type Rep SpanKind Source # | |
Defined in Instana.SDK.Span.Span type Rep SpanKind = D1 ('MetaData "SpanKind" "Instana.SDK.Span.Span" "instana-haskell-trace-sdk-0.10.2.0-inplace" 'False) (C1 ('MetaCons "EntryKind" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "ExitKind" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "IntermediateKind" 'PrefixI 'False) (U1 :: Type -> Type))) |
addAnnotation :: Annotation -> Span -> Span Source #
Add an annotation to the span's data section. For SDK spans, the annotation is added to span.data.sdk.custom.tags, for registered spans it is added directly to span.data.
addAnnotationAt :: Text -> Annotation -> Span -> Span Source #
Add an annotation at the given path to the span's data section.
addAnnotationValueAt :: Text -> AnnotationValue -> Span -> Span Source #
Add a list value at the given path to the span's data section. For SDK spans, you should use addAnnotationValueToSdkSpan instead. For annotations with simple values (string, number, boolean, etc.), you can also use the convenience function addAnnotationAt.
addJsonValueAt :: ToJSON a => Text -> a -> Span -> Span Source #
Add a simple value (string, boolean, number) at the given path to the span's data section. Should not be used for objects or lists in case you intend to merge them with additional values at the same path later.
errorCount :: Span -> Int Source #
Error count.
initialData :: SpanKind -> SpanType -> SpanData Source #
Returns the initial data (span.data) for a SpanType value.
serviceName :: Span -> Maybe Text Source #
An optional attribute for overriding the name of the service in Instana.
setCorrelationId :: Text -> Span -> Span Source #
Set the website monitoring correlation ID. This should only be set on root entry spans. It will be silently ignored for other types of spans.
setCorrelationType :: Text -> Span -> Span Source #
Set the website monitoring correlation type. This should only be set on root entry spans. It will be silently ignored for other types of spans.
setServiceName :: Text -> Span -> Span Source #
Override the name of the service for the associated call in Instana.
setSynthetic :: Bool -> Span -> Span Source #
Set the synthetic flag. This should only be set on entry spans. It will be silently ignored for other types of spans.
setTpFlag :: Span -> Span Source #
Set the span.tp flag. A span with span.tp = True has inherited the trace ID/ parent ID from W3C trace context instead of Instana headers. Only valid for non-root entry spans, will be silently ignored for root entry spans and exit spans.
setW3cTraceContext :: W3CTraceContext -> Span -> Span Source #
Attaches a W3C trace context to the span.
tpFlag :: Span -> Bool Source #
The span.tp flag. A span with span.tp = True has inherited the trace ID/ parent ID from W3C trace context instead of Instana headers. Only valid for non-root entry spans.
w3cTraceContext :: Span -> Maybe W3CTraceContext Source #
The W3C Trace Context. An entry span only has an associated W3C trace context, if W3C trace context headers have been received. In contrast, exit spans always have an associated W3C trace context.