diff --git a/ghc/tests/ccall/should_compile/cc006.hs b/ghc/tests/ccall/should_compile/cc006.hs
index 374010792b24674c69d3848ed52ce3c5f4da352b..ede31d75da15e59310208e2177d326dd3a8ef62c 100644
--- a/ghc/tests/ccall/should_compile/cc006.hs
+++ b/ghc/tests/ccall/should_compile/cc006.hs
@@ -1,6 +1,6 @@
 -- !!! cc006 -- ccall with non-standard boxed arguments and results
 
-module Test where
+module ShouldCompile where
 
 import Foreign
 import CCall
diff --git a/ghc/tests/ccall/should_compile/cc007.hs b/ghc/tests/ccall/should_compile/cc007.hs
index b1528b49c0e04d5f2255dbbb3efb4ed906e87699..70a15f272583fa90c0f758906d8cf5617f5593cd 100644
--- a/ghc/tests/ccall/should_compile/cc007.hs
+++ b/ghc/tests/ccall/should_compile/cc007.hs
@@ -1,4 +1,4 @@
 -- !!! cc007 -- foreign import with external name equal to Haskell name.
-module Test where
+module ShouldCompile where
 
 foreign import sine :: Double -> Double
diff --git a/ghc/tests/ccall/should_compile/cc008.hs b/ghc/tests/ccall/should_compile/cc008.hs
index 6e141f49b5a4029b7f1bae36ca191f356f9c60f5..b6725e3de870aec6258584cd767fb9b95c7ddb38 100644
--- a/ghc/tests/ccall/should_compile/cc008.hs
+++ b/ghc/tests/ccall/should_compile/cc008.hs
@@ -1,5 +1,5 @@
 -- !!! cc008 -- foreign export dynamic returning newtype of Addr
-module Test where
+module ShouldCompile where
 
 import Addr
 
diff --git a/ghc/tests/ccall/should_compile/cc009.hs b/ghc/tests/ccall/should_compile/cc009.hs
index 959ebea9a2e280e126703813c87760f1cc82d5cc..6a6ebca9e774493dd4981434ff56f1b75888c3cf 100644
--- a/ghc/tests/ccall/should_compile/cc009.hs
+++ b/ghc/tests/ccall/should_compile/cc009.hs
@@ -1,5 +1,5 @@
 -- !!! cc009 -- foreign label returning newtype of Addr
-module Test where
+module ShouldCompile where
 
 import Addr
 
diff --git a/ghc/tests/codeGen/should_run/Makefile b/ghc/tests/codeGen/should_run/Makefile
index 73d44ab1e63a5a0c8c43422cc19f43fe903b3076..d9b7a9f145268eb7b1ed3cee34a0f32255de641f 100644
--- a/ghc/tests/codeGen/should_run/Makefile
+++ b/ghc/tests/codeGen/should_run/Makefile
@@ -1,5 +1,5 @@
 #-----------------------------------------------------------------------------
-# $Id: Makefile,v 1.14 2000/08/22 14:05:05 sewardj Exp $
+# $Id: Makefile,v 1.15 2000/11/03 16:23:37 simonmar Exp $
 
 TOP = ../..
 include $(TOP)/mk/boilerplate.mk
@@ -39,7 +39,6 @@ SRC_MKDEPENDHS_OPTS += -fglasgow-exts
 
 .PRECIOUS: %.bin %.o
 
-clean ::
-	rm -f *.bin *.o
+CLEAN_FILES += PrelMain.hi
 
 include $(TOP)/mk/target.mk
diff --git a/ghc/tests/concurrent/should_run/Makefile b/ghc/tests/concurrent/should_run/Makefile
index b17dea19ec406b3c7c1f3422be064b75b9da0388..6b0271dd5af7d6e0ac80b4d32c10f02301e1a0c2 100644
--- a/ghc/tests/concurrent/should_run/Makefile
+++ b/ghc/tests/concurrent/should_run/Makefile
@@ -1,5 +1,5 @@
 #-----------------------------------------------------------------------------
-# $Id: Makefile,v 1.8 2000/06/12 17:01:57 panne Exp $
+# $Id: Makefile,v 1.9 2000/11/03 16:23:37 simonmar Exp $
 
 TOP = ../..
 include $(TOP)/mk/boilerplate.mk
@@ -16,4 +16,6 @@ conc021_RUNTEST_OPTS = -x 250
 
 SRC_HC_OPTS += -dcore-lint -package concurrent -fglasgow-exts
 
+CLEAN_FILES += PrelMain.hi
+
 include $(TOP)/mk/target.mk
diff --git a/ghc/tests/deSugar/should_compile/ds-wildcard.hs b/ghc/tests/deSugar/should_compile/ds-wildcard.hs
index 24c5b3b91b344373de24dd6562fe73ea39d9ef77..dae882c32b1419f448e7eed6db27e2a98ed50fa4 100644
--- a/ghc/tests/deSugar/should_compile/ds-wildcard.hs
+++ b/ghc/tests/deSugar/should_compile/ds-wildcard.hs
@@ -1,3 +1,3 @@
-module ShouldSucceed where
+module ShouldCompile where
 
 x@_ = x
diff --git a/ghc/tests/deSugar/should_compile/ds001.hs b/ghc/tests/deSugar/should_compile/ds001.hs
index a62c7b4205253a7727b36c2d51e93495bafccbed..d3f0b60f5618cd73253c6b0471af0b8f6c2392db 100644
--- a/ghc/tests/deSugar/should_compile/ds001.hs
+++ b/ghc/tests/deSugar/should_compile/ds001.hs
@@ -2,7 +2,7 @@
 --
 -- this tests ultra-simple function and pattern bindings (no patterns)
 
-module Test where
+module ShouldCompile where
 
 -- simple function bindings
 
diff --git a/ghc/tests/deSugar/should_compile/ds002.hs b/ghc/tests/deSugar/should_compile/ds002.hs
index a63de9423342bc9ac8fb12e1993737df3f602eb6..280674e1fe1a2046ca92bf96225102e02c2f8f47 100644
--- a/ghc/tests/deSugar/should_compile/ds002.hs
+++ b/ghc/tests/deSugar/should_compile/ds002.hs
@@ -2,7 +2,7 @@
 --
 -- this tests "overlapping" variables and guards
 
-module Test where
+module ShouldCompile where
 
 f x = x
 f y = y
diff --git a/ghc/tests/deSugar/should_compile/ds003.hs b/ghc/tests/deSugar/should_compile/ds003.hs
index 0faff0e8da1e62bf596ef13c341c302f472ead18..dafeac94b74cfda0451ea613fe669663a82ad6cf 100644
--- a/ghc/tests/deSugar/should_compile/ds003.hs
+++ b/ghc/tests/deSugar/should_compile/ds003.hs
@@ -1,6 +1,6 @@
 -- !!! ds003 -- list, tuple, lazy, as patterns
 --
-module Test where
+module ShouldCompile where
 
 f []		y	 True  = []
 f x		a@(y,ys) ~z    = []
diff --git a/ghc/tests/deSugar/should_compile/ds004.hs b/ghc/tests/deSugar/should_compile/ds004.hs
index cd89e1822d5175eb05e3276f88dffd14bf8532ae..ebbe8e06c227d1a4995e85a0212366ddd9422698 100644
--- a/ghc/tests/deSugar/should_compile/ds004.hs
+++ b/ghc/tests/deSugar/should_compile/ds004.hs
@@ -1,6 +1,6 @@
 -- !!! ds004 -- nodups from SLPJ p 79
 --
-module Test where
+module ShouldCompile where
 
 -- SLPJ, p 79
 nodups []                   = []
diff --git a/ghc/tests/deSugar/should_compile/ds005.hs b/ghc/tests/deSugar/should_compile/ds005.hs
index 6fca84b10b59951c64023542a473fb2d35b7a267..a02e8d9c1dd713d431db3f5586bb77a49390852d 100644
--- a/ghc/tests/deSugar/should_compile/ds005.hs
+++ b/ghc/tests/deSugar/should_compile/ds005.hs
@@ -2,7 +2,7 @@
 --
 -- this simply tests a "typical" example
 
