[Haskell-beginners] Warp and Yesod benchmark puzzle
Bryce
bryceverdier at gmail.com
Fri Aug 31 19:14:06 CEST 2012
I'll admit to only recently starting to play with Yesod, but I'll take a
stab at what I think is going on. Someone else can agree or disagree
with my response later ;)
I believe that the slowness comes from the extra overhead of using more
libraries. getHomeR has to process text in hamlet before it can pass
that onto defaultLayout and forward from there. I believe you might be
able to speed things up by using RepPlain. I would try this instead:
getHomeR = return . RepPlain . toContent $ "Hello World"
and see if that improves your speed at all.
Also, you are running warp in debug mode. That might have something to
do with it as well.
Bryce
On 08/31/2012 07:24 AM, Lorenzo Bolla wrote:
> Hi all,
>
> This is a question specific to the Yesod framework, but simple enough
> (I hope) to be considered a beginner question...
>
> I am puzzled by the performance of these two very simple web-servers,
> one written in Warp and another written in Yesod:
>
> === YESOD ===
>
> {-# LANGUAGE TypeFamilies, QuasiQuotes, MultiParamTypeClasses,
> TemplateHaskell #-}
> import Yesod
>
> data HelloWorld = HelloWorld
>
> mkYesod "HelloWorld" [parseRoutes|
> / HomeR GET
> |]
>
> instance Yesod HelloWorld
>
> getHomeR :: Handler RepHtml
> getHomeR = defaultLayout [whamlet|$newline always
> Hello World!
> |]
>
> main :: IO ()
> -- main = warpDebug 3000 HelloWorld
> main = warp 3000 HelloWorld
>
> === WARP ===
>
> {-# LANGUAGE OverloadedStrings #-}
>
> import Network.Wai
> import Network.HTTP.Types
> import Network.Wai.Handler.Warp (run)
> import Data.ByteString.Lazy.Char8 ()
>
> app :: Application
> app _ = return $ responseLBS
> status200
> [("Content-Type", "text/html")]
> "Hello, Warp!"
>
> main :: IO ()
> main = do
> putStrLn "http://localhost:8080/"
> run 8080 app
>
> ===
>
> I've tested both using httperf:
> $> httperf --hog --client=0/1 --server=localhost --port=3000 --uri=/
> --rate=1000 --send-buffer=4096 --recv-buffer=16384 --num-conns=100
> --num-calls=100 --burst-length=20
>
> and I got very different results:
>
> YESOD: Request rate: 4048.0 req/s (0.2 ms/req)
> WARP: Request rate: 33656.2 req/s (0.0 ms/req)
>
> Now, I understand that Yesod is expected to be slower than the "raw"
> Warp, but I wasn't expecting a 10x slowdown, especially for such a
> trivial Yesod app (no db, no auth, etc.).
>
> [
> Compilation command was: ghc -Wall -O2 --make yesod.hs
> $ yesod version
> yesod-core version:1.1.0
> ]
>
> What is going on?
>
> Thanks,
> L.
>
> _______________________________________________
> Beginners mailing list
> Beginners at haskell.org
> http://www.haskell.org/mailman/listinfo/beginners
More information about the Beginners
mailing list