Re: [Haskell-cafe] Wai and http-enumerator not as lazy as I'd like

2011-05-01 Thread Erik de Castro Lopo
Michael Snoyman wrote:

 On Fri, Apr 29, 2011 at 2:49 AM, Erik de Castro Lopo

  Has anyone done anything like this and care to shed some light?
 
 It's a little bit complicated, but hopefully this should help out:

Thats Michael. I've tried it and it works. Now to study it
and figure out how :-)
 
Cheers,
Erik
-- 
--
Erik de Castro Lopo
http://www.mega-nerd.com/

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Wai and http-enumerator not as lazy as I'd like

2011-04-29 Thread Michael Snoyman
On Fri, Apr 29, 2011 at 2:49 AM, Erik de Castro Lopo
mle...@mega-nerd.com wrote:
 Antoine Latter wrote:

 None of the lbs functions in http-enumerator can operate in constant
 space - they are all built on top of the utility function lbsIter
 which provides a warning:

  Convert the HTTP response into a Response value.
 
  Even though a Response contains a lazy bytestring, this function does not 
  utilize lazy
  I/O, and therefore the entire response body will live in memory. If you 
  want constant 
  memory usage, you'll need to write your own iteratee and use http or 
  httpRedirect
  directly.

 Thanks Antoine. I know I read the documention a number of times
 but still managed to fall into that trap. I think it was because
 I tired using httpDirect, couldn't figure it out and then fell
 back to using the non-lazy lbs version.

 Basically I need a serveRequest function with a signature:

     import qualified Network.HTTP.Enumerator     as HE
     import qualified Network.Wai                 as Wai

     serveRequest :: (MonadControlIO m, Failure HE.HttpException m) =
                         HE.Request m - m Wai.Response

 that calls httpRedirect to do a lazy download of the specified data and
 returns it as a Wai.Response using the ResponseEnumerator constructor.

 Unfortunately, I've tried a bunch if stuff and nothing I've come up with
 even comes close t type checking.

 Has anyone done anything like this and care to shed some light?

It's a little bit complicated, but hopefully this should help out:


import qualified Network.Wai as Wai
import qualified Network.Wai.Handler.Warp as Warp
import qualified Network.HTTP.Enumerator as HTTP
import Control.Monad.IO.Class (liftIO)
import Data.Maybe (fromJust)
import qualified Data.Enumerator as Enum
import qualified Data.Enumerator.List as EnumList
import Data.Enumerator ((=$))
import Blaze.ByteString.Builder (fromByteString)

main :: IO ()
main = Warp.run 3000 app

app :: Wai.Application
app _ = liftIO $ HTTP.withManager $ \m - return $
Wai.ResponseEnumerator $ \f -
Enum.run_ $ HTTP.httpRedirect myReq (toBuilder f) m
  where
toBuilder f a b = EnumList.map fromByteString =$ f a b

myReq :: HTTP.Request m
myReq = fromJust $ HTTP.parseUrl http://www.yesodweb.com/;

Michael

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Wai and http-enumerator not as lazy as I'd like

2011-04-28 Thread Erik de Castro Lopo
Antoine Latter wrote:

 None of the lbs functions in http-enumerator can operate in constant
 space - they are all built on top of the utility function lbsIter
 which provides a warning:
 
  Convert the HTTP response into a Response value.
 
  Even though a Response contains a lazy bytestring, this function does not 
  utilize lazy
  I/O, and therefore the entire response body will live in memory. If you 
  want constant 
  memory usage, you'll need to write your own iteratee and use http or 
  httpRedirect
  directly.

Thanks Antoine. I know I read the documention a number of times
but still managed to fall into that trap. I think it was because
I tired using httpDirect, couldn't figure it out and then fell
back to using the non-lazy lbs version.

Basically I need a serveRequest function with a signature:

    import qualified Network.HTTP.Enumerator     as HE
    import qualified Network.Wai                 as Wai

 serveRequest :: (MonadControlIO m, Failure HE.HttpException m) =
            HE.Request m - m Wai.Response

that calls httpRedirect to do a lazy download of the specified data and
returns it as a Wai.Response using the ResponseEnumerator constructor.

Unfortunately, I've tried a bunch if stuff and nothing I've come up with
even comes close t type checking.

Has anyone done anything like this and care to shed some light?

Cheers,
Erik
-- 
--
Erik de Castro Lopo
http://www.mega-nerd.com/

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Wai and http-enumerator not as lazy as I'd like

2011-04-26 Thread Antoine Latter
On Tue, Apr 26, 2011 at 7:27 AM, Erik de Castro Lopo
mle...@mega-nerd.com wrote:
 Hi all,

 I'm using Wai and http-enumerator to build a http proxy. The core of
 the code looks like this:

    import qualified Network.HTTP.Enumerator     as HE
    import qualified Network.Wai                 as Wai

    serveRequest :: forall (m :: * - *).
             (MonadControlIO m, Failure HE.HttpException m) =
             HE.Request m - m Wai.Response
    serveRequest request
     = do   HE.Response sc rh bs - HE.withManager $ HE.httpLbsRedirect request
            return $ Wai.responseLBS (mkStatus sc) rh bs

 This works but does not run in constant space as I would have hoped.
 The thing is, HE.httpLbsRedirect returns a lazy ByteString and
 Wai.responseLBS writes a lazy ByteString, so why isn't the whole thing
 lazy?


None of the lbs functions in http-enumerator can operate in constant
space - they are all built on top of the utility function lbsIter
which provides a warning:

 Convert the HTTP response into a Response value.

 Even though a Response contains a lazy bytestring, this function does not 
 utilize lazy
 I/O, and therefore the entire response body will live in memory. If you want 
 constant 
 memory usage, you'll need to write your own iteratee and use http or 
 httpRedirect
 directly.

See:

http://hackage.haskell.org/packages/archive/http-enumerator/0.6.0.2/doc/html/Network-HTTP-Enumerator.html#g:4

It might be good to have this warning on the functions that use
lbsIter, or have them use ByteStrings instead of Lazy ByteStrings.

Antoine

 I'd appreciate any clues.

 Cheers,
 Erik
 --
 --
 Erik de Castro Lopo
 http://www.mega-nerd.com/

 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe