domaindriven-core-0.5.0: Batteries included event sourcing and CQRS
Safe HaskellSafe-Inferred
LanguageHaskell2010

DomainDriven.Persistance.ForgetfulInMemory

Synopsis

Documentation

createForgetful Source #

Arguments

:: MonadIO m 
=> (model -> Stored event -> model) 
-> model

initial model

-> m (ForgetfulInMemory model event) 

data ForgetfulInMemory model event Source #

STM state without event persistance

Constructors

ForgetfulInMemory 

Fields

Instances

Instances details
Generic (ForgetfulInMemory model event) Source # 
Instance details

Defined in DomainDriven.Persistance.ForgetfulInMemory

Associated Types

type Rep (ForgetfulInMemory model event) :: Type -> Type #

Methods

from :: ForgetfulInMemory model event -> Rep (ForgetfulInMemory model event) x #

to :: Rep (ForgetfulInMemory model event) x -> ForgetfulInMemory model event #

ReadModel (ForgetfulInMemory model e) Source # 
Instance details

Defined in DomainDriven.Persistance.ForgetfulInMemory

Associated Types

type Model (ForgetfulInMemory model e) Source #

type Event (ForgetfulInMemory model e) Source #

WriteModel (ForgetfulInMemory model e) Source # 
Instance details

Defined in DomainDriven.Persistance.ForgetfulInMemory

Methods

transactionalUpdate :: MonadUnliftIO m => ForgetfulInMemory model e -> (Model (ForgetfulInMemory model e) -> m (Model (ForgetfulInMemory model e) -> a, [Event (ForgetfulInMemory model e)])) -> m a Source #

type Rep (ForgetfulInMemory model event) Source # 
Instance details

Defined in DomainDriven.Persistance.ForgetfulInMemory

type Rep (ForgetfulInMemory model event) = D1 ('MetaData "ForgetfulInMemory" "DomainDriven.Persistance.ForgetfulInMemory" "domaindriven-core-0.5.0-7rYqBJZZqKF59TNQHBa9rT" 'False) (C1 ('MetaCons "ForgetfulInMemory" 'PrefixI 'True) ((S1 ('MetaSel ('Just "stateRef") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (IORef model)) :*: S1 ('MetaSel ('Just "apply") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (model -> Stored event -> model))) :*: (S1 ('MetaSel ('Just "seed") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 model) :*: (S1 ('MetaSel ('Just "events") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (IORef [Stored event])) :*: S1 ('MetaSel ('Just "lock") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 QSem)))))
type Event (ForgetfulInMemory model e) Source # 
Instance details

Defined in DomainDriven.Persistance.ForgetfulInMemory

type Event (ForgetfulInMemory model e) = e
type Model (ForgetfulInMemory model e) Source # 
Instance details

Defined in DomainDriven.Persistance.ForgetfulInMemory

type Model (ForgetfulInMemory model e) = model