Re: [Haskell-cafe] Ackermann Function Memoization, GHC Weird Output or Bug?

2008-03-14 Thread 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

Re: [Haskell-cafe] Ackermann Function Memoization, GHC Weird Output or Bug?

2008-03-14 Thread 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

Re: [Haskell-cafe] Ackermann Function Memoization, GHC Weird Output or Bug?

2008-03-14 Thread Donnie Jones
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 [EMAIL PROTECTED] wrote: Here's the bug: {-# INLINE safeIndex #-} safeIndex :: Ix i = (i, i) - Int - i - Int safeIndex (l,u) n

[Haskell-cafe] Ackermann Function Memoization, GHC Weird Output or Bug?

2008-03-13 Thread Donnie Jones
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

Re: [Haskell-cafe] Ackermann Function Memoization, GHC Weird Output or Bug?

2008-03-13 Thread Brandon S. Allbery KF8NH
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