Hello!
On Wed, Dec 20, 2000 at 04:02:23PM +0200, Shlomi Fish wrote:
> [...]
> primes :: Int -> [Int]
> primes how_much = sieve [2..how_much] where
> sieve (p:x) =
> p : (if p <= mybound
> then sieve (remove (p*p) x)
> else x) where
>
> There are numerous ways of optimising sieving for primes, none of which
> have much to do with this list. For example, two suggestions:
> (1) for each k modulo 2*3*5*7, if k is divisible by 2/3/5 or 7, ignore, otherwise
> sieve separately for this k on higher primes. (Or you might use prod
There are numerous ways of optimising sieving for primes, none of which have much
to do with this list. For example, two suggestions:
(1) for each k modulo 2*3*5*7, if k is divisible by 2/3/5 or 7, ignore, otherwise
sieve separately for this k on higher primes. (Or you might use products of
On Tue, 19 Dec 2000, Simon Peyton-Jones wrote:
> | Another way to do this is to compute the final array directly,
> | instead of computing successive versions of the array:
> |
> | import Array
> | primes n = [ i | i <- [2 ..n], not (primesMap ! i)] where
> | primesMap = accumArray
| Another way to do this is to compute the final array directly,
| instead of computing successive versions of the array:
|
| import Array
| primes n = [ i | i <- [2 ..n], not (primesMap ! i)] where
| primesMap = accumArray (||) False (2,n) multList
| multList= [(m,True)
On Sun 17 Dec, Adrian Hey wrote:
> You can use a variation of this algorithm with lazy lists..
>
> primes = 2:(get_primes [3,5..])
> get_primes (x:xs) = x:(get_primes (strike (x+x) (x*x) xs))
^^^
Whoops,
Your algorithm seems to be based on the following idea:
calculate the non-primes and derive the primes from
them by calculating the set difference of the natural numbers
and the non-primes.
A naive implementation of this idea can be found as
primes'
in the attachached file. The function us
On Fri 15 Dec, Shlomi Fish wrote:
> There is a different algorithm which keeps a boolean map which tells whether
> the number at that position is prime or not. At start it is initialized to all
> trues. The algorithm iterates over all the numbers from 2 to the square root
> of the desired bound, a
Shlomi Fish wrote:
> As some of you may know, a Haskell program that prints all the primes can be
> as short as the following:
>
> primes = sieve [2.. ] where
> sieve (p:x) = p : sieve [ n | n <- x, n `mod` p > 0 ]
>
> Now, this program roughly corresponds to the following perl program:
Hi!
As some of you may know, a Haskell program that prints all the primes can be
as short as the following:
primes = sieve [2.. ] where
sieve (p:x) = p : sieve [ n | n <- x, n `mod` p > 0 ]
Now, this program roughly corresponds to the following perl program:
## SNIP SNIP #
#
10 matches
Mail list logo