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.Backend

Description

This is the primary module needed to write a new EventBackend and make it an EventBackendIn relevant monads.

Synopsis

Defining backends

class Event (BackendEvent backend) => EventBackend (backend :: Type) Source #

A resource allowing creation of new Events.

It must be an EventBackendIn some monad to be useful.

Associated Types

type BackendEvent backend :: Type -> Type Source #

The Event type this EventBackend can generate.

Events are parameterized by the type of fields they support.

type RootSelector backend :: Type -> Type Source #

The root of the selector tree this EventBackend supports.

Instances

Instances details
EventBackend (Proxy selector) Source #

An EventBackend that does nothing.

Instance details

Defined in Observe.Event.Backend

Associated Types

type BackendEvent (Proxy selector) :: Type -> Type Source #

type RootSelector (Proxy selector) :: Type -> Type 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 #

EventBackend (DataEventBackend m selector) Source #

Consume events by representing them as ordinary Haskell data.

Instance details

Defined in Observe.Event.Backend.Data

Associated Types

type BackendEvent (DataEventBackend m selector) :: Type -> Type Source #

type RootSelector (DataEventBackend m selector) :: Type -> Type Source #

(EventBackend b1, EventBackend b2, RootSelector b1 ~ RootSelector b2) => EventBackend (b1, b2) 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 BackendEvent (b1, b2) :: Type -> Type Source #

type RootSelector (b1, b2) :: Type -> Type Source #

class (EventBackend backend, EventIn m (BackendEvent backend)) => EventBackendIn m backend where Source #

An EventBackend which can be used in a given monad

Methods

newEvent Source #

Arguments

:: backend 
-> EventParams (RootSelector backend) field (EventReference (BackendEvent backend))

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

-> m (BackendEvent backend field) 

Create a new Event with the given field type.

Callers must ensure the resulting Event is finalized; the higher-level event initialization functions take care of this for you.

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

Create an event which has no duration.

Returns a reference to the event.

Instances

Instances details
(Monad m, ParametricFunctor m) => EventBackendIn m (Proxy selector) Source #

An EventBackend that does nothing.

Instance details

Defined in Observe.Event.Backend

Methods

newEvent :: Proxy selector -> EventParams (RootSelector (Proxy selector)) field (EventReference (BackendEvent (Proxy selector))) -> m (BackendEvent (Proxy selector) field) Source #

newInstantEvent :: Proxy selector -> EventParams (RootSelector (Proxy selector)) field (EventReference (BackendEvent (Proxy selector))) -> m (EventReference (BackendEvent (Proxy selector))) Source #

(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 #

(PrimMonad m, ParametricFunctor m) => EventBackendIn m (DataEventBackend m selector) Source #

Consume events by representing them as ordinary Haskell data.

Instance details

Defined in Observe.Event.Backend.Data

(EventBackendIn m b1, EventBackendIn m b2, RootSelector b1 ~ RootSelector b2) => EventBackendIn m (b1, b2) Source #

Combine two EventBackends.

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

Instance details

Defined in Observe.Event.Backend

Methods

newEvent :: (b1, b2) -> EventParams (RootSelector (b1, b2)) field (EventReference (BackendEvent (b1, b2))) -> m (BackendEvent (b1, b2) field) Source #

newInstantEvent :: (b1, b2) -> EventParams (RootSelector (b1, b2)) field (EventReference (BackendEvent (b1, b2))) -> m (EventReference (BackendEvent (b1, b2))) Source #

(EventBackendIn m backend, ParametricMonadTrans t, MonadTransMonadConstraint t m) => EventBackendIn (t m) backend Source #

Lift an EventBackend into a MonadTransformed monad.

Note that this instance is incoherent, so it can be overridden for your backend if need be. This instance will still be used in monad-generic code, however.

Instance details

Defined in Observe.Event.Backend

Methods

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

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

data EventParams selector field reference Source #

Parameters specifying a new Event

Constructors

EventParams 

Fields

Defining event types

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

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

It must be an EventIn some monad to be useful.

Associated Types

type EventReference event :: Type Source #

The type of references to an Event.

Methods

reference :: event field -> EventReference event Source #

Get a reference to this Event

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 #

class (Event event, Monad m, ParametricFunctor m) => EventIn m event where Source #

An Event which can be used in a given monad.

Laws:

  • finalize x >> finalize y = finalize x

Methods

finalize :: event field -> Maybe SomeException -> m () Source #

End the Event, perhaps due to an exception.

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

Implementations should ensure that subsequent finalizeations are no-ops.

addField :: event field -> field -> m () Source #

Add a field to an Event.

Instances

Instances details
(Monad m, ParametricFunctor m) => EventIn m (Const () :: Type -> Type) Source #

An EventBackend that does nothing.

Instance details

Defined in Observe.Event.Backend

Methods

finalize :: Const () field -> Maybe SomeException -> m () Source #

addField :: Const () field -> field -> m () Source #

(EventIn m e1, EventIn m e2) => EventIn m (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

Methods

finalize :: Product e1 e2 field -> Maybe SomeException -> m () Source #

addField :: Product e1 e2 field -> field -> m () Source #

(EventIn m event, ParametricMonadTrans t, MonadTransMonadConstraint t m) => EventIn (t m) event Source #

Lift an Event into a MonadTransformed monad.

Note that this instance is incoherent, so it can be overridden for your event type if need be. This instance will still be used in monad-generic code, however.

Instance details

Defined in Observe.Event.Backend

Methods

finalize :: event field -> Maybe SomeException -> t m () Source #

addField :: event field -> field -> t m () Source #

Selectors

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 

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.