| Copyright | Copyright 2022 Shea Levy. | 
|---|---|
| License | Apache-2.0 | 
| Maintainer | shea@shealevy.com | 
| Safe Haskell | Safe-Inferred | 
| Language | Haskell2010 | 
Observe.Event.Backend
Description
This is the primary module needed to write new EventBackends.
Synopsis
- data EventBackend m r s = EventBackend {- newEvent :: forall f. NewEventArgs r s f -> m (Event m r f)
- emitImmediateEvent :: forall f. NewEventArgs r s f -> m r
 
- data Event m r f = Event {- reference :: !r
- addField :: !(f -> m ())
- finalize :: !(Maybe SomeException -> m ())
 
- data NewEventArgs r s f = NewEventArgs {- newEventSelector :: !(s f)
- newEventParent :: !(Maybe r)
- newEventCauses :: ![r]
- newEventInitialFields :: ![f]
 
- simpleNewEventArgs :: s f -> NewEventArgs r s f
- unitEventBackend :: Applicative m => EventBackend m () s
- pairEventBackend :: Applicative m => EventBackend m a s -> EventBackend m b s -> EventBackend m (a, b) s
- noopEventBackend :: Applicative m => r -> EventBackend m r s
- hoistEventBackend :: Functor m => (forall x. m x -> n x) -> EventBackend m r s -> EventBackend n r s
- hoistEvent :: (forall x. m x -> n x) -> Event m r f -> Event n r f
- type InjectSelector s t = forall f. s f -> forall a. (forall g. t g -> (f -> g) -> a) -> a
- injectSelector :: (forall f. s f -> t f) -> InjectSelector s t
- idInjectSelector :: InjectSelector s s
- narrowEventBackend :: Functor m => InjectSelector s t -> EventBackend m r t -> EventBackend m r s
- setAncestorEventBackend :: r -> EventBackend m r s -> EventBackend m r s
- setInitialCauseEventBackend :: [r] -> EventBackend m r s -> EventBackend m r s
Core interface
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.
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. Seereference.
- s
- The type of event selectors. See newEventSelector.
Constructors
| EventBackend | |
| Fields 
 | |
An instrumentation event.
Events are the core of the instrumenting user's interface
 to eventuo11y. Typical usage would be to create an Event
 using withEvent and add fields to the Event at appropriate
 points in your code with addField.
Constructors
| Event | |
| Fields 
 | |
data NewEventArgs r s f Source #
Arguments specifying how an Event should be created.
See simpleNewEventArgs for a simple case.
Constructors
| NewEventArgs | |
| Fields 
 | |
simpleNewEventArgs :: s f -> NewEventArgs r s f Source #
NewEventArgs from a given selector, with no initial fields or explicit references.
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).
Backend composition
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).
noopEventBackend :: Applicative m => r -> EventBackend m r s Source #
A no-op EventBackend that can be integrated with other backends.
This can be used to purposefully ignore instrumentation from some call.
All events will have the given reference, so can be connected to appropriate events in non-no-op backends, but not in a way that can distinguish between different events from the same no-op backend.
Backend transformation
hoistEventBackend :: Functor m => (forall x. m x -> n x) -> EventBackend m r s -> EventBackend n r s Source #
Hoist an EventBackend along a given natural transformation into a new monad.
hoistEvent :: (forall x. m x -> n x) -> Event m r f -> Event n r f Source #
Hoist an Event along a given natural transformation into a new monad.
type InjectSelector s t = forall f. s f -> forall a. (forall g. t g -> (f -> g) -> a) -> a Source #
Inject a narrower selector and its fields into a wider selector.
See injectSelector for a simple way to construct one of these.
injectSelector :: (forall f. s f -> t f) -> InjectSelector s t Source #
Construct an InjectSelector with a straightforward injection from s to t
idInjectSelector :: InjectSelector s s Source #
The identity InjectSelector
narrowEventBackend :: Functor m => InjectSelector s t -> EventBackend m r t -> EventBackend m r s Source #
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.
setAncestorEventBackend :: r -> EventBackend m r s -> EventBackend m r s Source #
Transform an EventBackend so all of its Events have a given parent, if they
 are not given another parent.
setInitialCauseEventBackend :: [r] -> EventBackend m r s -> EventBackend m r s Source #
Transform an EventBackend so all of its Events have the given causes,
 if they are not given another set of causes.