[Haskell-cafe] [Newbie] Problem with Data.Map (or something else ?)

Bruno Carnazzi bcarnazzi at gmail.com
Mon Mar 31 11:51:43 EDT 2008


   Dears Haskellers,

As an Haskell newbie, I'm learning Haskell by trying to resolve Euler
Project problems (http://projecteuler.net/ ). I'm hanging on problem
14 (Collatz problem).

I've written the following program... Which does not end in a reasonable time :(
My algorithm seems ok to me but I see that memory consumption is gigantic...
Is this a memory problem with Data.Map ? Or an infinite loop ? (Where ?)
In a more general way, how can I troubleshoot these kind of problem ?

Here's the code :

import qualified Data.List as List
import qualified Data.Map as Map

f n | even n = n `div` 2
    | otherwise = 3 * n + 1

chain m n =
    let chain' cn cm | Map.member cn m = Map.map (+ (m Map.! cn)) cm
                     | otherwise = chain' (f cn) $! Map.insert cn 1
(Map.map (+1) cm)
    in chain' n Map.empty

chains n = List.foldl' (\m i -> Map.union m (chain m i))
(Map.singleton 1 1) [2..n]

maxCollatz c1@(_,l1) c2@(_,l2) | l1 < l2 = c2
                               | otherwise = c1

maxChain = List.foldl' maxCollatz (0,0) . Map.toList . chains

main =
    let n = 1000000
    in putStrLn $ show $ maxChain n

Hope someone can help me, I really don't see what is th problem...

Best regards,

Bruno.


More information about the Haskell-Cafe mailing list