diff options
author | simonpj <unknown> | 2002-09-13 15:02:50 +0000 |
---|---|---|
committer | simonpj <unknown> | 2002-09-13 15:02:50 +0000 |
commit | 9af77fa423926fbda946b31e174173d0ec5ebac8 (patch) | |
tree | 140cc94aa3e04f6e50c4bf07ceb0efe67d11b9c6 /ghc/compiler/codeGen | |
parent | 69e55e7476392a2b59b243a32065350c258d4970 (diff) | |
download | haskell-9af77fa423926fbda946b31e174173d0ec5ebac8.tar.gz |
[project @ 2002-09-13 15:02:25 by simonpj]
--------------------------------------
Make Template Haskell into the HEAD
--------------------------------------
This massive commit transfers to the HEAD all the stuff that
Simon and Tim have been doing on Template Haskell. The
meta-haskell-branch is no more!
WARNING: make sure that you
* Update your links if you are using link trees.
Some modules have been added, some have gone away.
* Do 'make clean' in all library trees.
The interface file format has changed, and you can
get strange panics (sadly) if GHC tries to read old interface files:
e.g. ghc-5.05: panic! (the `impossible' happened, GHC version 5.05):
Binary.get(TyClDecl): ForeignType
* You need to recompile the rts too; Linker.c has changed
However the libraries are almost unaltered; just a tiny change in
Base, and to the exports in Prelude.
NOTE: so far as TH itself is concerned, expression splices work
fine, but declaration splices are not complete.
---------------
The main change
---------------
The main structural change: renaming and typechecking have to be
interleaved, because we can't rename stuff after a declaration splice
until after we've typechecked the stuff before (and the splice
itself).
* Combine the renamer and typecheker monads into one
(TcRnMonad, TcRnTypes)
These two replace TcMonad and RnMonad
* Give them a single 'driver' (TcRnDriver). This driver
replaces TcModule.lhs and Rename.lhs
* The haskell-src library package has a module
Language/Haskell/THSyntax
which defines the Haskell data type seen by the TH programmer.
* New modules:
hsSyn/Convert.hs converts THSyntax -> HsSyn
deSugar/DsMeta.hs converts HsSyn -> THSyntax
* New module typecheck/TcSplice type-checks Template Haskell splices.
-------------
Linking stuff
-------------
* ByteCodeLink has been split into
ByteCodeLink (which links)
ByteCodeAsm (which assembles)
* New module ghci/ObjLink is the object-code linker.
* compMan/CmLink is removed entirely (was out of place)
Ditto CmTypes (which was tiny)
* Linker.c initialises the linker when it is first used (no need to call
initLinker any more). Template Haskell makes it harder to know when
and whether to initialise the linker.
-------------------------------------
Gathering the LIE in the type checker
-------------------------------------
* Instead of explicitly gathering constraints in the LIE
tcExpr :: RenamedExpr -> TcM (TypecheckedExpr, LIE)
we now dump the constraints into a mutable varabiable carried
by the monad, so we get
tcExpr :: RenamedExpr -> TcM TypecheckedExpr
Much less clutter in the code, and more efficient too.
(Originally suggested by Mark Shields.)
-----------------
Remove "SysNames"
-----------------
Because the renamer and the type checker were entirely separate,
we had to carry some rather tiresome implicit binders (or "SysNames")
along inside some of the HsDecl data structures. They were both
tiresome and fragile.
Now that the typechecker and renamer are more intimately coupled,
we can eliminate SysNames (well, mostly... default methods still
carry something similar).
-------------
Clean up HsPat
-------------
One big clean up is this: instead of having two HsPat types (InPat and
OutPat), they are now combined into one. This is more consistent with
the way that HsExpr etc is handled; there are some 'Out' constructors
for the type checker output.
So:
HsPat.InPat --> HsPat.Pat
HsPat.OutPat --> HsPat.Pat
No 'pat' type parameter in HsExpr, HsBinds, etc
Constructor patterns are nicer now: they use
HsPat.HsConDetails
for the three cases of constructor patterns:
prefix, infix, and record-bindings
The *same* data type HsConDetails is used in the type
declaration of the data type (HsDecls.TyData)
Lots of associated clean-up operations here and there. Less code.
Everything is wonderful.
Diffstat (limited to 'ghc/compiler/codeGen')
-rw-r--r-- | ghc/compiler/codeGen/CgCase.lhs | 2 | ||||
-rw-r--r-- | ghc/compiler/codeGen/CgClosure.lhs | 2 | ||||
-rw-r--r-- | ghc/compiler/codeGen/CgExpr.lhs | 2 | ||||
-rw-r--r-- | ghc/compiler/codeGen/CgHeapery.lhs | 2 | ||||
-rw-r--r-- | ghc/compiler/codeGen/CgLetNoEscape.lhs | 2 | ||||
-rw-r--r-- | ghc/compiler/codeGen/CgMonad.lhs | 2 | ||||
-rw-r--r-- | ghc/compiler/codeGen/CgRetConv.lhs | 2 | ||||
-rw-r--r-- | ghc/compiler/codeGen/CgStackery.lhs | 2 | ||||
-rw-r--r-- | ghc/compiler/codeGen/ClosureInfo.lhs | 2 | ||||
-rw-r--r-- | ghc/compiler/codeGen/CodeGen.lhs | 45 |
10 files changed, 31 insertions, 32 deletions
diff --git a/ghc/compiler/codeGen/CgCase.lhs b/ghc/compiler/codeGen/CgCase.lhs index fbc037ef5a..404e38510e 100644 --- a/ghc/compiler/codeGen/CgCase.lhs +++ b/ghc/compiler/codeGen/CgCase.lhs @@ -1,7 +1,7 @@ % % (c) The GRASP/AQUA Project, Glasgow University, 1992-1998 % -% $Id: CgCase.lhs,v 1.59 2002/09/04 10:00:45 simonmar Exp $ +% $Id: CgCase.lhs,v 1.60 2002/09/13 15:02:27 simonpj Exp $ % %******************************************************** %* * diff --git a/ghc/compiler/codeGen/CgClosure.lhs b/ghc/compiler/codeGen/CgClosure.lhs index 43b4146a56..2a6d941ee5 100644 --- a/ghc/compiler/codeGen/CgClosure.lhs +++ b/ghc/compiler/codeGen/CgClosure.lhs @@ -1,7 +1,7 @@ % % (c) The GRASP/AQUA Project, Glasgow University, 1992-1998 % -% $Id: CgClosure.lhs,v 1.57 2002/04/29 14:03:41 simonmar Exp $ +% $Id: CgClosure.lhs,v 1.58 2002/09/13 15:02:27 simonpj Exp $ % \section[CgClosure]{Code generation for closures} diff --git a/ghc/compiler/codeGen/CgExpr.lhs b/ghc/compiler/codeGen/CgExpr.lhs index 519cb652b5..a7cbef26e9 100644 --- a/ghc/compiler/codeGen/CgExpr.lhs +++ b/ghc/compiler/codeGen/CgExpr.lhs @@ -1,7 +1,7 @@ % % (c) The GRASP/AQUA Project, Glasgow University, 1992-1998 % -% $Id: CgExpr.lhs,v 1.50 2002/08/02 13:08:34 simonmar Exp $ +% $Id: CgExpr.lhs,v 1.51 2002/09/13 15:02:28 simonpj Exp $ % %******************************************************** %* * diff --git a/ghc/compiler/codeGen/CgHeapery.lhs b/ghc/compiler/codeGen/CgHeapery.lhs index 0d8e4d2de8..d41fcaf6b0 100644 --- a/ghc/compiler/codeGen/CgHeapery.lhs +++ b/ghc/compiler/codeGen/CgHeapery.lhs @@ -1,7 +1,7 @@ % % (c) The GRASP/AQUA Project, Glasgow University, 1992-1998 % -% $Id: CgHeapery.lhs,v 1.33 2002/09/04 10:00:46 simonmar Exp $ +% $Id: CgHeapery.lhs,v 1.34 2002/09/13 15:02:28 simonpj Exp $ % \section[CgHeapery]{Heap management functions} diff --git a/ghc/compiler/codeGen/CgLetNoEscape.lhs b/ghc/compiler/codeGen/CgLetNoEscape.lhs index db8dbcd5b2..521dc5cdd3 100644 --- a/ghc/compiler/codeGen/CgLetNoEscape.lhs +++ b/ghc/compiler/codeGen/CgLetNoEscape.lhs @@ -1,7 +1,7 @@ % % (c) The GRASP/AQUA Project, Glasgow University, 1993-1998 % -% $Id: CgLetNoEscape.lhs,v 1.17 2002/09/04 10:00:46 simonmar Exp $ +% $Id: CgLetNoEscape.lhs,v 1.18 2002/09/13 15:02:28 simonpj Exp $ % %******************************************************** %* * diff --git a/ghc/compiler/codeGen/CgMonad.lhs b/ghc/compiler/codeGen/CgMonad.lhs index 5c24825a9e..937c879758 100644 --- a/ghc/compiler/codeGen/CgMonad.lhs +++ b/ghc/compiler/codeGen/CgMonad.lhs @@ -1,7 +1,7 @@ % % (c) The GRASP/AQUA Project, Glasgow University, 1992-1998 % -% $Id: CgMonad.lhs,v 1.34 2002/04/29 14:03:42 simonmar Exp $ +% $Id: CgMonad.lhs,v 1.35 2002/09/13 15:02:28 simonpj Exp $ % \section[CgMonad]{The code generation monad} diff --git a/ghc/compiler/codeGen/CgRetConv.lhs b/ghc/compiler/codeGen/CgRetConv.lhs index cfb18bc7e5..825d748c05 100644 --- a/ghc/compiler/codeGen/CgRetConv.lhs +++ b/ghc/compiler/codeGen/CgRetConv.lhs @@ -1,7 +1,7 @@ % % (c) The GRASP Project, Glasgow University, 1992-1998 % -% $Id: CgRetConv.lhs,v 1.32 2002/08/02 13:08:34 simonmar Exp $ +% $Id: CgRetConv.lhs,v 1.33 2002/09/13 15:02:28 simonpj Exp $ % \section[CgRetConv]{Return conventions for the code generator} diff --git a/ghc/compiler/codeGen/CgStackery.lhs b/ghc/compiler/codeGen/CgStackery.lhs index cae8586b7c..58733cef55 100644 --- a/ghc/compiler/codeGen/CgStackery.lhs +++ b/ghc/compiler/codeGen/CgStackery.lhs @@ -1,7 +1,7 @@ % % (c) The GRASP/AQUA Project, Glasgow University, 1992-1998 % -% $Id: CgStackery.lhs,v 1.21 2002/08/29 15:44:13 simonmar Exp $ +% $Id: CgStackery.lhs,v 1.22 2002/09/13 15:02:29 simonpj Exp $ % \section[CgStackery]{Stack management functions} diff --git a/ghc/compiler/codeGen/ClosureInfo.lhs b/ghc/compiler/codeGen/ClosureInfo.lhs index 5840881330..d74a96d15e 100644 --- a/ghc/compiler/codeGen/ClosureInfo.lhs +++ b/ghc/compiler/codeGen/ClosureInfo.lhs @@ -1,7 +1,7 @@ % % (c) The GRASP/AQUA Project, Glasgow University, 1992-1998 % -% $Id: ClosureInfo.lhs,v 1.52 2002/04/29 14:03:43 simonmar Exp $ +% $Id: ClosureInfo.lhs,v 1.53 2002/09/13 15:02:29 simonpj Exp $ % \section[ClosureInfo]{Data structures which describe closures} diff --git a/ghc/compiler/codeGen/CodeGen.lhs b/ghc/compiler/codeGen/CodeGen.lhs index 76aa521612..51988973ff 100644 --- a/ghc/compiler/codeGen/CodeGen.lhs +++ b/ghc/compiler/codeGen/CodeGen.lhs @@ -31,7 +31,6 @@ import AbsCSyn import PrelNames ( gHC_PRIM ) import CLabel ( CLabel, mkSRTLabel, mkClosureLabel, mkPlainModuleInitLabel, mkModuleInitLabel ) - import PprAbsC ( dumpRealC ) import AbsCUtils ( mkAbstractCs, flattenAbsC ) import CgBindery ( CgIdInfo, addBindC, addBindsC, getCAddrModeAndInfo ) @@ -41,14 +40,15 @@ import CgConTbls ( genStaticConBits ) import ClosureInfo ( mkClosureLFInfo ) import CmdLineOpts ( DynFlags, DynFlag(..), opt_SccProfilingOn, opt_EnsureSplittableC ) +import HscTypes ( ModGuts(..), ModGuts, ForeignStubs(..), + typeEnvTyCons ) import CostCentre ( CollectedCCs ) import Id ( Id, idName, setIdName ) import Name ( nameSrcLoc, nameOccName, nameUnique, isInternalName, mkExternalName ) import OccName ( mkLocalOcc ) -import Module ( Module ) import PrimRep ( PrimRep(..) ) -import TyCon ( TyCon, isDataTyCon ) -import BasicTypes ( TopLevelFlag(..), Version ) +import TyCon ( isDataTyCon ) +import BasicTypes ( TopLevelFlag(..) ) import UniqSupply ( mkSplitUniqSupply ) import ErrUtils ( dumpIfSet_dyn, showPass ) import Panic ( assertPanic ) @@ -62,29 +62,27 @@ import DATA_IOREF ( readIORef ) \begin{code} codeGen :: DynFlags - -> Module -- Module name - -> [Module] -- Import names + -> ModGuts -> CollectedCCs -- (Local/global) cost-centres needing declaring/registering. - -> [Id] -- foreign-exported binders - -> [TyCon] -- Local tycons, including ones from classes -> [(StgBinding,[Id])] -- Bindings to convert, with SRTs -> IO AbstractC -- Output -codeGen dflags mod_name imported_modules cost_centre_info fe_binders - tycons stg_binds +codeGen dflags + mod_impl@(ModGuts { mg_module = mod_name, mg_types = type_env }) + cost_centre_info stg_binds = do showPass dflags "CodeGen" fl_uniqs <- mkSplitUniqSupply 'f' way <- readIORef v_Build_tag let + tycons = typeEnvTyCons type_env data_tycons = filter isDataTyCon tycons cinfo = MkCompInfo mod_name datatype_stuff = genStaticConBits cinfo data_tycons code_stuff = initC cinfo (mapCs cgTopBinding stg_binds) - init_stuff = mkModuleInit fe_binders mod_name way - imported_modules cost_centre_info + init_stuff = mkModuleInit way cost_centre_info mod_impl abstractC = mkAbstractCs [ maybeSplitCode, init_stuff, @@ -108,13 +106,14 @@ codeGen dflags mod_name imported_modules cost_centre_info fe_binders \begin{code} mkModuleInit - :: [Id] -- foreign exported functions - -> Module -- module name - -> String -- the "way" - -> [Module] -- import names + :: String -- the "way" -> CollectedCCs -- cost centre info + -> ModGuts -> AbstractC -mkModuleInit fe_binders mod way imps cost_centre_info +mkModuleInit way cost_centre_info + (ModGuts { mg_module = mod, + mg_foreign = ForeignStubs _ _ _ fe_binders, + mg_dir_imps = imported_modules }) = let register_fes = map (\f -> CMacroStmt REGISTER_FOREIGN_EXPORT [f]) fe_labels @@ -125,13 +124,13 @@ mkModuleInit fe_binders mod way imps cost_centre_info (cc_decls, cc_regs) = mkCostCentreStuff cost_centre_info -- we don't want/need to init GHC.Prim, so filter it out - mk_import_register imp - | imp == gHC_PRIM = AbsCNop - | otherwise = CMacroStmt REGISTER_IMPORT [ - CLbl (mkModuleInitLabel imp way) AddrRep - ] + mk_import_register mod + | mod == gHC_PRIM = AbsCNop + | otherwise = CMacroStmt REGISTER_IMPORT [ + CLbl (mkModuleInitLabel mod way) AddrRep + ] - register_imports = map mk_import_register imps + register_imports = map mk_import_register imported_modules in mkAbstractCs [ cc_decls, |