diff --git a/ghc/tests/Makefile b/ghc/tests/Makefile
index f70286764c0ae1e6613108a535eb7266897f8928..a76d13792287d079f13da252ea190e5c5611e8c7 100644
--- a/ghc/tests/Makefile
+++ b/ghc/tests/Makefile
@@ -6,7 +6,6 @@ SUBDIRS = \
 	codeGen \
 	deSugar \
 	deriving \
-	io \
 	printing \
 	reader \
 	rename \
@@ -14,7 +13,8 @@ SUBDIRS = \
 	stranal \
 	typecheck 
 
-#programs
+#	io \
+#	programs
 
 include $(TOP)/mk/target.mk
 
diff --git a/ghc/tests/ccall/should_compile/cc001.hs b/ghc/tests/ccall/should_compile/cc001.hs
index 8aeca950fcd0179ea2ad44b73defd6b6fe90213a..465a4332d5732a7c425d969213af6c49454f2f5f 100644
--- a/ghc/tests/ccall/should_compile/cc001.hs
+++ b/ghc/tests/ccall/should_compile/cc001.hs
@@ -1,24 +1,22 @@
 --!!! cc001 -- ccall with standard boxed arguments and results
 
-module Test where
-
-import GlaExts
+module ShouldCompile where
 
 -- simple functions
 
-a :: PrimIO Int
+a :: IO Int
 a = _ccall_ a
 
-b :: Int -> PrimIO Int
+b :: Int -> IO Int
 b x = _ccall_ b x
 
-c :: Int -> Char -> Float -> Double -> PrimIO Float
+c :: Int -> Char -> Float -> Double -> IO Float
 c x1 x2 x3 x4 = _ccall_ c x1 x2 x3 x4
 
 -- simple monadic code
 
-d =	a		`thenPrimIO` \ x ->
-	b x		`thenPrimIO` \ y ->
+d =	a		>>= \ x ->
+	b x		>>= \ y ->
 	c y 'f' 1.0 2.0
 
 
diff --git a/ghc/tests/ccall/should_compile/cc003.hs b/ghc/tests/ccall/should_compile/cc003.hs
index b8c8d3501ab7eec7662909c5a05cbff4913b9afb..a3dbf78b58357dad013fa271641c7bac8a3aebd9 100644
--- a/ghc/tests/ccall/should_compile/cc003.hs
+++ b/ghc/tests/ccall/should_compile/cc003.hs
@@ -1,9 +1,7 @@
 --!!! cc003 -- ccall with unresolved polymorphism (should fail)
 --!!! not anymore (as of 0.29, result type will default to ())
-module Test where
+module ShouldCompile where
 
-import GlaExts
-
-fubar :: PrimIO Int
-fubar = _ccall_ f `seqPrimIO` _ccall_ b
+fubar :: IO Int
+fubar = _ccall_ f >>_ccall_ b
 		     --^ result type of f "lost" (never gets generalised)
diff --git a/ghc/tests/ccall/should_compile/cc006.hs b/ghc/tests/ccall/should_compile/cc006.hs
index 27579e9aaf30fb858b633a70acb9ccd037b151fa..488491f9165c4c82e601f0ece79e56a56902c8e0 100644
--- a/ghc/tests/ccall/should_compile/cc006.hs
+++ b/ghc/tests/ccall/should_compile/cc006.hs
@@ -2,21 +2,21 @@
 
 module Test where
 
-import GlaExts
 import Foreign
+import CCall
 
 -- Test returning results
 
-a :: PrimIO Int
+a :: IO Int
 a = _ccall_ a
 
-b :: PrimIO (StablePtr Int)
+b :: IO (StablePtr Int)
 b = _ccall_ b
 
 -- Test taking arguments
 
-c :: ForeignObj -> PrimIO Int
+c :: ForeignObj -> IO Int
 c x = _ccall_ c x
 
-d :: StablePtr Int -> PrimIO Int
+d :: StablePtr Int -> IO Int
 d x = _ccall_ d x
diff --git a/ghc/tests/ccall/should_fail/cc002.hs b/ghc/tests/ccall/should_fail/cc002.hs
index c970d8854b8bcbd93165f22505eb02c603316e25..7dbbf7297e6ddc73ed09be9044a1df02a0563fe9 100644
--- a/ghc/tests/ccall/should_fail/cc002.hs
+++ b/ghc/tests/ccall/should_fail/cc002.hs
@@ -2,21 +2,20 @@
 
 module Test where
 
-import GlaExts
 import Foreign
 
 -- Test returning results
 
-a :: PrimIO ForeignObj
+a :: IO ForeignObj
 a = _ccall_ a
 
-b :: PrimIO (StablePtr Double)
+b :: IO (StablePtr Double)
 b = _ccall_ b
 
 -- Test taking arguments
 
-c :: ForeignObj -> PrimIO Int
+c :: ForeignObj -> IO Int
 c x = _ccall_ c x
 
-d :: StablePtr Int -> PrimIO Int
+d :: StablePtr Int -> IO Int
 d x = _ccall_ d x
diff --git a/ghc/tests/ccall/should_fail/cc002.stderr b/ghc/tests/ccall/should_fail/cc002.stderr
index cb76ea3dda65efd2e78d50915b4648f1aef46c83..87e047aed3ec4c6e31ce6c3d78297ac1146adb89 100644
--- a/ghc/tests/ccall/should_fail/cc002.stderr
+++ b/ghc/tests/ccall/should_fail/cc002.stderr
@@ -1,6 +1,6 @@
  
-cc002.hs:11: No instance for: `Foreign.CReturnable Foreign.ForeignObj'
-    arising from the result of the _ccall_ to a at cc002.hs:11
+cc002.hs:10: No instance for: `CReturnable ForeignObj'
+    arising from the result of the _ccall_ to a at cc002.hs:10
     When checking signature(s) for: `a'
 
 Compilation had errors
diff --git a/ghc/tests/ccall/should_fail/cc004.hs b/ghc/tests/ccall/should_fail/cc004.hs
index f53c61d500ffe79c85a1b381b2814d8b660103c3..eded2ff65c92abf871f0f0eb1ee770655b8b5e5a 100644
--- a/ghc/tests/ccall/should_fail/cc004.hs
+++ b/ghc/tests/ccall/should_fail/cc004.hs
@@ -1,27 +1,24 @@
 --!!! cc004 -- ccall with synonyms, polymorphic type variables and user type variables.
 module Test where
 
-import GlaExts
-
 -- Since I messed up the handling of polymorphism originally, I'll
 -- explicitly test code with UserSysTyVar (ie an explicit polymorphic
 -- signature)
 
-foo = _ccall_ f	`thenADR` \ a -> returnPrimIO (a + 1)
+foo = _ccall_ f	`thenADR` \ a -> return (a + 1)
  where 
-   thenADR :: PrimIO a -> (a -> PrimIO b) -> PrimIO b
-   thenADR = thenPrimIO
+   thenADR :: IO a -> (a -> IO b) -> IO b
+   thenADR = (>>=)
 
 -- and with a PolySysTyVar (ie no explicit signature)
 
-bar = _ccall_ f	`thenADR` \ a -> returnPrimIO (a + 1)
+bar = _ccall_ f	`thenADR` \ a -> return (a + 1)
  where 
-   -- thenADR :: PrimIO a -> (a -> PrimIO b) -> PrimIO b
-   thenADR = thenPrimIO
+   -- thenADR :: IO a -> (a -> IO b) -> IO b
+   thenADR = (>>=)
 
 -- and with a type synonym
 
 type INT = Int
-barfu :: PrimIO INT
+barfu :: IO INT
 barfu = _ccall_ b
-
diff --git a/ghc/tests/ccall/should_fail/cc004.stderr b/ghc/tests/ccall/should_fail/cc004.stderr
index 30d0497d9e12971c35a880f1c5cde3e6cbaae6e7..5ee6d6d577603ea6ffcd0c99b58a2f5161b5ba21 100644
--- a/ghc/tests/ccall/should_fail/cc004.stderr
+++ b/ghc/tests/ccall/should_fail/cc004.stderr
@@ -1,8 +1,8 @@
  
 cc004.hs:2: Cannot generalise these overloadings (in a _ccall_):
-		`Foreign.CReturnable taWY'
+		`CReturnable taLM'
  
 cc004.hs:2: Cannot generalise these overloadings (in a _ccall_):
-		`Foreign.CReturnable taXF'
+		`CReturnable taMJ'
 
 Compilation had errors
diff --git a/ghc/tests/deSugar/should_compile/ds002.stderr b/ghc/tests/deSugar/should_compile/ds002.stderr
index a023dacf1f54b808f802f1cd441fc4f3e3e1ef3a..e69de29bb2d1d6434b8b29ae775ad8c2e48c5391 100644
--- a/ghc/tests/deSugar/should_compile/ds002.stderr
+++ b/ghc/tests/deSugar/should_compile/ds002.stderr
@@ -1,9 +0,0 @@
-ds002.hs:13: 
-    Warning: Possibly incomplete patterns
-	in the definition of function `g'
-ds002.hs:8: 
-    Warning: Pattern match(es) completely overlapped
-	in the definition of function `f'
-ds002.hs:9: 
-    Warning: Pattern match(es) completely overlapped
-	in the definition of function `f'
diff --git a/ghc/tests/deSugar/should_compile/ds004.stderr b/ghc/tests/deSugar/should_compile/ds004.stderr
index 5154acff350cc65a8b7d8d747cc997e86a732bcc..e69de29bb2d1d6434b8b29ae775ad8c2e48c5391 100644
--- a/ghc/tests/deSugar/should_compile/ds004.stderr
+++ b/ghc/tests/deSugar/should_compile/ds004.stderr
@@ -1,3 +0,0 @@
-ds004.hs:6: 
-    Warning: Possibly incomplete patterns
-	in the definition of function `nodups'
diff --git a/ghc/tests/deSugar/should_compile/ds005.stderr b/ghc/tests/deSugar/should_compile/ds005.stderr
index 6c4bd831785dce94b9e927a4a74855aaee13bb73..e69de29bb2d1d6434b8b29ae775ad8c2e48c5391 100644
--- a/ghc/tests/deSugar/should_compile/ds005.stderr
+++ b/ghc/tests/deSugar/should_compile/ds005.stderr
@@ -1,3 +0,0 @@
-ds005.hs:13: 
-    Warning: Possibly incomplete patterns
-	in the definition of function `mappairs''
diff --git a/ghc/tests/deSugar/should_compile/ds015.stderr b/ghc/tests/deSugar/should_compile/ds015.stderr
index 4c17fabfd9f5c0c91ee386292c7a3f7706645d95..e69de29bb2d1d6434b8b29ae775ad8c2e48c5391 100644
--- a/ghc/tests/deSugar/should_compile/ds015.stderr
+++ b/ghc/tests/deSugar/should_compile/ds015.stderr
@@ -1,3 +0,0 @@
-ds015.hs:9: 
-    Warning: Possibly incomplete patterns
-	in a lambda abstraction: `(x PrelBase.: xs) -> ...'
diff --git a/ghc/tests/deSugar/should_compile/ds018.stderr b/ghc/tests/deSugar/should_compile/ds018.stderr
index c3f8846f04ff06db819d55e53351fcb52afbe21a..e69de29bb2d1d6434b8b29ae775ad8c2e48c5391 100644
--- a/ghc/tests/deSugar/should_compile/ds018.stderr
+++ b/ghc/tests/deSugar/should_compile/ds018.stderr
@@ -1,6 +0,0 @@
-ds018.hs:39: 
-    Warning: Possibly incomplete patterns
-	in the definition of function `fa'
-ds018.hs:41: 
-    Warning: Possibly incomplete patterns
-	in the definition of function `fb'
diff --git a/ghc/tests/deSugar/should_compile/ds019.stderr b/ghc/tests/deSugar/should_compile/ds019.stderr
index 46e8eee549fa585f1cab57f8c824f1bcad2b5cbe..e69de29bb2d1d6434b8b29ae775ad8c2e48c5391 100644
--- a/ghc/tests/deSugar/should_compile/ds019.stderr
+++ b/ghc/tests/deSugar/should_compile/ds019.stderr
@@ -1,6 +0,0 @@
-ds019.hs:7: 
-    Warning: Pattern match(es) completely overlapped
-	in the definition of function `f'
-ds019.hs:8: 
-    Warning: Pattern match(es) completely overlapped
-	in the definition of function `f'
diff --git a/ghc/tests/deSugar/should_compile/ds020.stderr b/ghc/tests/deSugar/should_compile/ds020.stderr
index 5939b39c655bf66f561751cc9e4641471e84f3d0..955d1e1e9fe9a44c1af66933722020aa1919e389 100644
--- a/ghc/tests/deSugar/should_compile/ds020.stderr
+++ b/ghc/tests/deSugar/should_compile/ds020.stderr
@@ -1,17 +1,2 @@
-ds020.hs:6: 
-    Warning: Pattern match(es) completely overlapped
-	in the definition of function `a'
-ds020.hs:9: 
-    Warning: Pattern match(es) completely overlapped
-	in the definition of function `b'
-ds020.hs:16: 
-    Warning: Pattern match(es) completely overlapped
-	in the definition of function `d'
-ds020.hs:17: 
-    Warning: Pattern match(es) completely overlapped
-	in the definition of function `d'
-ds020.hs:20: 
-    Warning: Pattern match(es) completely overlapped
-	in the definition of function `f'
 
 NOTE: Simplifier still going after 4 iterations; bailing out.
diff --git a/ghc/tests/deSugar/should_compile/ds021.stderr b/ghc/tests/deSugar/should_compile/ds021.stderr
index 1dc6f97b7577fa38c1e6c5cce16f316624137f80..e69de29bb2d1d6434b8b29ae775ad8c2e48c5391 100644
--- a/ghc/tests/deSugar/should_compile/ds021.stderr
+++ b/ghc/tests/deSugar/should_compile/ds021.stderr
@@ -1,3 +0,0 @@
-ds021.hs:8: 
-    Warning: Possibly incomplete patterns
-	in the definition of function `f'
diff --git a/ghc/tests/deSugar/should_compile/ds022.stderr b/ghc/tests/deSugar/should_compile/ds022.stderr
index db28c9ee62ffd700578923e002af59c4b60ea955..e69de29bb2d1d6434b8b29ae775ad8c2e48c5391 100644
--- a/ghc/tests/deSugar/should_compile/ds022.stderr
+++ b/ghc/tests/deSugar/should_compile/ds022.stderr
@@ -1,18 +0,0 @@
-ds022.hs:5: 
-    Warning: Possibly incomplete patterns
-	in the definition of function `f'
-ds022.hs:10: 
-    Warning: Possibly incomplete patterns
-	in the definition of function `g'
-ds022.hs:15: 
-    Warning: Possibly incomplete patterns
-	in the definition of function `h'
-ds022.hs:22: 
-    Warning: Pattern match(es) completely overlapped
-	in the definition of function `i'
-ds022.hs:23: 
-    Warning: Pattern match(es) completely overlapped
-	in the definition of function `i'
-ds022.hs:20: 
-    Warning: Possibly incomplete patterns
-	in the definition of function `i'
diff --git a/ghc/tests/deSugar/should_compile/ds025.stderr b/ghc/tests/deSugar/should_compile/ds025.stderr
index 0f5a9f043561adc120bce659b26e7be3469472e1..e69de29bb2d1d6434b8b29ae775ad8c2e48c5391 100644
--- a/ghc/tests/deSugar/should_compile/ds025.stderr
+++ b/ghc/tests/deSugar/should_compile/ds025.stderr
@@ -1,3 +0,0 @@
-ds025.hs:6: 
-    Warning: Possibly incomplete patterns
-	in the definition of function `ehead'
diff --git a/ghc/tests/deSugar/should_compile/ds027.stderr b/ghc/tests/deSugar/should_compile/ds027.stderr
index a90c1ac042011ef9abd23a1fa95fe8a7deca7a99..e69de29bb2d1d6434b8b29ae775ad8c2e48c5391 100644
--- a/ghc/tests/deSugar/should_compile/ds027.stderr
+++ b/ghc/tests/deSugar/should_compile/ds027.stderr
@@ -1,6 +0,0 @@
-ds027.hs:9: 
-    Warning: Possibly incomplete patterns
-	in the definition of function `/='
-ds027.hs:8: 
-    Warning: Possibly incomplete patterns
-	in the definition of function `=='
diff --git a/ghc/tests/deSugar/should_compile/ds031.stderr b/ghc/tests/deSugar/should_compile/ds031.stderr
index 106ea38296275c83b55cf90ae28b443284dd5213..e69de29bb2d1d6434b8b29ae775ad8c2e48c5391 100644
--- a/ghc/tests/deSugar/should_compile/ds031.stderr
+++ b/ghc/tests/deSugar/should_compile/ds031.stderr
@@ -1,3 +0,0 @@
-ds031.hs:4: 
-    Warning: Possibly incomplete patterns
-	in the definition of function `foldPair'
diff --git a/ghc/tests/deSugar/should_compile/ds032.stderr b/ghc/tests/deSugar/should_compile/ds032.stderr
index b7e6ee4468045d3038771b6c2badcfd09fc092b2..e69de29bb2d1d6434b8b29ae775ad8c2e48c5391 100644
--- a/ghc/tests/deSugar/should_compile/ds032.stderr
+++ b/ghc/tests/deSugar/should_compile/ds032.stderr
@@ -1,3 +0,0 @@
-ds032.hs:12: 
-    Warning: Possibly incomplete patterns
-	in the definition of function `flatten'
diff --git a/ghc/tests/deSugar/should_compile/ds035.hs b/ghc/tests/deSugar/should_compile/ds035.hs
index e6383bc059b3923ba676a1df6d454eeb823d25ba..ebe338ed08aa0a93cfb189bd0573c2331f895971 100644
--- a/ghc/tests/deSugar/should_compile/ds035.hs
+++ b/ghc/tests/deSugar/should_compile/ds035.hs
@@ -1,4 +1,6 @@
-import GlaExts
+module ShouldCompile where
+
+import GHC
 
 data CList = CNil | CCons Int# CList
 
diff --git a/ghc/tests/deSugar/should_compile/ds036.stderr b/ghc/tests/deSugar/should_compile/ds036.stderr
index 6608a1ac830f7a03bb70e398723070f5bf6bcef6..e69de29bb2d1d6434b8b29ae775ad8c2e48c5391 100644
--- a/ghc/tests/deSugar/should_compile/ds036.stderr
+++ b/ghc/tests/deSugar/should_compile/ds036.stderr
@@ -1,6 +0,0 @@
-ds036.hs:22: 
-    Warning: Possibly incomplete patterns
-	in the definition of function `brack''
-ds036.hs:44: 
-    Warning: Possibly incomplete patterns
-	in the definition of function `kh'
diff --git a/ghc/tests/deSugar/should_compile/ds037.stderr b/ghc/tests/deSugar/should_compile/ds037.stderr
index 955d1e1e9fe9a44c1af66933722020aa1919e389..e69de29bb2d1d6434b8b29ae775ad8c2e48c5391 100644
--- a/ghc/tests/deSugar/should_compile/ds037.stderr
+++ b/ghc/tests/deSugar/should_compile/ds037.stderr
@@ -1,2 +0,0 @@
-
-NOTE: Simplifier still going after 4 iterations; bailing out.
diff --git a/ghc/tests/deSugar/should_compile/ds038.stderr b/ghc/tests/deSugar/should_compile/ds038.stderr
index b7355d79b8dffbe2c047f34cd9cc788f1c079cff..e69de29bb2d1d6434b8b29ae775ad8c2e48c5391 100644
--- a/ghc/tests/deSugar/should_compile/ds038.stderr
+++ b/ghc/tests/deSugar/should_compile/ds038.stderr
@@ -1,3 +0,0 @@
-ds038.hs:7: 
-    Warning: Possibly incomplete patterns
-	in the definition of function `takeList'
diff --git a/ghc/tests/deriving/should_compile/drv001.stderr b/ghc/tests/deriving/should_compile/drv001.stderr
index c16539de0ecfcbf7df10154ab1b25704297b46d3..d3658a590153c90da096536f57e38dc9c4da4ff6 100644
--- a/ghc/tests/deriving/should_compile/drv001.stderr
+++ b/ghc/tests/deriving/should_compile/drv001.stderr
@@ -1,7 +1,7 @@
 ghc: module version changed to 1; reason: no old .hi file
 _interface_ ShouldSucceed 1
 _instance_modules_
-ArrBase IO PrelNum
+Addr ArrBase Foreign IO PrelNum
 _usages_
 PrelBase 1 :: $d1 1 $d12 1 $d15 1 $d16 1 $d2 1 $d22 1 $d23 1 $d24 1 $d25 1 $d27 1 $d28 1 $d3 1 $d33 1 $d34 1 $d35 1 $d38 1 $d39 1 $d4 1 $d40 1 $d42 1 $d43 1 $d45 1 $d46 1 $d47 1 $d50 1 $d51 1 $d52 1 $d55 1 $d56 1 $d7 1 $d8 1 $d9 1 $m- 1 $m/= 1 $m< 1 $m<= 1 $m> 1 $m>= 1 $m>> 1 $mcompare 1 $mfromInt 1 $mmax 1 $mmin 1 $mshowList 1 . 1 showList__ 1 showParen 1 showSpace 1 showString 1 Eq 1 Eval 1 Monad 1 MonadPlus 1 MonadZero 1 Num 1 Ord 1 Ordering 1 Show 1 ShowS 1 String 1;
 PrelNum 1 :: $d10 1 $d16 1 $d17 1 $d18 1 $d29 1 $d33 1 $d34 1 $d35 1;
diff --git a/ghc/tests/deriving/should_compile/drv002.stderr b/ghc/tests/deriving/should_compile/drv002.stderr
index 57fb93e72789d2f54185275063ce0afcd0317cb6..ee83144632d3293275258872dae3a7c4bb76ed50 100644
--- a/ghc/tests/deriving/should_compile/drv002.stderr
+++ b/ghc/tests/deriving/should_compile/drv002.stderr
@@ -1,7 +1,7 @@
 ghc: module version changed to 1; reason: no old .hi file
 _interface_ ShouldSucceed 1
 _instance_modules_
-ArrBase IO PrelNum
+Addr ArrBase Foreign IO PrelNum
 _usages_
 PrelBase 1 :: $d1 1 $d12 1 $d15 1 $d16 1 $d2 1 $d22 1 $d23 1 $d24 1 $d25 1 $d27 1 $d28 1 $d3 1 $d33 1 $d34 1 $d35 1 $d38 1 $d39 1 $d4 1 $d40 1 $d42 1 $d43 1 $d45 1 $d46 1 $d47 1 $d50 1 $d51 1 $d52 1 $d55 1 $d56 1 $d7 1 $d8 1 $d9 1 $m- 1 $m/= 1 $m< 1 $m<= 1 $m> 1 $m>= 1 $m>> 1 $mcompare 1 $mfromInt 1 $mmax 1 $mmin 1 $mshowList 1 . 1 showList__ 1 showParen 1 showSpace 1 showString 1 Eq 1 Eval 1 Monad 1 MonadPlus 1 MonadZero 1 Num 1 Ord 1 Ordering 1 Show 1 ShowS 1 String 1;
 PrelNum 1 :: $d10 1 $d16 1 $d17 1 $d18 1 $d29 1 $d33 1 $d34 1 $d35 1;
diff --git a/ghc/tests/deriving/should_compile/drv003.stderr b/ghc/tests/deriving/should_compile/drv003.stderr
index 80eb5de79a10c567c115b92dc1ac1eec9c33e496..d6de897fe1684ee7ea25a00b073b9b51cc863be0 100644
--- a/ghc/tests/deriving/should_compile/drv003.stderr
+++ b/ghc/tests/deriving/should_compile/drv003.stderr
@@ -1,13 +1,13 @@
  
-drv003.hs:15: No explicit method nor default method for `PrelBase.=='
-	      in an instance declaration for `PrelBase.Eq'
+drv003.hs:15: Warning: no explicit method nor default method for `=='
+	      in an instance declaration for `Eq'
  
-drv003.hs:12: No explicit method nor default method for `PrelBase.=='
-	      in an instance declaration for `PrelBase.Eq'
+drv003.hs:12: Warning: no explicit method nor default method for `=='
+	      in an instance declaration for `Eq'
 ghc: module version changed to 1; reason: no old .hi file
 _interface_ ShouldSucceed 1
 _instance_modules_
-ArrBase IO PrelNum
+Addr ArrBase Foreign IO PrelNum
 _usages_
 PrelBase 1 :: $d16 1 $d2 1 $d33 1 $d38 1 $d40 1 $d42 1 $d47 1 $d8 1 $m/= 1 && 1 not 1 Eq 1 Eval 1;
 PrelNum 1 :: $d18 1;
diff --git a/ghc/tests/deriving/should_compile/drv004.stderr b/ghc/tests/deriving/should_compile/drv004.stderr
index 4c2be3eede769ebde75c16704e07067bda86309e..8d0ecdc3db011918f445c65c60cafe0e1f3d66ff 100644
--- a/ghc/tests/deriving/should_compile/drv004.stderr
+++ b/ghc/tests/deriving/should_compile/drv004.stderr
@@ -1,7 +1,7 @@
 ghc: module version changed to 1; reason: no old .hi file
 _interface_ ShouldSucceed 1
 _instance_modules_
-ArrBase IO PrelNum
+Addr ArrBase Foreign IO PrelNum
 _usages_
 PrelBase 1 :: $d15 1 $d16 1 $d2 1 $d27 1 $d28 1 $d33 1 $d34 1 $d35 1 $d38 1 $d39 1 $d40 1 $d42 1 $d45 1 $d46 1 $d47 1 $d50 1 $d51 1 $d52 1 $d7 1 $d8 1 $m/= 1 $m< 1 $m<= 1 $m> 1 $m>= 1 $mcompare 1 $mmax 1 $mmin 1 && 1 . 1 not 1 Eq 1 Eval 1 Ord 1 Ordering 1 String 1;
 PrelNum 1 :: $d17 1 $d18 1;
diff --git a/ghc/tests/deriving/should_compile/drv005.stderr b/ghc/tests/deriving/should_compile/drv005.stderr
index 4bc65f5f287d055a0e1406a1916b3f4a0bbc26a6..e760118a44acc1c3f72a7a20bb26ce5fb9d09837 100644
--- a/ghc/tests/deriving/should_compile/drv005.stderr
+++ b/ghc/tests/deriving/should_compile/drv005.stderr
@@ -1,7 +1,7 @@
 ghc: module version changed to 1; reason: no old .hi file
 _interface_ ShouldSucceed 1
 _instance_modules_
-ArrBase IO PrelNum
+Addr ArrBase Foreign IO PrelNum
 _usages_
 PrelBase 1 :: $d14 1 $d2 1 $d26 1 $d31 1 $d38 1 $d40 1 $d42 1 $d45 1 $d47 1 $d6 1 $menumFromThenTo 1 $menumFromTo 1 Enum 1 Eval 1 Functor 1;
 PrelNum 1 :: $d8 1;
diff --git a/ghc/tests/deriving/should_compile/drv006.stderr b/ghc/tests/deriving/should_compile/drv006.stderr
index 7f6d7585261573b357be699202b67bdd4236ddd7..f4fb7f55509c4efc7c0996343e4848a9113fe971 100644
--- a/ghc/tests/deriving/should_compile/drv006.stderr
+++ b/ghc/tests/deriving/should_compile/drv006.stderr
@@ -1,9 +1,7 @@
-
-NOTE: Simplifier still going after 4 iterations; bailing out.
 ghc: module version changed to 1; reason: no old .hi file
 _interface_ ShouldSucceed 1
 _instance_modules_
-ArrBase IO PrelNum
+Addr ArrBase Foreign IO PrelNum
 _usages_
 Ix 1 :: $d4 1 $d5 1 $d6 1 $d7 1 $d8 1 $d9 1 Ix 1;
 PrelBase 1 :: $d1 1 $d11 1 $d12 1 $d14 1 $d15 1 $d16 1 $d2 1 $d22 1 $d24 1 $d25 1 $d26 1 $d27 1 $d28 1 $d3 1 $d31 1 $d32 1 $d33 1 $d34 1 $d35 1 $d38 1 $d39 1 $d4 1 $d40 1 $d42 1 $d43 1 $d45 1 $d46 1 $d47 1 $d50 1 $d51 1 $d52 1 $d55 1 $d56 1 $d6 1 $d7 1 $d8 1 $d9 1 $m- 1 $m/= 1 $m< 1 $m<= 1 $m> 1 $m>= 1 $m>> 1 $mcompare 1 $menumFromThenTo 1 $menumFromTo 1 $mfromInt 1 $mmax 1 $mmin 1 $mshowList 1 && 1 . 1 not 1 showList__ 1 showParen 1 showSpace 1 showString 1 Enum 1 Eq 1 Eval 1 Functor 1 Monad 1 MonadZero 1 Num 1 Ord 1 Ordering 1 Ordering 1 Show 1 ShowS 1 String 1;
diff --git a/ghc/tests/deriving/should_compile/drv008.stderr b/ghc/tests/deriving/should_compile/drv008.stderr
index 0b32c3bced1eecbf54cbd7cdd560e1a1d700bc04..88ccb2ddb852e4fffd7fcabb7e965cd298d6cc42 100644
--- a/ghc/tests/deriving/should_compile/drv008.stderr
+++ b/ghc/tests/deriving/should_compile/drv008.stderr
@@ -3,7 +3,7 @@ NOTE: Simplifier still going after 4 iterations; bailing out.
 ghc: module version changed to 1; reason: no old .hi file
 _interface_ ShouldSucceed 1
 _instance_modules_
-ArrBase IO PrelNum
+Addr ArrBase Foreign IO PrelNum
 _usages_
 Ix 1 :: $d4 1 $d5 1 $d6 1 $d7 1 $d8 1 $d9 1 Ix 1;
 PrelBase 1 :: $d1 1 $d11 1 $d12 1 $d14 1 $d15 1 $d16 1 $d2 1 $d22 1 $d24 1 $d25 1 $d26 1 $d27 1 $d28 1 $d3 1 $d31 1 $d32 1 $d33 1 $d34 1 $d35 1 $d38 1 $d39 1 $d4 1 $d40 1 $d42 1 $d43 1 $d45 1 $d46 1 $d47 1 $d50 1 $d51 1 $d52 1 $d55 1 $d56 1 $d6 1 $d7 1 $d8 1 $d9 1 $m- 1 $m/= 1 $m< 1 $m<= 1 $m> 1 $m>= 1 $m>> 1 $mcompare 1 $menumFromThenTo 1 $menumFromTo 1 $mfromInt 1 $mmax 1 $mmin 1 $mshowList 1 && 1 . 1 not 1 showList__ 1 showParen 1 showSpace 1 showString 1 Enum 1 Eq 1 Eval 1 Functor 1 Monad 1 MonadZero 1 Num 1 Ord 1 Ordering 1 Ordering 1 Show 1 ShowS 1 String 1;
diff --git a/ghc/tests/deriving/should_compile/drv009.stderr b/ghc/tests/deriving/should_compile/drv009.stderr
index 41123b3b1d0c785c72b1b00b52cba367e8dd9be7..20d6d0ead2b9db5508f5fac9595b1a9066de0a93 100644
--- a/ghc/tests/deriving/should_compile/drv009.stderr
+++ b/ghc/tests/deriving/should_compile/drv009.stderr
@@ -1,7 +1,7 @@
 ghc: module version changed to 1; reason: no old .hi file
 _interface_ ShouldSucceed 1
 _instance_modules_
-ArrBase IO PrelNum
+Addr ArrBase Foreign IO PrelNum
 _usages_
 Ix 1 :: $d4 1 $d5 1 $d6 1 $d7 1 $d8 1 $d9 1 Ix 1;
 PrelBase 1 :: $d1 1 $d11 1 $d12 1 $d14 1 $d15 1 $d16 1 $d2 1 $d22 1 $d24 1 $d25 1 $d26 1 $d27 1 $d28 1 $d3 1 $d31 1 $d32 1 $d33 1 $d34 1 $d35 1 $d38 1 $d39 1 $d4 1 $d40 1 $d42 1 $d43 1 $d45 1 $d46 1 $d47 1 $d50 1 $d51 1 $d52 1 $d55 1 $d56 1 $d6 1 $d7 1 $d8 1 $d9 1 $m- 1 $m/= 1 $m< 1 $m<= 1 $m> 1 $m>= 1 $m>> 1 $mcompare 1 $menumFromThenTo 1 $menumFromTo 1 $mfromInt 1 $mmax 1 $mmin 1 $mshowList 1 && 1 . 1 not 1 showList__ 1 showParen 1 showSpace 1 showString 1 Enum 1 Eq 1 Eval 1 Functor 1 Monad 1 MonadZero 1 Num 1 Ord 1 Ordering 1 Ordering 1 Show 1 ShowS 1 String 1;
diff --git a/ghc/tests/deriving/should_compile/drv010.stderr b/ghc/tests/deriving/should_compile/drv010.stderr
index cc508b3f01e24f33726d7770945c1ae08d5f670c..2f2a161291331f9bfa14f51073527c6f6a7cd92f 100644
--- a/ghc/tests/deriving/should_compile/drv010.stderr
+++ b/ghc/tests/deriving/should_compile/drv010.stderr
@@ -1,7 +1,7 @@
 ghc: module version changed to 1; reason: no old .hi file
 _interface_ ShouldSucceed 1
 _instance_modules_
-ArrBase IO PrelNum
+Addr ArrBase Foreign IO PrelNum
 _usages_
 PrelBase 1 :: $d14 1 $d2 1 $d26 1 $d31 1 $d38 1 $d40 1 $d42 1 $d45 1 $d47 1 $d6 1 $menumFromThenTo 1 $menumFromTo 1 Enum 1 Eval 1 Functor 1;
 PrelNum 1 :: $d8 1;
diff --git a/ghc/tests/deriving/should_fail/drvfail004.stderr b/ghc/tests/deriving/should_fail/drvfail004.stderr
index 88de069257fade7939598c8fd86a098ba2a6f8ea..3d36a66ba54c961b269a7ca7b44362883286d1f3 100644
--- a/ghc/tests/deriving/should_fail/drvfail004.stderr
+++ b/ghc/tests/deriving/should_fail/drvfail004.stderr
@@ -1,5 +1,5 @@
  
-drvfail004.hs:5: No instance for: `PrelBase.Eq (Foo taDR taDS)'
+drvfail004.hs:5: No instance for: `Eq (Foo taGu taGv)'
     arising from an instance declaration at drvfail004.hs:5
     When checking superclass constraints of an instance declaration
 
diff --git a/ghc/tests/deriving/should_fail/drvfail007.stderr b/ghc/tests/deriving/should_fail/drvfail007.stderr
index 5338ad458e1f695aebff4afd227c193ba4d603f4..29412dc1b53c73c1bb70ed84dad8e680e15527a7 100644
--- a/ghc/tests/deriving/should_fail/drvfail007.stderr
+++ b/ghc/tests/deriving/should_fail/drvfail007.stderr
@@ -1,10 +1,8 @@
  
-drvfail007.hs:2: No instance for: `PrelBase.Eq (PrelBase.Int
-						-> PrelBase.Int)'
+drvfail007.hs:2: No instance for: `Eq (Int -> Int)'
     When deriving classes for `Foo'
  
