[Haskell-cafe] Re: Importing Data.Char speeds up ghc around 70%
Daniel Fischer
daniel.is.fischer at web.de
Sat Dec 22 15:55:30 EST 2007
Am Samstag, 22. Dezember 2007 21:28 schrieb Joost Behrends:
Of course, one minute after I sent my previous mail, I receive this one :(
However, one point, it might be faster to factor out all factors p in found
and only then compute the intsqrt, like
found x = x{dividend = xstop, bound = intsqrt xstop, result = result x ++
replicate k p}
where
p = divisor x
(xstop,k) = go (dividend x) 0
go n m
| r == 0 = go q (m+1)
| otherwise = (n,m)
where
(q,r) = n `divMod` p
and then leaving out the recursive call in d2 etc.
For a measurable difference, you'd need a number with some high prime powers
as factors, but still, saves some work even for squares.
>
> I have found the problem: We must possibly work recursive on a found
> factor. This was done in former versions, but got lost when isolating the
> function "found". Here is a corrected version - complete again for
> reproducing easily the strange behavior with Data.Char. It decomposes
> 2^88+1 in 13 seconds.
>
>
> 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 = d2$found x
>
> d4 :: DivIter -> DivIter
> d4 x |dividend x `mod` divisor x > 0 = x {divisor = divisor x + 4}
>
> |otherwise = d4$found x
>
> d6 :: DivIter -> DivIter
> d6 x |dividend x `mod` divisor x > 0 = x {divisor = divisor x + 6}
>
> |otherwise = d6$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
>
> And now it uses also 1.34 minutes for 2^61+1 without importing Data.Char.
> Hmmm ...
>
> Cheers, Joost
>
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
More information about the Haskell-Cafe
mailing list