Quick question for a slow program

Hello, I was just brushing my haskell-fu skills writing a solution for Google Treasure Hunt Problem 4. Hers is what it looks like:
primes = sieve [2..] where sieve (p:xs) = p : sieve [x | x <- xs, x `mod` p /= 0]
sumOf n l = sum (take n l) : sumOf n (tail l)
find l = foldl1 aux l where aux (x:xs) (y:ys) | x == y = x : aux xs ys | x < y = aux xs (y:ys) | x > y = aux (x:xs) ys
puzzle = find (reverse [primes, p7, p17, p41, p541]) where p7 = sumOf 7 primes p17 = sumOf 17 primes p41 = sumOf 41 primes p541 = sumOf 541 primes
main = do mapM (\x -> putStrLn $ show x) puzzle
While the code is quite readable and straight forward it is as slow as tortoise with four legs broken. What optimizations would you suggest, while still keeping the code clear and highlevel? Thank you in advance. Cheers. -- Slavomir Kaslev

On Sat, Jun 7, 2008 at 10:26 AM, Slavomir Kaslev
Hello,
I was just brushing my haskell-fu skills writing a solution for Google Treasure Hunt Problem 4. Hers is what it looks like:
primes = sieve [2..] where sieve (p:xs) = p : sieve [x | x <- xs, x `mod` p /= 0]
Read this: www.cs.hmc.edu/~oneill/papers/Sieve-JFP.pdf This is probably the biggest culprit in your code. :-)

On Sat, 7 Jun 2008 12:26:17 +0300
"Slavomir Kaslev"
I was just brushing my haskell-fu skills writing a solution for Google Treasure Hunt Problem 4. Hers is what it looks like:
primes = sieve [2..] where sieve (p:xs) = p : sieve [x | x <- xs, x `mod` p /= 0]
sumOf n l = sum (take n l) : sumOf n (tail l)
find l = foldl1 aux l where aux (x:xs) (y:ys) | x == y = x : aux xs ys | x < y = aux xs (y:ys) | x > y = aux (x:xs) ys
puzzle = find (reverse [primes, p7, p17, p41, p541]) where p7 = sumOf 7 primes p17 = sumOf 17 primes p41 = sumOf 41 primes p541 = sumOf 541 primes
main = do mapM (\x -> putStrLn $ show x) puzzle
While the code is quite readable and straight forward it is as slow as tortoise with four legs broken. What optimizations would you suggest, while still keeping the code clear and highlevel?
While I can't quite prove it, I surmise find is wasting a lot of time tracking down numbers which are sums of three or four of those lists before continuing. Here's mine:
sliding n = map (sum . take n) $ tails primes
merge (x:xs) (y:ys) | x < y = x:merge xs (y:ys) | otherwise = y:merge (x:xs) ys
four = filter (\l -> length l == 5) $ group $ foldr1 merge $ map sliding [1,5,43,107,689]
In my original implementation I used an isPrime test at the end, but I like your approach better (hence the 1 in map sliding). Does this still count as "clear and highlevel"? :) Dries Harnie

Am Samstag, 7. Juni 2008 11:26 schrieb Slavomir Kaslev:
Hello,
I was just brushing my haskell-fu skills writing a solution for Google
Treasure Hunt Problem 4. Hers is what it looks like:
primes = sieve [2..] where sieve (p:xs) = p : sieve [x | x <- xs, x `mod` p /= 0]
That alone breaks at least three of the tortoise's legs. Simple trial division: primes = 2:3:filter isPrime [5,7 .. ] isPrime n | n < 2 = False | n < 4 = True | even n = False | otherwise = go (tail primes) where r = floor $ sqrt (fromIntegral n + 0.5) go (p:ps) = (r < p) || (n `mod` p /= 0) && go ps is orders of magnitude faster. A really good prime generator wins a lot.
sumOf n l = sum (take n l) : sumOf n (tail l)
This is also not really good, sumOf n l = zipWith (-) (drop n sms) sms where sms = scanl (+) 0 l is a bit faster, specialising primeSums = scanl (+) 0 primes sumOfPrimes n = zipWith (-) (drop n primeSums) primeSums a bit more. I don't see more improvements directly.
find l = foldl1 aux l where aux (x:xs) (y:ys) | x == y = x : aux xs ys
| x < y = aux xs (y:ys) | x > y = aux (x:xs) ys
puzzle = find (reverse [primes, p7, p17, p41, p541]) where p7 = sumOf 7 primes p17 = sumOf 17 primes p41 = sumOf 41 primes p541 = sumOf 541 primes
main = do mapM (\x -> putStrLn $ show x) puzzle
While the code is quite readable and straight forward it is as slow as tortoise with four legs broken. What optimizations would you suggest, while still keeping the code clear and highlevel?
Thank you in advance.
Cheers.

