[web-devel] ResponseEnumerator

Michael Snoyman michael at snoyman.com
Tue Dec 13 08:42:51 CET 2011


On Tue, Dec 13, 2011 at 9:37 AM, Kazu Yamamoto <kazu at iij.ad.jp> wrote:
> Hello,
>
> I have a question about WAI. ResponseEnumerator is defined as:
>
> type ResponseEnumerator a = (Status -> ResponseHeaders -> Iteratee Builder IO a) -> IO a
>
> Are there any reasons to use Builder instead of ByteString.
> I could not find code which makes use of Iteratee Builder IO a in Yesod.
>
> Michael posted the following code before. This code converts ByteString
> to Builder. But Builder is converted to ByteString in Warp.
>
> It seems to me that "Iteratee ByteString IO a" is more reasonable than
> "Iteratee ByteString IO a". Am I missing something?
>
> --Kazu
>
> ----
> data Proxy = Proxy
>
> mkYesod "Proxy" [parseRoutes|
> / RootR GET
> |]
>
> instance Yesod Proxy where
>    approot _ = ""
>
> getRootR :: GHandler Proxy Proxy ()
> getRootR = do
>    req <- liftIO $ parseUrl "http://www.yesodweb.com/"
>    sendWaiResponse $ ResponseEnumerator $ \f -> withManager $ \m ->
>        run_ (http req (blaze f) m)
>
> blaze :: (Status -> ResponseHeaders -> Iteratee Builder IO a)
>      -> Status -> ResponseHeaders -> Iteratee ByteString IO a
> blaze f s h =
>    joinI $ EL.map fromByteString $$ f s h'
>  where
>    h' = filter go h
>    go ("Content-Encoding", _) = False
>    go _ = True
>
> main :: IO ()
> main = warpDebug 3000 Proxy
> ----
>
> _______________________________________________
> web-devel mailing list
> web-devel at haskell.org
> http://www.haskell.org/mailman/listinfo/web-devel

It's a good question. The advantage of a Builder is that we get cheap
concatenation, so you can create a stream of smaller ByteStrings and
then Warp will automatically concatenate them together into larger
chunks. There are a few claims against this:

Q1. Shouldn't it be at the user's discretion to use Builders
internally and then create a stream of ByteStrings?
A1. That would be less efficient, as we wouldn't get cheap
concatenation with the response headers.

Q2. Isn't it really inefficient to convert from ByteString to Builder,
and then right back to ByteString?
A2. No. If the ByteStrings are small, then they will be copied into a
larger buffer, which should be a performance gain overall (less system
calls). If they are already large, then blaze-builder uses an
InsertByteString instruction to avoid copying.

Q3. Doesn't this prevent us from creating comet-style servers, since
data will be cached?
A3. You can force blaze-builder to output a ByteString before it is an
optimal size by sending a flush command.

If these answers make sense, I'll add them to the WAI docs.

Michael



More information about the web-devel mailing list