
Hi, I'm using HTTP-3001.0.4 with GHC 6.8.3 under Mac OS X 10.5 and Debian Lenny. If I open and close many connections, I eventually get the error. Anyone else seen this before? *** Exception: socket: resource exhausted (Too many open files) Apparently, the socket is not closing. in TCP.hs:168, the call to shutdown is raising a "socket already closed" exception. So, the program never reaches the sClose on line 171. A simple fix is: wanderlust:Network arjun$ diff TCP.hs.original TCP.hs 172c172 < } ---
} `Exception.catch` (\_ -> sClose sk)
The code that demonstrates this problem on Mac OS X is:
module Main where
import Network.HTTP import Network.URI (parseURI) import Data.Maybe (fromJust) import Control.Monad
googleM n = do s <- simpleHTTP $ Request (fromJust $ parseURI "http://www.google.com ") GET [] "" when (n `mod` 100 == 0) $ putStrLn (show n) return ()
main = mapM_ googleM [1..5000]
On Debian Lenny, the code works fine with google.com. However, when I try to connect to my local CouchDB server, it throws an exception after roughly 1000 connections. Thanks. Arjun