eventsource-api-1.0.2: Provides a eventsourcing high level API.

Copyright(C) 2016 Yorick Laupa
License(see the file LICENSE)
MaintainerYorick Laupa <yo.eight@gmail.com>
Stabilityprovisional
Portabilitynon-portable
Safe HaskellNone
LanguageHaskell2010

EventSource.Store

Description

 

Synopsis

Documentation

data Batch Source #

Represents batch information needed to read a stream.

Constructors

Batch 

data Subscription Source #

A subscription allows to be notified on every change occuring on a stream.

class Store store where Source #

Main event store abstraction. It exposes essential features expected from an event store.

Minimal complete definition

appendEvents, readBatch, subscribe

Methods

appendEvents :: (EncodeEvent a, MonadIO m) => store -> StreamName -> ExpectedVersion -> [a] -> m (Async EventNumber) Source #

Appends a batch of events at the end of a stream.

readBatch :: MonadIO m => store -> StreamName -> Batch -> m (Async (ReadStatus Slice)) Source #

Appends a batch of events at the end of a stream.

subscribe :: MonadIO m => store -> StreamName -> m Subscription Source #

Subscribes to given stream.

data SomeStore Source #

Utility type to pass any store that implements Store typeclass.

Constructors

Store store => SomeStore store 

data StreamIterator Source #

Allows to easily iterate over a stream's events.

iteratorNextEvent :: (DecodeEvent a, MonadIO m, MonadPlus m) => StreamIterator -> m (Maybe a) Source #

Reads the next available event from the StreamIterator and try to deserialize it at the same time.

iteratorReadAll :: MonadIO m => StreamIterator -> m [SavedEvent] Source #

Reads all events from the StreamIterator until reaching end of stream.

iteratorReadAllEvents :: (DecodeEvent a, MonadIO m, MonadPlus m) => StreamIterator -> m [a] Source #

Like iteratorReadAll but try to deserialize the events at the same time.

streamIterator :: (Store store, MonadIO m) => store -> StreamName -> m (ReadStatus StreamIterator) Source #

Returns a StreamIterator for the given stream name. The returned StreamIterator IS NOT THREADSAFE.

freshSubscriptionId :: MonadIO m => m SubscriptionId Source #

Returns a fresh subscription id.

startFrom :: EventNumber -> Batch Source #

Starts a Batch from a given point. The batch size is set to default, which is 500.

nextEventAs :: (DecodeEvent a, MonadIO m) => Subscription -> m (Either SomeException a) Source #

Waits for the next event and deserializes it on the go.

foldSub :: (DecodeEvent a, MonadIO m) => Subscription -> (a -> m ()) -> (SomeException -> m ()) -> m () Source #

Folds over every event coming from the subscription until the end of the universe, unless an Exception raises from the subscription. SomeException is used because we let the underlying subscription model exposed its own Exception. If the callback that handles incoming events throws an exception, it will not be catch by the error callback.

foldSubAsync :: DecodeEvent a => Subscription -> (a -> IO ()) -> (SomeException -> IO ()) -> IO (Async ()) Source #

Asynchronous version of foldSub.

appendEvent :: (EncodeEvent a, MonadIO m, Store store) => store -> StreamName -> ExpectedVersion -> a -> m (Async EventNumber) Source #

Appends a single event at the end of a stream.

forEvents :: (MonadIO m, DecodeEvent a, Store store) => store -> StreamName -> (a -> m ()) -> ExceptT ForEventFailure m () Source #

Iterates over all events of stream given a starting point and a batch size.

foldEventsM :: (MonadIO m, DecodeEvent a, Store store) => store -> StreamName -> (s -> a -> m s) -> s -> ExceptT ForEventFailure m s Source #

Like forEvents but expose signature similar to foldM.

foldEvents :: (MonadIO m, DecodeEvent a, Store store) => store -> StreamName -> (s -> a -> s) -> s -> ExceptT ForEventFailure m s Source #

Like foldEventsM but expose signature similar to foldl.

forSavedEvents :: (MonadIO m, Store store) => store -> StreamName -> (SavedEvent -> m ()) -> ExceptT ForEventFailure m () Source #

Like forEvents but provides access to SavedEvent instead of decoded event.

foldSavedEventsM :: (MonadIO m, Store store) => store -> StreamName -> (s -> SavedEvent -> m s) -> s -> ExceptT ForEventFailure m s Source #

Like forSavedEvents but expose signature similar to foldM.

foldSavedEvents :: (MonadIO m, Store store) => store -> StreamName -> (s -> SavedEvent -> s) -> s -> ExceptT ForEventFailure m s Source #

Like foldSavedEventsM but expose signature similar to foldl.

foldSubSaved :: MonadIO m => Subscription -> (SavedEvent -> m ()) -> (SomeException -> m ()) -> m () Source #

Similar to foldSub but provides access to the SavedEvent instead of decoded event.

foldSubSavedAsync :: Subscription -> (SavedEvent -> IO ()) -> (SomeException -> IO ()) -> IO (Async ()) Source #

Asynchronous version of foldSubSaved.