[Haskell-cafe] Safe FFI calls, -threaded and killThread

Simon Marlow simonmar at microsoft.com
Tue Oct 25 04:59:13 EDT 2005


On 25 October 2005 09:07, Einar Karttunen wrote:

> I noticed that killThread in GHC behaves in a problematic fashion with
> -threaded when the killed thread is in a midle of performing a safe
> FFI call. If the behaviour (blocking until the call is done) is
> intended adding documentation might be nice.
> 
> The example below demonstrates the problem. Tthe program gets stuck
> in the killThread call which is not very intuitive. Wrapping every
> killThread in forkIO does not sound very nice either.
> 
> - Einar Karttunen
> 
> import Control.Concurrent
> import Foreign.C
> 
> foreign import ccall threadsafe "sleep" sleep :: CInt -> IO CInt
> 
> main = do mv <- newEmptyMVar
>           tid <- forkIO $ sleep 100 >> putMVar mv ()
>           threadDelay 10000
>           e <- isEmptyMVar mv
>           if e then do putStrLn "killing sleeper"
>                        killThread tid
>                        putStrLn "done"
>                else do putStrLn "sleeper already done"

This is correct, I'll document the behaviour.

killThread/throwTo is currently synchronous - that is, it blocks until
the exception has been delivered to the target thread (unlike the
version in our PLDI paper which was non-blocking, IIRC).  A non-blocking
version can easily be constructed by using forkIO, as you noted.

We can't kill a thread that is involved in a safe foreign call, because
we have no control over the thread involved in the call.  This is the
really the only sensible behaviour.  In the case of an unbound Haskell
thread it would be possible to kill the Haskell thread while leaving the
foreign call running, but this can't be done if the Haskell thread is
bound (because the OS thread it is bound to is currently running foreign
code).

Cheers,
	Simon


More information about the Haskell-Cafe mailing list