instana-haskell-trace-sdk-0.10.2.0: SDK for adding custom Instana tracing support to Haskell applications.
Safe HaskellNone
LanguageHaskell2010

Instana.SDK.Span.Span

Description

 
Synopsis

Documentation

data Span Source #

A span.

Constructors

Entry EntrySpan 
Exit ExitSpan 

Instances

Instances details
Eq Span Source # 
Instance details

Defined in Instana.SDK.Span.Span

Methods

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

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

Show Span Source # 
Instance details

Defined in Instana.SDK.Span.Span

Methods

showsPrec :: Int -> Span -> ShowS #

show :: Span -> String #

showList :: [Span] -> ShowS #

Generic Span Source # 
Instance details

Defined in Instana.SDK.Span.Span

Associated Types

type Rep Span :: Type -> Type #

Methods

from :: Span -> Rep Span x #

to :: Rep Span x -> Span #

type Rep Span Source # 
Instance details

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)))

data SpanKind Source #

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

Instances details
Eq SpanKind Source # 
Instance details

Defined in Instana.SDK.Span.Span

Show SpanKind Source # 
Instance details

Defined in Instana.SDK.Span.Span

Generic SpanKind Source # 
Instance details

Defined in Instana.SDK.Span.Span

Associated Types

type Rep SpanKind :: Type -> Type #

Methods

from :: SpanKind -> Rep SpanKind x #

to :: Rep SpanKind x -> SpanKind #

type Rep SpanKind Source # 
Instance details

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.

addToErrorCount :: Int -> Span -> Span Source #

Add to the error count.

correlationId :: Span -> Maybe Text Source #

The website monitoring correlation ID.

correlationType :: Span -> Maybe Text Source #

The website monitoring correlation type.

errorCount :: Span -> Int Source #

Error count.

initialData :: SpanKind -> SpanType -> SpanData Source #

Returns the initial data (span.data) for a SpanType value.

parentId :: Span -> Maybe Id Source #

Parent span ID.

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.

spanData :: Span -> SpanData Source #

Optional additional span data.

spanId :: Span -> Id Source #

Accessor for the span ID.

spanKind :: Span -> SpanKind Source #

Kind of span.

spanName :: Span -> Text Source #

Name of span.

spanType :: Span -> SpanType Source #

Type of span (registerd span vs. SDK span)

synthetic :: Span -> Bool Source #

The synthetic flag.

timestamp :: Span -> Int Source #

Start time.

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.

traceId :: Span -> Id Source #

Accessor for the trace ID.

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.