| Safe Haskell | Safe-Inferred |
|---|---|
| Language | Haskell2010 |
Freckle.App.OpenTelemetry
Description
Application tracing via https://opentelemetry.io/
data App = App
{ -- ...
, appTracer :: Tracer
}
instance HasTracer App where
tracerL = lens appTracer $ x y -> x { appTracer = y }
loadApp f = do
-- ...
withTracerProvider $ tracerProvider -> do
let appTracer = makeTracer tracerProvider "my-app" tracerOptions
f App {..}
You may need to do this even if you don't plan to manually trace things, in
order to satisfy the MonadTracer constraint required by functions like
runDB. If you don't need this feature, and don't plan on running an
otel-collector, set OTEL_TRACES_EXPORTER=none in the environment, which
makes all tracing a no-op.
In the future, it should be possible to use OTEL_SDK_DISABLED for the same
purpose. See https://github.com/iand675/hs-opentelemetry/issues/60.
Synopsis
- class HasTracer s where
- data Tracer
- class Monad m => MonadTracer (m :: Type -> Type) where
- inSpan :: (MonadUnliftIO m, MonadTracer m, HasCallStack) => Text -> SpanArguments -> m a -> m a
- defaultSpanArguments :: SpanArguments
- serverSpanArguments :: SpanArguments
- clientSpanArguments :: SpanArguments
- producerSpanArguments :: SpanArguments
- consumerSpanArguments :: SpanArguments
- withTraceIdContext :: (MonadIO m, MonadMask m) => m a -> m a
- getCurrentTraceId :: MonadIO m => m (Maybe TraceId)
- getCurrentTraceIdAsDatadog :: MonadIO m => m (Maybe Word64)
- getCurrentSpanContext :: MonadIO m => m (Maybe SpanContext)
- class ToAttribute a where
- toAttribute :: a -> Attribute
- addCurrentSpanAttributes :: MonadIO m => HashMap Text Attribute -> m ()
- withTracerProvider :: MonadUnliftIO m => (TracerProvider -> m a) -> m a
- makeTracer :: TracerProvider -> InstrumentationLibrary -> TracerOptions -> Tracer
- tracerOptions :: TracerOptions
- byteStringToAttribute :: ByteString -> Attribute
- attributeValueLimit :: Int
Documentation
Effects
class Monad m => MonadTracer (m :: Type -> Type) where #
This is generally scoped by Monad stack to do different things
Instances
| HasTracer app => MonadTracer (AppExample app) Source # | |
Defined in Freckle.App.Test Methods getTracer :: AppExample app Tracer # | |
| (Monad m, HasTracer app) => MonadTracer (AppT app m) Source # | |
Defined in Freckle.App | |
| MonadTracer m => MonadTracer (IdentityT m) | |
Defined in OpenTelemetry.Trace.Monad | |
| MonadTracer m => MonadTracer (ReaderT r m) | |
Defined in OpenTelemetry.Trace.Monad | |
inSpan :: (MonadUnliftIO m, MonadTracer m, HasCallStack) => Text -> SpanArguments -> m a -> m a #
defaultSpanArguments :: SpanArguments #
Smart constructor for SpanArguments providing reasonable values for most Spans created
that are internal to an application.
Defaults:
kind:Internalattributes:[]links:[]startTime:Nothing(getTimestampwill be called uponSpancreation)
serverSpanArguments :: SpanArguments Source #
defaultSpanArguments with kind set to 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.
clientSpanArguments :: SpanArguments Source #
defaultSpanArguments with kind set to Kind
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.
producerSpanArguments :: SpanArguments Source #
defaultSpanArguments with kind set to 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.
consumerSpanArguments :: SpanArguments Source #
defaultSpanArguments with kind set to Consumer
Indicates that the span describes the child of an asynchronous Producer
request.
Querying
withTraceIdContext :: (MonadIO m, MonadMask m) => m a -> m a Source #
getCurrentSpanContext :: MonadIO m => m (Maybe SpanContext) Source #
Attributes
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
Setup
withTracerProvider :: MonadUnliftIO m => (TracerProvider -> m a) -> m a Source #
Tracer
makeTracer :: TracerProvider -> InstrumentationLibrary -> TracerOptions -> Tracer #
tracerOptions :: TracerOptions #
Default Tracer options
Utilities
byteStringToAttribute :: ByteString -> Attribute Source #
Convert a ByteString to an Attribute safely
- Decodes it as UTF-8 leniently,
- Truncates to fit within
attributeValueLimit
attributeValueLimit :: Int Source #
Character limit for Attribute values
OTel the spec doesn't specify a limit, but says that SDKs should decide some limit. It's not clear what the Haskell SDK does, if anything. New Relic applies a limit of 4095 characters on all metrics it handles, including those coming from OTel. Seems reasonable enough.