X-Git-Url: http://git.megacz.com/?a=blobdiff_plain;f=ghc%2Fcompiler%2FcodeGen%2FCodeGen.lhs;h=fd5ef9d3a1712d0f3383e2b9d94e556b1455f12c;hb=d28ba8c800901bea01f70c4719278c2a364cf9fc;hp=bf6177df7fac7bcaaed5cad97f9cad2d34dfb78f;hpb=b1604ac09c517187251509d53c61607a09b62873;p=ghc-hetmet.git diff --git a/ghc/compiler/codeGen/CodeGen.lhs b/ghc/compiler/codeGen/CodeGen.lhs index bf6177d..fd5ef9d 100644 --- a/ghc/compiler/codeGen/CodeGen.lhs +++ b/ghc/compiler/codeGen/CodeGen.lhs @@ -24,11 +24,13 @@ module CodeGen ( codeGen ) where -- bother to compile it. import CgExpr ( {-NOTHING!-} ) -- DO NOT DELETE THIS IMPORT +import DriverState ( v_Build_tag, v_MainModIs ) import StgSyn import CgMonad import AbsCSyn -import CLabel ( CLabel, mkSRTLabel, mkClosureLabel, mkModuleInitLabel ) - +import PrelNames ( gHC_PRIM, dOLLAR_MAIN, mAIN_Name ) +import CLabel ( mkSRTLabel, mkClosureLabel, + mkPlainModuleInitLabel, mkModuleInitLabel ) import PprAbsC ( dumpRealC ) import AbsCUtils ( mkAbstractCs, flattenAbsC ) import CgBindery ( CgIdInfo, addBindC, addBindsC, getCAddrModeAndInfo ) @@ -38,64 +40,73 @@ import CgConTbls ( genStaticConBits ) import ClosureInfo ( mkClosureLFInfo ) import CmdLineOpts ( DynFlags, DynFlag(..), opt_SccProfilingOn, opt_EnsureSplittableC ) -import CostCentre ( CostCentre, CostCentreStack ) +import HscTypes ( ForeignStubs(..), TypeEnv, typeEnvTyCons ) +import CostCentre ( CollectedCCs ) import Id ( Id, idName, setIdName ) -import Name ( globaliseName ) -import Module ( Module ) +import Name ( nameSrcLoc, nameOccName, nameUnique, isInternalName, mkExternalName ) +import OccName ( mkLocalOcc ) import PrimRep ( PrimRep(..) ) -import TyCon ( TyCon, isDataTyCon ) +import TyCon ( isDataTyCon ) +import Module ( Module, mkModuleName ) import BasicTypes ( TopLevelFlag(..) ) import UniqSupply ( mkSplitUniqSupply ) import ErrUtils ( dumpIfSet_dyn, showPass ) import Panic ( assertPanic ) +import qualified Module ( moduleName ) #ifdef DEBUG -import Id ( idCafInfo ) -import IdInfo ( mayHaveCafRefs ) import Outputable #endif + +import DATA_IOREF ( readIORef ) \end{code} \begin{code} codeGen :: DynFlags - -> Module -- Module name - -> [Module] -- Import names - -> ([CostCentre], -- Local cost-centres needing declaring/registering - [CostCentre], -- "extern" cost-centres needing declaring - [CostCentreStack]) -- Pre-defined "singleton" cost centre stacks - -> [Id] -- foreign-exported binders - -> [TyCon] -- Local tycons, including ones from classes - -> [(StgBinding,[Id])] -- Bindings to convert, with SRTs + -> Module + -> TypeEnv + -> ForeignStubs + -> [Module] -- directly-imported modules + -> CollectedCCs -- (Local/global) cost-centres needing declaring/registering. + -> [(StgBinding,[(Id,[Id])])] -- Bindings to convert, with SRTs -> IO AbstractC -- Output -codeGen dflags mod_name imported_modules cost_centre_info fe_binders - tycons stg_binds - = do { showPass dflags "CodeGen" +codeGen dflags this_mod type_env foreign_stubs imported_mods + cost_centre_info stg_binds + = do + showPass dflags "CodeGen" + fl_uniqs <- mkSplitUniqSupply 'f' + way <- readIORef v_Build_tag + mb_main_mod <- readIORef v_MainModIs + + let + tycons = typeEnvTyCons type_env + data_tycons = filter isDataTyCon tycons + + mapM_ (\x -> seq x (return ())) data_tycons + + let + + cinfo = MkCompInfo this_mod - ; fl_uniqs <- mkSplitUniqSupply 'f' - ; let datatype_stuff = genStaticConBits cinfo data_tycons code_stuff = initC cinfo (mapCs cgTopBinding stg_binds) - init_stuff = mkModuleInit fe_binders mod_name imported_modules - cost_centre_info + init_stuff = mkModuleInit way cost_centre_info + this_mod mb_main_mod + foreign_stubs imported_mods abstractC = mkAbstractCs [ maybeSplitCode, 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 + -- datatype closure table (for enumeration types) to + -- (say) PrelBase_True_closure, which is defined in + -- code_stuff - ; dumpIfSet_dyn dflags Opt_D_dump_absC "Abstract C" (dumpRealC abstractC) - ; return flat_abstractC - } - where - data_tycons = filter isDataTyCon tycons + dumpIfSet_dyn dflags Opt_D_dump_absC "Abstract C" (dumpRealC abstractC) - cinfo = MkCompInfo mod_name + return $! flattenAbsC fl_uniqs abstractC \end{code} %************************************************************************ @@ -106,36 +117,59 @@ codeGen dflags mod_name imported_modules cost_centre_info fe_binders \begin{code} mkModuleInit - :: [Id] -- foreign exported functions - -> Module -- module name - -> [Module] -- import names - -> ([CostCentre], -- cost centre info - [CostCentre], - [CostCentreStack]) + :: String -- the "way" + -> CollectedCCs -- cost centre info + -> Module + -> Maybe String -- Just m ==> we have flag: -main-is Foo.baz + -> ForeignStubs + -> [Module] -> AbstractC -mkModuleInit fe_binders mod imps cost_centre_info +mkModuleInit way cost_centre_info this_mod mb_main_mod foreign_stubs imported_mods = let - register_fes = - map (\f -> CMacroStmt REGISTER_FOREIGN_EXPORT [f]) fe_labels - - fe_labels = - map (\f -> CLbl (mkClosureLabel (idName f)) PtrRep) fe_binders - (cc_decls, cc_regs) = mkCostCentreStuff cost_centre_info - mk_import_register imp = - CMacroStmt REGISTER_IMPORT [ - CLbl (mkModuleInitLabel imp) AddrRep - ] - - register_imports = map mk_import_register imps + register_foreign_exports + = case foreign_stubs of + NoStubs -> [] + ForeignStubs _ _ _ fe_bndrs -> map mk_export_register fe_bndrs + + mk_export_register bndr + = CMacroStmt REGISTER_FOREIGN_EXPORT [lbl] + where + lbl = CLbl (mkClosureLabel (idName bndr)) PtrRep + -- we don't want/need to init GHC.Prim, so filter it out + + mk_import_register mod + | mod == gHC_PRIM = AbsCNop + | otherwise = CMacroStmt REGISTER_IMPORT [ + CLbl (mkModuleInitLabel mod way) AddrRep + ] + + register_mod_imports = map mk_import_register imported_mods + + -- When compiling the module in which the 'main' function lives, + -- we inject an extra stg_init procedure for stg_init_zdMain, for the + -- RTS to invoke. We must consult the -main-is flag in case the + -- user specified a different function to Main.main + main_mod_name = case mb_main_mod of + Just mod_name -> mkModuleName mod_name + Nothing -> mAIN_Name + main_init_block + | Module.moduleName this_mod /= main_mod_name + = AbsCNop -- The normal case + | otherwise -- this_mod contains the main function + = CModuleInitBlock (mkPlainModuleInitLabel dOLLAR_MAIN) + (mkModuleInitLabel dOLLAR_MAIN way) + (mk_import_register this_mod) in mkAbstractCs [ cc_decls, - CModuleInitBlock (mkModuleInitLabel mod) - (mkAbstractCs (register_fes ++ + CModuleInitBlock (mkPlainModuleInitLabel this_mod) + (mkModuleInitLabel this_mod way) + (mkAbstractCs (register_foreign_exports ++ cc_regs : - register_imports)) + register_mod_imports)), + main_init_block ] \end{code} @@ -164,10 +198,10 @@ mkCostCentreStuff (local_CCs, extern_CCs, singleton_CCSs) [ register_ccs, register_cc_stacks ] where mk_register cc - = CCallProfCCMacro SLIT("REGISTER_CC") [mkCCostCentre cc] + = CCallProfCCMacro FSLIT("REGISTER_CC") [mkCCostCentre cc] mk_register_ccs ccs - = CCallProfCCMacro SLIT("REGISTER_CCS") [mkCCostCentreStack ccs] + = CCallProfCCMacro FSLIT("REGISTER_CCS") [mkCCostCentreStack ccs] \end{code} %************************************************************************ @@ -187,92 +221,98 @@ style, with the increasing static environment being plumbed as a state variable. \begin{code} -cgTopBinding :: (StgBinding,[Id]) -> Code -cgTopBinding (StgNonRec id rhs, srt) +cgTopBinding :: (StgBinding,[(Id,[Id])]) -> Code +cgTopBinding (StgNonRec id rhs, srts) = absC maybeSplitCode `thenC` - maybeGlobaliseId id `thenFC` \ id' -> - let - srt_label = mkSRTLabel (idName id') - in - mkSRT srt_label srt [] `thenC` - setSRTLabel srt_label ( - cgTopRhs id' rhs `thenFC` \ (id, info) -> - addBindC id info - ) - -cgTopBinding (StgRec pairs, srt) + maybeExternaliseId id `thenFC` \ id' -> + mapM_ (mkSRT [id']) srts `thenC` + cgTopRhs id' rhs `thenFC` \ (id, info) -> + addBindC id info `thenC` + -- Add the un-externalised Id to the envt, so we + -- find it when we look up occurrences + nopC + +cgTopBinding (StgRec pairs, srts) = absC maybeSplitCode `thenC` let (bndrs, rhss) = unzip pairs in - mapFCs maybeGlobaliseId bndrs `thenFC` \ bndrs'@(id:_) -> + mapFCs maybeExternaliseId bndrs `thenFC` \ bndrs' -> let - srt_label = mkSRTLabel (idName id) - pairs' = zip bndrs' rhss + pairs' = zip bndrs' rhss in - mkSRT srt_label srt bndrs' `thenC` - setSRTLabel srt_label ( - fixC (\ new_binds -> + mapM_ (mkSRT bndrs') srts `thenC` + fixC (\ new_binds -> addBindsC new_binds `thenC` mapFCs ( \ (b,e) -> cgTopRhs b e ) pairs' - ) `thenFC` \ new_binds -> nopC - ) + ) `thenFC` \ new_binds -> + nopC -mkSRT :: CLabel -> [Id] -> [Id] -> Code -mkSRT lbl [] these = nopC -mkSRT lbl ids these +mkSRT :: [Id] -> (Id,[Id]) -> Code +mkSRT these (id,[]) = nopC +mkSRT these (id,ids) = mapFCs remap ids `thenFC` \ ids -> - absC (CSRT lbl (map (mkClosureLabel . idName) ids)) + remap id `thenFC` \ id -> + absC (CSRT (mkSRTLabel (idName id)) (map (mkClosureLabel . idName) ids)) where -- sigh, better map all the ids against the environment in case they've - -- been globalised (see maybeGlobaliseId below). + -- been externalised (see maybeExternaliseId below). remap id = case filter (==id) these of [] -> getCAddrModeAndInfo id `thenFC` \ (id, _, _) -> returnFC id (id':_) -> returnFC id' --- if we're splitting the object, we need to globalise all the top-level names --- (and then make sure we only use the globalised one in any C label we use --- which refers to this name). -maybeGlobaliseId :: Id -> FCode Id -maybeGlobaliseId id - = moduleName `thenFC` \ mod -> - let - name = idName id - - -- globalise the name for -split-objs, if necessary - real_name | opt_EnsureSplittableC = globaliseName name mod - | otherwise = name - - id' = setIdName id real_name - in - returnFC id' - -maybeSplitCode - | opt_EnsureSplittableC = CSplitMarker - | otherwise = AbsCNop - -- Urgh! I tried moving the forkStatics call from the rhss of cgTopRhs -- to enclose the listFCs in cgTopBinding, but that tickled the -- statics "error" call in initC. I DON'T UNDERSTAND WHY! cgTopRhs :: Id -> StgRhs -> FCode (Id, CgIdInfo) - -- the Id is passed along for setting up a binding... + -- The Id is passed along for setting up a binding... + -- It's already been externalised if necessary cgTopRhs bndr (StgRhsCon cc con args) - = maybeGlobaliseId bndr `thenFC` \ bndr' -> - forkStatics (cgTopRhsCon bndr con args) - -cgTopRhs bndr (StgRhsClosure cc bi srt fvs upd_flag args body) - = -- There should be no free variables - ASSERT(null fvs) - -- If the closure is a thunk, then the binder must be recorded as such. - ASSERT2(not (isUpdatable upd_flag) || mayHaveCafRefs (idCafInfo bndr), ppr bndr) - - getSRTLabel `thenFC` \srt_label -> - let lf_info = - mkClosureLFInfo bndr TopLevel [{-no fvs-}] upd_flag args srt_label srt + = forkStatics (cgTopRhsCon bndr con args) + +cgTopRhs bndr (StgRhsClosure cc bi fvs upd_flag srt args body) + = ASSERT(null fvs) -- There should be no free variables + let + srt_label = mkSRTLabel (idName bndr) + lf_info = mkClosureLFInfo bndr TopLevel [{-no fvs-}] upd_flag args in - maybeGlobaliseId bndr `thenFC` \ bndr' -> - forkStatics (cgTopRhsClosure bndr' cc bi args body lf_info) + setSRTLabel srt_label $ + forkStatics (cgTopRhsClosure bndr cc bi srt args body lf_info) +\end{code} + + +%************************************************************************ +%* * +\subsection{Stuff to support splitting} +%* * +%************************************************************************ + +If we're splitting the object, we need to externalise all the top-level names +(and then make sure we only use the externalised one in any C label we use +which refers to this name). + +\begin{code} +maybeExternaliseId :: Id -> FCode Id +maybeExternaliseId id + | opt_EnsureSplittableC, -- Externalise the name for -split-objs + isInternalName name + = moduleName `thenFC` \ mod -> + returnFC (setIdName id (mkExternalName uniq mod new_occ (nameSrcLoc name))) + | otherwise + = returnFC id + where + name = idName id + uniq = nameUnique name + new_occ = mkLocalOcc uniq (nameOccName name) + -- We want to conjure up a name that can't clash with any + -- existing name. So we generate + -- Mod_$L243foo + -- where 243 is the unique. + +maybeSplitCode + | opt_EnsureSplittableC = CSplitMarker + | otherwise = AbsCNop \end{code}