hs-opentelemetry-sdk-0.0.1.0: OpenTelemetry SDK for use in applications.
Safe HaskellNone
LanguageHaskell2010

OpenTelemetry.Trace

Synopsis

TracerProvider operations

data TracerProvider #

Tracers can be create from a TracerProvider.

shutdownTracerProvider :: MonadIO m => TracerProvider -> m () #

This method provides a way for provider to do any cleanup required.

This will also trigger shutdowns on all internal processors.

Since: hs-opentelemetry-api-0.0.1.0

Getting / setting the global TracerProvider

Alternative TracerProvider initialization

createTracerProvider :: MonadIO m => [Processor] -> TracerProviderOptions -> m TracerProvider #

Initialize a new tracer provider

You should generally use getGlobalTracerProvider for most applications.

Tracer operations

data Tracer #

The Tracer is responsible for creating Spans.

Each Tracer should be associated with the library or application that it instruments.

newtype TracerOptions #

Constructors

TracerOptions 

class HasTracer s where #

Methods

tracerL :: Lens' s Tracer #

data InstrumentationLibrary #

Instances

Instances details
Eq InstrumentationLibrary 
Instance details

Defined in OpenTelemetry.Internal.Trace.Types

Ord InstrumentationLibrary 
Instance details

Defined in OpenTelemetry.Internal.Trace.Types

Show InstrumentationLibrary 
Instance details

Defined in OpenTelemetry.Internal.Trace.Types

IsString InstrumentationLibrary 
Instance details

Defined in OpenTelemetry.Internal.Trace.Types

Generic InstrumentationLibrary 
Instance details

Defined in OpenTelemetry.Internal.Trace.Types

Associated Types

type Rep InstrumentationLibrary :: Type -> Type #

Hashable InstrumentationLibrary 
Instance details

Defined in OpenTelemetry.Internal.Trace.Types

type Rep InstrumentationLibrary 
Instance details

Defined in OpenTelemetry.Internal.Trace.Types

