black hole detection and concurrency

Simon Peyton-Jones simonpj at microsoft.com
Mon Dec 29 09:20:10 EST 2008


I have not followed the details of this thread, but Simon Marlow will be back in action on 5 Jan and he should know.

What I do know is that this is supposed to happen:

*         If a *synchronous* exception S is raised when evaluating a thunk, the thunk is permanently updated to "throw S".

*         If an *asynchronous* exception A is raised when evaluating  a thunk, the stack is copied into the heap, and the thunk is updated with a new thunk that, when evaluated, will resume evaluation where it left off.

But there may be some funny interactions with unsafePerformIO.

Simon

From: glasgow-haskell-users-bounces at haskell.org [mailto:glasgow-haskell-users-bounces at haskell.org] On Behalf Of Conal Elliott
Sent: 26 December 2008 06:15
To: glasgow-haskell-users at haskell.org
Subject: black hole detection and concurrency

I'm looking for information about black hole detection with ghc.  I'm getting "<<loop>>" where I don't think there is an actual black hole.  I get this message sometimes with the unamb package, which is implemented with unsafePerformIO, concurrency, and killThread, as described in http://conal.net/blog/posts/functional-concurrency-with-unambiguous-choice/ and http://conal.net/blog/posts/smarter-termination-for-thread-racing/ .

Suppose I have a definition 'v = unsafePerformIO ...', and v is used more than once.   Evaluation (to whnf) of v is begun and the evaluation thread gets killed before evaluation is complete.  Then the second use begins.  Will the second evaluation be (incorrectly) flagged as a black hole?

I haven't found a simple, reproducible example of incorrect black-hole reporting.  My current examples are tied up with the Reactive library.  I do have another strange symptom, which is "thread killed" message.  I wonder if it's related to the <<loop>> message.  Code below.

    Thanks,  - Conal


import Prelude hiding (catch)
import System.IO.Unsafe
import Control.Concurrent
import Control.Exception


-- *** Exception: thread killed
main :: IO ()
main = print $ f (f True) where f v = (v `unamb` True) `seq` v

-- | Unambiguous choice operator.  Equivalent to the ambiguous choice
-- operator, but with arguments restricted to be equal where not bottom,
-- so that the choice doesn't matter.  See also 'amb'.
unamb :: a -> a -> a
unamb a b = unsafePerformIO (evaluate a `race` evaluate b)

-- | Race two actions against each other in separate threads, and pick
-- whichever finishes first.  See also 'amb'.
race :: IO a -> IO a -> IO a
race a b = do
    v <- newEmptyMVar
    let t x = x >>= putMVar v
    withThread (t a) $ withThread (t b) $ takeMVar v
 where
   withThread u v = bracket (forkIO u) killThread (const v)
-------------- next part --------------
An HTML attachment was scrubbed...
URL: http://www.haskell.org/pipermail/glasgow-haskell-users/attachments/20081229/dc94d1c1/attachment-0001.htm


More information about the Glasgow-haskell-users mailing list