-module MapPairs where
+module ShouldCompile where
 
 -- from SLPJ, p 78
 mappairs f []     ys     = []
diff --git a/ghc/tests/deSugar/should_compile/ds006.hs b/ghc/tests/deSugar/should_compile/ds006.hs
index ba05547920f2d5ef1aa610ceba32a77df5bf1f1b..d66e7c17e8a56a0b2022ba79a66a7e9d23c5fac1 100644
--- a/ghc/tests/deSugar/should_compile/ds006.hs
+++ b/ghc/tests/deSugar/should_compile/ds006.hs
@@ -1,6 +1,6 @@
 -- !!! ds006 -- v | True = v+1 | False = v (dead code elim)
 --
-module Test where
+module ShouldCompile where
 
 v | True  = v + 1
   | False = v
diff --git a/ghc/tests/deSugar/should_compile/ds007.hs b/ghc/tests/deSugar/should_compile/ds007.hs
index dd0fcd50ebaa033032f30b2e0889e829f3760e67..ae12cf7a8cf88fb468a4496169f6093884639f57 100644
--- a/ghc/tests/deSugar/should_compile/ds007.hs
+++ b/ghc/tests/deSugar/should_compile/ds007.hs
@@ -1,6 +1,6 @@
 -- !!! ds007 -- simple local bindings
 
-module ShouldSucceed where
+module ShouldCompile where
 
 w = a where a = y
             y = []
diff --git a/ghc/tests/deSugar/should_compile/ds008.hs b/ghc/tests/deSugar/should_compile/ds008.hs
index a97470d99e2db5b9005e4a40878c86eda6ab2899..73707ed5659d22a5ccda3e2e7b9d8b162f6ad5e7 100644
--- a/ghc/tests/deSugar/should_compile/ds008.hs
+++ b/ghc/tests/deSugar/should_compile/ds008.hs
@@ -2,7 +2,7 @@
 --
 -- these tests involve way-cool TyApps
 
-module Test where
+module ShouldCompile where
 
 f x = []
 
diff --git a/ghc/tests/deSugar/should_compile/ds009.hs b/ghc/tests/deSugar/should_compile/ds009.hs
index ba205562ad8008a273fc282cf39adb5a8be02109..6ebcc96adfb67e6459f0b25d7105a6a3788b9c91 100644
--- a/ghc/tests/deSugar/should_compile/ds009.hs
+++ b/ghc/tests/deSugar/should_compile/ds009.hs
@@ -1,6 +1,6 @@
 -- !!! ds009 -- simple list comprehensions
 
-module SimpleListComp where
+module ShouldCompile where
 
 f xs = [ x | x <- xs ]
 
diff --git a/ghc/tests/deSugar/should_compile/ds010.hs b/ghc/tests/deSugar/should_compile/ds010.hs
index abf6fa1b3e06385fcbfd2a50cfaa455224d0e867..268610e124ee2762148c6250d3ec8b97f9af70dd 100644
--- a/ghc/tests/deSugar/should_compile/ds010.hs
+++ b/ghc/tests/deSugar/should_compile/ds010.hs
@@ -1,6 +1,6 @@
 -- !!! ds010 -- deeply-nested list comprehensions
 
