Domain Events in haskell

Hi Cafe, I am trying to write a very simple implementation of an event publisher pattern but I am stuck and do not know how to do this in Haskell. I have the following code: ======================== {-# LANGUAGE RankNTypes, NamedFieldPuns #-} module Domain.DomainEventPublisher where import Control.Monad (forM_) import HsFu.Data.DateTime import Domain.Client data DomainEvent = ClientChangeAgeDomainEvent data DomainEventContext = DomainEventContext { domainEventContext_event :: DomainEvent , domainEventContext_occurredOn :: DateTime } deriving (Show) data DomainEventPublisher = DomainEventPublisher { domainEventPublisher_subscribers :: [DomainEventContext -> IO ()] } mkEventPublisher :: DomainEventPublisher mkEventPublisher = DomainEventPublisher [] subscribe :: DomainEventPublisher -> (DomainEventContext -> IO ()) -> DomainEventPublisher subscribe publisher eventHandler = DomainEventPublisher { domainEventPublisher_subscribers = eventHandler : (domainEventPublisher_subscribers publisher) } publish :: DomainEventPublisher -> DomainEventContext -> IO () publish DomainEventPublisher{ domainEventPublisher_subscribers } event = forM_ domainEventPublisher_subscribers ($ event) ======================== My problem is that the publish method returns IO (), which means that events can only be published from the IO monad, but I would like events to be 'publish-able' from pure code. I can live with event handlers (passed into the subscribe function) being in the IO monad. Is there a better way to implement this pattern in Haskell? I have been racking my brain on this for a while now and cannot seem to come up with a good implementation. Regards --Rouan.

Hi Rouan,
I like how a similar concept is implemented in F# and I did a similar
Signal type in my simulation library Aivika [1]. Only in my case the
signals (events) are bound up with the modeling time.
The publish function can be indeed and should be pure. Moreover, I
personally preferred the IObservable concept above the Event one as the
former seems to be more functional-like.
Just in F# they introduce also the event source and treat the events and
their sources differently. Therefore, the publish function, being defined
for the event source, is pure.
Thanks,
David
[1] http://hackage.haskell.org/package/aivika
On Fri, Mar 28, 2014 at 2:59 PM, Rouan van Dalen
Hi Cafe,
I am trying to write a very simple implementation of an event publisher pattern but I am stuck and do not know how to do this in Haskell.
I have the following code:
========================
{-# LANGUAGE RankNTypes, NamedFieldPuns #-}
module Domain.DomainEventPublisher where
import Control.Monad (forM_)
import HsFu.Data.DateTime import Domain.Client
data DomainEvent = ClientChangeAgeDomainEvent
data DomainEventContext = DomainEventContext { domainEventContext_event :: DomainEvent , domainEventContext_occurredOn :: DateTime } deriving (Show)
data DomainEventPublisher = DomainEventPublisher { domainEventPublisher_subscribers :: [DomainEventContext -> IO ()] }
mkEventPublisher :: DomainEventPublisher mkEventPublisher = DomainEventPublisher []
subscribe :: DomainEventPublisher -> (DomainEventContext -> IO ()) -> DomainEventPublisher subscribe publisher eventHandler = DomainEventPublisher { domainEventPublisher_subscribers = eventHandler : (domainEventPublisher_subscribers publisher) }
publish :: DomainEventPublisher -> DomainEventContext -> IO () publish DomainEventPublisher{ domainEventPublisher_subscribers } event = forM_ domainEventPublisher_subscribers ($ event)
========================
My problem is that the publish method returns IO (), which means that events can only be published from the IO monad, but I would like events to be 'publish-able' from pure code.
I can live with event handlers (passed into the subscribe function) being in the IO monad.
Is there a better way to implement this pattern in Haskell?
I have been racking my brain on this for a while now and cannot seem to come up with a good implementation.
Regards --Rouan. _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Hi Rouan, I recently developed the effective-aspects package [1], which is a library for monadic pointcut/advice aspect-oriented programming (AOP) in Haskell. Essentially we keep track of the aspects (handlers if you think in terms of event-based programming) in a pure state monad. My problem is that the publish method returns IO (), which means that
events can only be published from the IO monad, but I would like events to be 'publish-able' from pure code.
In the library, you must define a monad with the AOT transformer on top,
say
type M = AOT IO
type M' = AOT (StateT String (ErrorT String Identity))
...
Our model is not tied to the IO monad (rather to an 'AOMonad' class that
provides weaving); hence it does supports pure events (join points in AOP
terminology). A pseudo-code example is:
-- foo has type A -> m B for some types A, B and monad m
-- adv has type Advice (A -> m B); which is a type synonym for (A -> m B)
-> A -> m B
do (deploy (aspect (pcCall foo) adv))
foo # arg
here the # is the 'open application' operator, which triggers the weaving
process that eventually executes the advice.
The main publication of this work can be found here:
http://hal.archives-ouvertes.fr/docs/00/87/27/82/PDF/TAOSD-EffectiveAspects....
I think your particular use case is not described in your email, but if you
want to expose some content other than the application's arguments it will
need some small work on my part (and a new version of the library). I will
be pleased to help you if you are interested in using the library, and if
you can wait a little--- I'm really time-constrained this month :)
Bests,
[1] http://hackage.haskell.org/package/effective-aspects
2014-03-28 11:59 GMT+01:00 Rouan van Dalen
Hi Cafe,
I am trying to write a very simple implementation of an event publisher pattern but I am stuck and do not know how to do this in Haskell.
I have the following code:
========================
{-# LANGUAGE RankNTypes, NamedFieldPuns #-}
module Domain.DomainEventPublisher where
import Control.Monad (forM_)
import HsFu.Data.DateTime import Domain.Client
data DomainEvent = ClientChangeAgeDomainEvent
data DomainEventContext = DomainEventContext { domainEventContext_event :: DomainEvent , domainEventContext_occurredOn :: DateTime } deriving (Show)
data DomainEventPublisher = DomainEventPublisher { domainEventPublisher_subscribers :: [DomainEventContext -> IO ()] }
mkEventPublisher :: DomainEventPublisher mkEventPublisher = DomainEventPublisher []
subscribe :: DomainEventPublisher -> (DomainEventContext -> IO ()) -> DomainEventPublisher subscribe publisher eventHandler = DomainEventPublisher { domainEventPublisher_subscribers = eventHandler : (domainEventPublisher_subscribers publisher) }
publish :: DomainEventPublisher -> DomainEventContext -> IO () publish DomainEventPublisher{ domainEventPublisher_subscribers } event = forM_ domainEventPublisher_subscribers ($ event)
========================
My problem is that the publish method returns IO (), which means that events can only be published from the IO monad, but I would like events to be 'publish-able' from pure code.
I can live with event handlers (passed into the subscribe function) being in the IO monad.
Is there a better way to implement this pattern in Haskell?
I have been racking my brain on this for a while now and cannot seem to come up with a good implementation.
Regards --Rouan. _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
-- Ismael
participants (3)
-
David Sorokin
-
Ismael Figueroa
-
Rouan van Dalen