[Haskell-cafe] Trying to write a very simple HTTP Client

Robert Greayer robgreayer at yahoo.com
Fri May 23 10:59:53 EDT 2008


--- Eric <eeoam at ukfsn.org> wrote:

> Hi all,
> 
> I've written the following program to connect to a
> submit an HTTP GET 
> request to a server and print the response:
> 
> module Main where
> 
> import Network
> import System.IO
> 
> main = withSocketsDo go
> 
> go = do putStrLn "Connecting..."
>             out <- connectTo "haskell.org"
> (PortNumber 80)
>             hPutStrLn out "GET /\r"
>             hPutStrLn out "Host: haskell.org\r"
>             hPutStrLn out "\r"
>             cs    <- hGetLine out
>             hClose out
>             print cs
> 
> When I run the program, however, I get the following
> error:
> 
> HTTPClient: <socket: 1872>: hGetLine: end of file
> 
> Can anyone see what's wrong?
> 
> 
> E.

Try calling 'hFlush out' prior to the call to
hGetLine.   I believe the output to the socket is
buffered, so the receiver isn't seeing your GET
request, and eventually closes the connection on its
end, leading to the EOF on  the hGetLine.


> 
> _______________________________________________
> 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