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/a... 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)

I have a good theory on the latter symptom (the "thread killed" message). Sticking in some traces, as in my appended code, helped me to see what's going on. It seems to be exactly what you describe -- the variable v is permanently bound to the exception it "evaluates" to. Since the right hand True portion of the unamb evaluates more quickly, the spawned threads are killed and the left hand (the v) "evaluates" to "thread killed". This remains the value of its thunk when you access it later. This problem seems sort of innate to a pure unamb utilizing unsafePerformIO and asynchronous exceptions. A clever use of `par` might conceivably help, given that if the par spark fails, the thunk can still be evaluated? Might be a dead end. Here's the code: go = f "f" (f "" True) where f s v = (unamb (s++"f") (s++"g") v True) `seq` v --unamb :: String -> String -> a -> a -> a unamb s s' a b = unsafePerformIO (race s s' (evaluate a) (evaluate b)) --race :: String -> String -> IO a -> IO a -> IO a race s s' a b = do v <- newEmptyMVar let t x = x >>= putMVar v withThread s (t a) $ withThread s' (t b) $ takeMVar v where withThread s u v = bracket (forkIO u) (killNote s) (const $ putStrLn ("in: " ++ s) >> v >>= \x -> putStrLn ("out: " ++ show x ++ " "++ s) >> return x) killNote s tid = throwTo tid (ErrorCall s) And a GHCi session: *Un> go in: ff in: fg in: f in: g out: True fg out: True ff <interactive>: ff *** Exception: ff Cheers, Sterl. On Dec 26, 2008, at 1:15 AM, Conal Elliott wrote:
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)
_______________________________________________ Glasgow-haskell-users mailing list Glasgow-haskell-users@haskell.org http://www.haskell.org/mailman/listinfo/glasgow-haskell-users

Thanks for the probing, Sterl.
I'm afraid I'm stuck here. Without the more effective thread killing (in
unamb), Reactive seems to be drowning in uselessly running threads. With
"improved" thread killing, I get many of these false black holes, instead of
computed values.
I don't know whether this problem is solvable on top of ghc's current RTS,
as you suggest (clever `par` use), but I don't know. I'm out of my depth
here and could sure use help.
Thanks, - Conal
On Fri, Dec 26, 2008 at 6:09 PM, Sterling Clover
I have a good theory on the latter symptom (the "thread killed" message). Sticking in some traces, as in my appended code, helped me to see what's going on. It seems to be exactly what you describe -- the variable v is permanently bound to the exception it "evaluates" to. Since the right hand True portion of the unamb evaluates more quickly, the spawned threads are killed and the left hand (the v) "evaluates" to "thread killed". This remains the value of its thunk when you access it later. This problem seems sort of innate to a pure unamb utilizing unsafePerformIO and asynchronous exceptions. A clever use of `par` might conceivably help, given that if the par spark fails, the thunk can still be evaluated? Might be a dead end.
Here's the code:
go = f "f" (f "" True) where f s v = (unamb (s++"f") (s++"g") v True) `seq` v
--unamb :: String -> String -> a -> a -> a unamb s s' a b = unsafePerformIO (race s s' (evaluate a) (evaluate b))
--race :: String -> String -> IO a -> IO a -> IO a race s s' a b = do v <- newEmptyMVar let t x = x >>= putMVar v withThread s (t a) $ withThread s' (t b) $ takeMVar v where withThread s u v = bracket (forkIO u) (killNote s) (const $ putStrLn ("in: " ++ s) >> v >>= \x -> putStrLn ("out: " ++ show x ++ " "++ s) >> return x)
killNote s tid = throwTo tid (ErrorCall s)
And a GHCi session:
*Un> go in: ff in: fg in: f in: g out: True fg out: True ff <interactive>: ff *** Exception: ff
Cheers, Sterl.
On Dec 26, 2008, at 1:15 AM, Conal Elliott wrote:
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)
_______________________________________________ Glasgow-haskell-users mailing list Glasgow-haskell-users@haskell.org http://www.haskell.org/mailman/listinfo/glasgow-haskell-users

