eventful-core-0.1.3: Core module for eventful

Safe HaskellNone
LanguageHaskell2010

Eventful.ProjectionCache.Types

Synopsis

Documentation

data ProjectionCache key orderKey serialized m Source #

A ProjectionCache caches snapshots of Projections in event streams. This is useful if your event streams are very large. This cache operates on some Monad m and stores the Projection state of type serialized.

At its core, this is essentially just a key-value store with knowledge of the stream UUID and EventVersion. It is recommended to use the other helper functions in this module to interpret the stored values using a Projection.

The key and orderKey type parameters are polymorphic so we can abstract over a cache for individual event streams, and a cache for globally ordered streams.

Constructors

ProjectionCache 

Fields

  • storeProjectionSnapshot :: key -> orderKey -> serialized -> m ()

    Stores the state for a projection at a given key and orderKey. This is pretty unsafe, because there is no guarantee what is stored is actually derived from the events in the stream. Consider using updateProjectionCache.

  • loadProjectionSnapshot :: key -> m (Maybe (orderKey, serialized))

    Loads the latest projection state from the cache.

type StreamProjectionCache serialized m = ProjectionCache UUID EventVersion serialized m Source #

Type synonym for a ProjectionCache used on individual event streams.

type GloballyOrderedProjectionCache key serialized m = ProjectionCache key SequenceNumber serialized m Source #

Type synonym for a ProjectionCache that is used in conjunction with a GloballyOrderedEventStore.

runProjectionCacheUsing :: (Monad m, Monad mstore) => (forall a. mstore a -> m a) -> ProjectionCache key orderKey serialized mstore -> ProjectionCache key orderKey serialized m Source #

Changes the monad a ProjectionCache runs in. This is useful to run the cache in another Monad while forgetting the original Monad.

serializedProjectionCache :: Monad m => Serializer state serialized -> ProjectionCache key orderKey serialized m -> ProjectionCache key orderKey state m Source #

Wraps a ProjectionCache and transparently serializes/deserializes events for you. Note that in this implementation deserialization errors when using getEvents are simply ignored (the event is not returned).

getLatestProjectionWithCache :: Monad m => EventStore event m -> StreamProjectionCache state m -> StreamProjection state event -> m (StreamProjection state event) Source #

Like getLatestProjection, but uses a ProjectionCache if it contains more recent state.

getLatestGlobalProjectionWithCache :: Monad m => GloballyOrderedEventStore event m -> GloballyOrderedProjectionCache key state m -> GloballyOrderedProjection state event -> key -> m (GloballyOrderedProjection state event) Source #

Like getLatestGlobalProjection, but uses a ProjectionCache if it contains more recent state.

updateProjectionCache :: Monad m => EventStore event m -> StreamProjectionCache state m -> StreamProjection state event -> m () Source #

Loads the latest projection state from the cache/store and stores this value back into the projection cache.