[Haskell-cafe] A tale of Project Euler

Andrew Coppin andrewcoppin at btinternet.com
Tue Nov 27 15:55:48 EST 2007


On the other hand, I must relay to you how much fun I had with certain 
other problems.

For example, problem #12. I started with this:

  triangles = scanl1 (+) [1..]

  divisors n = length $ filter (\x -> n `mod` x == 0) [1..n]

  answer = head $ dropWhile (\n -> divisors n < 500) triangles

Sadly, this is *absurdly* slow. I gave up after about 5 minutes of 
waiting. It had only scanned up to T[1,200]. Then I tried the following:

triangles = scanl1 (+) [1..]

primes :: [Word32]
primes = seive [2..]
  where
    seive (p:xs) = p : seive (filter (\x -> x `mod` p > 0) xs)

factors = work primes
  where
    work (p:ps) n =
      if p > n
        then []
        else
          if n `mod` p == 0
             then p : work (p:ps) (n `div` p)
             else work ps n

count_factors n =
  let
    fs = factors n
    fss = group fs
  in product $ map ((1+) . length) fss

answer = head $ dropWhile (\n -> count_factors n < 500) triangles

By looking only at *prime* divisors and then figuring out how many 
divisors there are in total (you don't even have to *compute* what they 
are, just *count* them!), I was able to get the correct solution in 
UNDER ONE SECOND! o_O :-D :^]

Now how about that for fast, eh?

(Actually, having solved it I discovered there's an even better way - 
apparently there's a relationship between the number of divisors of 
consecutive triangular numbers. I'm too noobish to understand the number 
theory here...)


Similarly, problem 24 neatly illustrates everything that is sweet and 
pure about Haskell:

  choose [x] = [(x,[])]
  choose (x:xs) = (x,xs) : map (\(y,ys) -> (y,x:ys)) (choose xs)

  permutations [x] = [[x]]
  permutations xs = do
    (x1,xs1) <- choose xs
    xs2 <- permutations xs1
    return (x1 : xs2)

  answer = (permutations "0123456789") !! 999999

This finds the answer in less than 3 seconds. And it is beautiful to 
behold. Yes, there is apparently some more sophisticated algorithm than 
actually enumerating the permutations. But I love the way I threw code 
together in the most intuitive way that fell into my head, and got a 
fast, performant answer. Perfection! :-)



More information about the Haskell-Cafe mailing list