Problems interrupting IO with -threaded

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)

Judah Jacobson wrote:
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).
Ah, this is a consequence of the change we made to stdin/stdout/stderr so that they no longer use O_NONBLOCK, but with -threaded they use blocking foreign calls instead. In your example, getChar is stuck in a blocking foreign call and can't be interrupted. I don't see a good workaround. One way is to add another thread: run the getChar in a subthread and the parent will be able to receive the signal. Or perhaps you could cause the read() that getChar has called to return EINTR, but that might not be enough because the I/O library executes mostly inside Control.Exception.block. Unix semantics just isn't the right thing when it comes to non-blocking I/O. If only there were non-blocking read()/write() system calls, we'd be fine. Cheers, Simon

On 2008 Jun 11, at 0:43, Simon Marlow wrote:
Unix semantics just isn't the right thing when it comes to non- blocking I/O. If only there were non-blocking read()/write() system calls, we'd be fine.
Have you considered using aio_read() and company? -- brandon s. allbery [solaris,freebsd,perl,pugs,haskell] allbery@kf8nh.com system administrator [openafs,heimdal,too many hats] allbery@ece.cmu.edu electrical and computer engineering, carnegie mellon university KF8NH

Brandon S. Allbery KF8NH wrote:
On 2008 Jun 11, at 0:43, Simon Marlow wrote:
Unix semantics just isn't the right thing when it comes to non-blocking I/O. If only there were non-blocking read()/write() system calls, we'd be fine.
Have you considered using aio_read() and company?
aio is not exactly the right API either. The IO manager would have to call aio_suspend(), and then in order to receive events from the RTS over the special pipe we have set up, the IO manager would have to issue its own aio_read() on this FD. And I'm not sure whether you can use aio_suspend() to wait for network accept(), but I suspect not. There ought to be a single way to wait for various different types of event on Unix. Cheers, Simon

Judah Jacobson wrote:
I'm writing a program that reads input from the user but should also handle a ctrl-c... It works fine compiled without -threaded, but with -threaded it blocks forever after a ctrl-c.
Simon Marlow wrote:
Ah, this is a consequence of the change we made to stdin/stdout/stderr so that they no longer use O_NONBLOCK, but with -threaded they use blocking foreign calls instead... I don't see a good workaround... Unix semantics just isn't the right thing when it comes to non-blocking I/O. If only there were non-blocking read()/write() system calls, we'd be fine.
I believe you that the Unix semantics may not be very pretty. But all modern high-level programming languages have a getChar that can be interrupted by ^C. Can't we just do what they all do? This is basic, essential functionality that we use every day. In my opinion, Judah should file a bug, and it should be marked high priority. Thanks, Yitz

Yitzchak Gale wrote:
Judah Jacobson wrote:
I'm writing a program that reads input from the user but should also handle a ctrl-c... It works fine compiled without -threaded, but with -threaded it blocks forever after a ctrl-c.
Simon Marlow wrote:
Ah, this is a consequence of the change we made to stdin/stdout/stderr so that they no longer use O_NONBLOCK, but with -threaded they use blocking foreign calls instead... I don't see a good workaround... Unix semantics just isn't the right thing when it comes to non-blocking I/O. If only there were non-blocking read()/write() system calls, we'd be fine.
I believe you that the Unix semantics may not be very pretty. But all modern high-level programming languages have a getChar that can be interrupted by ^C. Can't we just do what they all do? This is basic, essential functionality that we use every day.
In my opinion, Judah should file a bug, and it should be marked high priority.
You're right. I've created a ticket: http://hackage.haskell.org/trac/ghc/ticket/2363 Cheers, Simon
participants (4)
-
Brandon S. Allbery KF8NH
-
Judah Jacobson
-
Simon Marlow
-
Yitzchak Gale