-module Test where
+module ShouldCompile where
 
 z = [ (a,b,c,d,e,f,g,h,i,j) | a <- "12",
 			      b <- "12",
diff --git a/ghc/tests/deSugar/should_compile/ds011.hs b/ghc/tests/deSugar/should_compile/ds011.hs
index f9dc13d49a15dbb1a87872f8aecd27773c52ab81..dab482ff0433608f6352e8fc6ab29a7297fcf6ca 100644
--- a/ghc/tests/deSugar/should_compile/ds011.hs
+++ b/ghc/tests/deSugar/should_compile/ds011.hs
@@ -1,6 +1,6 @@
 -- !!! ds011 -- uses of "error"
 
-module Tests where
+module ShouldCompile where
 
 f = error []
 
diff --git a/ghc/tests/deSugar/should_compile/ds012.hs b/ghc/tests/deSugar/should_compile/ds012.hs
index 8870881441cb2ffd00421ec4888487eec958f626..4ef9d8cc1d4c8b4712aeb553704c8fb14e0dbb17 100644
--- a/ghc/tests/deSugar/should_compile/ds012.hs
+++ b/ghc/tests/deSugar/should_compile/ds012.hs
@@ -1,6 +1,6 @@
 -- !!! ds012 -- simple Integer arithmetic
 --
-module Tests where
+module ShouldCompile where
 
 f x = 1 + 2 - 3 + 4 * 5
 
diff --git a/ghc/tests/deSugar/should_compile/ds013.hs b/ghc/tests/deSugar/should_compile/ds013.hs
index da7267d761aa6e30b43d45a1a7ff8c05e7953143..3fb55ab47c7779f7c2a0ab60fa7c20e7f5114583 100644
--- a/ghc/tests/deSugar/should_compile/ds013.hs
+++ b/ghc/tests/deSugar/should_compile/ds013.hs
@@ -1,6 +1,6 @@
 -- !!! ds013 -- simple Rational arithmetic
 
-module Tests where
+module ShouldCompile where
 
 f = 1.5 + 2.0 - 3.14159265 + 4.2 * 5.111111111111111111111111111
 
diff --git a/ghc/tests/deSugar/should_compile/ds014.hs b/ghc/tests/deSugar/should_compile/ds014.hs
index 8770cb7814436c27749c17a8d970ad541cad5332..23b37098540199a04dd03f148f14d4adcf486e1d 100644
--- a/ghc/tests/deSugar/should_compile/ds014.hs
+++ b/ghc/tests/deSugar/should_compile/ds014.hs
@@ -1,7 +1,7 @@
 -- !!! ds014 -- character and string literals
 -- !!!   really should add ALL weird forms...
 
-module Tests where
+module ShouldCompile where
 
 a = 'a'
 b = "b"
diff --git a/ghc/tests/deSugar/should_compile/ds015.hs b/ghc/tests/deSugar/should_compile/ds015.hs
index b14cc6e5267a1bd60a3a137a87f3eaf23fd3fd61..24645778eed1df08a318178b1bb1a29cf223f18c 100644
--- a/ghc/tests/deSugar/should_compile/ds015.hs
+++ b/ghc/tests/deSugar/should_compile/ds015.hs
@@ -1,6 +1,6 @@
 -- !!! ds015 -- lambdas
 --
-module Tests where
+module ShouldCompile where
 
 f x = ( \ x -> x ) x
 
diff --git a/ghc/tests/deSugar/should_compile/ds016.hs b/ghc/tests/deSugar/should_compile/ds016.hs
index 370c37eaf832078745f69cabaf0cc13c7bec1aa1..41394e7ed9625337dbf5a2e8a5dd7a5770708779 100644
--- a/ghc/tests/deSugar/should_compile/ds016.hs
+++ b/ghc/tests/deSugar/should_compile/ds016.hs
@@ -1,6 +1,6 @@
 -- !!! ds016 -- case expressions
 --
-module Tests where
+module ShouldCompile where
 
 f x y z =
     case ( x ++ x ++ x ++ x ++ x ) of
diff --git a/ghc/tests/deSugar/should_compile/ds017.hs b/ghc/tests/deSugar/should_compile/ds017.hs
index 20092448d73d87e13e019b7772b71d53276b9a35..e6fd6d02f9e407ce02e1e553d820c5622281f384 100644
--- a/ghc/tests/deSugar/should_compile/ds017.hs
+++ b/ghc/tests/deSugar/should_compile/ds017.hs
@@ -1,6 +1,6 @@
 -- !!! ds017 -- let expressions
 --
-module Tests where
+module ShouldCompile where
 
 f x y z
   = let
diff --git a/ghc/tests/deSugar/should_compile/ds018.hs b/ghc/tests/deSugar/should_compile/ds018.hs
index 00098bd05c0c5361d456b66a98cd20e47965ae13..b521bada378ce5b46f90e87cdfe80fa328391b21 100644
--- a/ghc/tests/deSugar/should_compile/ds018.hs
+++ b/ghc/tests/deSugar/should_compile/ds018.hs
@@ -1,6 +1,6 @@
 -- !!! ds018 -- explicit lists and tuples
 --
-module Tests where
+module ShouldCompile where
 
 -- exprs
 
diff --git a/ghc/tests/deSugar/should_compile/ds019.hs b/ghc/tests/deSugar/should_compile/ds019.hs
index 8056a5470e26c961cdc631fbf08d04becdb2caf5..6bcf43f0ce01357195176903453a5a4499554de7 100644
--- a/ghc/tests/deSugar/should_compile/ds019.hs
+++ b/ghc/tests/deSugar/should_compile/ds019.hs
@@ -1,6 +1,6 @@
 -- !!! ds019 -- mixed var and uni-constructor pats
 
-module Test where
+module ShouldCompile where
 
 f (a,b,c) i     o = []
 f d       (j,k) p = []
diff --git a/ghc/tests/deSugar/should_compile/ds020.hs b/ghc/tests/deSugar/should_compile/ds020.hs
index 86ffff16e87388ce7a0698c6840c8a35fa7342fc..479d57ac4e3adcb1c139b75caae07f0d78e9acb6 100644
--- a/ghc/tests/deSugar/should_compile/ds020.hs
+++ b/ghc/tests/deSugar/should_compile/ds020.hs
@@ -1,6 +1,6 @@
 -- !!! ds020 -- lazy patterns (in detail)
 --
-module Test where
+module ShouldCompile where
 
 a ~([],[],[])    = []
 a ~(~[],~[],~[]) = []
diff --git a/ghc/tests/deSugar/should_compile/ds021.hs b/ghc/tests/deSugar/should_compile/ds021.hs
index 1f33591a055152a9191543db591db62632970a44..4faaba53fdfb2ebd1b1672118c84388c9fcd9e85 100644
--- a/ghc/tests/deSugar/should_compile/ds021.hs
+++ b/ghc/tests/deSugar/should_compile/ds021.hs
@@ -1,6 +1,6 @@
 -- !!! ds021 -- hairier uses of guards
 
-module Test where
+module ShouldCompile where
 
 f x y z | x == y     = []
 	| x /= z     = []
diff --git a/ghc/tests/deSugar/should_compile/ds022.hs b/ghc/tests/deSugar/should_compile/ds022.hs
index 672871093a13490707c72f73ed06d92870c46382..2ac429f95b97b7193ed3f24128e6ff06a3c698c5 100644
--- a/ghc/tests/deSugar/should_compile/ds022.hs
+++ b/ghc/tests/deSugar/should_compile/ds022.hs
@@ -1,6 +1,6 @@
 -- !!! ds022 -- literal patterns (wimp version)
 --
-module Tests where
+module ShouldCompile where
 
 f 1 1.1 = []
 f 2 2.2 = []
diff --git a/ghc/tests/deSugar/should_compile/ds023.hs b/ghc/tests/deSugar/should_compile/ds023.hs
index a15c464d38ee7d13638e11bcd53c2953ff903584..736107d9798c1617cc4b34c74d43c32264c22e64 100644
--- a/ghc/tests/deSugar/should_compile/ds023.hs
+++ b/ghc/tests/deSugar/should_compile/ds023.hs
@@ -1,6 +1,6 @@
 -- !!! ds023 -- overloading eg from section 9.2
 --
-module Tests where
+module ShouldCompile where
 
 f x	= g (x == x) x
 g b x	= abs (f x)
diff --git a/ghc/tests/deSugar/should_compile/ds024.hs b/ghc/tests/deSugar/should_compile/ds024.hs
index 9c1c9d86be1c4effae53bf0ab61bc76a4d0f061e..76606a90f766051bc01f1d9f89398b05bf6bc1c5 100644
--- a/ghc/tests/deSugar/should_compile/ds024.hs
+++ b/ghc/tests/deSugar/should_compile/ds024.hs
@@ -3,7 +3,7 @@
 -- do all the right types get stuck on all the
 -- Nils and Conses?
 
-module ShouldSucceed where
+module ShouldCompile where
 
 
 f x = [[], []]
diff --git a/ghc/tests/deSugar/should_compile/ds025.hs b/ghc/tests/deSugar/should_compile/ds025.hs
index 8b7651f9f1b9934c92b28b521c01213b532eba44..fdbf0ff6aee4f9583cdaba4dfba45e825a7b215d 100644
--- a/ghc/tests/deSugar/should_compile/ds025.hs
+++ b/ghc/tests/deSugar/should_compile/ds025.hs
@@ -1,6 +1,6 @@
 -- !!! ds025 -- overloaded assoc -- AbsBinds
 
-module Util where
+module ShouldCompile where
 
 ehead xs loc | null xs = error ("4"++loc)
              | True = head xs
diff --git a/ghc/tests/deSugar/should_compile/ds026.hs b/ghc/tests/deSugar/should_compile/ds026.hs
index 969587d70e579c36fe37533016c405f4abec9db0..f21ca0b18bafd5556e5e00d01403c2bf23386fd9 100644
--- a/ghc/tests/deSugar/should_compile/ds026.hs
+++ b/ghc/tests/deSugar/should_compile/ds026.hs
@@ -1,6 +1,6 @@
 -- !!! ds026 -- classes -- incl. polymorphic method
 
-module ShouldSucceed where
+module ShouldCompile where
 
 class Foo a where
   op :: a -> a
diff --git a/ghc/tests/deSugar/should_compile/ds027.hs b/ghc/tests/deSugar/should_compile/ds027.hs
index 5f7a54555accb973372a1fd84973faffa6b38262..436958e531bda58afcca18ec5959690808679dd9 100644
--- a/ghc/tests/deSugar/should_compile/ds027.hs
+++ b/ghc/tests/deSugar/should_compile/ds027.hs
@@ -1,6 +1,6 @@
 -- !!! ds027 -- simple instances
 --
-module Test where
+module ShouldCompile where
 
 data Foo = Bar | Baz
 
diff --git a/ghc/tests/deSugar/should_compile/ds028.hs b/ghc/tests/deSugar/should_compile/ds028.hs
index bec8c19b43154f33c21d6de1749433fb09358b60..4c7944aa3966983f59dc94566f8d9832a23519e1 100644
--- a/ghc/tests/deSugar/should_compile/ds028.hs
+++ b/ghc/tests/deSugar/should_compile/ds028.hs
@@ -1,6 +1,6 @@
 -- !!! ds028: failable pats in top row
 
-module ShouldSucceed where
+module ShouldCompile where
 
 
 -- when the first row of pats doesn't have convenient
diff --git a/ghc/tests/deSugar/should_compile/ds029.hs b/ghc/tests/deSugar/should_compile/ds029.hs
index 833e19b25db3838f5ccc2de67e788ea3391b7fd1..000052365e63eeacc504eb05f15236657051a1ea 100644
--- a/ghc/tests/deSugar/should_compile/ds029.hs
+++ b/ghc/tests/deSugar/should_compile/ds029.hs
@@ -1,7 +1,7 @@
 -- !!! ds029: pattern binding with guards (dubious but valid)
 --
 
-module Test where
+module ShouldCompile where
 
 f x = y
     where (y,z) | y < z     = (0,1)
diff --git a/ghc/tests/deSugar/should_compile/ds030.hs b/ghc/tests/deSugar/should_compile/ds030.hs
index 6046fd93eb495008389bb312b688f7233f412a95..8475b55a0fcc66327e4fe3350b611412e9f3fe94 100644
--- a/ghc/tests/deSugar/should_compile/ds030.hs
+++ b/ghc/tests/deSugar/should_compile/ds030.hs
@@ -1,5 +1,5 @@
 -- !!! ds030: checks that types substituted into binders
 --
-module Test where
+module ShouldCompile where
 
 f x = case x of [] -> (3::Int) ; _ -> (4::Int)
diff --git a/ghc/tests/deSugar/should_compile/ds031.hs b/ghc/tests/deSugar/should_compile/ds031.hs
index 3378800e169d02da98052ae62635a688e8dd86ed..5f25c15b196bd518afacf1bd1de44339ddf3795d 100644
--- a/ghc/tests/deSugar/should_compile/ds031.hs
+++ b/ghc/tests/deSugar/should_compile/ds031.hs
@@ -1,4 +1,4 @@
-module ShouldSucceed where
+module ShouldCompile where
 
 foldPair :: (a->a->a,b->b->b) -> (a,b) -> [(a,b)] -> (a,b)
 foldPair fg       ab [] = ab
diff --git a/ghc/tests/deSugar/should_compile/ds032.hs b/ghc/tests/deSugar/should_compile/ds032.hs
index 65f06c34174f322d7abd0ef06f381540a7b38a6f..09e2de15a70718b6f4a5921a9a6b004ab34b87e2 100644
--- a/ghc/tests/deSugar/should_compile/ds032.hs
+++ b/ghc/tests/deSugar/should_compile/ds032.hs
@@ -1,6 +1,6 @@
 -- !!! recursive funs tangled in an AbsBind
 
-module ShouldSucceed where
+module ShouldCompile where
 
 
 flatten :: Int		-- Indentation
diff --git a/ghc/tests/deSugar/should_compile/ds033.hs b/ghc/tests/deSugar/should_compile/ds033.hs
index 83a00cacb163d8964fa330d4cc5d8c6d680b5b0d..9d89a936c7c619593c7f5c874e77fce40189c84c 100644
--- a/ghc/tests/deSugar/should_compile/ds033.hs
+++ b/ghc/tests/deSugar/should_compile/ds033.hs
@@ -1,6 +1,6 @@
 -- !!! getting top-level dependencies right
 --
-module Test where
+module ShouldCompile where
 
 f1 x = g1 x
 g1 y = y
diff --git a/ghc/tests/deSugar/should_compile/ds034.hs b/ghc/tests/deSugar/should_compile/ds034.hs
index 47a190eff500b1de3d5339454ddbee820e644731..0725a7a97ffd402f9e6a7445810e9dde14f6b977 100644
--- a/ghc/tests/deSugar/should_compile/ds034.hs
+++ b/ghc/tests/deSugar/should_compile/ds034.hs
@@ -1,6 +1,6 @@
 -- !!! mutually-recursive methods in an instance declaration
 --
-module Test where
+module ShouldCompile where
 
 class Foo a where
     op1 :: a -> a 
diff --git a/ghc/tests/deSugar/should_compile/ds036.hs b/ghc/tests/deSugar/should_compile/ds036.hs
index fc30c077e368a180a57732485e9e8a461f7d1622..a024402a6886fecc5350e0c2fd7d83d71e44f584 100644
--- a/ghc/tests/deSugar/should_compile/ds036.hs
+++ b/ghc/tests/deSugar/should_compile/ds036.hs
@@ -13,7 +13,7 @@ error in the code below which disappears when the last line is
 commented out
 -}
 
-module Test2 where
+module ShouldCompile where
 
 --brack :: (Eq a) => a -> a -> [a] -> ([a],[a])
 --brack open close = brack' open close (1 :: Int)
diff --git a/ghc/tests/deSugar/should_compile/ds037.hs b/ghc/tests/deSugar/should_compile/ds037.hs
index 72eb43a42adefac09bef230e3e9dcd1f6fb4d084..d5fc1300f37cf3ef3be488bb97095bf04f1e123b 100644
--- a/ghc/tests/deSugar/should_compile/ds037.hs
+++ b/ghc/tests/deSugar/should_compile/ds037.hs
@@ -1,6 +1,6 @@
 -- !!! AbsBinds with tyvars, no dictvars, but some dict binds
 --
-module ShouldSucceed where
+module ShouldCompile where
 
 f x y = (fst (g y x), x+(1::Int))
 g x y = (fst (f x y), y+(1::Int))
diff --git a/ghc/tests/deSugar/should_compile/ds038.hs b/ghc/tests/deSugar/should_compile/ds038.hs
index 6436b57300befdd65f0d993371690159341ff8cf..04b043c1edb0735fac7dc3e1a942cc2a082990f5 100644
--- a/ghc/tests/deSugar/should_compile/ds038.hs
+++ b/ghc/tests/deSugar/should_compile/ds038.hs
@@ -1,7 +1,7 @@
 -- !!! Jon Hill reported a bug in desugaring this in 0.09
 -- !!! (recursive with n+k patts)
 --
-module ShouldSucceed where
+module ShouldCompile where
 
 takeList :: Int -> [a] -> [a]
 takeList 0     _      = []
diff --git a/ghc/tests/deSugar/should_compile/ds039.hs b/ghc/tests/deSugar/should_compile/ds039.hs
index a6588a4d42a740a861f820d3f348157f8f42b9c5..ad000a5c9fe91a1854e8fb03ef38e992866bef8c 100644
--- a/ghc/tests/deSugar/should_compile/ds039.hs
+++ b/ghc/tests/deSugar/should_compile/ds039.hs
@@ -1,7 +1,7 @@
 -- !!! make sure correct type applications get put in
 -- !!!   when (:) is saturated.
 
-module ShouldSucceed where
+module ShouldCompile where
 
 
 f = (:)
diff --git a/ghc/tests/deSugar/should_compile/ds040.hs b/ghc/tests/deSugar/should_compile/ds040.hs
index 8be249b4f76350035191739f018fc465f847e15e..c02f9f4393d177a926bb1fdf41ddbb4bcc97d603 100644
--- a/ghc/tests/deSugar/should_compile/ds040.hs
+++ b/ghc/tests/deSugar/should_compile/ds040.hs
@@ -1,3 +1,5 @@
+module ShouldCompile where
+
 -- !!! Another bug in overloaded n+k patts
 --
 
diff --git a/ghc/tests/deSugar/should_compile/ds041.hs b/ghc/tests/deSugar/should_compile/ds041.hs
index 072ed898b5760cb7e76b0360a7c55fd37508c315..9fafd5867304c744ad9d741b4c763b391f40aab4 100644
--- a/ghc/tests/deSugar/should_compile/ds041.hs
+++ b/ghc/tests/deSugar/should_compile/ds041.hs
@@ -7,7 +7,7 @@
 	   the constructor properly.
 -}
 
-module Bug where
+module ShouldCompile where
 
 data Eq a => Foo a = Foo { x :: a }
 
diff --git a/ghc/tests/deSugar/should_compile/ds045.hs b/ghc/tests/deSugar/should_compile/ds045.hs
index 207132ece03bfa6e8eb721af58fe4e9ce4e56b88..0bbc767e8951d68e9efed6293e593b531298d2ec 100644
--- a/ghc/tests/deSugar/should_compile/ds045.hs
+++ b/ghc/tests/deSugar/should_compile/ds045.hs
@@ -5,7 +5,7 @@
 -- To: glasgow-haskell-bugs@majordomo.haskell.org
 -- Subject: compiler-bug
 
-module Test where
+module ShouldCompile where
 
 erroR :: Int
 erroR = n where
diff --git a/ghc/tests/deSugar/should_compile/ds046.hs b/ghc/tests/deSugar/should_compile/ds046.hs
index 191e943b2aadfae23f610de44397a4ab962e9d39..5126ff3df42d32d6a42291235552b89188c98b63 100644
--- a/ghc/tests/deSugar/should_compile/ds046.hs
+++ b/ghc/tests/deSugar/should_compile/ds046.hs
@@ -1,4 +1,4 @@
-module Test where
+module ShouldCompile where
 
 -- Strict field unpacking tests: compile with -O -funbox-strict-fields.
 
