Odd behavior of ncurses with -threaded
Simon Hengel
simon.hengel at wiktory.org
Thu Nov 11 16:32:00 EST 2010
Hello,
the following program should wait 3 seconds for user input before. If
now user input occurs within that time, it just prints -1.
{-# LANGUAGE ForeignFunctionInterface #-}
module Main where
import Foreign
import Foreign.C.String
import Foreign.C.Types
import Foreign.C.Error
foreign import ccall unsafe initscr :: IO (Ptr ())
foreign import ccall unsafe endwin :: IO CInt
foreign import ccall unsafe getch :: IO CInt
foreign import ccall unsafe timeout :: CInt -> IO ()
main = do
initscr
timeout 3000
c <- getch
endwin
print c
This works just fine if I do not use the threaded RTS, say:
ghc --make -lcurses Main.hs
However, with
ghc --make -threaded -lcurses Main.hs
it prints -1 immediately without awaiting the 3 seconds.
Is that considered a bug? Should I open a ticket?
ghc: 6.12.1
linux: 2.6.32
ncurses: 5.7
Cheers,
Simon
More information about the Glasgow-haskell-users
mailing list