Difference between revisions of "99 questions/Solutions/35"

From HaskellWiki
Jump to navigation Jump to search
 
(code fix speed-wise: reuse of same primes list instead of implicit tower; remQuot instead of divMod; null.tail for (==1).length: making 1000 primes in Hugs: 29.7 mln reds -> 6.4mln, cpxty better too.)
Line 41: Line 41:
   
 
<haskell>
 
<haskell>
primeFactors n = factor n primes
+
primeFactors n = factor primes n
where factor n (p:ps) | p*p > n = [n]
+
where factor ps@(p:pt) n | p*p > n = [n]
| n `mod` p /= 0 = factor n ps
+
| rem n p == 0 = p : factor ps (quot n p)
| otherwise = p : factor (n `div` p) (p:ps)
+
| otherwise = factor pt n
primes = 2 : filter ((==1) . length . primeFactors) [3,5..]
+
primes = 2 : filter (null . tail . factor primes) [3,5..]
 
</haskell>
 
</haskell>

Revision as of 10:59, 31 May 2011

(**) Determine the prime factors of a given positive integer. Construct a flat list containing the prime factors in ascending order.

primeFactors :: Integer -> [Integer]
primeFactors a = let (f, f1) = factorPairOf a
                     f' = if prime f then [f] else primeFactors f
                     f1' = if prime f1 then [f1] else primeFactors f1
                 in f' ++ f1'
 where
 factorPairOf a = let f = head $ factors a
                 in (f, a `div` f)
 factors a = filter (isFactor a) [2..a-1]
 isFactor a b = a `mod` b == 0
 prime a = null $ factors a

Kind of ugly, but it works, though it may have bugs in corner cases. This uses the factor tree method of finding prime factors of a number. factorPairOf picks a factor and takes it and the factor you multiply it by and gives them to primeFactors. primeFactors checks to make sure the factors are prime. If not it prime factorizes them. In the end a list of prime factors is returned.

Another possibility is to observe that you need not ensure that potential divisors are primes, as long as you consider them in ascending order:

primeFactors n = primeFactors' n 2 where
    primeFactors' 1 _ = []
    primeFactors' n factor
      | n `mod` factor == 0 = factor : primeFactors' (n `div` factor) factor
      | otherwise           = primeFactors' n (factor + 1)

Thus, we just loop through all possible factors and add them to the list if they divide the original number. As the primes get farther apart, though, this will do a lot of needless checks to see if composite numbers are prime factors. However we can stop as soon as the candidate factor exceeds the square root of n:

primeFactors n = primeFactors' n 2 where
    primeFactors' n factor
      | factor*factor > n   = [n]
      | n `mod` factor == 0 = factor : primeFactors' (n `div` factor) factor
      | otherwise           = primeFactors' n (factor + 1)

You can avoid the needless work by just looping through the primes:

primeFactors n = factor primes n
  where factor ps@(p:pt) n | p*p > n      = [n]               
                           | rem n p == 0 = p : factor ps (quot n p) 
                           | otherwise    =     factor pt n
        primes = 2 : filter (null . tail . factor primes) [3,5..]