In the vein of benchmarking,

For those of you who follow comp.arch (or am I the only one?), you
have probably noticed the discussion about Stalin vs. C compilers.
For those who don't, it's basically one particular Scheme program
where compiled Scheme beats a naïve rewrite in C with orders of
magnitude (5s vs 30s was cited).

When rewriting in Haskell, I got some rather interesting results, hugs 
apparently runs the program about as fast as compiled Scheme (!) (I
get 8 seconds on a P150, while the numbers above were from a PPro200), 
and a compilation with GHC brings it down to about zero (0.7s to be
exact), but returns 0 instead of some large number.

This puzzles me, so I thought I'd turn to the list to see if anybody
here can shed light on my practices.  Am I committing some grave error 
in my translations?  Have I inadvertently performed source code
optimization?  Is there a bug in GHC?  Or is it just damned good at
figuring out things analytically?

The source code is as follows, with most of the original Scheme code
submitted in comments. (The missing Scheme is the integrate*
functions, which are rather trivially translated.  If anybody asks,
I'll dig them up).  Here goes:

-----8<----------------
integrate1D :: Double -> Double -> (Double->Double) -> Double
integrate1D l u f =
  let  d = (u-l)/8.0 in
     d * sum 
      [ (f l)*0.5,
        f (l+d),
        f (l+(2.0*d)),
        f (l+(3.0*d)),
        f (l+(4.0*d)),
        f (u-(3.0*d)),
        f (u-(2.0*d)),
        f (u-d),
        (f u)*0.5]

integrate2D l1 u1 l2 u2 f = integrate1D l2 u2 
                            (\y->integrate1D l1 u1 
                                  (\x->f x y))

zark u v = integrate2D 0.0 u 0.0 v (\x->(\y->x*y))

{-
(define (r-total N)
 (do ((I 1 (+ I 1))
      (Sum 0.0 (+ Sum (zark (* I 1.0) (* I 2.0)))))
   ((> I N) Sum)))
-}

ints = [1.0..]
zarks = zipWith zark ints (map (2.0*) ints)
rtotals = head zarks : zipWith (+) (tail zarks) rtotals
rtotal n = rtotals!!n

{-
(define (i-total N)
 (do ((I 1 (+ I 1))
      (Sum 0.0 (+ Sum (let ((I2 (* (* I I) 1.0))) (* I2 I2)))))
   ((> I N) Sum)))
-}

is = map (^4) ints
itotals = head is : zipWith (+) (tail is) itotals
itotal n = itotals!!n

{-
(define (error-sum-of-squares N)
 (do ((I 1 (+ I 1))
      (Sum 0.0 (+ Sum (let ((E (- (r-total I) (i-total I)))) (* E E)))))
   ((> I N) Sum)))

(begin (display (error-sum-of-squares 1000)) (newline))
-}

es = map (^2) (zipWith (-) rtotals itotals)
etotal n = sum (take n es)

main = putStrLn (show (etotal 1000))

--------8<----------------

Reply via email to