[GHC] #13525: hWaitForInput with timeout causes program to abort

GHC ghc-devs at haskell.org
Tue Sep 19 21:55:20 UTC 2017


#13525: hWaitForInput with timeout causes program to abort
----------------------------------+--------------------------------------
        Reporter:  bgamari        |                Owner:  (none)
            Type:  bug            |               Status:  closed
        Priority:  highest        |            Milestone:  8.2.1
       Component:  Compiler       |              Version:  8.0.2
      Resolution:  fixed          |             Keywords:
Operating System:  Linux          |         Architecture:  x86_64 (amd64)
 Type of failure:  Runtime crash  |            Test Case:
      Blocked By:                 |             Blocking:  8684
 Related Tickets:  #12912, #8684  |  Differential Rev(s):  Phab:D3473
       Wiki Page:                 |
----------------------------------+--------------------------------------

Comment (by Ben Gamari <ben@…>):

 In [changeset:"ba4dcc7cb77a37486368911fec854d112a1db93c/ghc"
 ba4dcc7c/ghc]:
 {{{
 #!CommitTicketReference repository="ghc"
 revision="ba4dcc7cb77a37486368911fec854d112a1db93c"
 base: Make it less likely for fdReady() to fail on Windows sockets.

 See the added comment for details.

 It's "less likely" because it can still fail if the socket happens to
 have an FD larger than 1023, which can happen if many files are opened.

 Until now, basic socket programs that use `hWaitForInput` were broken on
 Windows.

 That is because on Windows `FD_SETSIZE` defaults to 64, but pretty much
 all GHC programs seem to have > 64 FDs open, so you can't actually
 create a socket on which you can `select()`.

 It errors with `fdReady: fd is too big` even with an example as simple
 as the following (in this case, on my machine the `fd` is `284`):

   {-# LANGUAGE OverloadedStrings #-}

   import Control.Monad (forever)
   import Network.Socket
   import System.IO

   -- Simple echo server: Reads up to 10 chars from network, echoes them
 back.
   -- Uses the Handle API so that `hWaitForInput` can be used.
   main :: IO ()
   main = do
     sock <- socket AF_INET Stream 0
     setSocketOption sock ReuseAddr 1
     bind sock (SockAddrInet 1234 0x0100007f)
       -- 0x0100007f == 127.0.0.1 localhost
     listen sock 2
     forever $ do
       (connSock, _connAddr) <- accept sock
       putStrLn "Got connection"

       h <- socketToHandle connSock ReadWriteMode
       hSetBuffering h NoBuffering

       ready <- hWaitForInput h (5 * 1000) -- 5 seconds
       putStrLn $ "Ready: " ++ show ready

       line <- hGetLine h
       putStrLn "Got line"
       hPutStrLn h ("Got: " ++ line)
       hClose h

 I'm not sure how this was not discovered earlier; for #13525 (where
 `fdReady()` breaking completely was also discovered late) at least it
 failed only when the timeout was non-zero, which is not used in ghc
 beyond in `hWaitForInput`, but in this Windows socket case it breaks
 even on the 0-timeout.

 Maybe there is not actually anybody who uses sockets as handles on
 Windows?

 The workaround for now is to increase `FD_SETSIZE` on Windows;
 increasing it is possible on Windows and BSD, see

 https://stackoverflow.com/questions/7976388/increasing-limit-of-fd-setsi
 ze-and-select

 A real fix would be to move to IO Completion Ports on Windows, and thus
 get rid of the last uses of `select()` (the other platforms already use
 `poll()` but Windows doesn't have that).

 Reviewers: bgamari, austin, hvr, erikd, simonmar

 Reviewed By: bgamari

 Subscribers: rwbarton, thomie

 Differential Revision: https://phabricator.haskell.org/D3959
 }}}

-- 
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/13525#comment:11>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler


More information about the ghc-tickets mailing list