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

From HaskellWiki
Jump to navigation Jump to search
m
(additional solution)
Line 1: Line 1:
 
(**) Determine whether a given integer number is prime.
 
(**) Determine whether a given integer number is prime.
  +
  +
'''Solution 1'''
   
 
<haskell>
 
<haskell>
Line 14: Line 16:
   
 
<haskell>
 
<haskell>
{-# OPTIONS_GHC -O2 -fno-cse #-}
 
 
candidateFactors p = let z = floor $ sqrt $ fromIntegral p + 1 in
 
candidateFactors p = let z = floor $ sqrt $ fromIntegral p + 1 in
 
takeWhile (<= z) primesTME
 
takeWhile (<= z) primesTME
  +
</haskell>
 
  +
This uses
  +
<haskell>
 
{-# OPTIONS_GHC -O2 -fno-cse #-}
 
-- tree-merging Eratosthenes sieve
 
-- tree-merging Eratosthenes sieve
 
-- producing infinite list of all prime numbers
 
-- producing infinite list of all prime numbers
Line 27: Line 31:
 
gaps k xs@(x:t) | k==x = gaps (k+2) t
 
gaps k xs@(x:t) | k==x = gaps (k+2) t
 
| True = k : gaps (k+2) xs
 
| True = k : gaps (k+2) xs
  +
</haskell>
   
 
The tree-merging Eratosthenes sieve here seems to strike a good balance between efficiency and brevity, and semi-standard <code>union</code> function is readily available from <hask>Data.List.Ordered</hask>&nbsp;package, put here just for reference. More at [[Prime numbers]] haskellwiki page.
  +
<haskell>
 
-- duplicates-removing union of two ordered increasing lists
 
-- duplicates-removing union of two ordered increasing lists
 
union (x:xs) (y:ys) = case (compare x y) of
 
union (x:xs) (y:ys) = case (compare x y) of
Line 33: Line 40:
 
EQ -> x : union xs ys
 
EQ -> x : union xs ys
 
GT -> y : union (x:xs) ys
 
GT -> y : union (x:xs) ys
  +
</haskell>
  +
'''Solution 2'''
  +
  +
The following seems faster (in Hugs, Nov 2002 version), with the use of Q.35 solution for <code>primeFactors</code> (which itself uses <code>primesTME</code> from here, above):
  +
<haskell>
  +
isPrime n = n > 1 && n == head (primeFactors n)
 
</haskell>
 
</haskell>
   
  +
The <code>primeFactors</code> function reuses same <code>primesTME</code> list on subsequent invocations, but the <hask>(takeWhile ...)</hask>&nbsp;list in the first solution seems to be recreated anew for each call to <code>isPrime</code> (i.e. it may or may not be eliminated by a compiler, while the second solution explicitly uses the same <code>primesTME</code> list so there's no problem to begin with).
The tree-merging Eratosthenes sieve here seems to strike a good balance between efficiency and brevity. More at [[Prime numbers]] haskellwiki page.
 

Revision as of 06:57, 1 June 2011

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

Solution 1

isPrime :: Integral a => a -> Bool
isPrime p = p > 1 && 
            (all ((/= 0).(p `rem`)) $ candidateFactors p)

candidateFactors p = takeWhile ((<= p).(^2)) [2..]

Well, a natural number p is a prime number if it is larger than 1 and no natural number n >= 2 with 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 non-zero 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 primes <= sqrt P:

candidateFactors p = let z = floor $ sqrt $ fromIntegral p + 1 in
                     takeWhile (<= z) primesTME

This uses

{-# OPTIONS_GHC -O2 -fno-cse #-}
-- tree-merging Eratosthenes sieve
--  producing infinite list of all prime numbers
primesTME = 2 : gaps 3 (join [[p*p,p*p+2*p..] | p <- primes'])
  where
    primes' = 3 : gaps 5 (join [[p*p,p*p+2*p..] | p <- primes'])
    join  ((x:xs):t)        = x : union xs (join (pairs t))
    pairs ((x:xs):ys:t)     = (x : union xs ys) : pairs t
    gaps k xs@(x:t) | k==x  = gaps (k+2) t 
                    | True  = k : gaps (k+2) xs

The tree-merging Eratosthenes sieve here seems to strike a good balance between efficiency and brevity, and semi-standard union function is readily available from Data.List.Ordered package, put here just for reference. More at Prime numbers haskellwiki page.

-- duplicates-removing union of two ordered increasing lists
union (x:xs) (y:ys) = case (compare x y) of 
           LT -> x : union  xs  (y:ys)
           EQ -> x : union  xs     ys 
           GT -> y : union (x:xs)  ys

Solution 2

The following seems faster (in Hugs, Nov 2002 version), with the use of Q.35 solution for primeFactors (which itself uses primesTME from here, above):

isPrime n = n > 1 && n == head (primeFactors n)

The primeFactors function reuses same primesTME list on subsequent invocations, but the (takeWhile ...) list in the first solution seems to be recreated anew for each call to isPrime (i.e. it may or may not be eliminated by a compiler, while the second solution explicitly uses the same primesTME list so there's no problem to begin with).