Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- beginSpan :: MonadIO m => ByteString -> m SpanInFlight
- endSpan :: MonadIO m => SpanInFlight -> m ()
- withSpan :: forall m a. (MonadIO m, MonadMask m) => ByteString -> (SpanInFlight -> m a) -> m a
- withSpan_ :: (MonadIO m, MonadMask m) => ByteString -> m a -> m a
- setSpanId :: MonadIO m => SpanInFlight -> SpanId -> m ()
- setTraceId :: MonadIO m => SpanInFlight -> TraceId -> m ()
- setTag :: MonadIO m => SpanInFlight -> ByteString -> ByteString -> m ()
- addEvent :: MonadIO m => SpanInFlight -> ByteString -> ByteString -> m ()
- setParentSpanContext :: MonadIO m => SpanInFlight -> SpanContext -> m ()
- newtype SpanInFlight = SpanInFlight ProcessLocalSpanSerialNumber
- mkCounter :: MonadIO m => InstrumentName -> m Counter
- mkUpDownCounter :: MonadIO m => InstrumentName -> m UpDownCounter
- mkValueRecorder :: MonadIO m => InstrumentName -> m ValueRecorder
- mkSumObserver :: MonadIO m => InstrumentName -> m SumObserver
- mkUpDownSumObserver :: MonadIO m => InstrumentName -> m UpDownSumObserver
- mkValueObserver :: MonadIO m => InstrumentName -> m ValueObserver
- add :: MonadIO m => Instrument 'Synchronous 'Additive m' -> Int -> m ()
- record :: MonadIO m => Instrument 'Synchronous 'NonAdditive m' -> Int -> m ()
- observe :: MonadIO m => Instrument 'Asynchronous a m' -> Int -> m ()
- data Instrument (s :: Synchronicity) (a :: Additivity) (m :: Monotonicity)
- data SomeInstrument = forall s a m. SomeInstrument (Instrument s a m)
- type Counter = Instrument 'Synchronous 'Additive 'Monotonic
- type UpDownCounter = Instrument 'Synchronous 'Additive 'NonMonotonic
- type ValueRecorder = Instrument 'Synchronous 'NonAdditive 'NonMonotonic
- type SumObserver = Instrument 'Asynchronous 'Additive 'Monotonic
- type UpDownSumObserver = Instrument 'Asynchronous 'Additive 'NonMonotonic
- type ValueObserver = Instrument 'Asynchronous 'NonAdditive 'NonMonotonic
- data Synchronicity
- data Additivity
- data Monotonicity
- type InstrumentName = ByteString
- type InstrumentId = Word64
- instrumentName :: Instrument s a m -> InstrumentName
- instrumentId :: Instrument s a m -> InstrumentId
Spans
beginSpan :: MonadIO m => ByteString -> m SpanInFlight Source #
endSpan :: MonadIO m => SpanInFlight -> m () Source #
withSpan :: forall m a. (MonadIO m, MonadMask m) => ByteString -> (SpanInFlight -> m a) -> m a Source #
setTraceId :: MonadIO m => SpanInFlight -> TraceId -> m () Source #
setTag :: MonadIO m => SpanInFlight -> ByteString -> ByteString -> m () Source #
addEvent :: MonadIO m => SpanInFlight -> ByteString -> ByteString -> m () Source #
setParentSpanContext :: MonadIO m => SpanInFlight -> SpanContext -> m () Source #
newtype SpanInFlight Source #
Instances
Eq SpanInFlight Source # | |
Defined in OpenTelemetry.Eventlog_Internal (==) :: SpanInFlight -> SpanInFlight -> Bool # (/=) :: SpanInFlight -> SpanInFlight -> Bool # | |
Show SpanInFlight Source # | |
Defined in OpenTelemetry.Eventlog_Internal showsPrec :: Int -> SpanInFlight -> ShowS # show :: SpanInFlight -> String # showList :: [SpanInFlight] -> ShowS # | |
Hashable SpanInFlight Source # | |
Defined in OpenTelemetry.Eventlog_Internal hashWithSalt :: Int -> SpanInFlight -> Int # hash :: SpanInFlight -> Int # |
Metrics
mkUpDownCounter :: MonadIO m => InstrumentName -> m UpDownCounter Source #
mkValueRecorder :: MonadIO m => InstrumentName -> m ValueRecorder Source #
mkSumObserver :: MonadIO m => InstrumentName -> m SumObserver Source #
mkUpDownSumObserver :: MonadIO m => InstrumentName -> m UpDownSumObserver Source #
mkValueObserver :: MonadIO m => InstrumentName -> m ValueObserver Source #
add :: MonadIO m => Instrument 'Synchronous 'Additive m' -> Int -> m () Source #
Take a measurement for a synchronous, additive instrument (Counter
, UpDownCounter
)
record :: MonadIO m => Instrument 'Synchronous 'NonAdditive m' -> Int -> m () Source #
Take a measurement for a synchronous, non-additive instrument (ValueRecorder
)
observe :: MonadIO m => Instrument 'Asynchronous a m' -> Int -> m () Source #
Take a measurement for an asynchronous instrument (SumObserver
, UpDownSumObserver
, ValueObserver
)
data Instrument (s :: Synchronicity) (a :: Additivity) (m :: Monotonicity) Source #
An OpenTelemetry instrument as defined in the OpenTelemetry Metrics API (https://github.com/open-telemetry/opentelemetry-specification/blob/master/specification/metrics/api.md)
Instances
Eq (Instrument s a m) Source # | |
Defined in OpenTelemetry.Metrics_Internal (==) :: Instrument s a m -> Instrument s a m -> Bool # (/=) :: Instrument s a m -> Instrument s a m -> Bool # | |
Show (Instrument s a m) Source # | |
Defined in OpenTelemetry.Metrics_Internal showsPrec :: Int -> Instrument s a m -> ShowS # show :: Instrument s a m -> String # showList :: [Instrument s a m] -> ShowS # | |
Hashable (Instrument s a m) Source # | |
Defined in OpenTelemetry.Metrics_Internal hashWithSalt :: Int -> Instrument s a m -> Int # hash :: Instrument s a m -> Int # |
data SomeInstrument Source #
Existential wrapper for Instrument
. Use when the exact type of Instrument does not matter.
forall s a m. SomeInstrument (Instrument s a m) |
Instances
Eq SomeInstrument Source # | |
Defined in OpenTelemetry.Metrics_Internal (==) :: SomeInstrument -> SomeInstrument -> Bool # (/=) :: SomeInstrument -> SomeInstrument -> Bool # | |
Show SomeInstrument Source # | |
Defined in OpenTelemetry.Metrics_Internal showsPrec :: Int -> SomeInstrument -> ShowS # show :: SomeInstrument -> String # showList :: [SomeInstrument] -> ShowS # | |
Hashable SomeInstrument Source # | |
Defined in OpenTelemetry.Metrics_Internal hashWithSalt :: Int -> SomeInstrument -> Int # hash :: SomeInstrument -> Int # |
type Counter = Instrument 'Synchronous 'Additive 'Monotonic Source #
type UpDownCounter = Instrument 'Synchronous 'Additive 'NonMonotonic Source #
type ValueRecorder = Instrument 'Synchronous 'NonAdditive 'NonMonotonic Source #
type SumObserver = Instrument 'Asynchronous 'Additive 'Monotonic Source #
type InstrumentName = ByteString Source #
type InstrumentId = Word64 Source #
instrumentName :: Instrument s a m -> InstrumentName Source #
instrumentId :: Instrument s a m -> InstrumentId Source #