Int64 and efficiency
Ketil Malde
ketil+haskell at ii.uib.no
Mon Jun 6 07:43:48 EDT 2005
Hi,
Recently, Marcin 'Qrczak' Kowalczyk posted a micro-benchmark on
comp.lang.functional, illustrating performance with statically typed
Int and Integer, and Kogut's dynamically typed automatically-promoted
numbers. (Int is fastest, Kogut second, and Integer quite a bit
slower).
For fun, I tried to use Int64, but to my surprise it is a lot slower
than the others. Marcin suggested I look at stg and hc output (which
I did without getting much wiser) and made some guesses as to what the
reasons were.
I'm curious whether this is typical, and if so, whether there is a
theoretical reason why Int64 is so slow? (I would have expected a
factor of 2-4 worse than Int, but in reality it was about 35x slower)
(Code attached, replace MyInt as appropriate.)
-kzm
-------------- next part --------------
module Main where
import Data.Int
type MyInt = Int -- or Int64 or Integer
seqLength :: MyInt -> Int
seqLength x = loop x 0
where
loop :: MyInt -> Int -> Int
loop 1 len = len
loop k len
| even k = loop (k `quot` 2) $! len + 1
| otherwise = loop (3 * k + 1) $! len + 1
main :: IO ()
main = print $ sum $ map seqLength [1..100000]
-------------- next part --------------
--
If I haven't seen further, it is by standing in the footprints of giants
More information about the Glasgow-haskell-users
mailing list