#4449: GHC 7 can't do IO when demonized
----------------------------+-----------------------------------------------
  Reporter:  kazu-yamamoto  |          Owner:  tibbe      
      Type:  bug            |         Status:  new        
  Priority:  normal         |      Milestone:             
 Component:  Compiler       |        Version:  7.1        
Resolution:                 |       Keywords:  forkProcess
  Testcase:                 |      Blockedby:             
Difficulty:                 |             Os:  MacOS X    
  Blocking:                 |   Architecture:  x86        
   Failure:  None/Unknown   |  
----------------------------+-----------------------------------------------
Changes (by igloo):

  * owner:  => tibbe


Comment:

 On OS X, this program:
 {{{
 import Control.Concurrent
 import Network
 import System.IO

 import Prelude hiding (catch)
 import System
 import System.Posix

 main :: IO ()
 main = daemonize $ do
     writeFile "X1" "Here"
     s <- listenOn (Service "7000")
     writeFile "X2" "Here"
     loop s
     writeFile "X3" "Here"
     return ()

 loop :: Socket -> IO ()
 loop s = do
     writeFile "X4" "Here"
     (hdr,_,_) <- accept s
     writeFile "X5" "Here"
     _ <- forkIO $ echo hdr
     writeFile "X6" "Here"
     loop s

 echo :: Handle -> IO ()
 echo hdr = do
     writeFile "X7" "Here"
     str <- hGetLine hdr
     writeFile "X8" "Here"
     hPutStrLn hdr str
     writeFile "X9" "Here"
     hClose hdr
     writeFile "X0" "Here"
     return ()

 daemonize :: IO () -> IO ()
 daemonize program =

   do _ <- setFileCreationMask 0
      _ <- forkProcess p
      exitImmediately ExitSuccess

     where

       p  = do _ <- createSession
               _ <- forkProcess p'
               exitImmediately ExitSuccess

       p' = do -- changeWorkingDirectory "/"
               closeFileDescriptors
               blockSignal sigHUP
               program

 closeFileDescriptors :: IO ()
 closeFileDescriptors =
     do devNull <- openFd "/dev/null" ReadWrite Nothing defaultFileFlags
        let redirectTo fd' fd = closeFd fd >> dupTo fd' fd
        mapM_ (redirectTo devNull) [stdInput, stdOutput, stdError]

 blockSignal :: Signal -> IO ()
 blockSignal sig = installHandler sig Ignore Nothing >> pass

 pass :: IO ()
 pass = return ()
 }}}
 creates `X4` but not `X5` when I compile it with
 {{{
 ghc --make q -threaded
 }}}
 with 7.0.1 RC 2. It works when compiled with 6.12.3. Both have
 `network-2.2.3.1`.

 Tibbe, you're an OS X person, aren't you? As this seems to involve an
 overlap of network and the new IO manager, would you be able to take a
 look please?

-- 
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/4449#comment:22>
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

Reply via email to