-drvfail007.hs:2: No instance for: `PrelBase.Eq (PrelBase.Int
-						-> PrelBase.Int)'
+drvfail007.hs:2: No instance for: `Eq (Int -> Int)'
     When deriving classes for `Foo'
 
 Compilation had errors
diff --git a/ghc/tests/io/should_run/io002.hs b/ghc/tests/io/should_run/io002.hs
index 620b44d2ee743ddaecceb22689e8d6066f5f4541..abc5c3aeff2323e99b7f4a6a2df58fb219005d9e 100644
--- a/ghc/tests/io/should_run/io002.hs
+++ b/ghc/tests/io/should_run/io002.hs
@@ -2,12 +2,8 @@ import System (getEnv)
 
 main = 
     getEnv "TERM" >>= \ term -> 
-    putStr term >>
+    putStr "Got $TERM" >>
     putChar '\n' >>
     getEnv "One fish, two fish, red fish, blue fish" >>= \ fish -> 
     putStr fish >> 
     putChar '\n'
-
-
-
-
diff --git a/ghc/tests/io/should_run/io011.hs b/ghc/tests/io/should_run/io011.hs
index 8d8d7458fa95d406efad2d486bddb7f6fc7560b7..156c230c63bf75f7df8660cb6ef13c96a3f510ce 100644
--- a/ghc/tests/io/should_run/io011.hs
+++ b/ghc/tests/io/should_run/io011.hs
@@ -1,7 +1,7 @@
 import IO -- 1.3
 
 import Directory
-import GlaExts (trace)
+import IOExts (trace)
 
 main =
     createDirectory "foo" >>
diff --git a/ghc/tests/printing/should_compile/Print001.stderr b/ghc/tests/printing/should_compile/Print001.stderr
index 89ca0325555e5e27c710f94c733c26f67ea8f275..c618477a1d33a9a248f07544d93dd8f9cfeaecfc 100644
--- a/ghc/tests/printing/should_compile/Print001.stderr
+++ b/ghc/tests/printing/should_compile/Print001.stderr
@@ -1,46 +1,46 @@
 ==================== Typechecked ====================
-BarNil{-r8,x-}{i} = _/\_ a_tr4F -> BarNil{-r8,x-}{i} {_@_ a_tr4F}
+BarNil{-r8,x-}{i} = _/\_ a_tr4J -> BarNil{-r8,x-}{i} {_@_ a_tr4J}
 BarCon{-r7,x-}{i} =
-    _/\_ a_tr4F -> \ tpl_B1 tpl_B2 ->
-	BarCon{-r7,x-}{i} {_@_ a_tr4F tpl_B1 tpl_B2}
-MkFoo{-r4M,x-}{i} =
-    _/\_ d_tr4H e_tr4I f_tr4J -> \ tpl_B1 tpl_B2 tpl_B3 ->
-	MkFoo{-r4M,x-}{i}
-	    {_@_ d_tr4H _@_ e_tr4I _@_ f_tr4J tpl_B1 tpl_B2 tpl_B3}
-AbsBinds [taYm, taYn] [] [([taYn, taYm], g{-r4w,x-}, g_aYj)]
-    g_aYj x_r4D = lit_aZz
+    _/\_ a_tr4J -> \ tpl_B1 tpl_B2 ->
+	BarCon{-r7,x-}{i} {_@_ a_tr4J tpl_B1 tpl_B2}
+MkFoo{-r4Q,x-}{i} =
+    _/\_ d_tr4L e_tr4M f_tr4N -> \ tpl_B1 tpl_B2 tpl_B3 ->
+	MkFoo{-r4Q,x-}{i}
+	    {_@_ d_tr4L _@_ e_tr4M _@_ f_tr4N tpl_B1 tpl_B2 tpl_B3}
+AbsBinds [ta118, ta119] [] [([ta119, ta118], g{-r4A,x-}, g_a12b)]
+    g_a12b x_r4H = lit_a12j
 AbsBinds
-[taYB, taYC, taYD]
-[d.Eq_aYF, d.Ord_aYG, d.Ix_aYH]
-[([taYB, taYC, taYD], f2{-r4v,x-}, f2_aYy)]
-    f2_aYy x_r4B = x_r4B
+[ta11m, ta11n, ta11o]
+[d.Eq_a11q, d.Ord_a11r, d.Ix_a11s]
+[([ta11m, ta11n, ta11o], f2{-r4z,x-}, f2_a12k)]
+    f2_a12k x_r4F = x_r4F
 AbsBinds
-[taYS, taYT, taYU]
-[d.Eq_aYW]
-[([taYS, taYT, taYU], f{-r4u,x-}, f_aYP)]
-    f_aYP x_r4z = x_r4z
+[ta11C, ta11D, ta11E]
+[d.Eq_a11G]
+[([ta11C, ta11D, ta11E], f{-r4y,x-}, f_a12l)]
+    f_a12l x_r4D = x_r4D
 AbsBinds
-[taZ2, taZ4, taZ6]
+[ta11L, ta11N, ta11P]
 []
-[([taZ2, taZ4, taZ6], mkFoo{-r4x,x-}, mkFoo_aYY)]
-    mkFoo_aYY = MkFoo{-r4M,x-}{i} [taZ2, taZ4, taZ6]
-AbsBinds [taZo] [] [([taZo], $d1{-rZv,x-}, d.Eval_aZc)]
-    d.Eval_aZc = ({-dict-} [] [])
+[([ta11L, ta11N, ta11P], mkFoo{-r4B,x-}, mkFoo_a12m)]
+    mkFoo_a12m = MkFoo{-r4Q,x-}{i} [ta11L, ta11N, ta11P]
+AbsBinds [ta127] [] [([ta127], $d1{-r12f,x-}, d.Eval_a11V)]
+    d.Eval_a11V = ({-dict-} [] [])
 AbsBinds
-[taZp, taZq, taZr]
+[ta128, ta129, ta12a]
 []
-[([taZp, taZq, taZr], $d2{-rZx,x-}, d.Eval_aZk)]
-    d.Eval_aZk = ({-dict-} [] [])
-d.Fractional_aZn = PrelNum.$d23{-rES,p-}
-fromRational_aZy =
-    PrelNum.fromRational{-8T,p-} PrelBase.Float{-3c,W-}
-	d.Fractional_aZn
-lit_aZz = fromRational_aZy 2.0000000000000000
+[([ta128, ta129, ta12a], $d2{-r12h,x-}, d.Eval_a123)]
+    d.Eval_a123 = ({-dict-} [] [])
+d.Fractional_a126 = PrelNum.$d23{-rFn,p-}
+fromRational_a12i =
+    PrelNum.fromRational{-8U,p-} PrelBase.Float{-3c,W-}
+	d.Fractional_a126
+lit_a12j = fromRational_a12i 2.0000000000000000
 
 ghc: module version changed to 1; reason: no old .hi file
 _interface_ Print001 1
 _instance_modules_
-ArrBase IO PrelNum
+Addr ArrBase Foreign IO PrelNum
 _usages_
 Ix 1 :: $d3 1 $d4 1 $d5 1 $d6 1 $d7 1 $d8 1 $d9 1 Ix 1;
 PrelBase 1 :: $d1 1 $d11 1 $d12 1 $d14 1 $d15 1 $d16 1 $d2 1 $d22 1 $d27 1 $d28 1 $d3 1 $d31 1 $d32 1 $d33 1 $d34 1 $d35 1 $d38 1 $d39 1 $d4 1 $d40 1 $d41 1 $d42 1 $d43 1 $d45 1 $d46 1 $d47 1 $d50 1 $d51 1 $d52 1 $d55 1 $d56 1 $d6 1 $d7 1 $d8 1 $d9 1 $m- 1 $m/= 1 $m< 1 $m<= 1 $m> 1 $m>= 1 $mcompare 1 $menumFromThenTo 1 $menumFromTo 1 $mfromInt 1 $mmax 1 $mmin 1 $mshowList 1 Enum 1 Eq 1 Eval 1 Num 1 Ord 1 Ordering 1 Show 1 String 1;
diff --git a/ghc/tests/printing/should_compile/Print002.stderr b/ghc/tests/printing/should_compile/Print002.stderr
index abb6cc410157613f6f3d0de0f79711f3514d5ae5..897ddb10165aeffae8de2adb97d17aab5309b42f 100644
--- a/ghc/tests/printing/should_compile/Print002.stderr
+++ b/ghc/tests/printing/should_compile/Print002.stderr
@@ -11,243 +11,243 @@ MkFoo3{-rm,x-}{i} =
 :***{-ro,x-}{i} =
     _/\_ a_tr4k b_tr4l c_tr4m -> \ tpl_B1 tpl_B2 ->
 	:***{-ro,x-}{i} {_@_ a_tr4k _@_ b_tr4l _@_ c_tr4m tpl_B1 tpl_B2}
-AbsBinds [taFT] [d.Bar_aFW] [([taFT], f3d{-r4o,x-}, f3d_aFD)]
-    /////_aRB = /////{-r4C,x-} taFT d.Bar_aFW
-    f3d_aFD x_r48 y_r49 = x_r48 /////_aRB y_r49
-AbsBinds [taGe] [d.Bar_aGh] [([taGe], f3c{-r4p,x-}, f3c_aFY)]
-    /////_aRG = /////{-r4C,x-} taGe d.Bar_aGh
-    f3c_aFY x_r45 y_r46 = /////_aRG x_r45 y_r46
-AbsBinds [taGz] [d.Bar_aGC] [([taGz], f3b{-r4q,x-}, f3b_aGj)]
-    meth1_aRH = meth1{-r4B,x-} taGz d.Bar_aGC
-    f3b_aGj x_r42 y_r43 = x_r42 meth1_aRH y_r43
-AbsBinds [taGU] [d.Bar_aGX] [([taGU], f3a{-r4r,x-}, f3a_aGE)]
-    meth1_aRI = meth1{-r4B,x-} taGU d.Bar_aGX
-    f3a_aGE x_r3Z y_r40 = meth1_aRI x_r3Z y_r40
+AbsBinds [taIx] [d.Bar_aIA] [([taIx], f3d{-r4o,x-}, f3d_aTU)]
+    /////_aTV = /////{-r4C,x-} taIx d.Bar_aIA
+    f3d_aTU x_r48 y_r49 = x_r48 /////_aTV y_r49
+AbsBinds [taIR] [d.Bar_aIU] [([taIR], f3c{-r4p,x-}, f3c_aU0)]
+    /////_aU1 = /////{-r4C,x-} taIR d.Bar_aIU
+    f3c_aU0 x_r45 y_r46 = /////_aU1 x_r45 y_r46
+AbsBinds [taJb] [d.Bar_aJe] [([taJb], f3b{-r4q,x-}, f3b_aU2)]
+    meth1_aU3 = meth1{-r4B,x-} taJb d.Bar_aJe
+    f3b_aU2 x_r42 y_r43 = x_r42 meth1_aU3 y_r43
+AbsBinds [taJv] [d.Bar_aJy] [([taJv], f3a{-r4r,x-}, f3a_aU4)]
+    meth1_aU5 = meth1{-r4B,x-} taJv d.Bar_aJy
+    f3a_aU4 x_r3Z y_r40 = meth1_aU5 x_r3Z y_r40
 AbsBinds
-[taHp, taHr, taHt]
+[taJZ, taK1, taK3]
 []
-[([taHp, taHr, taHt], <<<<{-r4s,x-}, <<<<_aGZ)]
-    <<<<_aGZ x_r3T y_r3U
-	     = :***{-ro,x-}{i} [taHp, taHr, taHt] x_r3T y_r3U
-    <<<<_aGZ x_r3W y_r3X
-	     = :***{-ro,x-}{i} [taHp, taHr, taHt] x_r3W y_r3X
+[([taJZ, taK1, taK3], <<<<{-r4s,x-}, <<<<_aU6)]
+    <<<<_aU6 x_r3T y_r3U
+	     = :***{-ro,x-}{i} [taJZ, taK1, taK3] x_r3T y_r3U
+    <<<<_aU6 x_r3W y_r3X
+	     = :***{-ro,x-}{i} [taJZ, taK1, taK3] x_r3W y_r3X
 AbsBinds
-[taHL, taHN, taHP]
+[taKk, taKm, taKo]
 []
-[([taHL, taHN, taHP], .....{-r4t,x-}, ....._aHv)]
-    ....._aHv x_r3Q y_r3R
-	      = MkFoo3{-rm,x-}{i} [taHL, taHN, taHP] x_r3Q y_r3R
+[([taKk, taKm, taKo], .....{-r4t,x-}, ....._aU7)]
+    ....._aU7 x_r3Q y_r3R
+	      = MkFoo3{-rm,x-}{i} [taKk, taKm, taKo] x_r3Q y_r3R
 AbsBinds
-[taI7, taI9, taIb]
+[taKF, taKH, taKJ]
 []
-[([taI7, taI9, taIb], ....{-r4u,x-}, ...._aHR)]
-    ...._aHR x_r3N y_r3O
-	     = MkFoo3{-rm,x-}{i} [taI7, taI9, taIb] x_r3N y_r3O
+[([taKF, taKH, taKJ], ....{-r4u,x-}, ...._aU8)]
+    ...._aU8 x_r3N y_r3O
+	     = MkFoo3{-rm,x-}{i} [taKF, taKH, taKJ] x_r3N y_r3O
 AbsBinds
-[taIt, taIv, taIx]
+[taL0, taL2, taL4]
 []
-[([taIt, taIv, taIx], f2a{-r4v,x-}, f2a_aId)]
-    f2a_aId x_r3K y_r3L = :##{-rj,x-}{i} [taIt, taIv, taIx] x_r3K y_r3L
+[([taL0, taL2, taL4], f2a{-r4v,x-}, f2a_aU9)]
+    f2a_aU9 x_r3K y_r3L = :##{-rj,x-}{i} [taL0, taL2, taL4] x_r3K y_r3L
 AbsBinds
-[taIP, taIR, taIT]
+[taLl, taLn, taLp]
 []
-[([taIP, taIR, taIT], f2{-r4w,x-}, f2_aIz)]
-    f2_aIz x_r3H y_r3I = :##{-rj,x-}{i} [taIP, taIR, taIT] x_r3H y_r3I
+[([taLl, taLn, taLp], f2{-r4w,x-}, f2_aUa)]
+    f2_aUa x_r3H y_r3I = :##{-rj,x-}{i} [taLl, taLn, taLp] x_r3H y_r3I
 AbsBinds
-[taJb, taJd, taJf]
+[taLG, taLI, taLK]
 []
-[([taJb, taJd, taJf], f1a{-r4x,x-}, f1a_aIV)]
-    f1a_aIV x_r3E y_r3F
-	    = MkFoo1{-rk,x-}{i} [taJb, taJd, taJf] x_r3E y_r3F
+[([taLG, taLI, taLK], f1a{-r4x,x-}, f1a_aUb)]
+    f1a_aUb x_r3E y_r3F
+	    = MkFoo1{-rk,x-}{i} [taLG, taLI, taLK] x_r3E y_r3F
 AbsBinds
-[taJx, taJz, taJB]
+[taM1, taM3, taM5]
 []
-[([taJx, taJz, taJB], f1{-r4y,x-}, f1_aJh)]
-    f1_aJh x_r3B y_r3C
-	   = MkFoo1{-rk,x-}{i} [taJx, taJz, taJB] x_r3B y_r3C
+[([taM1, taM3, taM5], f1{-r4y,x-}, f1_aUc)]
+    f1_aUc x_r3B y_r3C
+	   = MkFoo1{-rk,x-}{i} [taM1, taM3, taM5] x_r3B y_r3C
 AbsBinds
-[taKj, taKm, taKn]
+[taMM, taMP, taMQ]
 []
-[([taKj, taKm, taKn], con2tag_Foo#_rD5, con2tag_Foo#_aJD)]
-    con2tag_Foo#_aJD (MkFoo1{-rk,x-}{i} _ _) = 0#
-    con2tag_Foo#_aJD (:##{-rj,x-}{i} _ _) = 1#
-    con2tag_Foo#_aJD (MkFoo3{-rm,x-}{i} _ _) = 2#
-    con2tag_Foo#_aJD (:***{-ro,x-}{i} _ _) = 3#
+[([taMM, taMP, taMQ], con2tag_Foo#_rFK, con2tag_Foo#_aUd)]
+    con2tag_Foo#_aUd (MkFoo1{-rk,x-}{i} _ _) = 0#
+    con2tag_Foo#_aUd (:##{-rj,x-}{i} _ _) = 1#
+    con2tag_Foo#_aUd (MkFoo3{-rm,x-}{i} _ _) = 2#
+    con2tag_Foo#_aUd (:***{-ro,x-}{i} _ _) = 3#
 AbsBinds
-[taKG, taKJ, taKM]
-[d.Eq_aMy, d.Eq_aMz, d.Eq_aMA]
-[([taKG, taKJ, taKM], $d1{-rRC,x-}, d.Eq_aKv)]
-    d.Eq_aME = d.Eq_aMy
-    ==_aRJ = PrelBase.=={-8Y,p-} taKG d.Eq_aME
-    d.Eq_aMG = d.Eq_aMz
-    ==_aRK = PrelBase.=={-8Y,p-} taKJ d.Eq_aMG
-    d.Eq_aMI = d.Eq_aMA
-    ==_aRL = PrelBase.=={-8Y,p-} taKM d.Eq_aMI
-    ==_aRM = ==_aRN
-    AbsBinds [] [] [([], ==_aRN, ==_aKz)]
-	==_aRP = ==_aRJ
-	==_aRQ = ==_aRK
-	==_aRR = ==_aRK
-	==_aRS = ==_aRL
-	==_aRT = ==_aRL
-	==_aKz (MkFoo1{-rk,x-}{i} a1_rDe a2_rDf)
-	       (MkFoo1{-rk,x-}{i} b1_rDg b2_rDh)
-	       = (a1_rDe ==_aRJ b1_rDg)
-		 PrelBase.&&{-rgs,p-} (a2_rDf ==_aRP b2_rDh)
-	==_aKz (:##{-rj,x-}{i} a1_rDj a2_rDk)
-	       (:##{-rj,x-}{i} b1_rDl b2_rDm)
-	       = (a1_rDj ==_aRK b1_rDl)
-		 PrelBase.&&{-rgs,p-} (a2_rDk ==_aRL b2_rDm)
-	==_aKz (MkFoo3{-rm,x-}{i} a1_rDo a2_rDp)
-	       (MkFoo3{-rm,x-}{i} b1_rDq b2_rDr)
-	       = (a1_rDo ==_aRQ b1_rDq)
-		 PrelBase.&&{-rgs,p-} (a2_rDp ==_aRR b2_rDr)
-	==_aKz (:***{-ro,x-}{i} a1_rDt a2_rDu)
-	       (:***{-ro,x-}{i} b1_rDv b2_rDw)
-	       = (a1_rDt ==_aRS b1_rDv)
-		 PrelBase.&&{-rgs,p-} (a2_rDu ==_aRT b2_rDw)
-	==_aKz a_rDy b_rDz = PrelBase.False{-58,w-}{i}
-    AbsBinds [] [] [([], /=_aRO, /=_aMr)]
-	/=_aMr a_rDD b_rDE = PrelBase.not{-rhq,p-} ==_aRM a_rDD b_rDE
-    d.Eq_aKv = ({-dict-} [] [==_aRN, /=_aRO])
+[taN8, taNb, taNe]
+[d.Eq_aOZ, d.Eq_aP0, d.Eq_aP1]
+[([taN8, taNb, taNe], $d1{-rTW,x-}, d.Eq_aMY)]
+    d.Eq_aP5 = d.Eq_aOZ
+    ==_aUe = PrelBase.=={-8Z,p-} taN8 d.Eq_aP5
+    d.Eq_aP7 = d.Eq_aP0
+    ==_aUf = PrelBase.=={-8Z,p-} taNb d.Eq_aP7
+    d.Eq_aP9 = d.Eq_aP1
+    ==_aUg = PrelBase.=={-8Z,p-} taNe d.Eq_aP9
+    ==_aUh = ==_aUi
+    AbsBinds [] [] [([], ==_aUi, ==_aUk)]
+	==_aUl = ==_aUe
+	==_aUm = ==_aUf
+	==_aUn = ==_aUf
+	==_aUo = ==_aUg
+	==_aUp = ==_aUg
+	==_aUk (MkFoo1{-rk,x-}{i} a1_rFT a2_rFU)
+	       (MkFoo1{-rk,x-}{i} b1_rFV b2_rFW)
+	       = (a1_rFT ==_aUe b1_rFV)
+		 PrelBase.&&{-rgw,p-} (a2_rFU ==_aUl b2_rFW)
+	==_aUk (:##{-rj,x-}{i} a1_rFY a2_rFZ)
+	       (:##{-rj,x-}{i} b1_rG0 b2_rG1)
+	       = (a1_rFY ==_aUf b1_rG0)
+		 PrelBase.&&{-rgw,p-} (a2_rFZ ==_aUg b2_rG1)
+	==_aUk (MkFoo3{-rm,x-}{i} a1_rG3 a2_rG4)
+	       (MkFoo3{-rm,x-}{i} b1_rG5 b2_rG6)
+	       = (a1_rG3 ==_aUm b1_rG5)
+		 PrelBase.&&{-rgw,p-} (a2_rG4 ==_aUn b2_rG6)
+	==_aUk (:***{-ro,x-}{i} a1_rG8 a2_rG9)
+	       (:***{-ro,x-}{i} b1_rGa b2_rGb)
+	       = (a1_rG8 ==_aUo b1_rGa)
+		 PrelBase.&&{-rgw,p-} (a2_rG9 ==_aUp b2_rGb)
+	==_aUk a_rGd b_rGe = PrelBase.False{-58,w-}{i}
+    AbsBinds [] [] [([], /=_aUj, /=_aUq)]
+	/=_aUq a_rGi b_rGj = PrelBase.not{-rhu,p-} ==_aUh a_rGi b_rGj
+    d.Eq_aMY = ({-dict-} [] [==_aUi, /=_aUj])
 AbsBinds
-[taRw, taRx, taRy]
+[taTP, taTQ, taTR]
 []
-[([taRw, taRx, taRy], $d2{-rRD,x-}, d.Eval_aMT)]
-    d.Eval_aMT = ({-dict-} [] [])
+[([taTP, taTQ, taTR], $d2{-rTX,x-}, d.Eval_aPk)]
+    d.Eval_aPk = ({-dict-} [] [])
 AbsBinds
-[taN8, taN9, taNa]
-[d.Ord_aRa, d.Ord_aRb, d.Ord_aRc, d.Eq_aRd]
-[([taN8, taN9, taNa], $d3{-rRE,x-}, d.Ord_aN1)]
-    d.Eq_aR9 = d.Eq_aRd
-    d.Ord_aPR = d.Ord_aRa
-    d.Ord_aPS = d.Ord_aRb
-    d.Ord_aPT = d.Ord_aRc
-    compare_aRU = compare_aS0
-    compare_aRV = compare_aS0
-    compare_aRW = compare_aS0
-    compare_aRX = compare_aS0
-    compare_aRY = compare_aS0
-    compare_aRZ = compare_aS0
-    AbsBinds [] [] [([], compare_aS0, compare_aN5)]
-	compare_aN5 a_rEw b_rEx
-		    = case con2tag_Foo#_rD5 [taNa, taN8, taN9] a_rEw of
-			a#_rFk
-			-> case con2tag_Foo#_rD5 [taNa, taN8, taN9] b_rEx of
-			     b#_rFm
-			     -> if a#_rFk GHC.==#{-79,w-}{I} b#_rFm then
-				    case cmp_eq_aS7 a_rEw b_rEx of
-				      PrelBase.LT{-rb5,p-}{i} -> PrelBase.LT{-rb5,p-}{i}
+[taPy, taPz, taPA]
+[d.Ord_aTt, d.Ord_aTu, d.Ord_aTv, d.Eq_aTw]
+[([taPy, taPz, taPA], $d3{-rTY,x-}, d.Ord_aPs)]
+    d.Eq_aTs = d.Eq_aTw
+    d.Ord_aSg = d.Ord_aTt
+    d.Ord_aSh = d.Ord_aTu
+    d.Ord_aSi = d.Ord_aTv
+    compare_aUr = compare_aUx
+    compare_aUs = compare_aUx
+    compare_aUt = compare_aUx
+    compare_aUu = compare_aUx
+    compare_aUv = compare_aUx
+    compare_aUw = compare_aUx
+    AbsBinds [] [] [([], compare_aUx, compare_aUE)]
+	compare_aUE a_rHb b_rHc
+		    = case con2tag_Foo#_rFK [taPA, taPy, taPz] a_rHb of
+			a#_rHZ
+			-> case con2tag_Foo#_rFK [taPA, taPy, taPz] b_rHc of
+			     b#_rI1
+			     -> if a#_rHZ GHC.==#{-79,w-}{I} b#_rI1 then
+				    case cmp_eq_aUF a_rHb b_rHc of
+				      PrelBase.LT{-rb7,p-}{i} -> PrelBase.LT{-rb7,p-}{i}
 				      PrelBase.EQ{-r4n,p-}{i} -> PrelBase.EQ{-r4n,p-}{i}
-				      PrelBase.GT{-rb6,p-}{i} -> PrelBase.GT{-rb6,p-}{i}
+				      PrelBase.GT{-rb8,p-}{i} -> PrelBase.GT{-rb8,p-}{i}
 				else
-				    if a#_rFk GHC.<#{-7b,w-}{I} b#_rFm then
-					PrelBase.LT{-rb5,p-}{i}
+				    if a#_rHZ GHC.<#{-7b,w-}{I} b#_rI1 then
+					PrelBase.LT{-rb7,p-}{i}
 				    else
-					PrelBase.GT{-rb6,p-}{i}
+					PrelBase.GT{-rb8,p-}{i}
 		    where
 			{- nonrec -}
 			AbsBinds
-			[taP3, taP4, taPb]
-			[d.Ord_aPj, d.Ord_aPl, d.Ord_aPn]
-			[([taP3, taP4, taPb], cmp_eq_rEz, cmp_eq_aNe)]
-			    compare_aS8 = PrelBase.compare{-rgH,p-} taP3 d.Ord_aPj
-			    compare_aS9 = compare_aS8
-			    compare_aSa = PrelBase.compare{-rgH,p-} taP4 d.Ord_aPl
-			    compare_aSb = PrelBase.compare{-rgH,p-} taPb d.Ord_aPn
-			    compare_aSc = compare_aSa
-			    compare_aSd = compare_aSa
-			    compare_aSe = compare_aSb
-			    compare_aSf = compare_aSb
-			    cmp_eq_aNe (MkFoo1{-rk,x-}{i} a1_rEB a2_rEC)
-				       (MkFoo1{-rk,x-}{i} b1_rED b2_rEE)
-				       = case compare_aS8 a1_rEB b1_rED of
-					   PrelBase.LT{-rb5,p-}{i} -> PrelBase.LT{-rb5,p-}{i}
+			[taRs, taRt, taRA]
+			[d.Ord_aRI, d.Ord_aRK, d.Ord_aRM]
+			[([taRs, taRt, taRA], cmp_eq_rHe, cmp_eq_aUG)]
+			    compare_aUH = PrelBase.compare{-rgL,p-} taRs d.Ord_aRI
+			    compare_aUI = compare_aUH
+			    compare_aUJ = PrelBase.compare{-rgL,p-} taRt d.Ord_aRK
+			    compare_aUK = PrelBase.compare{-rgL,p-} taRA d.Ord_aRM
+			    compare_aUL = compare_aUJ
+			    compare_aUM = compare_aUJ
+			    compare_aUN = compare_aUK
+			    compare_aUO = compare_aUK
+			    cmp_eq_aUG (MkFoo1{-rk,x-}{i} a1_rHg a2_rHh)
+				       (MkFoo1{-rk,x-}{i} b1_rHi b2_rHj)
+				       = case compare_aUH a1_rHg b1_rHi of
+					   PrelBase.LT{-rb7,p-}{i} -> PrelBase.LT{-rb7,p-}{i}
 					   PrelBase.EQ{-r4n,p-}{i}
-					   -> case compare_aS9 a2_rEC b2_rEE of
-						PrelBase.LT{-rb5,p-}{i} -> PrelBase.LT{-rb5,p-}{i}
+					   -> case compare_aUI a2_rHh b2_rHj of
+						PrelBase.LT{-rb7,p-}{i} -> PrelBase.LT{-rb7,p-}{i}
 						PrelBase.EQ{-r4n,p-}{i} -> PrelBase.EQ{-r4n,p-}{i}
-						PrelBase.GT{-rb6,p-}{i} -> PrelBase.GT{-rb6,p-}{i}
-					   PrelBase.GT{-rb6,p-}{i} -> PrelBase.GT{-rb6,p-}{i}
-			    cmp_eq_aNe (:##{-rj,x-}{i} a1_rEM a2_rEN)
-				       (:##{-rj,x-}{i} b1_rEO b2_rEP)
-				       = case compare_aSa a1_rEM b1_rEO of
-					   PrelBase.LT{-rb5,p-}{i} -> PrelBase.LT{-rb5,p-}{i}
+						PrelBase.GT{-rb8,p-}{i} -> PrelBase.GT{-rb8,p-}{i}
+					   PrelBase.GT{-rb8,p-}{i} -> PrelBase.GT{-rb8,p-}{i}
+			    cmp_eq_aUG (:##{-rj,x-}{i} a1_rHr a2_rHs)
+				       (:##{-rj,x-}{i} b1_rHt b2_rHu)
+				       = case compare_aUJ a1_rHr b1_rHt of
+					   PrelBase.LT{-rb7,p-}{i} -> PrelBase.LT{-rb7,p-}{i}
 					   PrelBase.EQ{-r4n,p-}{i}
-					   -> case compare_aSb a2_rEN b2_rEP of
-						PrelBase.LT{-rb5,p-}{i} -> PrelBase.LT{-rb5,p-}{i}
+					   -> case compare_aUK a2_rHs b2_rHu of
+						PrelBase.LT{-rb7,p-}{i} -> PrelBase.LT{-rb7,p-}{i}
 						PrelBase.EQ{-r4n,p-}{i} -> PrelBase.EQ{-r4n,p-}{i}
-						PrelBase.GT{-rb6,p-}{i} -> PrelBase.GT{-rb6,p-}{i}
-					   PrelBase.GT{-rb6,p-}{i} -> PrelBase.GT{-rb6,p-}{i}
-			    cmp_eq_aNe (MkFoo3{-rm,x-}{i} a1_rEX a2_rEY)
-				       (MkFoo3{-rm,x-}{i} b1_rEZ b2_rF0)
-				       = case compare_aSc a1_rEX b1_rEZ of
-					   PrelBase.LT{-rb5,p-}{i} -> PrelBase.LT{-rb5,p-}{i}
+						PrelBase.GT{-rb8,p-}{i} -> PrelBase.GT{-rb8,p-}{i}
+					   PrelBase.GT{-rb8,p-}{i} -> PrelBase.GT{-rb8,p-}{i}
+			    cmp_eq_aUG (MkFoo3{-rm,x-}{i} a1_rHC a2_rHD)
+				       (MkFoo3{-rm,x-}{i} b1_rHE b2_rHF)
+				       = case compare_aUL a1_rHC b1_rHE of
+					   PrelBase.LT{-rb7,p-}{i} -> PrelBase.LT{-rb7,p-}{i}
 					   PrelBase.EQ{-r4n,p-}{i}
-					   -> case compare_aSd a2_rEY b2_rF0 of
-						PrelBase.LT{-rb5,p-}{i} -> PrelBase.LT{-rb5,p-}{i}
+					   -> case compare_aUM a2_rHD b2_rHF of
+						PrelBase.LT{-rb7,p-}{i} -> PrelBase.LT{-rb7,p-}{i}
 						PrelBase.EQ{-r4n,p-}{i} -> PrelBase.EQ{-r4n,p-}{i}
-						PrelBase.GT{-rb6,p-}{i} -> PrelBase.GT{-rb6,p-}{i}
-					   PrelBase.GT{-rb6,p-}{i} -> PrelBase.GT{-rb6,p-}{i}
-			    cmp_eq_aNe (:***{-ro,x-}{i} a1_rF8 a2_rF9)
-				       (:***{-ro,x-}{i} b1_rFa b2_rFb)
-				       = case compare_aSe a1_rF8 b1_rFa of
-					   PrelBase.LT{-rb5,p-}{i} -> PrelBase.LT{-rb5,p-}{i}
+						PrelBase.GT{-rb8,p-}{i} -> PrelBase.GT{-rb8,p-}{i}
+					   PrelBase.GT{-rb8,p-}{i} -> PrelBase.GT{-rb8,p-}{i}
+			    cmp_eq_aUG (:***{-ro,x-}{i} a1_rHN a2_rHO)
+				       (:***{-ro,x-}{i} b1_rHP b2_rHQ)
+				       = case compare_aUN a1_rHN b1_rHP of
+					   PrelBase.LT{-rb7,p-}{i} -> PrelBase.LT{-rb7,p-}{i}
 					   PrelBase.EQ{-r4n,p-}{i}
-					   -> case compare_aSf a2_rF9 b2_rFb of
-						PrelBase.LT{-rb5,p-}{i} -> PrelBase.LT{-rb5,p-}{i}
+					   -> case compare_aUO a2_rHO b2_rHQ of
+						PrelBase.LT{-rb7,p-}{i} -> PrelBase.LT{-rb7,p-}{i}
 						PrelBase.EQ{-r4n,p-}{i} -> PrelBase.EQ{-r4n,p-}{i}
-						PrelBase.GT{-rb6,p-}{i} -> PrelBase.GT{-rb6,p-}{i}
-					   PrelBase.GT{-rb6,p-}{i} -> PrelBase.GT{-rb6,p-}{i}
-			    cmp_eq_aNe _ _
-				       = IOBase.error{-87,w-}
-					     PrelBase.Ordering{-3o,p-} "Urk! in TcGenDeriv"
+						PrelBase.GT{-rb8,p-}{i} -> PrelBase.GT{-rb8,p-}{i}
+					   PrelBase.GT{-rb8,p-}{i} -> PrelBase.GT{-rb8,p-}{i}
+			    cmp_eq_aUG _ _
+				       = Error.error{-87,w-}
+					     PrelBase.Ordering{-3n,p-} "Urk! in TcGenDeriv"
 			{- nonrec -}
-			cmp_eq_aS7 =
-			    cmp_eq_rEz [taN8, taN9, taNa] [d.Ord_aPR, d.Ord_aPS, d.Ord_aPT]
+			cmp_eq_aUF =
+			    cmp_eq_rHe [taPy, taPz, taPA] [d.Ord_aSg, d.Ord_aSh, d.Ord_aSi]
 			{- nonrec -}
-    AbsBinds [] [] [([], <_aS1, <_aPY)]
-	<_aPY a_rDK b_rDL
-	      = case compare_aRU a_rDK b_rDL of
-		  PrelBase.LT{-rb5,p-}{i} -> PrelBase.True{-5E,w-}{i}
+    AbsBinds [] [] [([], <_aUy, <_aUP)]
+	<_aUP a_rGp b_rGq
+	      = case compare_aUr a_rGp b_rGq of
+		  PrelBase.LT{-rb7,p-}{i} -> PrelBase.True{-5E,w-}{i}
 		  PrelBase.EQ{-r4n,p-}{i} -> PrelBase.False{-58,w-}{i}
-		  PrelBase.GT{-rb6,p-}{i} -> PrelBase.False{-58,w-}{i}
-    AbsBinds [] [] [([], <=_aS2, <=_aQb)]
-	<=_aQb a_rDS b_rDT
-	       = case compare_aRV a_rDS b_rDT of
-		   PrelBase.LT{-rb5,p-}{i} -> PrelBase.True{-5E,w-}{i}
+		  PrelBase.GT{-rb8,p-}{i} -> PrelBase.False{-58,w-}{i}
+    AbsBinds [] [] [([], <=_aUz, <=_aUQ)]
+	<=_aUQ a_rGx b_rGy
+	       = case compare_aUs a_rGx b_rGy of
+		   PrelBase.LT{-rb7,p-}{i} -> PrelBase.True{-5E,w-}{i}
 		   PrelBase.EQ{-r4n,p-}{i} -> PrelBase.True{-5E,w-}{i}
-		   PrelBase.GT{-rb6,p-}{i} -> PrelBase.False{-58,w-}{i}
-    AbsBinds [] [] [([], >=_aS3, >=_aQo)]
-	>=_aQo a_rE0 b_rE1
-	       = case compare_aRW a_rE0 b_rE1 of
-		   PrelBase.LT{-rb5,p-}{i} -> PrelBase.False{-58,w-}{i}
+		   PrelBase.GT{-rb8,p-}{i} -> PrelBase.False{-58,w-}{i}
+    AbsBinds [] [] [([], >=_aUA, >=_aUR)]
+	>=_aUR a_rGF b_rGG
+	       = case compare_aUt a_rGF b_rGG of
+		   PrelBase.LT{-rb7,p-}{i} -> PrelBase.False{-58,w-}{i}
 		   PrelBase.EQ{-r4n,p-}{i} -> PrelBase.True{-5E,w-}{i}
-		   PrelBase.GT{-rb6,p-}{i} -> PrelBase.True{-5E,w-}{i}
-    AbsBinds [] [] [([], >_aS4, >_aQB)]
-	>_aQB a_rE8 b_rE9
-	      = case compare_aRX a_rE8 b_rE9 of
-		  PrelBase.LT{-rb5,p-}{i} -> PrelBase.False{-58,w-}{i}
+		   PrelBase.GT{-rb8,p-}{i} -> PrelBase.True{-5E,w-}{i}
+    AbsBinds [] [] [([], >_aUB, >_aUS)]
+	>_aUS a_rGN b_rGO
+	      = case compare_aUu a_rGN b_rGO of
+		  PrelBase.LT{-rb7,p-}{i} -> PrelBase.False{-58,w-}{i}
 		  PrelBase.EQ{-r4n,p-}{i} -> PrelBase.False{-58,w-}{i}
-		  PrelBase.GT{-rb6,p-}{i} -> PrelBase.True{-5E,w-}{i}
-    AbsBinds [] [] [([], max_aS5, max_aQO)]
-	max_aQO a_rEg b_rEh
-		= case compare_aRY a_rEg b_rEh of
-		    PrelBase.LT{-rb5,p-}{i} -> b_rEh
-		    PrelBase.EQ{-r4n,p-}{i} -> a_rEg
-		    PrelBase.GT{-rb6,p-}{i} -> a_rEg
-    AbsBinds [] [] [([], min_aS6, min_aR1)]
-	min_aR1 a_rEo b_rEp
-		= case compare_aRZ a_rEo b_rEp of
-		    PrelBase.LT{-rb5,p-}{i} -> a_rEo
-		    PrelBase.EQ{-r4n,p-}{i} -> b_rEp
-		    PrelBase.GT{-rb6,p-}{i} -> b_rEp
-    d.Ord_aN1 =
+		  PrelBase.GT{-rb8,p-}{i} -> PrelBase.True{-5E,w-}{i}
+    AbsBinds [] [] [([], max_aUC, max_aUT)]
+	max_aUT a_rGV b_rGW
+		= case compare_aUv a_rGV b_rGW of
+		    PrelBase.LT{-rb7,p-}{i} -> b_rGW
+		    PrelBase.EQ{-r4n,p-}{i} -> a_rGV
+		    PrelBase.GT{-rb8,p-}{i} -> a_rGV
+    AbsBinds [] [] [([], min_aUD, min_aUU)]
+	min_aUU a_rH3 b_rH4
+		= case compare_aUw a_rH3 b_rH4 of
+		    PrelBase.LT{-rb7,p-}{i} -> a_rH3
+		    PrelBase.EQ{-r4n,p-}{i} -> b_rH4
+		    PrelBase.GT{-rb8,p-}{i} -> b_rH4
+    d.Ord_aPs =
 	({-dict-}
-	 [d.Eq_aR9]
-	 [compare_aS0, <_aS1, <=_aS2, >=_aS3, >_aS4, max_aS5, min_aS6])
-scsel_Bar2Print002Bar{-aRF,x-} = _/\_ t12 -> \ tpl_B1 -> tpl_B1
-AbsBinds [taRz] [d.Bar2_aRs] []
+	 [d.Eq_aTs]
+	 [compare_aUx, <_aUy, <=_aUz, >=_aUA, >_aUB, max_aUC, min_aUD])
+scsel_Bar2Print002Bar{-aTZ,x-} = _/\_ t12 -> \ tpl_B1 -> tpl_B1
+AbsBinds [taTS] [d.Bar2_aTL] []
 meth1{-r4B,x-} =
     _/\_ t12 -> \ tpl_B1 ->
 	case tpl_B1 of { PrelTup.(,,){-63,w-}{i} tpl_B1 tpl_B2 tpl_B3  ->
@@ -260,15 +260,12 @@ meth2{-r4D,x-} =
     _/\_ t12 -> \ tpl_B1 ->
 	case tpl_B1 of { PrelTup.(,,){-63,w-}{i} tpl_B1 tpl_B2 tpl_B3  ->
 	tpl_B3;}
-AbsBinds [taRA] [d.Bar_aRv] []
+AbsBinds [taTT] [d.Bar_aTO] []
 
-Print002.hs:35: 
-    Warning: Pattern match(es) completely overlapped
-	in the definition of function `<<<<'
 ghc: module version changed to 1; reason: no old .hi file
 _interface_ Print002 1
 _instance_modules_
