
Have you got a complete (but preferably small) program showing the problem?
Ian, Here is the source and behavior that I'm seeing (Linux x86, under both 6.6 and 6.7-20070404: module Main where import System.IO import System.IO.Unsafe import System.Process import Text.ParserCombinators.Parsec main :: IO () main = do (_, h, _, p) <- runInteractiveCommand "telnet nyx.nyx.net" t <- hGetContentsTimeout h 15000 print t >> terminateProcess p hGetContentsTimeout :: Handle -> Int -> IO String hGetContentsTimeout h t = do hSetBuffering stdin NoBuffering ready <- hWaitForInput h t; eof <- hIsEOF h if ((not ready) || eof) then return [] else do c <- hGetChar h s <- unsafeInterleaveIO (hGetContentsTimeout h t) return (c:s) -- Behavior with threaded RTS, string is returned early because of EOF: sebell@drei:~/src/remote$ ghc --make Remote.hs -o remote -threaded [1 of 1] Compiling Main ( Remote.hs, Remote.o ) Linking remote ... sebell@drei:~/src/remote$ ./remote "Trying 206.124.29.1...\nConnected to nyx.nyx.net.\nEscape character is '^]'.\n" -- Behavior with non-threaded RTS, proper timeout is observed: sebell@drei:~/src/remote$ ./remote "Trying 206.124.29.1...\nConnected to nyx.nyx.net.\nEscape character is '^]'.\n\n\n Welcome to Nyx, The Spirit of the Night\n (303) 409-1401\n nyx.nyx.net -- 206.124.29.1\n nyx10.nyx.net -- 206.124.29.2\n\n Free Public Internet Access\n\n ===========================\n New user? Login as new\n ===========================\n\n (If you get timed out, try later. Nyx would be too slow to use.)\n\n\n\n\r\n\r\nSunOS UNIX (nyx)\r\n\r\r\n\rlogin: "