Sterling Clover wrote:
I have a good theory on the latter symptom (the "thread killed" message). Sticking in some traces, as in my appended code, helped me to see what's going on. It seems to be exactly what you describe -- the variable v is permanently bound to the exception it "evaluates" to. Since the right hand True portion of the unamb evaluates more quickly, the spawned threads are killed and the left hand (the v) "evaluates" to "thread killed". This remains the value of its thunk when you access it later.
Thank you for that analysis. It's intriguing. Here's a cut down example:
import Control.Concurrent import Control.Concurrent.MVar import Control.Exception import System.IO.Unsafe
main :: IO () main = do v <- newEmptyMVar let y = print "a" >> takeMVar v >> print "b" x = unsafePerformIO $ y `finally` return () tid <- forkIO $ evaluate x yield print "killing" killThread tid putMVar v () yield print "finally" print x
Output: "a" "killing" "finally" test: thread killed Interestingly, the program works without the `finally` part, suspending the IO action y in the middle: Output without `finally`: "a" "killing" "finally" "b" () The `unamb` operator needs both behaviours: it has to kill its worker threads if it turns out that its value is not yet needed, but it also has to be suspended to allow it to be restarted later. *after some digging in the ghc sources* It may be possible to do the restarting manually:
let y = catchJust threadKilled (print "a" >> takeMVar v >> print "b") (\_ -> myThreadId >>= killThread >> y) threadKilled ThreadKilled = Just () threadKilled _ = Nothing
(for ghc 6.8 use threadKilled (AsyncException ThreadKilled) = Just ()) Output: "a" "killing" "finally" "a" "b" () The key part here is 'myThreadId >>= killThread' which throws an asynchronous exception to the thread itself, causing the update frames to be saved on the heap. Note that 'myThreadId >>= killThread' is not equivalent to 'throw ThreadKilled'; it is a synchronous exception and replaces thunks pointed to by the update frames by another call to the raise primitive - the result being that the exception gets rethrown whenever such a thunk is evaluated. This happens with 'finally' and 'bracket': they use 'throw' for re-throwing the exception. See rts/RaiseAsync.c (raiseAsync() in particular) for the gory details for the first case, and rts/Schedule.c, raiseExceptionHelper() for the second case. In the above code, there is a small window between catching the ThreadKilled exception and throwing it again though, where other exceptions may creep in. The only way I see of fixing that is to use 'block' and 'unblock' directly. Here is an attempt at the 'race' function, using block, catch and unblock. I'm not sure that it's correct. But it seems to work with Sterling's example at least, which triggers a restart.
race :: IO a -> IO a -> IO a race a b = block $ do v <- newEmptyMVar let t x = x >>= putMVar v ta <- forkIO (t a) tb <- forkIO (t b) let cleanup = killThread ta >> killThread tb unblock (do r <- takeMVar v; cleanup; return r) `catch` \e -> case e of ThreadKilled -> do cleanup myThreadId >>= killThread unblock (race a b) e -> throwIO e
Bertram