-ArrBase IO PrelNum
+Addr ArrBase Foreign IO PrelNum
 _usages_
 PrelBase 1 :: $d15 1 $d16 1 $d2 1 $d33 1 $d35 1 $d38 1 $d40 1 $d42 1 $d46 1 $d47 1 $d50 1 $d52 1 $d7 1 $d8 1 $m/= 1 $m< 1 $m<= 1 $m> 1 $m>= 1 $mcompare 1 $mmax 1 $mmin 1 && 1 . 1 not 1 Eq 1 Eval 1 Ord 1 Ordering 1;
 PrelNum 1 :: $d17 1 $d18 1;
diff --git a/ghc/tests/printing/should_compile/Print003.stderr b/ghc/tests/printing/should_compile/Print003.stderr
index f834031470b18e3adaf47c64b0ab1e091589c18d..3d1d9da65149736d20fe65fc947f70eca2f73c0d 100644
--- a/ghc/tests/printing/should_compile/Print003.stderr
+++ b/ghc/tests/printing/should_compile/Print003.stderr
@@ -5,12 +5,12 @@ bitRsh{-r3h,x-} =
 bitLsh{-r3i,x-} =
     _/\_ t12 -> \ tpl_B1 ->
 	case tpl_B1 of { PrelTup.(,){-62,w-}{i} tpl_B1 tpl_B2  -> tpl_B2;}
-AbsBinds [takI] [d.Bits_akH] []
+AbsBinds [tamf] [d.Bits_ame] []
 
 ghc: module version changed to 1; reason: no old .hi file
 _interface_ Word 1
 _instance_modules_
-ArrBase IO PrelNum
+Addr ArrBase Foreign IO PrelNum
 _exports_
 Word Bits(bitRsh bitLsh);
 _fixities_
diff --git a/ghc/tests/printing/should_compile/Print004.stderr b/ghc/tests/printing/should_compile/Print004.stderr
index 8a253dd06d40b0c3b4106005bd1acba8c03ead86..264777112a3eb5dcb84648d8ea42dda809f4cf82 100644
--- a/ghc/tests/printing/should_compile/Print004.stderr
+++ b/ghc/tests/printing/should_compile/Print004.stderr
@@ -1,56 +1,56 @@
  
-Print004.hs:18: No explicit method nor default method for `PrelBase.showsPrec'
-		in an instance declaration for `PrelBase.Show'
+Print004.hs:18: Warning: no explicit method nor default method for `showsPrec'
+		in an instance declaration for `Show'
 ==================== Typechecked ====================
 Con{-r6u,l-}{i} =
     _/\_ a_tr6C -> \ tpl_B1 -> Con{-r6u,l-}{i} {_@_ a_tr6C tpl_B1}
 Junk11{-r4,l-}{i} = _/\_ a_tr6A -> Junk11{-r4,l-}{i} {_@_ a_tr6A}
 Junk2{-r3,l-}{i} = _/\_ a_tr6A -> Junk2{-r3,l-}{i} {_@_ a_tr6A}
-AbsBinds [taFU] [] [([taFU], $d2{-rFW,x-}, d.Eval_aEz)]
-    d.Eval_aEz = ({-dict-} [] [])
-AbsBinds [taFV] [] [([taFV], $d3{-rFX,x-}, d.Eval_aEF)]
-    d.Eval_aEF = ({-dict-} [] [])
-AbsBinds [taEV] [d.Ord_aFg] [([taEV], $d4{-rFY,x-}, d.Show_aEL)]
-    d.Ord_aFo = d.Ord_aFg
-    d.Show_aFm = $d1{-rFZ,x-} taEV d.Ord_aFo
-    showsPrec_aG2 =
-	PrelBase.showsPrec{-r2c,p-} (FunnyInternalType{-r6v,l-} taEV)
-	    d.Show_aFm
-    showsPrec_aG3 = showsPrec_aG4
-    AbsBinds [] [] [([], showsPrec_aG4, showsPrec_aEP)]
-	showsPrec_aEP a_rDS (Con{-r6u,l-}{i} b1_rDT)
-		      = PrelBase.showParen{-r16,p-} a_rDS >=_aG0 lit_aG1
+AbsBinds [taIv] [] [([taIv], $d2{-rIx,x-}, d.Eval_aHe)]
+    d.Eval_aHe = ({-dict-} [] [])
+AbsBinds [taIw] [] [([taIw], $d3{-rIy,x-}, d.Eval_aHk)]
+    d.Eval_aHk = ({-dict-} [] [])
+AbsBinds [taHz] [d.Ord_aHT] [([taHz], $d4{-rIz,x-}, d.Show_aHq)]
+    d.Ord_aI1 = d.Ord_aHT
+    d.Show_aHZ = $d1{-rIA,x-} taHz d.Ord_aI1
+    showsPrec_aID =
+	PrelBase.showsPrec{-r2c,p-} (FunnyInternalType{-r6v,l-} taHz)
+	    d.Show_aHZ
+    showsPrec_aIE = showsPrec_aIF
+    AbsBinds [] [] [([], showsPrec_aIF, showsPrec_aIH)]
+	showsPrec_aIH a_rGx (Con{-r6u,l-}{i} b1_rGy)
+		      = PrelBase.showParen{-r16,p-} a_rGx >=_aIB lit_aIC
 						    PrelBase..{-rI,p-}
 							[PrelBase.String{-r2i,p-}, PrelBase.String{-r2i,p-}, PrelBase.String{-r2i,p-}] PrelBase.showString{-r18,p-} "Con "
-																       showsPrec_aG2 PrelBase.I#{-5b,w-}{i} 10#
-																		     b1_rDT
-    AbsBinds [] [] [([], showList_aG5, showList_aFb)]
-	showList_aFb = PrelBase.showList__{-r6F,p-}
-			   (OpaqueType{-r6,x-} taEV) showsPrec_aG3 PrelBase.I#{-5b,w-}{i} 0#
-    d.Show_aEL = ({-dict-} [] [showsPrec_aG4, showList_aG5])
-AbsBinds [taFD] [d.Ord_aFM] [([taFD], $d1{-rFZ,x-}, d.Show_aFv)]
-    d.Show_aFQ = d.Show_aFv
-    $mshowList_aG6 =
-	PrelBase.$mshowList{-rif,p-} (FunnyInternalType{-r6v,l-} taFD)
-	    d.Show_aFQ
-    AbsBinds [] [] [([], showsPrec_aG7, showsPrec_aFA)]
-	showsPrec_aFA
+																       showsPrec_aID PrelBase.I#{-5b,w-}{i} 10#
+																		     b1_rGy
+    AbsBinds [] [] [([], showList_aIG, showList_aII)]
+	showList_aII = PrelBase.showList__{-r6F,p-}
+			   (OpaqueType{-r6,x-} taHz) showsPrec_aIE PrelBase.I#{-5b,w-}{i} 0#
+    d.Show_aHq = ({-dict-} [] [showsPrec_aIF, showList_aIG])
+AbsBinds [taIf] [d.Ord_aIn] [([taIf], $d1{-rIA,x-}, d.Show_aI8)]
+    d.Show_aIr = d.Show_aI8
+    $mshowList_aIJ =
+	PrelBase.$mshowList{-rii,p-} (FunnyInternalType{-r6v,l-} taIf)
+	    d.Show_aIr
+    AbsBinds [] [] [([], showsPrec_aIK, showsPrec_aIM)]
+	showsPrec_aIM
 	    = GHCerr.noDefaultMethodError{-8k,w-}
-		  (PrelBase.Int{-3g,W-}
-		   -> FunnyInternalType{-r6v,l-} taFD
+		  (PrelBase.Int{-3f,W-}
+		   -> FunnyInternalType{-r6v,l-} taIf
 		   -> PrelBase.String{-r2i,p-}
-		   -> PrelBase.String{-r2i,p-}) "<NoSrcLoc>|PrelBase.showsPrec"
-    AbsBinds [] [] [([], showList_aG8, showList_aFJ)]
-	showList_aFJ = $mshowList_aG6
-    d.Show_aFv = ({-dict-} [] [showsPrec_aG7, showList_aG8])
-d.Ord_aFT = PrelBase.$d7{-rdY,p-}
->=_aG0 = PrelBase.>={-8Z,p-} PrelBase.Int{-3g,W-} d.Ord_aFT
-lit_aG1 = PrelBase.I#{-5b,w-}{i} 10#
+		   -> PrelBase.String{-r2i,p-}) "<NoSrcLoc>|showsPrec"
+    AbsBinds [] [] [([], showList_aIL, showList_aIN)]
+	showList_aIN = $mshowList_aIJ
+    d.Show_aI8 = ({-dict-} [] [showsPrec_aIK, showList_aIL])
+d.Ord_aIu = PrelBase.$d7{-re0,p-}
+>=_aIB = PrelBase.>={-810,p-} PrelBase.Int{-3f,W-} d.Ord_aIu
+lit_aIC = PrelBase.I#{-5b,w-}{i} 10#
 
 ghc: module version changed to 1; reason: no old .hi file
 _interface_ ExportOpaque 1
 _instance_modules_
-ArrBase IO PrelNum
+Addr ArrBase Foreign IO PrelNum
 _usages_
 PrelBase 1 :: $d1 1 $d12 1 $d15 1 $d16 1 $d2 1 $d22 1 $d27 1 $d28 1 $d3 1 $d33 1 $d34 1 $d35 1 $d38 1 $d39 1 $d4 1 $d40 1 $d42 1 $d43 1 $d45 1 $d46 1 $d47 1 $d50 1 $d51 1 $d52 1 $d55 1 $d56 1 $d7 1 $d8 1 $d9 1 $m- 1 $m/= 1 $m< 1 $m<= 1 $m> 1 $m>= 1 $mcompare 1 $mfromInt 1 $mmax 1 $mmin 1 $mshowList 1 . 1 showList__ 1 showParen 1 showSpace 1 showString 1 Eq 1 Eval 1 Num 1 Ord 1 Ordering 1 Show 1 ShowS 1 String 1;
 PrelNum 1 :: $d10 1 $d16 1 $d17 1 $d18 1 $d29 1 $d33 1 $d34 1 $d35 1;
