eventuo11y-0.1.0.0: An event-oriented observability library
CopyrightCopyright 2022 Shea Levy.
LicenseApache-2.0
Maintainershea@shealevy.com
Safe HaskellSafe-Inferred
LanguageHaskell2010

Observe.Event

Description

This is the primary module needed to instrument code with eventuo11y.

Instrumentors should first define selector types and field types appropriate to the unit of code they're instrumenting:

Selectors are values which designate the general category of event being created, parameterized by the type of fields that can be added to it. For example, a web service's selector type may have a ServicingRequest constructor, whose field type includes a ResponseCode constructor which records the HTTP status code. Selectors are intended to be of a domain-specific type per unit of functionality within an instrumented codebase, implemented as a GADT (but see DynamicEventSelector for a generic option).

Fields make up the basic data captured in an event. They should be added to an Event as the code progresses through various phases of work, and can be both milestone markers ("we got this far in the process") or more detailed instrumentation ("we've processed N records"). They are intended to be of a domain-specific type per unit of functionality within an instrumented codebase (but see DynamicField for a generic option).

Instrumentation then centers around Events, populated using the event manipulation functions. Events are initialized with EventBackends, typically via the resource-safe event allocation functions.

Depending on which EventBackends may end up consuming the Events, instrumentors will also need to define renderers for their selectors and fields. For example, they may need to implement values of types RenderSelectorJSON and RenderFieldJSON to use JSON rendering EventBackends.

Synopsis

Documentation

data Event m r s f Source #

An instrumentation event.

Events are the core of the instrumenting user's interface to eventuo11y. Typical usage would be to create an Event from an EventBackend with withEvent, or as a child of an another Event with withSubEvent, and add fields to the Event at appropriate points in your code with addField.

m
The monad we're instrumenting in.
r
The type of event references. See reference.
s
The type of event selectors for child events. See EventBackend.
f
The type of fields on this event. See addField.

Event manipulation

reference :: Event m r s f -> r Source #

Obtain a reference to an Event.

References are used to link Events together, either in parent-child relationships with addParent or in cause-effect relationships with addProximate.

References can live past when an event has been finalized or failEvented.

Code being instrumented should always have r as an unconstrained type parameter, both because it is an implementation concern for EventBackends and because references are backend-specific and it would be an error to reference an event in one backend from an event in a different backend.

addField Source #

Arguments

:: Event m r s f 
-> f

The field to add to the event.

-> m () 

Add a field to an Event.

Fields make up the basic data captured in an event. They should be added to an Event as the code progresses through various phases of work, and can be both milestone markers ("we got this far in the process") or more detailed instrumentation ("we've processed N records").

They are intended to be of a domain specific type per unit of functionality within an instrumented codebase (but see DynamicField for a generic option).

addParent Source #

Arguments

:: Event m r s f 
-> r

A reference to the parent, obtained via reference.

-> m () 

Mark another Event as a parent of this Event.

addProximate Source #

Arguments

:: Event m r s f 
-> r

A reference to the proximate cause, obtained via reference.

-> m () 

Mark another Event as a proximate cause of this Event.

Resource-safe event allocation

withEvent Source #

Arguments

:: MonadMask m 
=> EventBackend m r s 
-> forall f. s f

The event selector.

-> (Event m r s f -> m a) 
-> m a 

Run an action with a new Event, selected by the given selector.

The selector specifies the category of new event we're creating, as well as the type of fields that can be added to it (with addField).

Selectors are intended to be of a domain specific type per unit of functionality within an instrumented codebase, implemented as a GADT (but see DynamicEventSelector for a generic option).

The Event is automatically finalized (or, if appropriate, failEvented) at the end of the function it's passed to.

withSubEvent Source #

Arguments

:: MonadMask m 
=> Event m r s f

The parent Event.

-> forall f'. s f'

The child event selector.

