| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Eventful.Projection
- data Projection state event = Projection {
- projectionSeed :: state
- projectionEventHandler :: state -> event -> state
- latestProjection :: Foldable t => Projection state event -> t event -> state
- allProjections :: Projection state event -> [event] -> [state]
- data StreamProjection state event = StreamProjection {
- streamProjectionProjection :: Projection state event
- streamProjectionUuid :: !UUID
- streamProjectionVersion :: EventVersion
- streamProjectionState :: !state
- streamProjection :: Projection state event -> UUID -> StreamProjection state event
- getLatestProjection :: Monad m => EventStore event m -> StreamProjection state event -> m (StreamProjection state event)
- data GloballyOrderedProjection state serialized = GloballyOrderedProjection {
- globallyOrderedProjectionProjection :: !(Projection state (GloballyOrderedEvent serialized))
- globallyOrderedProjectionSequenceNumber :: !SequenceNumber
- globallyOrderedProjectionState :: !state
- globallyOrderedProjection :: Projection state (GloballyOrderedEvent serialized) -> GloballyOrderedProjection state serialized
- globallyOrderedProjectionEventHandler :: GloballyOrderedProjection state serialized -> GloballyOrderedEvent serialized -> GloballyOrderedProjection state serialized
- getLatestGlobalProjection :: Monad m => GloballyOrderedEventStore serialized m -> GloballyOrderedProjection state serialized -> m (GloballyOrderedProjection state serialized)
- serializedProjection :: Projection state event -> Serializer event serialized -> Projection state serialized
- projectionMapMaybe :: (eventB -> Maybe eventA) -> Projection state eventA -> Projection state eventB
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
| |
Instances
| Contravariant (Projection state) Source # | |
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 state event Source #
A StreamProjection is a Projection that has been constructed from
events from a particular event stream. This is mostly useful so we can
associate an EventVersion with some state.
Constructors
| StreamProjection | |
Fields
| |
streamProjection :: Projection state event -> UUID -> StreamProjection state event Source #
Initialize a StreamProjection with a Projection.
getLatestProjection :: Monad m => EventStore event m -> StreamProjection state event -> m (StreamProjection state event) Source #
Gets the latest projection from a store by using getEvents and then
applying the events using the Projection's event handler.
data GloballyOrderedProjection state serialized Source #
This is a combination of a Projection and the latest projection state
with respect to some SequenceNumber. This is useful for in-memory read
models, and for querying the latest state starting from some previous state
at a lower SequenceNumber.
Constructors
| GloballyOrderedProjection | |
Fields
| |
globallyOrderedProjection :: Projection state (GloballyOrderedEvent serialized) -> GloballyOrderedProjection state serialized Source #
Initialize a GloballyOrderedProjection at SequenceNumber 0 and with
the projection's seed value.
globallyOrderedProjectionEventHandler :: GloballyOrderedProjection state serialized -> GloballyOrderedEvent serialized -> GloballyOrderedProjection state serialized Source #
This applies an event to a GloballyOrderedProjection. NOTE: There is no
guarantee that the SequenceNumber for the event is the previous
SequenceNumber plus one (in fact, that isn't even a guarantee that some
stores can provide). This function will update the
GloballyOrderedProjetion to use the sequence number of the event.
getLatestGlobalProjection :: Monad m => GloballyOrderedEventStore serialized m -> GloballyOrderedProjection state serialized -> m (GloballyOrderedProjection state serialized) Source #
Gets globally ordered events from the event store and builds a
Projection based on ProjectionEvent. Optionally accepts the current
projection state as an argument.
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.