eventsourcing-0.9.0: CQRS/ES library.

Safe HaskellSafe
LanguageHaskell2010

Database.CQRS.Stream

Description

Events can be written to a stream and can be streamed from it.

Synopsis

Documentation

class Stream f stream where Source #

Associated Types

type EventType stream :: * Source #

Type of the events contained in that stream.

type EventIdentifier stream :: * Source #

Type of unique identifiers for events in the stream.

There must be a total order on identifiers so they can be sorted.

type EventMetadata stream :: * Source #

Depending on the store, this structure can contain the creation date, a correlation ID, etc.

Methods

streamEvents :: stream -> StreamBounds' stream -> Producer [Either (EventIdentifier stream, String) (EventWithContext' stream)] f () Source #

Stream all the events within some bounds in arbitrary batches.

Events must be streamed from lowest to greatest identifier. If the back-end is fetching events in batches, they can be returned in the same way to improve performace. If the event can't be decoded, a Left should be returned instead with the identifier and an error message.

Instances
MonadIO m => Stream m (Stream metadata event) Source # 
Instance details

Defined in Database.CQRS.InMemory

Associated Types

type EventType (Stream metadata event) :: Type Source #

type EventIdentifier (Stream metadata event) :: Type Source #

type EventMetadata (Stream metadata event) :: Type Source #

Methods

streamEvents :: Stream metadata event -> StreamBounds' (Stream metadata event) -> Producer [Either (EventIdentifier (Stream metadata event), String) (EventWithContext' (Stream metadata event))] m () Source #

Monad m => Stream m (TransformedStream m identifier metadata event) Source # 
Instance details

Defined in Database.CQRS.Transformer

Associated Types

type EventType (TransformedStream m identifier metadata event) :: Type Source #

type EventIdentifier (TransformedStream m identifier metadata event) :: Type Source #

type EventMetadata (TransformedStream m identifier metadata event) :: Type Source #

Methods

streamEvents :: TransformedStream m identifier metadata event -> StreamBounds' (TransformedStream m identifier metadata event) -> Producer [Either (EventIdentifier (TransformedStream m identifier metadata event), String) (EventWithContext' (TransformedStream m identifier metadata event))] m () Source #

class Stream f stream => WritableStream f stream where Source #

Methods

writeEventWithMetadata :: stream -> EventType stream -> EventMetadata stream -> ConsistencyCheck (EventIdentifier stream) -> f (EventIdentifier stream) Source #

Append the event to the stream and return the identifier.

The identifier must be greater than the previous events' identifiers.

The function must throw ConsistencyCheckError if the check fails.

Instances
(MonadError Error m, MonadIO m, NFData event, NFData metadata) => WritableStream m (Stream metadata event) Source # 
Instance details

Defined in Database.CQRS.InMemory

Methods

writeEventWithMetadata :: Stream metadata event -> EventType (Stream metadata event) -> EventMetadata (Stream metadata event) -> ConsistencyCheck (EventIdentifier (Stream metadata event)) -> m (EventIdentifier (Stream metadata event)) Source #

data EventWithContext identifier metadata event Source #

Once added to the stream, an event is adorned with an identifier and some metadata.

Constructors

EventWithContext 

Fields

Instances
(Eq identifier, Eq metadata, Eq event) => Eq (EventWithContext identifier metadata event) Source # 
Instance details

Defined in Database.CQRS.Stream

Methods

(==) :: EventWithContext identifier metadata event -> EventWithContext identifier metadata event -> Bool #

(/=) :: EventWithContext identifier metadata event -> EventWithContext identifier metadata event -> Bool #

(Show identifier, Show metadata, Show event) => Show (EventWithContext identifier metadata event) Source # 
Instance details

Defined in Database.CQRS.Stream

Methods

showsPrec :: Int -> EventWithContext identifier metadata event -> ShowS #

show :: EventWithContext identifier metadata event -> String #

showList :: [EventWithContext identifier metadata event] -> ShowS #

Generic (EventWithContext identifier metadata event) Source # 
Instance details

Defined in Database.CQRS.Stream

Associated Types

type Rep (EventWithContext identifier metadata event) :: Type -> Type #

Methods

from :: EventWithContext identifier metadata event -> Rep (EventWithContext identifier metadata event) x #

to :: Rep (EventWithContext identifier metadata event) x -> EventWithContext identifier metadata event #

type Rep (EventWithContext identifier metadata event) Source # 
Instance details

Defined in Database.CQRS.Stream

type Rep (EventWithContext identifier metadata event) = D1 (MetaData "EventWithContext" "Database.CQRS.Stream" "eventsourcing-0.9.0-4g8y83fLOKaCrH4ufVC9GA" False) (C1 (MetaCons "EventWithContext" PrefixI True) (S1 (MetaSel (Just "identifier") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 identifier) :*: (S1 (MetaSel (Just "metadata") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 metadata) :*: S1 (MetaSel (Just "event") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 event))))

