hs-opentelemetry-api-0.1.0.0: OpenTelemetry API for use by libraries for direct instrumentation or wrapper packages.
Copyright(c) Ian Duncan 2021
LicenseBSD-3
MaintainerIan Duncan
Stabilityexperimental
Portabilitynon-portable (GHC extensions)
Safe HaskellSafe-Inferred
LanguageHaskell2010

OpenTelemetry.Trace.Id

Description

Trace and Span Id generation

No Aeson instances are provided since they've got the potential to be transport-specific in format. Use newtypes for serialisation instead.

Synopsis

Working with TraceIds

data TraceId Source #

A valid trace identifier is a 16-byte array with at least one non-zero byte.

Instances

Instances details
IsString TraceId Source # 
Instance details

Defined in OpenTelemetry.Internal.Trace.Id

Methods

fromString :: String -> TraceId #

Generic TraceId Source # 
Instance details

Defined in OpenTelemetry.Internal.Trace.Id

Associated Types

type Rep TraceId :: Type -> Type #

Methods

from :: TraceId -> Rep TraceId x #

to :: Rep TraceId x -> TraceId #

Show TraceId Source # 
Instance details

Defined in OpenTelemetry.Internal.Trace.Id

Eq TraceId Source # 
Instance details

Defined in OpenTelemetry.Internal.Trace.Id

Methods

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

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

Ord TraceId Source # 
Instance details

Defined in OpenTelemetry.Internal.Trace.Id

Hashable TraceId Source # 
Instance details

Defined in OpenTelemetry.Internal.Trace.Id

Methods

hashWithSalt :: Int -> TraceId -> Int #

hash :: TraceId -> Int #

type Rep TraceId Source # 
Instance details

Defined in OpenTelemetry.Internal.Trace.Id

type Rep TraceId = D1 ('MetaData "TraceId" "OpenTelemetry.Internal.Trace.Id" "hs-opentelemetry-api-0.1.0.0-LmqUqstYJOqI8TtFBOKz6W" 'True) (C1 ('MetaCons "TraceId" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ShortByteString)))

Creating TraceIds

newTraceId :: MonadIO m => IdGenerator -> m TraceId Source #

Generate a TraceId using the provided IdGenerator

This function is generally called by the hs-opentelemetry-sdk, but may be useful in some testing situations.

Since: 0.1.0.0

Checking TraceIds for validity

isEmptyTraceId :: TraceId -> Bool Source #

Check whether all bytes in the TraceId are zero.

Since: 0.1.0.0

Encoding / decoding TraceId from bytes

traceIdBytes :: TraceId -> ByteString Source #

Access the byte-level representation of the provided TraceId

Since: 0.1.0.0

bytesToTraceId :: ByteString -> Either String TraceId Source #

Convert a ByteString to a TraceId. Will fail if the ByteString is not exactly 16 bytes long.

Since: 0.1.0.0

Encoding / decoding TraceId from a given Base encoding

baseEncodedToTraceId :: Base -> ByteString -> Either String TraceId Source #

Convert a ByteString of a specified base-encoding into a TraceId. Will fail if the decoded value is not exactly 16 bytes long.

Since: 0.1.0.0

traceIdBaseEncodedBuilder :: Base -> TraceId -> Builder Source #

Output a TraceId into a base-encoded bytestring Builder.

Since: 0.1.0.0

traceIdBaseEncodedByteString :: Base -> TraceId -> ByteString Source #

Output a TraceId into a base-encoded ByteString.

Since: 0.1.0.0

traceIdBaseEncodedText :: Base -> TraceId -> Text Source #

Output a TraceId into a base-encoded Text.

Since: 0.1.0.0

Working with SpanIds

data SpanId Source #

A valid span identifier is an 8-byte array with at least one non-zero byte.

Instances

Instances details
IsString SpanId Source # 
Instance details

Defined in OpenTelemetry.Internal.Trace.Id

Methods

fromString :: String -> SpanId #

Show SpanId Source # 
Instance details

Defined in OpenTelemetry.Internal.Trace.Id

Eq SpanId Source # 
Instance details

Defined in OpenTelemetry.Internal.Trace.Id

Methods

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

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

Ord SpanId Source # 
Instance details

Defined in OpenTelemetry.Internal.Trace.Id

Hashable SpanId Source # 
Instance details

Defined in OpenTelemetry.Internal.Trace.Id

Methods

hashWithSalt :: Int -> SpanId -> Int #

hash :: SpanId -> Int #

Creating SpanIds

newSpanId :: MonadIO m => IdGenerator -> m SpanId Source #

Generate a SpanId using the provided IdGenerator

This function is generally called by the hs-opentelemetry-sdk, but may be useful in some testing situations.

Since: 0.1.0.0

Checking SpanIds for validity

isEmptySpanId :: SpanId -> Bool Source #

Check whether all bytes in the SpanId are zero.

Since: 0.1.0.0

Encoding / decoding SpanId from bytes

spanIdBytes :: SpanId -> ByteString Source #

Access the byte-level representation of the provided SpanId

Since: 0.1.0.0

bytesToSpanId :: ByteString -> Either String SpanId Source #

Convert a ByteString of a specified base-encoding into a SpanId. Will fail if the decoded value is not exactly 8 bytes long.

Since: 0.1.0.0

Encoding / decoding SpanId from a given Base encoding

data Base #

The different bases that can be used.

See RFC4648 for details. In particular, Base64 can be standard or URL-safe. URL-safe encoding is often used in other specifications without padding characters.

RFC 2045 defines a separate Base64 encoding, which is not supported. This format requires a newline at least every 76 encoded characters, which works around limitations of older email programs that could not handle long lines. Be aware that other languages, such as Ruby, encode the RFC 2045 version by default. To decode their output, remove all newlines before decoding.

Examples

A quick example to show the differences:

>>> let input = "Is 3 > 2?" :: ByteString
>>> let convertedTo base = convertToBase base input :: ByteString
>>> convertedTo Base16
"49732033203e20323f"
>>> convertedTo Base32
"JFZSAMZAHYQDEPY="
>>> convertedTo Base64
"SXMgMyA+IDI/"
>>> convertedTo Base64URLUnpadded
"SXMgMyA-IDI_"
>>> convertedTo Base64OpenBSD
"QVKeKw.8GBG9"

Constructors

Base16

similar to hexadecimal

Instances

Instances details
Show Base 
Instance details

Defined in Data.ByteArray.Encoding

Methods

showsPrec :: Int -> Base -> ShowS #

show :: Base -> String #

showList :: [Base] -> ShowS #

Eq Base 
Instance details

Defined in Data.ByteArray.Encoding

Methods

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

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

baseEncodedToSpanId :: Base -> ByteString -> Either String SpanId Source #

Convert a ByteString of a specified base-encoding into a SpanId. Will fail if the decoded value is not exactly 8 bytes long.

Since: 0.1.0.0

spanIdBaseEncodedBuilder :: Base -> SpanId -> Builder Source #

Output a SpanId into a base-encoded bytestring Builder.

Since: 0.1.0.0

spanIdBaseEncodedByteString :: Base -> SpanId -> ByteString Source #

Output a SpanId into a base-encoded ByteString.

Since: 0.1.0.0

spanIdBaseEncodedText :: Base -> SpanId -> Text Source #

Output a SpanId into a base-encoded Text.

Since: 0.1.0.0