[web-devel] Conduit/Wai proxy, HOWTO?
Jason Dusek
jason.dusek at gmail.com
Wed Aug 29 08:29:50 CEST 2012
Please find below my signature a sketch of a WAI proxy server,
which always redirects every request to the same URL.
In the sketch, the function `magic' takes care of translating
from a Network.HTTP.Conduit.Response body to
Network.Wai.ResponseSource body. However, I am a at a loss as to
how to write `magic' safely. The body of a
Network.HTTP.Conduit.Response is a ResumableSource but the body
of Network.Wai.ResponseSource is a plain source and the
conversion from one to the other would seem to involve one of:
* Connecting the ResumableSource to a Sink, thus regrettably
forcing it all into memory,
* Unwrapping the resumable source and trying to figure out
what to do with the finalizer.
I was originally attracted to Wai/Warp/Conduit by the prospect
of building a high quality proxy server. I am building an web
service that talks to AWS and, for some tasks, must proxy
results back to the user.
I would be very grateful if someone could explain to me how best
to put together a simple, efficient proxy server with Wai and
Conduit.
--
Jason Dusek
pgp // solidsnack // C1EBC57DC55144F35460C8DF1FD4C6C1FED18A2B
> {-# LANGUAGE OverloadedStrings
> , RecordWildCards
> #-}
>
> import Control.Applicative
> import Control.Monad
> import Data.ByteString (ByteString)
> import qualified Data.ByteString.Char8 as Bytes
>
> import qualified Blaze.ByteString.Builder as Blaze
> import qualified Blaze.ByteString.Builder.Char.Utf8 as Blaze
> import Control.Monad.Trans
> import qualified Data.Conduit as Conduit
> import qualified Data.Conduit.List as Conduit
> import qualified Network.Wai as Wai
> import qualified Network.HTTP.Conduit as Conduit
> import qualified Network.HTTP.Types as HTTP
>
> wai :: String -> Wai.Application
> wai s req at Wai.Request{..} = Conduit.withManager go
> where
> magic = undefined
> go manager = do
> request <- liftIO $ Conduit.parseUrl s
> Conduit.Response s _ h src <- Conduit.http request manager
> return $ Wai.ResponseSource s h (magic src)
More information about the web-devel
mailing list