[Haskell-beginners] Using my first map instance

Darren Grant therealkludgy at gmail.com
Fri Sep 28 03:22:56 CEST 2012


Hi all,

I'm working on project euler problem 14, whose solution is the maximum
Collatz chain length for all natural numbers less than 1-million.

The naive approach takes too long to execute:

  collatz 1 = [1]
  collatz n = let next x | even x = x `div` 2 | otherwise = 3*x+1 in
n:collatz (next n)
  result = maximum [length (collatz x) | x <- [1..999999]]

I know there are a handful of approaches to take to reduce computation
time, but in this case I am focusing on exploiting fast recollection
of previously computed sub-chain lengths in a map.


So I wrote the following instead:

  import qualified Data.Map as M

  type CollatzSubMap = M.Map Int [Int]

  collatz :: (Int, CollatzSubMap) -> ([Int], CollatzSubMap)
  collatz (1,m) = ([1], m)
  collatz (n,m) = let next x | even x = x `div` 2 | otherwise = 3*x+1 in
		case M.lookup n m of
			Nothing -> let (ns,m') = collatz (next n, m) in (n:ns, M.insert n (n:ns) m')
			Just ns -> (ns,m)

  result = maximum [length $ fst $ collatz (x, M.empty) | x <-
[1..999999] :: [Int]]


Where I'm currently stumped is in feeding the resulting map from one
call to collatz into the next iteration in the list comprehension;
that M.empty should carry the end result of previous iterations.

Can anyone point me in the right direction? Other criticisms of the
code are also welcome.



Cheers,
Darren



More information about the Beginners mailing list