type Rep InstrumentationLibrary = D1 ('MetaData "InstrumentationLibrary" "OpenTelemetry.Internal.Trace.Types" "hs-opentelemetry-api-0.0.1.0-6Dv2z1KBcop7UAQrDIczSS" 'False) (C1 ('MetaCons "InstrumentationLibrary" 'PrefixI 'True) (S1 ('MetaSel ('Just "libraryName") 'SourceUnpack 'SourceStrict 'DecidedStrict) (Rec0 Text) :*: S1 ('MetaSel ('Just "libraryVersion") 'SourceUnpack 'SourceStrict 'DecidedStrict) (Rec0 Text)))

Span operations

data Span #

createSpan #

Arguments

:: (MonadIO m, HasCallStack) 
=> Tracer

Tracer to create the span from. Associated Processors and Exporters will be used for the lifecycle of the created Span

-> Context

Context, potentially containing a parent span. If no existing parent (or context) exists, you can use empty.

-> Text

Span name

-> SpanArguments

Additional span information

-> m Span

The created span.

Create a Span.

If the provided Context has a span in it (inserted via insertSpan), that Span will be used as the parent of the Span created via this API.

Note: if the hs-opentelemetry-sdk or another SDK is not installed, all actions that use the created Spans produced will be no-ops.

Since: hs-opentelemetry-api-0.0.1.0

createSpanWithoutCallStack #

Arguments

:: MonadIO m 
=> Tracer

Tracer to create the span from. Associated Processors and Exporters will be used for the lifecycle of the created Span

-> Context

Context, potentially containing a parent span. If no existing parent (or context) exists, you can use empty.

-> Text

Span name

-> SpanArguments

Additional span information

-> m Span

The created span.

The same thing as createSpan, except that it does not have a HasCallStack constraint.

defaultSpanArguments :: SpanArguments #

Smart constructor for SpanArguments providing reasonable values for most Spans created that are internal to an application.

Defaults:

data SpanArguments #

Non-name fields that may be set on initial creation of a Span.

Constructors

SpanArguments 

Fields

updateName #

Arguments

:: MonadIO m 
=> Span 
-> Text

The new span name, which supersedes whatever was passed in when the Span was started

-> m () 

Updates the Span name. Upon this update, any sampling behavior based on Span name will depend on the implementation.

Note that Samplers can only consider information already present during span creation. Any changes done later, including updated span name, cannot change their decisions.

Alternatives for the name update may be late Span creation, when Span is started with the explicit timestamp from the past at the moment where the final Span name is known, or reporting a Span with the desired name as a child Span.

Since: hs-opentelemetry-api-0.0.1.0

addAttribute :: (MonadIO m, ToAttribute a) => Span -> Text -> a -> m () #

As an application developer when you need to record an attribute first consult existing semantic conventions for Resources, Spans, and Metrics. If an appropriate name does not exists you will need to come up with a new name. To do that consider a few options:

The name is specific to your company and may be possibly used outside the company as well. To avoid clashes with names introduced by other companies (in a distributed system that uses applications from multiple vendors) it is recommended to prefix the new name by your company’s reverse domain name, e.g. 'com.acme.shopname'.

The name is specific to your application that will be used internally only. If you already have an internal company process that helps you to ensure no name clashes happen then feel free to follow it. Otherwise it is recommended to prefix the attribute name by your application name, provided that the application name is reasonably unique within your organization (e.g. 'myuniquemapapp.longitude' is likely fine). Make sure the application name does not clash with an existing semantic convention namespace.

The name may be generally applicable to applications in the industry. In that case consider submitting a proposal to this specification to add a new name to the semantic conventions, and if necessary also to add a new namespace.

It is recommended to limit names to printable Basic Latin characters (more precisely to 'U+0021' .. 'U+007E' subset of Unicode code points), although the Haskell OpenTelemetry specification DOES provide full Unicode support.

Attribute names that start with 'otel.' are reserved to be defined by OpenTelemetry specification. These are typically used to express OpenTelemetry concepts in formats that don’t have a corresponding concept.

For example, the 'otel.library.name' attribute is used to record the instrumentation library name, which is an OpenTelemetry concept that is natively represented in OTLP, but does not have an equivalent in other telemetry formats and protocols.

Any additions to the 'otel.*' namespace MUST be approved as part of OpenTelemetry specification.

addAttributes :: MonadIO m => Span -> [(Text, Attribute)] -> m () #

spanGetAttributes :: MonadIO m => Span -> m Attributes #

This can be useful for pulling data for attributes and using it to copy / otherwise use the data to further enrich instrumentation.

class ToAttribute a where #

Minimal complete definition

Nothing

Methods

toAttribute :: a -> Attribute #

Instances

Instances details
ToAttribute Bool 
Instance details

Defined in OpenTelemetry.Attributes

ToAttribute Double 
Instance details

Defined in OpenTelemetry.Attributes

ToAttribute Int 
Instance details

Defined in OpenTelemetry.Attributes

Methods

toAttribute :: Int -> Attribute #

ToAttribute Int64 
Instance details

Defined in OpenTelemetry.Attributes

ToAttribute Text 
Instance details

Defined in OpenTelemetry.Attributes

ToAttribute Attribute 
Instance details

Defined in OpenTelemetry.Attributes

ToAttribute PrimitiveAttribute 
Instance details

Defined in OpenTelemetry.Attributes

ToPrimitiveAttribute a => ToAttribute [a] 
Instance details

Defined in OpenTelemetry.Attributes

Methods

toAttribute :: [a] -> Attribute #

data Attribute #

Instances

Instances details
Eq Attribute 
Instance details

Defined in OpenTelemetry.Attributes

Data Attribute 
Instance details

Defined in OpenTelemetry.Attributes

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Attribute -> c Attribute #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Attribute #

toConstr :: Attribute -> Constr #

dataTypeOf :: Attribute -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Attribute) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Attribute) #

gmapT :: (forall b. Data b => b -> b) -> Attribute -> Attribute #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Attribute -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Attribute -> r #

gmapQ :: (forall d. Data d => d -> u) -> Attribute -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Attribute -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Attribute -> m Attribute #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Attribute -> m Attribute #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Attribute -> m Attribute #

Ord Attribute 
Instance details

Defined in OpenTelemetry.Attributes

Read Attribute 
Instance details

Defined in OpenTelemetry.Attributes

Show Attribute 
Instance details

Defined in OpenTelemetry.Attributes

Generic Attribute 
Instance details

Defined in OpenTelemetry.Attributes

Associated Types

type Rep Attribute :: Type -> Type #

Hashable Attribute 
Instance details

