[Haskell-cafe] benchmarking c/c++ and haskell

Vo Minh Thu noteed at gmail.com
Sun Sep 12 07:13:02 EDT 2010


Hi,

I would like to benchmark C/C++ and Haskell code. The goal is to
improve the Haskell port[0] of smallpt[1].

To make sure my approach was reliable, I got the code of two programs
(one in C, the other in Haskell) from a post[2] by Don. The code is
reproduced below. When timing the execution of both program, I have a
>4x difference. It is said on the blog the programs should have
similar performance.

I simply don't get the reason of such a difference. I've tried the
code on my Atom netbook and also on an older centrino machine. The
timing are similar (i.e. the C and Haskell program show >4x
difference). Both machines have GHC 6.12.1 on Linux.

Would you have an idea?

[0] http://hackage.haskell.org/package/smallpt-hs
[1] http://www.kevinbeason.com/smallpt/
[2] http://donsbot.wordpress.com/2008/06/04/haskell-as-fast-as-c-working-at-a-high-altitude-for-low-level-performance/



$ gcc -O2 mean.c -omean-c
$ ghc --make -O2 mean.hs -o mean-hs

$ time ./mean-c 1e8
50000000.500000

real    0m1.575s
user    0m1.513s
sys     0m0.000s

$ time ./mean-hs 1e8
50000000.5

real    0m6.997s
user    0m6.856s
sys     0m0.013s


-- file mean.hs
module Main where

import System.Environment
import Text.Printf

mean :: Double -> Double -> Double
mean n m = go 0 0 n
  where
  go :: Double -> Int -> Double -> Double
  go s l x | x > m      = s / fromIntegral l
           | otherwise  = go (s+x) (l+1) (x+1)

main = do
    [d] <- map read `fmap` getArgs
    printf "%f\n" (mean 1 d)

/* file mean.c */
#include <stdio.h>
#include <stdlib.h>

int
main (int argc, char **argv)
{
  double d = atof(argv[1]);
  double n;
  long a;
  double b;

  for (n = 1,
       a = 0,
       b = 0; n <= d; b+=n,
                      n++,
                      a++)
    ;

  printf("%f\n", b / a);

  return 0;
}


More information about the Haskell-Cafe mailing list