[Haskell-cafe] x86 code generation going wrong?
Chris Kuklewicz
haskell at list.mightyreason.com
Sat Jan 7 11:18:59 EST 2006
Hello,
I need to ask for some help to test x86 code generation.
There is a factor of two runtime difference between the code I am
benchmarking on my OS X powerbook G4 (ghc 6.4.1) and shootout's speed on
a linux x86 machine (ghc 6.4.1).
Could someone else running on x86 test the three versions pasted below
before I think about submitting another one to the shootout?
To compile "ghc --make filename.hs -o program"
To run "cat input-file | time ./program"
where to save space, the gzip'd input file is at
http://paradosso.mit.edu/~ckuklewicz/sum-file-test-input.gz
-------------------------------------------------------------------------
-- Original version
{-# OPTIONS -O2 #-}
import Char( ord )
main :: IO ()
main = getContents >>= print . accP 0 0
accP :: Int -> Int -> String -> Int
accP before this [] = before+this
accP before this ('\n':xs) = accP (before+this) 0 xs
accP before this ('-' :xs) = accN before this xs
accP before this (x :xs) = accP before (this*10+ord(x)-ord('0')) xs
accN :: Int -> Int -> String -> Int
accN before this [] = before-this
accN before this ('\n':xs) = accP (before-this) 0 xs
accN before this (x :xs) = accN before (this*10+ord(x)-ord('0')) xs
-------------------------------------------------------------------------
-- Faster on G4, 2x slower on x86
{-# OPTIONS -O2 -funbox-strict-fields #-}
import GHC.Base
data I = I !Int
main = print . new (I 0) =<< getContents
new (I i) [] = i
new (I i) ('-':xs) = neg (I 0) xs
where neg (I n) ('\n':xs) = new (I (i - n)) xs
neg (I n) (x :xs) = neg (I (parse x + (10 * n))) xs
new (I i) (x:xs) = pos (I (parse x)) xs
where pos (I n) ('\n':xs) = new (I (i + n)) xs
pos (I n) (x :xs) = pos (I (parse x + (10 * n))) xs
parse c = ord c - ord '0'
-------------------------------------------------------------------------
-- Explicitly unboxed proposal, faster on G4
{-# OPTIONS -fglasgow-exts -O2 #-}
import GHC.Base
main = print . sumFile =<< getContents
where sumFile = (\rest -> newLine rest 0#)
newLine [] rt = (I# rt)
newLine ('-':rest) rt = negLine rest 0#
where negLine ('\n':rest) soFar = newLine rest (rt -# soFar)
negLine ( x :rest) soFar = negLine rest (d2i x +# (10# *# soFar))
newLine (x:rest) rt = posLine rest (d2i x)
where posLine ('\n':rest) soFar = newLine rest (rt +# soFar)
posLine ( x :rest) soFar = posLine rest (d2i x +# (10# *# soFar))
d2i (C# c) = (ord# c) -# z
where z = ord# '0'#
-------------------------------------------------------------------------
Thanks,
Chris
More information about the Haskell-Cafe
mailing list