
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.

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@haskell.org http://www.haskell.org/mailman/listinfo/beginners

[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.

On Fri, Aug 31, 2012 at 10:13:20PM -0300, Felipe Almeida Lessa wrote:
[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
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.
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.
Good catch Felipe! It looks like `makeSessionBackend` is horribly slow... These are the numbers on my box: Warp 10250 req/s Yesod hamlet: 848 req/s no-hamlet: 940 req/s (getHomeR = return ∘ RepPlain ∘ toContent $ "Hello World!") no-session: 8000 req/s (makeSessionBackend = const $ return Nothing) L. -- Lorenzo Bolla http://lbolla.info

makeSessionBackend calls "getKey" from clientsession: http://hackage.haskell.org/packages/archive/clientsession/0.8.0/doc/html/src... Looking at that function no wonder it is a bottleneck: -- | Get a key from the given text file.---- If the file does not exist or is corrupted a random key will-- be generated and stored in that file.getKey :: FilePath -- ^ File name where key is stored. -> IO Key -- ^ The actual key.getKey keyFile = do exists <- doesFileExist keyFile if exists then S.readFile keyFile
= either (const newKey) return . initKey else newKey where newKey = do (bs, key') <- randomKey S.writeFile keyFile bs return key'
Plenty of syscalls, reading and parsing the same file over and over again.
Perhaps the default should be to store the key within the foundation
datatype at startup?
Best regards,
Krzysztof Skrzętnicki
On Sat, Sep 1, 2012 at 10:37 AM, Lorenzo Bolla
On Fri, Aug 31, 2012 at 10:13:20PM -0300, Felipe Almeida Lessa wrote:
[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
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.
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.
Good catch Felipe! It looks like `makeSessionBackend` is horribly slow... These are the numbers on my box:
Warp 10250 req/s
Yesod hamlet: 848 req/s no-hamlet: 940 req/s (getHomeR = return ∘ RepPlain ∘ toContent $ "Hello World!") no-session: 8000 req/s (makeSessionBackend = const $ return Nothing)
L.
-- Lorenzo Bolla http://lbolla.info
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners

On Sat, Sep 1, 2012 at 6:33 AM, Krzysztof Skrzętnicki
makeSessionBackend calls "getKey" from clientsession:
http://hackage.haskell.org/packages/archive/clientsession/0.8.0/doc/html/src...
Looking at that function no wonder it is a bottleneck:
-- | Get a key from the given text file. -- -- If the file does not exist or is corrupted a random key will -- be generated and stored in that file. getKey :: FilePath -- ^ File name where key is stored. -> IO Key -- ^ The actual key. getKey keyFile = do exists <- doesFileExist keyFile if exists then S.readFile keyFile >>= either (const newKey) return . initKey else newKey where newKey = do (bs, key') <- randomKey S.writeFile keyFile bs return key'
Plenty of syscalls, reading and parsing the same file over and over again. Perhaps the default should be to store the key within the foundation datatype at startup?
Unfortunately it's not so simple: makeSessionBackend is called just once by 'toWaiAppPlain', which is in turn called just once when your application starts. Cheers, =) -- Felipe.

On Sat, Sep 01, 2012 at 11:20:06AM -0300, Felipe Almeida Lessa wrote:
On Sat, Sep 1, 2012 at 6:33 AM, Krzysztof Skrzętnicki
wrote: makeSessionBackend calls "getKey" from clientsession:
http://hackage.haskell.org/packages/archive/clientsession/0.8.0/doc/html/src...
Looking at that function no wonder it is a bottleneck:
-- | Get a key from the given text file. -- -- If the file does not exist or is corrupted a random key will -- be generated and stored in that file. getKey :: FilePath -- ^ File name where key is stored. -> IO Key -- ^ The actual key. getKey keyFile = do exists <- doesFileExist keyFile if exists then S.readFile keyFile >>= either (const newKey) return . initKey else newKey where newKey = do (bs, key') <- randomKey S.writeFile keyFile bs return key'
Plenty of syscalls, reading and parsing the same file over and over again. Perhaps the default should be to store the key within the foundation datatype at startup?
Unfortunately it's not so simple: makeSessionBackend is called just once by 'toWaiAppPlain', which is in turn called just once when your application starts.
Cheers, =)
-- Felipe.
I wonder if the problem is rather the `decrypt`ion of the _SESSION cookie at each request, in which case the bottleneck is the encryption library (AES?). L. -- Lorenzo Bolla http://lbolla.info

On Sat, Sep 1, 2012 at 11:55 AM, Lorenzo Bolla
I wonder if the problem is rather the `decrypt`ion of the _SESSION cookie at each request, in which case the bottleneck is the encryption library (AES?).
I'm trying to test right now what happens to the performance when I change (pseudo-code) save = encrypt . encode load = decode . decrypt to just save = encode load = decode The clientsession library does not encode or decode the data and it's pretty fast. Maybe not fast enough, though =). Cheers, -- Felipe.

Just in case someone is following along this thread just on the mailing list, I've done some analysis on the GitHub issue (https://github.com/yesodweb/yesod/issues/415). Since it's easier to have an archive of the discussion there, I'd like to welcome anyone to bring your comments to GitHub =). Cheers, -- Felipe.
participants (4)
-
Bryce
-
Felipe Almeida Lessa
-
Krzysztof Skrzętnicki
-
Lorenzo Bolla