User defined Ix instances potentially unsafe

Matt Harden matth@mindspring.com
Tue, 01 May 2001 20:42:34 -0500


Sorry if this has been reported before.

I shouldn't be able to crash ghc or hugs without using any "unsafe"
features, right?  Well, here 'tis:

> module CrashArray where
> 
> import Array
> import Ix
> 
> newtype CrashIx = CrashIx Int deriving (Ord, Eq, Show)
> 
> instance Enum CrashIx where
>    toEnum   x = (CrashIx x)
>    fromEnum (CrashIx x) = x
> 
> instance Ix CrashIx where
>    inRange (_,_) _ = True
>    index (_,_) (CrashIx x) = x
>    range (x,y) = [x..y]
> 
> myArray = listArray (CrashIx 0, CrashIx 0) [0]
> crash = myArray ! (CrashIx maxBound)


In ghci-5.00, I get a segfault and hugs-feb-2000 says:
   INTERNAL ERROR: Error in graph

Now, admittedly my Ix instance is broken, but I don't think I should be
able to segfault the interpreter.

Unfortunately, I think the only way to fix this without changing the
Library Report would be to add another layer of range checking to the
array implementation.  Bleh.  Note also that the (inefficient)
implementation in the report wouldn't crash, but would get the "wrong"
error: "Undefined array element" instead of "Index out of range".

I think we might describe this as a bug in the Library Report, rather
than in any particular Haskell implementation.

Enjoy!

Matt Harden