Looking for the fastest Haskell primes algorithm

Today I happened to need a large list of prime numbers. Obviously this is a well-known problem, so I figured there would be something on Hackage that I could use. Surprisingly, there isn't, or if there is it's not easy to find. Searching for prime or primes on Hackage reveals nothing. Searching for primes on Hayoo gives Codec.Encryption.RSA.NumberTheory, but that uses the inefficient one-liner implementation. The HaskellWiki article on primes (http://www.haskell.org/haskellwiki/Prime_numbers) has a number of implementations, but the faster they get, the longer and uglier they become. Since it's such a common problem I'd say it would be a good idea to add a package to Hackage that exports primes :: [Integer] and hides the ugly implementation details. Data.Numbers.Primes seems a logical choice for the namespace, but I'm open to suggestions. The trick then is to find the most efficient implementation of primes. The Haskell wiki article mentions ONeillPrimes.hs as one of the fastest ones, but maybe there's a faster version. So my question is: does anybody know what the fastest Haskell algorithm for generating primes is?

Some other ideas for things to put in this package possibly:
is_prime :: Int -> Bool
nth_prime :: Int -> Int -- or Int -> Integer
prime_factors :: Int -> [Int]
I'm assuming there are faster ways of doing the first 2 than by just simply
looking through all of primes. Someone should also look through Euler - I'm
sure that will generate other ideas of things that could be useful in
playing with primes.
On Tue, Apr 14, 2009 at 8:40 AM, Niemeijer, R.A.
Today I happened to need a large list of prime numbers. Obviously this is a well-known problem, so I figured there would be something on Hackage that I could use. Surprisingly, there isn’t, or if there is it’s not easy to find. Searching for prime or primes on Hackage reveals nothing. Searching for primes on Hayoo gives Codec.Encryption.RSA.NumberTheory, but that uses the inefficient one-liner implementation. The HaskellWiki article on primes (http://www.haskell.org/haskellwiki/Prime_numbers) has a number of implementations, but the faster they get, the longer and uglier they become.
Since it’s such a common problem I’d say it would be a good idea to add a package to Hackage that exports
primes :: [Integer]
and hides the ugly implementation details. Data.Numbers.Primes seems a logical choice for the namespace, but I’m open to suggestions.
The trick then is to find the most efficient implementation of primes. The Haskell wiki article mentions ONeillPrimes.hs as one of the fastest ones, but maybe there’s a faster version. So my question is: does anybody know what the fastest Haskell algorithm for generating primes is?
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

I'd suggest also
primesFrom :: Integer -> [Integer]
and probably a separate function
nextPrime :: Integer -> Integer
2009/4/14 Andrew Wagner
Some other ideas for things to put in this package possibly: is_prime :: Int -> Bool nth_prime :: Int -> Int -- or Int -> Integer prime_factors :: Int -> [Int]
I'm assuming there are faster ways of doing the first 2 than by just simply looking through all of primes. Someone should also look through Euler - I'm sure that will generate other ideas of things that could be useful in playing with primes. On Tue, Apr 14, 2009 at 8:40 AM, Niemeijer, R.A.
wrote: Today I happened to need a large list of prime numbers. Obviously this is a well-known problem, so I figured there would be something on Hackage that I could use. Surprisingly, there isn’t, or if there is it’s not easy to find. Searching for prime or primes on Hackage reveals nothing. Searching for primes on Hayoo gives Codec.Encryption.RSA.NumberTheory, but that uses the inefficient one-liner implementation. The HaskellWiki article on primes (http://www.haskell.org/haskellwiki/Prime_numbers) has a number of implementations, but the faster they get, the longer and uglier they become.
Since it’s such a common problem I’d say it would be a good idea to add a package to Hackage that exports
primes :: [Integer]
and hides the ugly implementation details. Data.Numbers.Primes seems a logical choice for the namespace, but I’m open to suggestions.
The trick then is to find the most efficient implementation of primes. The Haskell wiki article mentions ONeillPrimes.hs as one of the fastest ones, but maybe there’s a faster version. So my question is: does anybody know what the fastest Haskell algorithm for generating primes is?
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
-- Eugene Kirpichov Web IR developer, market.yandex.ru

G'day all.
Quoting Eugene Kirpichov
I'd suggest also
primesFrom :: Integer -> [Integer]
This: primes :: [Integer] isn't as useful as you might think for a library, because it must, by definition, leak an uncontrolled amount of memory. This: primesUpTo :: Integer -> [Integer] is a better interface in that respect. For the number theory library, I went overboard with a bunch of type classes. I don't have the code handy, but this was the sort of thing: class TestableProperty s a | s -> a where is :: s -> a -> Bool data Prime = Prime class TestableProperty Prime Integer where is Prime n = {- ... -} Then you could add instances for Fibonacci or whatever you wanted. Cheers, Andrew Bromage

Unless primesUpTo n goes from highest to lowest prime (ending in 2), I don't see how sharing is possible (in either space or time) between primesUpTo for different n. Is it intended that the primes should therefore be listed in descending order? ajb@spamcop.net wrote:
primes :: [Integer]
isn't as useful as you might think for a library, because it must, by definition, leak an uncontrolled amount of memory. This:
primesUpTo :: Integer -> [Integer]
is a better interface in that respect.

G'day all.
Quoting Dan Weston
Unless primesUpTo n goes from highest to lowest prime (ending in 2), I don't see how sharing is possible (in either space or time) between primesUpTo for different n.
Given that it's a mistake for a library to leak memory, there are essentially three possibilities: Make the implementation impure, move responsibility onto the application, or only retain a finite number of primes between calls. This library: http://andrew.bromage.org/darcs/numbertheory/ only retains primes up to product [2,3,5,7,11,13,17], for several reasons: - It's convenient for the wheel algorithm to store all primes up to the product of the first k primes for some k. - It's ultra-convenient if the stored primes can fit in machine words. - For the types of numbers that we typically care about, it's useful to store at least all primes up to 2^(w/2) where w is the machine word size. - Storing more than a million seemed wrong. Cheers, Andrew Bromage

On Tue, Apr 14, 2009 at 2:47 PM, Andrew Wagner
Some other ideas for things to put in this package possibly: is_prime :: Int -> Bool
I'd also add isProbablePrime using a Miller-Rabin test or somesuch, for use with large numbers. It'd have to be in a monad which supplies randomness, of course. But to start with, I'd just package what I had and put it on Hackage. --Max

You might want to look at Pari/GP ( http://pari.math.u-bordeaux.fr/ ) for ideas of what kind of functions to supply. Also, as a source of ideas for algorithms.
Mike Matsko
----- Original Message -----
From: "Max Rabkin"
Some other ideas for things to put in this package possibly: is_prime :: Int -> Bool
I'd also add isProbablePrime using a Miller-Rabin test or somesuch, for use with large numbers. It'd have to be in a monad which supplies randomness, of course. But to start with, I'd just package what I had and put it on Hackage. --Max _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Niemeijer, R.A. wrote:
Since it’s such a common problem I’d say it would be a good idea to add a package to Hackage that exports
primes :: [Integer]
and hides the ugly implementation details. Data.Numbers.Primes seems a logical choice for the namespace, but I’m open to suggestions.
Excellent idea. Picking the most efficient implementation from the start isn't really necessary; if you find a faster implementation later you can just upload a new version. The API is unlikely to change in such a case anyway. Martijn.

You might want to start with the Sieve of Atkin:
http://en.wikipedia.org/wiki/Sieve_of_Atkin
-Edward
On Tue, Apr 14, 2009 at 8:40 AM, Niemeijer, R.A.
Today I happened to need a large list of prime numbers. Obviously this is a well-known problem, so I figured there would be something on Hackage that I could use. Surprisingly, there isn’t, or if there is it’s not easy to find. Searching for prime or primes on Hackage reveals nothing. Searching for primes on Hayoo gives Codec.Encryption.RSA.NumberTheory, but that uses the inefficient one-liner implementation. The HaskellWiki article on primes (http://www.haskell.org/haskellwiki/Prime_numbers) has a number of implementations, but the faster they get, the longer and uglier they become.
Since it’s such a common problem I’d say it would be a good idea to add a package to Hackage that exports
primes :: [Integer]
and hides the ugly implementation details. Data.Numbers.Primes seems a logical choice for the namespace, but I’m open to suggestions.
The trick then is to find the most efficient implementation of primes. The Haskell wiki article mentions ONeillPrimes.hs as one of the fastest ones, but maybe there’s a faster version. So my question is: does anybody know what the fastest Haskell algorithm for generating primes is?
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Edward Kmett wrote:
You might want to start with the Sieve of Atkin:
Also worth reading _Lazy wheel sieves and spirals of primes_: http://www.cs.york.ac.uk/ftpdir/pub/colin/jfp97lw.ps.gz -- Live well, ~wren

For isPrime you might want to implement the AKS test,
http://en.wikipedia.org/wiki/AKS_primality_test
On Tue, Apr 14, 2009 at 3:05 PM, Edward Kmett
You might want to start with the Sieve of Atkin:
http://en.wikipedia.org/wiki/Sieve_of_Atkin
-Edward
On Tue, Apr 14, 2009 at 8:40 AM, Niemeijer, R.A.
wrote: Today I happened to need a large list of prime numbers. Obviously this is a well-known problem, so I figured there would be something on Hackage that I could use. Surprisingly, there isn’t, or if there is it’s not easy to find. Searching for prime or primes on Hackage reveals nothing. Searching for primes on Hayoo gives Codec.Encryption.RSA.NumberTheory, but that uses the inefficient one-liner implementation. The HaskellWiki article on primes (http://www.haskell.org/haskellwiki/Prime_numbers) has a number of implementations, but the faster they get, the longer and uglier they become.
Since it’s such a common problem I’d say it would be a good idea to add a package to Hackage that exports
primes :: [Integer]
and hides the ugly implementation details. Data.Numbers.Primes seems a logical choice for the namespace, but I’m open to suggestions.
The trick then is to find the most efficient implementation of primes. The Haskell wiki article mentions ONeillPrimes.hs as one of the fastest ones, but maybe there’s a faster version. So my question is: does anybody know what the fastest Haskell algorithm for generating primes is?
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

I've just uploaded a package with some functions I had lying around.
http://hackage.haskell.org/cgi-bin/hackage-scripts/package/Numbers
Am 14.04.2009 um 14:40 schrieb Niemeijer, R.A.:
Today I happened to need a large list of prime numbers. Obviously this is a well-known problem, so I figured there would be something on Hackage that I could use. Surprisingly, there isn’t, or if there is it’s not easy to find. Searching for prime or primes on Hackage reveals nothing. Searching for primes on Hayoo gives Codec.Encryption.RSA.NumberTheory, but that uses the inefficient one-liner implementation. The HaskellWiki article on primes (http:// www.haskell.org/haskellwiki/Prime_numbers) has a number of implementations, but the faster they get, the longer and uglier they become.
Since it’s such a common problem I’d say it would be a good idea to add a package to Hackage that exports
primes :: [Integer]
and hides the ugly implementation details. Data.Numbers.Primes seems a logical choice for the namespace, but I’m open to suggestions.
The trick then is to find the most efficient implementation of primes. The Haskell wiki article mentions ONeillPrimes.hs as one of the fastest ones, but maybe there’s a faster version. So my question is: does anybody know what the fastest Haskell algorithm for generating primes is?
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

On Apr 15, 2009, at 5:27 PM, Adrian Neumann wrote:
I've just uploaded a package with some functions I had lying around.
http://hackage.haskell.org/cgi-bin/hackage-scripts/package/Numbers
This package seems to be missing the source file Data/Numbers/ Primes.hs so I couldn't compare it to my own implementation (see separate announcement). Cheers, Sebastian

Niemeijer, R.A. wrote:
Today I happened to need a large list of prime numbers. Obviously this is a well-known problem, so I figured there would be something on Hackage that I could use. Surprisingly, there isn't, or if there is it's not easy to find.
Since it's such a common problem I'd say it would be a good idea to add a package to Hackage that exports
primes :: [Integer]
and hides the ugly implementation details.
+1 except that exporting the potentially infinite list of primes is problematic in that it may become a memory leak. I'd suggest to export two versions primes :: [Integer] primes' :: () -> [Integer] for casual (i.e. throwaway program to solve a Project Euler problem) and for memory aware use respectively. Regards, apfelmus -- http://apfelmus.nfshost.com
participants (14)
-
Adrian Neumann
-
ajb@spamcop.net
-
Andrew Wagner
-
Dan Weston
-
Edward Kmett
-
Eugene Kirpichov
-
Heinrich Apfelmus
-
Lennart Augustsson
-
Martijn van Steenbergen
-
Max Rabkin
-
Michael Matsko
-
Niemeijer, R.A.
-
Sebastian Fischer
-
wren ng thornton