Concurrent Haskell problem/bug

Greg Mildenhall assassin@live.wasp.net.au
Tue, 10 Jul 2001 04:17:20 +0800 (WST)


OK, it appears that I am a complete fool. My first post on this list and I
forget to include the code I'm writing about.

-Greg

-----------------------------------------------------------------
import Concurrent
import IOExts

awk' x = (unsafePerformIO ppm',x)

ppm'  = do m <- newEmptyMVar
           hs <- sequence [forkIO (f m) | f <- replicate 3 (flip putMVar
True)]
           result <- assess 3 m
           sequence (map killThread hs)
           return result
             where assess 0 m = return True
                   assess n m = do h <- takeMVar m
                                   if h then (assess (n-1) m)
                                        else (return False)

main = sequence [putStrLn ( show (x,unsafePerformIO ppm')) | x <- [1..11]]

-----------------------------------------------------------------

On Tue, 10 Jul 2001, Greg Mildenhall wrote:

> I posted this on comp.lang.functional and someone suggested I try here.
> Apologies if it's not on-charter here - any redirections appreciated.
> 
> I'm seeing unexpected behaviour from GHC 5. (unexpected by me, anyway :)
> 
> The code which is producing the surprising results is at the bottom, but
> I'll breifly explain how it is meant to work here:
> 
> ppm' spawns three threads, and hands them all an MVar.
> Each thread just puts a True into that MVar and exits.
> ppm' takes three values in turn from the MVar and makes sure they are all
> True - if it sees a False value, it stops looking. Once it has assessed
> whether they have all returned true, it kills all of its child threads
> before returning the result of the assessment.
> 
> In this case, where each child returns True, the threads will have already
> exited, but my understanding is that they are not GCed while ppm' has a
> reference to their ThreadIds, so ppm' is still allowed to kill them.
> 
> The ppm' function is "done" 11 times (but some slightly modified versions
> caused me to need up to a hundred invocations in order to see the problem,
> so if you don't see the problem on your GHC, try > 11) and each invocation
> is wrapped up in an unsafePerformIO. (I don't think the unsafePerformIO
> should be a problem, because there oughtn't be any interaction between the
> seperate ppm' instances.)
> 
> Some of these 11 seem to return the expected result, but one of them
> doesn't. The output is this:
> ---------------------------
> (1,True)
> (2,True)
> (3,True)
> (4,True)
> (5,True)
> (6,True)
> (7,True)
> (8,True)
> (9,True)
> (10,True)
> PPM: no threads to run:  infinite loop or deadlock?
> ---------------------------
> 
> So there _does_ seem to be a strange interaction between seperate
> occurrences of ppm'. Can anyone see how that is happening?
> (of course the other possibility is that I've done something
> really silly in my code and not noticed, but I'm happy to take
> suggestions on that front, too. :)
> 
> If noone here can see what is causing it, is anyone here brave enough
> to say "this is probably a GHC bug" and recommend how best I report it?
> 
> Thanks for any insight you can offer me.
> 
> -Greg Mildenhall
> 
> 
> _______________________________________________
> Glasgow-haskell-users mailing list
> Glasgow-haskell-users@haskell.org
> http://www.haskell.org/mailman/listinfo/glasgow-haskell-users
>