e11y-0.1.0.0: An event-oriented observability library
CopyrightCopyright 2024 Shea Levy.
LicenseApache-2.0
Maintainershea@shealevy.com
Safe HaskellSafe-Inferred
LanguageGHC2021

Observe.Event

Description

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

To consume instrumentation, see Observe.Event.Backend.

Synopsis

Selectors and fields

Instrumentors should first define selector 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.

Fields make up the basic data captured in an event. They should be added to an Event (with addEventField) 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.

type family SubSelector field :: Type -> Type Source #

The selector type for sub-Events underneath an Event of the given field type.

Instrumented code will typically involve nested scopes of events, including calls across different modules, with different types of events expected in different contexts. To support this, each field type has an associated SubSelector type to identify the kind of events that can occur in the scope where the event is active. This results in a tree of event types represented by a tree of selectors, reflecting the tree of instrumented source components: Each selector of the root selector type specifies a field type, which in turn specifies yet another selector (and, with it, its sub-tree). Use cases which require picking out a linear path through this tree can use Selectors.

If there are no sub-Events under Events with field type f, then you can use NoEventsSelector: type instance SubSelector f = NoEventsSelector.

If you want to retain the set of possible event types as in the parent scope, simply set SubSelector to the very same selector type that the parent selector came from.

data NoEventsSelector f Source #

A selector type with no values.

This results in an EventBackend which cannot create any Events, which is useful to terminate the tree of event types generated by SubSelector

Selector rendering

EventBackends will typically require the user to provide a "rendering function" to translate Event-based instrumentation into the format required for the backend. The full type of this will depend on the backend in question, but it will typically involve a function of the form Selectors selector field -> T field for some T (perhaps a function type taking further arguments). The Selectors type is not the simplest to work with, but in most cases the selectorRendering function can be used to write your renderer.

Consider the following selector tree:

module Parent where

import Child

data ParentSelector field where
  ParentA :: ParentSelector AField
  ParentB :: ParentSelector BField

data AField = AField Int
type instance SubSelector AField = NoEventsSelector

data BField = BYes | BNo
type instance SubSelector BField = ChildSelector
module Child where

data ChildSelector field where
  Child :: ChildSelector CField

data CField = CField
type instance SubSelector CField = NoEventsSelector

You could write renderers for these as follows:

module Parent where -- Or it could be in a separate module if you want to keep instrumentation and rendering apart

renderParentSelector :: Selectors ParentSelector field -> Identity field -- Obviously in a real case it wouldn't be Identity
renderParentSelector = selectorRendering $ \case
  ParentA -> noSubEventsSelectorRendering (Identity $ AField 0)
  ParentB -> SelectorRendering
    { renderTopSelector = Identity BYes
    , renderSubSelector = renderChildSelector -- You could also modify the T CField after calling the child renderer
    }
module Child where

renderChildSelector :: Selectors ChildSelector field -> Identity field
renderChildSelector = selectorRendering $ \Child ->
  noSubEventsSelectorRendering $ Identity CField

selectorRendering :: (forall field. selector field -> SelectorRendering t field) -> forall field. Selectors selector field -> t field Source #

Generate a rendering function from a SelectorRendering for each top-level selector.

data SelectorRendering t field Source #

Data needed to define a rendering of Selectors of a given field type.

Constructors

SelectorRendering 

Fields

noSubEventsSelectorRendering :: SubSelector field ~ NoEventsSelector => t field -> SelectorRendering t field Source #

Generate a SelectorRendering for events with no sub-events.

data Selectors selector field where Source #

A nested sequence of selectors, starting from a given root selector family and ending in a selector selecting a given field type.

For example, given:

data FooSelector :: Type -> Type where Foo :: FooSelector FooField
data FooField
type instance SubSelector FooField = BarSelector
data BarSelector :: Type -> Type where Bar :: BarSelector BarField
data BarField
type instance SubSelector BarField = NoEventsSelector

Then Leaf Foo is a sequence Selectors picking out an Event with field type FooField, and Foo :/ Leaf Bar is a sequence of Selectors picking out an Event with field type BarField underneath an Event with field type FooField.

See the selector and field documentation for more details.

Constructors

Leaf :: selector field -> Selectors selector field 
(:/) :: selector field -> Selectors (SubSelector field) field' -> Selectors selector field' infixr 5 

Event initialization

