Given the linear dependencies in prime number generation, shy of using a probabilistic sieving method, I'm not sure that it's possible to hope for any kind of parallel number generation. All you are going to do is for yourself to eat the cost of synchronisation for no gain.

Ben

On Fri May 16 2014 at 16:53:38, Norbert Melzer <timmelzer@gmail.com> wrote:
Hi there!

I am trying to enhence the speed of my Project Euler solutions…

My original function is this:

```haskell
problem10' ::  Integer
problem10' = sum $ takeWhile (<=2000000) primes
  where
    primes                  = filter isPrime possiblePrimes
    isPrime n               = n == head (primeFactors n)
    possiblePrimes          = (2:3:concat [ [6*pp-1, 6*pp+1] | pp <- [1..] ])
    primeFactors m          = pf 2 m
    pf n m | n*n > m        = [m]
           | n*n       == m  = [n,n]
           | m `mod` n == 0  = n:pf n (m `div` n)
           | otherwise      = pf (n+1) m
```

Even if the generation of primes is relatively slow and could be much better, I want to focus on parallelization, so I tried the following:

```haskell
parFilter :: (a -> Bool) -> [a] -> [a]
parFilter _ [] = []
parFilter f (x:xs) =
  let px = f x
      pxs = parFilter f xs
  in par px $ par pxs $ case px of True -> x : pxs
                                   False -> pxs

problem10' ::  Integer
problem10' = sum $ takeWhile (<=2000000) primes
  where
    primes                  = parFilter isPrime possiblePrimes
    isPrime n               = n == head (primeFactors n)
    possiblePrimes          = (2:3:concat [ [6*pp-1, 6*pp+1] | pp <- [1..] ])
    primeFactors m          = pf 2 m
    pf n m | n*n > m        = [m]
           | n*n       == m  = [n,n]
           | m `mod` n == 0  = n:pf n (m `div` n)
           | otherwise      = pf (n+1) m
```

This approach was about half as slow as the first solution (~15 seconds old, ~30 the new one!).

Trying to use `Control.Parallel.Strategies.evalList` for `possiblePrimes` resulted in a huge waste of memory, since it forced to generate an endless list, and does not stop…

Trying the same for `primeFactors` did not gain any speed, but was not much slower at least, but I did not expect much, since I look at its head only…

Only thing I could imagine to parallelize any further would be the takeWhile, but then I don't get how I should do it…

Any ideas how to do it?

TIA
Norbert

_______________________________________________
Beginners mailing list
Beginners@haskell.org
http://www.haskell.org/mailman/listinfo/beginners