99 questions/Solutions/35

From HaskellWiki
< 99 questions‎ | Solutions
Revision as of 16:55, 13 July 2010 by Wapcaplet (talk | contribs)
(diff) ← Older revision | Latest revision (diff) | Newer revision → (diff)
Jump to navigation Jump to search

(**) 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 n primes
  where factor n (p:ps) | p*p > n = [n]
                        | n `mod` p /= 0 = factor n ps
                        | otherwise = p : factor (n `div` p) (p:ps)
        primes = 2 : filter ((==1) . length . primeFactors) [3,5..]