Actual instrumentation centers around Events, which can be initialized in the appropriate computational contexts given an appropriate selector value.

withEvent Source #

Arguments

:: (HasEvents m backend selector, MonadWithExceptable m) 
=> selector field

The event selector

-> (HasSubEvents m backend field => m a)

The eventful computation

-> m a 

Run a computation during an Event selected by the selector.

Parentless Events created during the computation will be marked as children of the new Event.

The Event will be finalized at the end of the computation.

See withRelatedEvent if you need to specify relationships.

instantEvent Source #

Arguments

:: HasEvents m backend selector 
=> selector field

The event selector

-> [field]

The fields of the event.

-> m (EventReference (BackendEvent backend)) 

Emit an instantaneous Event with the given selector and fields.

See instantRelatedEvent if you need to specify relationships.

class Event (event :: Type -> Type) Source #

A resource allowing instrumentation of code via fields of a given type.

It must be an EventIn some monad to be useful.

Minimal complete definition

reference

Instances

Instances details
Event (Const () :: Type -> Type) Source #

An EventBackend that does nothing.

Instance details

Defined in Observe.Event.Backend

Associated Types

type EventReference (Const ()) Source #

Methods

reference :: Const () field -> EventReference (Const ()) Source #

(Event e1, Event e2) => Event (Product e1 e2) Source #

Combine two EventBackends.

All operations are performed sequentially, with no exception safety between calls.

Instance details

Defined in Observe.Event.Backend

Associated Types

type EventReference (Product e1 e2) Source #

Methods

reference :: Product e1 e2 field -> EventReference (Product e1 e2) Source #

Event relationships

Events can be related to each other in two ways: An Event can have another Event as a parent, and an Event can have any number of other Events as proximate causes.

In normal usage, these relationships are handled for you: withEvent automatically marks new Events created in the scope of the Event as children.

If you need to specify more complex relationships, you can get a reference to an Event using eventReference. References are monad-independent data that can outlive the Event itself, and are used to tell an EventBackend which other Events are involved in a new one.

eventReference :: HasEvent event field => EventReference event Source #

Get a reference to the current Event.

withRelatedEvent Source #

Arguments

:: (HasEvents m backend selector, MonadWithExceptable m) 
=> selector field

The event selector

-> Maybe (EventReference (BackendEvent backend))

The parent of this event

-> [EventReference (BackendEvent backend)]

The causes of this event

-> (HasSubEvents m backend field => m a)

The eventful computation

-> m a 

Run a computation during an Event selected by the selector and with the given parent and causes.

Parentless Events created during the computation will be marked as children of the new Event.

The Event will be finalized at the end of the computation.

See withEvent if you don't need to specify any relationships.

For a more flexible allocation, see allocateRelatedEvent.

allocateRelatedEvent Source #

Arguments

:: (HasEvents m backend selector, Exceptable e) 
=> selector field

The event selector

-> Maybe (EventReference (BackendEvent backend))

The parent of this event

-> [EventReference (BackendEvent backend)]

The causes of this event

-> GeneralAllocate m e () releaseArg (BackendEvent backend field) 

A GeneralAllocate-ion of a new Event, selected by the selector and with the given parent and causes.

The Event with be finalized upon release.

See allocateEventArgs for full flexibility in specifying allocation.

You will likely want to construct a SubEventBackend to create a HasSubEvents context when using this Event.

instantRelatedEvent Source #

Arguments

:: HasEvents m backend selector 
=> selector field

The event selector

-> [field]

The fields of the event.

-> Maybe (EventReference (BackendEvent backend))

The parent of this event

-> [EventReference (BackendEvent backend)]

The causes of this event

-> m (EventReference (BackendEvent backend)) 

Emit an instantaneous Event with the given selector and fields and the given parent and causes.

See instantEvent if you don't need to specify any relationships.

See instantEventArgs for full control over Event configuration.

Event-supporting computational contexts

type HasEvents m backend selector = (?e11yBackend :: backend, EventBackendIn m backend, selector ~ RootSelector backend) Source #

A computational context supporting creating Events from a given selector family.

In typical usage, backend will be kept as a type parameter, to be determined at the call site by the dynamically-scoped ?e11yBackend parameter.

HasEvents can be satisfied by binding the ?e11yBackend implicit parameter to an appropriate value. Proxy selector can be used as a no-op EventBackend, and a pair of backends with the same RootSelector can be used as a backend as well.

type HasEvent event field = (?e11yEvent :: event field, Event event) Source #

A scope containing an event of the given field type.

In typical usage, event will be kept as a type parameter, to be determined at the call site by the dynamically-scoped ?e11yEvent parameter.

HasEvent can be satisfied by binding the ?e11yEvent implicit parameter to an appropriate value. withEvent handles this for you.

type HasEventIn m event field = (HasEvent event field, EventIn m event) Source #

A computational context occurring during an event of the given field type.

In typical usage, event will be kept as a type parameter, to be determined at the call site by the dynamically-scoped ?e11yEvent parameter.

HasEventIn can be satisfied by binding the ?e11yEvent implicit parameter to an appropriate value. withEvent handles this for you.

type HasSubEvents m backend field = (HasEventIn m (BackendEvent backend) field, ?e11yBackend :: SubEventBackend backend field) Source #

A computational context occurring during an event of the given field type, allowing the creation of new Events according to its SubSelector which are children of the given event.

In typical usage, backend will be kept as a type parameter, to be determined at the call site by the dynamically-scoped ?e11yBackend parameter.

HasSubEvents can be satisfied by binding the ?e11yEvent and ?e11yBackend implicit parameters to appropriate values, the latter via SubEventBackend. withEvent handles this for you.

Lower-level Event allocation management

data SubEventBackend backend field Source #

An EventBackend to use in the context of a running Event.

It creates events selected by the SubSelector of the event's field type, and any parentless events created by it are made children of the event.

Constructors

SubEventBackend 

Fields

Instances

Instances details
(EventBackendIn m backend, ParametricFunctor m) => EventBackendIn m (SubEventBackend backend field) Source #

Create Events in the parent EventBackend which are children of the running Event and are selected by the SubSelector of its field type.

Instance details

Defined in Observe.Event

Methods

newEvent :: SubEventBackend backend field -> EventParams (RootSelector (SubEventBackend backend field)) field0 (EventReference (BackendEvent (SubEventBackend backend field))) -> m (BackendEvent (SubEventBackend backend field) field0) Source #

newInstantEvent :: SubEventBackend backend field -> EventParams (RootSelector (SubEventBackend backend field)) field0 (EventReference (BackendEvent (SubEventBackend backend field))) -> m (EventReference (BackendEvent (SubEventBackend backend field))) Source #

EventBackend backend => EventBackend (SubEventBackend backend field) Source #

Create Events in the parent EventBackend which are children of the running Event and are selected by the SubSelector of its field type.

Instance details

Defined in Observe.Event

Associated Types

type BackendEvent (SubEventBackend backend field) :: Type -> Type Source #

type RootSelector (SubEventBackend backend field) :: Type -> Type Source #

type BackendEvent (SubEventBackend backend field) Source # 
Instance details

Defined in Observe.Event

type BackendEvent (SubEventBackend backend field)
type RootSelector (SubEventBackend backend field) Source # 
Instance details

Defined in Observe.Event

type RootSelector (SubEventBackend backend field) = SubSelector field

allocateEventArgs Source #

Arguments

:: (HasEvents m backend selector, Exceptable e) 
=> EventParams selector field (EventReference (BackendEvent backend))

Specify the event, matching the appropriate selector type for this EventBackend.

-> GeneralAllocate m e () releaseArg (BackendEvent backend field) 

A GeneralAllocate-ion of a new Event described by EventParams

The Event with be finalized upon release.

You probably want allocateRelatedEvent.

You will likely want to construct a SubEventBackend to construct a HasSubEvents context when using this Event.

instantEventArgs :: HasEvents m backend selector => EventParams selector field (EventReference (BackendEvent backend)) -> m (EventReference (BackendEvent backend)) Source #

Emit an instantaneous Event described by EventParams

You probably want instantEvent or instantRelatedEvent

Event manipulation

addEventField :: HasEventIn m event field => field -> m () Source #

Add a field to the running Event.

finalizeEvent :: HasEventIn m event field => Maybe SomeException -> m () Source #

End the running Event manually, perhaps due to an exception.

It is implementation-specific whether addEventField after finalizeEvent has any effect (but it is not an error).

Subsequent finalizeations, including those that result from leaving the withEvent scope or releasing the allocateEventArgs allocation, will be no-ops.