[Haskell-beginners] Download a large file using Network.HTTP

Felipe Almeida Lessa felipe.lessa at gmail.com
Mon Dec 10 14:50:02 CET 2012


And here's the guy who's http-conduit's maintainer =).  The only thing
I said that he didn't is that you may take the total size from the
response headers, but you may do this over his code.

Cheers,

On Mon, Dec 10, 2012 at 11:46 AM, Michael Snoyman <michael at snoyman.com> wrote:
> Here's an example of printing the total number of bytes consumed using
> http-conduit:
>
> import           Control.Monad.IO.Class (liftIO)
> import qualified Data.ByteString        as S
> import           Data.Conduit
> import           Data.Conduit.Binary    as CB
> import           Network.HTTP.Conduit
>
> main :: IO ()
> main = withManager $ \manager -> do
>     req <- parseUrl "http://www.yesodweb.com/"
>     res <- http req manager
>     responseBody res $$+- printProgress =$ CB.sinkFile "yesodweb.html"
>
> printProgress :: Conduit S.ByteString (ResourceT IO) S.ByteString
> printProgress =
>     loop 0
>   where
>     loop len = await >>= maybe (return ()) (\bs -> do
>         let len' = len + S.length bs
>         liftIO $ putStrLn $ "Bytes consumed: " ++ show len'
>         yield bs
>         loop len')
>
>
> HTH,
> Michael
>
>
> On Mon, Dec 10, 2012 at 3:34 PM, Cedric Fung <root at vec.io> wrote:
>>
>> Hi,
>>
>> Are there any suggestions to download a large file with Haskell? I have
>> read the docs for Network, Network.HTTP and Network.HTTP.Conduit, but can't
>> find anything which fit my requirements.
>>
>> I want to download a large file from an HTTP URL, and show the progress
>> instantly. Maybe some functions which read HTTP connection and return a lazy
>> ByteString could do this work?
>>
>> Though I found a low-level socket lazy package, which seems to work, I
>> just want a more high level API.
>>
>> Thanks and regards.
>>
>> _______________________________________________
>> Beginners mailing list
>> Beginners at haskell.org
>> http://www.haskell.org/mailman/listinfo/beginners
>>
>
>
> _______________________________________________
> Beginners mailing list
> Beginners at haskell.org
> http://www.haskell.org/mailman/listinfo/beginners
>



-- 
Felipe.



More information about the Beginners mailing list