#5611: Asynchronous exception discarded after safe FFI call
---------------------------------+------------------------------------------
Reporter: joeyadams | Owner:
Type: bug | Status: new
Priority: normal | Component: Runtime System
Version: 7.0.3 | Keywords: FFI, exception
Testcase: | Blockedby:
Os: Unknown/Multiple | Blocking:
Architecture: Unknown/Multiple | Failure: Incorrect result at runtime
---------------------------------+------------------------------------------
'''Note:''' This bug appears to be fixed already, as it does not appear
with GHC 7.2.1 . I'm submitting a bug report anyway, to document its
presence.
The bug is: when an asynchronous exception is thrown to a thread making a
(safe) foreign call, the thread throwing the exception blocks like it
should, but then the exception isn't actually delivered. For example:
{{{
{-# LANGUAGE ForeignFunctionInterface #-}
import Control.Concurrent
import Foreign.C
import System.IO
foreign import ccall safe "unistd.h sleep"
sleep :: CUInt -> IO CUInt
main :: IO ()
main = do
hSetBuffering stdout LineBuffering
tid <- forkIO $ do
putStrLn "child: Sleeping"
_ <- sleep 1
-- The following lines should not happen after the killThread from
the
-- parent thread completes. However, they do...
putStrLn "child: Done sleeping"
threadDelay 1000000
putStrLn "child: Done waiting"
threadDelay 100000
putStrLn $ "parent: Throwing exception to thread " ++ show tid
throwTo tid $ userError "Exception delivered successfully"
putStrLn "parent: Done throwing exception"
threadDelay 2000000
}}}
When the bug is present, the program prints:
{{{
child: Sleeping
parent: Throwing exception to thread ThreadId 4
child: Done sleeping
parent: Done throwing exception
child: Done waiting
}}}
"child: Done waiting" should not be printed after completion of the
throwTo, and the exception message should appear. On GHC 7.2.1, the
program prints:
{{{
child: Sleeping
parent: Throwing exception to thread ThreadId 4
parent: Done throwing exception
ffi-sleep: user error (Exception delivered successfully)
}}}
This bug has been reproduced in GHC 7.0.3, on both Linux and Windows. It
has also been reproduced on GHC 7.0.4.
--
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/5611>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
_______________________________________________
Glasgow-haskell-bugs mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs