"make clean" in here now works as advertised.
 -- !!! cc006 -- ccall with non-standard boxed arguments and results
 
-module Test where
+module ShouldCompile where
 
 import Foreign
 import CCall
 
 -- !!! cc007 -- foreign import with external name equal to Haskell name.
-module Test where
+module ShouldCompile where
 
 foreign import sine :: Double -> Double
 
 -- !!! cc008 -- foreign export dynamic returning newtype of Addr
-module Test where
+module ShouldCompile where
 
 import Addr
 
 
 -- !!! cc009 -- foreign label returning newtype of Addr
-module Test where
+module ShouldCompile where
 
 import Addr
 
 
 #-----------------------------------------------------------------------------
-# $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
 
 .PRECIOUS: %.bin %.o
 
-clean ::
-       rm -f *.bin *.o
+CLEAN_FILES += PrelMain.hi
 
 include $(TOP)/mk/target.mk
 
 #-----------------------------------------------------------------------------
-# $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
 
 SRC_HC_OPTS += -dcore-lint -package concurrent -fglasgow-exts
 
+CLEAN_FILES += PrelMain.hi
+
 include $(TOP)/mk/target.mk
 
-module ShouldSucceed where
+module ShouldCompile where
 
 x@_ = x
 
 --
 -- this tests ultra-simple function and pattern bindings (no patterns)
 
-module Test where
+module ShouldCompile where
 
 -- simple function bindings
 
 
 --
 -- this tests "overlapping" variables and guards
 
-module Test where
+module ShouldCompile where
 
 f x = x
 f y = y
 
 -- !!! ds003 -- list, tuple, lazy, as patterns
 --
-module Test where
+module ShouldCompile where
 
 f []           y        True  = []
 f x            a@(y,ys) ~z    = []
 
 -- !!! ds004 -- nodups from SLPJ p 79
 --
-module Test where
+module ShouldCompile where
 
 -- SLPJ, p 79
 nodups []                   = []
 
 --
 -- this simply tests a "typical" example
 
-module MapPairs where
+module ShouldCompile where
 
 -- from SLPJ, p 78
 mappairs f []     ys     = []
 
 -- !!! ds006 -- v | True = v+1 | False = v (dead code elim)
 --
-module Test where
+module ShouldCompile where
 
 v | True  = v + 1
   | False = v
 
 -- !!! ds007 -- simple local bindings
 
-module ShouldSucceed where
+module ShouldCompile where
 
 w = a where a = y
             y = []
 
 --
 -- these tests involve way-cool TyApps
 
-module Test where
+module ShouldCompile where
 
 f x = []
 
 
 -- !!! ds009 -- simple list comprehensions
 
-module SimpleListComp where
+module ShouldCompile where
 
 f xs = [ x | x <- xs ]
 
 
 -- !!! 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",
 
 -- !!! ds011 -- uses of "error"
 
-module Tests where
+module ShouldCompile where
 
 f = error []
 
 
 -- !!! ds012 -- simple Integer arithmetic
 --
-module Tests where
+module ShouldCompile where
 
 f x = 1 + 2 - 3 + 4 * 5
 
 
 -- !!! ds013 -- simple Rational arithmetic
 
-module Tests where
+module ShouldCompile where
 
 f = 1.5 + 2.0 - 3.14159265 + 4.2 * 5.111111111111111111111111111
 
 
 -- !!! ds014 -- character and string literals
 -- !!!   really should add ALL weird forms...
 
-module Tests where
+module ShouldCompile where
 
 a = 'a'
 b = "b"
 
 -- !!! ds015 -- lambdas
 --
-module Tests where
+module ShouldCompile where
 
 f x = ( \ x -> x ) x
 
 
 -- !!! ds016 -- case expressions
 --
-module Tests where
+module ShouldCompile where
 
 f x y z =
     case ( x ++ x ++ x ++ x ++ x ) of
 
 -- !!! ds017 -- let expressions
 --
-module Tests where
+module ShouldCompile where
 
 f x y z
   = let
 
 -- !!! ds018 -- explicit lists and tuples
 --
-module Tests where
+module ShouldCompile where
 
 -- exprs
 
 
 -- !!! ds019 -- mixed var and uni-constructor pats
 
-module Test where
+module ShouldCompile where
 
 f (a,b,c) i     o = []
 f d       (j,k) p = []
 
 -- !!! ds020 -- lazy patterns (in detail)
 --
-module Test where
+module ShouldCompile where
 
 a ~([],[],[])    = []
 a ~(~[],~[],~[]) = []
 
 -- !!! ds021 -- hairier uses of guards
 
-module Test where
+module ShouldCompile where
 
 f x y z | x == y     = []
        | x /= z     = []
 
 -- !!! ds022 -- literal patterns (wimp version)
 --
-module Tests where
+module ShouldCompile where
 
 f 1 1.1 = []
 f 2 2.2 = []
 
 -- !!! 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)
 
 -- do all the right types get stuck on all the
 -- Nils and Conses?
 
-module ShouldSucceed where
+module ShouldCompile where
 
 
 f x = [[], []]
 
 -- !!! ds025 -- overloaded assoc -- AbsBinds
 
-module Util where
+module ShouldCompile where
 
 ehead xs loc | null xs = error ("4"++loc)
              | True = head xs
 
 -- !!! ds026 -- classes -- incl. polymorphic method
 
-module ShouldSucceed where
+module ShouldCompile where
 
 class Foo a where
   op :: a -> a
 
 -- !!! ds027 -- simple instances
 --
-module Test where
+module ShouldCompile where
 
 data Foo = Bar | Baz
 
 
 -- !!! ds028: failable pats in top row
 
-module ShouldSucceed where
+module ShouldCompile where
 
 
 -- when the first row of pats doesn't have convenient
 
 -- !!! ds029: pattern binding with guards (dubious but valid)
 --
 
-module Test where
+module ShouldCompile where
 
 f x = y
     where (y,z) | y < z     = (0,1)
 
 -- !!! ds030: checks that types substituted into binders
 --
-module Test where
+module ShouldCompile where
 
 f x = case x of [] -> (3::Int) ; _ -> (4::Int)
 
-module ShouldSucceed where
+module ShouldCompile where
 
 foldPair :: (a->a->a,b->b->b) -> (a,b) -> [(a,b)] -> (a,b)
 foldPair fg       ab [] = ab
 
 -- !!! recursive funs tangled in an AbsBind
 
-module ShouldSucceed where
+module ShouldCompile where
 
 
 flatten :: Int         -- Indentation
 
 -- !!! getting top-level dependencies right
 --
-module Test where
+module ShouldCompile where
 
 f1 x = g1 x
 g1 y = y
 
 -- !!! mutually-recursive methods in an instance declaration
 --
-module Test where
+module ShouldCompile where
 
 class Foo a where
     op1 :: a -> a 
 
 commented out
 -}
 
-module Test2 where
+module ShouldCompile where
 
 --brack :: (Eq a) => a -> a -> [a] -> ([a],[a])
 --brack open close = brack' open close (1 :: Int)
 
 -- !!! 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))
 
 -- !!! 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     _      = []
 
 -- !!! make sure correct type applications get put in
 -- !!!   when (:) is saturated.
 
-module ShouldSucceed where
+module ShouldCompile where
 
 
 f = (:)
 
+module ShouldCompile where
+
 -- !!! Another bug in overloaded n+k patts
 --
 
 
           the constructor properly.
 -}
 
-module Bug where
+module ShouldCompile where
 
 data Eq a => Foo a = Foo { x :: a }
 
 
 -- To: glasgow-haskell-bugs@majordomo.haskell.org
 -- Subject: compiler-bug
 
-module Test where
+module ShouldCompile where
 
 erroR :: Int
 erroR = n where
 
-module Test where
+module ShouldCompile where
 
 -- Strict field unpacking tests: compile with -O -funbox-strict-fields.
 
 
 -- !!! 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]
 
 
 -- !!! newtypes with a labelled field.
-module ShouldSucceed where
+module ShouldCompile where
 
 newtype Foo = Foo { x :: Int } deriving (Eq)
 
 
 
 .PRECIOUS: %.o %.bin
 
+CLEAN_FILES += *.out *.inout
+
 include $(TOP)/mk/target.mk
 
 #-----------------------------------------------------------------------------
+# $Id: should_compile.mk,v 1.4 2000/11/03 16:23:38 simonmar Exp $
 # template for should_compile tests.
 
 HS_SRCS = $(wildcard *.hs)
 
 %.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
 
 #-----------------------------------------------------------------------------
+# $Id: should_fail.mk,v 1.4 2000/11/03 16:23:38 simonmar Exp $
 # template for should_fail tests
 
 HS_SRCS = $(wildcard *.hs)
        @$(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
 
 %.bin : %.o
        $(HC) $(HC_OPTS) $($*_LD_OPTS) $< -o $@
 
-CLEAN_FILES += $(BINS)
+CLEAN_FILES += $(BINS) Main.hi
 
 #-----------------------------------------------------------------------------
-# $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
 #
 #      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
 
+#-----------------------------------------------------------------------------
+# $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
 
 
 read022_HC_OPTS = -fglasgow-exts
 read024_HC_OPTS = -fglasgow-exts
 
+CLEAN_FILES += T1.hi T2.hi MyList.hi
+
 include $(TOP)/mk/target.mk
 
+++ /dev/null
-__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) ;
 
 -- !!! tests fixity reading and printing
