
[Forwarding to Yesod's mailing list as well. I'll copy all of the
original text below for those who aren't on haskell-beginners.]
On Fri, Aug 31, 2012 at 11:24 AM, Lorenzo Bolla
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.
This is actually a rather tricky and interesting question =). My knee-jerk reaction is "profile!". Profiling will give you more clues about where the time is being spent. As Bryce said, you're using defaultLayout and Hamlet, which should slow things down. Also, you're implicitly using clientsession, you may try setting makeSessionBackend [1] to 'const $ return Nothing' and see what kind of performance you get. Cheers! [1] http://hackage.haskell.org/packages/archive/yesod-core/1.1.1.1/doc/html/Yeso... -- Felipe.