Finding primes using a primes map with Haskell and Hugs98

Shlomi Fish shlomif@vipe.technion.ac.il
Wed, 20 Dec 2000 16:02:23 +0200 (IST)


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 (||) False (2,n) multList
> | 	multList    = [(m,True) | j <- [2 .. n `div` 2], m <- 
> | multiples j]
> | 	multiples j = takeWhile (n>=) [k*j | k <- [2..]]
> 
> This style is definitely the way to go.  Haskell does badly
> if you update an array one index at a time.  
> 

Unfortunately, it seems that this style is not the way to go. This program
cannot scale beyond 5000 while my second program scales beyond 30000. I'm
not saying 30000 is a good limit, but 5000 is much worse.

Anyway, somebody who contacted me in private suggested the following
method. It is a similiar algorithm which uses a list instead of an array.


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
             remove what (a:as) | what > how_much = (a:as)
                                | a < what = a:(remove what as)
                                | a == what = (remove (what+step) as)
                                | a > what = a:(remove (what+step) as)
             remove what [] = []
             step = (if (p == 2) then p else (2*p)) 
         sieve [] = []
         mybound = ceiling(sqrt(fromIntegral how_much))

I optimized it quite a bit, but the concept remained the same. 

Anyway, this code can scale very well to 100000 and beyond. But it's not
exactly the same algorithm.

I also implemented this algorithm in perl, and I can send it in person if
anybody requests it.

I'll try to see how the two programs run in GHC and HBC.

Regards,

	Shlomi Fish




> Remember that arrays can be recursive.  Here's a definition
> of Fibonacci for example; you can probably adapt it for primes
> 
> fibs :: Int -> Array Int Int
> -- If a = fibs n, then a!i is fib(i), for i<=n.
> fibs n = a
>           where
> 	 a = array (1,n) ([(1,1),(2,1)] ++ [(i,a!(i-1) + a!(i-2) | i <-
> [3..n]])
> 		-- Notice that a is recursive
> 
> Simon
> 
> _______________________________________________
> Haskell mailing list
> Haskell@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell
> 



----------------------------------------------------------------------
Shlomi Fish        shlomif@vipe.technion.ac.il 
Home Page:         http://t2.technion.ac.il/~shlomif/
Home E-mail:       shlomif@techie.com

The prefix "God Said" has the extraordinary logical property of 
converting any statement that follows it into a true one.