Difference between revisions of "Simple Servers"

From HaskellWiki
Jump to navigation Jump to search
 
Line 78: Line 78:
   
 
<haskell>
 
<haskell>
  +
{-# 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 hiding (accept)
 
import Network.Socket (fdSocket, accept)
 
import Network.Socket (fdSocket, accept)

Revision as of 01:59, 18 January 2010

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

* Recent GHC
* Libraries: network, network-bytestring, event

Benchmarks with httperf,

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

Basic concurrent server

Concurrent, with String IO:

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)

{-# 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:

{-# 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.