#4449: GHC 7 can't do IO when demonized
----------------------------+-----------------------------------------------
Reporter: kazu-yamamoto | Owner: tibbe
Type: bug | Status: new
Priority: normal | Milestone: 7.0.2
Component: Compiler | Version: 7.1
Resolution: | Keywords: forkProcess
Testcase: | Blockedby:
Difficulty: | Os: MacOS X
Blocking: | Architecture: x86
Failure: None/Unknown |
----------------------------+-----------------------------------------------
Comment(by kazu-yamamoto):
To narrow the problem, I made the following code. Please compile it on
Snow Leopard with GHC 7.0.2rc1/-threaded. When you run it, you can see the
following warnings:
{{{
kqueue: kevent: invalid argument (Bad file descriptor)
kqueue: ioManagerWakeup: write: Bad file descriptor
kqueue: sendWakeup: invalid argument (Bad file descriptor)
kqueue: ioManagerDie: write: Bad file descriptor
}}}
Code:
{{{
module Main where
import Control.Concurrent
import System.Event (new)
import System.Exit
import System.IO
import System.Posix
main :: IO ()
main = daemonize $ do
new
threadDelay 100000000
daemonize :: IO () -> IO ()
daemonize program = do
forkProcess $ do
forkProcess program
exitImmediately ExitSuccess
exitImmediately ExitSuccess
}}}
--
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/4449#comment:28>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
_______________________________________________
Glasgow-haskell-bugs mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs