hs-opentelemetry-sdk-0.0.3.6: OpenTelemetry SDK for use in applications.
Copyright(c) Ian Duncan 2021
LicenseBSD-3
MaintainerIan Duncan
Stabilityexperimental
Portabilitynon-portable (GHC extensions)
Safe HaskellSafe-Inferred
LanguageHaskell2010

OpenTelemetry.Trace

Description

Traces track the progression of a single request, called a trace, as it is handled by services that make up an application. The request may be initiated by a user or an application. Distributed tracing is a form of tracing that traverses process, network and security boundaries. Each unit of work in a trace is called a span; a trace is a tree of spans. Spans are objects that represent the work being done by individual services or components involved in a request as it flows through a system. A span contains a span context, which is a set of globally unique identifiers that represent the unique request that each span is a part of. A span provides Request, Error and Duration (RED) metrics that can be used to debug availability as well as performance issues.

Here is a visualization of the relationship between traces and spans:

A trace contains a single root span which encapsulates the end-to-end latency for the entire request. You can think of this as a single logical operation, such as clicking a button in a web application to add a product to a shopping cart. The root span would measure the time it took from an end-user clicking that button to the operation being completed or failing (so, the item is added to the cart or some error occurs) and the result being displayed to the user. A trace is comprised of the single root span and any number of child spans, which represent operations taking place as part of the request. Each span contains metadata about the operation, such as its name, start and end timestamps, attributes (which represent additonal user-defined metadata about a span), events, and status.

To create and manage spans in OpenTelemetry, the OpenTelemetry API provides the tracer interface. This object is responsible for tracking the active span in your process, and allows you to access the current span in order to perform operations on it such as adding attributes, events, and finishing it when the work it tracks is complete. One or more tracer objects can be created in a process through the tracer provider, a factory interface that allows for multiple tracers to be instantiated in a single process with different options.

Generally, the lifecycle of a span resembles the following:

  • A request is received by a service. The span context is extracted from the request headers, if it exists.
  • A new span is created as a child of the extracted span context; if none exists, a new root span is created.
  • The service handles the request. Additional attributes and events are added to the span that are useful for understanding the context of the request, such as the hostname of the machine handling the request, or customer identifiers.
  • New spans may be created to represent work being done by sub-components of the service.
  • When the service makes a remote call to another service, the current span context is serialized and forwarded to the next service by injecting the span context into the headers or message envelope.
  • The work being done by the service completes, successfully or not. The span status is appropriately set, and the span is marked finished.
  • For more information, see the traces specification, which covers concepts including: trace, span, parent/child relationship, span context, attributes, events and links.

This module implements eveything required to conform to the trace & span public interface described by the OpenTelemetry specification.

See OpenTelemetry.Trace.Monad for an implementation of inSpan variants that are slightly easier to use in idiomatic Haskell monadic code.

Synopsis

How to use this library

Quick start

  1. Initialize a TracerProvider.
  2. Create a Tracer for your system.
  3. Add relevant pre-made instrumentation
  4. Annotate your internal functions using the inSpan function or one of its variants.

Configuration

General configuration variables

NameDescriptionDefaultNotes
OTEL_RESOURCE_ATTRIBUTESKey-value pairs to be used as resource attributesSee Resource semantic conventions for details.See Resource SDK for more details.
OTEL_SERVICE_NAMESets the value of the `service.name` resource attributeIf `service.name` is also provided in OTEL_RESOURCE_ATTRIBUTES, then OTEL_SERVICE_NAME takes precedence.
OTEL_LOG_LEVELLog level used by the SDK logger"info"
OTEL_PROPAGATORSPropagators to be used as a comma-separated list"tracecontext,baggage"Values MUST be deduplicated in order to register a Propagator only once.
OTEL_TRACES_SAMPLERSampler to be used for traces"parentbased_always_on"See Sampling
OTEL_TRACES_SAMPLER_ARGString value to be used as the sampler argumentThe specified value will only be used if OTEL_TRACES_SAMPLER is set. Each Sampler type defines its own expected input, if any. Invalid or unrecognized input MUST be logged and MUST be otherwise ignored, i.e. the SDK MUST behave as if OTEL_TRACES_SAMPLER_ARG is not set.

