| Copyright | Copyright 2022 Shea Levy. |
|---|---|
| License | Apache-2.0 |
| Maintainer | shea@shealevy.com |
| Safe Haskell | Safe-Inferred |
| Language | Haskell2010 |
Observe.Event.Explicit
Description
MonadEvent and EventT-based instrumentation
implicitly track the underlying EventBackend for you. This module is for those
who would rather pass around EventBackends explicitly.
Synopsis
- data Event m r f
- hoistEvent :: (forall x. m x -> n x) -> Event m r f -> Event n r f
- addField :: Event m r f -> f -> m ()
- reference :: Event m r f -> r
- addParent :: Event m r f -> r -> m ()
- addProximate :: Event m r f -> r -> m ()
- addReference :: Event m r f -> Reference r -> m ()
- data Reference r = Reference !ReferenceType !r
- data ReferenceType
- allocateEvent :: (Monad m, Exceptable e) => EventBackend m r s -> forall f. s f -> GeneralAllocate m e () releaseArg (Event m r f)
- withEvent :: MonadWithExceptable m => EventBackend m r s -> forall f. s f -> (Event m r f -> m a) -> m a
- withSubEvent :: MonadWithExceptable m => EventBackend m r s -> Event m r f -> forall f'. s f' -> (Event m r f' -> m a) -> m a
- data EventBackend m r s
- subEventBackend :: PrimMonad m => InjectSelector s t -> Event m r f -> EventBackend m r t -> EventBackend m r s
- causedEventBackend :: PrimMonad m => InjectSelector s t -> Event m r f -> EventBackend m r t -> EventBackend m r s
- hoistEventBackend :: Functor m => (forall x. m x -> n x) -> EventBackend m r s -> EventBackend n r s
- narrowEventBackend :: Functor m => InjectSelector s t -> EventBackend m r t -> EventBackend m r s
- 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
- setDefaultReferenceEventBackend :: PrimMonad m => Reference r -> EventBackend m r s -> EventBackend m r s
- setAncestorEventBackend :: PrimMonad m => r -> EventBackend m r s -> EventBackend m r s
- setInitialCauseEventBackend :: PrimMonad m => r -> EventBackend m r s -> EventBackend m r s
- setReferenceEventBackend :: Monad m => Reference r -> EventBackend m r s -> EventBackend m r s
- setParentEventBackend :: Monad m => r -> EventBackend m r s -> EventBackend m r s
- setProximateEventBackend :: Monad m => r -> EventBackend m r s -> EventBackend m r s
- 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
- finalize :: Event m r f -> Maybe SomeException -> m ()
- newEvent :: EventBackend m r s -> forall f. s f -> m (Event m r f)
- newSubEvent :: Monad m => EventBackend m r s -> Event m r f -> forall f'. s f' -> m (Event m r f')
Documentation
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.
Event manipulation
addField :: Event m r f -> f -> m () Source #
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).
reference :: Event m r f -> r Source #
Obtain a reference to an Event.
References are used to link Events together, via addReference.
References can live past when an event has been finalized.
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.
addProximate :: Event m r f -> r -> m () Source #
addReference :: Event m r f -> Reference r -> m () Source #
data ReferenceType Source #
Instances
| Eq ReferenceType Source # | |
Defined in Observe.Event.Backend Methods (==) :: ReferenceType -> ReferenceType -> Bool # (/=) :: ReferenceType -> ReferenceType -> Bool # | |
Resource-safe event allocation
allocateEvent :: (Monad m, Exceptable e) => EventBackend m r s -> forall f. s f -> GeneralAllocate m e () releaseArg (Event m r f) Source #
Allocate 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).
Arguments
| :: MonadWithExceptable m | |
| => EventBackend m r s | |
| -> forall f. s f | The event selector. |
| -> (Event m r 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 at the end of the function it's passed to.
Arguments
| :: MonadWithExceptable m | |
| => EventBackend m r s | |
| -> Event m r f | The parent |
| -> forall f'. s f' | The child event selector. |
| -> (Event m r 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 at the end of the function it's passed to.
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. Seereference. s- The type of event selectors. See
newEvent.
Backend transformation
Arguments
| :: PrimMonad m | |
| => InjectSelector s t | Bring selectors from the new backend into the parent event's backend. |
| -> Event m r f | The parent event. |
| -> EventBackend m r t | |
| -> EventBackend m r s |
An EventBackend where every otherwise parentless event will be marked
as a child of the given Event.
Arguments
| :: PrimMonad m | |
| => InjectSelector s t | Bring selectors from the new backend into the causing event's backend. |
| -> Event m r f | The causing event. |
| -> EventBackend m r t | |
| -> EventBackend m r s |
An EventBackend where every otherwise causeless event will be marked
as caused by the given Event.
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.
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.
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
setDefaultReferenceEventBackend :: PrimMonad m => Reference r -> EventBackend m r s -> EventBackend m r s Source #
Transform an EventBackend so all of its Events have a given Reference, if they
haven't been given a Reference of the same ReferenceType by the time they are finalized.
See setReferenceEventBackend if the Reference should be applied unconditionally.
setAncestorEventBackend :: PrimMonad m => 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 by the time they are finalized.
See setParentEventBackend if the parent should be set unconditionally.
setInitialCauseEventBackend :: PrimMonad m => r -> EventBackend m r s -> EventBackend m r s Source #
Transform an EventBackend so all of its Events have a given proximate cause,
if they are not given another proximate cause by the time they are finalized.
See setProximateEventBackend if the proximate cause should be set unconditionally.
setReferenceEventBackend :: Monad m => Reference r -> EventBackend m r s -> EventBackend m r s Source #
Transform an EventBackend so all of its Events have a given Reference.
You likely want setDefaultReferenceEventBackend, if your monad supports it.
setParentEventBackend :: Monad m => r -> EventBackend m r s -> EventBackend m r s Source #
Transform an EventBackend so all of its Events have a given parent.
You likely want setAncestorEventBackend, if your monad supports it.
setProximateEventBackend :: Monad m => r -> EventBackend m r s -> EventBackend m r s Source #
Transform an EventBackend so all of its Events have a given proximate cause.
You likely want setInitialCauseEventBackend, if your monad supports it.
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.
Primitive Event resource management.
Prefer the resource-safe event allocation functions to these when possible.
finalize :: Event m r f -> Maybe SomeException -> m () Source #
Mark an Event as finished, perhaps 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.
As a result, it is likely pointless to call
addField or addReference (or addParent / addProximate)
after this call, though it still may be reasonable to call reference.
newEvent :: EventBackend m r s -> forall f. s f -> m (Event m r f) Source #
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.
Arguments
| :: Monad m | |
| => EventBackend m r s | |
| -> Event m r f | The parent event. |
| -> forall f'. s f' | The child event selector. |
| -> m (Event m r 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.