[Wai] Sending partial files

Hi all, Is there a way to send a part of a file in response to a request using WAI? I'm assuming it's possible, but I'm having a little trouble figuring out the type signatures in Network.Wai. I think I'll be able to adapt the Data.Enumerator.Binary.enumFile and enumHandle functions to handle a range, so I guess the question is really: How can I send a status + headers + arbitrary output from an enumerator in WAI? Cheers,

On Wed, Feb 2, 2011 at 7:05 PM, Bardur Arantsson
Hi all,
Is there a way to send a part of a file in response to a request using WAI? I'm assuming it's possible, but I'm having a little trouble figuring out the type signatures in Network.Wai.
I think I'll be able to adapt the Data.Enumerator.Binary.enumFile and enumHandle functions to handle a range, so I guess the question is really: How can I send a status + headers + arbitrary output from an enumerator in WAI?
Here's the short answer: {-# LANGUAGE OverloadedStrings #-} import Network.Wai import Network.Wai.Handler.Warp (run) import Data.Enumerator (run_, enumList, ($$)) import Blaze.ByteString.Builder (copyByteString) main = run 3000 $ const $ return $ ResponseEnumerator $ \f -> run_ $ enumList 1 (map copyByteString ["Hello", " ", "World"]) $$ f status200 [("Content-Type", "text/plain")] Obviously in your case, you wouldn't want to use enumList, but your enumFile/enumHandle code instead. Let's break that out a little bit with some type signatures and some comments: -- Stock standard main :: IO () main = run 3000 app -- An application that always returns the same response app :: Application app _ = return res -- Our constant response: remember the type sig of the ResponseEnumerator data -- constructor: -- -- ResponseEnumerator :: ResponseEnumerator a -> Response -- -- where -- -- type ResponseEnumerator a = (Status -> ResponseHeaders -> Iteratee Builder IO a) -> IO a res :: Response res = ResponseEnumerator resE resE :: ResponseEnumerator a -- resE :: (Status -> ResponseHeaders -> Iteratee Builder IO a) -> IO a resE genIter = -- this is just standard code to apply an enumerator to an iteratee and -- then run the whole thing run_ $ enum $$ iter where -- our enumerator, you'll want something more intelligent enum = enumList 1 $ map copyByteString ["Hello", " ", "World"] -- And the tricky part. The argument to our ResponseEnumerator is in fact -- an iteratee-generating function. Given a status and some response -- headers, it gives you back an iteratee that will send code to the -- client. iter = genIter status200 [("Content-Type", "text/plain")] Let me know if you have any questions. Michael

On 2011-02-02 18:44, Michael Snoyman wrote:
On Wed, Feb 2, 2011 at 7:05 PM, Bardur Arantsson
wrote: Hi all,
Is there a way to send a part of a file in response to a request using WAI? I'm assuming it's possible, but I'm having a little trouble figuring out the type signatures in Network.Wai.
I think I'll be able to adapt the Data.Enumerator.Binary.enumFile and enumHandle functions to handle a range, so I guess the question is really: How can I send a status + headers + arbitrary output from an enumerator in WAI?
Here's the short answer:
[--snip--] Thanks for the very thorough explanation -- hopefully it'll help in getting WAI/enumerators to "click". I'll give it another go during the weekend. Cheers, Bárður
participants (2)
-
Bardur Arantsson
-
Michael Snoyman