Batch span processor configuration variables

NameDescriptionDefaultNotes
OTEL_BSP_SCHEDULE_DELAYDelay interval between two consecutive exports5000
OTEL_BSP_EXPORT_TIMEOUTMaximum allowed time to export data30000
OTEL_BSP_MAX_QUEUE_SIZEMaximum queue size2048
OTEL_BSP_MAX_EXPORT_BATCH_SIZEMaximum batch size512Must be less than or equal to OTEL_BSP_MAX_QUEUE_SIZE

Attribute limits

NameDescriptionDefaultNotes
OTEL_ATTRIBUTE_VALUE_LENGTH_LIMITMaximum allowed attribute value sizeEmpty value is treated as infinity. Non-integer and negative values are invalid.
OTEL_ATTRIBUTE_COUNT_LIMITMaximum allowed span attribute count128

Span limits

NameDescriptionDefaultNotes
OTEL_SPAN_ATTRIBUTE_VALUE_LENGTH_LIMITMaximum allowed attribute value sizeEmpty value is treated as infinity. Non-integer and negative values are invalid.
OTEL_SPAN_ATTRIBUTE_COUNT_LIMITMaximum allowed span attribute count128
OTEL_SPAN_EVENT_COUNT_LIMITMaximum allowed span event count128
OTEL_SPAN_LINK_COUNT_LIMITMaximum allowed span link count128
OTEL_EVENT_ATTRIBUTE_COUNT_LIMITMaximum allowed attribute per span event count128
OTEL_LINK_ATTRIBUTE_COUNT_LIMITMaximum allowed attribute per span link count128

Exporting data

TracerProvider operations

A TracerProvider is key to using OpenTelemetry tracing. It is the data structure responsible for designating how spans are processed and exported

You will generally only need to call initializeGlobalTracerProvider on initialization, and shutdownTracerProvider when your application exits.

main :: IO ()
main = withTracer $ tracer -> do
  -- your existing code here...
  pure ()
  where
    withTracer f = bracket
      -- Install the SDK, pulling configuration from the environment
      initializeGlobalTracerProvider
      -- Ensure that any spans that haven't been exported yet are flushed
      shutdownTracerProvider
      (tracerProvider -> do
        -- Get a tracer so you can create spans
        tracer <- getTracer tracerProvider "your-app-name-or-subsystem"
        f tracer
      )

data TracerProvider #

Tracers can be created from a TracerProvider.

initializeGlobalTracerProvider :: IO TracerProvider Source #

Create a new TracerProvider and set it as the global tracer provider. This pulls all configuration from environment variables. The full list of environment variables supported is specified in the configuration section of this module's documentation.

Note however, that 3rd-party span processors, exporters, sampling strategies, etc. may have their own set of environment-based configuration values that they utilize.

getTracerProviderInitializationOptions' :: ResourceMerge 'Nothing any ~ 'Nothing => Resource any -> IO ([Processor], TracerProviderOptions) Source #

Detect options for initializing a tracer provider from the app environment, taking additional supported resources as well.

Since: 0.0.3.1

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

getGlobalTracerProvider :: MonadIO m => m TracerProvider #

Access the globally configured TracerProvider. Once the the global tracer provider is initialized via the OpenTelemetry SDK, Tracers created from this TracerProvider will export spans to their configured exporters. Prior to that, any Tracers acquired from the uninitialized TracerProvider will create no-op spans.

Since: hs-opentelemetry-api-0.0.1.0

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

Overwrite the globally configured TracerProvider.