On Dec 27, 2008, at 9:02 AM, Bertram Felgenhauer wrote:
The key part here is 'myThreadId >>= killThread' which throws an asynchronous exception to the thread itself, causing the update frames to be saved on the heap.
Note that 'myThreadId >>= killThread' is not equivalent to 'throw ThreadKilled'; it is a synchronous exception and replaces thunks pointed to by the update frames by another call to the raise primitive - the result being that the exception gets rethrown whenever such a thunk is evaluated. This happens with 'finally' and 'bracket': they use 'throw' for re-throwing the exception.
See rts/RaiseAsync.c (raiseAsync() in particular) for the gory details for the first case, and rts/Schedule.c, raiseExceptionHelper() for the second case.
In the above code, there is a small window between catching the ThreadKilled exception and throwing it again though, where other exceptions may creep in. The only way I see of fixing that is to use 'block' and 'unblock' directly.
That certainly seems to do the trick for the simple example at least. One way to reason about it better would be, instead of folding everything into the race function, to simply modify ghc's bracket function to give us the behavior we'd prefer (speaking of which, I recall there's something in the works for 6.12 or so to improve rethrowing of asynchronous exceptions?) brackAsync before after thing = block (do a <- before r <- catch (unblock (thing a)) (\_ -> after a >> myThreadId >>= killThread >> brackAsync before after thing ) after a return r ) where threadKilled ThreadKilled = Just () threadKilled _ = Nothing This brackAsync just drops in to the previous code where bracket was and appears to perform correctly. Further, if we place a trace after the killThread, we se it gets executed once when the example is read (i.e. a resumption) but it does not get executed if the (`seq` v) is removed from the example So this gives me some hope that this is actually doing what we'd like. I don't doubt it may have further kinks however. Cheers, Sterl.

Sterling Clover wrote:
On Dec 27, 2008, at 9:02 AM, Bertram Felgenhauer wrote:
In the above code, there is a small window between catching the ThreadKilled exception and throwing it again though, where other exceptions may creep in. The only way I see of fixing that is to use 'block' and 'unblock' directly.
That certainly seems to do the trick for the simple example at least. One way to reason about it better would be, instead of folding everything into the race function, to simply modify ghc's bracket function to give us the behavior we'd prefer (speaking of which, I recall there's something in the works for 6.12 or so to improve rethrowing of asynchronous exceptions?)
brackAsync before after thing = block (do a <- before r <- catch (unblock (thing a)) (\_ -> after a >> myThreadId >>= killThread >> brackAsync before after thing ) after a return r ) where threadKilled ThreadKilled = Just () threadKilled _ = Nothing
This code turns any exception into ThreadKilled further down the stack. (\e -> do after a myThreadId >>= flip throwTo (e :: SomeException) ... might do the trick. My assumption was that anything but 'ThreadKilled' would be a real error. This isn't really true, I guess - thanks to throwTo, any exception could be asynchronous. If an exception is thrown, 'after a' is run again after the computation has resumed. That's why I did the cleanup within the 'catch'. But there's no reason why you couldn't do that as well: brackAsync before after thing = block $ do a <- before catch (unblock (thing a) >>= \r -> after a >> return r) $ \e -> do after a myThreadId >>= flip throwTo (e :: SomeException) brackAsync before after thing )
This brackAsync just drops in to the previous code where bracket was and appears to perform correctly.
Right. 'race' should also unblock exceptions in the worker threads, withThread u v = brackAsync (forkIO (unblock u)) killThread (const v) but that's an independent change.
Further, if we place a trace after the killThread, we se it gets executed once when the example is read (i.e. a resumption) but it does not get executed if the (`seq` v) is removed from the example So this gives me some hope that this is actually doing what we'd like. I don't doubt it may have further kinks however.
At least the GHC RTS has support for the hard part - unwinding the stack so that computations can be resumed seamlessly. I'm not sure which of the approaches I like better - it seems that we have a choice between turning async exceptions into sync ones or vice versa, and neither choice is strictly superior to the other. Enjoy, Bertram 'race' update: - Bugfix: Previously, only AsyncException-s would be caught. Use 'fromException' to select the ThreadKilled exception. - I tried using a custom 'SuspendException' type, but this resulted in 'test: SuspendException' messages on the console, while ThreadKilled is silently ignored... as documented: http://www.haskell.org/ghc/docs/latest/html/libraries/base/Control-Concurren... (http://tinyurl.com/9t5pxs) - Tweak: Block exceptions while running 'cleanup' to avoid killing threads twice. - Trick: takeMVar is a blocking operation, so exceptions can be delivered while it's waiting - there's no need to use 'unblock' for this. In other words, unblock (takeMVar v) and takeMVar v are essentially equivalent for our purposes. race :: IO a -> IO a -> IO a race a b = block $ do v <- newEmptyMVar let t x = unblock (x >>= putMVar v) ta <- forkIO (t a) tb <- forkIO (t b) let cleanup = killThread ta >> killThread tb (do r <- takeMVar v; cleanup; return r) `catch` \e -> cleanup >> case fromException e of Just ThreadKilled -> do myThreadId >>= killThread unblock (race a b) _ -> throwIO e

Thanks very much for these ideas. Peter Verswyvelen suggested running the example repeatedly to see if it always runs correctly. He found, and I verified, that the example runs fine with Bertram's last version of unamb below, *unless* it's compiled with -threaded and run with +RTS -N2. In the latter case, it locks up after a while. I also tried a version with brackAsync and found that it eventually locks up even under ghci. When compiled & run multi-threaded, it locks up almost immediately. I've attached a module, TestRace.hs, containing these experiments. - Conal On Sat, Dec 27, 2008 at 6:03 PM, Bertram Felgenhauer < bertram.felgenhauer@googlemail.com> wrote:
On Dec 27, 2008, at 9:02 AM, Bertram Felgenhauer wrote:
In the above code, there is a small window between catching the ThreadKilled exception and throwing it again though, where other exceptions may creep in. The only way I see of fixing that is to use 'block' and 'unblock' directly.
That certainly seems to do the trick for the simple example at least. One way to reason about it better would be, instead of folding everything into the race function, to simply modify ghc's bracket function to give us the behavior we'd prefer (speaking of which, I recall there's something in
Sterling Clover wrote: the
works for 6.12 or so to improve rethrowing of asynchronous exceptions?)
brackAsync before after thing = block (do a <- before r <- catch (unblock (thing a)) (\_ -> after a >> myThreadId >>= killThread >> brackAsync before after thing ) after a return r ) where threadKilled ThreadKilled = Just () threadKilled _ = Nothing
This code turns any exception into ThreadKilled further down the stack.
(\e -> do after a myThreadId >>= flip throwTo (e :: SomeException) ...
might do the trick.
My assumption was that anything but 'ThreadKilled' would be a real error. This isn't really true, I guess - thanks to throwTo, any exception could be asynchronous.
If an exception is thrown, 'after a' is run again after the computation has resumed.
That's why I did the cleanup within the 'catch'.
But there's no reason why you couldn't do that as well:
brackAsync before after thing = block $ do a <- before catch (unblock (thing a) >>= \r -> after a >> return r) $ \e -> do after a myThreadId >>= flip throwTo (e :: SomeException) brackAsync before after thing )
This brackAsync just drops in to the previous code where bracket was and appears to perform correctly.
Right. 'race' should also unblock exceptions in the worker threads,
withThread u v = brackAsync (forkIO (unblock u)) killThread (const v)
but that's an independent change.
Further, if we place a trace after the killThread, we se it gets executed once when the example is read (i.e. a resumption) but it does not get executed if the (`seq` v) is removed from the example So this gives me some hope that this is actually doing what we'd like. I don't doubt it may have further kinks however.
At least the GHC RTS has support for the hard part - unwinding the stack so that computations can be resumed seamlessly.
I'm not sure which of the approaches I like better - it seems that we have a choice between turning async exceptions into sync ones or vice versa, and neither choice is strictly superior to the other.
Enjoy,
Bertram
'race' update: - Bugfix: Previously, only AsyncException-s would be caught. Use 'fromException' to select the ThreadKilled exception. - I tried using a custom 'SuspendException' type, but this resulted in 'test: SuspendException' messages on the console, while ThreadKilled is silently ignored... as documented:
http://www.haskell.org/ghc/docs/latest/html/libraries/base/Control-Concurren... (http://tinyurl.com/9t5pxs) - Tweak: Block exceptions while running 'cleanup' to avoid killing threads twice. - Trick: takeMVar is a blocking operation, so exceptions can be delivered while it's waiting - there's no need to use 'unblock' for this. In other words, unblock (takeMVar v) and takeMVar v are essentially equivalent for our purposes.
race :: IO a -> IO a -> IO a race a b = block $ do v <- newEmptyMVar let t x = unblock (x >>= putMVar v) ta <- forkIO (t a) tb <- forkIO (t b) let cleanup = killThread ta >> killThread tb (do r <- takeMVar v; cleanup; return r) `catch` \e -> cleanup >> case fromException e of Just ThreadKilled -> do myThreadId >>= killThread unblock (race a b) _ -> throwIO e _______________________________________________ Reactive mailing list Reactive@haskell.org http://www.haskell.org/mailman/listinfo/reactive

Conal Elliott wrote:
Thanks very much for these ideas. Peter Verswyvelen suggested running the example repeatedly to see if it always runs correctly. He found, and I verified, that the example runs fine with Bertram's last version of unamb below, *unless* it's compiled with -threaded and run with +RTS -N2. In the latter case, it locks up after a while.
It seems that we've found an RTS bug. If a thread is started with exceptions blocked, then throwTo might never deliver its exception and block forever, as can be seen with the following test program, which locks up after a while (immediately with the non-threaded RTS) import Control.Exception import Control.Concurrent import Control.Monad test n = do t <- block $ forkIO yield yield putStr $ show n ++ ": kill\n" killThread t main = forM_ [1..] test Or, even more convincing: import Control.Exception import GHC.Conc main = do t1 <- block $ forkIO yield t2 <- forkIO $ killThread t1 yield yield threadStatus t1 >>= print threadStatus t2 >>= print prints (fairly reliably, it seems): ThreadFinished ThreadBlocked BlockedOnException (Trac is giving me errors right now. I'm planning to report this later.)
I also tried a version with brackAsync and found that it eventually locks up even under ghci. When compiled & run multi-threaded, it locks up almost immediately.
-- This one locks up after a while even in ghci. When compiled -threaded -- and run +RTS -N2, it locks up almost immediately. a `race` b = do v <- newEmptyMVar let t x = x >>= putMVar v withThread (t a) $ withThread (t b) $ takeMVar v where withThread u v = brackAsync (forkIO u) killThread (const v)
At the point the 'forkIO' is run, exceptions are blocked, making the thread basically immortal. Using
withThread u v = brackAsync (forkIO $ unblock u) killThread (const v)
we get the same behaviour as with my 'race' - it works for a while, but locks up eventually. I believe that the actual lockup is similar to the test programs above in all cases - what's different is just the probability of triggering it. regards, Bertram

Hi, Bertram Felgenhauer wrote: [snip]
race :: IO a -> IO a -> IO a
Two quick notes on that function:
race a b = block $ do v <- newEmptyMVar let t x = x >>= putMVar v
Should be let t x = unblock (x >>= putMVar v) Otherwise the computation 'x' not be interruptible unless it explicitely uses 'unblock' or a blocking operation like reading an MVar.
ta <- forkIO (t a) tb <- forkIO (t b) let cleanup = killThread ta >> killThread tb unblock (do r <- takeMVar v; cleanup; return r) `catch` \e -> case e of ThreadKilled -> do cleanup myThreadId >>= killThread unblock (race a b)
On the other hand, this 'unblock' should have no effect: If we ever return here, it'll be in a different thread, or after another exception handler has enabled exceptions for the current thread.
e -> throwIO e
Oops. This should call cleanup as well. (I guess it should be done before the 'case' expression) e -> cleanup >> throwIO e Bertram

| I have a good theory on the latter symptom (the "thread killed" | message). Sticking in some traces, as in my appended code, helped me | to see what's going on. It seems to be exactly what you describe -- | the variable v is permanently bound to the exception it "evaluates" | to. Since the right hand True portion of the unamb evaluates more | quickly, the spawned threads are killed and the left hand (the v) | "evaluates" to "thread killed". This is odd (to me). The "permanently bound" stuff applies only to *synchronous* exceptions, which thread-killing is not. Simon M will have more to say when he gets back Simon

Simon Peyton-Jones wrote:
| I have a good theory on the latter symptom (the "thread killed" | message). Sticking in some traces, as in my appended code, helped me | to see what's going on. It seems to be exactly what you describe -- | the variable v is permanently bound to the exception it "evaluates" | to. Since the right hand True portion of the unamb evaluates more | quickly, the spawned threads are killed and the left hand (the v) | "evaluates" to "thread killed".
This is odd (to me). The "permanently bound" stuff applies only to *synchronous* exceptions, which thread-killing is not. Simon M will have more to say when he gets back
This is true when the exception is raised the first time. However, some exception handling functions like 'bracket' catch the exception, do their cleanup, and then throw the exception again. This is done in onException, and goes through throwIO and eventually raiseIO#. At this point the originally asynchronous exception has become a synchronous one. As I wrote elsewhere in this thread, this should not be a problem without unsafePerformIO. Bertram

On Mon, Dec 29, 2008 at 05:07:22PM +0100, Bertram Felgenhauer wrote:
Simon Peyton-Jones wrote:
This is odd (to me). The "permanently bound" stuff applies only to *synchronous* exceptions, which thread-killing is not. Simon M will have more to say when he gets back
This is true when the exception is raised the first time. However, some exception handling functions like 'bracket' catch the exception, do their cleanup, and then throw the exception again. This is done in onException, and goes through throwIO and eventually raiseIO#. At this point the originally asynchronous exception has become a synchronous one.
We don't currently have a way to know whether an exception was thrown asynchronously or not, right? Should we actually be throwing data SomeExceptionSync = SomeExceptionSync Bool -- synchronous? SomeException with catch etc ignoring the Bool, but bracket etc handling it appropriately? Thanks Ian

Ian Lynagh wrote:
On Mon, Dec 29, 2008 at 05:07:22PM +0100, Bertram Felgenhauer wrote:
This is odd (to me). The "permanently bound" stuff applies only to *synchronous* exceptions, which thread-killing is not. Simon M will have more to say when he gets back This is true when the exception is raised the first time. However, some exception handling functions like 'bracket' catch the exception, do
Simon Peyton-Jones wrote: their cleanup, and then throw the exception again. This is done in onException, and goes through throwIO and eventually raiseIO#. At this point the originally asynchronous exception has become a synchronous one.
We don't currently have a way to know whether an exception was thrown asynchronously or not, right?
Should we actually be throwing data SomeExceptionSync = SomeExceptionSync Bool -- synchronous? SomeException with catch etc ignoring the Bool, but bracket etc handling it appropriately?
This ticket describes the problem and a possible solution: http://hackage.haskell.org/trac/ghc/ticket/2558 Cheers, Simon

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@haskell.org [mailto:glasgow-haskell-users-bounces@haskell.org] On Behalf Of Conal Elliott Sent: 26 December 2008 06:15 To: glasgow-haskell-users@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)
participants (6)
-
Bertram Felgenhauer
-
Conal Elliott
-
Ian Lynagh
-
Simon Marlow
-
Simon Peyton-Jones
-
Sterling Clover