diff --git a/ghc/tests/deSugar/should_compile/ds047.hs b/ghc/tests/deSugar/should_compile/ds047.hs
index 90078e072adc468175257152c5540660cb2550b8..f6ee2b5dc72b98686204d3f7fb56c598e27f5e8c 100644
--- a/ghc/tests/deSugar/should_compile/ds047.hs
+++ b/ghc/tests/deSugar/should_compile/ds047.hs
@@ -1,6 +1,6 @@
 -- !!! Nullary rec-pats for constructors that hasn't got any labelled
 -- !!! fields is legal Haskell, and requires extra care in the desugarer.
-module Test where
+module ShouldCompile where
 
 data X = X Int [Int]
 
diff --git a/ghc/tests/deSugar/should_compile/ds048.hs b/ghc/tests/deSugar/should_compile/ds048.hs
index 20034304cfa05900b297723cd2093f73eccf02a1..9274aacbea76c22f18878c84f4d3430b5f28d320 100644
--- a/ghc/tests/deSugar/should_compile/ds048.hs
+++ b/ghc/tests/deSugar/should_compile/ds048.hs
@@ -1,5 +1,5 @@
 -- !!! newtypes with a labelled field.
-module ShouldSucceed where
+module ShouldCompile where
 
 newtype Foo = Foo { x :: Int } deriving (Eq)
 
diff --git a/ghc/tests/io/should_run/Makefile b/ghc/tests/io/should_run/Makefile
index 86ffcf7863bb7cf3c55c5c723a81fa5c6cc7bfcf..4e19bcf7b05ed04055d50f025d6d9d6e47568dca 100644
--- a/ghc/tests/io/should_run/Makefile
+++ b/ghc/tests/io/should_run/Makefile
@@ -27,4 +27,6 @@ io028_RUNTEST_OPTS += -i io028.hs
 
 .PRECIOUS: %.o %.bin
 
+CLEAN_FILES += *.out *.inout
+
 include $(TOP)/mk/target.mk
diff --git a/ghc/tests/mk/should_compile.mk b/ghc/tests/mk/should_compile.mk
index 929ced279909532f1e309e8bb820fb17f85643fb..3fdcc626ae97a7c121274eafb783170afa38c745 100644
--- a/ghc/tests/mk/should_compile.mk
+++ b/ghc/tests/mk/should_compile.mk
@@ -1,4 +1,5 @@
 #-----------------------------------------------------------------------------
+# $Id: should_compile.mk,v 1.4 2000/11/03 16:23:38 simonmar Exp $
 # template for should_compile tests.
 
 HS_SRCS = $(wildcard *.hs)
@@ -9,7 +10,10 @@ SRC_RUNTEST_OPTS += -x 0 \
 
 %.o : %.hs
 	@echo ---- Testing for successful compilation of $<
-	@$(RUNTEST) $(HC) $(RUNTEST_OPTS) -- $(HC_OPTS) -c $< -o $@
+	$(RUNTEST) $(HC) $(RUNTEST_OPTS) -- $(HC_OPTS) -c $< -o $@
 
 all :: $(HS_OBJS)
 
+# Most single-module tests are declared to be module ShouldCompile, so we
+# can clean the .hi files in one go:
+CLEAN_FILES += ShouldCompile.hi
diff --git a/ghc/tests/mk/should_fail.mk b/ghc/tests/mk/should_fail.mk
index 17b10e6b9faf8ef3d46b0d186c8acac89ebe4d5e..ab201a98cc355735284f5212f3d7af14b195b353 100644
--- a/ghc/tests/mk/should_fail.mk
+++ b/ghc/tests/mk/should_fail.mk
@@ -1,4 +1,5 @@
 #-----------------------------------------------------------------------------
+# $Id: should_fail.mk,v 1.4 2000/11/03 16:23:38 simonmar Exp $
 # template for should_fail tests
 
 HS_SRCS = $(wildcard *.hs)
@@ -12,3 +13,6 @@ SRC_RUNTEST_OPTS += -x 1 \
 	@$(RUNTEST) $(HC) $(RUNTEST_OPTS) -- $(HC_OPTS) -c $< -o $@
 
 all :: $(HS_OBJS)
+
+# occasionally a test goes wrong and compiles by mistake, so...
+CLEAN_FILES += ShouldFail.hi
diff --git a/ghc/tests/mk/should_run.mk b/ghc/tests/mk/should_run.mk
index eb0336b55c7e16ff2e3d8ceaf4a83221a0b9cf2c..d9b5e68c18437faca6748b61f0dfb9322cc76e58 100644
--- a/ghc/tests/mk/should_run.mk
+++ b/ghc/tests/mk/should_run.mk
@@ -17,4 +17,4 @@ all :: $(RUNTESTS)
 %.bin : %.o
 	$(HC) $(HC_OPTS) $($*_LD_OPTS) $< -o $@
 
-CLEAN_FILES += $(BINS)
+CLEAN_FILES += $(BINS) Main.hi
diff --git a/ghc/tests/programs/Makefile b/ghc/tests/programs/Makefile
index f832adbb558bed41060219b5cc5fb3b34b4a9c3d..accac815bc31b10bf372911c590e5c3906d636f9 100644
--- a/ghc/tests/programs/Makefile
+++ b/ghc/tests/programs/Makefile
@@ -1,5 +1,5 @@
 #-----------------------------------------------------------------------------
-# $Id: Makefile,v 1.7 2000/04/11 11:53:47 simonmar Exp $
+# $Id: Makefile,v 1.8 2000/11/03 16:23:38 simonmar Exp $
 #
 # (c) The GHC Team, 1999-2000
 #
@@ -22,7 +22,7 @@ NOT_THESE += north_lias
 #	Deliberately causes divide by zero, and
 #	we can't catch that yet
 
-NOT_THESE += andy_cherry barton-mangler-bug callback cvh_unboxing dmgob_native1 dmgob_native2 fast2haskell fexport jtod_circint okeefe_neural
+NOT_THESE += andy_cherry barton-mangler-bug cvh_unboxing dmgob_native1 dmgob_native2 fast2haskell fexport jtod_circint okeefe_neural
 #	doesn't compile
 
 NOT_THESE += jeff-bug lennart_array
diff --git a/ghc/tests/programs/callback/Makefile b/ghc/tests/programs/callback/Makefile
index 8eb5c96256ea2c5d92f1867c4d0f229543ed73d7..a826efd99d583a08e3db1952a106060d85fb92a3 100644
--- a/ghc/tests/programs/callback/Makefile
+++ b/ghc/tests/programs/callback/Makefile
@@ -1,9 +1,11 @@
+#-----------------------------------------------------------------------------
+# $Id
+
 TOP = ..
 include $(TOP)/mk/boilerplate.mk
 
-SRC_HC_OPTS += -fglasgow-exts
-
-CC = $(HC)
+SRC_HC_OPTS += -fglasgow-exts -fvia-C
+SRC_LD_OPTS += Main_stub.o
 
 all :: runtest
 
diff --git a/ghc/tests/reader/should_compile/Makefile b/ghc/tests/reader/should_compile/Makefile
index ac9ca82eed18a2881f0cd450234313ecaf6f28ac..a7bb484f7e7b7fdf75979024c90ea553146bc30d 100644
--- a/ghc/tests/reader/should_compile/Makefile
+++ b/ghc/tests/reader/should_compile/Makefile
@@ -10,4 +10,6 @@ read014_HC_OPTS += -Wall
 read022_HC_OPTS = -fglasgow-exts
 read024_HC_OPTS = -fglasgow-exts
 
+CLEAN_FILES += T1.hi T2.hi MyList.hi
+
 include $(TOP)/mk/target.mk
