[Haskell-cafe] Intuition to understand poor man's concurrency

Benjamin Franksen benjamin.franksen at helmholtz-berlin.de
Wed Jul 30 11:49:32 UTC 2014


martin wrote:
> I am trying to understand the ideas of Koen Klaessen, published in
> Functional Pearls: "A poor man's concurrency" (1993).
> 
> Anyways, I believe I was able to convert that into modern haskell syntax -
> at least it compiles. But I have trouble to understand the Monad instance
> presented there. Could anyobody walk me through the bind function?
> 
> newtype C m a = C ((a -> Action m) -> Action m)
> 
> instance Monad m => Monad (C m) where
>         (C m) >>= k = C cont
>                 where
>                     cont c = m (\a ->
>                                         let C h = k a
>                                         in h c)
>         return x = C $ \c -> c x
> 
> 
> data Action m =
>         Atom (m (Action m))
>         | Fork (Action m) (Action m)
>         | Stop

I find it easier to think about continuations when I remove the wrapping and 
unwrapping of the newtype. To further simplify things, we note that the 
above code makes no use whatsoever of the structure of 'Action m'. (In 
particular, the 'Monad m' constraint is not needed.) This means we can 
replace 'Action m' by a simple type variable 'w':

  type C w a = (a -> w) -> w

The definition of >>= can then almost be derived from the types alone:

  m >>= k = ...

We have m :: (a -> w) -> w and k :: a -> (b -> w) -> w, so

  m >>= k :: (b -> w) -> w

We are given an f :: b -> w as argument and the only function we have that 
takes such a thing as an argument is k, which additionally has the right 
return type (namely w). We could be tempted to try

  r = k x f where ...

with some x :: a as its first argument. However, we do not have a function 
that gives us an x :: a as result. Instead, let's take a look at what we do 
have. We already used the k, but not yet the m. The type of m tells us that 
it takes a function of type a -> w and returns some x :: w. With a bit of 
squinting, one sees that, if we abstract out the x from k x f, we get 
exactly what m takes as input:

  \x -> k x f :: a -> w

and so the solution is clear: we apply the given m to this function, 
resulting in:

  m >>= k = \f -> m (\x -> k x f)

If you re-add the newtype wrapping and unwrapping, this is exactly the same 
as your definition above.

This is one answer to the question of how one can arrive at a suitable 
definition of >>= for the continuation monad. But it does not tell us 
anything about how to arrive at an intuition about what this implementation 
really does. Maybe someone else can explain this...

Cheers
Ben
-- 
"Make it so they have to reboot after every typo." ― Scott Adams




More information about the Haskell-Cafe mailing list