[web-devel] HTTP Status with Streaming Request Bodies

Mark Fine mark.fine at gmail.com
Mon Feb 29 06:49:49 UTC 2016


Looking through the code and experimenting, using the 'Expect:
100-continue' header resulted in the desired behavior - having the response
headers checked before the request body was streamed.

Mark

On Sun, Feb 28, 2016 at 2:20 PM, Mark Fine <mark.fine at gmail.com> wrote:

> I'm running into a problem handling requests with streaming request bodies
> that fail - using http-client, the failure takes a long time (potentially
> never) to propagate. Simple code (runnable project here
> <https://github.com/mfine/streamy>):
>
> {-# LANGUAGE OverloadedStrings #-}
>
> import Control.Monad
> import Data.Conduit.Combinators
> import Network.HTTP.Conduit
> import System.Environment
>
> a :: IO ()
> a = do
>   manager <- newManager tlsManagerSettings
>   request <- parseUrl "http://httpbin.org/status/409"
>   void $ httpLbs request manager
>
> b :: IO ()
> b = do
>   manager <- newManager tlsManagerSettings
>   request <- parseUrl "http://httpbin.org/status/409"
>   void $ flip httpLbs manager request
>     { requestBody = requestBodySourceChunked $ repeatM $ return "a"
>     }
>
> Running "a" above works as expected (propagating the error immediately).
> Running "b" has variable results, mostly never propagating the error.
> Looking at the wire, I can see that the 409 status comes back, but the
> exception does not propagate.
>
> Is there something I can do here to get quicker failure? Thanks!
>
> Mark
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/web-devel/attachments/20160228/d2d8520a/attachment.html>


More information about the web-devel mailing list