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

Donnie Jones donnie at darthik.com
Fri Mar 14 15:35:02 EDT 2008


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 <cgibbard at gmail.com> wrote:
>
> 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 <emertens at gmail.com> 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 at haskell.org
> >  http://www.haskell.org/mailman/listinfo/haskell-cafe
> >
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: http://www.haskell.org/pipermail/haskell-cafe/attachments/20080314/b14bab36/attachment.htm


More information about the Haskell-Cafe mailing list