[Haskell-cafe] hGetLine problem

Michael Walter michael.walter at gmail.com
Fri Dec 10 11:01:50 EST 2004


But if the forkIO'ed process terminates because of an exception, that
shouldn't influence the main process, right?

- Michael


On Fri, 10 Dec 2004 10:18:33 +0000, Keean Schupke
<k.schupke at imperial.ac.uk> wrote:
> What is happening is that the socket is closed after the accept
> but before the hGetLine, so the handle is invalid (there is no
> socket any more)... This is correct behaviour when the client
> closes the connection whilst you are writing to it...
> 
> The answer is just to catch the exception.
> 
>     Keean.
> 
> 
> 
> 
> Michael Walter wrote:
> 
> >Yep - this program "sometimes" fails for me with such an error message:
> >
> >  Fail: <socket: 8>: hGetLine: invalid argument (Invalid argument)
> >
> >If I omit the forkIO and do synchronous processing, I noticed that
> >Apache Benchmark connects a second time but closes the connection
> >immediately. When I added a `catch` \e -> mainLoop socket at the end
> >of the main loop, it worked fine.
> >
> >But when I reintroduced the forkIO, it seemed to be "hanging" in the
> >main process's accept (when the fork failed with above's error
> >message).
> >
> >Any ideas?
> >
> >Confusingly yours,
> >Michael
> >
> >
> >On Thu, 9 Dec 2004 14:29:10 -0500, Michael Walter
> ><michael.walter at gmail.com> wrote:
> >
> >
> >>Hello again,
> >>
> >>this test program should do the relevant parts for the bug -- on
> >>Windows it works fine, though, I'll have to check at home whether it's
> >>reproducable using it.
> >>
> >>- Michael
> >>
> >>module Test where
> >>
> >>import Control.Concurrent
> >>import Network
> >>import System.IO
> >>
> >>mainLoop socket = do
> >>        (handle, _, _) <- accept socket
> >>        forkIO $ do
> >>                line <- hGetLine handle
> >>                putStrLn line
> >>                hPutStrLn handle "HTTP/1.0 200 OK\r"
> >>                hPutStrLn handle "Content-Type: text/html\r"
> >>                hPutStrLn handle "\r"
> >>                hPutStrLn handle "Test\r"
> >>                hClose handle
> >>        mainLoop socket
> >>
> >>main = withSocketsDo $ listenOn (PortNumber 8000) >>= mainLoop
> >>
> >>
> >>
> >>
> >>On Thu, 9 Dec 2004 11:44:16 -0500, Michael Walter
> >><michael.walter at gmail.com> wrote:
> >>
> >>
> >>>I'll do so at lunch break/from home tonight.
> >>>
> >>>Thanks,
> >>>Michael
> >>>
> >>>
> >>>
> >>>
> >>>On Thu, 9 Dec 2004 16:19:20 +0000, Jules Bean <jules at jellybean.co.uk> wrote:
> >>>
> >>>
> >>>>On 9 Dec 2004, at 15:30, Michael Walter wrote:
> >>>>
> >>>>
> >>>>>I continued toying with my toy web server, and I'm "sometimes" getting
> >>>>>"Invalid argument" errors in hGetLine for a handle I retrieved from
> >>>>>Network.listenOn.
> >>>>>
> >>>>>
> >>>>>
> >>>>My first guess would be that hGetLine would return invalid argument if
> >>>>it was called on a handle which represents a file which is now closed.
> >>>>However, testing in GHCI suggests that returns "illegal operation
> >>>>(handle is closed)". Could be different for network sockets, I suppose.
> >>>>
> >>>>
> >>>>
> >>>>
> >>>>
> >>>>>"Sometimes", because it works fine in the browser, except when I
> >>>>>reload very frequently -- maybe it's related to some concurrency
> >>>>>issues (I'm using forkIO to spawn off the handler process from the
> >>>>>main server loop). When I wanted to benchmark the server using "ab"
> >>>>>(Apache Benchmark), it didn't even "survive" one request but Fail'ed
> >>>>>using that error message - "<handle: n>: hGetLine: Invalid argument".
> >>>>>
> >>>>>I tried adjusting the buffering mode.
> >>>>>
> >>>>>Do you have any ideas?
> >>>>>
> >>>>>
> >>>>>
> >>>>Sounds like a double-close error or something like that. Hard to say
> >>>>without seeing the code. Can you make a minimal example?
> >>>>
> >>>>Jules
> >>>>
> >>>>
> >>>>
> >>>>
> >_______________________________________________
> >Haskell-Cafe mailing list
> >Haskell-Cafe at haskell.org
> >http://www.haskell.org/mailman/listinfo/haskell-cafe
> >
> >
> 
>


More information about the Haskell-Cafe mailing list