Copyright | (C) 2016 Yorick Laupa |
---|---|
License | (see the file LICENSE) |
Maintainer | Yorick Laupa <yo.eight@gmail.com> |
Stability | provisional |
Portability | non-portable |
Safe Haskell | None |
Language | Haskell2010 |
Synopsis
- data Batch' a = Batch' {}
- type Batch = Batch' EventNumber
- data Subscription = Subscription {
- subscriptionId :: SubscriptionId
- subscriptionStream :: forall m. MonadBase IO m => Stream (Of SavedEvent) m ()
- data SubscriptionId
- data ExpectedVersionException = ExpectedVersionException {}
- class Store store where
- appendEvents :: (EncodeEvent a, MonadBase IO m) => store -> StreamName -> ExpectedVersion -> [a] -> m (Async EventNumber)
- readStream :: MonadBase IO m => store -> StreamName -> Batch -> Stream (Of SavedEvent) (ExceptT ReadFailure m) ()
- subscribe :: MonadBase IO m => store -> StreamName -> m Subscription
- toStore :: store -> SomeStore
- data SomeStore = Store store => SomeStore store
- freshSubscriptionId :: MonadBase IO m => m SubscriptionId
- startFrom :: a -> Batch' a
- appendEvent :: (EncodeEvent a, MonadBase IO m, Store store) => store -> StreamName -> ExpectedVersion -> a -> m (Async EventNumber)
- unhandled :: (MonadBase IO m, Exception e) => Stream (Of a) (ExceptT e m) () -> Stream (Of a) m ()
Documentation
Represents batch information needed to read a stream.
type Batch = Batch' EventNumber Source #
data Subscription Source #
A subscription allows to be notified on every change occuring on a stream.
Subscription | |
|
data SubscriptionId Source #
Represents a subscription id.
Instances
Eq SubscriptionId Source # | |
Defined in EventSource.Store (==) :: SubscriptionId -> SubscriptionId -> Bool # (/=) :: SubscriptionId -> SubscriptionId -> Bool # | |
Ord SubscriptionId Source # | |
Defined in EventSource.Store compare :: SubscriptionId -> SubscriptionId -> Ordering # (<) :: SubscriptionId -> SubscriptionId -> Bool # (<=) :: SubscriptionId -> SubscriptionId -> Bool # (>) :: SubscriptionId -> SubscriptionId -> Bool # (>=) :: SubscriptionId -> SubscriptionId -> Bool # max :: SubscriptionId -> SubscriptionId -> SubscriptionId # min :: SubscriptionId -> SubscriptionId -> SubscriptionId # | |
Show SubscriptionId Source # | |
Defined in EventSource.Store showsPrec :: Int -> SubscriptionId -> ShowS # show :: SubscriptionId -> String # showList :: [SubscriptionId] -> ShowS # |
data ExpectedVersionException Source #
Instances
Show ExpectedVersionException Source # | |
Defined in EventSource.Store showsPrec :: Int -> ExpectedVersionException -> ShowS # show :: ExpectedVersionException -> String # showList :: [ExpectedVersionException] -> ShowS # | |
Exception ExpectedVersionException Source # | |
class Store store where Source #
Main event store abstraction. It exposes essential features expected from an event store.
appendEvents :: (EncodeEvent a, MonadBase IO m) => store -> StreamName -> ExpectedVersion -> [a] -> m (Async EventNumber) Source #
Appends a batch of events at the end of a stream.
readStream :: MonadBase IO m => store -> StreamName -> Batch -> Stream (Of SavedEvent) (ExceptT ReadFailure m) () Source #
Reads a stream in a stream-processing fashion.
subscribe :: MonadBase IO m => store -> StreamName -> m Subscription Source #
Subscribes to given stream.
toStore :: store -> SomeStore Source #
Encapsulates to an abstract store.
Instances
Store SomeStore Source # | |
Defined in EventSource.Store appendEvents :: (EncodeEvent a, MonadBase IO m) => SomeStore -> StreamName -> ExpectedVersion -> [a] -> m (Async EventNumber) Source # readStream :: MonadBase IO m => SomeStore -> StreamName -> Batch -> Stream (Of SavedEvent) (ExceptT ReadFailure m) () Source # subscribe :: MonadBase IO m => SomeStore -> StreamName -> m Subscription Source # |
Utility type to pass any store that implements Store
typeclass.
Instances
Store SomeStore Source # | |
Defined in EventSource.Store appendEvents :: (EncodeEvent a, MonadBase IO m) => SomeStore -> StreamName -> ExpectedVersion -> [a] -> m (Async EventNumber) Source # readStream :: MonadBase IO m => SomeStore -> StreamName -> Batch -> Stream (Of SavedEvent) (ExceptT ReadFailure m) () Source # subscribe :: MonadBase IO m => SomeStore -> StreamName -> m Subscription Source # |
freshSubscriptionId :: MonadBase IO m => m SubscriptionId Source #
Returns a fresh subscription id.
startFrom :: a -> Batch' a Source #
Starts a Batch
from a given point. The batch size is set to default,
which is 500.
appendEvent :: (EncodeEvent a, MonadBase IO m, Store store) => store -> StreamName -> ExpectedVersion -> a -> m (Async EventNumber) Source #
Appends a single event at the end of a stream.