diff --git a/ghc/tests/reader/should_fail/read001.stderr b/ghc/tests/reader/should_fail/read001.stderr
index c0b3af1fbac6e073d245039285e957045e5a32ac..3691e5d1c032716132b11d0c2dec9a2ffcb14975 100644
--- a/ghc/tests/reader/should_fail/read001.stderr
+++ b/ghc/tests/reader/should_fail/read001.stderr
@@ -42,7 +42,7 @@ expr a b c d
 	   + ((9 *)))
 	  + ((* 8)))
 	 + (case x of
-	      []
+	      Prelude.[]
 	      | null x -> 99
 	      | otherwise -> 98
 	      | True -> 97
diff --git a/ghc/tests/reader/should_fail/read003.stderr b/ghc/tests/reader/should_fail/read003.stderr
index 60371414c688fb3509acd3e2622867ba6d373981..43e9e8da8218d3f830b3e0291a9f5ad24d882ebe 100644
--- a/ghc/tests/reader/should_fail/read003.stderr
+++ b/ghc/tests/reader/should_fail/read003.stderr
@@ -11,15 +11,15 @@ module Read003 where
 
  
 read003.hs:8: Cannot construct the infinite type (occur check)
-		  `taGL' = `(taGL, taGO, taGR)'
-    Expected: `taGL'
-    Inferred: `(taGL, [taH0], taGR)'
+		  `taIl' = `(taIl, taIo, taIr)'
+    Expected: `taIl'
+    Inferred: `(taIl, [taIz], taIr)'
     In a pattern binding:
 	`~(a, b, c)
 	     | nullity b = a
 	     | nullity c = a
-	     | PrelBase.otherwise = a
+	     | otherwise = a
 	     where
-		 nullity = PrelList.null'
+		 nullity = null'
 
 Compilation had errors
diff --git a/ghc/tests/rename/should_compile/rn022.stderr b/ghc/tests/rename/should_compile/rn022.stderr
index 096cbd6426de618bee4b14a408d11dcccb71dac0..e69de29bb2d1d6434b8b29ae775ad8c2e48c5391 100644
--- a/ghc/tests/rename/should_compile/rn022.stderr
+++ b/ghc/tests/rename/should_compile/rn022.stderr
@@ -1,6 +0,0 @@
-rn022.hs:9: 
-    Warning: Possibly incomplete patterns
-	in the definition of function `f'
-rn022.hs:11: 
-    Warning: Possibly incomplete patterns
-	in the definition of function `g'
diff --git a/ghc/tests/rename/should_fail/rnfail007.stderr b/ghc/tests/rename/should_fail/rnfail007.stderr
index 99f54cd8be352cb8accd81fa17ec639be8f294c1..ce39d461d05f817161043c7b09cb3da9742a6afe 100644
--- a/ghc/tests/rename/should_fail/rnfail007.stderr
+++ b/ghc/tests/rename/should_fail/rnfail007.stderr
@@ -1,4 +1,4 @@
  
-rnfail007.hs:3: Module Main must include a definition for `Main.main'
+rnfail007.hs:3: Module Main must include a definition for `main'
 
 Compilation had errors
diff --git a/ghc/tests/rename/should_fail/rnfail008.stderr b/ghc/tests/rename/should_fail/rnfail008.stderr
index 36ec7437fc09baf89634e94825f7e94b4841e801..41b22f2a60fc3e342cde0292dcfacb8f1bf14444 100644
--- a/ghc/tests/rename/should_fail/rnfail008.stderr
+++ b/ghc/tests/rename/should_fail/rnfail008.stderr
@@ -1,11 +1,11 @@
  
-rnfail008.hs:18: No explicit method nor default method for `op1'
+rnfail008.hs:18: Warning: no explicit method nor default method for `op1'
 		 in an instance declaration for `K'
  
-rnfail008.hs:18: No explicit method nor default method for `op2'
+rnfail008.hs:18: Warning: no explicit method nor default method for `op2'
 		 in an instance declaration for `K'
  
-rnfail008.hs:14: No explicit method nor default method for `op2'
+rnfail008.hs:14: Warning: no explicit method nor default method for `op2'
 		 in an instance declaration for `K'
  
 rnfail008.hs:18: Class `K' does not have a method `op3'
diff --git a/ghc/tests/typecheck/should_compile/tc001.stderr b/ghc/tests/typecheck/should_compile/tc001.stderr
index 11802c8f259210e72281981ee2fddc6a48e3289a..88a4388793c21e8b1714d581df94d9926cce9929 100644
--- a/ghc/tests/typecheck/should_compile/tc001.stderr
+++ b/ghc/tests/typecheck/should_compile/tc001.stderr
@@ -1,7 +1,7 @@
 ghc: module version changed to 1; reason: no old .hi file
 _interface_ ShouldSucceed 1
 _instance_modules_
-ArrBase IO PrelNum
+Addr ArrBase Foreign IO PrelNum
 _usages_
 PrelBase 1 :: $d1 1 $d12 1 $d16 1 $d2 1 $d22 1 $d28 1 $d3 1 $d33 1 $d34 1 $d38 1 $d39 1 $d4 1 $d40 1 $d42 1 $d43 1 $d45 1 $d47 1 $d55 1 $d8 1 $d9 1 $m- 1 $m/= 1 $mfromInt 1 $mshowList 1 Eq 1 Eval 1 Num 1 Show 1 String 1;
 PrelNum 1 :: $d10 1 $d16 1 $d18 1 $d29 1 $d33 1 $d35 1;
diff --git a/ghc/tests/typecheck/should_compile/tc002.stderr b/ghc/tests/typecheck/should_compile/tc002.stderr
index 1daaf64253595bf659313a1610d4a70b9995eef6..c9c56095674a3347d9010a0fcd9c4b6f8d3da5a4 100644
--- a/ghc/tests/typecheck/should_compile/tc002.stderr
+++ b/ghc/tests/typecheck/should_compile/tc002.stderr
@@ -1,7 +1,7 @@
 ghc: module version changed to 1; reason: no old .hi file
 _interface_ ShouldSucceed 1
 _instance_modules_
-ArrBase IO PrelNum
+Addr ArrBase Foreign IO PrelNum
 _usages_
 PrelBase 1 :: $d1 1 $d12 1 $d16 1 $d2 1 $d22 1 $d28 1 $d3 1 $d33 1 $d34 1 $d38 1 $d39 1 $d4 1 $d40 1 $d42 1 $d43 1 $d45 1 $d47 1 $d55 1 $d8 1 $d9 1 $m- 1 $m/= 1 $mfromInt 1 $mshowList 1 Eq 1 Eval 1 Num 1 Show 1 String 1;
 PrelNum 1 :: $d10 1 $d16 1 $d18 1 $d29 1 $d33 1 $d35 1;
diff --git a/ghc/tests/typecheck/should_compile/tc003.stderr b/ghc/tests/typecheck/should_compile/tc003.stderr
index 68f4b9880e0060b238f8cb2ec22a62cbf1694e9a..508a6f13943170724b5e210604651e34237017b5 100644
--- a/ghc/tests/typecheck/should_compile/tc003.stderr
+++ b/ghc/tests/typecheck/should_compile/tc003.stderr
@@ -1,7 +1,7 @@
 ghc: module version changed to 1; reason: no old .hi file
 _interface_ ShouldSucceed 1
 _instance_modules_
-ArrBase IO PrelNum
+Addr ArrBase Foreign IO PrelNum
 _usages_
 PrelBase 1 :: $d1 1 $d12 1 $d16 1 $d2 1 $d22 1 $d28 1 $d3 1 $d33 1 $d34 1 $d38 1 $d39 1 $d4 1 $d40 1 $d42 1 $d43 1 $d45 1 $d47 1 $d55 1 $d8 1 $d9 1 $m- 1 $m/= 1 $mfromInt 1 $mshowList 1 Eq 1 Eval 1 Num 1 Show 1 String 1;
 PrelNum 1 :: $d10 1 $d16 1 $d18 1 $d29 1 $d33 1 $d35 1;
diff --git a/ghc/tests/typecheck/should_compile/tc004.stderr b/ghc/tests/typecheck/should_compile/tc004.stderr
index d102fb9b6c5ef7a5b2876f4c07932fd2d56a8b11..8220d5bf347acf3189555e534d5463307ef54ffb 100644
--- a/ghc/tests/typecheck/should_compile/tc004.stderr
+++ b/ghc/tests/typecheck/should_compile/tc004.stderr
@@ -1,7 +1,7 @@
 ghc: module version changed to 1; reason: no old .hi file
 _interface_ ShouldSucceed 1
 _instance_modules_
-ArrBase IO PrelNum
+Addr ArrBase Foreign IO PrelNum
 _exports_
 ShouldSucceed f;
 _declarations_
diff --git a/ghc/tests/typecheck/should_compile/tc005.stderr b/ghc/tests/typecheck/should_compile/tc005.stderr
index 0937f4b90fd8b5f6b5a9ce83dc0fd89469982879..ea6a75006d60dd2eaab164d634a1726dc0c80ea7 100644
--- a/ghc/tests/typecheck/should_compile/tc005.stderr
+++ b/ghc/tests/typecheck/should_compile/tc005.stderr
@@ -1,7 +1,7 @@
 ghc: module version changed to 1; reason: no old .hi file
 _interface_ ShouldSucceed 1
 _instance_modules_
-ArrBase IO PrelNum
+Addr ArrBase Foreign IO PrelNum
 _usages_
 PrelBase 1 :: $d1 1 $d12 1 $d16 1 $d2 1 $d22 1 $d28 1 $d3 1 $d33 1 $d34 1 $d38 1 $d39 1 $d4 1 $d40 1 $d42 1 $d43 1 $d45 1 $d47 1 $d55 1 $d8 1 $d9 1 $m- 1 $m/= 1 $mfromInt 1 $mshowList 1 Eq 1 Eval 1 Num 1 Show 1 String 1;
 PrelNum 1 :: $d10 1 $d16 1 $d18 1 $d29 1 $d33 1 $d35 1;
diff --git a/ghc/tests/typecheck/should_compile/tc006.stderr b/ghc/tests/typecheck/should_compile/tc006.stderr
index 391fe62c39ae7e7bca6c4e5cbe9cc4d7025ccca0..05f49c6a467db0b1a84e0518ec444d14a4c788e0 100644
--- a/ghc/tests/typecheck/should_compile/tc006.stderr
+++ b/ghc/tests/typecheck/should_compile/tc006.stderr
@@ -1,7 +1,7 @@
 ghc: module version changed to 1; reason: no old .hi file
 _interface_ ShouldSucceed 1
 _instance_modules_
-ArrBase IO PrelNum
+Addr ArrBase Foreign IO PrelNum
 _usages_
 PrelBase 1 :: $d1 1 $d12 1 $d16 1 $d2 1 $d22 1 $d28 1 $d3 1 $d33 1 $d34 1 $d38 1 $d39 1 $d4 1 $d40 1 $d42 1 $d43 1 $d45 1 $d47 1 $d55 1 $d8 1 $d9 1 $m- 1 $m/= 1 $mfromInt 1 $mshowList 1 Eq 1 Eval 1 Num 1 Show 1 String 1;
 PrelNum 1 :: $d10 1 $d16 1 $d18 1 $d29 1 $d33 1 $d35 1;
diff --git a/ghc/tests/typecheck/should_compile/tc007.stderr b/ghc/tests/typecheck/should_compile/tc007.stderr
index 6c3b87eb1976026f3f1e5de3400f084c543a3ff8..84f0bb1c4760ce8759a508c18d161e2f8ae9cbcf 100644
--- a/ghc/tests/typecheck/should_compile/tc007.stderr
+++ b/ghc/tests/typecheck/should_compile/tc007.stderr
@@ -1,7 +1,7 @@
 ghc: module version changed to 1; reason: no old .hi file
 _interface_ ShouldSucceed 1
 _instance_modules_
-ArrBase IO PrelNum
+Addr ArrBase Foreign IO PrelNum
 _usages_
 PrelBase 1 :: $d1 1 $d12 1 $d16 1 $d2 1 $d22 1 $d28 1 $d3 1 $d33 1 $d34 1 $d38 1 $d39 1 $d4 1 $d40 1 $d42 1 $d43 1 $d45 1 $d47 1 $d55 1 $d8 1 $d9 1 $m- 1 $m/= 1 $mfromInt 1 $mshowList 1 Eq 1 Eval 1 Num 1 Show 1 String 1;
 PrelNum 1 :: $d10 1 $d16 1 $d18 1 $d29 1 $d33 1 $d35 1;
diff --git a/ghc/tests/typecheck/should_compile/tc008.stderr b/ghc/tests/typecheck/should_compile/tc008.stderr
index 67e97e9ed03e68df784831bd7f9c75015f215164..aa89166155448d75fd5f3e69a84420aead75c619 100644
--- a/ghc/tests/typecheck/should_compile/tc008.stderr
+++ b/ghc/tests/typecheck/should_compile/tc008.stderr
@@ -1,7 +1,7 @@
 ghc: module version changed to 1; reason: no old .hi file
 _interface_ ShouldSucceed 1
 _instance_modules_
-ArrBase IO PrelNum
+Addr ArrBase Foreign IO PrelNum
 _usages_
 PrelBase 1 :: $d1 1 $d12 1 $d16 1 $d2 1 $d22 1 $d28 1 $d3 1 $d33 1 $d34 1 $d38 1 $d39 1 $d4 1 $d40 1 $d42 1 $d43 1 $d45 1 $d47 1 $d55 1 $d8 1 $d9 1 $m- 1 $m/= 1 $mfromInt 1 $mshowList 1 Eq 1 Eval 1 Num 1 Show 1 String 1;
 PrelNum 1 :: $d10 1 $d16 1 $d18 1 $d29 1 $d33 1 $d35 1;
diff --git a/ghc/tests/typecheck/should_compile/tc009.stderr b/ghc/tests/typecheck/should_compile/tc009.stderr
index f12bd58f60d0423847842706bd16f027abedc14c..71f58ca4201b3418d47fbb28f673ee13adb026ab 100644
--- a/ghc/tests/typecheck/should_compile/tc009.stderr
+++ b/ghc/tests/typecheck/should_compile/tc009.stderr
@@ -1,7 +1,7 @@
 ghc: module version changed to 1; reason: no old .hi file
 _interface_ ShouldSucceed 1
 _instance_modules_
-ArrBase IO PrelNum
+Addr ArrBase Foreign IO PrelNum
 _usages_
 PrelBase 1 :: $d1 1 $d12 1 $d16 1 $d2 1 $d22 1 $d28 1 $d3 1 $d33 1 $d34 1 $d38 1 $d39 1 $d4 1 $d40 1 $d42 1 $d43 1 $d45 1 $d47 1 $d55 1 $d8 1 $d9 1 $m- 1 $m/= 1 $mfromInt 1 $mshowList 1 Eq 1 Eval 1 Num 1 Show 1 String 1;
 PrelNum 1 :: $d10 1 $d16 1 $d18 1 $d29 1 $d33 1 $d35 1;
diff --git a/ghc/tests/typecheck/should_compile/tc010.stderr b/ghc/tests/typecheck/should_compile/tc010.stderr
index cc53509bf3cbf20e6ad77dabba27ebf1b0f421c5..1171203a6e329121074cdcaa49ddb86439caa65b 100644
--- a/ghc/tests/typecheck/should_compile/tc010.stderr
+++ b/ghc/tests/typecheck/should_compile/tc010.stderr
@@ -1,7 +1,7 @@
 ghc: module version changed to 1; reason: no old .hi file
 _interface_ ShouldSucceed 1
 _instance_modules_
-ArrBase IO PrelNum
+Addr ArrBase Foreign IO PrelNum
 _usages_
 PrelBase 1 :: $d1 1 $d12 1 $d16 1 $d2 1 $d22 1 $d24 1 $d25 1 $d28 1 $d3 1 $d33 1 $d34 1 $d38 1 $d39 1 $d4 1 $d40 1 $d42 1 $d43 1 $d45 1 $d47 1 $d55 1 $d8 1 $d9 1 $m- 1 $m/= 1 $m>> 1 $mfromInt 1 $mshowList 1 Eq 1 Eval 1 Monad 1 MonadZero 1 Num 1 Show 1 String 1;
 PrelNum 1 :: $d10 1 $d16 1 $d18 1 $d29 1 $d33 1 $d35 1;
diff --git a/ghc/tests/typecheck/should_compile/tc011.stderr b/ghc/tests/typecheck/should_compile/tc011.stderr
index 4d864308e2d6246008baa23b445ab696d9cf698d..35af5a10a004158bbab376f12596d4455c3d8463 100644
--- a/ghc/tests/typecheck/should_compile/tc011.stderr
+++ b/ghc/tests/typecheck/should_compile/tc011.stderr
@@ -1,7 +1,7 @@
 ghc: module version changed to 1; reason: no old .hi file
 _interface_ ShouldSucceed 1
 _instance_modules_
-ArrBase IO PrelNum
+Addr ArrBase Foreign IO PrelNum
 _exports_
 ShouldSucceed x;
 _declarations_
diff --git a/ghc/tests/typecheck/should_compile/tc012.stderr b/ghc/tests/typecheck/should_compile/tc012.stderr
index 0959c286cd2cf6e615f23be8f488670e22edd486..e3f87fcd31bb8af3bc3476e92b1a8ed3b8b244d4 100644
--- a/ghc/tests/typecheck/should_compile/tc012.stderr
+++ b/ghc/tests/typecheck/should_compile/tc012.stderr
@@ -1,7 +1,7 @@
 ghc: module version changed to 1; reason: no old .hi file
 _interface_ ShouldSucceed 1
 _instance_modules_
-ArrBase IO PrelNum
+Addr ArrBase Foreign IO PrelNum
 _exports_
 ShouldSucceed q;
 _declarations_
diff --git a/ghc/tests/typecheck/should_compile/tc013.stderr b/ghc/tests/typecheck/should_compile/tc013.stderr
index a7dedfc2efef175da8889d10455c1fd7f3cca72d..2146b79428ecca9af13e803fe3ddf54e9e12797a 100644
--- a/ghc/tests/typecheck/should_compile/tc013.stderr
+++ b/ghc/tests/typecheck/should_compile/tc013.stderr
@@ -1,7 +1,7 @@
 ghc: module version changed to 1; reason: no old .hi file
 _interface_ ShouldSucceed 1
 _instance_modules_
-ArrBase IO PrelNum
+Addr ArrBase Foreign IO PrelNum
 _usages_
 PrelBase 1 :: $d1 1 $d12 1 $d16 1 $d2 1 $d22 1 $d28 1 $d3 1 $d33 1 $d34 1 $d38 1 $d39 1 $d4 1 $d40 1 $d42 1 $d43 1 $d45 1 $d47 1 $d55 1 $d8 1 $d9 1 $m- 1 $m/= 1 $mfromInt 1 $mshowList 1 Eq 1 Eval 1 Num 1 Show 1 String 1;
 PrelNum 1 :: $d10 1 $d16 1 $d18 1 $d29 1 $d33 1 $d35 1;
diff --git a/ghc/tests/typecheck/should_compile/tc014.stderr b/ghc/tests/typecheck/should_compile/tc014.stderr
index a099af43bbca4eaa884101d42c8ee97850694d91..155d2c7e1cdc81457fd4413372fa8ccfafe23823 100644
--- a/ghc/tests/typecheck/should_compile/tc014.stderr
+++ b/ghc/tests/typecheck/should_compile/tc014.stderr
@@ -1,7 +1,7 @@
 ghc: module version changed to 1; reason: no old .hi file
 _interface_ ShouldSucceed 1
 _instance_modules_
-ArrBase IO PrelNum
+Addr ArrBase Foreign IO PrelNum
 _usages_
 PrelBase 1 :: $d1 1 $d12 1 $d16 1 $d2 1 $d22 1 $d28 1 $d3 1 $d33 1 $d34 1 $d38 1 $d39 1 $d4 1 $d40 1 $d42 1 $d43 1 $d45 1 $d47 1 $d55 1 $d8 1 $d9 1 $m- 1 $m/= 1 $mfromInt 1 $mshowList 1 Eq 1 Eval 1 Num 1 Show 1 String 1;
 PrelNum 1 :: $d10 1 $d16 1 $d18 1 $d29 1 $d33 1 $d35 1;
diff --git a/ghc/tests/typecheck/should_compile/tc015.stderr b/ghc/tests/typecheck/should_compile/tc015.stderr
index 64fd545063b32694c94082254c17f86fee4e7b99..262e0b8d01886ec76ea1d87795abc56751a01b14 100644
--- a/ghc/tests/typecheck/should_compile/tc015.stderr
+++ b/ghc/tests/typecheck/should_compile/tc015.stderr
@@ -1,7 +1,7 @@
 ghc: module version changed to 1; reason: no old .hi file
 _interface_ ShouldSucceed 1
 _instance_modules_
-ArrBase IO PrelNum
+Addr ArrBase Foreign IO PrelNum
 _exports_
 ShouldSucceed u;
 _declarations_
diff --git a/ghc/tests/typecheck/should_compile/tc016.stderr b/ghc/tests/typecheck/should_compile/tc016.stderr
index e02f7e9442c6628c56379903d075fbb642b75015..3790594456ba1d441c50876f6438d74ea928969b 100644
--- a/ghc/tests/typecheck/should_compile/tc016.stderr
+++ b/ghc/tests/typecheck/should_compile/tc016.stderr
@@ -1,7 +1,7 @@
 ghc: module version changed to 1; reason: no old .hi file
 _interface_ ShouldSucceed 1
 _instance_modules_
-ArrBase IO PrelNum
+Addr ArrBase Foreign IO PrelNum
 _exports_
 ShouldSucceed f;
 _declarations_
diff --git a/ghc/tests/typecheck/should_compile/tc017.stderr b/ghc/tests/typecheck/should_compile/tc017.stderr
index d11f8178fe98ad68604d8df23b751392599a6fc0..9c455b20bdbc02021ebb50f937395bd89a1260ef 100644
--- a/ghc/tests/typecheck/should_compile/tc017.stderr
+++ b/ghc/tests/typecheck/should_compile/tc017.stderr
@@ -1,7 +1,7 @@
 ghc: module version changed to 1; reason: no old .hi file
 _interface_ ShouldSucceed 1
 _instance_modules_
-ArrBase IO PrelNum
+Addr ArrBase Foreign IO PrelNum
 _usages_
 PrelBase 1 :: $d1 1 $d12 1 $d16 1 $d2 1 $d22 1 $d28 1 $d3 1 $d33 1 $d34 1 $d38 1 $d39 1 $d4 1 $d40 1 $d42 1 $d43 1 $d45 1 $d47 1 $d55 1 $d8 1 $d9 1 $m- 1 $m/= 1 $mfromInt 1 $mshowList 1 Eq 1 Eval 1 Num 1 Show 1 String 1;
 PrelNum 1 :: $d10 1 $d16 1 $d18 1 $d29 1 $d33 1 $d35 1;
diff --git a/ghc/tests/typecheck/should_compile/tc018.stderr b/ghc/tests/typecheck/should_compile/tc018.stderr
index 75cf5bc35d8a57c2099764e57ebbd46e4e4ae8d1..2506dd20272ace2c8508cda3f6583fa00c059c11 100644
--- a/ghc/tests/typecheck/should_compile/tc018.stderr
+++ b/ghc/tests/typecheck/should_compile/tc018.stderr
@@ -1,7 +1,7 @@
 ghc: module version changed to 1; reason: no old .hi file
 _interface_ ShouldSucceed 1
 _instance_modules_
-ArrBase IO PrelNum
+Addr ArrBase Foreign IO PrelNum
 _usages_
 PrelBase 1 :: $d1 1 $d12 1 $d16 1 $d2 1 $d22 1 $d28 1 $d3 1 $d33 1 $d34 1 $d38 1 $d39 1 $d4 1 $d40 1 $d42 1 $d43 1 $d45 1 $d47 1 $d55 1 $d8 1 $d9 1 $m- 1 $m/= 1 $mfromInt 1 $mshowList 1 Eq 1 Eval 1 Num 1 Show 1 String 1;
 PrelNum 1 :: $d10 1 $d16 1 $d18 1 $d29 1 $d33 1 $d35 1;
diff --git a/ghc/tests/typecheck/should_compile/tc019.stderr b/ghc/tests/typecheck/should_compile/tc019.stderr
index 86dba12ecfab0285b7022394f08ba781e7d23cb4..3a7f9a891c6dfae1fa7afac301def2a4dc0c4ab5 100644
--- a/ghc/tests/typecheck/should_compile/tc019.stderr
+++ b/ghc/tests/typecheck/should_compile/tc019.stderr
@@ -1,7 +1,7 @@
 ghc: module version changed to 1; reason: no old .hi file
 _interface_ ShouldSucceed 1
 _instance_modules_
-ArrBase IO PrelNum
+Addr ArrBase Foreign IO PrelNum
 _usages_
 PrelBase 1 :: $d1 1 $d12 1 $d16 1 $d2 1 $d22 1 $d24 1 $d25 1 $d28 1 $d3 1 $d33 1 $d34 1 $d38 1 $d39 1 $d4 1 $d40 1 $d42 1 $d43 1 $d45 1 $d47 1 $d55 1 $d8 1 $d9 1 $m- 1 $m/= 1 $m>> 1 $mfromInt 1 $mshowList 1 Eq 1 Eval 1 Monad 1 MonadZero 1 Num 1 Show 1 String 1;
 PrelNum 1 :: $d10 1 $d16 1 $d18 1 $d29 1 $d33 1 $d35 1;
diff --git a/ghc/tests/typecheck/should_compile/tc020.stderr b/ghc/tests/typecheck/should_compile/tc020.stderr
index a5b7f4ad2fb1ea647ecdd79e3ec428ce8ae1014f..ac9f1a277114913b04afcd55a7af3da2e544a75c 100644
--- a/ghc/tests/typecheck/should_compile/tc020.stderr
+++ b/ghc/tests/typecheck/should_compile/tc020.stderr
@@ -1,7 +1,7 @@
 ghc: module version changed to 1; reason: no old .hi file
 _interface_ ShouldSucceed 1
 _instance_modules_
-ArrBase IO PrelNum
+Addr ArrBase Foreign IO PrelNum
 _exports_
 ShouldSucceed f;
 _declarations_
diff --git a/ghc/tests/typecheck/should_compile/tc021.stderr b/ghc/tests/typecheck/should_compile/tc021.stderr
index e1c6ce19db13c05153c4231064a1fe45d999b3a8..800b67358dae557fa8b4fb9f548a1c4f580ce927 100644
--- a/ghc/tests/typecheck/should_compile/tc021.stderr
+++ b/ghc/tests/typecheck/should_compile/tc021.stderr
@@ -1,7 +1,7 @@
 ghc: module version changed to 1; reason: no old .hi file
 _interface_ ShouldSucceed 1
 _instance_modules_
-ArrBase IO PrelNum
+Addr ArrBase Foreign IO PrelNum
 _exports_
 ShouldSucceed a f x;
 _declarations_
diff --git a/ghc/tests/typecheck/should_compile/tc022.stderr b/ghc/tests/typecheck/should_compile/tc022.stderr
index b1e947db6df8e7ac3c02803e26ea2d10c1c331ae..a850abd17f9064f1b588b3f20c44fb25261623c2 100644
--- a/ghc/tests/typecheck/should_compile/tc022.stderr
+++ b/ghc/tests/typecheck/should_compile/tc022.stderr
@@ -1,7 +1,7 @@
 ghc: module version changed to 1; reason: no old .hi file
 _interface_ ShouldSucceed 1
 _instance_modules_
-ArrBase IO PrelNum
+Addr ArrBase Foreign IO PrelNum
 _exports_
 ShouldSucceed iD main;
 _declarations_
diff --git a/ghc/tests/typecheck/should_compile/tc023.stderr b/ghc/tests/typecheck/should_compile/tc023.stderr
index 05f57cc8f04e24f3b89f70723866becf2019030b..4ef514c76888ce782f585388e6fb41580bcd7ee5 100644
--- a/ghc/tests/typecheck/should_compile/tc023.stderr
+++ b/ghc/tests/typecheck/should_compile/tc023.stderr
@@ -1,7 +1,7 @@
 ghc: module version changed to 1; reason: no old .hi file
 _interface_ ShouldSucceed 1
 _instance_modules_
-ArrBase IO PrelNum
+Addr ArrBase Foreign IO PrelNum
 _exports_
 ShouldSucceed k main s;
 _declarations_
diff --git a/ghc/tests/typecheck/should_compile/tc024.stderr b/ghc/tests/typecheck/should_compile/tc024.stderr
index 05f57cc8f04e24f3b89f70723866becf2019030b..4ef514c76888ce782f585388e6fb41580bcd7ee5 100644
--- a/ghc/tests/typecheck/should_compile/tc024.stderr
+++ b/ghc/tests/typecheck/should_compile/tc024.stderr
@@ -1,7 +1,7 @@
 ghc: module version changed to 1; reason: no old .hi file
 _interface_ ShouldSucceed 1
 _instance_modules_
-ArrBase IO PrelNum
+Addr ArrBase Foreign IO PrelNum
 _exports_
 ShouldSucceed k main s;
 _declarations_
diff --git a/ghc/tests/typecheck/should_compile/tc025.stderr b/ghc/tests/typecheck/should_compile/tc025.stderr
index 1b2392fd668563e327d7b71c7fa64df656607fbb..8c452f5fc547c2be281471c03424e169d1de511b 100644
--- a/ghc/tests/typecheck/should_compile/tc025.stderr
+++ b/ghc/tests/typecheck/should_compile/tc025.stderr
@@ -1,7 +1,7 @@
 ghc: module version changed to 1; reason: no old .hi file
 _interface_ ShouldSucceed 1
 _instance_modules_
-ArrBase IO PrelNum
+Addr ArrBase Foreign IO PrelNum
 _exports_
 ShouldSucceed g;
 _declarations_
diff --git a/ghc/tests/typecheck/should_compile/tc026.stderr b/ghc/tests/typecheck/should_compile/tc026.stderr
index 05b41403ef62d51104458bd04c7d71a788eb4d5b..d6be593e2fb0c0547c38f4da9b7d723cb300e83a 100644
--- a/ghc/tests/typecheck/should_compile/tc026.stderr
+++ b/ghc/tests/typecheck/should_compile/tc026.stderr
@@ -1,7 +1,7 @@
 ghc: module version changed to 1; reason: no old .hi file
 _interface_ ShouldSucceed 1
 _instance_modules_
-ArrBase IO PrelNum
+Addr ArrBase Foreign IO PrelNum
 _exports_
 ShouldSucceed f g;
 _declarations_
diff --git a/ghc/tests/typecheck/should_compile/tc027.stderr b/ghc/tests/typecheck/should_compile/tc027.stderr
index 130b5c2dcebb2772dbf65892d8807ff653a08707..2cc5756ff31d4fc9e2acc788f790ac2119190f45 100644
--- a/ghc/tests/typecheck/should_compile/tc027.stderr
+++ b/ghc/tests/typecheck/should_compile/tc027.stderr
@@ -3,7 +3,7 @@ NOTE: Simplifier still going after 4 iterations; bailing out.
 ghc: module version changed to 1; reason: no old .hi file
 _interface_ ShouldSucceed 1
 _instance_modules_
-ArrBase IO PrelNum
+Addr ArrBase Foreign IO PrelNum
 _exports_
 ShouldSucceed f g h;
 _declarations_
diff --git a/ghc/tests/typecheck/should_compile/tc028.stderr b/ghc/tests/typecheck/should_compile/tc028.stderr
index 8f522a4f695b1221c6ecc0ff594df14b5498033b..79f69009b15ac94819feebe9530e27e9878a6bea 100644
--- a/ghc/tests/typecheck/should_compile/tc028.stderr
+++ b/ghc/tests/typecheck/should_compile/tc028.stderr
@@ -1,7 +1,7 @@
 ghc: module version changed to 1; reason: no old .hi file
 _interface_ ShouldSucceed 1
 _instance_modules_
-ArrBase IO PrelNum
+Addr ArrBase Foreign IO PrelNum
 _exports_
 ShouldSucceed H;
 _declarations_
diff --git a/ghc/tests/typecheck/should_compile/tc029.stderr b/ghc/tests/typecheck/should_compile/tc029.stderr
index 7b6b0b45db6aeea45021f8612623865a9c5a35ec..ade1d7d432ce6d2c4beaa6300c03e805429928ff 100644
--- a/ghc/tests/typecheck/should_compile/tc029.stderr
+++ b/ghc/tests/typecheck/should_compile/tc029.stderr
@@ -1,7 +1,7 @@
 ghc: module version changed to 1; reason: no old .hi file
 _interface_ ShouldSucceed 1
 _instance_modules_
-ArrBase IO PrelNum
+Addr ArrBase Foreign IO PrelNum
 _usages_
 PrelBase 1 :: $d2 1 $d38 1 $d40 1 $d42 1 $d45 1 $d47 1 Eval 1;
 _exports_
diff --git a/ghc/tests/typecheck/should_compile/tc030.stderr b/ghc/tests/typecheck/should_compile/tc030.stderr
index 5f93c0bf42b5015d773160e2030cdf39af61135b..cd73040e383e3c3e5ecd5341576190a6943c23ad 100644
--- a/ghc/tests/typecheck/should_compile/tc030.stderr
+++ b/ghc/tests/typecheck/should_compile/tc030.stderr
@@ -1,7 +1,7 @@
 ghc: module version changed to 1; reason: no old .hi file
 _interface_ ShouldSucceed 1
 _instance_modules_
-ArrBase IO PrelNum
+Addr ArrBase Foreign IO PrelNum
 _exports_
 ShouldSucceed G H;
 _declarations_
diff --git a/ghc/tests/typecheck/should_compile/tc031.stderr b/ghc/tests/typecheck/should_compile/tc031.stderr
index 666d47bdb5d36ff19194c06735f8c393200cad87..8a8cb2cf72de47dc6405ebfad9befc4dc96fc604 100644
--- a/ghc/tests/typecheck/should_compile/tc031.stderr
+++ b/ghc/tests/typecheck/should_compile/tc031.stderr
@@ -1,7 +1,7 @@
 ghc: module version changed to 1; reason: no old .hi file
 _interface_ ShouldSucceed 1
 _instance_modules_
-ArrBase IO PrelNum
+Addr ArrBase Foreign IO PrelNum
 _usages_
 PrelBase 1 :: $d2 1 $d38 1 $d40 1 $d42 1 $d47 1 Eval 1;
 _exports_
diff --git a/ghc/tests/typecheck/should_compile/tc032.stderr b/ghc/tests/typecheck/should_compile/tc032.stderr
index b835b4c8b7caf934e18bb0d3a49f6c7ace09a795..15d5915fefd2f4b069239cadcad06da43208509d 100644
--- a/ghc/tests/typecheck/should_compile/tc032.stderr
+++ b/ghc/tests/typecheck/should_compile/tc032.stderr
@@ -1,7 +1,7 @@
 ghc: module version changed to 1; reason: no old .hi file
 _interface_ ShouldSucceed 1
 _instance_modules_
-ArrBase IO PrelNum
+Addr ArrBase Foreign IO PrelNum
 _usages_
 PrelBase 1 :: $d2 1 $d38 1 $d39 1 $d40 1 $d42 1 $d45 1 $d47 1 Eval 1;
 PrelTup 1 :: $d13 1;
diff --git a/ghc/tests/typecheck/should_compile/tc033.stderr b/ghc/tests/typecheck/should_compile/tc033.stderr
index a4f61e0fb1ecfbae7d8d438f91f70f32cae3047e..2eb48a6cf177283ee5becbb6b08daaac817390c4 100644
--- a/ghc/tests/typecheck/should_compile/tc033.stderr
+++ b/ghc/tests/typecheck/should_compile/tc033.stderr
@@ -1,7 +1,7 @@
 ghc: module version changed to 1; reason: no old .hi file
 _interface_ ShouldSucceed 1
 _instance_modules_
-ArrBase IO PrelNum
+Addr ArrBase Foreign IO PrelNum
 _usages_
 PrelBase 1 :: $d2 1 $d38 1 $d40 1 $d42 1 $d47 1 Eval 1;
 _exports_
diff --git a/ghc/tests/typecheck/should_compile/tc034.stderr b/ghc/tests/typecheck/should_compile/tc034.stderr
index 57e4b08b6b249a19bbdc4aa60f2d1721068c55ff..e9e3b6f7fb052e3d502386a813584721103d2928 100644
--- a/ghc/tests/typecheck/should_compile/tc034.stderr
+++ b/ghc/tests/typecheck/should_compile/tc034.stderr
@@ -1,7 +1,7 @@
 ghc: module version changed to 1; reason: no old .hi file
 _interface_ ShouldSucceed 1
 _instance_modules_
-ArrBase IO PrelNum
+Addr ArrBase Foreign IO PrelNum
 _usages_
 PrelBase 1 :: $d1 1 $d12 1 $d16 1 $d2 1 $d22 1 $d28 1 $d3 1 $d33 1 $d34 1 $d38 1 $d39 1 $d4 1 $d40 1 $d42 1 $d43 1 $d45 1 $d47 1 $d55 1 $d8 1 $d9 1 $m- 1 $m/= 1 $mfromInt 1 $mshowList 1 Eq 1 Eval 1 Num 1 Show 1 String 1;
 PrelNum 1 :: $d10 1 $d16 1 $d18 1 $d29 1 $d33 1 $d35 1;
diff --git a/ghc/tests/typecheck/should_compile/tc035.stderr b/ghc/tests/typecheck/should_compile/tc035.stderr
index df81df5d5f43873f5e8d2c4802ea26dc9e5b7088..36da589cffa54b789222e71e552125d96a34c86d 100644
--- a/ghc/tests/typecheck/should_compile/tc035.stderr
+++ b/ghc/tests/typecheck/should_compile/tc035.stderr
@@ -1,7 +1,7 @@
 ghc: module version changed to 1; reason: no old .hi file
 _interface_ ShouldSucceed 1
 _instance_modules_
-ArrBase IO PrelNum
+Addr ArrBase Foreign IO PrelNum
 _usages_
 PrelBase 1 :: $d2 1 $d23 1 $d24 1 $d25 1 $d38 1 $d39 1 $d40 1 $d42 1 $d45 1 $d47 1 $m>> 1 Eval 1 Monad 1 MonadPlus 1 MonadZero 1;
 PrelTup 1 :: $d13 1;
diff --git a/ghc/tests/typecheck/should_compile/tc036.stderr b/ghc/tests/typecheck/should_compile/tc036.stderr
index 53dc074527438052981e0b3fa047ef8992947436..0a41bfbb072d0186ddc396d7fdcadf3508df85bf 100644
--- a/ghc/tests/typecheck/should_compile/tc036.stderr
+++ b/ghc/tests/typecheck/should_compile/tc036.stderr
@@ -1,7 +1,7 @@
 ghc: module version changed to 1; reason: no old .hi file
 _interface_ ShouldSucceed 1
 _instance_modules_
-ArrBase IO PrelNum
+Addr ArrBase Foreign IO PrelNum
 _usages_
 PrelBase 1 :: $d16 1 $d33 1 $d8 1 $m/= 1 Eq 1;
 PrelNum 1 :: $d18 1;
diff --git a/ghc/tests/typecheck/should_compile/tc037.stderr b/ghc/tests/typecheck/should_compile/tc037.stderr
index 3aad75ee06117980ccdedd00b0b3d16c16815225..221be461f8968f7c3efa0568104d26563ad80569 100644
--- a/ghc/tests/typecheck/should_compile/tc037.stderr
+++ b/ghc/tests/typecheck/should_compile/tc037.stderr
@@ -1,7 +1,7 @@
 ghc: module version changed to 1; reason: no old .hi file
 _interface_ ShouldSucceed 1
 _instance_modules_
-ArrBase IO PrelNum
+Addr ArrBase Foreign IO PrelNum
 _exports_
 ShouldSucceed Eq'(deq);
 _instances_
diff --git a/ghc/tests/typecheck/should_compile/tc038.stderr b/ghc/tests/typecheck/should_compile/tc038.stderr
index a1268ff5b1546f25000666bade19b95c22544b6f..dadfea7c98b3c77ad9662f82b2818f1e31ca9c7c 100644
--- a/ghc/tests/typecheck/should_compile/tc038.stderr
+++ b/ghc/tests/typecheck/should_compile/tc038.stderr
@@ -1,7 +1,7 @@
 ghc: module version changed to 1; reason: no old .hi file
 _interface_ ShouldSucceed 1
 _instance_modules_
-ArrBase IO PrelNum
+Addr ArrBase Foreign IO PrelNum
 _usages_
 PrelBase 1 :: $d1 1 $d12 1 $d16 1 $d2 1 $d22 1 $d28 1 $d3 1 $d33 1 $d34 1 $d38 1 $d39 1 $d4 1 $d40 1 $d42 1 $d43 1 $d45 1 $d47 1 $d55 1 $d8 1 $d9 1 $m- 1 $m/= 1 $mfromInt 1 $mshowList 1 Eq 1 Eval 1 Num 1 Show 1 String 1;
 PrelNum 1 :: $d10 1 $d16 1 $d18 1 $d29 1 $d33 1 $d35 1;
diff --git a/ghc/tests/typecheck/should_compile/tc039.stderr b/ghc/tests/typecheck/should_compile/tc039.stderr
index 53dc074527438052981e0b3fa047ef8992947436..0a41bfbb072d0186ddc396d7fdcadf3508df85bf 100644
--- a/ghc/tests/typecheck/should_compile/tc039.stderr
+++ b/ghc/tests/typecheck/should_compile/tc039.stderr
@@ -1,7 +1,7 @@
 ghc: module version changed to 1; reason: no old .hi file
 _interface_ ShouldSucceed 1
 _instance_modules_
-ArrBase IO PrelNum
+Addr ArrBase Foreign IO PrelNum
 _usages_
 PrelBase 1 :: $d16 1 $d33 1 $d8 1 $m/= 1 Eq 1;
 PrelNum 1 :: $d18 1;
diff --git a/ghc/tests/typecheck/should_compile/tc040.stderr b/ghc/tests/typecheck/should_compile/tc040.stderr
index 9d372f60ece0509b792cdc58cc766526d4e1360e..162f7653723f43e5d1455613ce540e19764fae9a 100644
--- a/ghc/tests/typecheck/should_compile/tc040.stderr
+++ b/ghc/tests/typecheck/should_compile/tc040.stderr
@@ -1,7 +1,7 @@
 ghc: module version changed to 1; reason: no old .hi file
 _interface_ ShouldSucceed 1
 _instance_modules_
-ArrBase IO PrelNum
+Addr ArrBase Foreign IO PrelNum
 _usages_
 PrelBase 1 :: $d16 1 $d28 1 $d33 1 $d8 1 $m/= 1 Eq 1;
 PrelNum 1 :: $d18 1;
diff --git a/ghc/tests/typecheck/should_compile/tc041.stderr b/ghc/tests/typecheck/should_compile/tc041.stderr
index 2e602324231aec86615b98b64137a0c7c4250fda..8120ea0143a19022853cd0d4953a7c852a50e0c2 100644
--- a/ghc/tests/typecheck/should_compile/tc041.stderr
+++ b/ghc/tests/typecheck/should_compile/tc041.stderr
@@ -1,7 +1,7 @@
 ghc: module version changed to 1; reason: no old .hi file
 _interface_ ShouldSucceed 1
 _instance_modules_
-ArrBase IO PrelNum
+Addr ArrBase Foreign IO PrelNum
 _exports_
 ShouldSucceed f H(op1);
 _instances_
diff --git a/ghc/tests/typecheck/should_compile/tc042.stderr b/ghc/tests/typecheck/should_compile/tc042.stderr
index 8f47de17780a45ae790b013653875a1f4a3a31df..e8eaaea434c7a0f2fc13ef260164d3e4e9f42df1 100644
--- a/ghc/tests/typecheck/should_compile/tc042.stderr
+++ b/ghc/tests/typecheck/should_compile/tc042.stderr
@@ -1,7 +1,7 @@
 ghc: module version changed to 1; reason: no old .hi file
 _interface_ ShouldSucceed 1
 _instance_modules_
-ArrBase IO PrelNum
+Addr ArrBase Foreign IO PrelNum
 _usages_
 PrelBase 1 :: $d2 1 $d38 1 $d40 1 $d42 1 $d47 1 Eval 1;
 _exports_
diff --git a/ghc/tests/typecheck/should_compile/tc043.stderr b/ghc/tests/typecheck/should_compile/tc043.stderr
index 44993e3804946a925478616f04344d5b3a6352b7..55733426523d1ec6ebfcbdc8cee8b863d43be13e 100644
--- a/ghc/tests/typecheck/should_compile/tc043.stderr
+++ b/ghc/tests/typecheck/should_compile/tc043.stderr
@@ -1,7 +1,7 @@
 ghc: module version changed to 1; reason: no old .hi file
 _interface_ ShouldSucceed 1
 _instance_modules_
-ArrBase IO PrelNum
+Addr ArrBase Foreign IO PrelNum
 _usages_
 PrelBase 1 :: $d1 1 $d12 1 $d16 1 $d2 1 $d22 1 $d28 1 $d3 1 $d33 1 $d34 1 $d38 1 $d39 1 $d4 1 $d40 1 $d42 1 $d43 1 $d45 1 $d47 1 $d55 1 $d8 1 $d9 1 $m- 1 $m/= 1 $mfromInt 1 $mshowList 1 Eq 1 Eval 1 Num 1 Show 1 String 1;
 PrelNum 1 :: $d10 1 $d16 1 $d18 1 $d29 1 $d33 1 $d35 1;
diff --git a/ghc/tests/typecheck/should_compile/tc044.stderr b/ghc/tests/typecheck/should_compile/tc044.stderr
index 8b16f120b1a6915b2998050b3d0ea2f22951584c..60311a3eb970013b39278dd0d0681525abd1b9b4 100644
--- a/ghc/tests/typecheck/should_compile/tc044.stderr
+++ b/ghc/tests/typecheck/should_compile/tc044.stderr
@@ -1,7 +1,7 @@
 ghc: module version changed to 1; reason: no old .hi file
 _interface_ ShouldSucceed 1
 _instance_modules_
-ArrBase IO PrelNum
+Addr ArrBase Foreign IO PrelNum
 _usages_
 PrelBase 1 :: otherwise 1;
 _exports_
diff --git a/ghc/tests/typecheck/should_compile/tc045.stderr b/ghc/tests/typecheck/should_compile/tc045.stderr
index af259656a00a75a4ae0705971927070d3a3cbc2f..30e8f91f3a548eace466e8d4fbe055529083d151 100644
--- a/ghc/tests/typecheck/should_compile/tc045.stderr
+++ b/ghc/tests/typecheck/should_compile/tc045.stderr
@@ -1,7 +1,7 @@
 ghc: module version changed to 1; reason: no old .hi file
 _interface_ ShouldSucceed 1
 _instance_modules_
-ArrBase IO PrelNum
+Addr ArrBase Foreign IO PrelNum
 _exports_
 ShouldSucceed B(op2) C(op1);
 _instances_
diff --git a/ghc/tests/typecheck/should_compile/tc046.stderr b/ghc/tests/typecheck/should_compile/tc046.stderr
index f62216ded07ec401cba857f248bcc935f2393a45..de5bf29d969643b7588d5ac01b83f9a02b9d6e79 100644
--- a/ghc/tests/typecheck/should_compile/tc046.stderr
+++ b/ghc/tests/typecheck/should_compile/tc046.stderr
@@ -1,7 +1,7 @@
 ghc: module version changed to 1; reason: no old .hi file
 _interface_ ShouldSucceed 1
 _instance_modules_
-ArrBase IO PrelNum
+Addr ArrBase Foreign IO PrelNum
 _exports_
 ShouldSucceed B(op2) C(op1);
 _declarations_
diff --git a/ghc/tests/typecheck/should_compile/tc047.stderr b/ghc/tests/typecheck/should_compile/tc047.stderr
index f1c1a173fd1414b3a88e946a4435e8e527e4840f..5c55b7a4736e50e558b192faa1ec84d2c6d6fad2 100644
--- a/ghc/tests/typecheck/should_compile/tc047.stderr
+++ b/ghc/tests/typecheck/should_compile/tc047.stderr
@@ -1,7 +1,7 @@
 ghc: module version changed to 1; reason: no old .hi file
 _interface_ ShouldSucceed 1
 _instance_modules_
-ArrBase IO PrelNum
+Addr ArrBase Foreign IO PrelNum
 _exports_
 ShouldSucceed f mp sd OL;
 _declarations_
diff --git a/ghc/tests/typecheck/should_compile/tc048.stderr b/ghc/tests/typecheck/should_compile/tc048.stderr
index 2807b7370eb3c01026c6587cf3a4cae53447c2bd..7cb4d0cb8abb6be3584848232b9ef62305ad51db 100644
--- a/ghc/tests/typecheck/should_compile/tc048.stderr
+++ b/ghc/tests/typecheck/should_compile/tc048.stderr
@@ -1,7 +1,7 @@
 ghc: module version changed to 1; reason: no old .hi file
 _interface_ ShouldSucceed 1
 _instance_modules_
-ArrBase IO PrelNum
+Addr ArrBase Foreign IO PrelNum
 _usages_
 PrelBase 1 :: $d2 1 $d38 1 $d40 1 $d42 1 $d45 1 $d47 1 Eval 1;
 PrelTup 1 :: $d13 1;
diff --git a/ghc/tests/typecheck/should_compile/tc049.stderr b/ghc/tests/typecheck/should_compile/tc049.stderr
index 2b3ffb38309482d95dfeaa47c12467fa252b3b0f..a0561cf036bb035817302a7ab23c10c809a90585 100644
--- a/ghc/tests/typecheck/should_compile/tc049.stderr
+++ b/ghc/tests/typecheck/should_compile/tc049.stderr
@@ -1,7 +1,7 @@
 ghc: module version changed to 1; reason: no old .hi file
 _interface_ ShouldSucceed 1
 _instance_modules_
-ArrBase IO PrelNum
+Addr ArrBase Foreign IO PrelNum
 _usages_
 PrelBase 1 :: $d1 1 $d12 1 $d15 1 $d16 1 $d2 1 $d22 1 $d27 1 $d28 1 $d3 1 $d33 1 $d34 1 $d35 1 $d38 1 $d39 1 $d4 1 $d40 1 $d42 1 $d43 1 $d45 1 $d46 1 $d47 1 $d50 1 $d51 1 $d52 1 $d55 1 $d56 1 $d7 1 $d8 1 $d9 1 $m- 1 $m/= 1 $m< 1 $m<= 1 $m> 1 $m>= 1 $mcompare 1 $mfromInt 1 $mmax 1 $mmin 1 $mshowList 1 Eq 1 Eval 1 Num 1 Ord 1 Ordering 1 Show 1 String 1;
 PrelNum 1 :: $d10 1 $d16 1 $d17 1 $d18 1 $d29 1 $d33 1 $d34 1 $d35 1;
diff --git a/ghc/tests/typecheck/should_compile/tc050.stderr b/ghc/tests/typecheck/should_compile/tc050.stderr
index 0f747a52770a2621b0a1f0ceace11abe53bd22f3..9eb6fc06096277e46fa81a7415364485a7b7ccfd 100644
--- a/ghc/tests/typecheck/should_compile/tc050.stderr
+++ b/ghc/tests/typecheck/should_compile/tc050.stderr
@@ -1,7 +1,7 @@
 ghc: module version changed to 1; reason: no old .hi file
 _interface_ ShouldSucceed 1
 _instance_modules_
-ArrBase IO PrelNum
+Addr ArrBase Foreign IO PrelNum
 _usages_
 PrelBase 1 :: $d1 1 $d12 1 $d16 1 $d2 1 $d22 1 $d28 1 $d3 1 $d33 1 $d34 1 $d38 1 $d39 1 $d4 1 $d40 1 $d42 1 $d43 1 $d45 1 $d47 1 $d55 1 $d8 1 $d9 1 $m- 1 $m/= 1 $mfromInt 1 $mshowList 1 Eq 1 Eval 1 Num 1 Show 1 String 1;
 PrelNum 1 :: $d10 1 $d16 1 $d18 1 $d29 1 $d33 1 $d35 1;
diff --git a/ghc/tests/typecheck/should_compile/tc051.stderr b/ghc/tests/typecheck/should_compile/tc051.stderr
index 1e76949041db39fdbff5300b7e14496587d19b71..f59cf5fd8202ea486df04ae4fcab042096780fb8 100644
--- a/ghc/tests/typecheck/should_compile/tc051.stderr
+++ b/ghc/tests/typecheck/should_compile/tc051.stderr
@@ -1,7 +1,7 @@
 ghc: module version changed to 1; reason: no old .hi file
 _interface_ ShouldSucceed 1
 _instance_modules_
-ArrBase IO PrelNum
+Addr ArrBase Foreign IO PrelNum
 _exports_
 ShouldSucceed Eq'(doubleeq) Ord'(lt);
 _instances_
diff --git a/ghc/tests/typecheck/should_compile/tc052.stderr b/ghc/tests/typecheck/should_compile/tc052.stderr
index f0d4613698cee1e58509eae217e4263f2a6a2aef..47f7889015e2666c8d42c867ac9bb8dda6b48f8a 100644
--- a/ghc/tests/typecheck/should_compile/tc052.stderr
+++ b/ghc/tests/typecheck/should_compile/tc052.stderr
@@ -1,7 +1,7 @@
 ghc: module version changed to 1; reason: no old .hi file
 _interface_ ShouldSucceed 1
 _instance_modules_
-ArrBase IO PrelNum
+Addr ArrBase Foreign IO PrelNum
 _exports_
 ShouldSucceed A B C;
 _declarations_
diff --git a/ghc/tests/typecheck/should_compile/tc053.stderr b/ghc/tests/typecheck/should_compile/tc053.stderr
index 971239f2932f1fbbbb9570884faa68606a30aca7..9ef7c16093a95c5193101e25beb79c622fb560ad 100644
--- a/ghc/tests/typecheck/should_compile/tc053.stderr
+++ b/ghc/tests/typecheck/should_compile/tc053.stderr
@@ -1,7 +1,7 @@
 ghc: module version changed to 1; reason: no old .hi file
 _interface_ ShouldSucceed 1
 _instance_modules_
-ArrBase IO PrelNum
+Addr ArrBase Foreign IO PrelNum
 _usages_
 PrelBase 1 :: $d1 1 $d12 1 $d16 1 $d2 1 $d22 1 $d28 1 $d3 1 $d33 1 $d34 1 $d38 1 $d39 1 $d4 1 $d40 1 $d42 1 $d43 1 $d45 1 $d47 1 $d55 1 $d8 1 $d9 1 $m- 1 $m/= 1 $mfromInt 1 $mshowList 1 Eq 1 Eval 1 Num 1 Show 1 String 1;
 PrelNum 1 :: $d10 1 $d16 1 $d18 1 $d29 1 $d33 1 $d35 1;
diff --git a/ghc/tests/typecheck/should_compile/tc054.stderr b/ghc/tests/typecheck/should_compile/tc054.stderr
index 59dfc9362f379f7a93705ad9fcbc390496deafe5..91bc997cf2f1e9418ba0ab2f4f3effbeb557d761 100644
--- a/ghc/tests/typecheck/should_compile/tc054.stderr
+++ b/ghc/tests/typecheck/should_compile/tc054.stderr
@@ -1,7 +1,7 @@
 ghc: module version changed to 1; reason: no old .hi file
 _interface_ ShouldSucceed 1
 _instance_modules_
-ArrBase IO PrelNum
+Addr ArrBase Foreign IO PrelNum
 _usages_
 PrelBase 1 :: $d1 1 $d12 1 $d16 1 $d2 1 $d22 1 $d28 1 $d3 1 $d33 1 $d34 1 $d38 1 $d39 1 $d4 1 $d40 1 $d42 1 $d43 1 $d45 1 $d47 1 $d55 1 $d8 1 $d9 1 $m- 1 $m/= 1 $mfromInt 1 $mshowList 1 otherwise 1 Eq 1 Eval 1 Num 1 Show 1 String 1;
 PrelNum 1 :: $d10 1 $d16 1 $d18 1 $d29 1 $d33 1 $d35 1;
diff --git a/ghc/tests/typecheck/should_compile/tc055.stderr b/ghc/tests/typecheck/should_compile/tc055.stderr
index 31d508c0c128ba8236ab9bd4e890e88e06537b7e..71de449f6d4b13356f1c086cfad49eeb2b9f4bba 100644
--- a/ghc/tests/typecheck/should_compile/tc055.stderr
+++ b/ghc/tests/typecheck/should_compile/tc055.stderr
@@ -3,7 +3,7 @@ NOTE: Simplifier still going after 4 iterations; bailing out.
 ghc: module version changed to 1; reason: no old .hi file
 _interface_ ShouldSucceed 1
 _instance_modules_
-ArrBase IO PrelNum
+Addr ArrBase Foreign IO PrelNum
 _exports_
 ShouldSucceed x y;
 _declarations_
diff --git a/ghc/tests/typecheck/should_compile/tc056.stderr b/ghc/tests/typecheck/should_compile/tc056.stderr
index 8306e236df921f3286f2fbc6245e9f7812dae205..de6b555fa5b2d2b00164999aca896851489d38a1 100644
--- a/ghc/tests/typecheck/should_compile/tc056.stderr
+++ b/ghc/tests/typecheck/should_compile/tc056.stderr
@@ -4,7 +4,7 @@ tc056.hs:15:warning:
 ghc: module version changed to 1; reason: no old .hi file
 _interface_ ShouldSucceed 1
 _instance_modules_
-ArrBase IO PrelNum
+Addr ArrBase Foreign IO PrelNum
 _usages_
 PrelBase 1 :: $d1 1 $d12 1 $d16 1 $d2 1 $d22 1 $d28 1 $d3 1 $d33 1 $d34 1 $d38 1 $d39 1 $d4 1 $d40 1 $d42 1 $d43 1 $d45 1 $d47 1 $d55 1 $d8 1 $d9 1 $m- 1 $m/= 1 $mfromInt 1 $mshowList 1 Eq 1 Eval 1 Num 1 Show 1 String 1;
 PrelNum 1 :: $d10 1 $d16 1 $d18 1 $d29 1 $d33 1 $d35 1;
diff --git a/ghc/tests/typecheck/should_compile/tc057.stderr b/ghc/tests/typecheck/should_compile/tc057.stderr
index db733208f5284010a2ff9ed1ece9a2faa6a3fc8b..d65ab5e4d94b56e2833bb37d782a8782ac8ea1e0 100644
--- a/ghc/tests/typecheck/should_compile/tc057.stderr
+++ b/ghc/tests/typecheck/should_compile/tc057.stderr
@@ -1,7 +1,7 @@
 ghc: module version changed to 1; reason: no old .hi file
 _interface_ ShouldSucceed 1
 _instance_modules_
-ArrBase IO PrelNum
+Addr ArrBase Foreign IO PrelNum
 _usages_
 PrelBase 1 :: $d1 1 $d12 1 $d16 1 $d2 1 $d22 1 $d28 1 $d3 1 $d33 1 $d34 1 $d38 1 $d39 1 $d4 1 $d40 1 $d42 1 $d43 1 $d45 1 $d47 1 $d55 1 $d8 1 $d9 1 $m- 1 $m/= 1 $mfromInt 1 $mshowList 1 Eq 1 Eval 1 Num 1 Show 1 String 1;
 PrelNum 1 :: $d10 1 $d16 1 $d18 1 $d29 1 $d33 1 $d35 1;
diff --git a/ghc/tests/typecheck/should_compile/tc058.stderr b/ghc/tests/typecheck/should_compile/tc058.stderr
index 0c771c3db01ea9972710a7e66bbfa2b2a4e9a77d..b6a219b9a0c75777cd66073d429a3b10959afc90 100644
--- a/ghc/tests/typecheck/should_compile/tc058.stderr
+++ b/ghc/tests/typecheck/should_compile/tc058.stderr
@@ -1,7 +1,7 @@
 ghc: module version changed to 1; reason: no old .hi file
 _interface_ ShouldSucceed 1
 _instance_modules_
-ArrBase IO PrelNum
+Addr ArrBase Foreign IO PrelNum
 _usages_
 PrelBase 1 :: $d1 1 $d12 1 $d16 1 $d2 1 $d22 1 $d28 1 $d3 1 $d33 1 $d34 1 $d38 1 $d39 1 $d4 1 $d40 1 $d42 1 $d43 1 $d45 1 $d47 1 $d55 1 $d8 1 $d9 1 $m- 1 $m/= 1 $mfromInt 1 $mshowList 1 Eq 1 Eval 1 Num 1 Show 1 String 1;
 PrelNum 1 :: $d10 1 $d16 1 $d18 1 $d29 1 $d33 1 $d35 1;
diff --git a/ghc/tests/typecheck/should_compile/tc059.stderr b/ghc/tests/typecheck/should_compile/tc059.stderr
index 3167850478b4ab962d8537cc92a242154a1da812..49727c87b8a734b32c778622e3c71336f281783a 100644
--- a/ghc/tests/typecheck/should_compile/tc059.stderr
+++ b/ghc/tests/typecheck/should_compile/tc059.stderr
@@ -1,7 +1,7 @@
 ghc: module version changed to 1; reason: no old .hi file
 _interface_ ShouldSucceed 1
 _instance_modules_
-ArrBase IO PrelNum
+Addr ArrBase Foreign IO PrelNum
 _usages_
 PrelBase 1 :: $d1 1 $d12 1 $d16 1 $d2 1 $d22 1 $d28 1 $d3 1 $d33 1 $d34 1 $d38 1 $d39 1 $d4 1 $d40 1 $d42 1 $d43 1 $d45 1 $d47 1 $d55 1 $d8 1 $d9 1 $m- 1 $m/= 1 $mfromInt 1 $mshowList 1 Eq 1 Eval 1 Num 1 Show 1 String 1;
 PrelNum 1 :: $d10 1 $d16 1 $d18 1 $d29 1 $d33 1 $d35 1;
diff --git a/ghc/tests/typecheck/should_compile/tc060.stderr b/ghc/tests/typecheck/should_compile/tc060.stderr
index 540303277c4980166103a65ae34d0c8652518974..264ba32d84540cb89b9490b83acf63a6edfc343e 100644
--- a/ghc/tests/typecheck/should_compile/tc060.stderr
+++ b/ghc/tests/typecheck/should_compile/tc060.stderr
@@ -1,7 +1,7 @@
 ghc: module version changed to 1; reason: no old .hi file
 _interface_ ShouldSucceed 1
 _instance_modules_
-ArrBase IO PrelNum
+Addr ArrBase Foreign IO PrelNum
 _exports_
 ShouldSucceed Eq2(deq);
 _instances_
diff --git a/ghc/tests/typecheck/should_compile/tc061.stderr b/ghc/tests/typecheck/should_compile/tc061.stderr
index 7d96c35a27577e8944b678440517925f83c29635..f9a20e725a7bfed88c84d385c3a0ab06d226b4d4 100644
--- a/ghc/tests/typecheck/should_compile/tc061.stderr
+++ b/ghc/tests/typecheck/should_compile/tc061.stderr
@@ -1,7 +1,7 @@
 ghc: module version changed to 1; reason: no old .hi file
 _interface_ ShouldSucceed 1
 _instance_modules_
-ArrBase IO PrelNum
+Addr ArrBase Foreign IO PrelNum
 _exports_
 ShouldSucceed Eq1(deq);
 _instances_
diff --git a/ghc/tests/typecheck/should_compile/tc062.stderr b/ghc/tests/typecheck/should_compile/tc062.stderr
index b515b6a36355dd7eede25f4840515e0abaab0b06..55402b32838b4ac8f84bd5cabdb1ca9378a69863 100644
--- a/ghc/tests/typecheck/should_compile/tc062.stderr
+++ b/ghc/tests/typecheck/should_compile/tc062.stderr
@@ -1,7 +1,7 @@
 ghc: module version changed to 1; reason: no old .hi file
 _interface_ ShouldSucceed 1
 _instance_modules_
-ArrBase IO PrelNum
+Addr ArrBase Foreign IO PrelNum
 _exports_
 ShouldSucceed f Eq1(deq);
 _instances_
diff --git a/ghc/tests/typecheck/should_compile/tc063.stderr b/ghc/tests/typecheck/should_compile/tc063.stderr
index e74ac448a0a4f3e2d583f6f9bbf4182fdfad5aa1..bd3f8d1f34743d128f833086678519977f39877a 100644
--- a/ghc/tests/typecheck/should_compile/tc063.stderr
+++ b/ghc/tests/typecheck/should_compile/tc063.stderr
@@ -1,7 +1,7 @@
 ghc: module version changed to 1; reason: no old .hi file
 _interface_ ShouldSucceed 1
 _instance_modules_
-ArrBase IO PrelNum
+Addr ArrBase Foreign IO PrelNum
 _usages_
 PrelBase 1 :: $d2 1 $d38 1 $d40 1 $d42 1 $d47 1 Eval 1;
 _exports_
diff --git a/ghc/tests/typecheck/should_compile/tc064.stderr b/ghc/tests/typecheck/should_compile/tc064.stderr
index dd1d098a095e104c8b4bc3cf566e15bf2283c700..aba81f5db41369f5836708959d30c5def673c5dc 100644
--- a/ghc/tests/typecheck/should_compile/tc064.stderr
+++ b/ghc/tests/typecheck/should_compile/tc064.stderr
@@ -1,7 +1,7 @@
 ghc: module version changed to 1; reason: no old .hi file
 _interface_ ShouldSucceed 1
 _instance_modules_
-ArrBase IO PrelNum
+Addr ArrBase Foreign IO PrelNum
 _usages_
 PrelBase 1 :: $d2 1 $d38 1 $d40 1 $d42 1 $d47 1 Eval 1;
 _exports_
diff --git a/ghc/tests/typecheck/should_compile/tc065.stderr b/ghc/tests/typecheck/should_compile/tc065.stderr
index b4d5dc3f12e4185383d4b27481d498a83cac6dd0..57029aa54b88fe01291affa1129693a442517859 100644
--- a/ghc/tests/typecheck/should_compile/tc065.stderr
+++ b/ghc/tests/typecheck/should_compile/tc065.stderr
@@ -1,7 +1,7 @@
 ghc: module version changed to 1; reason: no old .hi file
 _interface_ ShouldSucceed 1
 _instance_modules_
-ArrBase IO PrelNum
+Addr ArrBase Foreign IO PrelNum
 _usages_
 List 1 :: partition 1;
 PrelBase 1 :: $d15 1 $d16 1 $d2 1 $d23 1 $d24 1 $d25 1 $d26 1 $d27 1 $d28 1 $d33 1 $d35 1 $d38 1 $d40 1 $d42 1 $d45 1 $d46 1 $d47 1 $d50 1 $d52 1 $d7 1 $d8 1 $m/= 1 $m< 1 $m<= 1 $m> 1 $m>= 1 $m>> 1 $mcompare 1 $mmax 1 $mmin 1 otherwise 1 Eq 1 Eval 1 Functor 1 Monad 1 MonadPlus 1 MonadZero 1 Ord 1 Ordering 1;
diff --git a/ghc/tests/typecheck/should_compile/tc066.stderr b/ghc/tests/typecheck/should_compile/tc066.stderr
index e5a0b63e6f4f36425c7deb9578e87afa7e958dcf..b97b2208c8a2e6ab9d8b07015615a011b7a28f02 100644
--- a/ghc/tests/typecheck/should_compile/tc066.stderr
+++ b/ghc/tests/typecheck/should_compile/tc066.stderr
@@ -1,7 +1,7 @@
 ghc: module version changed to 1; reason: no old .hi file
 _interface_ ShouldSucceed 1
 _instance_modules_
-ArrBase IO PrelNum
+Addr ArrBase Foreign IO PrelNum
 _usages_
 PrelBase 1 :: $d2 1 $d38 1 $d40 1 $d42 1 $d47 1 $m>> 1 Eval 1 Monad 1 MonadZero 1;
 _exports_
diff --git a/ghc/tests/typecheck/should_compile/tc067.stderr b/ghc/tests/typecheck/should_compile/tc067.stderr
index 173dc29de818a768f5598d3882388c0a16b1b02c..0a6b7da25d8e24ed254dc68833897ddc3fe866c0 100644
--- a/ghc/tests/typecheck/should_compile/tc067.stderr
+++ b/ghc/tests/typecheck/should_compile/tc067.stderr
@@ -1,7 +1,7 @@
 ghc: module version changed to 1; reason: no old .hi file
 _interface_ ShouldSucceed 1
 _instance_modules_
-ArrBase IO PrelNum
+Addr ArrBase Foreign IO PrelNum
 _exports_
 ShouldSucceed f;
 _declarations_
diff --git a/ghc/tests/typecheck/should_compile/tc068.stderr b/ghc/tests/typecheck/should_compile/tc068.stderr
index 9ef579963c6aa58d345f8821c8370a9e5dba2e7f..6a8a26080895a94a03ba89e59ef50f8d4f9160dd 100644
--- a/ghc/tests/typecheck/should_compile/tc068.stderr
+++ b/ghc/tests/typecheck/should_compile/tc068.stderr
@@ -1,7 +1,7 @@
 ghc: module version changed to 1; reason: no old .hi file
 _interface_ ShouldSucceed 1
 _instance_modules_
-ArrBase IO PrelNum
+Addr ArrBase Foreign IO PrelNum
 _usages_
 PrelBase 1 :: $d16 1 $d2 1 $d33 1 $d38 1 $d40 1 $d42 1 $d47 1 $d8 1 $m/= 1 not 1 Eq 1 Eval 1;
 PrelNum 1 :: $d18 1;
diff --git a/ghc/tests/typecheck/should_compile/tc069.stderr b/ghc/tests/typecheck/should_compile/tc069.stderr
index a02c45dee52693fbdb2ecf4523a7fd5625d1176f..4c080cade75084494c13c546bd3e1a5479b93683 100644
--- a/ghc/tests/typecheck/should_compile/tc069.stderr
+++ b/ghc/tests/typecheck/should_compile/tc069.stderr
@@ -1,7 +1,7 @@
 ghc: module version changed to 1; reason: no old .hi file
 _interface_ ShouldSucceed 1
 _instance_modules_
-ArrBase IO PrelNum
+Addr ArrBase Foreign IO PrelNum
 _exports_
 ShouldSucceed x y ys;
 _declarations_
diff --git a/ghc/tests/typecheck/should_compile/tc070.stderr b/ghc/tests/typecheck/should_compile/tc070.stderr
index dd1d098a095e104c8b4bc3cf566e15bf2283c700..aba81f5db41369f5836708959d30c5def673c5dc 100644
--- a/ghc/tests/typecheck/should_compile/tc070.stderr
+++ b/ghc/tests/typecheck/should_compile/tc070.stderr
@@ -1,7 +1,7 @@
 ghc: module version changed to 1; reason: no old .hi file
 _interface_ ShouldSucceed 1
 _instance_modules_
-ArrBase IO PrelNum
+Addr ArrBase Foreign IO PrelNum
 _usages_
 PrelBase 1 :: $d2 1 $d38 1 $d40 1 $d42 1 $d47 1 Eval 1;
 _exports_
diff --git a/ghc/tests/typecheck/should_compile/tc073.stderr b/ghc/tests/typecheck/should_compile/tc073.stderr
index 173dc29de818a768f5598d3882388c0a16b1b02c..0a6b7da25d8e24ed254dc68833897ddc3fe866c0 100644
--- a/ghc/tests/typecheck/should_compile/tc073.stderr
+++ b/ghc/tests/typecheck/should_compile/tc073.stderr
@@ -1,7 +1,7 @@
 ghc: module version changed to 1; reason: no old .hi file
 _interface_ ShouldSucceed 1
 _instance_modules_
-ArrBase IO PrelNum
+Addr ArrBase Foreign IO PrelNum
 _exports_
 ShouldSucceed f;
 _declarations_
diff --git a/ghc/tests/typecheck/should_compile/tc074.stderr b/ghc/tests/typecheck/should_compile/tc074.stderr
index 9ef579963c6aa58d345f8821c8370a9e5dba2e7f..6a8a26080895a94a03ba89e59ef50f8d4f9160dd 100644
--- a/ghc/tests/typecheck/should_compile/tc074.stderr
+++ b/ghc/tests/typecheck/should_compile/tc074.stderr
@@ -1,7 +1,7 @@
 ghc: module version changed to 1; reason: no old .hi file
 _interface_ ShouldSucceed 1
 _instance_modules_
-ArrBase IO PrelNum
+Addr ArrBase Foreign IO PrelNum
 _usages_
 PrelBase 1 :: $d16 1 $d2 1 $d33 1 $d38 1 $d40 1 $d42 1 $d47 1 $d8 1 $m/= 1 not 1 Eq 1 Eval 1;
 PrelNum 1 :: $d18 1;
diff --git a/ghc/tests/typecheck/should_compile/tc076.stderr b/ghc/tests/typecheck/should_compile/tc076.stderr
index 2ac809c494cca774f43477801388b706c15f9914..dcf88add540538b0ef3364660508d3a13cc535fb 100644
--- a/ghc/tests/typecheck/should_compile/tc076.stderr
+++ b/ghc/tests/typecheck/should_compile/tc076.stderr
@@ -1,7 +1,7 @@
 ghc: module version changed to 1; reason: no old .hi file
 _interface_ ShouldSucceed 1
 _instance_modules_
-ArrBase IO PrelNum
+Addr ArrBase Foreign IO PrelNum
 _usages_
 PrelBase 1 :: $d24 1 $d25 1 $m>> 1 Monad 1 MonadZero 1;
 _exports_
diff --git a/ghc/tests/typecheck/should_compile/tc077.stderr b/ghc/tests/typecheck/should_compile/tc077.stderr
index 68caa3a404e95c3b1484ec5ae2116f3dd2479e50..3fac8048d0125b603c79b308f58ae10dc5fc5efb 100644
--- a/ghc/tests/typecheck/should_compile/tc077.stderr
+++ b/ghc/tests/typecheck/should_compile/tc077.stderr
@@ -1,7 +1,7 @@
 ghc: module version changed to 1; reason: no old .hi file
 _interface_ ShouldSucceed 1
 _instance_modules_
-ArrBase IO PrelNum
+Addr ArrBase Foreign IO PrelNum
 _usages_
 PrelBase 1 :: $d1 1 $d12 1 $d16 1 $d2 1 $d22 1 $d28 1 $d3 1 $d33 1 $d34 1 $d38 1 $d39 1 $d4 1 $d40 1 $d42 1 $d43 1 $d45 1 $d47 1 $d55 1 $d8 1 $d9 1 $m- 1 $m/= 1 $mfromInt 1 $mshowList 1 Eq 1 Eval 1 Num 1 Show 1 String 1;
 PrelNum 1 :: $d10 1 $d16 1 $d18 1 $d29 1 $d33 1 $d35 1;
diff --git a/ghc/tests/typecheck/should_compile/tc078.stderr b/ghc/tests/typecheck/should_compile/tc078.stderr
index e6f115fa51c04c9e6bf7b987e4f9d22c4057e959..635d90700599cf9d87926b8d61ecb8ed82970653 100644
--- a/ghc/tests/typecheck/should_compile/tc078.stderr
+++ b/ghc/tests/typecheck/should_compile/tc078.stderr
@@ -1,10 +1,10 @@
  
-tc078.hs:7: No explicit method nor default method for `PrelBase.=='
-	    in an instance declaration for `PrelBase.Eq'
+tc078.hs:7: Warning: no explicit method nor default method for `=='
+	    in an instance declaration for `Eq'
 ghc: module version changed to 1; reason: no old .hi file
 _interface_ ShouldFail 1
 _instance_modules_
-ArrBase IO PrelNum
+Addr ArrBase Foreign IO PrelNum
 _usages_
 PrelBase 1 :: $d15 1 $d16 1 $d2 1 $d33 1 $d35 1 $d38 1 $d40 1 $d42 1 $d46 1 $d47 1 $d50 1 $d52 1 $d7 1 $d8 1 $m/= 1 $m< 1 $m<= 1 $m> 1 $m>= 1 $mcompare 1 $mmax 1 $mmin 1 Eq 1 Eval 1 Ord 1 Ordering 1;
 PrelNum 1 :: $d17 1 $d18 1;
diff --git a/ghc/tests/typecheck/should_compile/tc079.stderr b/ghc/tests/typecheck/should_compile/tc079.stderr
index d244cf4cfbc81bf060bb244d10f375d8bcffd3a7..111697c16872a11c11e486d25706df5b41edf5fd 100644
--- a/ghc/tests/typecheck/should_compile/tc079.stderr
+++ b/ghc/tests/typecheck/should_compile/tc079.stderr
@@ -1,7 +1,7 @@
 ghc: module version changed to 1; reason: no old .hi file
 _interface_ ShouldSucceed 1
 _instance_modules_
-ArrBase IO PrelNum
+Addr ArrBase Foreign IO PrelNum
 _usages_
 PrelBase 1 :: $d15 1 $d16 1 $d27 1 $d28 1 $d33 1 $d35 1 $d50 1 $d52 1 $d7 1 $d8 1 $m/= 1 $m< 1 $m<= 1 $m> 1 $m>= 1 $mcompare 1 $mmax 1 $mmin 1 && 1 Eq 1 Ord 1 Ordering 1;
 PrelNum 1 :: $d17 1 $d18 1;
diff --git a/ghc/tests/typecheck/should_compile/tc080.stderr b/ghc/tests/typecheck/should_compile/tc080.stderr
index cf70ed48460e7cafa099987ad8c091307bdf57c1..6a1f478bf50cb7715499fc4efaca33ce3fe627c0 100644
--- a/ghc/tests/typecheck/should_compile/tc080.stderr
+++ b/ghc/tests/typecheck/should_compile/tc080.stderr
@@ -3,7 +3,7 @@ NOTE: Simplifier still going after 4 iterations; bailing out.
 ghc: module version changed to 1; reason: no old .hi file
 _interface_ ShouldSucceed 1
 _instance_modules_
-ArrBase IO PrelNum
+Addr ArrBase Foreign IO PrelNum
 _usages_
 PrelBase 1 :: $d1 1 $d11 1 $d12 1 $d14 1 $d15 1 $d16 1 $d2 1 $d22 1 $d23 1 $d24 1 $d25 1 $d26 1 $d27 1 $d28 1 $d3 1 $d31 1 $d32 1 $d33 1 $d34 1 $d35 1 $d38 1 $d39 1 $d4 1 $d40 1 $d42 1 $d43 1 $d45 1 $d46 1 $d47 1 $d50 1 $d51 1 $d52 1 $d55 1 $d56 1 $d6 1 $d7 1 $d8 1 $d9 1 $m- 1 $m/= 1 $m< 1 $m<= 1 $m> 1 $m>= 1 $m>> 1 $mcompare 1 $menumFromThenTo 1 $menumFromTo 1 $mfromInt 1 $mmax 1 $mmin 1 $mshowList 1 . 1 dropWhile 1 isDigit 1 isSpace 1 ord 1 Enum 1 Eq 1 Eval 1 Functor 1 Monad 1 MonadPlus 1 MonadZero 1 Num 1 Ord 1 Ordering 1 Show 1 String 1;
 PrelList 1 :: all 1 length 1 null 1 tail 1;
diff --git a/ghc/tests/typecheck/should_compile/tc081.stderr b/ghc/tests/typecheck/should_compile/tc081.stderr
index 49535310bbae1de14e832a167cb21326da670318..f49dbc2a19c5940f67d9da913743fd892c1fe82b 100644
--- a/ghc/tests/typecheck/should_compile/tc081.stderr
+++ b/ghc/tests/typecheck/should_compile/tc081.stderr
@@ -1,7 +1,7 @@
 ghc: module version changed to 1; reason: no old .hi file
 _interface_ ShouldSucceed 1
 _instance_modules_
-ArrBase IO PrelNum
+Addr ArrBase Foreign IO PrelNum
 _usages_
 PrelBase 1 :: $d1 1 $d12 1 $d15 1 $d16 1 $d2 1 $d22 1 $d27 1 $d28 1 $d3 1 $d33 1 $d34 1 $d35 1 $d38 1 $d39 1 $d4 1 $d40 1 $d42 1 $d43 1 $d45 1 $d46 1 $d47 1 $d50 1 $d51 1 $d52 1 $d55 1 $d56 1 $d7 1 $d8 1 $d9 1 $m- 1 $m/= 1 $m< 1 $m<= 1 $m> 1 $m>= 1 $mcompare 1 $mfromInt 1 $mmax 1 $mmin 1 $mshowList 1 Eq 1 Eval 1 Num 1 Ord 1 Ordering 1 Show 1 String 1;
 PrelNum 1 :: $d10 1 $d16 1 $d17 1 $d18 1 $d29 1 $d33 1 $d34 1 $d35 1;
diff --git a/ghc/tests/typecheck/should_compile/tc082.stderr b/ghc/tests/typecheck/should_compile/tc082.stderr
index 0312fb689b7740df4f947f63aa050691d75fabfe..6e58d5b653df84ef96c32d34aa1a89683d4f3071 100644
--- a/ghc/tests/typecheck/should_compile/tc082.stderr
+++ b/ghc/tests/typecheck/should_compile/tc082.stderr
@@ -1,7 +1,7 @@
 ghc: module version changed to 1; reason: no old .hi file
 _interface_ ShouldSucceed 1
 _instance_modules_
-ArrBase IO PrelNum
+Addr ArrBase Foreign IO PrelNum
 _usages_
 PrelBase 1 :: id 1;
 _exports_
diff --git a/ghc/tests/typecheck/should_compile/tc084.stderr b/ghc/tests/typecheck/should_compile/tc084.stderr
index 7746d8acfc2a138b8aaf5fe3e9e81f9e8f3ebb55..f37af692359e922d2061b5d7317ee08842720b00 100644
--- a/ghc/tests/typecheck/should_compile/tc084.stderr
+++ b/ghc/tests/typecheck/should_compile/tc084.stderr
@@ -1,7 +1,7 @@
 ghc: module version changed to 1; reason: no old .hi file
 _interface_ ShouldSucceed 1
 _instance_modules_
-ArrBase IO PrelNum
+Addr ArrBase Foreign IO PrelNum
 _usages_
 PrelBase 1 :: $d1 1 $d12 1 $d16 1 $d2 1 $d22 1 $d28 1 $d3 1 $d33 1 $d34 1 $d38 1 $d39 1 $d4 1 $d40 1 $d42 1 $d43 1 $d45 1 $d47 1 $d55 1 $d8 1 $d9 1 $m- 1 $m/= 1 $mfromInt 1 $mshowList 1 Eq 1 Eval 1 Num 1 Show 1 String 1;
 PrelNum 1 :: $d10 1 $d16 1 $d18 1 $d29 1 $d33 1 $d35 1;
diff --git a/ghc/tests/typecheck/should_compile/tc085.hs b/ghc/tests/typecheck/should_compile/tc085.hs
index ca2822f34419bfc2f3963bb48158c9becff67d04..90d5cf031ff0a759b74628698faf9d8b76bc5fe8 100644
--- a/ghc/tests/typecheck/should_compile/tc085.hs
+++ b/ghc/tests/typecheck/should_compile/tc085.hs
@@ -1,9 +1,11 @@
 --!!! From a bug report from Satnam.
 --!!! To do with re-exporting importees from PreludeGla* modules.
-module ShouldSucceed ( module GlaExts ) where
+module ShouldSucceed ( module IOExts, module GHC ) where
 
---OLD: import PreludeGlaIO
-import GlaExts
+--OLD:   import GlaExts
+--OLDER: import PreludeGlaIO
+import IOExts
+import GHC
 
 type FooType = Int
 data FooData = FooData
diff --git a/ghc/tests/typecheck/should_compile/tc085.stderr b/ghc/tests/typecheck/should_compile/tc085.stderr
index 9b49fecfe5835c49a6dc64ded813fffadafcb2aa..e650de569bbd6f465e97cbbaf4d221e87b9a45bc 100644
--- a/ghc/tests/typecheck/should_compile/tc085.stderr
+++ b/ghc/tests/typecheck/should_compile/tc085.stderr
@@ -1,22 +1,16 @@
 ghc: module version changed to 1; reason: no old .hi file
 _interface_ ShouldSucceed 1
 _instance_modules_
-ArrBase IO PrelNum
+Addr ArrBase Foreign IO PrelNum
 _usages_
-GlaExts 1 ::;
+GHC 2 ::;
+IOExts 1 ::;
 PrelBase 1 :: $d2 1 $d38 1 $d40 1 $d42 1 $d47 1 Eval 1;
 _exports_
-ArrBase boundsOfArray boundsOfByteArray freezeAddrArray freezeArray freezeCharArray freezeDoubleArray freezeFloatArray freezeIntArray indexAddrArray indexAddrOffAddr indexCharArray indexCharOffAddr indexDoubleArray indexDoubleOffAddr indexFloatArray indexFloatOffAddr indexIntArray indexIntOffAddr newAddrArray newArray newCharArray newDoubleArray newFloatArray newIntArray readAddrArray readArray readCharArray readDoubleArray readFloatArray readIntArray thawArray unsafeFreezeArray unsafeFreezeByteArray writeAddrArray writeArray writeCharArray writeDoubleArray writeFloatArray writeIntArray ByteArray(ByteArray) MutableArray(MutableArray) MutableByteArray(MutableByteArray);
-Foreign Addr(A#) Word(W#);
-GHC *# *## **## +# +## -# -## /## /=# /=## <# <## <=# <=## ==# ==## ># >## >=# >=## acosDouble# acosFloat# addr2Int# and# asinDouble# asinFloat# atanDouble# atanFloat# chr# cmpInteger# cosDouble# cosFloat# coshDouble# coshFloat# deRefStablePtr# decodeDouble# decodeFloat# delay# divideFloat# double2Float# double2Int# encodeDouble# encodeFloat# eqAddr# eqChar# eqFloat# eqWord# errorIO# expDouble# expFloat# float2Double# float2Int# fork# geAddr# geChar# geFloat# geWord# gtAddr# gtChar# gtFloat# gtWord# iShiftL# iShiftRA# iShiftRL# indexAddrArray# indexAddrOffAddr# indexAddrOffForeignObj# indexArray# indexCharArray# indexCharOffAddr# indexCharOffForeignObj# indexDoubleArray# indexDoubleOffAddr# indexDoubleOffForeignObj# indexFloatArray# indexFloatOffAddr# indexFloatOffForeignObj# indexIntArray# indexIntOffAddr# indexIntOffForeignObj# int2Addr# int2Double# int2Float# int2Integer# int2Word# integer2Int# leAddr# leChar# leFloat# leWord# logDouble# logFloat# ltAddr# ltChar# ltFloat# ltWord# makeForeignObj# makeStablePtr# minusFloat# minusInteger# neAddr# neChar# neFloat# neWord# negateDouble# negateFloat# negateInt# negateInteger# newAddrArray# newArray# newCharArray# newDoubleArray# newFloatArray# newIntArray# newSynchVar# not# or# ord# par# parAt# parAtForNow# parGlobal# parLocal# plusFloat# plusInteger# powerFloat# putMVar# quotInt# quotRemInteger# readAddrArray# readArray# readCharArray# readDoubleArray# readFloatArray# readIntArray# realWorld# remInt# sameMutableArray# sameMutableByteArray# seq# shiftL# shiftRA# shiftRL# sinDouble# sinFloat# sinhDouble# sinhFloat# sqrtDouble# sqrtFloat# takeMVar# tanDouble# tanFloat# tanhDouble# tanhFloat# timesFloat# timesInteger# unsafeFreezeArray# unsafeFreezeByteArray# waitRead# waitWrite# word2Int# writeAddrArray# writeArray# writeCharArray# writeDoubleArray# writeFloatArray# writeForeignObj# writeIntArray# -> Addr# All Array# ByteArray# Char# Double# Float# ForeignObj# Int# MutableArray# MutableByteArray# RealWorld StablePtr# State# SynchVar# Void Word#;
-IOBase ioToPrimIO ioToST primIOToIO seqIO_Prim stToIO thenIO_Prim trace;
-Ix Ix;
-PrelBase Char(C#) Double(D#) Float(F#) Int(I#) Integer(J#) Lift(Lift);
-STBase fixPrimIO listPrimIO mapAndUnzipPrimIO mapPrimIO returnPrimIO seqPrimIO thenPrimIO PrimIO ST;
-UnsafeST unsafeInterleavePrimIO unsafePerformPrimIO;
-_fixities_
-infixr 1 seqIO_Prim;
-infixr 1 thenIO_Prim;
+GHC *# *## **## +# +## -# -## /## /=# /=## <# <## <=# <=## ==# ==## ># >## >=# >=## acosDouble# acosFloat# addr2Int# and# asinDouble# asinFloat# atanDouble# atanFloat# chr# cmpInteger# cosDouble# cosFloat# coshDouble# coshFloat# deRefStablePtr# decodeDouble# decodeFloat# delay# divideFloat# double2Float# double2Int# encodeDouble# encodeFloat# eqAddr# eqChar# eqFloat# eqWord# errorIO# expDouble# expFloat# float2Double# float2Int# fork# geAddr# geChar# geFloat# geWord# gtAddr# gtChar# gtFloat# gtWord# iShiftL# iShiftRA# iShiftRL# indexAddrArray# indexAddrOffAddr# indexAddrOffForeignObj# indexArray# indexCharArray# indexCharOffAddr# indexCharOffForeignObj# indexDoubleArray# indexDoubleOffAddr# indexDoubleOffForeignObj# indexFloatArray# indexFloatOffAddr# indexFloatOffForeignObj# indexIntArray# indexIntOffAddr# indexIntOffForeignObj# int2Addr# int2Double# int2Float# int2Integer# int2Word# integer2Int# leAddr# leChar# leFloat# leWord# logDouble# logFloat# ltAddr# ltChar# ltFloat# ltWord# makeForeignObj# makeStablePtr# minusFloat# minusInteger# neAddr# neChar# neFloat# neWord# negateDouble# negateFloat# negateInt# negateInteger# newAddrArray# newArray# newCharArray# newDoubleArray# newFloatArray# newIntArray# newSynchVar# not# or# ord# par# parAt# parAtAbs# parAtForNow# parAtRel# parGlobal# parLocal# plusFloat# plusInteger# powerFloat# putMVar# quotInt# quotRemInteger# readAddrArray# readArray# readCharArray# readDoubleArray# readFloatArray# readIntArray# realWorld# reallyUnsafePtrEquality# remInt# sameMutableArray# sameMutableByteArray# seq# shiftL# shiftRA# shiftRL# sinDouble# sinFloat# sinhDouble# sinhFloat# sqrtDouble# sqrtFloat# takeMVar# tanDouble# tanFloat# tanhDouble# tanhFloat# timesFloat# timesInteger# unsafeFreezeArray# unsafeFreezeByteArray# waitRead# waitWrite# word2Int# writeAddrArray# writeArray# writeCharArray# writeDoubleArray# writeFloatArray# writeForeignObj# writeIntArray# xor# -> Addr# All Array# ByteArray# Char# Double# Float# ForeignObj# Int# MutableArray# MutableByteArray# RealWorld StablePtr# State# SynchVar# Void Word#;
+IOBase fixIO performGC;
+IORef newIORef readIORef writeIORef IORef;
+Unsafe trace unsafeInterleaveIO unsafePerformIO;
 _instances_
 instance {PrelBase.Eval FooData} = $d1;
 _declarations_
diff --git a/ghc/tests/typecheck/should_compile/tc086.stderr b/ghc/tests/typecheck/should_compile/tc086.stderr
index 116286b45d40966d49a49d1375431f070f140cbf..1371b0a4d5de315a994f38d883eaf23e874bc233 100644
--- a/ghc/tests/typecheck/should_compile/tc086.stderr
+++ b/ghc/tests/typecheck/should_compile/tc086.stderr
@@ -1,7 +1,7 @@
 ghc: module version changed to 1; reason: no old .hi file
 _interface_ ShouldSucceed 1
 _instance_modules_
-ArrBase IO PrelNum
+Addr ArrBase Foreign IO PrelNum
 _usages_
 PrelBase 1 :: $d1 1 $d12 1 $d16 1 $d2 1 $d22 1 $d28 1 $d3 1 $d33 1 $d34 1 $d35 1 $d38 1 $d39 1 $d4 1 $d40 1 $d42 1 $d43 1 $d45 1 $d46 1 $d47 1 $d55 1 $d56 1 $d8 1 $d9 1 $m- 1 $m/= 1 $mfromInt 1 $mshowList 1 Eq 1 Eval 1 Num 1 Ordering 1 Ordering 1 Show 1 String 1;
 PrelNum 1 :: $d10 1 $d16 1 $d18 1 $d29 1 $d33 1 $d35 1;
diff --git a/ghc/tests/typecheck/should_compile/tc087.hs b/ghc/tests/typecheck/should_compile/tc087.hs
index cb4b92566b95113b5b096c29f136faa956d59ef3..415fbc6ee18be47dbe0025f194a5a612dbb96108 100644
--- a/ghc/tests/typecheck/should_compile/tc087.hs
+++ b/ghc/tests/typecheck/should_compile/tc087.hs
@@ -1,7 +1,5 @@
 module ShouldSucceed where
 
-import GlaExts
-
 data SeqView t a              =  Null
                               |  Cons a (t a)
 
diff --git a/ghc/tests/typecheck/should_compile/tc087.stderr b/ghc/tests/typecheck/should_compile/tc087.stderr
index 9fe3538fcc0cc7352198aea776b49c8ca14765d3..8643e5c0756f46debccd1a63ae01e22ff6bdc455 100644
--- a/ghc/tests/typecheck/should_compile/tc087.stderr
+++ b/ghc/tests/typecheck/should_compile/tc087.stderr
@@ -1,7 +1,7 @@
 ghc: module version changed to 1; reason: no old .hi file
 _interface_ ShouldSucceed 1
 _instance_modules_
-ArrBase IO PrelNum
+Addr ArrBase Foreign IO PrelNum
 _usages_
 IOBase 1 :: $d2 1 $d3 1 $d7 1 IO 1;
 PrelBase 1 :: $d1 1 $d11 1 $d12 1 $d14 1 $d15 1 $d16 1 $d2 1 $d22 1 $d24 1 $d25 1 $d27 1 $d28 1 $d3 1 $d31 1 $d32 1 $d33 1 $d34 1 $d35 1 $d38 1 $d39 1 $d4 1 $d40 1 $d42 1 $d43 1 $d45 1 $d46 1 $d47 1 $d50 1 $d51 1 $d52 1 $d55 1 $d56 1 $d6 1 $d7 1 $d8 1 $d9 1 $m- 1 $m/= 1 $m< 1 $m<= 1 $m> 1 $m>= 1 $m>> 1 $mcompare 1 $menumFromThenTo 1 $menumFromTo 1 $mfromInt 1 $mmax 1 $mmin 1 $mshowList 1 otherwise 1 Enum 1 Eq 1 Eval 1 Monad 1 MonadZero 1 Num 1 Ord 1 Ordering 1 Show 1 String 1;
diff --git a/ghc/tests/typecheck/should_compile/tc088.stderr b/ghc/tests/typecheck/should_compile/tc088.stderr
index efbb004bb9b3adf10a33d585c26610cfb4e1f783..4b3e7c879586beb6b35434579d8c78867656fbd7 100644
--- a/ghc/tests/typecheck/should_compile/tc088.stderr
+++ b/ghc/tests/typecheck/should_compile/tc088.stderr
@@ -1,7 +1,7 @@
 ghc: module version changed to 1; reason: no old .hi file
 _interface_ ShouldSucceed 1
 _instance_modules_
-ArrBase IO PrelNum ShouldSucceed
+Addr ArrBase Foreign IO PrelNum ShouldSucceed
 _usages_
 PrelBase 1 :: $d1 1 $d12 1 $d16 1 $d2 1 $d22 1 $d28 1 $d3 1 $d33 1 $d34 1 $d38 1 $d39 1 $d4 1 $d40 1 $d42 1 $d43 1 $d45 1 $d47 1 $d55 1 $d8 1 $d9 1 $m- 1 $m/= 1 $mfromInt 1 $mshowList 1 Eq 1 Eval 1 Num 1 Show 1 String 1;
 PrelNum 1 :: $d10 1 $d16 1 $d18 1 $d29 1 $d33 1 $d35 1;
diff --git a/ghc/tests/typecheck/should_compile/tc089.stderr b/ghc/tests/typecheck/should_compile/tc089.stderr
index 8d85aca7c02199f17fa61aec7980ab3869ad6ff4..1de00ea34eea0c81dc3ca94b0ee8af82b7de1d5c 100644
--- a/ghc/tests/typecheck/should_compile/tc089.stderr
+++ b/ghc/tests/typecheck/should_compile/tc089.stderr
@@ -1,7 +1,7 @@
 ghc: module version changed to 1; reason: no old .hi file
 _interface_ ShouldSucceed 1
 _instance_modules_
-ArrBase IO PrelNum
+Addr ArrBase Foreign IO PrelNum
 _exports_
 ShouldSucceed absAnd absIf bottom f f_rec f_rec0 f_rec1 f_rec2 fac fac_rec fac_rec0 fac_rec1 fac_rec2 fac_rec3 fac_rec4 g g_rec g_rec0 g_rec1 g_rec2 g_rec3 g_rec4 g_rec5 g_rec6 g_rec7 g_rec8 head one s_1_0 s_2_0 s_2_1 s_3_0 s_3_1 s_3_2;
 _declarations_
diff --git a/ghc/tests/typecheck/should_compile/tc090.stderr b/ghc/tests/typecheck/should_compile/tc090.stderr
index 5ef41cbf8457e6e07a70c08699b620e3b1bd4163..9ff9689782303c63e2025cf7431779888bfe316f 100644
--- a/ghc/tests/typecheck/should_compile/tc090.stderr
+++ b/ghc/tests/typecheck/should_compile/tc090.stderr
@@ -1,7 +1,7 @@
 ghc: module version changed to 1; reason: no old .hi file
 _interface_ ShouldSucceed 1
 _instance_modules_
-ArrBase IO PrelNum
+Addr ArrBase Foreign IO PrelNum
 _usages_
 PrelBase 1 :: $d15 1 $d16 1 $d33 1 $d35 1 $d50 1 $d52 1 $d7 1 $d8 1 $m/= 1 $m< 1 $m<= 1 $m> 1 $m>= 1 $mcompare 1 $mmax 1 $mmin 1 Eq 1 Ord 1 Ordering 1;
 PrelNum 1 :: $d17 1 $d18 1;
diff --git a/ghc/tests/typecheck/should_compile/tc091.stderr b/ghc/tests/typecheck/should_compile/tc091.stderr
index bbb399aeb46f442eb5df836972c5832cd67cca5c..b5319e9c6051246c8834d2ffdb3144214919aee9 100644
--- a/ghc/tests/typecheck/should_compile/tc091.stderr
+++ b/ghc/tests/typecheck/should_compile/tc091.stderr
@@ -1,7 +1,7 @@
 ghc: module version changed to 1; reason: no old .hi file
 _interface_ ShouldSucceed 1
 _instance_modules_
-ArrBase IO PrelNum
+Addr ArrBase Foreign IO PrelNum
 _usages_
 PrelBase 1 :: $d1 1 $d11 1 $d12 1 $d14 1 $d15 1 $d16 1 $d2 1 $d22 1 $d27 1 $d28 1 $d3 1 $d31 1 $d32 1 $d33 1 $d34 1 $d35 1 $d38 1 $d39 1 $d4 1 $d40 1 $d42 1 $d43 1 $d45 1 $d46 1 $d47 1 $d50 1 $d51 1 $d52 1 $d55 1 $d56 1 $d6 1 $d7 1 $d8 1 $d9 1 $m- 1 $m/= 1 $m< 1 $m<= 1 $m> 1 $m>= 1 $mcompare 1 $menumFromThenTo 1 $menumFromTo 1 $mfromInt 1 $mmax 1 $mmin 1 $mshowList 1 Enum 1 Eq 1 Eval 1 Num 1 Ord 1 Ordering 1 Show 1 String 1;
 PrelList 1 :: length 1;
diff --git a/ghc/tests/typecheck/should_compile/tc092.stderr b/ghc/tests/typecheck/should_compile/tc092.stderr
index 012e69fbe661af7abeb2e7bfac1f169d9ffc4d3e..b66c1f4c5c45507190692a1efb656ddb02f9025f 100644
--- a/ghc/tests/typecheck/should_compile/tc092.stderr
+++ b/ghc/tests/typecheck/should_compile/tc092.stderr
@@ -1,7 +1,7 @@
 ghc: module version changed to 1; reason: no old .hi file
 _interface_ ShouldSucceed 1
 _instance_modules_
-ArrBase IO PrelNum
+Addr ArrBase Foreign IO PrelNum
 _usages_
 PrelBase 1 :: $d15 1 $d16 1 $d2 1 $d27 1 $d28 1 $d33 1 $d35 1 $d38 1 $d40 1 $d42 1 $d45 1 $d46 1 $d47 1 $d50 1 $d52 1 $d7 1 $d8 1 $m/= 1 $m< 1 $m<= 1 $m> 1 $m>= 1 $mcompare 1 $mmax 1 $mmin 1 Eq 1 Eval 1 Ord 1 Ordering 1;
 PrelNum 1 :: $d17 1 $d18 1;
diff --git a/ghc/tests/typecheck/should_compile/tc093.stderr b/ghc/tests/typecheck/should_compile/tc093.stderr
index 99091fe6f57e9cfd67a63b7b4dec2f00eb36b6b7..5ee6184e0623116c3adab7cb37c2e927e39858e7 100644
--- a/ghc/tests/typecheck/should_compile/tc093.stderr
+++ b/ghc/tests/typecheck/should_compile/tc093.stderr
@@ -1,7 +1,7 @@
 ghc: module version changed to 1; reason: no old .hi file
 _interface_ ShouldSucceed 1
 _instance_modules_
-ArrBase IO PrelNum
+Addr ArrBase Foreign IO PrelNum
 _usages_
 PrelBase 1 :: $d1 1 $d12 1 $d15 1 $d16 1 $d2 1 $d22 1 $d25 1 $d27 1 $d28 1 $d3 1 $d33 1 $d34 1 $d35 1 $d38 1 $d39 1 $d4 1 $d40 1 $d42 1 $d43 1 $d45 1 $d46 1 $d47 1 $d50 1 $d51 1 $d52 1 $d55 1 $d56 1 $d7 1 $d8 1 $d9 1 $m- 1 $m/= 1 $m< 1 $m<= 1 $m> 1 $m>= 1 $m>> 1 $mcompare 1 $mfromInt 1 $mmax 1 $mmin 1 $mshowList 1 && 1 . 1 not 1 showList__ 1 showParen 1 showSpace 1 showString 1 Eq 1 Eval 1 Monad 1 Num 1 Ord 1 Ordering 1 Show 1 ShowS 1 String 1;
 PrelNum 1 :: $d10 1 $d16 1 $d17 1 $d18 1 $d29 1 $d33 1 $d34 1 $d35 1;
diff --git a/ghc/tests/typecheck/should_fail/Digraph.stderr b/ghc/tests/typecheck/should_fail/Digraph.stderr
index 48a75b8975a23921d2a2d4ec0ed4c8e5cf9e9fb7..51066077bd2ad57e2bdf72f8a7e185aeb2e9dc9c 100644
--- a/ghc/tests/typecheck/should_fail/Digraph.stderr
+++ b/ghc/tests/typecheck/should_fail/Digraph.stderr
@@ -1,32 +1,28 @@
  
 Digraph.hs:19: A type signature is more polymorphic than the inferred type
-		   Can't for-all the type variable(s) `taW8'
-		   in the inferred type `[Edge taW8]'
+		   Can't for-all the type variable(s) `taYK'
+		   in the inferred type `[Edge taYK]'
     When checking signature for `reversed_edges'
     In an equation for function `stronglyConnComp':
 	`stronglyConnComp es vs
-			  = PrelTup.snd (span_tree (new_range reversed_edges)
-						   (PrelBase.[], (PrelBase.[]))
-						   (PrelTup.snd (dfs (new_range es)
-								     (PrelBase.[], (PrelBase.[]))
-								     vs)))
+			  = snd (span_tree (new_range reversed_edges)
+					   ([], ([]))
+					   (snd (dfs (new_range es) ([], ([])) vs)))
 			  where
-			      span_tree r (vs, ns) PrelBase.[] = (vs, (ns))
-			      span_tree r (vs, ns) (x PrelBase.: xs)
-					| x PrelList.elem vs = span_tree r (vs, (ns)) xs
-					| PrelBase.otherwise
-					= span_tree r (vs', ((x PrelBase.: ns') PrelBase.: ns)) xs
+			      span_tree r (vs, ns) [] = (vs, (ns))
+			      span_tree r (vs, ns) (x : xs)
+					| x elem vs = span_tree r (vs, (ns)) xs
+					| otherwise = span_tree r (vs', ((x : ns') : ns)) xs
 					where
-					    (vs', ns')
-						= dfs r (x PrelBase.: vs, (PrelBase.[])) (r x)
-			      new_range PrelBase.[] w = PrelBase.[]
-			      new_range ((x, y) PrelBase.: xys) w
-					= if x PrelBase.== w then
-					      (y PrelBase.: (new_range xys w))
+					    (vs', ns') = dfs r (x : vs, ([])) (r x)
+			      new_range [] w = []
+			      new_range ((x, y) : xys) w
+					= if x == w then
+					      (y : (new_range xys w))
 					  else
 					      (new_range xys w)
 			      swap (x, y) = (y, (x))
-			      reversed_edges :: _forall_ [v] (PrelBase.Eq v) => [Edge v]
-			      reversed_edges = PrelBase.map swap es'
+			      reversed_edges :: _forall_ [v] (Eq v) => [Edge v]
+			      reversed_edges = map swap es'
 
 Compilation had errors
diff --git a/ghc/tests/typecheck/should_fail/tcfail001.hs b/ghc/tests/typecheck/should_fail/tcfail001.hs
index dafb83af1e76576970af2d51401a074644c59964..a90d2308b902b02921c1c5d31e8e18e6c88fb07e 100644
--- a/ghc/tests/typecheck/should_fail/tcfail001.hs
+++ b/ghc/tests/typecheck/should_fail/tcfail001.hs
@@ -1,6 +1,6 @@
 --!!! This should fail with a type error: the instance method
 --!!! has a function type when it should have the type [a].
-module Test where
+module ShouldFail where
 
 class A a where
  op :: a
diff --git a/ghc/tests/typecheck/should_fail/tcfail001.stderr b/ghc/tests/typecheck/should_fail/tcfail001.stderr
index d0042ad8c3534252383923b5722714bae7983599..8c791bbaaf54bea5e9bebcaf6c4b75c9a988ea77 100644
--- a/ghc/tests/typecheck/should_fail/tcfail001.stderr
+++ b/ghc/tests/typecheck/should_fail/tcfail001.stderr
@@ -2,10 +2,9 @@
 tcfail001.hs:9:warning:
     Duplicated class assertion `A a' in context: `(A a, A a)'
  
-tcfail001.hs:9: Couldn't match the type
-		    `GHC.-> oakH' against `PrelBase.[]'
-    Expected: `oakH -> oakI'
-    Inferred: `[takF]'
-    In an equation for function `op': `op PrelBase.[] = PrelBase.[]'
+tcfail001.hs:9: Couldn't match the type `-> oamd' against `[]'
+    Expected: `oamd -> oame'
+    Inferred: `[tamb]'
+    In an equation for function `op': `op [] = []'
 
 Compilation had errors
diff --git a/ghc/tests/typecheck/should_fail/tcfail002.stderr b/ghc/tests/typecheck/should_fail/tcfail002.stderr
index ee23cc06ff12d06c0d6fd55fe35113b285fbb2b5..27d80c2a8f575ddac47607bc10af8ab27b95dc9d 100644
--- a/ghc/tests/typecheck/should_fail/tcfail002.stderr
+++ b/ghc/tests/typecheck/should_fail/tcfail002.stderr
@@ -1,8 +1,8 @@
  
 tcfail002.hs:4: Cannot construct the infinite type (occur check)
-		    `takl' = `[takl]'
-    Expected: `[takl]'
-    Inferred: `takl'
+		    `talR' = `[talR]'
+    Expected: `[talR]'
+    Inferred: `talR'
     In an equation for function `c': `c z = z'
 
 Compilation had errors
diff --git a/ghc/tests/typecheck/should_fail/tcfail003.stderr b/ghc/tests/typecheck/should_fail/tcfail003.stderr
index 0d6092306c0551374face893e7a8d85780ffe601..370ea4831f19fa52c6fd7cd93714fe2409dc0e92 100644
--- a/ghc/tests/typecheck/should_fail/tcfail003.stderr
+++ b/ghc/tests/typecheck/should_fail/tcfail003.stderr
@@ -1,5 +1,5 @@
  
-tcfail003.hs:3: No instance for: `PrelBase.Num PrelBase.Char'
+tcfail003.hs:3: No instance for: `Num Char'
     arising from the literal 1 at tcfail003.hs:3
 
 Compilation had errors
diff --git a/ghc/tests/typecheck/should_fail/tcfail004.stderr b/ghc/tests/typecheck/should_fail/tcfail004.stderr
index e89c848f4c5779c6e3d5c6c78581f9b678edd908..3a12eb67d2a8d7c9dff601315cc0aa9b513a5455 100644
--- a/ghc/tests/typecheck/should_fail/tcfail004.stderr
+++ b/ghc/tests/typecheck/should_fail/tcfail004.stderr
@@ -1,8 +1,7 @@
  
-tcfail004.hs:3: Couldn't match the type
-		    `PrelTup.(,,) taSf' against `PrelTup.(,)'
-    Expected: `(taSf, taSh, taSj)'
-    Inferred: `(taS9, taSc)'
+tcfail004.hs:3: Couldn't match the type `(,,) taUT' against `(,)'
+    Expected: `(taUT, taUV, taUX)'
+    Inferred: `(taUN, taUQ)'
     In a pattern binding: `(f, g) = (1, 2, 3)'
 
 Compilation had errors
diff --git a/ghc/tests/typecheck/should_fail/tcfail005.stderr b/ghc/tests/typecheck/should_fail/tcfail005.stderr
index 4b84b4c729dfbb2eba49cbea701d12ec5a924519..38e9a9dd859891ffd7e27340f7b1bb076166e9b2 100644
--- a/ghc/tests/typecheck/should_fail/tcfail005.stderr
+++ b/ghc/tests/typecheck/should_fail/tcfail005.stderr
@@ -1,8 +1,7 @@
  
-tcfail005.hs:3: Couldn't match the type
-		    `PrelTup.(,) taRt' against `PrelBase.[]'
-    Expected: `(taRt, taRv)'
-    Inferred: `[taRp]'
-    In a pattern binding: `(h PrelBase.: i) = (1, ('a'))'
+tcfail005.hs:3: Couldn't match the type `(,) taU7' against `[]'
+    Expected: `(taU7, taU9)'
+    Inferred: `[taU3]'
+    In a pattern binding: `(h : i) = (1, ('a'))'
 
 Compilation had errors
diff --git a/ghc/tests/typecheck/should_fail/tcfail006.stderr b/ghc/tests/typecheck/should_fail/tcfail006.stderr
index adc03d675cb032da85bfa8114ec5743d4ca0d063..840b2dc7166a6901c9ad4bfd3c07c0dba2986074 100644
--- a/ghc/tests/typecheck/should_fail/tcfail006.stderr
+++ b/ghc/tests/typecheck/should_fail/tcfail006.stderr
@@ -1,5 +1,5 @@
  
-tcfail006.hs:4: No instance for: `PrelBase.Num PrelBase.Bool'
+tcfail006.hs:4: No instance for: `Num Bool'
     arising from the literal 1 at tcfail006.hs:4
 
 Compilation had errors
diff --git a/ghc/tests/typecheck/should_fail/tcfail007.stderr b/ghc/tests/typecheck/should_fail/tcfail007.stderr
index 9cbed2642ed99ecac78990e06687a6eaeab2c115..094e0523a623d0e7d6c59d8cef9359bf84e9859c 100644
--- a/ghc/tests/typecheck/should_fail/tcfail007.stderr
+++ b/ghc/tests/typecheck/should_fail/tcfail007.stderr
@@ -1,5 +1,5 @@
  
-tcfail007.hs:4: No instance for: `PrelBase.Num PrelBase.Bool'
-    arising from use of `PrelBase.+' at tcfail007.hs:4
+tcfail007.hs:4: No instance for: `Num Bool'
+    arising from use of `+' at tcfail007.hs:4
 
 Compilation had errors
diff --git a/ghc/tests/typecheck/should_fail/tcfail008.stderr b/ghc/tests/typecheck/should_fail/tcfail008.stderr
index b0e401cdc168f0afd5e724c945e87775d155aa79..18abfc50b3524f0528c7187067d4f05a9b590f4c 100644
--- a/ghc/tests/typecheck/should_fail/tcfail008.stderr
+++ b/ghc/tests/typecheck/should_fail/tcfail008.stderr
@@ -1,11 +1,11 @@
  
-tcfail008.hs:3: No instance for: `PrelBase.Num [taBU]'
+tcfail008.hs:3: No instance for: `Num [taEy]'
     arising from the literal 2 at tcfail008.hs:3
  
-tcfail008.hs:3: No instance for: `PrelBase.Num [taBU]'
+tcfail008.hs:3: No instance for: `Num [taEy]'
     arising from the literal 2 at tcfail008.hs:3
  
-tcfail008.hs:3: No instance for: `PrelBase.Num [PrelBase.Int]'
+tcfail008.hs:3: No instance for: `Num [Int]'
     arising from the literal 2 at tcfail008.hs:3
 
 Compilation had errors
diff --git a/ghc/tests/typecheck/should_fail/tcfail009.stderr b/ghc/tests/typecheck/should_fail/tcfail009.stderr
index 212a9663f33d3b2e4f11c2d9251332660849df5e..3214d09c7162247c2c2e71b403992c267b0ad3e9 100644
--- a/ghc/tests/typecheck/should_fail/tcfail009.stderr
+++ b/ghc/tests/typecheck/should_fail/tcfail009.stderr
@@ -1,8 +1,7 @@
  
-tcfail009.hs:3: Couldn't match the type
-		    `PrelBase.Int' against `PrelBase.Integer'
-    Expected: `PrelBase.Integer'
-    Inferred: `PrelBase.Int'
-    In an expression with a type signature: `2 :: PrelBase.Integer'
+tcfail009.hs:3: Couldn't match the type `Int' against `Integer'
+    Expected: `Integer'
+    Inferred: `Int'
+    In an expression with a type signature: `2 :: Integer'
 
 Compilation had errors
diff --git a/ghc/tests/typecheck/should_fail/tcfail010.stderr b/ghc/tests/typecheck/should_fail/tcfail010.stderr
index fe1e652479273d96f65f0b680604a8eca7343041..a4c2089da950c297aa3e9229dfaa557b4bf1c68f 100644
--- a/ghc/tests/typecheck/should_fail/tcfail010.stderr
+++ b/ghc/tests/typecheck/should_fail/tcfail010.stderr
@@ -1,8 +1,8 @@
  
-tcfail010.hs:3: No instance for: `PrelBase.Num [taC3]'
-    arising from use of `PrelBase.+' at tcfail010.hs:3
+tcfail010.hs:3: No instance for: `Num [taEH]'
+    arising from use of `+' at tcfail010.hs:3
  
-tcfail010.hs:3: No instance for: `PrelBase.Num [taC3]'
-    arising from use of `PrelBase.+' at tcfail010.hs:3
+tcfail010.hs:3: No instance for: `Num [taEH]'
+    arising from use of `+' at tcfail010.hs:3
 
 Compilation had errors
diff --git a/ghc/tests/typecheck/should_fail/tcfail012.stderr b/ghc/tests/typecheck/should_fail/tcfail012.stderr
index 017841bb483246ddc252955fbf847d915c204058..954d4617ac7a71bd55916daf3e28caf0e9d765c8 100644
--- a/ghc/tests/typecheck/should_fail/tcfail012.stderr
+++ b/ghc/tests/typecheck/should_fail/tcfail012.stderr
@@ -1,8 +1,7 @@
  
-tcfail012.hs:3: Couldn't match the type
-		    `[tak5]' against `PrelBase.Bool'
-    Expected: `[tak5]'
-    Inferred: `PrelBase.Bool'
-    In a pattern binding: `PrelBase.True = PrelBase.[]'
+tcfail012.hs:3: Couldn't match the type `[talB]' against `Bool'
+    Expected: `[talB]'
+    Inferred: `Bool'
+    In a pattern binding: `True = []'
 
 Compilation had errors
diff --git a/ghc/tests/typecheck/should_fail/tcfail013.stderr b/ghc/tests/typecheck/should_fail/tcfail013.stderr
index 4bbf2b14a7a36fb4c42e110a5b47f8b196f4451e..5d3a555d8f708cd9d1748180b8b3d33b52bcf48f 100644
--- a/ghc/tests/typecheck/should_fail/tcfail013.stderr
+++ b/ghc/tests/typecheck/should_fail/tcfail013.stderr
@@ -1,8 +1,7 @@
  
-tcfail013.hs:4: Couldn't match the type
-		    `[taC0]' against `PrelBase.Bool'
-    Expected: `PrelBase.Bool'
-    Inferred: `[taC0]'
-    In an equation for function `f': `f PrelBase.True = 2'
+tcfail013.hs:4: Couldn't match the type `[taEE]' against `Bool'
+    Expected: `Bool'
+    Inferred: `[taEE]'
+    In an equation for function `f': `f True = 2'
 
 Compilation had errors
diff --git a/ghc/tests/typecheck/should_fail/tcfail014.stderr b/ghc/tests/typecheck/should_fail/tcfail014.stderr
index b4ed254cb1f768a681b4c7ace55a483ec836a57f..bf65e9bc84f5b92e22e55d51c023939c12f96677 100644
--- a/ghc/tests/typecheck/should_fail/tcfail014.stderr
+++ b/ghc/tests/typecheck/should_fail/tcfail014.stderr
@@ -1,24 +1,17 @@
  
 tcfail014.hs:5: Cannot construct the infinite type (occur check)
-		    `oaCu' = `oaCu -> oaCw'
-    Expected: `oaCu -> oaCw'
-    Inferred: `oaCu'
+		    `oaF6' = `oaF6 -> oaF8'
+    Expected: `oaF6 -> oaF8'
+    Inferred: `oaF6'
+    In the first argument of `z', namely `z'
     In an equation for function `h': `h z = z z'
     In an equation for function `g':
 	`g y
-	   = h PrelBase.+ 2
+	   = h + 2
 	   where
 	       h z = z z'
-    In an equation for function `f':
-	`f x
-	   = g PrelBase.+ 1
-	   where
-	       g y
-		 = h PrelBase.+ 2
-		 where
-		     h z = z z'
  
-tcfail014.hs:5: No instance for: `PrelBase.Num (taCQ -> taCS)'
-    arising from use of `PrelBase.+' at tcfail014.hs:5
+tcfail014.hs:5: No instance for: `Num (taFs -> taFu)'
+    arising from use of `+' at tcfail014.hs:5
 
 Compilation had errors
diff --git a/ghc/tests/typecheck/should_fail/tcfail015.stderr b/ghc/tests/typecheck/should_fail/tcfail015.stderr
index 554045bdff9badce0d308f299f7dab35efbb30b6..74f130dd7d3d0b5d0c2e227deb22ad1d47d15f97 100644
--- a/ghc/tests/typecheck/should_fail/tcfail015.stderr
+++ b/ghc/tests/typecheck/should_fail/tcfail015.stderr
@@ -1,5 +1,5 @@
  
-tcfail015.hs:7: No instance for: `PrelBase.Num PrelBase.Bool'
+tcfail015.hs:7: No instance for: `Num Bool'
     arising from the literal 2 at tcfail015.hs:7
 
 Compilation had errors
diff --git a/ghc/tests/typecheck/should_fail/tcfail016.stderr b/ghc/tests/typecheck/should_fail/tcfail016.stderr
index 71fb52b6f03f97be32096dfa2d70961b61d0036d..c2df52f6134130e0c445e1901d8b5761f1576e03 100644
--- a/ghc/tests/typecheck/should_fail/tcfail016.stderr
+++ b/ghc/tests/typecheck/should_fail/tcfail016.stderr
@@ -1,9 +1,9 @@
  
-tcfail016.hs:9: Couldn't match the type
-		    `Expr' against `PrelTup.(,) taRG'
-    Expected: `AnnExpr taRG'
-    Inferred: `Expr taRG'
-    In an equation for function `g':
-	`g (App e1 e2) = (g e1) PrelBase.++ (g e2)'
+tcfail016.hs:9: Couldn't match the type `Expr' against `(,) taUk'
+    Expected: `AnnExpr taUk'
+    Inferred: `Expr taUk'
+    In the first argument of `g', namely `e1'
+    In the first argument of `++', namely `(g e1)'
+    In an equation for function `g': `g (App e1 e2) = (g e1) ++ (g e2)'
 
 Compilation had errors
diff --git a/ghc/tests/typecheck/should_fail/tcfail017.stderr b/ghc/tests/typecheck/should_fail/tcfail017.stderr
index 13becd1e72e269624fd6b709e4b948c4962304c2..9431a0873fa70ce36ac3ba864d6bf934f1e8f267 100644
--- a/ghc/tests/typecheck/should_fail/tcfail017.stderr
+++ b/ghc/tests/typecheck/should_fail/tcfail017.stderr
@@ -1,5 +1,5 @@
  
-tcfail017.hs:11: No instance for: `C [takL]'
+tcfail017.hs:11: No instance for: `C [tamh]'
     arising from an instance declaration at tcfail017.hs:11
     When checking superclass constraints of an instance declaration
 
