Prime numbers: Difference between revisions
m (Added a link to DList package.) |
(Made sieve more readable) |
||
Line 29: | Line 29: | ||
EQ -> x : (merge xt yt) | EQ -> x : (merge xt yt) | ||
GT -> y : (merge xs yt) | GT -> y : (merge xs yt) | ||
diff xs@(x:xt) ys@(y:yt) = case compare x y of | diff xs@(x:xt) ys@(y:yt) = case compare x y of | ||
LT -> x : (diff xt ys) | LT -> x : (diff xt ys) | ||
EQ -> diff xt yt | EQ -> diff xt yt | ||
GT -> diff xs yt | GT -> diff xs yt | ||
primes, nonprimes :: [Int] | |||
primes = [2,3,5] ++ (diff [7,9..] nonprimes) | |||
primes = | nonprimes = foldr1 f $ map g $ tail primes | ||
where | where f (x:xt) ys = x : (merge xt ys) | ||
g p = [ n*p | n <- [p,p+2..]] | |||
</haskell> | </haskell> | ||
<hask> | <hask>nonprimes</hask> effectively implements a heap, exploiting Haskell's lazy evaluation model. For another example of this idiom see the Prelude's <hask>ShowS</hask> type, which again exploits Haskell's lazy evaluation model | ||
to avoid explicitly coding efficient concatenable strings. This is generalized by the [http://hackage.haskell.org/cgi-bin/hackage-scripts/package/dlist-0.3 DList package]. | to avoid explicitly coding efficient concatenable strings. This is generalized by the [http://hackage.haskell.org/cgi-bin/hackage-scripts/package/dlist-0.3 DList package]. | ||
[[Category:Code]] | [[Category:Code]] |
Revision as of 08:41, 10 July 2007
The following is an elegant (and highly inefficient) way to generate a list of all the prime numbers in the universe:
primes = sieve [2..] where
sieve (p:xs) = p : sieve (filter (\x -> x `mod` p > 0) xs)
With this definition made, a few other useful (??) functions can be added:
is_prime n = n `elem` (takeWhile (n >=) primes)
factors n = filter (\p -> n `mod` p == 0) primes
factorise 1 = []
factorise n =
let f = head $ factors n
in f : factorise (n `div` f)
(Note the use of takeWhile
to prevent the infinite list of primes requiring an infinite amount of CPU time and RAM to process!)
The following is a more efficient prime generator, implementing the sieve of Eratosthenes:
merge xs@(x:xt) ys@(y:yt) = case compare x y of
LT -> x : (merge xt ys)
EQ -> x : (merge xt yt)
GT -> y : (merge xs yt)
diff xs@(x:xt) ys@(y:yt) = case compare x y of
LT -> x : (diff xt ys)
EQ -> diff xt yt
GT -> diff xs yt
primes, nonprimes :: [Int]
primes = [2,3,5] ++ (diff [7,9..] nonprimes)
nonprimes = foldr1 f $ map g $ tail primes
where f (x:xt) ys = x : (merge xt ys)
g p = [ n*p | n <- [p,p+2..]]
nonprimes
effectively implements a heap, exploiting Haskell's lazy evaluation model. For another example of this idiom see the Prelude's ShowS
type, which again exploits Haskell's lazy evaluation model
to avoid explicitly coding efficient concatenable strings. This is generalized by the DList package.