Defined in OpenTelemetry.Attributes

ToAttribute Attribute 
Instance details

Defined in OpenTelemetry.Attributes

type Rep Attribute 
Instance details

Defined in OpenTelemetry.Attributes

type Rep Attribute = D1 ('MetaData "Attribute" "OpenTelemetry.Attributes" "hs-opentelemetry-api-0.0.1.0-6Dv2z1KBcop7UAQrDIczSS" 'False) (C1 ('MetaCons "AttributeValue" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 PrimitiveAttribute)) :+: C1 ('MetaCons "AttributeArray" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [PrimitiveAttribute])))

data PrimitiveAttribute #

Instances

Instances details
Eq PrimitiveAttribute 
Instance details

Defined in OpenTelemetry.Attributes

Data PrimitiveAttribute 
Instance details

Defined in OpenTelemetry.Attributes

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> PrimitiveAttribute -> c PrimitiveAttribute #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c PrimitiveAttribute #

toConstr :: PrimitiveAttribute -> Constr #

dataTypeOf :: PrimitiveAttribute -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c PrimitiveAttribute) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c PrimitiveAttribute) #

gmapT :: (forall b. Data b => b -> b) -> PrimitiveAttribute -> PrimitiveAttribute #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> PrimitiveAttribute -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> PrimitiveAttribute -> r #

gmapQ :: (forall d. Data d => d -> u) -> PrimitiveAttribute -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> PrimitiveAttribute -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> PrimitiveAttribute -> m PrimitiveAttribute #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> PrimitiveAttribute -> m PrimitiveAttribute #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> PrimitiveAttribute -> m PrimitiveAttribute #

Ord PrimitiveAttribute 
Instance details

Defined in OpenTelemetry.Attributes

Read PrimitiveAttribute 
Instance details

Defined in OpenTelemetry.Attributes

Show PrimitiveAttribute 
Instance details

Defined in OpenTelemetry.Attributes

Generic PrimitiveAttribute 
Instance details

Defined in OpenTelemetry.Attributes

Associated Types

type Rep PrimitiveAttribute :: Type -> Type #

Hashable PrimitiveAttribute 
Instance details

Defined in OpenTelemetry.Attributes

ToPrimitiveAttribute PrimitiveAttribute 
Instance details

Defined in OpenTelemetry.Attributes

ToAttribute PrimitiveAttribute 
Instance details

Defined in OpenTelemetry.Attributes

type Rep PrimitiveAttribute 
Instance details

Defined in OpenTelemetry.Attributes

type Rep PrimitiveAttribute = D1 ('MetaData "PrimitiveAttribute" "OpenTelemetry.Attributes" "hs-opentelemetry-api-0.0.1.0-6Dv2z1KBcop7UAQrDIczSS" 'False) ((C1 ('MetaCons "TextAttribute" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)) :+: C1 ('MetaCons "BoolAttribute" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool))) :+: (C1 ('MetaCons "DoubleAttribute" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Double)) :+: C1 ('MetaCons "IntAttribute" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int64))))

data SpanKind #

SpanKind describes the relationship between the Span, its parents, and its children in a Trace. SpanKind describes two independent properties that benefit tracing systems during analysis.

The first property described by SpanKind reflects whether the Span is a remote child or parent. Spans with a remote parent are interesting because they are sources of external load. Spans with a remote child are interesting because they reflect a non-local system dependency.

The second property described by SpanKind reflects whether a child Span represents a synchronous call. When a child span is synchronous, the parent is expected to wait for it to complete under ordinary circumstances. It can be useful for tracing systems to know this property, since synchronous Spans may contribute to the overall trace latency. Asynchronous scenarios can be remote or local.

In order for SpanKind to be meaningful, callers SHOULD arrange that a single Span does not serve more than one purpose. For example, a server-side span SHOULD NOT be used directly as the parent of another remote span. As a simple guideline, instrumentation should create a new Span prior to extracting and serializing the SpanContext for a remote call.

To summarize the interpretation of these kinds

SpanKindSynchronousAsynchronousRemote IncomingRemote Outgoing
Clientyesyes
Serveryesyes
Produceryesmaybe
Consumeryesmaybe
Internal

Constructors

Server

Indicates that the span covers server-side handling of a synchronous RPC or other remote request. This span is the child of a remote Client span that was expected to wait for a response.

Client