Tracers acquired from the previously installed TracerProvider will continue to use that TracerProviders configured span processors, exporters, and other settings.

Since: hs-opentelemetry-api-0.0.1.0

Tracer operations

data Tracer #

The Tracer is responsible for creating Spans.

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

Instances

Instances details
Show Tracer 
Instance details

Defined in OpenTelemetry.Internal.Trace.Types

tracerName :: Tracer -> InstrumentationLibrary #

Get the name of the Tracer

Since: hs-opentelemetry-api-0.0.10

newtype TracerOptions #

Tracer configuration options.

Constructors

TracerOptions 

Fields

  • tracerSchema :: Maybe Text

    OpenTelemetry provides a schema for describing common attributes so that backends can easily parse and identify relevant information. It is important to understand these conventions when writing instrumentation, in order to normalize your data and increase its utility.

    In particular, this option is valuable to set when possible, because it allows vendors to normalize data accross releases in order to account for attribute name changes.

tracerOptions :: TracerOptions #

Default Tracer options

class HasTracer s where #

A small utility lens for extracting a Tracer from a larger data type

This will generally be most useful as a means of implementing getTracer

Since: hs-opentelemetry-api-0.0.1.0

Methods

tracerL :: Lens' s Tracer #

data InstrumentationLibrary #

An identifier for the library that provides the instrumentation for a given Instrumented Library. Instrumented Library and Instrumentation Library may be the same library if it has built-in OpenTelemetry instrumentation.

The inspiration of the OpenTelemetry project is to make every library and application observable out of the box by having them call OpenTelemetry API directly. However, many libraries will not have such integration, and as such there is a need for a separate library which would inject such calls, using mechanisms such as wrapping interfaces, subscribing to library-specific callbacks, or translating existing telemetry into the OpenTelemetry model.

A library that enables OpenTelemetry observability for another library is called an Instrumentation Library.

An instrumentation library should be named to follow any naming conventions of the instrumented library (e.g. middleware for a web framework).

If there is no established name, the recommendation is to prefix packages with "hs-opentelemetry-instrumentation", followed by the instrumented library name itself.

In general, you can initialize the instrumentation library like so:

import qualified Data.Text as T
import Data.Version (showVersion)
import Paths_your_package_name

instrumentationLibrary :: InstrumentationLibrary
instrumentationLibrary = InstrumentationLibrary
  { libraryName = "your_package_name"
  , libraryVersion = T.pack $ showVersion version
  }

Constructors

InstrumentationLibrary 

Fields

Instances

Instances details
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 #

Show InstrumentationLibrary 
Instance details

Defined in OpenTelemetry.Internal.Trace.Types

Eq InstrumentationLibrary 
Instance details

Defined in OpenTelemetry.Internal.Trace.Types

Ord InstrumentationLibrary 
Instance details

Defined in OpenTelemetry.Internal.Trace.Types

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.1.0.0-LmqUqstYJOqI8TtFBOKz6W" '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 #

A Span is the fundamental type you'll work with to trace your systems.

