opentelemetry-extra-0.8.0
Safe HaskellNone
LanguageHaskell2010

OpenTelemetry.Common

Synopsis

Documentation

newtype SpanName Source #

Constructors

SpanName Text 

Instances

Instances details
Eq SpanName Source # 
Instance details

Defined in OpenTelemetry.Common

Show SpanName Source # 
Instance details

Defined in OpenTelemetry.Common

Generic SpanName Source # 
Instance details

Defined in OpenTelemetry.Common

Associated Types

type Rep SpanName :: Type -> Type #

Methods

from :: SpanName -> Rep SpanName x #

to :: Rep SpanName x -> SpanName #

type Rep SpanName Source # 
Instance details

Defined in OpenTelemetry.Common

type Rep SpanName = D1 ('MetaData "SpanName" "OpenTelemetry.Common" "opentelemetry-extra-0.8.0-AGHJfM0VEJAESAbiZVwscL" 'True) (C1 ('MetaCons "SpanName" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)))

newtype TagName Source #

Constructors

TagName Text 

Instances

Instances details
Eq TagName Source # 
Instance details

Defined in OpenTelemetry.Common

Methods

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

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

Show TagName Source # 
Instance details

Defined in OpenTelemetry.Common

IsString TagName Source # 
Instance details

Defined in OpenTelemetry.Common

Methods

fromString :: String -> TagName #

Generic TagName Source # 
Instance details

Defined in OpenTelemetry.Common

Associated Types

type Rep TagName :: Type -> Type #

Methods

from :: TagName -> Rep TagName x #

to :: Rep TagName x -> TagName #

Hashable TagName Source # 
Instance details

Defined in OpenTelemetry.Common

Methods

hashWithSalt :: Int -> TagName -> Int #

hash :: TagName -> Int #

type Rep TagName Source # 
Instance details

Defined in OpenTelemetry.Common

type Rep TagName = D1 ('MetaData "TagName" "OpenTelemetry.Common" "opentelemetry-extra-0.8.0-AGHJfM0VEJAESAbiZVwscL" 'True) (C1 ('MetaCons "TagName" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)))

newtype TagVal Source #

Constructors

TagVal Text 

Instances

Instances details
Eq TagVal Source # 
Instance details

Defined in OpenTelemetry.Common

Methods

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

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

Show TagVal Source # 
Instance details

Defined in OpenTelemetry.Common

Generic TagVal Source # 
Instance details

Defined in OpenTelemetry.Common

Associated Types

type Rep TagVal :: Type -> Type #

Methods

from :: TagVal -> Rep TagVal x #

to :: Rep TagVal x -> TagVal #

ToTagValue TagVal Source # 
Instance details

Defined in OpenTelemetry.Common

type Rep TagVal Source # 
Instance details

Defined in OpenTelemetry.Common

type Rep TagVal = D1 ('MetaData "TagVal" "OpenTelemetry.Common" "opentelemetry-extra-0.8.0-AGHJfM0VEJAESAbiZVwscL" 'True) (C1 ('MetaCons "TagVal" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)))

newtype EventName Source #

Constructors

EventName Text 

Instances

Instances details
Eq EventName Source # 
Instance details

Defined in OpenTelemetry.Common

Show EventName Source # 
Instance details

Defined in OpenTelemetry.Common

Generic EventName Source # 
Instance details

Defined in OpenTelemetry.Common

Associated Types

type Rep EventName :: Type -> Type #

type Rep EventName Source # 
Instance details

Defined in OpenTelemetry.Common

type Rep EventName = D1 ('MetaData "EventName" "OpenTelemetry.Common" "opentelemetry-extra-0.8.0-AGHJfM0VEJAESAbiZVwscL" 'True) (C1 ('MetaCons "EventName" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)))

newtype EventVal Source #

Constructors

EventVal Text 

Instances

Instances details
Eq EventVal Source # 
Instance details

Defined in OpenTelemetry.Common

Show EventVal Source # 
Instance details

Defined in OpenTelemetry.Common

Generic EventVal Source # 
Instance details

Defined in OpenTelemetry.Common

Associated Types

type Rep EventVal :: Type -> Type #

Methods

from :: EventVal -> Rep EventVal x #

to :: Rep EventVal x -> EventVal #

type Rep EventVal Source # 
Instance details

Defined in OpenTelemetry.Common

type Rep EventVal = D1 ('MetaData "EventVal" "OpenTelemetry.Common" "opentelemetry-extra-0.8.0-AGHJfM0VEJAESAbiZVwscL" 'True) (C1 ('MetaCons "EventVal" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)))

data TagValue Source #

Instances

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

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

ToTagValue Text Source # 
Instance details

Defined in OpenTelemetry.Common

ToTagValue TagVal Source # 
Instance details

Defined in OpenTelemetry.Common

data InstrumentType Source #

Reflects the constructors of Instrument

Instances

Instances details
Enum InstrumentType Source # 
Instance details

Defined in OpenTelemetry.Common

Eq InstrumentType Source # 
Instance details

Defined in OpenTelemetry.Common

Show InstrumentType Source # 
Instance details

Defined in OpenTelemetry.Common

Generic InstrumentType Source # 
Instance details

Defined in OpenTelemetry.Common

Associated Types

type Rep InstrumentType :: Type -> Type #

Hashable InstrumentType Source # 
Instance details

Defined in OpenTelemetry.Common

type Rep InstrumentType Source # 
Instance details

Defined in OpenTelemetry.Common

type Rep InstrumentType = D1 ('MetaData "InstrumentType" "OpenTelemetry.Common" "opentelemetry-extra-0.8.0-AGHJfM0VEJAESAbiZVwscL" 'False) ((C1 ('MetaCons "CounterType" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "UpDownCounterType" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ValueRecorderType" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "SumObserverType" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "UpDownSumObserverType" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ValueObserverType" 'PrefixI 'False) (U1 :: Type -> Type))))

data CaptureInstrument Source #

Instances

Instances details
Eq CaptureInstrument Source # 
Instance details

Defined in OpenTelemetry.Common

Show CaptureInstrument Source # 
Instance details

Defined in OpenTelemetry.Common

Generic CaptureInstrument Source # 
Instance details

Defined in OpenTelemetry.Common

Associated Types

type Rep CaptureInstrument :: Type -> Type #

Hashable CaptureInstrument Source # 
Instance details

Defined in OpenTelemetry.Common

type Rep CaptureInstrument Source # 
Instance details

Defined in OpenTelemetry.Common

type Rep CaptureInstrument = D1 ('MetaData "CaptureInstrument" "OpenTelemetry.Common" "opentelemetry-extra-0.8.0-AGHJfM0VEJAESAbiZVwscL" 'False) (C1 ('MetaCons "CaptureInstrument" 'PrefixI 'True) (S1 ('MetaSel ('Just "instrumentType") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 InstrumentType) :*: S1 ('MetaSel ('Just "instrumentName") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 ByteString)))

data MetricDatapoint a Source #

Constructors

MetricDatapoint 

Fields

Instances

Instances details
Functor MetricDatapoint Source # 
Instance details

Defined in OpenTelemetry.Common

Methods

fmap :: (a -> b) -> MetricDatapoint a -> MetricDatapoint b #

(<$) :: a -> MetricDatapoint b -> MetricDatapoint a #

Eq a => Eq (MetricDatapoint a) Source # 
Instance details

Defined in OpenTelemetry.Common

Show a => Show (MetricDatapoint a) Source # 
Instance details

Defined in OpenTelemetry.Common

data SpanEvent Source #

Instances

Instances details
Eq SpanEvent Source # 
Instance details

Defined in OpenTelemetry.Common

Show SpanEvent Source # 
Instance details

Defined in OpenTelemetry.Common

data SpanStatus Source #

Constructors

OK 

Instances

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

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