Floating point performance

Jan Kort kort@wins.uva.nl
Fri, 26 Jan 2001 17:40:17 +0100


Hi,
I noticed ghc (version 4.08.1) floating point performance is
really slow on my computer: a 270Mhz sun ultra5. The program
below does 1 milion floating point multiplications and takes
2 seconds to run. I made a profile and it says most of the
time (93%) is spent in the function bar. Any idea what is
going on ?

Regards,
  Jan

module Main where

foo :: Double -> [Double]
foo 0 = [1]
foo n = bar n:foo (n-1)

bar :: Double -> Double
bar n = n*1*1*1*1*1*1*1*1*1*1
         *1*1*1*1*1*1*1*1*1*1
         *1*1*1*1*1*1*1*1*1*1
         *1*1*1*1*1*1*1*1*1*1
         *1*1*1*1*1*1*1*1*1*1
         *1*1*1*1*1*1*1*1*1*1
         *1*1*1*1*1*1*1*1*1*1
         *1*1*1*1*1*1*1*1*1*1
         *1*1*1*1*1*1*1*1*1*1
         *1*1*1*1*1*1*1*1*1*1

foldl'           :: (a -> b -> a) -> a -> [b] -> a
foldl' _ a []     = a
foldl' f a (x:xs) = (foldl' f $! f a x) xs

main :: IO()
main = putStrLn (show (foldl' (+) 0 (foo 10000)))

---------------------------
Profile:

        total time  =        2.60 secs   (130 ticks @ 20 ms)
        total alloc =  24,845,828 bytes  (excludes profiling overheads)

COST CENTRE          MODULE     %time %alloc

bar                  Main        93.1   96.1
foo                  Main         3.1    2.4
foldl'               Main         3.1    1.4


                                              individual     inherited
COST CENTRE              MODULE     entries  %time %alloc   %time %alloc

MAIN                     MAIN             0    0.0   0.0    100.0 100.0
 main                    Main             0    0.0   0.0      0.0   0.0
 CAF                     PrelShow         1    0.0   0.0      0.0   0.0
 CAF                     PrelFloat        3    0.0   0.0      0.0   0.0
 CAF                     PrelHandle       3    0.0   0.0      0.0   0.0
 CAF                     Main             9    0.0   0.0    100.0 100.0
  main                   Main             1    0.8   0.0    100.0 100.0
   foo                   Main         10001    3.1   2.4     96.2  98.5
    bar                  Main         10000   93.1  96.1     93.1  96.1
   foldl'                Main         10002    3.1   1.4      3.1   1.4