Claus> None of which is satisfactory. You might also want to add
   Claus> yourself to this ticket:

   Claus>    "index out of range" error message regression
   Claus> http://hackage.haskell.org/trac/ghc/ticket/2669

How do I do that?

Ghc Trac's idea of voting is by adding yourself to the cc, so that
tickets can be sorted by length of cc list:

   http://hackage.haskell.org/trac/ghc/report/17

That is often subverted by closing tickets as duplicate/related,
without transferring the cc list to the one ticket that is kept;-)

Apart from the immediate bug of not getting any information,
there's also the more general issue of wanting information about
the call site (who called which operation, leading to the exception).

A solution to that issue has been sought for a long time, but there
seem to be so many options that the discussion has slowed down to a halt:

   Lexical call site string
   http://hackage.haskell.org/trac/ghc/ticket/960

   Maintaining an explicit call stack
   http://hackage.haskell.org/trac/ghc/wiki/ExplicitCallStack

Using your own wrappers to give you the missing information
is probably the best short-term workaround, but it is no fun.
Something like this, perhaps:

   import qualified Data.Array.IArray as A
   import Control.Exception

   arr ! index = mapException (addErrorInfo (" ! "++show index)) $ arr A.! index
   arr // idxs = mapException (addErrorInfo (" // "++show idxs)) $ arr A.// idxs

   addErrorInfo info (ErrorCall str) = ErrorCall (str++":"++info)

   test1 i = (A.array (1,5) [(i,i)|i<-[1..5]] :: A.Array Int Int) ! i
   test2 i = (A.array (1,5) [(i,i)|i<-[1..5]] :: A.Array Int Int) // [(i,0)]

   *Main> test1 0
   *** Exception: Error in array index: ! 0
   *Main> test1 3
   3
   *Main> test1 8
   *** Exception: Error in array index: ! 8
   *Main> test2 0
   array *** Exception: Error in array index: // [(0,0)]
   *Main> test2 4
   array (1,5) [(1,1),(2,2),(3,3),(4,0),(5,5)]
   *Main> test2 7
   array *** Exception: Error in array index: // [(7,0)]

Claus

_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe

Reply via email to