[Haskell-cafe] Re: MonadFix

Daniel Fischer daniel.is.fischer at web.de
Fri Dec 21 07:56:42 EST 2007


Am Freitag, 21. Dezember 2007 11:33 schrieb apfelmus:
> Joost Behrends wrote:
> > apfelmus writes:
> >> How about separating the candidate prime numbers from the recursion
> >>
> >>    factorize :: Integer -> [Integer]
> >>    factorize = f primes'
> >>       where
> >>       primes' = 2:[3,5..]
> >>       f (p:ps) n
> >>
> >>          | r == 0    = p : f (p:ps) q
> >>          | p*p > n   = [n]
> >>          | otherwise = f ps n
> >>
> >>          where
> >>          (q,r) = n `divMod` p
> >
> > (besides: p < intsqrt n must stay, otherwise you have
> > the expensive p*p at every step)
>
> Huh?  p < intsqrt n  is evaluated just as often as  p*p > n , with
> changing  n  . Why would that be less expensive? Btw, the code above
> test for  r==0  first, which means that the following  p*p > n  is
> tested exactly once for every prime candidate  p .

However, when you do the sensible thing (which Joost did) and have the intsqrt 
a parameter of the function, like in

factorize :: Integer -> [Integer]
factorize n = f n (intsqrt n) primes'
      where
	primes' = something more or less clever here
	f m sr (p:ps)
	    | r == 0    = p:f q (intsqrt q) (p:ps)
	    | p > sr    = if m == 1 then [] else [m]
	    | otherwise = f m sr ps
	      where
		(q,r) = m `quotRem` p

, then you only have the expensive intsqrt for each prime factor, and the test 
for each candidate is only one comparison instead of one multiplication and 
one comparison. Since usually the number of prime factors is minuscule 
compared to the number of candidates to be tested, that's indeed faster for 
most inputs (in my tests ~28.5% less run time).
Some speed is also gained by using quotRem instead of divMod (pace, Henning, I 
agree divMod is preferable, but quotRem is a primitive).

But of course, the most could be gained from a better algorithm.

>
> Regards,
> apfelmus
>

Cheers,
Daniel



More information about the Haskell-Cafe mailing list