[Haskell-cafe] Simple HTTP lib for Windows?
Neil Mitchell
ndmitchell at gmail.com
Thu Jan 18 05:26:21 EST 2007
Hi,
I've often wondered the same as the above poster. Something like
readWebPage (in the same style as readFile) would be a really handy
function. Do no libraries provide this?
(if not, can one start providing it? MissingH?)
Thanks
Neil
On 1/18/07, Alistair Bayley <alistair at abayley.org> wrote:
> > I'd like to write a very simple Haskell script that when given a URL, looks
> > up the page, and returns a string of HTML. I don't see an HTTP library in
> > the standard libs, and the one in Hackage requires Windows machines have GHC
> > and MinGW to be installed and in the PATH.
> >
> > Is there a simple way to get the contents of a webpage using Haskell on a
> > Windows box?
>
> This isn't exactly what you want, but it gets you partway there. Not
> sure if LineBuffering or NoBuffering is the best option. Line
> buffering should be fine for just text output, but if you request a
> binary object (like an image) then you have to read exactly the number
> of bytes specified, and no more.
>
> Alistair
>
> module Main where
>
> import System.IO
> import Network
>
> main = client "www.haskell.org" 80 "/haskellwiki/Haskell"
>
> client server port page = do
> h <- connectTo server (PortNumber port)
> hSetBuffering h NoBuffering
> putStrLn "send request"
> hPutStrLn h ("GET " ++ page ++ "\r")
> hPutStrLn h "\r"
> hPutStrLn h "\r"
> putStrLn "wait for response"
> readResponse h
> putStrLn ""
>
> readResponse h = do
> closed <- hIsClosed h
> eof <- hIsEOF h
> if closed || eof
> then return ()
> else do
> c <- hGetChar h
> putChar c
> readResponse h
> _______________________________________________
> 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