A span is a single piece of instrumentation from a single location in your code or infrastructure. A span represents a single "unit of work" done by a service. Each span contains several key pieces of data:

  • A service name identifying the service the span is from
  • A name identifying the role of the span (like function or method name)
  • A timestamp that corresponds to the start of the span
  • A duration that describes how long that unit of work took to complete
  • An ID that uniquely identifies the span
  • A trace ID identifying which trace the span belongs to
  • A parent ID representing the parent span that called this span. (There is no parent ID for the root span of a given trace, which denotes that it's the start of the trace.)
  • Any additional metadata that might be helpful.
  • Zero or more links to related spans. Links can be useful for connecting causal relationships between things like web requests that enqueue asynchronous tasks to be processed.
  • Events, which denote a point in time occurrence. These can be useful for recording data about a span such as when an exception was thrown, or to emit structured logs into the span tree.

A trace is made up of multiple spans. Tracing vendors such as Zipkin, Jaeger, Honeycomb, Datadog, Lightstep, etc. use the metadata from each span to reconstruct the relationships between them and generate a trace diagram.

Instances

Instances details
Show Span 
Instance details

Defined in OpenTelemetry.Internal.Trace.Types

Methods

showsPrec :: Int -> Span -> ShowS #

show :: Span -> String #

showList :: [Span] -> ShowS #

inSpan #

Arguments

:: (MonadUnliftIO m, HasCallStack) 
=> Tracer 
-> Text

The name of the span. This may be updated later via updateName

-> SpanArguments

Additional options for creating the span, such as SpanKind, span links, starting attributes, etc.

-> m a

The action to perform. inSpan will record the time spent on the action without forcing strict evaluation of the result. Any uncaught exceptions will be recorded and rethrown.

-> m a 

The simplest function for annotating code with trace information.

Since: hs-opentelemetry-api-0.0.1.0

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

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 NewLink #

This is a link that is being added to a span which is going to be created.

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 scatter/gather (also called fork/join) 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

NewLink 

Fields

Instances

inSpan' #

Arguments

:: (MonadUnliftIO m, HasCallStack) 
=> Tracer 
-> Text

The name of the span. This may be updated later via updateName

-> SpanArguments 
-> (Span -> m a) 
-> m a 

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 #

Arguments

:: (MonadIO m, ToAttribute a) 
=> Span

Span to add the attribute to

-> Text

Attribute name

-> a

Attribute value

-> m () 

Add an attribute to a span. Only has a useful effect on recording spans.

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.

Since: hs-opentelemetry-api-0.0.1.0

addAttributes :: MonadIO m => Span -> HashMap Text Attribute -> m () #

A convenience function related to addAttribute that adds multiple attributes to a span at the same time.

This function may be slightly more performant than repeatedly calling addAttribute.

Since: hs-opentelemetry-api-0.0.1.0

recordException :: (MonadIO m, Exception e) => Span -> HashMap 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.

Since: hs-opentelemetry-api-0.0.1.0

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 NewEvent #

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.

When creating an event, this is the version that you will use. Attributes added that exceed the configured attribute limits will be dropped, which is accounted for in the Event structure.

Since: hs-opentelemetry-api-0.0.1.0

Constructors

NewEvent 

Fields

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

Add an event to a recording span. Events will not be recorded for remote spans and dropped spans.

Since: hs-opentelemetry-api-0.0.1.0

inSpan'' #

Arguments

:: (MonadUnliftIO m, HasCallStack) 
=> Tracer 
-> Text

The name of the span. This may be updated later via updateName

-> SpanArguments 
-> (Span -> m a) 
-> m a 

Primitive span and tracing operations

Alternative TracerProvider initialization

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

Initialize a new tracer provider

You should generally use getGlobalTracerProvider for most applications.

emptyTracerProviderOptions :: TracerProviderOptions #

Options for creating a TracerProvider with invalid ids, no resources, default limits, and no propagators.

In effect, tracing is a no-op when using this configuration.

Since: hs-opentelemetry-api-0.0.1.0

detectBuiltInResources :: IO (Resource 'Nothing) Source #

Use all built-in resource detectors to populate resource information.

Currently used detectors include:

This list will grow in the future as more detectors are implemented.

Since: 0.0.1.0

detectSampler :: IO Sampler Source #

Detect a sampler from the app environment. If no sampler is specified, the parentbased sampler is used.

Since: 0.0.3.3

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.

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

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 #

Convert a Haskell value to an Attribute value.

For most values, you can define an instance of ToPrimitiveAttribute and use the default toAttribute implementation:

data Foo = Foo

instance ToPrimitiveAttribute Foo where
  toPrimitiveAttribute Foo = TextAttribute Foo
instance ToAttribute foo

Minimal complete definition

Nothing

Methods

toAttribute :: a -> Attribute #

Instances

Instances details
ToAttribute Int64 
Instance details

Defined in OpenTelemetry.Attributes

ToAttribute Attribute 
Instance details

Defined in OpenTelemetry.Attributes

ToAttribute PrimitiveAttribute 
Instance details

Defined in OpenTelemetry.Attributes

ToAttribute Text 
Instance details

Defined in OpenTelemetry.Attributes

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 #

ToPrimitiveAttribute a => ToAttribute [a] 
Instance details

Defined in OpenTelemetry.Attributes

Methods

toAttribute :: [a] -> Attribute #

data Attribute #

An attribute represents user-provided metadata about a span, link, or event.

Telemetry tools may use this data to support high-cardinality querying, visualization in waterfall diagrams, trace sampling decisions, and more.

Constructors

AttributeValue PrimitiveAttribute

An attribute representing a single primitive value

AttributeArray [PrimitiveAttribute]

An attribute representing an array of primitive values.

All values in the array MUST be of the same primitive attribute type.

Instances

Instances details
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 #

IsString Attribute

Create a TextAttribute from the string value.

Since: hs-opentelemetry-api-0.0.2.1

Instance details

Defined in OpenTelemetry.Attributes

Generic Attribute 
Instance details

Defined in OpenTelemetry.Attributes

Associated Types

type Rep Attribute :: Type -> Type #

Read Attribute 
Instance details

Defined in OpenTelemetry.Attributes

Show Attribute 
Instance details

Defined in OpenTelemetry.Attributes

Eq Attribute 
Instance details

Defined in OpenTelemetry.Attributes

Ord Attribute 
Instance details

Defined in OpenTelemetry.Attributes

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.1.0.0-LmqUqstYJOqI8TtFBOKz6W" 'False) (C1 ('MetaCons "AttributeValue" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 PrimitiveAttribute)) :+: C1 ('MetaCons "AttributeArray" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 [PrimitiveAttribute])))

data PrimitiveAttribute #

Instances

Instances details
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 #

IsString PrimitiveAttribute

Create a TextAttribute from the string value.

Since: hs-opentelemetry-api-0.0.2.1

Instance details

Defined in OpenTelemetry.Attributes

Generic PrimitiveAttribute 
Instance details

Defined in OpenTelemetry.Attributes

Associated Types

type Rep PrimitiveAttribute :: Type -> Type #

Read PrimitiveAttribute 
Instance details

Defined in OpenTelemetry.Attributes

Show PrimitiveAttribute 
Instance details

Defined in OpenTelemetry.Attributes

Eq PrimitiveAttribute 
Instance details

Defined in OpenTelemetry.Attributes

Ord PrimitiveAttribute 
Instance details

Defined in OpenTelemetry.Attributes

Hashable PrimitiveAttribute 
Instance details

Defined in OpenTelemetry.Attributes

ToAttribute PrimitiveAttribute 
Instance details

Defined in OpenTelemetry.Attributes

ToPrimitiveAttribute 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.1.0.0-LmqUqstYJOqI8TtFBOKz6W" 'False) ((C1 ('MetaCons "TextAttribute" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Text)) :+: C1 ('MetaCons "BoolAttribute" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Bool))) :+: (C1 ('MetaCons "DoubleAttribute" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Double)) :+: C1 ('MetaCons "IntAttribute" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Int64))))

data Link #

This is an immutable link for an existing span.

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.

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 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
Show SpanContext 
Instance details

Defined in OpenTelemetry.Internal.Trace.Types

Eq SpanContext 
Instance details

Defined in OpenTelemetry.Internal.Trace.Types

data ImmutableSpan #

The frozen representation of a Span that originates from the currently running process.

Only Processors and Exporters should use rely on this interface.

Constructors

ImmutableSpan 

Fields

Instances

Instances details
Show ImmutableSpan 
Instance details

Defined in OpenTelemetry.Internal.Trace.Types