Re: [Haskell-cafe] Parallel interruptible computations

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: -- | Composable events data Event a where SumEvent :: Event a -> Event a -> Event a -- The first event to fire will be returned. AppEvent :: Event (a -> b) -> Event a -> Event b -- Both events should fire, and then the result is returned. PureEvent :: a -> Event a -- Create a fake event. The result is useable with no delay. EmptyEvent :: Event a -- An event that is never fired. BindEvent :: Event a -> (a -> Event b) -> Event b -- The first event should fire, then a second event is created using the result. BaseEvent :: BaseEvent a -> Event a -- Embed a base event. ShortcutEvents :: [Event a] -> ([Maybe a] -> Maybe b) -> Event b -- The function is called each time an event fires, as soon as the result can be computed from the available data, it is returned, dismissing the events that haven't fired yet. instance Functor Event where fmap f a = pure f <*> a instance Applicative Event where pure = PureEvent (<*>) = AppEvent instance Alternative Event where (<|>) = SumEvent empty = EmptyEvent instance Monad Event where (>>=) = BindEvent return = PureEvent instance MonadPlus Event where mplus = SumEvent mzero = EmptyEvent 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. Cheers, Corentin

Corentin,
As far as I understand, it is similar in implementation to what I have in my simulation library Aivika [1]. Please correct me if I am wrong:
-- | Execute the specified computations in parallel within
-- the current computation and return their results. The cancellation
-- of any of the nested computations affects the current computation.
-- The exception raised in any of the nested computations is propagated
-- to the current computation as well.
processParallel :: [Process a] -> Process [a]
It looks like that my Process type is an equivalent of your type Event in some sense. Only here we would have to cancel (or, interrupt in your terms) all other Process computations right after we receive a final result.
So, if it is true then it is possible to write a new function based on the stated above so that it would be similar to the ShortcutEvents function:
shortcutProcesses: [Process a] -> ([Maybe a] -> Maybe b) -> Process b
Probably, I should add such a function to my library too.
Thanks,
David
[1] http://hackage.haskell.org/package/aivika
08 сент. 2014 г., в 0:23, Corentin Dupont
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:
-- | Composable events data Event a where SumEvent :: Event a -> Event a -> Event a -- The first event to fire will be returned. AppEvent :: Event (a -> b) -> Event a -> Event b -- Both events should fire, and then the result is returned. PureEvent :: a -> Event a -- Create a fake event. The result is useable with no delay. EmptyEvent :: Event a -- An event that is never fired. BindEvent :: Event a -> (a -> Event b) -> Event b -- The first event should fire, then a second event is created using the result. BaseEvent :: BaseEvent a -> Event a -- Embed a base event. ShortcutEvents :: [Event a] -> ([Maybe a] -> Maybe b) -> Event b -- The function is called each time an event fires, as soon as the result can be computed from the available data, it is returned, dismissing the events that haven't fired yet.
instance Functor Event where fmap f a = pure f <*> a
instance Applicative Event where pure = PureEvent (<*>) = AppEvent
instance Alternative Event where (<|>) = SumEvent empty = EmptyEvent
instance Monad Event where (>>=) = BindEvent return = PureEvent
instance MonadPlus Event where mplus = SumEvent mzero = EmptyEvent
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.
Cheers, Corentin

Corentin,
Only in my case the computations are executed ultimately from the event queue and they are bound up with the modeling time. If the time as a factor is not needed in your case, then this is not a problem to exclude the queue from consideration. The main idea is how we can use continuations, one of which is invoked when canceling (interrupting) the computation.
David
08 сент. 2014 г., в 5:53, David Sorokin
Corentin,
As far as I understand, it is similar in implementation to what I have in my simulation library Aivika [1]. Please correct me if I am wrong:
-- | Execute the specified computations in parallel within -- the current computation and return their results. The cancellation -- of any of the nested computations affects the current computation. -- The exception raised in any of the nested computations is propagated -- to the current computation as well. processParallel :: [Process a] -> Process [a]
It looks like that my Process type is an equivalent of your type Event in some sense. Only here we would have to cancel (or, interrupt in your terms) all other Process computations right after we receive a final result.
So, if it is true then it is possible to write a new function based on the stated above so that it would be similar to the ShortcutEvents function:
shortcutProcesses: [Process a] -> ([Maybe a] -> Maybe b) -> Process b
Probably, I should add such a function to my library too.
Thanks, David
[1] http://hackage.haskell.org/package/aivika
08 сент. 2014 г., в 0:23, Corentin Dupont
написал(а): 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:
-- | Composable events data Event a where SumEvent :: Event a -> Event a -> Event a -- The first event to fire will be returned. AppEvent :: Event (a -> b) -> Event a -> Event b -- Both events should fire, and then the result is returned. PureEvent :: a -> Event a -- Create a fake event. The result is useable with no delay. EmptyEvent :: Event a -- An event that is never fired. BindEvent :: Event a -> (a -> Event b) -> Event b -- The first event should fire, then a second event is created using the result. BaseEvent :: BaseEvent a -> Event a -- Embed a base event. ShortcutEvents :: [Event a] -> ([Maybe a] -> Maybe b) -> Event b -- The function is called each time an event fires, as soon as the result can be computed from the available data, it is returned, dismissing the events that haven't fired yet.
instance Functor Event where fmap f a = pure f <*> a
instance Applicative Event where pure = PureEvent (<*>) = AppEvent
instance Alternative Event where (<|>) = SumEvent empty = EmptyEvent
instance Monad Event where (>>=) = BindEvent return = PureEvent
instance MonadPlus Event where mplus = SumEvent mzero = EmptyEvent
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.
Cheers, Corentin

Interresting!
Could you make your type "Process" an instance of MonadParallel?
https://hackage.haskell.org/package/monad-parallel-0.7.1.2/docs/Control-Mona...
This way you could use Control.Monad.Parallel.sequence instead of
processParallel.
But as you can see, processParallel, albeit making the computations in
parallel, as to wait for all processes to finish.
In my case, I want to be able to cancel some of the remaining events: so
Control.Monad.Parallel doesn't seem to be a good fit.
On Mon, Sep 8, 2014 at 3:53 AM, David Sorokin
Corentin,
As far as I understand, it is similar in implementation to what I have in my simulation library Aivika [1]. Please correct me if I am wrong:
-- | Execute the specified computations in parallel within -- the current computation and return their results. The cancellation -- of any of the nested computations affects the current computation. -- The exception raised in any of the nested computations is propagated -- to the current computation as well. processParallel :: [Process a] -> Process [a]
It looks like that my Process type is an equivalent of your type Event in some sense. Only here we would have to cancel (or, interrupt in your terms) all other Process computations right after we receive a final result.
So, if it is true then it is possible to write a new function based on the stated above so that it would be similar to the ShortcutEvents function:
shortcutProcesses: [Process a] -> ([Maybe a] -> Maybe b) -> Process b
Probably, I should add such a function to my library too.
Thanks, David
[1] http://hackage.haskell.org/package/aivika
08 сент. 2014 г., в 0:23, Corentin Dupont
написал(а): 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:
-- | Composable events data Event a where SumEvent :: Event a -> Event a -> Event a -- The first event to fire will be returned. AppEvent :: Event (a -> b) -> Event a -> Event b -- Both events should fire, and then the result is returned. PureEvent :: a -> Event a -- Create a fake event. The result is useable with no delay. EmptyEvent :: Event a -- An event that is never fired. BindEvent :: Event a -> (a -> Event b) -> Event b -- The first event should fire, then a second event is created using the result. BaseEvent :: BaseEvent a -> Event a -- Embed a base event. ShortcutEvents :: [Event a] -> ([Maybe a] -> Maybe b) -> Event b -- The function is called each time an event fires, as soon as the result can be computed from the available data, it is returned, dismissing the events that haven't fired yet.
instance Functor Event where fmap f a = pure f <*> a
instance Applicative Event where pure = PureEvent (<*>) = AppEvent
instance Alternative Event where (<|>) = SumEvent empty = EmptyEvent
instance Monad Event where (>>=) = BindEvent return = PureEvent
instance MonadPlus Event where mplus = SumEvent mzero = EmptyEvent
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.
Cheers, Corentin

Hi Corentin
On Mon, Sep 8, 2014 at 8:23 AM, Corentin Dupont
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? Chris

On Mon, Sep 8, 2014 at 7:55 AM, Chris Wong
Hi Corentin
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
On Mon, Sep 8, 2014 at 8:23 AM, Corentin Dupont
wrote: 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??

"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"
Oh, I see now. So we need to reflect on the structure of the computation, to figure out what widgets to show. That makes sense. Chris
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??
participants (3)
-
Chris Wong
-
Corentin Dupont
-
David Sorokin