diff --git a/Data/Array/Base.hs b/Data/Array/Base.hs
index f9cc0c5b40ca8fe95c47c7817f0fca819d81a7f0..52e4c18dad79a227dd593f9966ec888becba9165 100644
--- a/Data/Array/Base.hs
+++ b/Data/Array/Base.hs
@@ -108,10 +108,11 @@ safeRangeSize (l,u) = let r = rangeSize (l, u)
{-# INLINE safeIndex #-}
safeIndex :: Ix i => (i, i) -> Int -> i -> Int
-safeIndex (l,u) n i = let i' = unsafeIndex (l,u) i
+safeIndex (l,u) n i = let i' = index (l,u) i
in if (0 <= i') && (i' < n)
then i'
- else error "Error in array index"
+ else error ("Error in array index; " ++ show i' ++
+ " not in range [0.." ++ show n ++ ")")
{-# INLINE unsafeReplaceST #-}
unsafeReplaceST :: (IArray a e, Ix i) => a i e -> [(Int, e)] -> ST s (STArray s i e)
diff --git a/tests/Makefile b/tests/Makefile
new file mode 100644
index 0000000000000000000000000000000000000000..6a0abcf1cf7f79f47ac3db01eec1eb9ff6ff7b45
--- /dev/null
+++ b/tests/Makefile
@@ -0,0 +1,7 @@
+# This Makefile runs the tests using GHC's testsuite framework. It
+# assumes the package is part of a GHC build tree with the testsuite
+# installed in ../../../testsuite.
+
+TOP=../../../testsuite
+include $(TOP)/mk/boilerplate.mk
+include $(TOP)/mk/test.mk
diff --git a/tests/T2120.hs b/tests/T2120.hs
new file mode 100644
index 0000000000000000000000000000000000000000..82150ef1860e49b6bda594187c3132b9c29a7097
--- /dev/null
+++ b/tests/T2120.hs
@@ -0,0 +1,17 @@
+
+module Main (main) where
+
+import Control.Exception
+import Data.Array.IArray
+import Prelude hiding (catch)
+
+a :: Array Int Int
+a = listArray (1,4) [1..4]
+
+b :: Array (Int,Int) Int
+b = listArray ((0,0), (3,3)) (repeat 0)
+
+main :: IO ()
+main = do print (a ! 5) `catch` \e -> print (e :: SomeException)
+ print (b ! (0,5)) `catch` \e -> print (e :: SomeException)
+
diff --git a/tests/T2120.stdout b/tests/T2120.stdout
new file mode 100644
index 0000000000000000000000000000000000000000..518a3e883f19dab10041a7c92919a2bdd85b3365
--- /dev/null
+++ b/tests/T2120.stdout
@@ -0,0 +1,2 @@
+Ix{Int}.index: Index (5) out of range ((1,4))
+Error in array index
diff --git a/tests/all.T b/tests/all.T
new file mode 100644
index 0000000000000000000000000000000000000000..9814b76dd898ee8c269c3594aa9062160044b781
--- /dev/null
+++ b/tests/all.T
@@ -0,0 +1,3 @@
+
+test('T2120', normal, compile_and_run, [''])
+