Deadlock detection different in ghc-5.04?
Volker Stolz
vs@foldr.org
Mon, 22 Jul 2002 16:51:31 +0200
Hi, for some concurrency abstractions I decided to use deadlock
detection by means of exceptions which didn't work out as expected.
Below is some simplifed source code showing the problem: My assumption
was since GHC should be able to detect that the child still has a
reference to mv_should_work -- although in an exception handler -- the
RTS would never decide to kill the other thread.
Unluckily, this assumption turned out to be false. Did I overestimate
GHC's capabilities or is this a bug? Especially as ghc-5.02.2 shows the
desired behaviour (you just need to drop the "Control.")...
Instead of exiting silently, the program terminates in the exception handler
in the main thread with ghc-5.04.
\begin{code}
module Main where
import Concurrent
import qualified Control.Exception
main = do
mv_should_work <- newEmptyMVar
mv_deadlock <- newEmptyMVar
forkIO $ do
Control.Exception.catch (takeMVar mv_deadlock) -- deadlock
(\ e -> putMVar mv_should_work ())
yield >> yield >> yield
Control.Exception.catch (takeMVar mv_should_work)
(\ e -> putStrLn $ "main caught: " ++ (show e))
\end{code}
--
Volker Stolz * http://www-i2.informatik.rwth-aachen.de/stolz/ * PGP * S/MIME
http://news.bbc.co.uk: `Israeli forces [...], declaring curfews that
confine more than 700,000 people to their homes.'