[Haskell-cafe] Re: FASTER primes

Will Ness will_n48 at yahoo.com
Wed Jan 6 09:24:51 EST 2010


Will Ness <will_n48 <at> yahoo.com> writes:

> 
> Daniel Fischer <daniel.is.fischer <at> web.de> writes:
> 
> > Am Dienstag 05 Januar 2010 14:49:58 schrieb Will Ness:
> > >
> > >   euler ks@(p:rs) = p : euler (rs `minus` map (*p) ks)
> > >   primes = 2:euler [3,5..]
> > >
> > >
> 
> Re-write:
> 
>  primes  = euler $ rollFrom [2] 1
>   = 2:euler ( rollFrom [3] 1 `minus` map(2*) (rollFrom [2] 1)) )
>               rollFrom [3,4] 2 `minus` rollFrom [4] 2
>                     -- rollFrom [3] 2 --
>   = 2:3:euler (rollFrom [5] 2 `minus` map(3*) (rollFrom [3] 2))
>                rollFrom [5,7,9] 6 `minus` rollFrom [9] 6
>                     -- rollFrom [5,7] 6 --
>   = 2:3:5:euler (rollFrom [7,11] 6 `minus` rollFrom [25,35] 30)
>                    [7,11, 13,17, 19,23, 25,29, 31,35] 30
>                  -- rollFrom [7,11,13,17,19,23,29,31] 30 --
>   = .....
> 

correction:

    where
      rollOnce (x:xs) by = (x, xs ++ [x+by])
      rollFrom xs by = concat $ iterate (map (+ by)) (xs)
      multRoll xs@(x:_) by p = takeWhile (< (x+p*by)) $ rollFrom xs by

 
> so, reifying, we get
> 
>  data Roll a = Roll [a] a
> 
>  rollOnce (Roll (x:xs) by) = (x,Roll (xs ++ [x+by]) by)
>  rollFrom (Roll xs by) = concat $ iterate (map (+ by)) (xs)
>  multRoll r@(Roll (x:_) by) p 
>   = Roll (takeWhile (< (x+p*by)) $ rollFrom r) (by*p)
> 
>  primes  = euler $ Roll [2] 1
>  euler r@(Roll xs _)
>         = x:euler (Roll (mxs `minus` map (x*) xs)  mby)
>   where  
>    (x,r') = rollOnce r
>    (Roll mxs mby) = multRoll r' x
> 

There's much extra primes pre-calculated inside the Roll, of course.

For any (Roll xs@(x:_) _),  (takeWhile (< x*x) xs) are all primes too.

When these are used, the code's complexity is around O(n^1.5), and it runs 
about 1.8x slower than Postponed Filters.

The "faithful sieve"'s empirical complexity is above 2.10..2.25 and rising. So 
it might not be exponential, bbut is worse than power it seems anyway.







More information about the Haskell-Cafe mailing list