class MonadMetadata metadata m where Source #

The event metadata come from the current "environment".

Methods

getMetadata :: m metadata Source #

Instances
Monad m => MonadMetadata () m Source # 
Instance details

Defined in Database.CQRS.Stream

Methods

getMetadata :: m () Source #

data ConsistencyCheck identifier Source #

A condition to check before inserting a new event in a stream.

This can be used to enforce consistency by checking that no new events were inserted since some validation has been performed and therefore that the validations are still sound.

Constructors

NoConsistencyCheck

Always write the new event.

CheckNoEvents

There are no events in that stream.

CheckLastEvent identifier

The latest event's identifier matches.

writeEvent :: (Monad m, MonadMetadata (EventMetadata stream) m, WritableStream m stream) => stream -> EventType stream -> m (EventIdentifier stream) Source #

Get the metadata from the environment, append the event to the store and return the identifier.

writeEventCc :: (Monad m, MonadMetadata (EventMetadata stream) m, WritableStream m stream) => stream -> EventType stream -> ConsistencyCheck (EventIdentifier stream) -> m (EventIdentifier stream) Source #

Get the metadata from the environment, validate the consistency check, append the event to the store and return its identifier.

optimistically :: MonadError Error m => m a -> m a Source #

Execute an action and retry indefinitely as long as it throws ConsistencyCheckError.

This makes it possible to have Optimistic Concurrency Control when writing events by getting the aggregate and using writeEventCc or writeEventWithMetadata inside the action passed to optimistically.

/! It does NOT create a transaction when you can write several events. You should only use this to write a single event!

data StreamBounds identifier Source #

Lower/upper bounds of an event stream.

The Semigroup instance returns bounds for the intersection of the two streams.

Constructors

StreamBounds 

Fields

Instances
Functor StreamBounds Source # 
Instance details

Defined in Database.CQRS.Stream

Methods

fmap :: (a -> b) -> StreamBounds a -> StreamBounds b #

(<$) :: a -> StreamBounds b -> StreamBounds a #

Foldable StreamBounds Source # 
Instance details

Defined in Database.CQRS.Stream

Methods

fold :: Monoid m => StreamBounds m -> m #

foldMap :: Monoid m => (a -> m) -> StreamBounds a -> m #

foldr :: (a -> b -> b) -> b -> StreamBounds a -> b #

foldr' :: (a -> b -> b) -> b -> StreamBounds a -> b #

foldl :: (b -> a -> b) -> b -> StreamBounds a -> b #

foldl' :: (b -> a -> b) -> b -> StreamBounds a -> b #

foldr1 :: (a -> a -> a) -> StreamBounds a -> a #

foldl1 :: (a -> a -> a) -> StreamBounds a -> a #

toList :: StreamBounds a -> [a] #

null :: StreamBounds a -> Bool #

length :: StreamBounds a -> Int #

elem :: Eq a => a -> StreamBounds a -> Bool #

maximum :: Ord a => StreamBounds a -> a #

minimum :: Ord a => StreamBounds a -> a #

sum :: Num a => StreamBounds a -> a #

product :: Num a => StreamBounds a -> a #

Traversable StreamBounds Source # 
Instance details

Defined in Database.CQRS.Stream

Methods

traverse :: Applicative f => (a -> f b) -> StreamBounds a -> f (StreamBounds b) #

sequenceA :: Applicative f => StreamBounds (f a) -> f (StreamBounds a) #

mapM :: Monad m => (a -> m b) -> StreamBounds a -> m (StreamBounds b) #

sequence :: Monad m => StreamBounds (m a) -> m (StreamBounds a) #

Ord identifier => Semigroup (StreamBounds identifier) Source # 
Instance details

Defined in Database.CQRS.Stream

Methods

(<>) :: StreamBounds identifier -> StreamBounds identifier -> StreamBounds identifier #

sconcat :: NonEmpty (StreamBounds identifier) -> StreamBounds identifier #

stimes :: Integral b => b -> StreamBounds identifier -> StreamBounds identifier #

Ord identifier => Monoid (StreamBounds identifier) Source # 
Instance details

Defined in Database.CQRS.Stream

Methods

mempty :: StreamBounds identifier #

mappend :: StreamBounds identifier -> StreamBounds identifier -> StreamBounds identifier #

mconcat :: [StreamBounds identifier] -> StreamBounds identifier #

afterEvent :: Ord identifier => identifier -> StreamBounds identifier Source #

After the event with the given identifier, excluding it.

untilEvent :: Ord identifier => identifier -> StreamBounds identifier Source #

Until the event with the given identifier, including it.