[Haskell-cafe] Unwanted http-conduit buffering of chunked request body?

Michael Snoyman michael at snoyman.com
Wed Oct 30 03:54:51 UTC 2013


On Wed, Oct 30, 2013 at 4:18 AM, Manuel Gómez <targen at gmail.com> wrote:

> Hi list,
>
> I’ve been playing with http-conduit in an attempt to do some manual
> testing on a HTTP service, and I ran into something I had not
> expected.  I was trying to set up a POST request with a chunked
> request body from a conduit.  The following code does work:
>
> > {-# LANGUAGE OverloadedStrings #-}
> >
> > import Blaze.ByteString.Builder.ByteString (fromByteString)
> > import Control.Concurrent (threadDelay)
> > import Control.Monad.IO.Class (liftIO)
> > import Control.Monad.Trans.Resource (runResourceT)
> > import Data.ByteString (getLine)
> > import Data.Conduit (yield)
> > import Network.HTTP.Conduit (RequestBody(RequestBodySourceChunked),
> http, method, parseUrl, rawBody, requestBody, withManager)
> >
> > source = do say "a"; wait; say "b"; wait; say "c"
> >
> > wait = liftIO $ threadDelay 1000000
> > say = yield . fromByteString
> >
> > main = runResourceT $ do
> >   req <- parseUrl "http://localhost:12345/"
> >   withManager $ http req
> >     { method = "POST"
> >     , requestBody = RequestBodySourceChunked source
> >     }
>
> The important part is the `source` conduit: it yields a string, waits
> for a bit, yields another, waits for a bit, and yields again.  I
> expected this to send chunks as soon as the source yielded them.
> However, it seems to be sending all the chunks together at the end,
> when the source finishes.
>
> Doing the same thing without `wait`, and with `forever` as opposed to
> just sending three bits of string, seems to work closer to my
> expectations: it seems to buffer for a bit, then it sends what was
> buffered, then it buffers some more, and so on.
>
> Is this http-conduit or Blaze doing undesired buffering?  A quick run
> on `strace` seems to indicate it’s only doing the `send` system call
> every once in a while, so the buffering seems to be happening inside
> Haskell.
>
> I’m not even sure this is how the HTTP chunked transfer encoding is
> meant to be used — my actual use case has to do with sending
> potentially large files and hopefully using constant memory at the
> other end, but I’m also curious about using this to send asynchronous
> events and such.  Is this how it’s supposed to work?
>

In order to get the behavior you're looking for, you need to flush the
Builders to cause the buffers to be emptied. The important change is to
your say function:

say :: Monad m => ByteString -> Source m Builder
say bs = yield (fromByteString bs <> flush)

I've set this up as a SoH tutorial as well:
https://www.fpcomplete.com/user/snoyberg/random-code-snippets/http-conduit-buffering-tutorial

Michael
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://www.haskell.org/pipermail/haskell-cafe/attachments/20131030/1b5a59d6/attachment.html>


More information about the Haskell-Cafe mailing list