diff --git a/ghc/tests/typecheck/should_fail/tcfail018.hs b/ghc/tests/typecheck/should_fail/tcfail018.hs
index d91306ac553b6454726b08dbfd5264c4e34d7ffa..9d811dcda28ff381423330d0c9404f3ead3aa593 100644
--- a/ghc/tests/typecheck/should_fail/tcfail018.hs
+++ b/ghc/tests/typecheck/should_fail/tcfail018.hs
@@ -1,5 +1,5 @@
 
 
-module ShouldSucc where
+module ShouldFail where
 
 (a:[]) = 1
diff --git a/ghc/tests/typecheck/should_fail/tcfail018.stderr b/ghc/tests/typecheck/should_fail/tcfail018.stderr
index f23ff10a74b3bb4a39b8afdc5cc2ce6116665ee8..ecb7bed3e10df2271bcebdfd1afaab83bd3540a2 100644
--- a/ghc/tests/typecheck/should_fail/tcfail018.stderr
+++ b/ghc/tests/typecheck/should_fail/tcfail018.stderr
@@ -1,8 +1,8 @@
  
-tcfail018.hs:5: No instance for: `PrelBase.Num [taBW]'
+tcfail018.hs:5: No instance for: `Num [taEA]'
     arising from the literal 1 at tcfail018.hs:5
  
-tcfail018.hs:5: No instance for: `PrelBase.Num [taBW]'
+tcfail018.hs:5: No instance for: `Num [taEA]'
     arising from the literal 1 at tcfail018.hs:5
 
 Compilation had errors
diff --git a/ghc/tests/typecheck/should_fail/tcfail019.hs b/ghc/tests/typecheck/should_fail/tcfail019.hs
index b3da9cdebcba0b097cb993b191358b337fc8ec1c..af46532f4471eb5b861e7ffd69a6c8704e713b19 100644
--- a/ghc/tests/typecheck/should_fail/tcfail019.hs
+++ b/ghc/tests/typecheck/should_fail/tcfail019.hs
@@ -1,5 +1,4 @@
-
-module P where
+module ShouldFail where
 
 class A a where
  p1 :: a -> a
diff --git a/ghc/tests/typecheck/should_fail/tcfail019.stderr b/ghc/tests/typecheck/should_fail/tcfail019.stderr
index c4534e6ebf70311bfa93b624dd5777332d81e204..94b0b4e5a2e1325b710b9c76ac8aa2c3c8a69694 100644
--- a/ghc/tests/typecheck/should_fail/tcfail019.stderr
+++ b/ghc/tests/typecheck/should_fail/tcfail019.stderr
@@ -1,18 +1,18 @@
  
-tcfail019.hs:20: No instance for: `B [tali]'
-    arising from an instance declaration at tcfail019.hs:20
+tcfail019.hs:19: No instance for: `B [tamO]'
+    arising from an instance declaration at tcfail019.hs:19
     When checking methods of an instance declaration
  
-tcfail019.hs:20: No instance for: `C [tali]'
-    arising from an instance declaration at tcfail019.hs:20
+tcfail019.hs:19: No instance for: `C [tamO]'
+    arising from an instance declaration at tcfail019.hs:19
     When checking methods of an instance declaration
  
-tcfail019.hs:20: No instance for: `B [tali]'
-    arising from an instance declaration at tcfail019.hs:20
+tcfail019.hs:19: No instance for: `B [tamO]'
+    arising from an instance declaration at tcfail019.hs:19
     When checking superclass constraints of an instance declaration
  
-tcfail019.hs:20: No instance for: `C [tali]'
-    arising from an instance declaration at tcfail019.hs:20
+tcfail019.hs:19: No instance for: `C [tamO]'
+    arising from an instance declaration at tcfail019.hs:19
     When checking superclass constraints of an instance declaration
 
 Compilation had errors
diff --git a/ghc/tests/typecheck/should_fail/tcfail020.hs b/ghc/tests/typecheck/should_fail/tcfail020.hs
index 9697838fb1c2c396fcad4d38a065d7c0be2e21bd..0d3dc2594a131e7110b8a7ce7a228449a681b364 100644
--- a/ghc/tests/typecheck/should_fail/tcfail020.hs
+++ b/ghc/tests/typecheck/should_fail/tcfail020.hs
@@ -1,5 +1,4 @@
-
-module P where
+module ShouldFail where
 
 class A a where
  p1 :: a -> a
diff --git a/ghc/tests/typecheck/should_fail/tcfail020.stderr b/ghc/tests/typecheck/should_fail/tcfail020.stderr
index cad885a37396611cb5becb85d8cdc00775f8d0f0..ec1caf0733e4ee75f90f61f9aa33b6470b8c3329 100644
--- a/ghc/tests/typecheck/should_fail/tcfail020.stderr
+++ b/ghc/tests/typecheck/should_fail/tcfail020.stderr
@@ -1,6 +1,6 @@
  
-tcfail020.hs:12: No instance for: `A [taBL]'
-    arising from an instance declaration at tcfail020.hs:12
+tcfail020.hs:11: No instance for: `A [taEp]'
+    arising from an instance declaration at tcfail020.hs:11
     When checking superclass constraints of an instance declaration
 
 Compilation had errors
diff --git a/ghc/tests/typecheck/should_fail/tcfail023.hs b/ghc/tests/typecheck/should_fail/tcfail023.hs
index ae2a3564610a6f4922a3aec719673d37046a7e05..e9535bea7140f0b768029ebacb1f685114692d3e 100644
--- a/ghc/tests/typecheck/should_fail/tcfail023.hs
+++ b/ghc/tests/typecheck/should_fail/tcfail023.hs
@@ -1,3 +1,6 @@
+module ShouldFail where
+
+--!!! Duplicate instances
 
 data B = C
 
diff --git a/ghc/tests/typecheck/should_fail/tcfail023.stderr b/ghc/tests/typecheck/should_fail/tcfail023.stderr
index 6451879128b357f20a76c86e38ff0f96b3d78b52..4520320ddbbf2f20156468f115f65995e8bb0d3a 100644
--- a/ghc/tests/typecheck/should_fail/tcfail023.stderr
+++ b/ghc/tests/typecheck/should_fail/tcfail023.stderr
@@ -1,24 +1,21 @@
  
-tcfail023.hs:2: Duplicate or overlapping instance declarations
-    for `A B' at tcfail023.hs:8 and tcfail023.hs:11
+tcfail023.hs:1: Duplicate or overlapping instance declarations
+    for `A B' at tcfail023.hs:11 and tcfail023.hs:14
  
-tcfail023.hs:2: Duplicate or overlapping instance declarations
-    for `A B' at tcfail023.hs:8 and tcfail023.hs:11
+tcfail023.hs:1: Duplicate or overlapping instance declarations
+    for `A B' at tcfail023.hs:11 and tcfail023.hs:14
  
-tcfail023.hs:2: Duplicate or overlapping instance declarations
-    for `A B' at tcfail023.hs:8 and tcfail023.hs:11
+tcfail023.hs:1: Duplicate or overlapping instance declarations
+    for `A B' at tcfail023.hs:11 and tcfail023.hs:14
  
-tcfail023.hs:11: Couldn't match the type
-		     `PrelBase.Bool' against `B'
-    Expected: `PrelBase.Bool'
+tcfail023.hs:14: Couldn't match the type `Bool' against `B'
+    Expected: `Bool'
     Inferred: `B'
-    In an equation for function `op': `op C = PrelBase.True'
+    In an equation for function `op': `op C = True'
  
-tcfail023.hs:8: Couldn't match the type `PrelBase.Bool' against `B'
-    Expected: `PrelBase.Bool'
+tcfail023.hs:11: Couldn't match the type `Bool' against `B'
+    Expected: `Bool'
     Inferred: `B'
-    In an equation for function `op': `op C = PrelBase.True'
- 
-tcfail023.hs:2: Module Main must include a definition for `Main.main'
+    In an equation for function `op': `op C = True'
 
 Compilation had errors
diff --git a/ghc/tests/typecheck/should_fail/tcfail028.stderr b/ghc/tests/typecheck/should_fail/tcfail028.stderr
index 1f259fa353231f656da67594fd453116946febc6..280f45acd83e8319500dff1c62168c82410c164f 100644
--- a/ghc/tests/typecheck/should_fail/tcfail028.stderr
+++ b/ghc/tests/typecheck/should_fail/tcfail028.stderr
@@ -1,6 +1,6 @@
  
-tcfail028.hs:4: Couldn't match the kind `ka2559 -> *' against `*'
-    When unifying two kinds `ka2559 -> *' and `*'
+tcfail028.hs:4: Couldn't match the kind `ka2689 -> *' against `*'
+    When unifying two kinds `ka2689 -> *' and `*'
     In the data declaration for `A'
 
 Compilation had errors
diff --git a/ghc/tests/typecheck/should_fail/tcfail029.stderr b/ghc/tests/typecheck/should_fail/tcfail029.stderr
index b0689617f1250cd4d1b23ecdab33ae7677bb8552..211b411f3c6faaed7e207abf5134b5eed4d23b6d 100644
--- a/ghc/tests/typecheck/should_fail/tcfail029.stderr
+++ b/ghc/tests/typecheck/should_fail/tcfail029.stderr
@@ -1,5 +1,5 @@
  
-tcfail029.hs:6: No instance for: `PrelBase.Ord Foo'
-    arising from use of `PrelBase.>' at tcfail029.hs:6
+tcfail029.hs:6: No instance for: `Ord Foo'
+    arising from use of `>' at tcfail029.hs:6
 
 Compilation had errors
diff --git a/ghc/tests/typecheck/should_fail/tcfail030.stderr b/ghc/tests/typecheck/should_fail/tcfail030.stderr
index 9feab77b28a93723aa808c337396ee1182910860..e2f5c836ce9fecbd4d406fcb02c25b3549f6c2ba 100644
--- a/ghc/tests/typecheck/should_fail/tcfail030.stderr
+++ b/ghc/tests/typecheck/should_fail/tcfail030.stderr
@@ -1,4 +1,4 @@
  
-tcfail030.hs:0: Module Main must include a definition for `Main.main'
+tcfail030.hs:0: Module Main must include a definition for `main'
 
 Compilation had errors
diff --git a/ghc/tests/typecheck/should_fail/tcfail031.stderr b/ghc/tests/typecheck/should_fail/tcfail031.stderr
index 7fd3b04ba67101764904c372fa3b810c088ccd3c..786d1cc7fc821dfcad04dafcf478987426484769 100644
--- a/ghc/tests/typecheck/should_fail/tcfail031.stderr
+++ b/ghc/tests/typecheck/should_fail/tcfail031.stderr
@@ -1,8 +1,7 @@
  
-tcfail031.hs:3: Couldn't match the type
-		    `PrelBase.Char' against `PrelBase.Bool'
-    Expected: `PrelBase.Char'
-    Inferred: `PrelBase.Bool'
+tcfail031.hs:3: Couldn't match the type `Char' against `Bool'
+    Expected: `Char'
+    Inferred: `Bool'
     In the predicate expression `'a''
     In an equation for function `f': `f x = if 'a' then 1 else 2'
 
diff --git a/ghc/tests/typecheck/should_fail/tcfail032.hs b/ghc/tests/typecheck/should_fail/tcfail032.hs
index 0e8884da3fe754d3f3deb3ec6f7f6c64e01f0b09..5950064655fab2567d47970a15df6f82e4243615 100644
--- a/ghc/tests/typecheck/should_fail/tcfail032.hs
+++ b/ghc/tests/typecheck/should_fail/tcfail032.hs
@@ -9,7 +9,7 @@ It *is* an error, because x does not have the polytype
 becuase it is monomorphic, but the error message isn't very illuminating.
 -}
 
-module TcSig where
+module ShouldFail where
 
 f x = (x :: (Eq a) => a -> Int)
 
diff --git a/ghc/tests/typecheck/should_fail/tcfail032.stderr b/ghc/tests/typecheck/should_fail/tcfail032.stderr
index 41a51e50840ee6ab889c3631ae7d39e0af4708db..1bcfb865b21e09b5f792acd05f64b247622751f2 100644
--- a/ghc/tests/typecheck/should_fail/tcfail032.stderr
+++ b/ghc/tests/typecheck/should_fail/tcfail032.stderr
@@ -1,8 +1,8 @@
  
 tcfail032.hs:14: A type signature is more polymorphic than the inferred type
-		     Can't for-all the type variable(s) `taAX'
-		     in the inferred type `taAX -> PrelBase.Int'
+		     Can't for-all the type variable(s) `taDB'
+		     in the inferred type `taDB -> Int'
     In an expression with a type signature:
-	`x :: _forall_ [a] (PrelBase.Eq a) => a -> PrelBase.Int'
+	`x :: _forall_ [a] (Eq a) => a -> Int'
 
 Compilation had errors
diff --git a/ghc/tests/typecheck/should_fail/tcfail033.stderr b/ghc/tests/typecheck/should_fail/tcfail033.stderr
index 505c9429b293292beacc1003be90ec825d749ee2..9052ddba7d6b1d28d9a04624833e06f28e865d3f 100644
--- a/ghc/tests/typecheck/should_fail/tcfail033.stderr
+++ b/ghc/tests/typecheck/should_fail/tcfail033.stderr
@@ -1,8 +1,8 @@
  
 tcfail033.hs:4: Cannot construct the infinite type (occur check)
-		    `taGE' = `(taGE, taGH)'
-    Expected: `aaGJ taGE'
-    Inferred: `aaGJ (taGE, taGH)'
+		    `taIc' = `(taIc, taIf)'
+    Expected: `aaIh taIc'
+    Inferred: `aaIh (taIc, taIf)'
     In a pattern binding: `buglet = [x | (x, y) <- buglet]'
 
 Compilation had errors
diff --git a/ghc/tests/typecheck/should_fail/tcfail034.hs b/ghc/tests/typecheck/should_fail/tcfail034.hs
index 82aa18b41872cc2446c25314d973d24f73f7daef..0bbb75fab8cfd572110299cec9f0092555fc0b51 100644
--- a/ghc/tests/typecheck/should_fail/tcfail034.hs
+++ b/ghc/tests/typecheck/should_fail/tcfail034.hs
@@ -10,7 +10,7 @@ I came across a rather nasty error message when I gave a function an
 incorrect type signature (the context is wrong). I can remember reading 
 in the source about this problem - I just thought I'd let you know anyway :-)
 -}
-module ShouldSucceed where
+module ShouldFail where
 
 
 test::(Num a, Eq a) => a -> Bool
diff --git a/ghc/tests/typecheck/should_fail/tcfail034.stderr b/ghc/tests/typecheck/should_fail/tcfail034.stderr
index 10f39722a8d849d482dcd8340a3f92fb57ecd3ee..b24a1384d96bb3ae913d726caf0776564501a2b2 100644
--- a/ghc/tests/typecheck/should_fail/tcfail034.stderr
+++ b/ghc/tests/typecheck/should_fail/tcfail034.stderr
@@ -1,7 +1,7 @@
  
-tcfail034.hs:13: Context `{PrelNum.Integral taU6}'
+tcfail034.hs:13: Context `{Integral taWK}'
 		     required by inferred type, but missing on a type signature
-		     `PrelNum.Integral taU6' arising from use of `PrelNum.mod' at tcfail034.hs:17
+		     `Integral taWK' arising from use of `mod' at tcfail034.hs:17
     When checking signature(s) for: `test'
 
 Compilation had errors
diff --git a/ghc/tests/typecheck/should_fail/tcfail035.hs b/ghc/tests/typecheck/should_fail/tcfail035.hs
index a12908ee5a246ed9f0ede3b95b7a6baa2aba0d6f..555fa70e87ac2be4d6514e12c19be5ccce6107db 100644
--- a/ghc/tests/typecheck/should_fail/tcfail035.hs
+++ b/ghc/tests/typecheck/should_fail/tcfail035.hs
@@ -1,6 +1,6 @@
 --!!! instances with empty where parts: duplicate
 --
-module M where
+module ShouldFail where
 
 data NUM = ONE | TWO
 instance Num NUM
diff --git a/ghc/tests/typecheck/should_fail/tcfail035.stderr b/ghc/tests/typecheck/should_fail/tcfail035.stderr
index c5b3cdbc0d5b797b40835202d3ae92245a9bedbe..0d7e28d880b459e8fd8d67af82cd24cb22b2cb5e 100644
--- a/ghc/tests/typecheck/should_fail/tcfail035.stderr
+++ b/ghc/tests/typecheck/should_fail/tcfail035.stderr
@@ -1,68 +1,68 @@
  
-tcfail035.hs:9: No explicit method nor default method for `PrelBase.showsPrec'
-		in an instance declaration for `PrelBase.Show'
+tcfail035.hs:9: Warning: no explicit method nor default method for `showsPrec'
+		in an instance declaration for `Show'
  
-tcfail035.hs:8: No explicit method nor default method for `PrelBase.=='
-		in an instance declaration for `PrelBase.Eq'
+tcfail035.hs:8: Warning: no explicit method nor default method for `=='
+		in an instance declaration for `Eq'
  
-tcfail035.hs:7: No explicit method nor default method for `PrelBase.+'
-		in an instance declaration for `PrelBase.Num'
+tcfail035.hs:7: Warning: no explicit method nor default method for `+'
+		in an instance declaration for `Num'
  
-tcfail035.hs:7: No explicit method nor default method for `PrelBase.*'
-		in an instance declaration for `PrelBase.Num'
+tcfail035.hs:7: Warning: no explicit method nor default method for `*'
+		in an instance declaration for `Num'
  
-tcfail035.hs:7: No explicit method nor default method for `PrelBase.negate'
-		in an instance declaration for `PrelBase.Num'
+tcfail035.hs:7: Warning: no explicit method nor default method for `negate'
+		in an instance declaration for `Num'
  
-tcfail035.hs:7: No explicit method nor default method for `PrelBase.abs'
-		in an instance declaration for `PrelBase.Num'
+tcfail035.hs:7: Warning: no explicit method nor default method for `abs'
+		in an instance declaration for `Num'
  
-tcfail035.hs:7: No explicit method nor default method for `PrelBase.signum'
-		in an instance declaration for `PrelBase.Num'
+tcfail035.hs:7: Warning: no explicit method nor default method for `signum'
+		in an instance declaration for `Num'
  
-tcfail035.hs:7: No explicit method nor default method for `PrelBase.fromInteger'
-		in an instance declaration for `PrelBase.Num'
+tcfail035.hs:7: Warning: no explicit method nor default method for `fromInteger'
+		in an instance declaration for `Num'
  
-tcfail035.hs:6: No explicit method nor default method for `PrelBase.+'
-		in an instance declaration for `PrelBase.Num'
+tcfail035.hs:6: Warning: no explicit method nor default method for `+'
+		in an instance declaration for `Num'
  
-tcfail035.hs:6: No explicit method nor default method for `PrelBase.*'
-		in an instance declaration for `PrelBase.Num'
+tcfail035.hs:6: Warning: no explicit method nor default method for `*'
+		in an instance declaration for `Num'
  
-tcfail035.hs:6: No explicit method nor default method for `PrelBase.negate'
-		in an instance declaration for `PrelBase.Num'
+tcfail035.hs:6: Warning: no explicit method nor default method for `negate'
+		in an instance declaration for `Num'
  
-tcfail035.hs:6: No explicit method nor default method for `PrelBase.abs'
-		in an instance declaration for `PrelBase.Num'
+tcfail035.hs:6: Warning: no explicit method nor default method for `abs'
+		in an instance declaration for `Num'
  
-tcfail035.hs:6: No explicit method nor default method for `PrelBase.signum'
-		in an instance declaration for `PrelBase.Num'
+tcfail035.hs:6: Warning: no explicit method nor default method for `signum'
+		in an instance declaration for `Num'
  
-tcfail035.hs:6: No explicit method nor default method for `PrelBase.fromInteger'
-		in an instance declaration for `PrelBase.Num'
+tcfail035.hs:6: Warning: no explicit method nor default method for `fromInteger'
+		in an instance declaration for `Num'
  
 tcfail035.hs:3: Duplicate or overlapping instance declarations
-    for `PrelBase.Num NUM' at tcfail035.hs:6 and tcfail035.hs:7
+    for `Num NUM' at tcfail035.hs:6 and tcfail035.hs:7
  
 tcfail035.hs:3: Duplicate or overlapping instance declarations
-    for `PrelBase.Num NUM' at tcfail035.hs:6 and tcfail035.hs:7
+    for `Num NUM' at tcfail035.hs:6 and tcfail035.hs:7
  
 tcfail035.hs:3: Duplicate or overlapping instance declarations
-    for `PrelBase.Num NUM' at tcfail035.hs:6 and tcfail035.hs:7
+    for `Num NUM' at tcfail035.hs:6 and tcfail035.hs:7
  
-tcfail035.hs:7: No instance for: `PrelBase.Eval NUM'
+tcfail035.hs:7: No instance for: `Eval NUM'
     arising from an instance declaration at tcfail035.hs:7
     When checking methods of an instance declaration
  
-tcfail035.hs:7: No instance for: `PrelBase.Eval NUM'
+tcfail035.hs:7: No instance for: `Eval NUM'
     arising from an instance declaration at tcfail035.hs:7
     When checking superclass constraints of an instance declaration
  
-tcfail035.hs:6: No instance for: `PrelBase.Eval NUM'
+tcfail035.hs:6: No instance for: `Eval NUM'
     arising from an instance declaration at tcfail035.hs:6
     When checking methods of an instance declaration
  
-tcfail035.hs:6: No instance for: `PrelBase.Eval NUM'
+tcfail035.hs:6: No instance for: `Eval NUM'
     arising from an instance declaration at tcfail035.hs:6
     When checking superclass constraints of an instance declaration
 
diff --git a/ghc/tests/typecheck/should_fail/tcfail036.hs b/ghc/tests/typecheck/should_fail/tcfail036.hs
index eb9f9aff85b8767fb1670d1160385c4dc7559f46..3b316a71309f109609213ce700b955afd4cb5767 100644
--- a/ghc/tests/typecheck/should_fail/tcfail036.hs
+++ b/ghc/tests/typecheck/should_fail/tcfail036.hs
@@ -1,6 +1,6 @@
 --!!! prelude class name in an instance-tycon position
 --
-module M where
+module ShouldFail where
 
 data NUM = ONE | TWO
 instance Num NUM
diff --git a/ghc/tests/typecheck/should_fail/tcfail036.stderr b/ghc/tests/typecheck/should_fail/tcfail036.stderr
index 8b34ed7a344cb419d35c2aead13688ccbf4890c7..1f9f358b3f0fe609988754c2b92337cd5d5ece61 100644
--- a/ghc/tests/typecheck/should_fail/tcfail036.stderr
+++ b/ghc/tests/typecheck/should_fail/tcfail036.stderr
@@ -1,93 +1,93 @@
  
-tcfail036.hs:8: No explicit method nor default method for `PrelBase.+'
-		in an instance declaration for `PrelBase.Num'
+tcfail036.hs:8: Warning: no explicit method nor default method for `+'
+		in an instance declaration for `Num'
  
-tcfail036.hs:8: No explicit method nor default method for `PrelBase.*'
-		in an instance declaration for `PrelBase.Num'
+tcfail036.hs:8: Warning: no explicit method nor default method for `*'
+		in an instance declaration for `Num'
  
-tcfail036.hs:8: No explicit method nor default method for `PrelBase.negate'
-		in an instance declaration for `PrelBase.Num'
+tcfail036.hs:8: Warning: no explicit method nor default method for `negate'
+		in an instance declaration for `Num'
  
-tcfail036.hs:8: No explicit method nor default method for `PrelBase.abs'
-		in an instance declaration for `PrelBase.Num'
+tcfail036.hs:8: Warning: no explicit method nor default method for `abs'
+		in an instance declaration for `Num'
  
-tcfail036.hs:8: No explicit method nor default method for `PrelBase.signum'
-		in an instance declaration for `PrelBase.Num'
+tcfail036.hs:8: Warning: no explicit method nor default method for `signum'
+		in an instance declaration for `Num'
  
-tcfail036.hs:8: No explicit method nor default method for `PrelBase.fromInteger'
-		in an instance declaration for `PrelBase.Num'
+tcfail036.hs:8: Warning: no explicit method nor default method for `fromInteger'
+		in an instance declaration for `Num'
  
-tcfail036.hs:7: No explicit method nor default method for `PrelBase.*'
-		in an instance declaration for `PrelBase.Num'
+tcfail036.hs:7: Warning: no explicit method nor default method for `*'
+		in an instance declaration for `Num'
  
-tcfail036.hs:7: No explicit method nor default method for `PrelBase.negate'
-		in an instance declaration for `PrelBase.Num'
+tcfail036.hs:7: Warning: no explicit method nor default method for `negate'
+		in an instance declaration for `Num'
  
-tcfail036.hs:7: No explicit method nor default method for `PrelBase.abs'
-		in an instance declaration for `PrelBase.Num'
+tcfail036.hs:7: Warning: no explicit method nor default method for `abs'
+		in an instance declaration for `Num'
  
-tcfail036.hs:7: No explicit method nor default method for `PrelBase.signum'
-		in an instance declaration for `PrelBase.Num'
+tcfail036.hs:7: Warning: no explicit method nor default method for `signum'
+		in an instance declaration for `Num'
  
-tcfail036.hs:7: No explicit method nor default method for `PrelBase.fromInteger'
-		in an instance declaration for `PrelBase.Num'
+tcfail036.hs:7: Warning: no explicit method nor default method for `fromInteger'
+		in an instance declaration for `Num'
  
-tcfail036.hs:9: Class used as a type constructor: `PrelBase.Num'
+tcfail036.hs:9: Class used as a type constructor: `Num'
  
 tcfail036.hs:3: Duplicate or overlapping instance declarations
-    for `PrelBase.Num NUM' at tcfail036.hs:7 and tcfail036.hs:8
+    for `Num NUM' at tcfail036.hs:7 and tcfail036.hs:8
  
 tcfail036.hs:3: Duplicate or overlapping instance declarations
-    for `PrelBase.Num NUM' at tcfail036.hs:7 and tcfail036.hs:8
+    for `Num NUM' at tcfail036.hs:7 and tcfail036.hs:8
  
 tcfail036.hs:3: Duplicate or overlapping instance declarations
-    for `PrelBase.Num NUM' at tcfail036.hs:7 and tcfail036.hs:8
+    for `Num NUM' at tcfail036.hs:7 and tcfail036.hs:8
  
-tcfail036.hs:8: No instance for: `PrelBase.Eq NUM'
+tcfail036.hs:8: No instance for: `Eq NUM'
     arising from an instance declaration at tcfail036.hs:8
     When checking methods of an instance declaration
  
-tcfail036.hs:8: No instance for: `PrelBase.Show NUM'
+tcfail036.hs:8: No instance for: `Show NUM'
     arising from an instance declaration at tcfail036.hs:8
     When checking methods of an instance declaration
  
-tcfail036.hs:8: No instance for: `PrelBase.Eval NUM'
+tcfail036.hs:8: No instance for: `Eval NUM'
     arising from an instance declaration at tcfail036.hs:8
     When checking methods of an instance declaration
  
-tcfail036.hs:8: No instance for: `PrelBase.Eq NUM'
+tcfail036.hs:8: No instance for: `Eq NUM'
     arising from an instance declaration at tcfail036.hs:8
     When checking superclass constraints of an instance declaration
  
-tcfail036.hs:8: No instance for: `PrelBase.Show NUM'
+tcfail036.hs:8: No instance for: `Show NUM'
     arising from an instance declaration at tcfail036.hs:8
     When checking superclass constraints of an instance declaration
  
-tcfail036.hs:8: No instance for: `PrelBase.Eval NUM'
+tcfail036.hs:8: No instance for: `Eval NUM'
     arising from an instance declaration at tcfail036.hs:8
     When checking superclass constraints of an instance declaration
  
-tcfail036.hs:7: No instance for: `PrelBase.Eq NUM'
+tcfail036.hs:7: No instance for: `Eq NUM'
     arising from an instance declaration at tcfail036.hs:7
     When checking methods of an instance declaration
  
-tcfail036.hs:7: No instance for: `PrelBase.Show NUM'
+tcfail036.hs:7: No instance for: `Show NUM'
     arising from an instance declaration at tcfail036.hs:7
     When checking methods of an instance declaration
  
-tcfail036.hs:7: No instance for: `PrelBase.Eval NUM'
+tcfail036.hs:7: No instance for: `Eval NUM'
     arising from an instance declaration at tcfail036.hs:7
     When checking methods of an instance declaration
  
-tcfail036.hs:7: No instance for: `PrelBase.Eq NUM'
+tcfail036.hs:7: No instance for: `Eq NUM'
     arising from an instance declaration at tcfail036.hs:7
     When checking superclass constraints of an instance declaration
  
-tcfail036.hs:7: No instance for: `PrelBase.Show NUM'
+tcfail036.hs:7: No instance for: `Show NUM'
     arising from an instance declaration at tcfail036.hs:7
     When checking superclass constraints of an instance declaration
  
-tcfail036.hs:7: No instance for: `PrelBase.Eval NUM'
+tcfail036.hs:7: No instance for: `Eval NUM'
     arising from an instance declaration at tcfail036.hs:7
     When checking superclass constraints of an instance declaration
 
diff --git a/ghc/tests/typecheck/should_fail/tcfail037.hs b/ghc/tests/typecheck/should_fail/tcfail037.hs
index 07b308b98cc357bc8befc1f494d4abf435f41c93..998abd681a196b11a08c3007d4e574d02c0b09f8 100644
--- a/ghc/tests/typecheck/should_fail/tcfail037.hs
+++ b/ghc/tests/typecheck/should_fail/tcfail037.hs
@@ -1,6 +1,6 @@
 --!!! PreludeCore entities cannot be redefined at the top-level
 --
-module M where
+module ShouldFail where
 
 data NUM = ONE | TWO
 
diff --git a/ghc/tests/typecheck/should_fail/tcfail038.hs b/ghc/tests/typecheck/should_fail/tcfail038.hs
index 7d03529a4e787831c6818b2f566c6b399c762fd9..905d9ae8080b9b1435b0d56a6d1cb33b6ae381a6 100644
--- a/ghc/tests/typecheck/should_fail/tcfail038.hs
+++ b/ghc/tests/typecheck/should_fail/tcfail038.hs
@@ -1,6 +1,6 @@
 --!!! duplicate class-method declarations
 
-module M where
+module ShouldFail where
 
 data NUM = ONE | TWO
 instance Eq NUM where
diff --git a/ghc/tests/typecheck/should_fail/tcfail039.hs b/ghc/tests/typecheck/should_fail/tcfail039.hs
index f0df10c28712da89ec5cab0205395e2d552c2ec5..10d501a381dd00bdd2f9c63591cf1e694004899f 100644
--- a/ghc/tests/typecheck/should_fail/tcfail039.hs
+++ b/ghc/tests/typecheck/should_fail/tcfail039.hs
@@ -1,6 +1,6 @@
 --!!! bogus re-use of prelude class-method name (==)
 --
-module M where
+module ShouldFail where
 
 data NUM = ONE | TWO
 class EQ a where
diff --git a/ghc/tests/typecheck/should_fail/tcfail040.hs b/ghc/tests/typecheck/should_fail/tcfail040.hs
index c611518ee4ab606bea2dec148d1174f4db5ed505..16e5948b81058a603945392452c1d3527900dd17 100644
--- a/ghc/tests/typecheck/should_fail/tcfail040.hs
+++ b/ghc/tests/typecheck/should_fail/tcfail040.hs
@@ -1,6 +1,6 @@
 --!!! instances of functions
 --
-module M where
+module ShouldFail where
 
 data NUM = ONE | TWO
 
diff --git a/ghc/tests/typecheck/should_fail/tcfail040.stderr b/ghc/tests/typecheck/should_fail/tcfail040.stderr
index 9bdf2736c9651e067dba2ddb2e136655b41f715d..37a8b172a61dc40b2780ccf71bbb72ec78874cca 100644
--- a/ghc/tests/typecheck/should_fail/tcfail040.stderr
+++ b/ghc/tests/typecheck/should_fail/tcfail040.stderr
@@ -1,5 +1,5 @@
  
-tcfail040.hs:3: Ambiguous context `{ORD taBP}'
-		    `ORD taBP' arising from use of `<<' at tcfail040.hs:19
+tcfail040.hs:3: Ambiguous context `{ORD taEt}'
+		    `ORD taEt' arising from use of `<<' at tcfail040.hs:19
 
 Compilation had errors
diff --git a/ghc/tests/typecheck/should_fail/tcfail042.hs b/ghc/tests/typecheck/should_fail/tcfail042.hs
index 37c24936a99607b27e61485cfbffe02d840e60e8..03286e644312c7742e65999548ce6c97df8fbf00 100644
--- a/ghc/tests/typecheck/should_fail/tcfail042.hs
+++ b/ghc/tests/typecheck/should_fail/tcfail042.hs
@@ -1,3 +1,5 @@
+module ShouldFail where
+
 --!!! weird class/instance examples off the haskell list
 --
 
diff --git a/ghc/tests/typecheck/should_fail/tcfail042.stderr b/ghc/tests/typecheck/should_fail/tcfail042.stderr
index 9b822e209b30c6d7e6cac4044c85c8036a55dc5b..7c4aa5de17d6c2e032ee57d413371241b90b1dc4 100644
--- a/ghc/tests/typecheck/should_fail/tcfail042.stderr
+++ b/ghc/tests/typecheck/should_fail/tcfail042.stderr
@@ -1,9 +1,7 @@
  
-tcfail042.hs:16: Context `{PrelBase.Num taHH}'
+tcfail042.hs:18: Context `{Num taFC}'
 		     required by inferred type, but missing on a type signature
-		     `PrelBase.Num taHH' arising from an instance declaration at tcfail042.hs:16
+		     `Num taFC' arising from an instance declaration at tcfail042.hs:18
     When checking superclass constraints of an instance declaration
- 
-tcfail042.hs:4: Module Main must include a definition for `Main.main'
 
 Compilation had errors
diff --git a/ghc/tests/typecheck/should_fail/tcfail044.hs b/ghc/tests/typecheck/should_fail/tcfail044.hs
index 3f899a6f6b883b0c1394ee243cb73a404aa779b2..883f0ee14371cd8ea9ebd951b421053304dbd913 100644
--- a/ghc/tests/typecheck/should_fail/tcfail044.hs
+++ b/ghc/tests/typecheck/should_fail/tcfail044.hs
@@ -1,6 +1,6 @@
 --!!! tcfail044: duplicated type variable in instance decls
 --
-module Main where
+module ShouldFail where
 
 instance (Eq a) => Eq (a->a)
  
@@ -19,4 +19,4 @@ ss = sin * sin
 cc = cos * cos
 tt = ss + cc
 
-main = putStr ((show (tt 0.4))++ "  "++(show (tt 1.652)))
+--main = putStr ((show (tt 0.4))++ "  "++(show (tt 1.652)))
diff --git a/ghc/tests/typecheck/should_fail/tcfail044.stderr b/ghc/tests/typecheck/should_fail/tcfail044.stderr
index 07e4b0b5fdcb179adc70a2b34fe295fb792bda4e..58e3646b768676ef7c5c50bb3b973cfddda8c332 100644
--- a/ghc/tests/typecheck/should_fail/tcfail044.stderr
+++ b/ghc/tests/typecheck/should_fail/tcfail044.stderr
@@ -7,8 +7,7 @@ tcfail044.hs:5: The type
 		    `a -> a'
 		cannot be used as an instance type
  
