[Haskell-cafe] Re: Importing Data.Char speeds up ghc around 70%

Joost Behrends webmaster at h-labahn.de
Sat Dec 22 15:28:00 EST 2007


Daniel Fischer <daniel.is.fischer <at> web.de> writes:

> I can't reproduce it, both run in 130s here (SuSE 8.2, 1200MHz Duron).
> However, it's running over 30 minutes now trying to factorise 2^88+1 without 
> any sign of approaching success, which suggests your code has a bug (the 
> factorization is [257,229153,119782433,43872038849], so even a naive approach 
> shouldn't take much longer than a minute).
>

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



More information about the Haskell-Cafe mailing list