Indicates that the span describes a synchronous request to some remote service. This span is the parent of a remote Server span and waits for its response.

Producer

Indicates that the span describes the parent of an asynchronous request. This parent span is expected to end before the corresponding child Producer span, possibly even before the child span starts. In messaging scenarios with batching, tracing individual messages requires a new Producer span per message to be created.

Consumer

Indicates that the span describes the child of an asynchronous Producer request.

Internal

Default value. Indicates that the span represents an internal operation within an application, as opposed to an operations with remote parents or children.

Instances

Instances details
Show SpanKind 
Instance details

Defined in OpenTelemetry.Internal.Trace.Types

data Link #

A Span may be linked to zero or more other Spans (defined by SpanContext) that are causally related. Links can point to Spans inside a single Trace or across different Traces. Links can be used to represent batched operations where a Span was initiated by multiple initiating Spans, each representing a single incoming item being processed in the batch.

Another example of using a Link is to declare the relationship between the originating and following trace. This can be used when a Trace enters trusted boundaries of a service and service policy requires the generation of a new Trace rather than trusting the incoming Trace context. The new linked Trace may also represent a long running asynchronous data processing operation that was initiated by one of many fast incoming requests.

When using the scattergather (also called forkjoin) pattern, the root operation starts multiple downstream processing operations and all of them are aggregated back in a single Span. This last Span is linked to many operations it aggregates. All of them are the Spans from the same Trace. And similar to the Parent field of a Span. It is recommended, however, to not set parent of the Span in this scenario as semantically the parent field represents a single parent scenario, in many cases the parent Span fully encloses the child Span. This is not the case in scatter/gather and batch scenarios.

Constructors

Link 

Fields

Instances

data Event #

A “log” that happens as part of a span. An operation that is too fast for its own span, but too unique to roll up into its parent span.

Events contain a name, a timestamp, and an optional set of Attributes, along with a timestamp. Events represent an event that occurred at a specific time within a span’s workload.

Instances

Instances details
Show Event 
Instance details

Defined in OpenTelemetry.Internal.Trace.Types

Methods

showsPrec :: Int -> Event -> ShowS #

show :: Event -> String #

showList :: [Event] -> ShowS #

data NewEvent #

Constructors

NewEvent 

Fields

addEvent :: MonadIO m => Span -> NewEvent -> m () #

recordException :: (MonadIO m, Exception e) => Span -> [(Text, Attribute)] -> Maybe Timestamp -> e -> m () #

A specialized variant of addEvent that records attributes conforming to the OpenTelemetry specification's semantic conventions

Since: hs-opentelemetry-api-0.0.1.0

setStatus :: MonadIO m => Span -> SpanStatus -> m () #

Sets the Status of the Span. If used, this will override the default Span status, which is Unset.

These values form a total order: Ok > Error > Unset. This means that setting Status with StatusCode=Ok will override any prior or future attempts to set span Status with StatusCode=Error or StatusCode=Unset.

data SpanStatus #

The status of a Span. This may be used to indicate the successful completion of a span.

The default is Unset

These values form a total order: Ok > Error > Unset. This means that setting Status with StatusCode=Ok will override any prior or future attempts to set span Status with StatusCode=Error or StatusCode=Unset.

Constructors

Unset

The default status.

Error Text

The operation contains an error. The text field may be empty, or else provide a description of the error.

Ok

The operation has been validated by an Application developer or Operator to have completed successfully.

data SpanContext #

A SpanContext represents the portion of a Span which must be serialized and propagated along side of a distributed context. SpanContexts are immutable.

Instances

Instances details
Eq SpanContext 
Instance details

Defined in OpenTelemetry.Internal.Trace.Types

Show SpanContext 
Instance details

Defined in OpenTelemetry.Internal.Trace.Types

endSpan #

Arguments

:: MonadIO m 
=> Span 
-> Maybe Timestamp

Optional Timestamp signalling the end time of the span. If not provided, the current time will be used.

-> m () 

Signals that the operation described by this span has now (or at the time optionally specified) ended.

This does have any effects on child spans. Those may still be running and can be ended later.

This also does not inactivate the Span in any Context it is active in. It is still possible to use an ended span as parent via a Context it is contained in. Also, putting the Span into a Context will still work after the Span was ended.

Since: hs-opentelemetry-api-0.0.1.0