Safe Haskell | None |
---|---|
Language | Haskell2010 |
- data EventStore serialized m = EventStore {
- getLatestVersion :: UUID -> m EventVersion
- getEvents :: UUID -> Maybe EventVersion -> m [StoredEvent serialized]
- storeEvents :: ExpectedVersion -> UUID -> [serialized] -> m (Maybe EventWriteError)
- newtype GloballyOrderedEventStore serialized m = GloballyOrderedEventStore {
- getSequencedEvents :: SequenceNumber -> m [GloballyOrderedEvent (StoredEvent serialized)]
- data ExpectedVersion
- data EventWriteError = EventStreamNotAtExpectedVersion EventVersion
- data StoredEvent event = StoredEvent {}
- data GloballyOrderedEvent event = GloballyOrderedEvent {}
- newtype EventVersion = EventVersion {}
- newtype SequenceNumber = SequenceNumber {}
- transactionalExpectedWriteHelper :: Monad m => (UUID -> m EventVersion) -> (UUID -> [serialized] -> m ()) -> ExpectedVersion -> UUID -> [serialized] -> m (Maybe EventWriteError)
EventStore
data EventStore serialized m Source #
The EventStore
is the core type of eventful. A store operates in some
monad m
and stores events by serializing them to the type serialized
.
EventStore | |
|
newtype GloballyOrderedEventStore serialized m Source #
Gets all the events ordered starting with a given SequenceNumber
, and
ordered by SequenceNumber
. This is used when replaying all the events in a
store.
GloballyOrderedEventStore | |
|
data ExpectedVersion Source #
ExpectedVersion is used to assert the event stream is at a certain version number. This is used when multiple writers are concurrently writing to the event store. If the expected version is incorrect, then storing fails.
AnyVersion | Used when the writer doesn't care what version the stream is at. |
NoStream | The stream shouldn't exist yet. |
StreamExists | The stream should already exist. |
ExactVersion EventVersion | Used to assert the stream is at a particular version. |
data EventWriteError Source #
Utility types
data StoredEvent event Source #
A StoredEvent
is an event with associated storage metadata.
StoredEvent | |
|
Functor StoredEvent Source # | |
Foldable StoredEvent Source # | |
Traversable StoredEvent Source # | |
Eq event => Eq (StoredEvent event) Source # | |
Show event => Show (StoredEvent event) Source # | |
data GloballyOrderedEvent event Source #
A GloballyOrderedEvent
is an event that has a global SequenceNumber
.
GloballyOrderedEvent | |
|
Functor GloballyOrderedEvent Source # | |
Foldable GloballyOrderedEvent Source # | |
Traversable GloballyOrderedEvent Source # | |
Eq event => Eq (GloballyOrderedEvent event) Source # | |
Show event => Show (GloballyOrderedEvent event) Source # | |
newtype EventVersion Source #
Event versions are a strictly increasing series of integers for each projection. They allow us to order the events when they are replayed, and they also help as a concurrency check in a multi-threaded environment so services modifying the projection can be sure the projection didn't change during their execution.
newtype SequenceNumber Source #
The sequence number gives us a global ordering of events in a particular event store. Using sequence numbers is not strictly necessary for an event sourcing and CQRS system, but it makes it way easier to replay events consistently without having to use distributed transactions in an event bus. In SQL-based event stores, they are also very cheap to create.
Utility functions
transactionalExpectedWriteHelper :: Monad m => (UUID -> m EventVersion) -> (UUID -> [serialized] -> m ()) -> ExpectedVersion -> UUID -> [serialized] -> m (Maybe EventWriteError) Source #
Helper to create storeEventsRaw
given a function to get the latest
stream version and a function to write to the event store. **NOTE**: This
only works if the monad m
is transactional.