The second prime generator on this page http://www.haskell.org/haskellwiki/Prime_numbers is quick and easy. I keep it nearby for all those sudden attacks of needing to solve yet another projecteuler problem. -ljr Slavomir Kaslev wrote:
Hello,
I was just brushing my haskell-fu skills writing a solution for Google Treasure Hunt Problem 4. Hers is what it looks like:
primes = sieve [2..] where sieve (p:xs) = p : sieve [x | x <- xs, x `mod` p /= 0]
sumOf n l = sum (take n l) : sumOf n (tail l)
find l = foldl1 aux l where aux (x:xs) (y:ys) | x == y = x : aux xs ys | x < y = aux xs (y:ys) | x > y = aux (x:xs) ys
puzzle = find (reverse [primes, p7, p17, p41, p541]) where p7 = sumOf 7 primes p17 = sumOf 17 primes p41 = sumOf 41 primes p541 = sumOf 541 primes
main = do mapM (\x -> putStrLn $ show x) puzzle
While the code is quite readable and straight forward it is as slow as tortoise with four legs broken. What optimizations would you suggest, while still keeping the code clear and highlevel?
Thank you in advance.
Cheers.

Lanny Ripple wrote:
The second prime generator on this page
http://www.haskell.org/haskellwiki/Prime_numbers
is quick and easy. I keep it nearby for all those sudden attacks of needing to solve yet another projecteuler problem.
The second prime sieve did not create an implicit heap as advertised. I've fixed that and also cleaned up the page a bit, moving this sieve to the section "Implicit Heap". Regards, apfelmus

At least when I teased apart why the first one worked it looked heap-like. Each step of the foldr pulled off the smallest nonprime and merged the next two lists guaranteeing that the next smallest nonprime would be at the head of the next step. Can't argue with results though. The version you have up is about twice as fast as the old one (if a bit harder to read). -ljr apfelmus wrote:
Lanny Ripple wrote:
The second prime generator on this page
http://www.haskell.org/haskellwiki/Prime_numbers
is quick and easy. I keep it nearby for all those sudden attacks of needing to solve yet another projecteuler problem.
The second prime sieve did not create an implicit heap as advertised. I've fixed that and also cleaned up the page a bit, moving this sieve to the section "Implicit Heap".
Regards, apfelmus
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Lanny Ripple wrote:
At least when I teased apart why the first one worked it looked heap-like. Each step of the foldr pulled off the smallest nonprime and merged the next two lists guaranteeing that the next smallest nonprime would be at the head of the next step.
Well, there is heap and heap. It's true that the tree of calls to merge fulfills the heap property, see the following diagrams: merge before evaluation / \ 4 merge : / \ 6 9 merge : : / \ 8 12 25 merge : ... : / \ ... 30 49 ... : : ... ... 4 first element : merge / \ 6 9 : : 8 merge : / \ ... 12 25 : : ... merge / \ 30 49 : : ... merge / \ ... ... 4 first and second element : 6 : merge / \ 8 9 : : ... merge / \ 12 25 : : ... merge / \ 30 49 : : ... merge / \ ... ... and so on. But as you can see, the heap is not balanced, foldr1 merge only generates a linear chain of merge nodes. A balanced tree like merge / \ merge merge / \ / \ 4 9 25 49 : : : : ... ... ... ... would be better, except that we need a variant that with an infinite number of leaves. The function foldTree builds such a tree. There is also the complication that the heap "bites its own tail" in that the multiples of a prime, and hence the heap, are not available until the prime itself has been calculated from the heap. The People a data structure solves this. Regards, apfelmus
participants (6)
-
apfelmus
-
Daniel Fischer
-
David MacIver
-
Dries Harnie
-
Lanny Ripple
-
Slavomir Kaslev