-module Reader where
+module ShouldCompile where
 
 infixl 1 `f`
 infixr 2 \\\
 
 -- !!! Testing layout rule
-module Layout where
+module ShouldCompile where
 
 l1 :: IO ()
 l1 = do
 
-module ShouldFail where
+module ShouldCompile where
 
 {-
 From: Kevin Hammond <kh>
 
+module ShouldCompile where
+
 -- !!! Empty comments terminating a file..
 main = print "Hello" --
 
+++ /dev/null
-Haskell compiler received signal 2
 
 
 data MyList a =   Empty
                 | (MyList a) ::: (MyList a)
-
 
-module User where
+module ShouldCompile where
 
 import MyList
 
 
-module ShouldSucceed where
+module ShouldCompile where
 
 {-# SPECIALISE f :: Int -> Int #-}
 f n = n + 1
 
 -- !!! combining undeclared infix operators
-module ShouldSucceed where
+module ShouldCompile where
 
 -- should default to 'infixl 9'
 
 
 -- !!! Infix record constructor.
-module ShouldSucceed where
+module ShouldCompile where
 
 data Rec = (:<-:) { a :: Int, b :: Float }
 
 -- !!! do & where interaction
-module ShouldSucceed where
+module ShouldCompile where
 
 f1 :: IO a -> IO [a]
 f1 x = do
 
 -- !!! Empty export lists are legal (and useful.)
-module T () where
+module ShouldCompile () where
 
 ng1 x y = negate y
 
 
 -- !!! 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;;;;;}
 
 -- !!! Checking that both import lists and 'hiding' lists might
 -- !!! be empty.
-module ShouldSucceed where
+module ShouldCompile where
 
 import List  ()
 import List  hiding ()
 
 -- !!! Checking that empty declarations are permitted.
-module ShouldSucceed where
+module ShouldCompile where
 
 
 class Foo a where
 
 -- !!! Checking that empty contexts are permitted.
-module ShouldSucceed where
+module ShouldCompile where
 
 data () => Foo a = Foo a
 
 
 -- !!! Checking what's legal in the body of a class declaration.
-module ShouldSucceed where
+module ShouldCompile where
 
 class Foo a where {
   (--<>--) :: a -> a -> Int  ;
 
 -- !!! 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,(==))
 
 -- !!! Empty export list
 
-module Reader() where
+module ShouldCompile() where
 
 instance Show (a->b) where
   show f = "<<function>>"
 
 # 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
 
 
 
 -- !!! Re-exporting a module whose contents is partially hidden.
-module ShouldSucceed ( module List ) where
+module ShouldCompile ( module List ) where
 
 import List hiding ( sort )
 
 
 -- !!! 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
 
 -- !!! 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
 
 -- !!! 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 )
 
 y = x
 
 z :: Int
-z = ShouldSucceed.x
+z = ShouldCompile.x
 
 sortOf :: Ord a=> [a] -> [a]
 sortOf = List.sort
 
 -- !!! Checking that lazy name clashing works.
-module ShouldSucceed where
+module ShouldCompile where
 
 import List ( reverse, sort )
 
 reverse :: Int -- Clashes with List.reverse, 
 reverse = 3    -- but the only uses are qualified
 
-x = ShouldSucceed.reverse
+x = ShouldCompile.reverse
 
 y = List.reverse
 
 
 -- !!! 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
 
 -- !!! 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
 
 -- !!! 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 )
 
 y = x
 
 z :: Int
-z = ShouldSucceed.x
+z = ShouldCompile.x
 
 sortOf :: Ord a=> [a] -> [a]
 sortOf = List.sort
 
 -- !!! Checking that lazy name clashing works
-module ShouldSucceed where
+module ShouldCompile where
 
 import List ( sort )
 
 sort = 3
 
 foo :: Int
-foo = ShouldSucceed.sort
+foo = ShouldCompile.sort
 
 baz :: (Ord a) => [a] -> [a]
 baz = List.sort
 
 -- !!! Checking that empty declarations are permitted.
-module ShouldSucceed where
+module ShouldCompile where
 
 
 class Foo a where
 
 -- !!! Checking what's legal in the body of a class declaration.
-module ShouldSucceed where
+module ShouldCompile where
 
 class Foo a where {
   (--<>--) :: a -> a -> Int  ;
 
 -- !!! 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,(==))
 
 -- !!! Checking that you can hide a constructor
-module ShouldSucceed where
+module ShouldCompile where
 
 import Rn037Help hiding( C )
        -- C is the constructor, but we should
 
 -- 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
 
 -- !!! class/instance mumble that failed Lint at one time
 --
-module Test where
+module ShouldCompile where
 class Foo a where
    op :: Int -> a -> Bool
 
 
 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