diff options
Diffstat (limited to 'ghc/compiler/codeGen')
-rw-r--r-- | ghc/compiler/codeGen/CgCase.lhs | 4 | ||||
-rw-r--r-- | ghc/compiler/codeGen/CodeGen.lhs | 34 |
2 files changed, 20 insertions, 18 deletions
diff --git a/ghc/compiler/codeGen/CgCase.lhs b/ghc/compiler/codeGen/CgCase.lhs index ecd4a1cd01..07b1db4135 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.48 2000/11/07 15:21:39 simonmar Exp $ +% $Id: CgCase.lhs,v 1.49 2000/11/10 15:12:51 simonpj Exp $ % %******************************************************** %* * @@ -402,7 +402,7 @@ getPrimAppResultAmodes uniq (StgAlgAlts ty alts some_default) [ CTemp (getUnique arg) (idPrimRep arg) | arg <- args ] _ -> panic "getPrimAppResultAmodes: case of unboxed tuple has multiple branches" - | otherwise = panic ("getPrimAppResultAmodes: case of primop has strange type: " ++ showSDoc (ppr ty)) + | otherwise = pprPanic "getPrimAppResultAmodes: case of primop has strange type:" (ppr ty) where (tycon, _, _) = splitAlgTyConApp ty diff --git a/ghc/compiler/codeGen/CodeGen.lhs b/ghc/compiler/codeGen/CodeGen.lhs index 8eab80e904..462f0ff4d7 100644 --- a/ghc/compiler/codeGen/CodeGen.lhs +++ b/ghc/compiler/codeGen/CodeGen.lhs @@ -40,7 +40,7 @@ import PrimRep ( PrimRep(..) ) import TyCon ( TyCon, isDataTyCon ) import BasicTypes ( TopLevelFlag(..) ) import UniqSupply ( mkSplitUniqSupply ) -import ErrUtils ( dumpIfSet_dyn ) +import ErrUtils ( dumpIfSet_dyn, showPass ) import Panic ( assertPanic ) \end{code} @@ -60,26 +60,28 @@ codeGen :: DynFlags codeGen dflags mod_name imported_modules cost_centre_info fe_binders tycons stg_binds - = mkSplitUniqSupply 'f' >>= \ fl_uniqs -> -- absC flattener - let - datatype_stuff = genStaticConBits cinfo data_tycons - code_stuff = initC cinfo (cgTopBindings maybe_split stg_binds) - init_stuff = mkModuleInit fe_binders mod_name imported_modules - cost_centre_info - - abstractC = mkAbstractCs [ maybe_split, - init_stuff, - code_stuff, - datatype_stuff] + = do { showPass dflags "CodeGen" + + ; fl_uniqs <- mkSplitUniqSupply 'f' + ; let + datatype_stuff = genStaticConBits cinfo data_tycons + code_stuff = initC cinfo (cgTopBindings maybe_split stg_binds) + init_stuff = mkModuleInit fe_binders mod_name imported_modules + cost_centre_info + + abstractC = mkAbstractCs [ maybe_split, + init_stuff, + code_stuff, + datatype_stuff] -- Put datatype_stuff after code_stuff, because the -- datatype closure table (for enumeration types) -- to (say) PrelBase_True_closure, which is defined in code_stuff - flat_abstractC = flattenAbsC fl_uniqs abstractC - in - dumpIfSet_dyn dflags Opt_D_dump_absC "Abstract C" (dumpRealC abstractC) >> - return flat_abstractC + flat_abstractC = flattenAbsC fl_uniqs abstractC + ; dumpIfSet_dyn dflags Opt_D_dump_absC "Abstract C" (dumpRealC abstractC) + ; return flat_abstractC + } where data_tycons = filter isDataTyCon tycons |