#3914: handleToFd closes Fd when Handle is GC'd
--------------------------+-------------------------------------------------
    Reporter:  danderson  |       Owner:                             
        Type:  bug        |      Status:  new                        
    Priority:  normal     |   Component:  libraries/base             
     Version:  6.10.4     |    Keywords:                             
          Os:  Linux      |    Testcase:                             
Architecture:  x86        |     Failure:  Incorrect result at runtime
--------------------------+-------------------------------------------------
 The following reproduction case creates a TCP server that will read
 forever from the first client that connects to it. Having a client do so
 (eg. with `cat /dev/urandom | nc localhost 4242`) will fairly rapidly
 cause the server to crash with a "Bad file descriptor" exception.

 {{{
 module Main where

 import Control.Monad(forever)
 import Network
 import System.IO
 import System.Posix.IO(fdToHandle, handleToFd)

 main = withSocketsDo $ do
     (hdl, _, _) <- listenOn (PortNumber 4242) >>= accept
     newHdl <- handleToFd hdl >>= fdToHandle
     forever $ hGetChar newHdl >>= putChar >> hFlush stdout
 }}}

 My hunch on the cause is that handleToFd doesn't let go of the underlying
 system file descriptor when it returns the Fd. Later, when the GC runs, it
 collects hdl and incorrectly closes the system fd, now in use by newHdl.

 An strace of the server binary confirms this sequence of events (shortened
 to the essentials, but the sequencing is as shown - 4 is the hdl/newHdl
 file descriptor):

 {{{
 ...
 select(5, [4], [], NULL, {134, 217727}) = 1 (in [4], left {134, 203169})
 ...
 close(4)                                = 0
 ...
 select(5, [4], [], NULL, {0, 0})        = -1 EBADF (Bad file descriptor)
 write(2, "Minimal: ", 9Minimal: )                = 9
 write(2, "<file descriptor: 4>: hGetChar: "..., 70<file descriptor: 4>:
 hGetChar: invalid argument (Bad file descriptor)) = 70
 }}}

 Running the binary with '+RTS -s' also shows that some GC passes did occur
 during the short lifetime of the program, further pointing the finger at
 incorrect collection of the system fd.

 While the reproduction recipe seems silly, the handleToFd >>= fdToHandle
 scenario is actually very useful when doing low level FFI. The real code
 where I hit this bug is
 http://bitbucket.org/danderson/tunskell/src/330b5edba1dc/Ioctl.hsc . I
 extract the Fd in order to make an ioctl() call, then return a new Handle
 of that Fd after the ioctl() finishes. Using this pattern, the code
 reading from that tweaked Handle dies after the first GC pass.

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