Pragmatic concurrency Re: [Haskell-cafe] multiple computations, same input

Jon Fairbairn jon.fairbairn at cl.cam.ac.uk
Wed Mar 29 06:50:02 EST 2006


On 2006-03-28 at 08:02+0200 Tomasz Zielonka wrote:
> I wonder if it would be possible to remove the space-leak by running both
> branches concurrently, and scheduling threads in a way that would
> minimise the space-leak. I proposed this before
> 
>   http://www.haskell.org/pipermail/haskell-cafe/2005-December/013428.html
> 
> I would like to hear opinions from some compiler gurus.

This is something I've been thinking about on and off for a
long time (probably since John Hughes mentioned the case of
"average"). I even kept Tomasz's original message in my
inbox until today in the hope that I'd get round to sending
a response, but my flaky health gets in the way. So here,
and I hope people will allow for the fact that I'm half
asleep as I write this, is an attempt.

There are some observations I'd like to make, and a
proposal. Since the proposal relates (in a small way) to
concurrency and is, I think worthwhile, I've cc'd this
message to haskell-prime.

1) choosing the optimal reduction strategy is undecidable

2) we shouldn't (in general) attempt to do undecidable
   things automatically

3) Separation of concerns: Pragmatic decisions about
   evaluation order should be kept separate from the
   denotational aspect of the code. By this token, seq
   shouldn't be a function (because it isn't one), but a
   pragma.  The fact that it's shorter to write seq a b than
   {-# SEQ a #-} b is a matter of syntax, so shouldn't rate
   highly in language design decisions. Perhaps we want a
   different syntax for this kind of pragma, but that's a
   side issue.

So, to take Tomasz's example of wc, we want to be able to
define it essentially this way:

wc cs = (ll, ww, cc) where ll = lines cs
                           ww = words cs
                           cc = length cs

but add [a] pragma[s] to the effect that evaluation should
be input driven, and that ll, ww, and cc are to be given
equal time. Something like {-# STEPPER cs; ROUND_ROBIN
ll,ww,cc #-} (please do not take this as a suggestion of
real syntax!).

The way I would implement this is to add a new primitive,
STEP, which is like seq except that it only evaluates its
argument until it encounters another STEP. (It really isn't
much different to seq).

So after the compiler understood the pragma, it would
replace wc with this (allowing the compiler to pretend step
is a function):

wc cs = (ll, ww, cc) where ll = lines cs'
                           ww = words cs'
                           cc = length cs'
                           cs' = foldr (\a -> STEP ll . STEP ww . STEP cc . (a:))
                                       []
                                       cs

Evaluation would start as normal (a wrinkle here is that the
way I've written it, whichever element of the tuple is
evaluated first gets two goes at the start, but that's a
compiler detail). when it came to evaluating cs', it would
be looking at a thunk something like

STEP ll (STEP ww (STEP cc ('x': ...)))

update the thunk to 

(STEP ww (STEP cc ('x': ...)))

evaluate ll until (and if) it hits the thunk again, update
it to

(STEP cc ('x': ...))

evaluate ww until it hits the thunk, update it to 

'x' : (STEP ...)

evaluate cc, and so on.

It seems to me that this wouldn't take much effort to
implement, but it would provide a simple means of removing
space leaks from a whole bunch of programmes without
mangling the source code much.

  Jón


-- 
Jón Fairbairn                              Jon.Fairbairn at cl.cam.ac.uk




More information about the Haskell-Cafe mailing list