diff --git a/ghc/tests/reader/should_compile/MyList.hi b/ghc/tests/reader/should_compile/MyList.hi
deleted file mode 100644
index 07777f36483816d03022f0f6f455780d2c79c4f8..0000000000000000000000000000000000000000
--- a/ghc/tests/reader/should_compile/MyList.hi
+++ /dev/null
@@ -1,5 +0,0 @@
-__interface MyList 1 0 where
-__export MyList MyList{Empty ZCZCZC};
-import PrelBase 16 :: addr2Integer 1 foldr 1 int2Integer 1 integer_0 1 integer_1 1 integer_2 1 integer_m1 1;
-import PrelPack 15 :: packCStringzh 1 unpackAppendCStringzh 1 unpackCStringzh 1 unpackFoldrCStringzh 1 unpackNByteszh 1;
-2 data MyList a = Empty |  ZCZCZC (MyList a) (MyList a) ;
diff --git a/ghc/tests/reader/should_compile/read002.hs b/ghc/tests/reader/should_compile/read002.hs
index 0d26eb755b83eddf0f0f88f625e8fe64b7a40e13..5b069fe2c65a67ed7eaf408dc8c58bd9b4aa5900 100644
--- a/ghc/tests/reader/should_compile/read002.hs
+++ b/ghc/tests/reader/should_compile/read002.hs
@@ -1,5 +1,5 @@
 -- !!! tests fixity reading and printing
-module Reader where
+module ShouldCompile where
 
 infixl 1 `f`
 infixr 2 \\\
diff --git a/ghc/tests/reader/should_compile/read003.hs b/ghc/tests/reader/should_compile/read003.hs
index d0e520648cd73f152db03cabd41bd612c71a2ebd..afc3a21007bace554c2e0f2a5160da0f4a68192e 100644
--- a/ghc/tests/reader/should_compile/read003.hs
+++ b/ghc/tests/reader/should_compile/read003.hs
@@ -1,5 +1,5 @@
 -- !!! Testing layout rule
-module Layout where
+module ShouldCompile where
 
 l1 :: IO ()
 l1 = do
