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

Observe.Event.Render.InMemory

Description

 
Synopsis

Documentation

listInMemoryBackend Source #

Arguments

:: (MemoryEvent IO (ListAppendVector IO) UTCTime s -> IO ())

Notify of an Event with no parents or causes

-> EventBackend IO (MemoryEvent IO (ListAppendVector IO) UTCTime s) s 

An EventBackend whose Events are essentially plain Haskell values.

The reference of an Event from this EventBackend will be a MemoryEvent, which can be examined to extract information about the Event.

timelessListInMemoryBackend Source #

Arguments

:: PrimMonad m 
=> (MemoryEvent m (ListAppendVector m) () s -> m ())

Notify of an Event with no parents or causes

-> EventBackend m (MemoryEvent m (ListAppendVector m) () s) s 

An EventBackend whose Events are essentially plain Haskell values.

The reference of an Event from this EventBackend will be a MemoryEvent, which can be examined to extract information about the Event.

inMemoryBackend Source #

Arguments

:: Monad m 
=> InMemoryEffects m appvec ts 
-> (MemoryEvent m appvec ts s -> m ())

Notify of an Event with no parents or causes

-> EventBackend m (MemoryEvent m appvec ts s) s 

An EventBackend whose Events are essentially plain Haskell values.

The reference of an Event from this EventBackend will be a MemoryEvent, which can be examined to extract information about the Event.

appvec
An append-only vector type, see AppendVectorEffects
ts
A timestamp, see TimestampEffects

MemoryEvent

data MemoryEvent m appvec ts s Source #

An plain data type representing an Event

appvec
An append-only vector type, see AppendVectorEffects
ts
A timestamp, see TimestampEffects

Constructors

forall f. MemoryEvent 

Fields

data TimedEventAction ts f Source #

An action that occurred during an Event at some time.

ts
A timestamp, see TimestampEffects

Constructors

TimedEventAction 

Fields

data EventAction f Source #

An action on an Event

Constructors

AddField !f

A field was added with addField

Finalize !(Maybe SomeException)

The Event was finalized with finalize

Effects

InMemoryEffects

data InMemoryEffects m appvec ts Source #

Monadic effects needed to construct an inMemoryBackend

appvec
An append-only vector type, see AppendVectorEffects
ts
A timestamp, see TimestampEffects

Constructors

InMemoryEffects 

Fields

hoistInMemoryEffects :: (forall x. m x -> n x) -> InMemoryEffects m appvec ts -> InMemoryEffects n appvec ts Source #

Hoist InMemoryEffects along a given natural transformation into a new monad

AppendVectorEffects

data AppendVectorEffects m appvec Source #

Monadic effects to manipulate append-only vectors.

Constructors

AppendVectorEffects 

Fields

  • newVector :: !(forall a. m (appvec a))

    Create a new vector

  • appendVector :: !(forall a. appvec a -> a -> m ())

    Append a value to a vector

hoistAppendVectorEffects :: (forall x. m x -> n x) -> AppendVectorEffects m appvec -> AppendVectorEffects n appvec Source #

Hoist AppendVectorEffects along a given natural transformation into a new monad

newtype ListAppendVector m a Source #

An append-only vector in some PrimMonad based on lists.

Constructors

ListAppendVector (MutVar (PrimState m) [a]) 

TimestampEffects

newtype TimestampEffects m ts Source #

Monadic effects to manage timestamps.

Constructors

TimestampEffects 

Fields

hoistTimestampEffects :: (forall x. m x -> n x) -> TimestampEffects m ts -> TimestampEffects n ts Source #

Hoist TimestampEffects along a given natural transformation into a new monad