Prime factors in Haskell

18,991

Solution 1

A simple approach to determine the prime factors of n is to

  • search for the first divisor d in [2..n-1]
  • if D exists: return d : primeFactors(div n d)
  • otherwise return n (since n is prime)

Code:

prime_factors :: Int -> [Int]

prime_factors 1 = []
prime_factors n
  | factors == []  = [n]
  | otherwise = factors ++ prime_factors (n `div` (head factors))
  where factors = take 1 $ filter (\x -> (n `mod` x) == 0) [2 .. n-1]

This obviously could use a lot of optimization (search only from 2 to sqrt(N), cache the prime numbers found so far and compute the division only for these etc.)

UPDATE

A slightly modified version using case (as suggested by @user5402):

prime_factors n =
  case factors of
    [] -> [n]
    _  -> factors ++ prime_factors (n `div` (head factors))
  where factors = take 1 $ filter (\x -> (n `mod` x) == 0) [2 .. n-1]

Solution 2

This is a good-performanced and easy-to-understand implementation, in which isPrime and primes are defined recursively, and primes will be cached by default. primeFactors definition is just a proper use of primes, the result will contains continuous-duplicated numbers, this feature makes it easy to count the number of each factor via (map (head &&& length) . group) and it's easy to unique it via (map head . group) :

isPrime :: Int -> Bool
primes :: [Int]

isPrime n | n < 2 = False
isPrime n = all (\p -> n `mod` p /= 0) . takeWhile ((<= n) . (^ 2)) $ primes
primes = 2 : filter isPrime [3..]

primeFactors :: Int -> [Int]
primeFactors n = iter n primes where
    iter n (p:_) | n < p^2 = [n | n > 1]
    iter n ps@(p:ps') =
        let (d, r) = n `divMod` p
        in if r == 0 then p : iter d ps else iter n ps'

And the usage:

> import Data.List
> import Control.Arrow

> primeFactors 12312
[2,2,2,3,3,3,3,19]

> (map (head &&& length) . group) (primeFactors 12312)
[(2,3),(3,4),(19,1)]

> (map head . group) (primeFactors 12312)
[2,3,19]

Solution 3

Until the dividend m < 2,

  1. take the first divisor n from primes.
  2. repeat dividing m by n while divisible.
  3. take the next divisor n from primes, and go to 2.

The list of all divisors actually used are prime factors of original m.

Code:

-- | prime factors
--
-- >>> factors 13
-- [13]
-- >>> factors 16
-- [2,2,2,2]
-- >>> factors 60
-- [2,2,3,5]
--
factors :: Int -> [Int]
factors m = f m (head primes) (tail primes) where
  f m n ns
    | m < 2 = []
    | m `mod` n == 0 = n : f (m `div` n) n ns
    | otherwise = f m (head ns) (tail ns)

-- | primes
--
-- >>> take 10 primes
-- [2,3,5,7,11,13,17,19,23,29]
--
primes :: [Int]
primes = f [2..] where f (p : ns) = p : f [n | n <- ns, n `mod` p /= 0]

Update:

This replacement code improves performance by avoiding unnecessary evaluations:

factors m = f m (head primes) (tail primes) where
  f m n ns
    | m < 2 = []
    | m < n ^ 2 = [m]   -- stop early
    | m `mod` n == 0 = n : f (m `div` n) n ns
    | otherwise = f m (head ns) (tail ns)

primes can also be sped up drastically, as mentioned in Will Ness's comment:

primes = 2 : filter (\n-> head (factors n) == n) [3,5..]

Solution 4

I just worked on this problem. Here's my solution.

Two helping functions are

factors n = [x | x <- [1..n], mod n x == 0]
isPrime n = factors n == [1,n]

Then using a list comprehension to get all prime factors and how many are they.

prime_factors num = [(last $ takeWhile (\n -> (x^n) `elem` (factors num)) [1..], x) | x <- filter isPrime $ factors num]

where

x <- filter isPrime $ factors num

tells me what prime factors the given number has, and

last $ takeWhile (\n -> (x^n) `elem` (factors num)) [1..]

tells me how many this factor is.

Examples

> prime_factors 36    -- 36 = 4 * 9
[(2,2),(2,3)]

> prime_factors 1800  -- 1800 = 8 * 9 * 25
[(3,2),(2,3),(2,5)]

Solution 5

Haskell allows you to create infinite lists, that are mutually recursive. Let's take an advantage of this.

First let's create a helper function that divides a number by another as much as possible. We'll need it, once we find a factor, to completely eliminate it from a number.

import Data.Maybe (mapMaybe)

-- Divide the first argument as many times as possible by the second one.
divFully :: Integer -> Integer -> Integer
divFully n q | n `mod` q == 0   = divFully (n `div` q) q
             | otherwise        = n

Next, assuming we have somewhere the list of all primes, we can easily find factors of a numbers by dividing it by all primes less than the square root of the number, and if the number is divisible, noting the prime number.

-- | A lazy infinite list of non-trivial factors of all numbers.
factors :: [(Integer, [Integer])]
factors = (1, []) : (2, [2]) : map (\n -> (n, divisors primes n)) [3..]
  where
    divisors :: [Integer] -> Integer -> [Integer]
    divisors _ 1          = []   -- no more divisors
    divisors (p:ps) n
        | p^2 > n       = [n]  -- no more divisors, `n` must be prime
        | n' < n        = p : divisors ps n'    -- divides
        | otherwise     = divisors ps n'        -- doesn't divide
      where
        n' = divFully n p

Conversely, when we have the list of all factors of numbers, it's easy to find primes: They are exactly those numbers, whose only prime factor is the number itself.

-- | A lazy infinite list of primes.
primes :: [Integer]
primes = mapMaybe isPrime factors
  where
    -- |  A number is prime if it's only prime factor is the number itself.
    isPrime (n, [p]) | n == p  = Just p
    isPrime _                  = Nothing

The trick is that we start the list of factors manually, and that to determine the list of prime factors of a number we only need primes less then its square root. Let's see what happens when we consume the list of factors a bit and we're trying to compute the list of factors of 3. We're consuming the list of primes, taking 2 (which can be computed from what we've given manually). We see that it doesn't divide 3 and that since it's greater than the square root of 3, there are no more possible divisors of 3. Therefore the list of factors for 3 is [3]. From this, we can compute that 3 is another prime. Etc.

