Re: Fw: speed of compiled Haskell code.

2000-03-22 Thread Ch. A. Herrmann

Hi,

 very slow. After we made the insert operation in the AVL tree
 hyperstrict and a few similar changes, our program behaved very
 well and is surely faster than if written in C using naive data
 structures and algorithms.  We used combinators like strict2 f x
 y = strict (strict f x) y to achieve a simple code.

Jan I find this interesting. It would be nice if you would like to
Jan explain me what you mean by " hyperstrict"

I agree with the definition of hyperstrictness, that a function is
hyperstrict if it evaluates its arguments completely.

What I meant concerning the AVL tree was not complete hyperstrictness
but, that all parts which influence the structure of the tree
are evaluated when a new element is inserted. The crucial point
is that the application of the tree constructors must be strict to
guarantee that the restructuring balancing operation is performed
immediately. The comparison operators and the condition in
if-then-else are strict anyway and, thus, will force sufficient
evaluation. However, data stored in the tree that is not used for
the operations on the tree need not be evaluated.

Cheers
Christoph
 

  




Re: Fw: speed of compiled Haskell code.

2000-03-21 Thread Ketil Malde

"Jan Brosius" [EMAIL PROTECTED] writes:

 NO, NO and NO , please read only what I have written. 

You mean, apart from

 This seems that Haskell cannot be considered as a language for real
 world applications but merely as a toy for researchers .

?  I could have sworn you were saying here that Haskell was unsuitable
for "real" work, due to the cited performance loss of factor of 6-10. 

My point was that there's plenty of work being done in languages a lot 
slower than Haskell.  There may be reasons for not using Haskell in
the "real" world, performance is IMHO not an important one.

-kzm
-- 
If I haven't seen further, it is by standing in the footprints of giants




Re: Fw: speed of compiled Haskell code.

2000-03-21 Thread Ketil Malde


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




Re: Fw: speed of compiled Haskell code.

2000-03-21 Thread Jan de Wit

Hi All,

   I find this interesting. It would be nice if you would like to explain me
   what you mean by " hyperstrict"
   
I think hyperstrict means that a function completely evaluates *all* of its
arguments before the body of the function, as opposed to only some of
them. 
A function f taking n arguments is strict in its i'th argument if
f a_1 .. a_i-1  _|_ a_i+1 .. a_n = _|_
E.g. const is strict in its first argument but not in its second.

f is strict in all arguments if
f a_1 .. a_n = _|_ whenever one of the a_i's is _|_.
multOrAdd x y z = if x then y * z else y + z 
is strict in all of it arguments.
Hyperstrict has, in my view at least, also an annotation of completely
evaluating all arguments before the body of the function - something else
than (eventually) evaluating them all. I'm not sure about this though,
maybe someone can shed more light on this matter. 

Hope this helps (or leads to someone else giving a better definition :-)

Jan de Wit