[Haskell-cafe] Importing Data.Char speeds up ghc around 70%
Joost Behrends
webmaster at h-labahn.de
Sat Dec 22 13:00:29 EST 2007
Hi,
while still working on optimizing (naively programmed) primefactors i watched a
very strange behavior of ghc. The last version below takes 2.34 minutes on my
system for computing 2^61+1 = 3*768614,336404,564651. Importing Data.Char
without anywhere using it reduces this time to 1.34 minute - a remarkable speed
up. System is WindowsXP on 2.2GHZ Intel, 512MB Ram.
I give the complete code here - hopefully all tabs are (4) blanks. Can this be
reproduced ? I compile just with --make -O2.
module Main
where
import IO
import System.Exit
import Data.Char
main = do
hSetBuffering stdin LineBuffering
putStrLn "Number to decompose ?"
s <- getLine
if s == [] then
exitWith ExitSuccess
else do
putStrLn (show$primefactors$read s)
main
data DivIter = DivIter {dividend :: Integer,
divisor :: Integer,
bound :: Integer,
result :: [Integer]}
intsqrt m = floor (sqrt $ fromInteger m)
primefactors :: Integer -> [Integer]
primefactors n | n<2 = []
| even n = o2 ++ (primefactors o1)
| otherwise = if z/=1 then result res ++[z] else result res
where
res = divisions (DivIter {dividend = o1,
divisor = 3,
bound = intsqrt(o1),
result = o2})
z = dividend res -- is 1 sometimes
(o1,o2) = twosect (n,[])
twosect :: (Integer,[Integer]) -> (Integer,[Integer])
twosect m |odd (fst m) = m
|even (fst m) = twosect (div (fst m) 2, snd m ++ [2])
found :: DivIter -> DivIter
found x = x {dividend = xidiv,
bound = intsqrt(xidiv),
result = result x ++ [divisor x]}
where xidiv = (dividend x) `div` (divisor x)
d2 :: DivIter -> DivIter
d2 x |dividend x `mod` divisor x > 0 = x { divisor = divisor x + 2}
|otherwise = found x
d4 :: DivIter -> DivIter
d4 x |dividend x `mod` divisor x > 0 = x { divisor = divisor x + 4}
|otherwise = found x
d6 :: DivIter -> DivIter
d6 x |dividend x `mod` divisor x > 0 = x { divisor = divisor x + 6}
|otherwise = found x
divisions :: DivIter -> DivIter
divisions y |or[divisor y == 3,
divisor y == 5] = divisions (d2 y)
|divisor y <= bound y = divisions (d6$d2$d6$d4$d2$d4$d2$d4 y)
|otherwise = y
More information about the Haskell-Cafe
mailing list