opentelemetry-0.1.0

Safe HaskellSafe
LanguageHaskell2010

OpenTelemetry.Common

Documentation

newtype TraceId Source #

Constructors

TId Word64 
Instances
Eq TraceId Source # 
Instance details

Defined in OpenTelemetry.Common

Methods

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

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

Show TraceId Source # 
Instance details

Defined in OpenTelemetry.Common

Generic TraceId Source # 
Instance details

Defined in OpenTelemetry.Common

Associated Types

type Rep TraceId :: Type -> Type #

Methods

from :: TraceId -> Rep TraceId x #

to :: Rep TraceId x -> TraceId #

Hashable TraceId Source # 
Instance details

Defined in OpenTelemetry.Common

Methods

hashWithSalt :: Int -> TraceId -> Int #

hash :: TraceId -> Int #

type Rep TraceId Source # 
Instance details

Defined in OpenTelemetry.Common

type Rep TraceId = D1 (MetaData "TraceId" "OpenTelemetry.Common" "opentelemetry-0.1.0-BAvROEGZKIiIoVcgHpNy9P" True) (C1 (MetaCons "TId" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Word64)))

newtype SpanId Source #

Constructors

SId Word64 
Instances
Eq SpanId Source # 
Instance details

Defined in OpenTelemetry.Common

Methods

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

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

Show SpanId Source # 
Instance details

Defined in OpenTelemetry.Common

Generic SpanId Source # 
Instance details

Defined in OpenTelemetry.Common

Associated Types

type Rep SpanId :: Type -> Type #

Methods

from :: SpanId -> Rep SpanId x #

to :: Rep SpanId x -> SpanId #

Hashable SpanId Source # 
Instance details

Defined in OpenTelemetry.Common

Methods

hashWithSalt :: Int -> SpanId -> Int #

hash :: SpanId -> Int #

type Rep SpanId Source # 
Instance details

Defined in OpenTelemetry.Common

type Rep SpanId = D1 (MetaData "SpanId" "OpenTelemetry.Common" "opentelemetry-0.1.0-BAvROEGZKIiIoVcgHpNy9P" True) (C1 (MetaCons "SId" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Word64)))

data Tracer threadId Source #

Constructors

Tracer 

Fields

Instances
Eq threadId => Eq (Tracer threadId) Source # 
Instance details

Defined in OpenTelemetry.Common

Methods

(==) :: Tracer threadId -> Tracer threadId -> Bool #

(/=) :: Tracer threadId -> Tracer threadId -> Bool #

Show threadId => Show (Tracer threadId) Source # 
Instance details

Defined in OpenTelemetry.Common

Methods

showsPrec :: Int -> Tracer threadId -> ShowS #

show :: Tracer threadId -> String #

showList :: [Tracer threadId] -> ShowS #

tracerPushSpan :: (Eq tid, Hashable tid) => Tracer tid -> tid -> Span -> Tracer tid Source #

tracerPopSpan :: (Eq tid, Hashable tid) => Tracer tid -> tid -> (Maybe Span, Tracer tid) Source #

createTracer :: (Hashable tid, Eq tid) => IO (Tracer tid) Source #

data SpanContext Source #

Constructors

SpanContext !SpanId !TraceId 
Instances
Eq SpanContext Source # 
Instance details

Defined in OpenTelemetry.Common

Show SpanContext Source # 
Instance details

Defined in OpenTelemetry.Common

Generic SpanContext Source # 
Instance details

Defined in OpenTelemetry.Common

Associated Types

type Rep SpanContext :: Type -> Type #

type Rep SpanContext Source # 
Instance details

Defined in OpenTelemetry.Common

type Rep SpanContext = D1 (MetaData "SpanContext" "OpenTelemetry.Common" "opentelemetry-0.1.0-BAvROEGZKIiIoVcgHpNy9P" False) (C1 (MetaCons "SpanContext" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 SpanId) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 TraceId)))

data TagValue Source #

Instances
Eq TagValue Source # 
Instance details

Defined in OpenTelemetry.Common

Show TagValue Source # 
Instance details

Defined in OpenTelemetry.Common

class ToTagValue a where Source #

Methods

toTagValue :: a -> TagValue Source #

Instances
ToTagValue Bool Source # 
Instance details

Defined in OpenTelemetry.Common

ToTagValue Int Source # 
Instance details

Defined in OpenTelemetry.Common

ToTagValue String Source # 
Instance details

Defined in OpenTelemetry.Common

data Span Source #

Instances
Eq Span Source # 
Instance details

Defined in OpenTelemetry.Common

Methods

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

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

Show Span Source # 
Instance details

Defined in OpenTelemetry.Common

Methods

showsPrec :: Int -> Span -> ShowS #

show :: Span -> String #

showList :: [Span] -> ShowS #

data SpanEvent Source #

Instances
Eq SpanEvent Source # 
Instance details

Defined in OpenTelemetry.Common

Show SpanEvent Source # 
Instance details

Defined in OpenTelemetry.Common

data SpanStatus Source #

Constructors

OK 
Instances
Eq SpanStatus Source # 
Instance details

Defined in OpenTelemetry.Common

Show SpanStatus Source # 
Instance details

Defined in OpenTelemetry.Common

data Event Source #

Constructors

Event Text Timestamp 
Instances
Eq Event Source # 
Instance details

Defined in OpenTelemetry.Common

Methods

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

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

Show Event Source # 
Instance details

Defined in OpenTelemetry.Common

Methods

showsPrec :: Int -> Event -> ShowS #

show :: Event -> String #

showList :: [Event] -> ShowS #

data SpanProcessor Source #

Constructors

SpanProcessor 

Fields

data Exporter thing Source #

Constructors

Exporter 

Fields