Check whether an integer (or all elements of a list of integers) be prime

与世无争的帅哥 提交于 2019-12-06 13:14:14

Ok,

let's do this step by step:

In math a (natural) number n is prime if it has exactly 2 divisors: 1 and itself (mind 1 is not a prime).

So let's first get all of the divisors of a number:

divisors :: Integer -> [Integer]
divisors n = [ d | d <- [1..n], n `mod` d == 0 ]

then get the count of them:

divisorCount :: Integer -> Int
divisorCount = length . divisors

and voila we have the most naive implementation using just the definition:

isPrime :: Integer -> Bool
isPrime n = divisorCount n == 2

now of course there can be quite some impprovements:

  • instead check that there is no divisor > 1 and < n
  • you don't have to check all divisors up to n-1, it's enough to check to the squareroot of n
  • ...

Ok just to give a bit more performant version and make @Jubobs happy ;) here is an alternative:

isPrime :: Integer -> Bool
isPrime n
  | n <= 1 = False
  | otherwise = not . any divides $ [2..sqrtN]
  where divides d = n `mod` d == 0
        sqrtN = floor . sqrt $ fromIntegral n

This one will check that there is no divisor between 2 and the squareroot of the number

complete code:

using quickcheck to make sure the two definitions are ok:

module Prime where

import Test.QuickCheck

divisors :: Integer -> [Integer]
divisors n = [ d | d <- [1..n], n `mod` d == 0 ]

divisorCount :: Integer -> Int
divisorCount = length . divisors

isPrime :: Integer -> Bool
isPrime n
  | n <= 1 = False
  | otherwise = not . any divides $ [2..sqrtN]
  where divides d = n `mod` d == 0
        sqrtN = floor . sqrt $ fromIntegral n

isPrime' :: Integer -> Bool
isPrime' n = divisorCount n == 2

main :: IO()
main = quickCheck (\n -> isPrime' n == isPrime n)

!!warning!!

I just saw (had something in the back of my mind), that the way I did sqrtN is not the best way to do it - sorry for that. I think for the examples with small numbers here it will be no problem, but maybe you really want to use something like this (right from the link):

(^!) :: Num a => a -> Int -> a
(^!) x n = x^n

squareRoot :: Integer -> Integer
squareRoot 0 = 0
squareRoot 1 = 1
squareRoot n =
   let twopows = iterate (^!2) 2
       (lowerRoot, lowerN) =
          last $ takeWhile ((n>=) . snd) $ zip (1:twopows) twopows
       newtonStep x = div (x + div n x) 2
       iters = iterate newtonStep (squareRoot (div n lowerN) * lowerRoot)
       isRoot r  =  r^!2 <= n && n < (r+1)^!2
   in  head $ dropWhile (not . isRoot) iters

but this seems a bit heavy for the question on hand so I just remark it here.

Here are two facts about prime numbers.

  1. The first prime number is 2.
  2. An integer larger than 2 is prime iff it's not divisible by any prime number up to its square root.

This knowledge should naturally lead you to something like the following approach:

-- primes : the infinite list of prime numbers
primes :: [Integer]
primes = 2 : filter isPrime [3,5..]

-- isPrime n : is positive integer 'n' a prime number?
isPrime :: Integer -> Bool
isPrime n
    | n < 2     = False
    | otherwise = all (\p -> n `mod` p /= 0) (primesPrefix n)
    where primesPrefix n = takeWhile (\p -> p * p <= n) primes

As a bonus, here is a function to test whether all items of a list of integers be prime numbers.

-- arePrimes ns : are all integers in list 'ns' prime numbers?
arePrimes :: [Integer] -> Bool
arePrimes = all isPrime

Some examples in ghci:

ghci> isPrime 3
True
ghci> isPrime 99
False
ghci> arePrimes [2,3,7]
True
ghci> arePrimes [2,3,4,7]
False

You can get a recursive formulation from the "2 divisors" variant by step-wise refinement:

isPrime n 
    = 2 == length  [ d | d <- [1..n], rem n d == 0 ]
    = n > 1 && null [ d | d <- [2..n-1], rem n d == 0 ]
    = n > 1 && and [ rem n d > 0 | d <- takeWhile ((<= n).(^2)) [2..] ]
    = n > 1 && g 2
       where
         g d = d^2 > n || (rem n d > 0 && g (d+1))
    = n == 2 || (n > 2 && rem n 2 > 0 && g 3)
       where
         g d = d^2 > n || (rem n d > 0 && g (d+2))

And that's your recursive function. Convince yourself of each step's validity.

Of course after we've checked the division by 2, there's no need to try dividing by 4,6,8, etc.; that's the reason for the last transformation, to check by odds only. But really we need to check the divisibility by primes only.

易学教程内所有资源均来自网络或用户发布的内容,如有违反法律规定的内容欢迎反馈
该文章没有解决你所遇到的问题?点击提问,说说你的问题,让更多的人一起探讨吧!