Simple Servers

From HaskellWiki
Revision as of 03:08, 18 January 2010 by DonStewart (talk | contribs)
Jump to navigation Jump to search
The printable version is no longer supported and may have rendering errors. Please update your browser bookmarks and please use the default browser print function instead.

Some example of simple web server designs using increasingly more sophisticated approaches. Requirements:

Some more context on the background to this problem is available.

Benchmarks with httperf,

   $ httperf --server=localhost --port=5002 --uri=/ --num-conns=10000

Author: dons

Results

Req/sec with different IO and event mechanisms

Basic concurrent server

Concurrent, with String IO. Here on each accept from the main thread, we create a new Handle, and forkIO a lightweight Haskell thread to write a string back to the client. Relies on the runtime scheduler to wake up the main thread in a timely fashion (i.e. via the current 'select' mechanism).

import Network
import Control.Concurrent
import System.IO

main = withSocketsDo $ do
    sock <- listenOn $ PortNumber 5002
    loop sock

loop sock = do
   (h,_,_) <- accept sock
   forkIO $ body h
   loop sock
  where
   body h = do
       hPutStr h msg
       hFlush h
       hClose h

msg = "HTTP/1.0 200 OK\r\nContent-Length: 5\r\n\r\nPong!\r\n"

Measurements:

  • $ ghc -O2 --make A.hs
  • Request rate: 6569.1 req/s (0.2 ms/req)

Concurrent, with network-bytestring

Now, using bytestring IO (via the network-bytestring package) (but still using the rts' select-based preemptive threads). Just means we allocate nothing in the body, and avoid a couple of copies to do the IO.

{-# LANGUAGE OverloadedStrings #-}

import Data.ByteString.Char8

import Network hiding (accept)
import Network.Socket
import Network.Socket.ByteString (sendAll)
import Control.Concurrent

main = withSocketsDo $ do
    sock <- listenOn $ PortNumber 5002
    loop sock

loop sock = do
   (conn, _) <- accept sock
   forkIO $ body conn
   loop sock
  where
   body c = do sendAll c msg
               sClose c

msg = "HTTP/1.0 200 OK\r\nContent-Length: 5\r\n\r\nPong!\r\n"

Measurements:

  • $ ghc -O2 --make H.hs
  • Request rate: 9901.7 req/s (0.1 ms/req)

Epoll-based event callbacks

Now, instead of using the RTS' select mechanism to wake up threads, we use a custom epoll handler. Using epoll-based event handling, and bytestring IO. The epoll approach will be replace GHC's select model soon (design here showing how the concurrent Haskell primitives may be implemented in terms of epoll).

{-# LANGUAGE OverloadedStrings #-}

-- A simple example of an epoll based http server in Haskell.
--
-- Uses two libraries:
--   * network-bytestring, bytestring-based socket IO.
--      - cabal install network-bytestring: 
--
--   * haskell-event, epoll-based scalable IO events
--      - git clone git://github.com/tibbe/event.git
--      - autoreconf ; then cabal install

import Network hiding (accept)
import Network.Socket (fdSocket, accept)
import Network.Socket.ByteString
import Data.ByteString.Char8
import System.Event
import System.Posix
import System.Posix.IO

main = withSocketsDo $ do
    sock <- listenOn $ PortNumber 5002
    let fd = fromIntegral (fdSocket sock)
    mgr <- new
    registerFd mgr (client sock) fd evtRead
    loop mgr

client sock _ _ = do
    (c,_) <- accept sock
    sendAll c msg
    sClose c

msg = "HTTP/1.0 200 OK\r\nContent-Length: 5\r\n\r\nPong!\r\n"

Measurements:

  • ghc -O2 --make Epoll.hs
  • Request rate: 15042.6 req/s (0.1 ms/req)

So significantly better.