diff --git a/ghc/tests/reader/should_compile/read004.hs b/ghc/tests/reader/should_compile/read004.hs
index f21bb121c0a66b692bd2c2b9a06a4f964ff84929..0741d0cd92cc0f71894d5fa28f1dffcd47c8cff8 100644
--- a/ghc/tests/reader/should_compile/read004.hs
+++ b/ghc/tests/reader/should_compile/read004.hs
@@ -1,4 +1,4 @@
-module ShouldFail where
+module ShouldCompile where
 
 {-
 From: Kevin Hammond <kh>
diff --git a/ghc/tests/reader/should_compile/read005.hs b/ghc/tests/reader/should_compile/read005.hs
index e02b3d0a9af608b6a398ea69c7483efbfbeeab86..6e2c57590282fbddfbe2721988a6547526bf9a8a 100644
--- a/ghc/tests/reader/should_compile/read005.hs
+++ b/ghc/tests/reader/should_compile/read005.hs
@@ -1,2 +1,4 @@
+module ShouldCompile where
+
 -- !!! Empty comments terminating a file..
 main = print "Hello" --
diff --git a/ghc/tests/reader/should_compile/read005.stderr b/ghc/tests/reader/should_compile/read005.stderr
deleted file mode 100644
index 482b571640f59eb7323216e22d6d3de97b40d9e5..0000000000000000000000000000000000000000
--- a/ghc/tests/reader/should_compile/read005.stderr
+++ /dev/null
@@ -1 +0,0 @@
-Haskell compiler received signal 2
diff --git a/ghc/tests/reader/should_compile/read006.hs b/ghc/tests/reader/should_compile/read006.hs
index bb26ed024efee40581ac4bf4e49c8ea468d926b5..f04b29b69201dc479485a7ade69cce26eb246454 100644
--- a/ghc/tests/reader/should_compile/read006.hs
+++ b/ghc/tests/reader/should_compile/read006.hs
@@ -3,4 +3,3 @@ module MyList (MyList(Empty, (:::))) where
 
 data MyList a =   Empty
                 | (MyList a) ::: (MyList a)
-
diff --git a/ghc/tests/reader/should_compile/read007.hs b/ghc/tests/reader/should_compile/read007.hs
index a65188318f648d861ca396702c087d03760dfeff..55a4332a25250ce30721172401232f14eca791d7 100644
--- a/ghc/tests/reader/should_compile/read007.hs
+++ b/ghc/tests/reader/should_compile/read007.hs
@@ -1,4 +1,4 @@
-module User where
+module ShouldCompile where
 
 import MyList
 
diff --git a/ghc/tests/reader/should_compile/read008.hs b/ghc/tests/reader/should_compile/read008.hs
index 12e2bb6745a0cf26b3d8286ad953d1ffb6ff7416..20060b0c4d424b6160f99f62544091580d79b9f9 100644
--- a/ghc/tests/reader/should_compile/read008.hs
+++ b/ghc/tests/reader/should_compile/read008.hs
@@ -1,4 +1,4 @@
-module ShouldSucceed where
+module ShouldCompile where
 
 {-# SPECIALISE f :: Int -> Int #-}
 f n = n + 1
diff --git a/ghc/tests/reader/should_compile/read009.hs b/ghc/tests/reader/should_compile/read009.hs
index 588aae82d7acc6d83d5bb093af59a40dfebde241..5294012de1c4e4d6c7df5745c067aa6a2bc5fd7e 100644
--- a/ghc/tests/reader/should_compile/read009.hs
+++ b/ghc/tests/reader/should_compile/read009.hs
@@ -1,5 +1,5 @@
 -- !!! combining undeclared infix operators
-module ShouldSucceed where
+module ShouldCompile where
 
 -- should default to 'infixl 9'
 
diff --git a/ghc/tests/reader/should_compile/read010.hs b/ghc/tests/reader/should_compile/read010.hs
index 579152bc4f9dce771241e90b968091e5487e5680..d20f5fcc86b6c871b2e1c179c11f3716051af875 100644
--- a/ghc/tests/reader/should_compile/read010.hs
+++ b/ghc/tests/reader/should_compile/read010.hs
@@ -1,4 +1,4 @@
 -- !!! Infix record constructor.
-module ShouldSucceed where
+module ShouldCompile where
 
 data Rec = (:<-:) { a :: Int, b :: Float }
diff --git a/ghc/tests/reader/should_compile/read011.hs b/ghc/tests/reader/should_compile/read011.hs
index fec644b2b523eba305e4c34f0e19e2c7a06b61cd..7e20d468f0be8e2081434c72331dc5f83d5a4b29 100644
--- a/ghc/tests/reader/should_compile/read011.hs
+++ b/ghc/tests/reader/should_compile/read011.hs
@@ -1,5 +1,5 @@
 -- !!! do & where interaction
-module ShouldSucceed where
+module ShouldCompile where
 
 f1 :: IO a -> IO [a]
 f1 x = do
diff --git a/ghc/tests/reader/should_compile/read014.hs b/ghc/tests/reader/should_compile/read014.hs
index b8bfe7f9c7be04b9471d3fea5c71fd4c81382bf6..55fc053a8b8d3ec572fa55a0a01a5b74923bb5bc 100644
--- a/ghc/tests/reader/should_compile/read014.hs
+++ b/ghc/tests/reader/should_compile/read014.hs
@@ -1,5 +1,5 @@
 -- !!! Empty export lists are legal (and useful.)
-module T () where
+module ShouldCompile () where
 
 ng1 x y = negate y
 
diff --git a/ghc/tests/reader/should_compile/read015.hs b/ghc/tests/reader/should_compile/read015.hs
index 2cee2da2306971f6a5d7350e908cc62377a8df22..7ba6140662986f122aa9b32a289f14fc6a35c506 100644
--- a/ghc/tests/reader/should_compile/read015.hs
+++ b/ghc/tests/reader/should_compile/read015.hs
@@ -1,2 +1,2 @@
 -- !!! Testing whether the parser likes empty declarations..
-module M where { ;;;;;x=let{;;;;;y=2;;;;}in y;;;;;}
+module ShouldCompile where { ;;;;;x=let{;;;;;y=2;;;;}in y;;;;;}
diff --git a/ghc/tests/reader/should_compile/read016.hs b/ghc/tests/reader/should_compile/read016.hs
index a2f43119e6fb617d52663211c7459263fd66cba0..c333c40045c32d93864be59e1ec9fab29dc83a90 100644
--- a/ghc/tests/reader/should_compile/read016.hs
+++ b/ghc/tests/reader/should_compile/read016.hs
@@ -1,6 +1,6 @@
 -- !!! Checking that both import lists and 'hiding' lists might
 -- !!! be empty.
-module ShouldSucceed where
+module ShouldCompile where
 
 import List  ()
 import List  hiding ()
diff --git a/ghc/tests/reader/should_compile/read017.hs b/ghc/tests/reader/should_compile/read017.hs
index e87fedef4902b2a195e6d312f694ff38b3f34c38..4349cb27cadc7a68bb9794da8dc7943f64072f73 100644
--- a/ghc/tests/reader/should_compile/read017.hs
+++ b/ghc/tests/reader/should_compile/read017.hs
@@ -1,5 +1,5 @@
 -- !!! Checking that empty declarations are permitted.
-module ShouldSucceed where
+module ShouldCompile where
 
 
 class Foo a where
diff --git a/ghc/tests/reader/should_compile/read018.hs b/ghc/tests/reader/should_compile/read018.hs
index ed3f07d7ad49d515b9f7fdf854de45bc574124fd..e4abfb6fea190977dc9a0f30110e17f31ea7f4f3 100644
--- a/ghc/tests/reader/should_compile/read018.hs
+++ b/ghc/tests/reader/should_compile/read018.hs
@@ -1,5 +1,5 @@
 -- !!! Checking that empty contexts are permitted.
-module ShouldSucceed where
+module ShouldCompile where
 
 data () => Foo a = Foo a
 
diff --git a/ghc/tests/reader/should_compile/read019.hs b/ghc/tests/reader/should_compile/read019.hs
index 2ba776d3486cbdfcc6381ce1fd3076019b20a20b..3de6a9b71db8662050cb002547913fac61f0a9f3 100644
--- a/ghc/tests/reader/should_compile/read019.hs
+++ b/ghc/tests/reader/should_compile/read019.hs
@@ -1,5 +1,5 @@
 -- !!! Checking what's legal in the body of a class declaration.
-module ShouldSucceed where
+module ShouldCompile where
 
 class Foo a where {
   (--<>--) :: a -> a -> Int  ;
diff --git a/ghc/tests/reader/should_compile/read020.hs b/ghc/tests/reader/should_compile/read020.hs
index ea6c04d68d924503e35dbb3232076253c021abf3..50efcf3a556fe769051dfbe8905297c702efca7a 100644
--- a/ghc/tests/reader/should_compile/read020.hs
+++ b/ghc/tests/reader/should_compile/read020.hs
@@ -1,5 +1,5 @@
 -- !!! Checking that qualified method names are legal in instance body.
-module ShouldSucceed where
+module ShouldCompile where
 
 import Prelude hiding (Eq, (==))
 import Prelude as P (Eq,(==))
diff --git a/ghc/tests/reader/should_compile/read021.hs b/ghc/tests/reader/should_compile/read021.hs
index b515df2c7735b5b4d4203a46d126f0df0cf9134b..8d5856e9b62df5dcc3b9f890c17dfc1135aeb5d1 100644
--- a/ghc/tests/reader/should_compile/read021.hs
+++ b/ghc/tests/reader/should_compile/read021.hs
@@ -1,6 +1,6 @@
 -- !!! Empty export list
 
-module Reader() where
+module ShouldCompile() where
 
 instance Show (a->b) where
   show f = "<<function>>"
diff --git a/ghc/tests/rename/should_compile/Makefile b/ghc/tests/rename/should_compile/Makefile
index 45b95af16fd79be3df1986535cff413c209c9a7e..9614587edce835d491144a12928feeb59af10957 100644
--- a/ghc/tests/rename/should_compile/Makefile
+++ b/ghc/tests/rename/should_compile/Makefile
@@ -11,6 +11,9 @@ SRC_HC_OPTS += -dcore-lint
 # rn025_HC_OPTS = -hi -hi-with-exports
 # Rn037Help_HC_OPTS = -hi
 
+CLEAN_FILES += Confused.hi Foo.hi Imp10.hi Imp100.hi Imp1000.hi \
+	Imp500.hi Main.hi Mod10.hi OK.hi ShouldSucceed.hi Silly.hi Test.hi
+
 include $(TOP)/mk/target.mk
 
 
diff --git a/ghc/tests/rename/should_compile/rn025.hs b/ghc/tests/rename/should_compile/rn025.hs
index 2d4838c8a874ea2e146d5be111454629ee788126..9eb64e01b923a951150a9b7a5dcc71f255fd60e5 100644
--- a/ghc/tests/rename/should_compile/rn025.hs
+++ b/ghc/tests/rename/should_compile/rn025.hs
@@ -1,5 +1,5 @@
 -- !!! Re-exporting a module whose contents is partially hidden.
-module ShouldSucceed ( module List ) where
+module ShouldCompile ( module List ) where
 
 import List hiding ( sort )
 
diff --git a/ghc/tests/rename/should_compile/rn026.hs b/ghc/tests/rename/should_compile/rn026.hs
index ff705b6f97d59ac0d494c1c79d0cb184be025d0f..fdba3a8d54a92bd4135cca52e9b390822e93acf2 100644
--- a/ghc/tests/rename/should_compile/rn026.hs
+++ b/ghc/tests/rename/should_compile/rn026.hs
@@ -1,6 +1,6 @@
 -- !!! Checking that more than imported module can share a local
 -- !!! local alias.
-module ShouldSucceed where
+module ShouldCompile where
 
 import qualified List  as X
 import qualified Maybe as X
diff --git a/ghc/tests/rename/should_compile/rn027.hs b/ghc/tests/rename/should_compile/rn027.hs
index c773f91cb907bd1303e8fbaa396e040773c50a94..e9bd760d478ef79196d8587106cfe48581ed06b2 100644
--- a/ghc/tests/rename/should_compile/rn027.hs
+++ b/ghc/tests/rename/should_compile/rn027.hs
@@ -1,6 +1,6 @@
 -- !!! Checking that an imported module may still have
 -- !!! a local alias without having used 'qualified'.
-module ShouldSucceed where
+module ShouldCompile where
 
 import List  as X
 import Maybe as X
diff --git a/ghc/tests/rename/should_compile/rn028.hs b/ghc/tests/rename/should_compile/rn028.hs
index 82438e836f2038753e990944f72ed810a1c4dae4..16e31a4a2096a4b9aeb9a63fc7d83675c236da03 100644
--- a/ghc/tests/rename/should_compile/rn028.hs
+++ b/ghc/tests/rename/should_compile/rn028.hs
@@ -1,7 +1,7 @@
 -- !!! Checking that a toplevel declaration 'f' in module M is accessible
 -- !!! as both 'f' and 'M.f' within the scope of M. Similarly for imported
 -- !!! entities.
-module ShouldSucceed where
+module ShouldCompile where
 
 import List ( sort )
 
@@ -12,7 +12,7 @@ y :: Int
 y = x
 
 z :: Int
-z = ShouldSucceed.x
+z = ShouldCompile.x
 
 sortOf :: Ord a=> [a] -> [a]
 sortOf = List.sort
diff --git a/ghc/tests/rename/should_compile/rn029.hs b/ghc/tests/rename/should_compile/rn029.hs
index 354fef5b056bdfa60e8f0975ce3492d98b615c43..5b87602ee9b11215a0c84711289903ba253df265 100644
--- a/ghc/tests/rename/should_compile/rn029.hs
+++ b/ghc/tests/rename/should_compile/rn029.hs
@@ -1,5 +1,5 @@
 -- !!! Checking that lazy name clashing works.
-module ShouldSucceed where
+module ShouldCompile where
 
 import List ( reverse, sort )
 
@@ -10,7 +10,7 @@ sort = 4	-- but never used, so OK
 reverse :: Int	-- Clashes with List.reverse, 
 reverse = 3	-- but the only uses are qualified
 
-x = ShouldSucceed.reverse
+x = ShouldCompile.reverse
 
 y = List.reverse
 
diff --git a/ghc/tests/rename/should_compile/rn030.hs b/ghc/tests/rename/should_compile/rn030.hs
index ff705b6f97d59ac0d494c1c79d0cb184be025d0f..fdba3a8d54a92bd4135cca52e9b390822e93acf2 100644
--- a/ghc/tests/rename/should_compile/rn030.hs
+++ b/ghc/tests/rename/should_compile/rn030.hs
@@ -1,6 +1,6 @@
 -- !!! Checking that more than imported module can share a local
 -- !!! local alias.
-module ShouldSucceed where
+module ShouldCompile where
 
 import qualified List  as X
 import qualified Maybe as X
diff --git a/ghc/tests/rename/should_compile/rn031.hs b/ghc/tests/rename/should_compile/rn031.hs
index 4ffeacafef8d530062622f6c53155f14ccca4063..bea26c0da0c22ca7626467b1f53e99497efe9c83 100644
--- a/ghc/tests/rename/should_compile/rn031.hs
+++ b/ghc/tests/rename/should_compile/rn031.hs
@@ -1,6 +1,6 @@
 -- !!! Checking that an imported module may still have
 -- !!! a local alias without having used 'qualified'.
-module ShouldSucceed where
+module ShouldCompile where
 
 import List  as X
 import Maybe as X
diff --git a/ghc/tests/rename/should_compile/rn032.hs b/ghc/tests/rename/should_compile/rn032.hs
index 82438e836f2038753e990944f72ed810a1c4dae4..16e31a4a2096a4b9aeb9a63fc7d83675c236da03 100644
--- a/ghc/tests/rename/should_compile/rn032.hs
+++ b/ghc/tests/rename/should_compile/rn032.hs
@@ -1,7 +1,7 @@
 -- !!! Checking that a toplevel declaration 'f' in module M is accessible
 -- !!! as both 'f' and 'M.f' within the scope of M. Similarly for imported
 -- !!! entities.
-module ShouldSucceed where
+module ShouldCompile where
 
 import List ( sort )
 
@@ -12,7 +12,7 @@ y :: Int
 y = x
 
 z :: Int
-z = ShouldSucceed.x
+z = ShouldCompile.x
 
 sortOf :: Ord a=> [a] -> [a]
 sortOf = List.sort
diff --git a/ghc/tests/rename/should_compile/rn033.hs b/ghc/tests/rename/should_compile/rn033.hs
index 62aba9183e2cf9709594878a60f4d1ede567ab4f..87589e94846f274dbdfc2b22d50addbc6943385e 100644
--- a/ghc/tests/rename/should_compile/rn033.hs
+++ b/ghc/tests/rename/should_compile/rn033.hs
@@ -1,5 +1,5 @@
 -- !!! Checking that lazy name clashing works
-module ShouldSucceed where
+module ShouldCompile where
 
 import List ( sort )
 
@@ -7,7 +7,7 @@ sort :: Int
 sort = 3
 
 foo :: Int
-foo = ShouldSucceed.sort
+foo = ShouldCompile.sort
 
 baz :: (Ord a) => [a] -> [a]
 baz = List.sort
diff --git a/ghc/tests/rename/should_compile/rn034.hs b/ghc/tests/rename/should_compile/rn034.hs
index 311739104bb9cccf32ffe2639cd090f17ba007b0..b8fc047171bfc20fcc9abdc48af66e098854fbba 100644
--- a/ghc/tests/rename/should_compile/rn034.hs
+++ b/ghc/tests/rename/should_compile/rn034.hs
@@ -1,5 +1,5 @@
 -- !!! Checking that empty declarations are permitted.
-module ShouldSucceed where
+module ShouldCompile where
 
 
 class Foo a where
diff --git a/ghc/tests/rename/should_compile/rn035.hs b/ghc/tests/rename/should_compile/rn035.hs
index 2ba776d3486cbdfcc6381ce1fd3076019b20a20b..3de6a9b71db8662050cb002547913fac61f0a9f3 100644
--- a/ghc/tests/rename/should_compile/rn035.hs
+++ b/ghc/tests/rename/should_compile/rn035.hs
@@ -1,5 +1,5 @@
 -- !!! Checking what's legal in the body of a class declaration.
-module ShouldSucceed where
+module ShouldCompile where
 
 class Foo a where {
   (--<>--) :: a -> a -> Int  ;
diff --git a/ghc/tests/rename/should_compile/rn036.hs b/ghc/tests/rename/should_compile/rn036.hs
index ea6c04d68d924503e35dbb3232076253c021abf3..50efcf3a556fe769051dfbe8905297c702efca7a 100644
--- a/ghc/tests/rename/should_compile/rn036.hs
+++ b/ghc/tests/rename/should_compile/rn036.hs
@@ -1,5 +1,5 @@
 -- !!! Checking that qualified method names are legal in instance body.
-module ShouldSucceed where
+module ShouldCompile where
 
 import Prelude hiding (Eq, (==))
 import Prelude as P (Eq,(==))
diff --git a/ghc/tests/rename/should_compile/rn037.hs b/ghc/tests/rename/should_compile/rn037.hs
index 668d707a5c79690c2ad4cdec7168244b88f965de..bd9a9b6bc673d10e79b4bbed36b3a40b19091f5b 100644
--- a/ghc/tests/rename/should_compile/rn037.hs
+++ b/ghc/tests/rename/should_compile/rn037.hs
@@ -1,5 +1,5 @@
 -- !!! Checking that you can hide a constructor
-module ShouldSucceed where
+module ShouldCompile where
 
 import Rn037Help hiding( C )
 	-- C is the constructor, but we should
diff --git a/ghc/tests/simplCore/should_compile/simpl001.hs b/ghc/tests/simplCore/should_compile/simpl001.hs
index 9b3adc595b36e298a1418a27411829a6b09e0f61..4b2bfcc24021b0b602086c88a0be1c664b640b47 100644
--- a/ghc/tests/simplCore/should_compile/simpl001.hs
+++ b/ghc/tests/simplCore/should_compile/simpl001.hs
@@ -3,7 +3,7 @@
 -- only tickled by the simplifier
 
 -- type Foo a b = a -> (b -> a) -> b
-module Test where
+module ShouldCompile where
 
 (++++) :: (a -> (b -> a) -> b) -> (a -> (b -> a) -> b) -> a -> (b -> a) -> b
 x ++++ y = y
diff --git a/ghc/tests/simplCore/should_compile/simpl002.hs b/ghc/tests/simplCore/should_compile/simpl002.hs
index 58e072f77cd69f7fc45af2f4a9fc113349485e5c..b262f47d381283f401927b9b47788435d30fccf8 100644
--- a/ghc/tests/simplCore/should_compile/simpl002.hs
+++ b/ghc/tests/simplCore/should_compile/simpl002.hs
@@ -1,6 +1,6 @@
 -- !!! class/instance mumble that failed Lint at one time
 --
-module Test where
+module ShouldCompile where
 class Foo a where
    op :: Int -> a -> Bool
 
diff --git a/ghc/tests/simplCore/should_compile/simpl003.hs b/ghc/tests/simplCore/should_compile/simpl003.hs
index 3cd1af476c462dc0bdf6e4ed24024ef343969ec0..2f36696c0b022fbd7379f98193b3fa70ce70dee1 100644
--- a/ghc/tests/simplCore/should_compile/simpl003.hs
+++ b/ghc/tests/simplCore/should_compile/simpl003.hs
@@ -5,7 +5,7 @@ From: Julian Seward (DRL PhD) <sewardj@computer-science.manchester.ac.uk>
 Message-Id: <9412081138.AA16652@rdf009.cs.man.ac.uk>
 To: partain@dcs.gla.ac.uk
 -}
-module ShouldFail where
+module ShouldCompile where
 
 type IMonad a
    = IMonadState -> IMonadReturn a