eventful-core-0.2.0: Core module for eventful

Safe HaskellNone
LanguageHaskell2010

Eventful.Projection

Synopsis

Documentation

data Projection state event Source #

A Projection is a piece of state that is constructed only from events. A Projection is how you reconstruct event sourced state from the ordered stream of events that constitute that state. The "seed" of a Projection is the initial state before any events are applied. The event handler for a projection is the function that actually modifies state based on the given event.

Constructors

Projection 

Fields

  • projectionSeed :: state

    Initial state of a projection

  • projectionEventHandler :: state -> event -> state

    The function that applies and event to the current state, producing a new state.

Instances

Contravariant (Projection state) Source # 

Methods

contramap :: (a -> b) -> Projection state b -> Projection state a #

(>$) :: b -> Projection state b -> Projection state a #

latestProjection :: Foldable t => Projection state event -> t event -> state Source #

Computes the latest state of a Projection from some events.

allProjections :: Projection state event -> [event] -> [state] Source #

Given a list of events, produce all the Projections that were ever produced. Just a scanl using projectionEventHandler. This function is useful for testing Projections; you can easily assert that all the states of a Projection are valid given a list of events.

data StreamProjection key position state event Source #

A StreamProjection is a Projection that has been constructed from events from a particular event stream. This is useful when we want to cache the resulting state and also keep track of what part of the stream the state is caught up to.

Constructors

StreamProjection 

streamProjection :: key -> position -> Projection state event -> StreamProjection key position state event Source #

Initialize a StreamProjection with a Projection, key, and order key.

getLatestStreamProjection :: (Monad m, Num position) => EventStoreReader key position m (StreamEvent key position event) -> StreamProjection key position state event -> m (StreamProjection key position state event) Source #

Gets the latest projection from a store by querying events from the latest order key and then applying the events using the Projection's event handler.

serializedProjection :: Projection state event -> Serializer event serialized -> Projection state serialized Source #

Use a Serializer to wrap a Projection with event type event so it uses the serialized type.

projectionMapMaybe :: (eventB -> Maybe eventA) -> Projection state eventA -> Projection state eventB Source #

Transform a Projection when you only have a partial relationship between the source event type and the target event type.