diff --git a/ghc/tests/lib/should_run/Makefile b/ghc/tests/lib/should_run/Makefile
index 7ba97000a7d01d2f40ec112efd0b3767e6a93f77..5d86a0cea686400c0bf8a464451aedb7732a28ee 100644
--- a/ghc/tests/lib/should_run/Makefile
+++ b/ghc/tests/lib/should_run/Makefile
@@ -1,5 +1,5 @@
 #-----------------------------------------------------------------------------
-# $Id: Makefile,v 1.6 1998/08/14 13:02:00 simonm Exp $
+# $Id: Makefile,v 1.7 1998/10/08 11:52:34 simonm Exp $
 
 TOP = ../..
 include $(TOP)/mk/boilerplate.mk
@@ -9,7 +9,8 @@ SRC_HC_OPTS += -dcore-lint
 
 packedstring001_HC_OPTS = -syslib misc
 exceptions001_HC_OPTS   = -fglasgow-exts
-stableptr002_HC_OPTS   = -fglasgow-exts
+stableptr002_HC_OPTS    = -fglasgow-exts
+list001_HC_OPTS         = -fglasgow-exts
 
 stableptr001_RUNTEST_OPTS = +RTS -K4m
 dynamic001_HC_OPTS = -syslib exts
diff --git a/ghc/tests/lib/should_run/exceptions001.hs b/ghc/tests/lib/should_run/exceptions001.hs
index 38411a81b49680d947c9a34f85cd3144842e50c7..fa38c0fc2b2f6332a06078fad226c74d695a28e7 100644
--- a/ghc/tests/lib/should_run/exceptions001.hs
+++ b/ghc/tests/lib/should_run/exceptions001.hs
@@ -2,7 +2,7 @@ module Main where
 
 import Prelude hiding (catch)
 import Exception
-import IO hiding (try)
+import IO hiding (try, catch)
 
 main = do
   ioTest
@@ -18,27 +18,28 @@ ioTest = catchIO (fail (userError "wibble"))
 				     else error "help!")
 
 errorTest :: IO ()
-errorTest = case getExceptions (1 + error "call to 'error'") of
-		Left exceptions -> putStr "error call caught\n"
-		Right val	-> error "help!"
+errorTest = getException (1 + error "call to 'error'") >>= \r ->
+	    case r of
+		Just exception -> putStr "error call caught\n"
+		Nothing        -> error "help!"
 
 instance (Show a, Eq a) => Num (Maybe a) where {}
 
 noMethodTest :: IO ()
-noMethodTest = catch (case Just () + Just () of Nothing -> return ())
-  (\exs -> case unsafePromiseSingleton exs of
-		NoMethodError err -> putStr "no method error\n"
-		other             -> error "help!")
+noMethodTest = getException (Just () + Just ()) >>= \ r ->
+	case r of
+		Just (NoMethodError err) -> putStr "no method error\n"
+		other                    -> error "help!"
 
 patMatchTest :: IO ()
-patMatchTest = catchOne (case test1 [1..10] of () -> return ())
+patMatchTest = catch (case test1 [1..10] of () -> return ())
   (\ex -> case ex of
 		PatternMatchFail err -> putStr err
 		other 		     -> error "help!")
 		  
 test1 [] = ()
 
-guardTest = catchOne (case test2 of () -> return ())
+guardTest = catch (case test2 of () -> return ())
   (\ex -> case ex of
 		NonExhaustiveGuards err -> putStr err
 		other 		     -> error "help!")
diff --git a/ghc/tests/lib/should_run/exceptions001.stdout b/ghc/tests/lib/should_run/exceptions001.stdout
index e69de29bb2d1d6434b8b29ae775ad8c2e48c5391..c0af83012af98bb4c94ca55a0f84c210a88f7c1e 100644
--- a/ghc/tests/lib/should_run/exceptions001.stdout
+++ b/ghc/tests/lib/should_run/exceptions001.stdout
@@ -0,0 +1,6 @@
+io exception caught
+error call caught
+no method error
+exceptions001.hs:40: Non-exhaustive patterns in function test1
+exceptions001.hs:47: Non-exhaustive guards in 
+43
\ No newline at end of file
diff --git a/ghc/tests/lib/should_run/list001.hs b/ghc/tests/lib/should_run/list001.hs
index 48104c6db011b54d7ce8e19b2177b7f031fd8e9e..a1ea6502168625733ae96c9a817a6747ac7fc23c 100644
--- a/ghc/tests/lib/should_run/list001.hs
+++ b/ghc/tests/lib/should_run/list001.hs
@@ -13,19 +13,19 @@ main = do
 
   -- head
   print (head [1,2,3,4], head "a")
