Ackermann Function Memoization, GHC Weird Output or Bug?

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

On Mar 13, 2008, at 23:47 , Donnie Jones wrote:
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?
Per http://www.haskell.org/ghc/docs/latest/html/libraries/base/ Control-Exception.html: "NOTE: GHC currently does not throw ArrayExceptions" -- brandon s. allbery [solaris,freebsd,perl,pugs,haskell] allbery@kf8nh.com system administrator [openafs,heimdal,too many hats] allbery@ece.cmu.edu electrical and computer engineering, carnegie mellon university KF8NH

Here's the bug:
{-# INLINE safeIndex #-}
safeIndex :: Ix i => (i, i) -> Int -> i -> Int
safeIndex (l,u) n i = let i' = unsafeIndex (l,u) i
in if (0 <= i') && (i' < n)
then i'
else error "Error in array index"
unsafeIndex here is just a function which transforms indices into Int
indices into the flat array and does no checking of validity. Then
safeIndex simply checks if the result is nonnegative and less than the
size of the array. Whoops! The actual test to see if the index was
valid in the first place didn't actually get performed!
- Cale
On 14/03/2008, Eric Mertens
Smaller example of this behavior:
array ((0,0),(1,1)) [((1,1),6)] ! (0,3) 6
--
Eric Mertens
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Hello,
It seems this bug has already been submitted:
http://hackage.haskell.org/trac/ghc/ticket/2120
Thanks for the help.
__
Donnie Jones
On 3/14/08, Cale Gibbard
Here's the bug:
{-# INLINE safeIndex #-} safeIndex :: Ix i => (i, i) -> Int -> i -> Int safeIndex (l,u) n i = let i' = unsafeIndex (l,u) i in if (0 <= i') && (i' < n) then i' else error "Error in array index"
unsafeIndex here is just a function which transforms indices into Int indices into the flat array and does no checking of validity. Then safeIndex simply checks if the result is nonnegative and less than the size of the array. Whoops! The actual test to see if the index was valid in the first place didn't actually get performed!
- Cale
On 14/03/2008, Eric Mertens
wrote: Smaller example of this behavior:
array ((0,0),(1,1)) [((1,1),6)] ! (0,3) 6
--
Eric Mertens
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
participants (4)
-
Brandon S. Allbery KF8NH
-
Cale Gibbard
-
Donnie Jones
-
Eric Mertens