[Haskell-cafe] concurrency vs. I/O in GHC

Donn Cave donn at avvanta.com
Sat Oct 23 18:17:55 EDT 2010


Quoth Claude Heiland-Allen <claudiusmaximus at goto10.org>,
...
> The conclusion I drew was that "unsafe" foreign functions block the 
> current "capability" (OS thread) and any "threads" (Haskell forkIO etc) 
> currently scheduled on that capability, but other capabilities and 
> threads continue executing as normal.

If a trivial test program would help, here I call the sleep() function,
which I believe on a POSIX platform suspends the thread until receipt
of a SIGALRM.

If "unsafe", during the execution of sleep() in one thread, Haskell
execution will be blocked in the other, so they will alternate.
If "safe", the two sleep intervals will overlap.  I believe we all
now expect that, but if it does come as a surprise, I hope someone
will test it on a more common platform.  +RTS -N2 makes no difference.

	Donn Cave, donn at avvanta.com
-----------------------------------
{-# LANGUAGE ForeignFunctionInterface #-}
module Main (main) where
import Control.Concurrent (forkOS)
import Foreign
import Foreign.C

foreign import ccall unsafe "sleep" sleep :: CInt -> IO CInt

rep :: (CInt -> IO CInt) -> CInt -> IO ()
rep f s = do
	print s
	f s
	rep f s

main = do
	forkOS $ rep sleep 3
	rep sleep 1


More information about the Haskell-Cafe mailing list