Problems interrupting IO with -threaded

Judah Jacobson judah.jacobson at gmail.com
Mon Jun 9 15:09:31 EDT 2008


Hi all,

I'm writing a program that reads input from the user but should also
handle a ctrl-c.  My attempt is below; the program forks a thread to
read one character of input, and kills that thread upon receiving a
sigINT.  It works fine compiled without -threaded, but with -threaded
it blocks forever after a ctrl-c.

I know that in general, foreign calls are not interruptible; but the
documentation for Control.Concurrent and System.Timeout suggests that
I/O operations are a special case.  In particular, the documentation
for System.Timeout.timeout says:

"Standard I/O functions like hGetBuf, hPutBuf, Network.Socket.accept,
or hWaitForInput appear to be blocking, but they really don't because
the runtime system uses scheduling mechanisms like select(2) to
perform asynchronous I/O, so it is possible to interrupt standard
socket I/O or file I/O using this combinator."

So is the behavior that I'm seeing correct?  If so, it seems odd to
get better concurrency without the threaded runtime.  If not, I can
file a bug for this.  I used ghc-6.8.2 and HEAD on OS X 10.5 (x86).

Thanks,
-Judah


--------------
module Main where

import Control.Monad
import System.Posix.Signals
import Control.Concurrent
import Control.Concurrent.MVar

import System.IO

main = do
    hSetBuffering stdin NoBuffering
    hSetEcho stdin False
    mv <- newEmptyMVar
    let handler = putMVar mv Nothing
    installHandler sigINT (CatchOnce handler) Nothing
    tid <- forkIO (myGetChar mv)
    c <- takeMVar mv
    when (c==Nothing) $ do
        killThread tid
    putStrLn ("Result: " ++ show c)

myGetChar mv = do
    c <- getChar
    putMVar mv (Just c)


More information about the Glasgow-haskell-users mailing list