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

From HaskellWiki
Jump to navigation Jump to search
(Faster alternative)
(Undo revision 38538 by Newgame (Talk))
Line 7: Line 7:
   
 
Well, a natural number p is a prime number iff it is larger than 1 and no natural number n with n >= 2 and n^2 <= p is a divisor of p. That's exactly what is implemented: we take the list of all integral numbers starting with 2 as long as their square is at most p and check that for all these n there is a remainder concerning the division of p by n.
 
Well, a natural number p is a prime number iff it is larger than 1 and no natural number n with n >= 2 and n^2 <= p is a divisor of p. That's exactly what is implemented: we take the list of all integral numbers starting with 2 as long as their square is at most p and check that for all these n there is a remainder concerning the division of p by n.
 
A faster alternative that does not test if ''all'' numbers between 2 and n are ''not'' divisors of p. It rather tests if ''at least one'' number between 2 and n is a divisor of p and when this is the case p can immediately be dismissed and the next number can be tested:
 
 
<haskell>
 
isPrime :: Integral a => a -> Bool
 
isPrime p = p > 1 && (not $ any (\n -> p `mod` n == 0) $ takeWhile (\n -> n*n <= p) [2..])
 
</haskell>
 
   
 
However, we don't actually need to check all natural numbers <= sqrt P. We need only check the all natural primes <= sqrt P.
 
However, we don't actually need to check all natural numbers <= sqrt P. We need only check the all natural primes <= sqrt P.

Revision as of 20:41, 8 February 2011

(**) Determine whether a given integer number is prime.

isPrime :: Integral a => a -> Bool
isPrime p = p > 1 && (all (\n -> p `mod` n /= 0 ) $ takeWhile (\n -> n*n <= p) [2..])

Well, a natural number p is a prime number iff it is larger than 1 and no natural number n with n >= 2 and n^2 <= p is a divisor of p. That's exactly what is implemented: we take the list of all integral numbers starting with 2 as long as their square is at most p and check that for all these n there is a remainder concerning the division of p by n.

However, we don't actually need to check all natural numbers <= sqrt P. We need only check the all natural primes <= sqrt P.

-- Infinite list of all prime numbers
allPrimes :: [Int]
allPrimes = filter (isPrime) [2..]

isPrime :: Int -> Bool
isPrime p
    | p < 2  = error "Number too small"
    | p == 2 = True
    | p > 2  = all (\n -> p `mod` n /= 0) (getPrimes sqrtp)
    where getPrimes z = takeWhile (<= z) allPrimes
          sqrtp = floor . sqrt $ fromIntegral p

Note that the mutual dependency of allPrimes and isPrime would result in an infinite loop if we weren't careful. But since we limit our observation of allPrimes to <= sqrt x, we avoid infinite recursion.

While the mutual dependency is interesting, this second version is not necessarily more efficient than the first. Though we avoid checking all natural numbers <= sqrt P in the isPrime method, we instead check the primality of all natural numbers <= sqrt P in the allPrimes definition.