
#13497: GHC does not use select()/poll() correctly on non-Linux platforms -------------------------------------+------------------------------------- Reporter: nh2 | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Runtime System | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: 8684 Related Tickets: #8684, #12912 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by nh2): When testing my change on Windows, I found that the `if (isSock){ select(...) }` part seems completely 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 [https://github.com/nh2/ghc-socket- test/blob/af74bb348e88f3f7ca717c70540936fea1293257/ghc-socket-test.hs this] (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? It seems an approriate workaround for now is to increase `FD_SETSIZE` (which is possible on Windows and BSD, see [https://stackoverflow.com/questions/7976388/increasing-limit-of-fd- setsize-and-select here]) on Windows. A real fix would be to move to IO Completion Ports, and thus get rid of the last use of `select()` (the other platforms already use `poll()` but Windows doesn't have that). -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13497#comment:23 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler