
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.

Hey!
It's probably going to be easier to use http-conduit. As the docs of
httpLbs say,
If you want more power, such as interleaved actions on the
response body during download, you'll need to use 'http' directly.
So you'll need to use the 'http' function. On the response headers
you'll find the total size of the download. With that size in hand,
you may implement a Conduit (from the conduit package)
type TotalSize = Int
findTotalSize :: ResponseHeaders -> Maybe TotalSize
showProgress :: MonadIO m => Maybe TotalSize -> Conduit ByteString
m ByteString
All data will pass through this conduit, so it may just keep track of
how many bytes it has seen already and show the progress while
returning the data itself unaltered. Then you'll just need a Sink
that saves the file (e.g. sinkFile from Data.Conduit.Binary) and to
connect everything, e.g.
res <- http request manager
let mtotalSize = findTotalSize (responseHeaders res)
responseBody res $= showProgress mtotalSize $$ sinkFile "output"
Cheers,
On Mon, Dec 10, 2012 at 11:34 AM, Cedric Fung
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@haskell.org http://www.haskell.org/mailman/listinfo/beginners
-- Felipe.

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
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@haskell.org http://www.haskell.org/mailman/listinfo/beginners

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
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
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@haskell.org http://www.haskell.org/mailman/listinfo/beginners
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners
-- Felipe.

It's so amazing to receive your help. I have just learnt Haskell for about 1 week, wish I could handle it soon. The Haskell community is small (at least smaller than the Ruby's) but full of kindly people. On Mon, Dec 10, 2012 at 9:50 PM, Felipe Almeida Lessa < felipe.lessa@gmail.com> wrote:
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
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
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@haskell.org http://www.haskell.org/mailman/listinfo/beginners
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners
-- Felipe.

Wow, thanks to Felipe's and Michael's quick response. Haskell community is
so kind.
I will try your suggestions right now!
On Mon, Dec 10, 2012 at 9:46 PM, Michael Snoyman
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
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@haskell.org http://www.haskell.org/mailman/listinfo/beginners
participants (3)
-
Cedric Fung
-
Felipe Almeida Lessa
-
Michael Snoyman