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

From HaskellWiki
Jump to navigation Jump to search
(change the 2nd version code)
(9 intermediate revisions by 4 users not shown)
Line 1: Line 1:
 
(**) Determine whether a given integer number is prime.
 
(**) Determine whether a given integer number is prime.
   
 
Well, a natural number ''k'' is a prime number if it is larger than '''1''' and no natural number ''n >= 2'' with ''n^2 <= k'' is a divisor of ''k''. However, we don't actually need to check all natural numbers ''n <= sqrt k''. We need only check the '''''primes''' p <= sqrt k'':
'''Solution 1'''
 
   
 
<haskell>
 
<haskell>
 
isPrime :: Integral a => a -> Bool
 
isPrime :: Integral a => a -> Bool
isPrime p = p > 1 &&
+
isPrime k = k > 1 &&
(all ((/= 0).(p `rem`)) $ candidateFactors p)
+
foldr (\p r -> p*p > k || k `rem` p /= 0 && r)
 
True primesTME
 
candidateFactors p = takeWhile ((<= p).(^2)) [2..]
 
 
</haskell>
 
</haskell>
   
 
This uses
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'':
 
   
<haskell>
 
candidateFactors p = let z = floor $ sqrt $ fromIntegral p + 1 in
 
takeWhile (<= z) primesTME
 
</haskell>
 
This uses
 
 
<haskell>
 
<haskell>
 
{-# OPTIONS_GHC -O2 -fno-cse #-}
 
{-# OPTIONS_GHC -O2 -fno-cse #-}
Line 33: Line 25:
 
</haskell>
 
</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.
+
The tree-merging Eratosthenes sieve here seems to strike a good balance between efficiency and brevity. More at [[Prime numbers]] haskellwiki page. The semi-standard <code>union</code> function is readily available from <hask>Data.List.Ordered</hask>&nbsp;package, put here just for reference:
  +
  +
 
<haskell>
 
<haskell>
 
-- duplicates-removing union of two ordered increasing lists
 
-- duplicates-removing union of two ordered increasing lists
Line 41: Line 36:
 
GT -> y : union (x:xs) ys
 
GT -> y : union (x:xs) ys
 
</haskell>
 
</haskell>
'''Solution 2'''
 
   
  +
Here is another solution, intended to be extremely short while still being reasonably fast.
The following is faster (in Hugs, Nov 2002 version):
 
  +
 
<haskell>
 
<haskell>
isPrime n = n > 1 &&
+
isPrime :: (Integral a) => a -> Bool
foldr (\p r -> p*p > n || n `rem` p /= 0 && r)
+
isPrime n | n < 4 = n > 1
  +
isPrime n = all ((/=0).mod n) $ 2:3:[x + i | x <- [6,12..s], i <- [-1,1]]
True primesTME
 
  +
where s = floor $ sqrt $ fromIntegral n
 
</haskell>
 
</haskell>
   
  +
This one does not go as far as the previous, but it does observe the fact that you only need to check numbers of the form 6k +/- 1 up to the square root. And according to some quick tests (nothing extensive) this version can run a bit faster in some cases, but slower in others; depending on optimization settings and the size of the input.
This 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).
 
  +
  +
''There is a subtle bug in the version above. I'm new here (the wiki and the language) and don't know how corrections are best made (here, or on discussion?). Anyway, the above version will fail on 25, because the bound of s is incorrect. It is x+i that is bounded by the sqrt of the argument, not x. This version will work correctly:''
  +
 
<haskell>
  +
isPrime n | n < 4 = n /= 1
  +
isPrime n = all ((/=0) . mod n) $ takeWhile (<= m) candidates
  +
where candidates = (2:3:[x + i | x <- [6,12..], i <- [-1,1]])
 
m = floor . sqrt $ fromIntegral n
 
</haskell>
  +
  +
  +
[[Category:Programming exercise spoilers]]

Revision as of 19:42, 18 January 2014

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

Well, a natural number k is a prime number if it is larger than 1 and no natural number n >= 2 with n^2 <= k is a divisor of k. However, we don't actually need to check all natural numbers n <= sqrt k. We need only check the primes p <= sqrt k:

isPrime :: Integral a => a -> Bool
isPrime k = k > 1 &&
   foldr (\p r -> p*p > k || k `rem` p /= 0 && r)
      True 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. More at Prime numbers haskellwiki page. The semi-standard union function is readily available from Data.List.Ordered package, put here just for reference:


-- 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

Here is another solution, intended to be extremely short while still being reasonably fast.

isPrime :: (Integral a) => a -> Bool
isPrime n | n < 4 = n > 1
isPrime n = all ((/=0).mod n) $ 2:3:[x + i | x <- [6,12..s], i <- [-1,1]]
            where s = floor $ sqrt $ fromIntegral n

This one does not go as far as the previous, but it does observe the fact that you only need to check numbers of the form 6k +/- 1 up to the square root. And according to some quick tests (nothing extensive) this version can run a bit faster in some cases, but slower in others; depending on optimization settings and the size of the input.

There is a subtle bug in the version above. I'm new here (the wiki and the language) and don't know how corrections are best made (here, or on discussion?). Anyway, the above version will fail on 25, because the bound of s is incorrect. It is x+i that is bounded by the sqrt of the argument, not x. This version will work correctly:

isPrime n | n < 4 = n /= 1 
isPrime n = all ((/=0) . mod n) $ takeWhile (<= m) candidates 
        where candidates = (2:3:[x + i | x <- [6,12..], i <- [-1,1]])
              m = floor . sqrt $ fromIntegral n