-> (Event m r s f' -> m a) 
-> m a 

Run an action with a new Event as a child of the given Event, selected by the given selector.

The selector specifies the category of new event we're creating, as well as the type of fields that can be added to it (with addField).

Selectors are intended to be of a domain specific type per unit of functionality within an instrumented codebase, implemented as a GADT (but see DynamicEventSelector for a generic option).

The Event is automatically finalized (or, if appropriate, failEvented) at the end of the function it's passed to.

Acquire/MonadResource variants

acquireEvent Source #

Arguments

:: MonadUnliftIO m 
=> EventBackend m r s 
-> forall f. s f

The event selector.

-> m (Acquire (Event m r s f)) 

An Acquire variant of withEvent, usable in a MonadResource with allocateAcquire.

Until snoyberg/conduit#460 is addressed, exception information will not be captured.

acquireSubEvent Source #

Arguments

:: MonadUnliftIO m 
=> Event m r s f

The parent event.

-> forall f'. s f'

The child event selector.

-> m (Acquire (Event m r s f')) 

An Acquire variant of withSubEvent, usable in a MonadResource with allocateAcquire.

Until snoyberg/conduit#460 is addressed, exception information will not be captured.

EventBackends

data EventBackend m r s Source #

A backend for creating Events.

Different EventBackends will be used to emit instrumentation to different systems. Multiple backends can be combined with pairEventBackend.

A simple EventBackend for logging to a Handle can be created with jsonHandleBackend.

Typically the entrypoint for some eventuo11y-instrumented code will take an EventBackend, polymorphic in r and possibly m. Calling code can use subEventBackend to place the resulting events in its hierarchy.

From an EventBackend, new events can be created via selectors (of type s f for some field type f), typically with the resource-safe allocation functions. Selectors are values which designate the general category of event being created, as well as the type of fields that can be added to it. For example, a web service's selector type may have a ServicingRequest constructor, whose field type includes a ResponseCode constructor which records the HTTP status code.

Selectors are intended to be of a domain specific type per unit of functionality within an instrumented codebase, implemented as a GADT (but see DynamicEventSelector for a generic option).

Implementations must ensure that EventBackends and their underlying Events are safe to use across threads.

m
The monad we're instrumenting in.
r
The type of event references used in this EventBackend. See reference.
s
The type of event selectors.

subEventBackend Source #

Arguments

:: Monad m 
=> Event m r s f

The parent event.

-> EventBackend m r s 

An EventBackend where every otherwise parentless event will be marked as a child of the given Event.

unitEventBackend :: Applicative m => EventBackend m () s Source #

A no-op EventBackend.

This can be used if calling instrumented code from an un-instrumented context, or to purposefully ignore instrumentation from some call.

unitEventBackend is the algebraic unit of pairEventBackend.

pairEventBackend :: Applicative m => EventBackend m a s -> EventBackend m b s -> EventBackend m (a, b) s Source #

An EventBackend which sequentially generates Events in the two given EventBackends.

This can be used to emit instrumentation in multiple ways (e.g. logs to grafana and metrics on a prometheus HTML page).

hoistEventBackend Source #

Arguments

:: (Functor m, Functor n) 
=> (forall x. m x -> n x)

Natural transformation from m to n.

-> EventBackend m r s 
-> EventBackend n r s 

Hoist an EventBackend along a given natural transformation into a new monad.

narrowEventBackend Source #

Arguments

:: Functor m 
=> (forall f. s f -> t f)

Inject a narrow selector into the wider selector type.

-> EventBackend m r t 
-> EventBackend m r s 

Narrow an EventBackend to a new selector type via a given injection function.

A typical usage, where component A calls component B, would be to have A's selector type have a constructor to take any value of B's selector type (and preserve the field) and then call narrowEventBackend with that constructor when invoking functions in B.

See narrowEventBackend' for a more general, if unweildy, variant.

narrowEventBackend' Source #

Arguments

:: Functor m 
=> (forall f. s f -> forall a. (forall g. t g -> (f -> g) -> a) -> a)

Simultaneously inject a narrow selector into the wider selector type and the narrow selector's field into the wider selector's field type.

-> EventBackend m r t 
-> EventBackend m r s 

Narrow an EventBackend to a new selector type via a given injection function.

See narrowEventBackend for a simpler, if less general, variant.

Primitive Event resource management.

Prefer the resource-safe event allocation functions to these when possible.

finalize :: Monad m => Event m r s f -> m () Source #

Mark an Event as finished.

In normal usage, this should be automatically called via the use of the resource-safe event allocation functions.

This is a no-op if the Event has already been finalized or failEvented. As a result, it is likely pointless to call addField, addParent, or addProximate after this call, though it still may be reasonable to call reference.

failEvent :: Monad m => Event m r s f -> Maybe SomeException -> m () Source #

Mark an Event as having failed, possibly due to an Exception.

In normal usage, this should be automatically called via the use of the resource-safe event allocation functions.

This is a no-op if the Event has already been finalized or failEvented. As a result, it is likely pointless to call addField, addParent, or addProximate after this call, though it still may be reasonable to call reference.

newEvent Source #

Arguments

:: Applicative m 
=> EventBackend m r s 
-> forall f. s f

The event selector.

-> m (Event m r s f) 

Create a new Event, selected by the given selector.

The selector specifies the category of new event we're creating, as well as the type of fields that can be added to it (with addField).

Selectors are intended to be of a domain specific type per unit of functionality within an instrumented codebase, implemented as a GADT (but see DynamicEventSelector for a generic option).

Consider the resource-safe event allocation functions instead of calling this directly.

newSubEvent Source #

Arguments

:: Monad m 
=> Event m r s f

The parent event.

-> forall f'. s f'

The child event selector.

-> m (Event m r s f') 

Create a new Event as a child of the given Event, selected by the given selector.

The selector specifies the category of new event we're creating, as well as the type of fields that can be added to it (with addField).

Selectors are intended to be of a domain specific type per unit of functionality within an instrumented codebase, implemented as a GADT (but see DynamicEventSelector for a generic option).

Consider the resource-safe event allocation functions instead of calling this directly.