Copyright | (C) 2017 Yorick Laupa |
---|---|
License | (see the file LICENSE) |
Maintainer | Yorick Laupa <yo.eight@gmail.com> |
Stability | experimental |
Portability | non-portable |
Safe Haskell | None |
Language | Haskell2010 |
EventSource.Aggregate
Contents
Description
Implementation of an aggregate abstraction. Link: https://en.wikipedia.org/wiki/Domain-driven_design.
- class StreamId a where
- class Aggregate a where
- class Aggregate a => Validate a where
- type Decision a = Either (Err a) (Evt a)
- data Agg a
- aggId :: Agg a -> Id a
- runAgg :: MonadBase IO (M a) => Agg a -> Action a r -> (r -> M a ()) -> M a ()
- newAgg :: (Aggregate a, MonadBaseControl IO (M a)) => SomeStore -> Id a -> a -> M a (Agg a)
- loadAgg :: (Aggregate a, StreamId (Id a), DecodeEvent (Evt a), MonadBaseControl IO (M a)) => SomeStore -> Id a -> a -> M a (Either ForEventFailure (Agg a))
- loadOrCreateAgg :: (Aggregate a, StreamId (Id a), DecodeEvent (Evt a), MonadBaseControl IO (M a)) => SomeStore -> Id a -> a -> M a (Agg a)
- submitCmd :: (Validate a, MonadBase IO (M a), StreamId (Id a), EncodeEvent (Evt a)) => Agg a -> Cmd a -> M a (Decision a)
- submitEvt :: (Aggregate a, MonadBase IO (M a)) => Agg a -> Evt a -> M a ()
- snapshot :: MonadBase IO (M a) => Agg a -> M a a
- route :: MonadBase IO (M a) => Agg a -> (SomeStore -> a -> (a -> r -> M a ()) -> M a ()) -> M a r
- closeAgg :: Agg a -> M a ()
- execute :: MonadBase IO (M a) => Agg a -> Action a r -> M a r
- newtype Action' e s m a = Action' {
- runAction :: e -> s -> (s -> a -> m ()) -> m ()
- type Action a r = Action' (AggEnv a) (AggState a) (M a) r
- askEnv :: Action' e s m e
- getState :: Action' e s m s
- putState :: s -> Action' e s m ()
- data AggEnv a = AggEnv {
- aggEnvStore :: SomeStore
- aggEnvId :: Id a
- data AggState a = AggState {
- aggStateVersion :: !ExpectedVersion
- aggState :: !a
- persist :: (StreamId id, EncodeEvent event, MonadBase IO m) => SomeStore -> id -> ExpectedVersion -> event -> m EventNumber
Documentation
class StreamId a where Source #
Maps an id to a StreamName
.
Minimal complete definition
Methods
toStreamName :: a -> StreamName Source #
Aggregate
class Aggregate a where Source #
Represents a stream aggregate. An aggregate can rebuild its internal state by replaying all the stream's events that aggregate is responsible for.
Minimal complete definition
Associated Types
Type of the id associated to the aggregate.
Type of event handled by the aggregate.
Type of monad stack used by the aggregate.
Methods
apply :: a -> Evt a -> M a a Source #
Given current aggregate state, updates it according to the event the aggregate receives.
Instances
AggregateIO event state => Aggregate (Simple id command event state) Source # | |
class Aggregate a => Validate a where Source #
Represents an aggregate that support validation. An aggregate that supports
validation can receive command and decide if it was valid or not. When the
validation is successful, The aggregate emits an event that will be
persisted and pass to apply
function.
Minimal complete definition
Associated Types
Type of command supported by the aggregate.
Type of error that aggregate can yield.
Methods
validate :: a -> Cmd a -> M a (Decision a) Source #
Validates a command. If the command validation succeeds, it will emits an event. Otherwise, it will returns an error.
Instances
ValidateIO command event state => Validate (Simple id command event state) Source # | |
type Decision a = Either (Err a) (Evt a) Source #
When validating a command, tells if the command was valid. If the command is valid, it returns an event. Otherwise, it returns an error.
A stream aggregate. An aggregate updates its internal based on the event
it receives. You can read its current state by using snapshot
. If it
supports validation, through Validated
typeclass, it can receive
command and emits an event if the command was successful. Otherwise, it will
yield an error. When receiving valid command, an aggregate will persist the
resulting event. An aggregate is only responsible of its own stream.
runAgg :: MonadBase IO (M a) => Agg a -> Action a r -> (r -> M a ()) -> M a () Source #
Executes an action on an aggregate.
newAgg :: (Aggregate a, MonadBaseControl IO (M a)) => SomeStore -> Id a -> a -> M a (Agg a) Source #
Creates a new aggregate given an eventstore handle, an id and an initial state.
loadAgg :: (Aggregate a, StreamId (Id a), DecodeEvent (Evt a), MonadBaseControl IO (M a)) => SomeStore -> Id a -> a -> M a (Either ForEventFailure (Agg a)) Source #
Creates an aggregate and replays its entire stream to rebuild its internal state.
loadOrCreateAgg :: (Aggregate a, StreamId (Id a), DecodeEvent (Evt a), MonadBaseControl IO (M a)) => SomeStore -> Id a -> a -> M a (Agg a) Source #
Like loadAgg
but call loadAgg
in case of ForEventFailure
error.
Interactions
submitCmd :: (Validate a, MonadBase IO (M a), StreamId (Id a), EncodeEvent (Evt a)) => Agg a -> Cmd a -> M a (Decision a) Source #
Submits a command to the aggregate. If the command was valid, it returns an event otherwise an error. In case of a valid command, the aggregate persist the resulting event to the eventstore. The aggregate will also update its internal state accordingly.
submitEvt :: (Aggregate a, MonadBase IO (M a)) => Agg a -> Evt a -> M a () Source #
Submits an event. The aggregate will update its internal state accondingly.
route :: MonadBase IO (M a) => Agg a -> (SomeStore -> a -> (a -> r -> M a ()) -> M a ()) -> M a r Source #
Uses usually by Root aggregates which usually have unusual workflow and make great use of a CPS-ed computation. http://blog.sapiensworks.com/post/2016/07/14/DDD-Aggregate-Decoded-1
Internal
newtype Action' e s m a Source #
Internal aggregate action. An action is executed by an aggregate. An action embodies fundamental operations like submitting event, validating command or returning the current snapshot of an aggregate. Action are CPS-ed encoded so the execution model can be flexible. An action can perform synchronously or asynchronously.
type Action a r = Action' (AggEnv a) (AggState a) (M a) r Source #
An action configured to aggregate internal types.
Aggregate internal environment.
Constructors
AggEnv | |
Fields
|
Aggregate internal state.
Constructors
AggState | |
Fields
|
persist :: (StreamId id, EncodeEvent event, MonadBase IO m) => SomeStore -> id -> ExpectedVersion -> event -> m EventNumber Source #
Persists an event to the eventstore.