Share:
18,991

Related videos on Youtube

Chris
Author by

Chris

Updated on September 19, 2022

Comments

  • Chris
    Chris over 1 year

    I'm new to Haskell.

    How to generate a list of lists which contains prime factors of next integers?

    Currently, I only know how to generate prime numbers:

    primes = map head $ iterate (\(x:xs) -> [y | y<-xs, y `mod` x /= 0 ]) [2..]
    
    • GS - Apologise to Monica
      GS - Apologise to Monica over 10 years
      How far have you got? For example you could try writing a function to factorize a single number.
  • ErikR
    ErikR over 10 years
    instead of factors == [], it is more idiomatic (and perhaps more efficient) to use case factors of [] -> ...
  • d8d0d65b3f7cf42
    d8d0d65b3f7cf42 over 10 years
    note that foo == [] introduces an Eq constraint in the type of foo (which is actually not needed here) while case foo of [] -> ... does not.
  • bheklilr
    bheklilr over 10 years
    An alternative to factors == [] but still using guards would be to just use null factors instead.
  • d12frosted
    d12frosted over 10 years
    there is no need too check all [2..n-1] numbers. You can only check all [2..sqrt(n)], because if p | n, then p <= sqrt(n).
  • Frank Schmitt
    Frank Schmitt over 10 years
    @RottenBrain I know (I mentioned it in my answer as a possible optimization) - I didn't want to spoil the fun for the OP :-)
  • d12frosted
    d12frosted about 10 years
    @Frank Schmitt, oh sorry. You really have mentioned this optimisation :)
  • Will Ness
    Will Ness almost 10 years
    without the sqrt it's just terrible, and even with it it's suboptimal.
  • Frank Schmitt
    Frank Schmitt almost 10 years
    @WillNess Then please go ahead and post your own optimized solution :-)
  • Will Ness
    Will Ness almost 10 years
  • Will Ness
    Will Ness about 8 years
    this code is slow twice over: in factors it doesn't stop at sqrt, and in primes it doesn't wait until sqr -- of a prime.
  • Hironobu Nagaya
    Hironobu Nagaya about 8 years
    @WillNess Thanks to your advice, I can update code. This code become faster significantly by adding only a guard. Original code takes 15 seconds to factorize 599946, while updated code takes only 6 milliseconds.
  • Will Ness
    Will Ness about 8 years
    great; you've improved your factors but not the primes which still is much too slow. compare your definition's speed with that of 2:filter (\n-> head (factors n) == ...... (complete the definition). :) can you find the reason for such a difference in speed? see also "empirical orders of growth".
  • Hironobu Nagaya
    Hironobu Nagaya about 8 years
    @WillNess I understood what you intend to do, but I could not complete your code snippet. I feel sorry but can you show me primes you defined?
  • Will Ness
    Will Ness about 8 years
    sure, it's primes = 2:filter (\n-> head (factors n) == n) [3,5..]. :)
  • dz902
    dz902 over 7 years
    @FrankSchmitt Thanks for the explanation! So we recursively divide n by the factor smaller than sqrt n, thus never need to check numbers beyond sqrt n.
  • Frank Schmitt
    Frank Schmitt over 7 years
    @Dai Exactly. this_comment_was_too_short
  • Will Ness
    Will Ness about 4 years
    let fac = mfac n 2 in fac : factors' (n `div` fac) is suboptimal, always starts from 2, can start from the previous fac.