-  catchOne (print (head [] :: String)) (\_ -> putStr "head []\n")
+  catch (print (head [] :: String)) (\_ -> putStr "head []\n")
 
   -- tail
   print (tail [1,2,3,4], tail "a")
-  catchOne (print (tail [] :: String)) (\_ -> putStr "tail []\n")
+  catch (print (tail [] :: String)) (\_ -> putStr "tail []\n")
 
   -- init
   print (init [1,2,3,4], init "a")
-  catchOne (print (init [] :: String)) (\_ -> putStr "init []\n")
+  catch (print (init [] :: String)) (\_ -> putStr "init []\n")
 
   -- last
   print (last [1,2,3,4], last "a")
-  catchOne (print (last [] :: String)) (\_ -> putStr "last []\n")
+  catch (print (last [] :: String)) (\_ -> putStr "last []\n")
 
   -- null
   print [null [], null "abc"]
@@ -38,43 +38,43 @@ main = do
 
   -- foldl1
   print (foldl1 (+) [1..10])
-  catchOne (print (foldl1 (+) [] :: Int)) (\_ -> putStr "foldl1 []\n")
+  catch (print (foldl1 (+) [] :: Int)) (\_ -> putStr "foldl1 []\n")
 
   -- scanl
   print (scanl  (+) 1 [1..10])
 
   -- scanl1
   print (scanl1 (+) [1..10])
-  catchOne (print (scanl1 (+) [] :: [Int])) (\_ -> putStr "scanl1 []\n")
+  catch (print (scanl1 (+) [] :: [Int])) (\_ -> putStr "scanl1 []\n")
 
   -- foldr1
   print (foldr1 (+) [1..10])
-  catchOne (print (foldr1 (+) [] :: Int)) (\_ -> putStr "foldr1 []\n")
+  catch (print (foldr1 (+) [] :: Int)) (\_ -> putStr "foldr1 []\n")
 
   -- scanr
   print (scanr  (+) 1 [1..10])
 
   -- scanr1
   print (scanr1 (+) [1..10])
-  catchOne (print (scanr1 (+) [] :: [Int])) (\_ -> putStr "scanr1 []\n")
+  catch (print (scanr1 (+) [] :: [Int])) (\_ -> putStr "scanr1 []\n")
 
   -- iterate
   print (take 10 (cycle (take 4 (iterate (+1) 1))))
 
   -- take
   print (take 4 (repeat "x"), take 0 (repeat "x"), take 5 [1..4])
-  catchOne (print (take (-1) [1..10])) (\_ -> putStr "take (-1)\n")
+  catch (print (take (-1) [1..10])) (\_ -> putStr "take (-1)\n")
 
   -- replicate
   print [replicate 2 "abc", replicate 0 "abc", replicate 3 []]
 
   -- drop
   print [drop 5 [1..10], drop 0 [1..10], drop 5 [1..4]]
-  catchOne (print (drop (-1) [1..10])) (\_ -> putStr "drop (-1)\n")
+  catch (print (drop (-1) [1..10])) (\_ -> putStr "drop (-1)\n")
 
   -- splitAt
   print [splitAt 5 [1..10], splitAt 5 [1..4]]
-  catchOne (print (splitAt (-1) [1..10])) (\_ -> putStr "splitAt (-1)\n")
+  catch (print (splitAt (-1) [1..10])) (\_ -> putStr "splitAt (-1)\n")
 
   -- scan
   print (span (<5) [1..10])
@@ -108,11 +108,11 @@ main = do
 
   -- maximum
   print (maximum [1..10])
-  catchOne (print (maximum [] :: Int)) (\_ -> putStr "maximum []\n")
+  catch (print (maximum [] :: Int)) (\_ -> putStr "maximum []\n")
 
   -- minimum
   print (minimum [1..10])
-  catchOne (print (minimum [] :: Int)) (\_ -> putStr "minimum []\n")
+  catch (print (minimum [] :: Int)) (\_ -> putStr "minimum []\n")
 
   -- concatMap
   print (concatMap (:[]) [(1::Int)..10])
diff --git a/ghc/tests/lib/should_run/packedstring001.hs b/ghc/tests/lib/should_run/packedstring001.hs
index 7ffce8ee3f08fbd233e4e7aa019140389e431b42..3ed6a11df7d8126fc30ee056a9bab230b5916ced 100644
--- a/ghc/tests/lib/should_run/packedstring001.hs
+++ b/ghc/tests/lib/should_run/packedstring001.hs
@@ -1,3 +1,5 @@
+{-# OPTIONS -fglasgow-exts #-}
+
 module Main (main) where
 
 import Char (isSpace)