| Copyright | Copyright 2023 Shea Levy. |
|---|---|
| License | Apache-2.0 |
| Maintainer | shea@shealevy.com |
| Safe Haskell | Safe-Inferred |
| Language | Haskell2010 |
Observe.Event.Render.InMemory
Description
Synopsis
- listInMemoryBackend :: (PrimMonad m, MonadIO m) => EventBackend m (MemoryEvent m (ListAppendVector m) UTCTime s) s
- timelessListInMemoryBackend :: PrimMonad m => EventBackend m (MemoryEvent m (ListAppendVector m) () s) s
- inMemoryBackend :: Monad m => InMemoryEffects m appvec ts -> EventBackend m (MemoryEvent m appvec ts s) s
- data MemoryEvent m appvec ts s = forall f.MemoryEvent {
- initArgs :: !(NewEventArgs (MemoryEvent m appvec ts s) s f)
- start :: !ts
- dynamicValues :: !(Maybe (appvec (TimedEventAction ts f)))
- data TimedEventAction ts f = TimedEventAction {
- when :: !ts
- act :: !(EventAction f)
- data EventAction f
- = AddField !f
- | Finalize !(Maybe SomeException)
- data InMemoryEffects m appvec ts = InMemoryEffects {
- appendVectorEffects :: !(AppendVectorEffects m appvec)
- timestampEffects :: !(TimestampEffects m ts)
- hoistInMemoryEffects :: (forall x. m x -> n x) -> InMemoryEffects m appvec ts -> InMemoryEffects n appvec ts
- listInMemoryEffects :: (PrimMonad m, MonadIO m) => InMemoryEffects m (ListAppendVector m) UTCTime
- timelessListInMemoryEffects :: PrimMonad m => InMemoryEffects m (ListAppendVector m) ()
- data AppendVectorEffects m appvec = AppendVectorEffects {
- newVector :: !(forall a. m (appvec a))
- appendVector :: !(forall a. appvec a -> a -> m ())
- hoistAppendVectorEffects :: (forall x. m x -> n x) -> AppendVectorEffects m appvec -> AppendVectorEffects n appvec
- newtype ListAppendVector m a = ListAppendVector (MutVar (PrimState m) [a])
- listAppendVectorEffects :: PrimMonad m => AppendVectorEffects m (ListAppendVector m)
- newtype TimestampEffects m ts = TimestampEffects {
- getTimestamp :: m ts
- hoistTimestampEffects :: (forall x. m x -> n x) -> TimestampEffects m ts -> TimestampEffects n ts
- dummyTimestampEffects :: Applicative m => TimestampEffects m ()
- ioTimestampEffects :: TimestampEffects IO UTCTime
Documentation
listInMemoryBackend :: (PrimMonad m, MonadIO m) => EventBackend m (MemoryEvent m (ListAppendVector m) UTCTime s) s Source #
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 :: PrimMonad m => EventBackend m (MemoryEvent m (ListAppendVector m) () s) s Source #
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 :: Monad m => InMemoryEffects m appvec ts -> EventBackend m (MemoryEvent m appvec ts s) s Source #
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
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
listInMemoryEffects :: (PrimMonad m, MonadIO m) => InMemoryEffects m (ListAppendVector m) UTCTime Source #
InMemoryEffects based on listAppendVectorEffects and ioTimestampEffects.
timelessListInMemoryEffects :: PrimMonad m => InMemoryEffects m (ListAppendVector m) () Source #
InMemoryEffects based on listAppendVectorEffects with meaningless timestamps.
AppendVectorEffects
data AppendVectorEffects m appvec Source #
Monadic effects to manipulate append-only vectors.
Constructors
| AppendVectorEffects | |
Fields
| |
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]) |
listAppendVectorEffects :: PrimMonad m => AppendVectorEffects m (ListAppendVector m) Source #
AppendVectorEffects in some PrimMonad based on lists.
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
dummyTimestampEffects :: Applicative m => TimestampEffects m () Source #
TimestampEffects with meaningless timestamps.
ioTimestampEffects :: TimestampEffects IO UTCTime Source #
TimestampEffects using the system clock