-tcfail044.hs:20: No instance for: `PrelBase.Num (PrelBase.Float
-						 -> PrelBase.Float)'
-    arising from use of `PrelBase.+' at tcfail044.hs:20
+tcfail044.hs:20: No instance for: `Num (Float -> Float)'
+    arising from use of `+' at tcfail044.hs:20
 
 Compilation had errors
diff --git a/ghc/tests/typecheck/should_fail/tcfail045.hs b/ghc/tests/typecheck/should_fail/tcfail045.hs
index b189d40077e078900c3fa5db54930a5c5d7c43e4..2bff7e512c60b37d3ba27d3ccf42bac5c1b6166f 100644
--- a/ghc/tests/typecheck/should_fail/tcfail045.hs
+++ b/ghc/tests/typecheck/should_fail/tcfail045.hs
@@ -1,11 +1,13 @@
 --!!! a bad _CCallable thing (from a bug from Satnam)
 --
-module ShouldSucceed where
+module ShouldFail where
 
 import Foreign
+import Addr
+import CCall
 
 data Socket = Socket# Addr
 instance CCallable Socket
 
-f :: Socket -> PrimIO ()
+f :: Socket -> IO ()
 f x = _ccall_ foo x
diff --git a/ghc/tests/typecheck/should_fail/tcfail045.stderr b/ghc/tests/typecheck/should_fail/tcfail045.stderr
index aab4038d5328569c6bb5c827b860af4afd93657d..a12ddfc69e23d8dddd2aa3a3f86656253a23901f 100644
--- a/ghc/tests/typecheck/should_fail/tcfail045.stderr
+++ b/ghc/tests/typecheck/should_fail/tcfail045.stderr
@@ -1,4 +1,9 @@
  
-tcfail045.hs:10: Type constructor or class not in scope: `PrimIO'
+tcfail045.hs:10: Unacceptable instance type for ccall-ish class
+		     class `CCallable' type `Socket'
+ 
+tcfail045.hs:13: No instance for: `CCallable Socket'
+    arising from an argument in the _ccall_ to foo, namely `x' at tcfail045.hs:13
+    When checking signature(s) for: `f'
 
 Compilation had errors
diff --git a/ghc/tests/typecheck/should_fail/tcfail046.hs b/ghc/tests/typecheck/should_fail/tcfail046.hs
index 40fad6ba7d4a99bfeb125f921e0e2aafe0bfa70b..25520d9a0c86f59c260232449bf83584ce04d114 100644
--- a/ghc/tests/typecheck/should_fail/tcfail046.hs
+++ b/ghc/tests/typecheck/should_fail/tcfail046.hs
@@ -1,13 +1,7 @@
 --!! function types in deriving Eq things
 -- From a bug report by Dave Harrison <D.A.Harrison@newcastle.ac.uk>
 
-module Simulation(Process,
-		  Status,
-		  Pid,
-		  Time,
-		  Continuation,
-		  Message,
-		  MessList ) where
+module ShouldFail where
 
 type 	Process a = Pid -> Time -> Message a -> ( MessList a, 
 			     		   	  Continuation a)
diff --git a/ghc/tests/typecheck/should_fail/tcfail046.stderr b/ghc/tests/typecheck/should_fail/tcfail046.stderr
index 9a5aae59c9ce4b254782d42d136120e3a6101a7a..897ea90a62f2e875ba037a799ccb639ede47c1d4 100644
--- a/ghc/tests/typecheck/should_fail/tcfail046.stderr
+++ b/ghc/tests/typecheck/should_fail/tcfail046.stderr
@@ -1,14 +1,14 @@
  
-tcfail046.hs:4: No instance for: `PrelBase.Eq (Process a)'
-    When deriving classes for `Continuation'
- 
-tcfail046.hs:4: No instance for: `PrelBase.Eq (Process a)'
+tcfail046.hs:4: No instance for: `Eq (Process a)'
     When deriving classes for `Message'
  
-tcfail046.hs:4: No instance for: `PrelBase.Eq (Process a)'
+tcfail046.hs:4: No instance for: `Eq (Process a)'
     When deriving classes for `Continuation'
  
-tcfail046.hs:4: No instance for: `PrelBase.Eq (Process a)'
+tcfail046.hs:4: No instance for: `Eq (Process a)'
     When deriving classes for `Message'
+ 
+tcfail046.hs:4: No instance for: `Eq (Process a)'
+    When deriving classes for `Continuation'
 
 Compilation had errors
diff --git a/ghc/tests/typecheck/should_fail/tcfail047.hs b/ghc/tests/typecheck/should_fail/tcfail047.hs
index 12770a33eb2fbc8de61354bb27bb672b5e20bb1d..f3cdb19741cbd7180e2b8a71c5e722cd24fe0aad 100644
--- a/ghc/tests/typecheck/should_fail/tcfail047.hs
+++ b/ghc/tests/typecheck/should_fail/tcfail047.hs
@@ -1,3 +1,4 @@
+module ShouldFail where
 
 class A a where
  op1 :: a -> a
diff --git a/ghc/tests/typecheck/should_fail/tcfail047.stderr b/ghc/tests/typecheck/should_fail/tcfail047.stderr
index 1ef8be50e622b1bdf2313d55934d353fac92e25b..b95c59bd83e4f4d08e14d51255fd190f8f606b9d 100644
--- a/ghc/tests/typecheck/should_fail/tcfail047.stderr
+++ b/ghc/tests/typecheck/should_fail/tcfail047.stderr
@@ -1,8 +1,6 @@
  
-tcfail047.hs:6: The type
+tcfail047.hs:7: The type
 		    `(a, (b, c))'
 		cannot be used as an instance type
- 
-tcfail047.hs:2: Module Main must include a definition for `Main.main'
 
 Compilation had errors
diff --git a/ghc/tests/typecheck/should_fail/tcfail055.stderr b/ghc/tests/typecheck/should_fail/tcfail055.stderr
index c3987fb62a5cb4100759d7cebbfed0cad479c14f..623875c96f37c50011b64de72cb85b4c5bcd84b9 100644
--- a/ghc/tests/typecheck/should_fail/tcfail055.stderr
+++ b/ghc/tests/typecheck/should_fail/tcfail055.stderr
@@ -1,9 +1,7 @@
  
-tcfail055.hs:3: Couldn't match the type
-		    `PrelBase.Int' against `PrelBase.Float'
-    Expected: `PrelBase.Int'
-    Inferred: `PrelBase.Float'
-    In an expression with a type signature:
-	`x PrelBase.+ 1 :: PrelBase.Int'
+tcfail055.hs:3: Couldn't match the type `Int' against `Float'
+    Expected: `Int'
+    Inferred: `Float'
+    In an expression with a type signature: `x + 1 :: Int'
 
 Compilation had errors
diff --git a/ghc/tests/typecheck/should_fail/tcfail056.stderr b/ghc/tests/typecheck/should_fail/tcfail056.stderr
index 472e4252d1d1b77681725906d5638ae0a117f9a5..6349ccf18de2b9f7d3ae20610f3092f35a66ee6a 100644
--- a/ghc/tests/typecheck/should_fail/tcfail056.stderr
+++ b/ghc/tests/typecheck/should_fail/tcfail056.stderr
@@ -1,16 +1,16 @@
  
-tcfail056.hs:10: No explicit method nor default method for `PrelBase.=='
-		 in an instance declaration for `PrelBase.Eq'
+tcfail056.hs:10: Warning: no explicit method nor default method for `=='
+		 in an instance declaration for `Eq'
  
 tcfail056.hs:1: Duplicate or overlapping instance declarations
-    for `PrelBase.Eq Foo' at tcfail056.hs:6 and tcfail056.hs:10
+    for `Eq Foo' at tcfail056.hs:6 and tcfail056.hs:10
  
 tcfail056.hs:1: Duplicate or overlapping instance declarations
-    for `PrelBase.Eq Foo' at tcfail056.hs:6 and tcfail056.hs:10
+    for `Eq Foo' at tcfail056.hs:6 and tcfail056.hs:10
  
 tcfail056.hs:1: Duplicate or overlapping instance declarations
-    for `PrelBase.Eq Foo' at tcfail056.hs:6 and tcfail056.hs:10
+    for `Eq Foo' at tcfail056.hs:6 and tcfail056.hs:10
  
-tcfail056.hs:10: Class `PrelBase.Eq' does not have a method `<='
+tcfail056.hs:10: Class `Eq' does not have a method `<='
 
 Compilation had errors
diff --git a/ghc/tests/typecheck/should_fail/tcfail057.stderr b/ghc/tests/typecheck/should_fail/tcfail057.stderr
index afa37632e5e0a3c47c5acaae89000e4f3e00db1b..921a57283b023f8e7b31b6976f5ba163a0dc6d19 100644
--- a/ghc/tests/typecheck/should_fail/tcfail057.stderr
+++ b/ghc/tests/typecheck/should_fail/tcfail057.stderr
@@ -1,4 +1,4 @@
  
-tcfail057.hs:5: Class used as a type constructor: `PrelNum.RealFrac'
+tcfail057.hs:5: Class used as a type constructor: `RealFrac'
 
 Compilation had errors
diff --git a/ghc/tests/typecheck/should_fail/tcfail058.stderr b/ghc/tests/typecheck/should_fail/tcfail058.stderr
index 89073edad220275c9437d57bb2bd6b0831b94889..36c71c8851d16414a33e7599456eb4a57fe81cbd 100644
--- a/ghc/tests/typecheck/should_fail/tcfail058.stderr
+++ b/ghc/tests/typecheck/should_fail/tcfail058.stderr
@@ -1,4 +1,4 @@
  
-tcfail058.hs:6: Type constructor used as a class: `ArrBase.Array'
+tcfail058.hs:6: Type constructor used as a class: `Array'
 
 Compilation had errors
diff --git a/ghc/tests/typecheck/should_fail/tcfail062.hs b/ghc/tests/typecheck/should_fail/tcfail062.hs
index 5c9b0ea2156b7d765f3d90ecd167d42341222829..b7391d692490c5540b05a5c775f09ce25caab916 100644
--- a/ghc/tests/typecheck/should_fail/tcfail062.hs
+++ b/ghc/tests/typecheck/should_fail/tcfail062.hs
@@ -1,6 +1,6 @@
 --!!! bug report from Satnam
 --
-module RubyAST
+module ShouldFail
 where
 
 type Module = (String,[Declaration])
diff --git a/ghc/tests/typecheck/should_fail/tcfail065.stderr b/ghc/tests/typecheck/should_fail/tcfail065.stderr
index 7e1ca9ba2d4dde053ca9d22acbc4e1d01d600116..1002a1d75521b9b7c22043f5dadae4787ee486f1 100644
--- a/ghc/tests/typecheck/should_fail/tcfail065.stderr
+++ b/ghc/tests/typecheck/should_fail/tcfail065.stderr
@@ -1,7 +1,7 @@
  
 tcfail065.hs:29: A type signature is more polymorphic than the inferred type
-		     Can't for-all the type variable(s) `taIg'
-		     in the inferred type `taIg -> X taIg -> X taIg'
+		     Can't for-all the type variable(s) `taKg'
+		     in the inferred type `taKg -> X taKg -> X taKg'
     When checking signature for `setX'
 
 Compilation had errors
diff --git a/ghc/tests/typecheck/should_fail/tcfail067.hs b/ghc/tests/typecheck/should_fail/tcfail067.hs
index 99d4c648c06a8f15ffae96d889d82cafff89ac40..db9cb9c40243d224a7fc81cbf056517d49efc370 100644
--- a/ghc/tests/typecheck/should_fail/tcfail067.hs
+++ b/ghc/tests/typecheck/should_fail/tcfail067.hs
@@ -1,4 +1,4 @@
-module SubRange where
+module ShouldFail where
 
 infixr 1 `rangeOf`
 
diff --git a/ghc/tests/typecheck/should_fail/tcfail067.stderr b/ghc/tests/typecheck/should_fail/tcfail067.stderr
index 8a61b7702c8fc12c8cb7d2093b529fea837ed6bb..d19c5eab4299cf0f966e131aefab87e70bfc8546 100644
--- a/ghc/tests/typecheck/should_fail/tcfail067.stderr
+++ b/ghc/tests/typecheck/should_fail/tcfail067.stderr
@@ -1,18 +1,18 @@
  
-tcfail067.hs:65: No explicit method nor default method for `PrelBase.abs'
-		 in an instance declaration for `PrelBase.Num'
+tcfail067.hs:65: Warning: no explicit method nor default method for `abs'
+		 in an instance declaration for `Num'
  
-tcfail067.hs:65: No explicit method nor default method for `PrelBase.signum'
-		 in an instance declaration for `PrelBase.Num'
+tcfail067.hs:65: Warning: no explicit method nor default method for `signum'
+		 in an instance declaration for `Num'
  
-tcfail067.hs:1: Context `{PrelBase.Ord ta174}'
+tcfail067.hs:1: Context `{Ord ta19s}'
 		    required by inferred type, but missing on a type signature
-		    `PrelBase.Ord ta174' arising from use of `SubRange' at tcfail067.hs:76
+		    `Ord ta19s' arising from use of `SubRange' at tcfail067.hs:76
     When checking signature(s) for: `numSubRangeBinOp'
  
-tcfail067.hs:65: Context `{PrelBase.Ord ta18F}'
+tcfail067.hs:65: Context `{Ord ta1aY}'
 		     required by inferred type, but missing on a type signature
-		     `PrelBase.Ord ta18F' arising from use of `numSubRangeNegate' at tcfail067.hs:61
+		     `Ord ta1aY' arising from use of `numSubRangeNegate' at tcfail067.hs:61
     When checking methods of an instance declaration
 
 Compilation had errors
diff --git a/ghc/tests/typecheck/should_fail/tcfail068.hs b/ghc/tests/typecheck/should_fail/tcfail068.hs
index d24354063458972e0c58712f70c11f9dace848f3..75e0125c7c487de3cf65ce01da3d1e8b914e76ef 100644
--- a/ghc/tests/typecheck/should_fail/tcfail068.hs
+++ b/ghc/tests/typecheck/should_fail/tcfail068.hs
@@ -1,9 +1,9 @@
 --!! Make sure that state threads don't escape
 --!! (example from Neil Ashton at York)
 --
-module IndTree(IndTree(..), itgen, itiap, itrap, itrapstate) where
+module ShouldFail where
 
-import GlaExts
+import MutableArray
 import ST
 
 type IndTree s t = MutableArray s (Int,Int) t
@@ -16,32 +16,32 @@ itgen n x =
 itiap :: Constructed a => (Int,Int) -> (a->a) -> IndTree s a -> IndTree s a
 itiap i f arr =
 	runST (
-	readArray arr i `thenStrictlyST` \val ->
-	writeArray arr i (f val) `seqStrictlyST`
-	returnStrictlyST arr)
+	readArray arr i >>= \val ->
+	writeArray arr i (f val) >>
+	return arr)
 
 itrap :: Constructed a => ((Int,Int),(Int,Int)) -> (a->a) -> IndTree s a -> IndTree s a
 itrap ((i,k),(j,l)) f arr = runST(itrap' i k)
 	where
-	itrap' i k = if k > l then returnStrictlyST arr
-		     else (itrapsnd i k `seqStrictlyST`
+	itrap' i k = if k > l then return arr
+		     else (itrapsnd i k >>
 			itrap' i (k+1))
-	itrapsnd i k = if i > j then returnStrictlyST arr
-                     else (readArray arr (i,k) `thenStrictlyST` \val ->
-		        writeArray arr (i,k) (f val) `seqStrictlyST`
+	itrapsnd i k = if i > j then return arr
+                     else (readArray arr (i,k) >>= \val ->
+		        writeArray arr (i,k) (f val) >>
 		        itrapsnd (i+1) k)
 
 itrapstate :: Constructed b => ((Int,Int),(Int,Int)) -> (a->b->(a,b)) -> ((Int,Int)->c->a) ->
 		(a->c) -> c -> IndTree s b -> (c, IndTree s b)
 itrapstate ((i,k),(j,l)) f c d s arr = runST(itrapstate' i k s)
 	where
-	itrapstate' i k s = if k > l then returnStrictlyST (s,arr)
-			    else (itrapstatesnd i k s `thenStrictlyST` \(s,arr) ->
+	itrapstate' i k s = if k > l then return (s,arr)
+			    else (itrapstatesnd i k s >>= \(s,arr) ->
 				itrapstate' i (k+1) s)
-	itrapstatesnd i k s = if i > j then returnStrictlyST (s,arr)
-                            else (readArray arr (i,k) `thenStrictlyST` \val ->
+	itrapstatesnd i k s = if i > j then return (s,arr)
+                            else (readArray arr (i,k) >>= \val ->
 		               let (newstate, newval) = f (c (i,k) s) val
-		               in writeArray arr (i,k) newval `seqStrictlyST`
+		               in writeArray arr (i,k) newval >>
 		               itrapstatesnd (i+1) k (d newstate))
 
 -- stuff from Auxiliary: copied here (partain)
@@ -65,8 +65,6 @@ nonempty (_:_) = True
 compose :: [a->a] -> a -> a
 compose = foldr (.) id
 
-data Maybe t = Just t | Nothing
-
 class Constructed a where
    normal :: a -> Bool
 
diff --git a/ghc/tests/typecheck/should_fail/tcfail068.stderr b/ghc/tests/typecheck/should_fail/tcfail068.stderr
index d69518f45ea3699f13b7c477b211c450d1a3ccc6..ffaed805ea3771fcdd94f473c237c5a5deb0d4c6 100644
--- a/ghc/tests/typecheck/should_fail/tcfail068.stderr
+++ b/ghc/tests/typecheck/should_fail/tcfail068.stderr
@@ -1,43 +1,73 @@
  
-tcfail068.hs:4:
-    Conflicting definitions for: `Just'
-	Imported from Prelude at tcfail068.hs:4
-	Defined at tcfail068.hs:68
- 
-tcfail068.hs:4:
-    Conflicting definitions for: `Nothing'
-	Imported from Prelude at tcfail068.hs:4
-	Defined at tcfail068.hs:70
- 
-tcfail068.hs:4:
-    Conflicting definitions for: `Maybe'
-	Imported from Prelude at tcfail068.hs:4
-	Defined at tcfail068.hs:68
- 
-tcfail068.hs:19: Value not in scope: `returnStrictlyST'
- 
-tcfail068.hs:19: Value not in scope: `seqStrictlyST'
- 
-tcfail068.hs:21: Value not in scope: `thenStrictlyST'
- 
-tcfail068.hs:26: Value not in scope: `returnStrictlyST'
- 
-tcfail068.hs:26: Value not in scope: `seqStrictlyST'
- 
-tcfail068.hs:29: Value not in scope: `returnStrictlyST'
- 
-tcfail068.hs:30: Value not in scope: `seqStrictlyST'
- 
-tcfail068.hs:29: Value not in scope: `thenStrictlyST'
- 
-tcfail068.hs:38: Value not in scope: `returnStrictlyST'
- 
-tcfail068.hs:38: Value not in scope: `thenStrictlyST'
- 
-tcfail068.hs:41: Value not in scope: `returnStrictlyST'
- 
-tcfail068.hs:42: Value not in scope: `seqStrictlyST'
- 
-tcfail068.hs:41: Value not in scope: `thenStrictlyST'
+tcfail068.hs:45: A type signature is more polymorphic than the inferred type
+		     Can't for-all the type variable(s) `ta16y'
+		     in the inferred type `ST ta16y (ta16r, IndTree ta16y ta16o)'
+    In a polymorphic function argument `(itrapstate' i k s)'
+    In the first argument of `runST', namely `(itrapstate' i k s)'
+    In an equation for function `itrapstate':
+	`itrapstate ((i, k), (j, l)) f c d s arr
+		    = runST (itrapstate' i k s)
+		    where
+			itrapstatesnd i k s
+				      = if i > j then
+					    return (s, (arr))
+					else
+					    ((readArray arr (i, (k)))
+					     >>= (\ val
+						    -> let (newstate, newval) = f (c (i, (k)) s) val
+						       in
+							 (writeArray arr (i, (k)) newval)
+							 >> (itrapstatesnd (i + 1) k (d newstate))))
+			itrapstate' i k s
+				    = if k > l then
+					  return (s, (arr))
+				      else
+					  ((itrapstatesnd i k s)
+					   >>= (\ (s, arr) -> itrapstate' i (k + 1) s))'
+ 
+tcfail068.hs:32: A type signature is more polymorphic than the inferred type
+		     Can't for-all the type variable(s) `ta19A'
+		     in the inferred type `ST ta19A (IndTree ta19A ta19x)'
+    In a polymorphic function argument `(itrap' i k)'
+    In the first argument of `runST', namely `(itrap' i k)'
+    In an equation for function `itrap':
+	`itrap ((i, k), (j, l)) f arr
+	       = runST (itrap' i k)
+	       where
+		   itrapsnd i k
+			    = if i > j then
+				  return arr
+			      else
+				  ((readArray arr (i, (k)))
+				   >>= (\ val
+					  -> (writeArray arr (i, (k)) (f val))
+					     >> (itrapsnd (i + 1) k)))
+		   itrap' i k
+			  = if k > l then
+				return arr
+			    else
+				((itrapsnd i k) >> (itrap' i (k + 1)))'
+ 
+tcfail068.hs:21: A type signature is more polymorphic than the inferred type
+		     Can't for-all the type variable(s) `ta1bT'
+		     in the inferred type `ST ta1bT (IndTree ta1bT ta1bE)'
+    In a polymorphic function argument `((readArray arr i)
+					 >>= (\ val -> (writeArray arr i (f val)) >> (return arr)))'
+    In the first argument of `runST', namely
+	`((readArray arr i)
+	  >>= (\ val -> (writeArray arr i (f val)) >> (return arr)))'
+    In an equation for function `itiap':
+	`itiap i f arr
+	       = runST ((readArray arr i)
+			>>= (\ val -> (writeArray arr i (f val)) >> (return arr)))'
+ 
+tcfail068.hs:14: A type signature is more polymorphic than the inferred type
+		     Can't for-all the type variable(s) `ta1cM'
+		     in the inferred type `ST ta1cM (IndTree ta1cM ta1cF)'
+    In a polymorphic function argument `(newArray ((1, (1)), (n)) x)'
+    In the first argument of `runST', namely
+	`(newArray ((1, (1)), (n)) x)'
+    In an equation for function `itgen':
+	`itgen n x = runST (newArray ((1, (1)), (n)) x)'
 
 Compilation had errors
diff --git a/ghc/tests/typecheck/should_fail/tcfail069.hs b/ghc/tests/typecheck/should_fail/tcfail069.hs
index 73dd738549470d2a7e1daf16161a8bae0ae7e9e1..63684fa9db3c10ded4274a8013b6760cb4b620da 100644
--- a/ghc/tests/typecheck/should_fail/tcfail069.hs
+++ b/ghc/tests/typecheck/should_fail/tcfail069.hs
@@ -13,7 +13,7 @@ error recovery mechanism.
 
 -}
 
-module Too_Kuch( too_much ) where
+module ShouldFail where
 
 too_much :: [Int] -> [(Int,Int)] -> [(Int,[Int])] -> Bool
 too_much ds ((k,m):q1) s0
diff --git a/ghc/tests/typecheck/should_fail/tcfail069.stderr b/ghc/tests/typecheck/should_fail/tcfail069.stderr
index 290c0099447b8f7cf0f8d82bbaf96676eac56c28..0a081e9a215c01072fce9503d6324446d7b340b3 100644
--- a/ghc/tests/typecheck/should_fail/tcfail069.stderr
+++ b/ghc/tests/typecheck/should_fail/tcfail069.stderr
@@ -1,14 +1,12 @@
  
-tcfail069.hs:21: Couldn't match the type
-		     `PrelTup.(,) taCp' against `PrelBase.[]'
-    Expected: `[taCt]'
-    Inferred: `([PrelBase.Int], [PrelBase.Int])'
-    In a "case" branch: `PrelBase.[]' -> `IOBase.error "foo"'
-    In the case expression
-	`case (list1, (list2)) of PrelBase.[] -> IOBase.error "foo"'
+tcfail069.hs:21: Couldn't match the type `(,) taAJ' against `[]'
+    Expected: `[taAN]'
+    Inferred: `([Int], [Int])'
+    In a "case" branch: `[]' -> `error "foo"'
+    In the case expression `case (list1, (list2)) of [] -> error "foo"'
     In an equation for function `too_much':
-	`too_much ds ((k, m) PrelBase.: q1) s0
-		  = case (list1, (list2)) of PrelBase.[] -> IOBase.error "foo"
+	`too_much ds ((k, m) : q1) s0
+		  = case (list1, (list2)) of [] -> error "foo"
 		  where
 		      list2 = ds
 		      list1 = ds'
diff --git a/ghc/tests/typecheck/should_fail/tcfail070.stderr b/ghc/tests/typecheck/should_fail/tcfail070.stderr
index 13ee2e207e8e5538be55e5da331577b50f390891..a332f23b0ef1dcbccc651a90a21241661f6f8ceb 100644
--- a/ghc/tests/typecheck/should_fail/tcfail070.stderr
+++ b/ghc/tests/typecheck/should_fail/tcfail070.stderr
@@ -1,6 +1,6 @@
  
-tcfail070.hs:13: Couldn't match the kind `*' against `* -> ka1936'
-    When unifying two kinds `*' and `* -> ka1936'
+tcfail070.hs:13: Couldn't match the kind `*' against `* -> ka1998'
+    When unifying two kinds `*' and `* -> ka1998'
     In the type declaration for `State'
 
 Compilation had errors
diff --git a/ghc/tests/typecheck/should_fail/tcfail071.hs b/ghc/tests/typecheck/should_fail/tcfail071.hs
index 49587286b998ba457e3adf94f0a8a7623bde9eab..9aa6f0730a9a45291bfa1c39bd3f3c796545549f 100644
--- a/ghc/tests/typecheck/should_fail/tcfail071.hs
+++ b/ghc/tests/typecheck/should_fail/tcfail071.hs
@@ -1,6 +1,6 @@
 --!!! Mis-matched contexts in a mutually recursive group
 
-module Foo7( f ) where
+module ShouldFail where
 
 f :: (Ord c) => c -> c
 f c = g c
diff --git a/ghc/tests/typecheck/should_fail/tcfail071.stderr b/ghc/tests/typecheck/should_fail/tcfail071.stderr
index 9681c40d3e7b8fbfb68ce02de44c2495f1ce7d24..e36f4466a58777db9b9d87e5d34952370a1f5ad7 100644
--- a/ghc/tests/typecheck/should_fail/tcfail071.stderr
+++ b/ghc/tests/typecheck/should_fail/tcfail071.stderr
@@ -1,15 +1,11 @@
  
 tcfail071.hs:10: Couldn't match the signature/existential type variable
-		     `taD0' with the type `taDe -> taDb -> taDb'
-    Expected: `taD0'
-    Inferred: `taDe -> taDb -> taDb'
-    In a pattern binding:
-	`p = PrelBase.foldr (f c) PrelBase.[] PrelBase.[]'
-    In an equation for function `g':
-	`g c
-	   = c
-	   where
-	       p = PrelBase.foldr (f c) PrelBase.[] PrelBase.[]'
+		     `taEm' with the type `taEz -> taEw -> taEw'
+    Expected: `taEm'
+    Inferred: `taEz -> taEw -> taEw'
+    In the first argument of `f', namely `c'
+    In the first argument of `foldr', namely `(f c)'
+    In a pattern binding: `p = foldr (f c) [] []'
  
 tcfail071.hs:8: Mismatched contexts
     When matching the contexts of the signatures for `f' and `g'
diff --git a/ghc/tests/typecheck/should_fail/tcfail072.hs b/ghc/tests/typecheck/should_fail/tcfail072.hs
index f7f57a76f4ed50ae2dbc81ebf454216833b2802a..501976e5bef125a265b08f426e3c62a8de0b2545 100644
--- a/ghc/tests/typecheck/should_fail/tcfail072.hs
+++ b/ghc/tests/typecheck/should_fail/tcfail072.hs
@@ -14,7 +14,7 @@
   local binds for:
 -}
 
-module Tmp( g ) where
+module ShouldFail where
 
 data AB p q = A
             | B p q
diff --git a/ghc/tests/typecheck/should_fail/tcfail072.stderr b/ghc/tests/typecheck/should_fail/tcfail072.stderr
index 08d5d5a87fa3230817ec8e36a2580cda22fb9123..208259aeedd49c687f812a979b80c9ee8a7d4eb7 100644
--- a/ghc/tests/typecheck/should_fail/tcfail072.stderr
+++ b/ghc/tests/typecheck/should_fail/tcfail072.stderr
@@ -1,6 +1,6 @@
  
-tcfail072.hs:17: Ambiguous context `{PrelBase.Ord taDn}'
-		     `PrelBase.Ord taDn' arising from use of `g' at tcfail072.hs:23
+tcfail072.hs:17: Ambiguous context `{Ord taEJ}'
+		     `Ord taEJ' arising from use of `g' at tcfail072.hs:23
     When checking signature(s) for: `g'
 
 Compilation had errors
diff --git a/ghc/tests/typecheck/should_fail/tcfail073.hs b/ghc/tests/typecheck/should_fail/tcfail073.hs
index 00a06cbecef608f66880ecb52d94b0c2a9d33a57..4a269108fe46482d89897a482c51e07697af0b28 100644
--- a/ghc/tests/typecheck/should_fail/tcfail073.hs
+++ b/ghc/tests/typecheck/should_fail/tcfail073.hs
@@ -1,6 +1,6 @@
--- what error do you get if you redefined PreludeCore instances?
+-- what error do you get if you redefined Prelude instances?
 
-module Test where
+module ShouldFail where
 
 f x@(a,b) y@(c,d) = x == y
 
diff --git a/ghc/tests/typecheck/should_fail/tcfail073.stderr b/ghc/tests/typecheck/should_fail/tcfail073.stderr
index 3c43c914c32c543f2da9f1773defcab1f30408c3..01d7d68eb03484468810f60a3a2f93b79024a219 100644
--- a/ghc/tests/typecheck/should_fail/tcfail073.stderr
+++ b/ghc/tests/typecheck/should_fail/tcfail073.stderr
@@ -1,16 +1,16 @@
  
 tcfail073.hs:3: Duplicate or overlapping instance declarations
-    for `PrelBase.Eq (a, b)' at tcfail073.hs:8 and <NoSrcLoc>
+    for `Eq (a, b)' at tcfail073.hs:8 and <NoSrcLoc>
  
 tcfail073.hs:3: Duplicate or overlapping instance declarations
-    for `PrelBase.Eq (a, b)' at tcfail073.hs:8 and <NoSrcLoc>
+    for `Eq (a, b)' at tcfail073.hs:8 and <NoSrcLoc>
  
 tcfail073.hs:3: Duplicate or overlapping instance declarations
-    for `PrelBase.Eq (a, b)' at tcfail073.hs:8 and <NoSrcLoc>
+    for `Eq (a, b)' at tcfail073.hs:8 and <NoSrcLoc>
  
-tcfail073.hs:8: Context `{PrelBase.Eq taR4}'
+tcfail073.hs:8: Context `{Eq taTH}'
 		    required by inferred type, but missing on a type signature
-		    `PrelBase.Eq taR4' arising from use of `PrelBase.==' at tcfail073.hs:8
+		    `Eq taTH' arising from use of `==' at tcfail073.hs:8
     When checking methods of an instance declaration
 
 Compilation had errors
diff --git a/ghc/tests/typecheck/should_fail/tcfail075.hs b/ghc/tests/typecheck/should_fail/tcfail075.hs
index 42f7c7572e14a099c93dca3b9fd39813d8759228..202c6aa539ffbf88a47abf24b0dce29d9dbef17d 100644
--- a/ghc/tests/typecheck/should_fail/tcfail075.hs
+++ b/ghc/tests/typecheck/should_fail/tcfail075.hs
@@ -2,7 +2,7 @@
 
 {-# OPTIONS -fglasgow-exts #-}
 
-module Main where
+module ShouldFail where
 
 x = 1#
 
diff --git a/ghc/tests/typecheck/should_fail/tcfail076.hs b/ghc/tests/typecheck/should_fail/tcfail076.hs
index 7e0b45ae64a1a9a25a17cad3d9f178e89d6d1357..08f775b8ca93e8d39687faaa6833a709acb9380f 100644
--- a/ghc/tests/typecheck/should_fail/tcfail076.hs
+++ b/ghc/tests/typecheck/should_fail/tcfail076.hs
@@ -9,10 +9,9 @@ Needless to say that it uses some of GHC's arcane type extensions.
 
 {-# OPTIONS -fglasgow-exts #-}
 
-module Test			(  module Test  )
-where
+module ShouldFail where
 
-import GlaExts
+import GHC ( All )
 
 data ContT m a		=  KContT ((All res) => (a -> m res) -> m res)
 unKContT (KContT x)	=  x
diff --git a/ghc/tests/typecheck/should_fail/tcfail076.stderr b/ghc/tests/typecheck/should_fail/tcfail076.stderr
index f0df2765fe3d94c3abd2b0e0ef15c402e6c5bc12..641470a3bc214a7259936c948536379b7bb5b78d 100644
--- a/ghc/tests/typecheck/should_fail/tcfail076.stderr
+++ b/ghc/tests/typecheck/should_fail/tcfail076.stderr
@@ -1,11 +1,12 @@
  
-tcfail076.hs:21: A type signature is more polymorphic than the inferred type
-		     Can't for-all the type variable(s) `taCl'
-		     in the inferred type `(taCb -> aaCa taCl) -> aaCa taCl'
+tcfail076.hs:20: A type signature is more polymorphic than the inferred type
+		     Can't for-all the type variable(s) `taEJ'
+		     in the inferred type `(taEz -> aaEy taEJ) -> aaEy taEJ'
     In a polymorphic function argument `(\ cont' -> cont a)'
-    In an equation for function `callcc':
-	`callcc f
-		= KContT (\ cont
-			    -> unKContT (f (\ a -> KContT (\ cont' -> cont a))) cont)'
+    In the first argument of `KContT', namely `(\ cont' -> cont a)'
+    In the first argument of `f', namely
+	`(\ a -> KContT (\ cont' -> cont a))'
+    In the first argument of `unKContT', namely
+	`(f (\ a -> KContT (\ cont' -> cont a)))'
 
 Compilation had errors