[Haskell-cafe] Parallel interruptible computations

Corentin Dupont corentin.dupont at gmail.com
Mon Sep 8 08:51:06 UTC 2014


On Mon, Sep 8, 2014 at 7:55 AM, Chris Wong <lambda.fairy at gmail.com> wrote:

> Hi Corentin
>
> On Mon, Sep 8, 2014 at 8:23 AM, Corentin Dupont
> <corentin.dupont at gmail.com> wrote:
> > Hi guys,
> > thanks for the nice answers!
> > I'll give you a little bit more context: I'm designing an event engine. I
> > have instances for Applicative, Alternative, Monad, MonadPlus.
> > It's like that:
> >
> > ... snip ...
> >
> > The Applicative instance is good if you have two events and you want
> both of
> > them to fire ("and"). The Alternative instance is good if you have two
> > events and you need only one to fire ("or").
> > But what if you have several events, but you need only a part of them to
> > fire in order to construct a final result? Say you have 10 events, but
> the 5
> > first to fire will give you enough data to construct a result.
> > You cannot do that with Applicative/Alternative because with Applicative,
> > you need *all* events results, with Alternative you need *only one*.
> >
> > That's why I added this primitive "ShortcutEvents" in my DSL, but I'm not
> > convinced by it. So my questions are:
> > 1. is ShortcutEvents expressible in term of
> > Applicative/Alternative/Monad/MonadPlus?
> > 2. if not is their a well known typeclass that covers this case?
> > 3. if not is their a better way to write it? I especially don't like the
> > list of Event, I'd prefer a more generic writing. What if I want a
> structure
> > containing the events, instead of a list? What if I want event of various
> > types (say a pair (Event a, Event b) for example)?
> >
> > Note that I'm not working with streams of events (like in traditional FRP
> > frameworks): just with single events (the "BaseEvents") that I want to
> > combine with each other. Those "BaseEvents" will fire only once. The
> final
> > result of the combination of events will trigger a callback.
>
> There's one thing I don't quite understand: why is Event expressed as
> a free monad/applicative structure? Based on your description alone,
> it sounds like
>
>     type Event a = Maybe (BaseEvent a)
>
> would suffice. Or am I missing something?
>
>
Hi Chris!
"Event" is a small DSL that I interpret in the back end.
It allows me to write nice expressions about events. Say you have functions
to create text fields and buttons on the GUI:

-- Create an event binded to a text field, with the first argument as a
title.
-- Once validated, the event returns the content of the text field.
inputText :: String -> Event String

-- Create an event binded to a button, with the first argument as a title.
inputButton :: String -> Event ()


You could then express nice combinations:

-- using Applicative: create a form with two fields
data NameSurname = NameSurname String String
form1 :: Event NameSurname
form1 = NameSurname <$> onInputText "Name:" <*> onInputText "Surname:"

-- using Alternative: create two buttons, first button clicked returns
False, the second True
form2 :: Event Boolean
form2 = True <$ inputButton "click here for True" <|> False <$ inputButton
"click here for False"

-- using Monad: create the two buttons of form2, if "True" button is
clicked, then a text field appears asking for a name.
form3 :: Event String
form3 = do
   myBool <- form2
   if myBool then onInputText "Name:"
   else return "No name"

But I am lacking a way to express the situation where I have a bunch of
events, which can be cancelled as soon as a result can be calculated:
ShortcutEvents :: [Event a] -> ([Maybe a] -> Maybe b) -> Event b

You can think of it as a generalization of the "or" shortcut, where the
evaluation is cut short if the first argument evaluates to True.


With your type:
type Event a = Maybe (BaseEvent a)
Could you express the combinations above??
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://www.haskell.org/pipermail/haskell-cafe/attachments/20140908/e3ddd430/attachment.html>


More information about the Haskell-Cafe mailing list