
Hello, I'm learning Haskell, so I was attempting memoization based upon the Fibonacci examples but for the Ackermann function. In my tests, I found what seems to be truncated output. See my comments at the end of the code for the test cases and output. ### Begin Code ### module Main where import Data.Array main = do let m = 3 n = 1 a = ackermann_mem m n putStrLn("Ackermann-mem " ++ show m ++ " " ++ show n ++ " = " ++ show a) -- Functions. -- Based upon examples from: -- http://reddit.com/r/programming/info/16ofr/comments) http://reddit.com/r/programming/info/16ofr/comments%29 tabulate bounds f = array bounds [(i, f i) | i <- range bounds] dp bounds f = (memo!) where memo = tabulate bounds (f (memo!)) -- Trying to apply memoization function to Ackermann. ackermann_mem m n = dp ((0,0), (30, 1000)) ack (m, n) where ack rec (0, n) = n + 1 ack rec (m, 0) = rec (m - 1, 1) ack rec (m, n) = rec (m - 1, rec (m, n - 1)) {- Test cases: ackermann_mem 4 1 = 533 -- when using (30, 1000) as upper bound. ackermann_mem 4 1 = 5533 -- when using (30, 10000) as upper bound. ackermann_mem 4 1 = 65533 -- when using (30, 100000) as upper bound. <--- correct answer! -} ### End Code ### It seems if I don't choose an upper bound pair for (m,n) that is large enough I get truncated output for the answer, instead of GHC giving me an array index exception... This behavior seems very odd to me, can someone explain? Or is this a bug? Thank you. __ Donnie Jones