[Haskell-cafe] Downloading web page in Haskell
Don Stewart
dons at galois.com
Sat Nov 20 15:47:52 EST 2010
michael:
> 2010/11/20 José Romildo Malaquias <j.romildo at gmail.com>:
> > In order to download a given web page, I wrote the attached program. The
> > problem is that the page is not being full downloaded. It is being
> > somehow intettupted.
> >
> > Any clues on how to solve this problem?
>
> My guess is that there's a character encoding issue. Another approach
> would be using the http-enumerator package[1]. The equivalent program
> is:
>
> module Main where
>
> import Network.HTTP.Enumerator (simpleHttp)
> import qualified Data.ByteString.Lazy as L
>
> main =
> do src <- simpleHttp
> "http://www.adorocinema.com/common/search/search_by_film/?criteria=Bourne"
> L.writeFile "test.html" src
> L.putStrLn src
>
FWIW, with this url, I get the same problem using the Curl package (via the download-curl):
import Network.Curl.Download
import qualified Data.ByteString as B
main = do
edoc <- openURI "http://www.adorocinema.com/common/search/search_by_film/?criteria=Bourne"
case edoc of
Left err -> print err
Right doc -> B.writeFile "test.html" doc
Not a problem on e.g. http://haskell.org
-- Don
More information about the Haskell-Cafe
mailing list