
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