diff options
author | dias@eecs.harvard.edu <unknown> | 2008-10-13 13:25:56 +0000 |
---|---|---|
committer | dias@eecs.harvard.edu <unknown> | 2008-10-13 13:25:56 +0000 |
commit | e6243a818496aad82b6f47511d3bd9bc800f747d (patch) | |
tree | a955151d25ddca7966ba8d23192ef62a47d84acf /compiler/codeGen/StgCmm.hs | |
parent | 176fa33f17dd78355cc572e006d2ab26898e2c69 (diff) | |
download | haskell-e6243a818496aad82b6f47511d3bd9bc800f747d.tar.gz |
Big collection of patches for the new codegen branch.
o Fixed bug that emitted the copy-in code for closure entry
in the wrong place -- at the initialization of the closure.
o Refactored some of the closure entry code.
o Added code to check that no LocalRegs are live-in to a procedure
-- trip up some buggy programs earlier
o Fixed environment bindings for thunks
-- we weren't (re)binding the free variables in a thunk
o Fixed a bug in proc-point splitting that dropped some updates
to the entry block in a procedure.
o Fixed improper calls to code that generates CmmLit's for strings
o New invariant on cg_loc in CgIdInfo: the expression is always tagged
o Code to load free vars on entry to a thunk was (wrongly) placed before
the heap check.
o Some of the StgCmm code was redundantly passing around Id's
along with CgIdInfo's; no more.
o Initialize the LocalReg's that point to a closure before allocating and
initializing the closure itself -- otherwise, we have problems with
recursive closure bindings
o BlockEnv and BlockSet types are now abstract.
o Update frames:
- push arguments in Old call area
- keep track of the return sp in the FCode monad
- keep the return sp in every call, tail call, and return
(because it might be different at different call sites,
e.g. tail calls to the gc after a heap check are performed
before pushing the update frame)
- set the sp appropriately on returns and tail calls
o Reduce call, tail call, and return to a single LastCall node
o Added slow entry code, using different calling conventions on entry and tail call
o More fixes to the calling convention code.
The tricky stuff is all about the closure environment: it must be passed in R1,
but in non-closures, there is no such argument, so we can't treat all arguments
the same way: the closure environment is special. Maybe the right step forward
would be to define a different calling convention for closure arguments.
o Let-no-escapes need to be emitted out-of-line -- otherwise, we drop code.
o Respect RTS requirement of word alignment for pointers
My stack allocation can pack sub-word values into a single word on the stack,
but it wasn't requiring word-alignment for pointers. It does now,
by word-aligning both pointer registers and call areas.
o CmmLint was over-aggresively ruling out non-word-aligned memory references,
which may be kosher now that we can spill small values into a single word.
o Wrong label order on a conditional branch when compiling switches.
o void args weren't dropped in many cases.
To help prevent this kind of mistake, I defined a NonVoid wrapper,
which I'm applying only to Id's for now, although there are probably
other good candidates.
o A little code refactoring: separate modules for procpoint analysis splitting,
stack layout, and building infotables.
o Stack limit check: insert along with the heap limit check, using a symbolic
constant (a special CmmLit), then replace it when the stack layout is known.
o Removed last node: MidAddToContext
o Adding block id as a literal: means that the lowering of the calling conventions
no longer has to produce labels early, which was inhibiting common-block elimination.
Will also make it easier for the non-procpoint-splitting path.
o Info tables: don't try to describe the update frame!
o Over aggressive use of NonVoid!!!!
Don't drop the non-void args before setting the type of the closure!!!
o Sanity checking:
Added a pass to stub dead dead slots on the stack
(only ~10 lines with the dataflow framework)
o More sanity checking:
Check that incoming pointer arguments are non-stubbed.
Note: these checks are still subject to dead-code removal, but they should
still be quite helpful.
o Better sanity checking: why stop at function arguments?
Instead, in mkAssign, check that _any_ assignment to a pointer type is non-null
-- the sooner the crash, the easier it is to debug.
Still need to add the debugging flag to turn these checks on explicitly.
o Fixed yet another calling convention bug.
This time, the calls to the GC were wrong. I've added a new convention
for GC calls and invoked it where appropriate.
We should really straighten out the calling convention stuff:
some of the code (and documentation) is spread across the compiler,
and there's some magical use of the node register that should really
be handled (not avoided) by calling conventions.
o Switch bug: the arms in mkCmmLitSwitch weren't returning to a single join point.
o Environment shadowing problem in Stg->Cmm:
When a closure f is bound at the top-level, we should not bind f to the
node register on entry to the closure.
Why? Because if the body of f contains a let-bound closure g that refers
to f, we want to make sure that it refers to the static closure for f.
Normally, this would all be fine, because when we compile a closure,
we rebind free variables in the environment. But f doesn't look like
a free variable because it's a static value. So, the binding for f
remains in the environment when we compile g, inconveniently referring
to the wrong thing.
Now, I bind the variable in the local environment only if the closure is not
bound at the top level. It's still okay to make assumptions about the
node holding the closure environment; we just won't find the binding
in the environment, so code that names the closure will now directly
get the label of the static closure, not the node register holding a
pointer to the static closure.
o Don't generate bogus Cmm code containing SRTs during the STG -> Cmm pass!
The tables made reference to some labels that don't exist when we compute and
generate the tables in the back end.
o Safe foreign calls need some special treatment (at least until we have the integrated
codegen). In particular:
o they need info tables
o they are not procpoints -- the successor had better be in the same procedure
o we cannot (yet) implement the calling conventions early, which means we have
to carry the calling-conv info all the way to the end
o We weren't following the old convention when registering a module.
Now, we use update frames to push any new modules that have to be registered
and enter the youngest one on the stack.
We also use the update frame machinery to specify that the return should pop
the return address off the stack.
o At each safe foreign call, an infotable must be at the bottom of the stack,
and the TSO->sp must point to it.
o More problems with void args in a direct call to a function:
We were checking the args (minus voids) to check whether the call was saturated,
which caused problems when the function really wasn't saturated because it
took an extra void argument.
o Forgot to distinguish integer != from floating != during Stg->Cmm
o Updating slotEnv and areaMap to include safe foreign calls
The dataflow analyses that produce the slotEnv and areaMap give
results for each basic block, but we also need the results for
a safe foreign call, which is a middle node.
After running the dataflow analysis, we have another pass that
updates the results to includ any safe foreign calls.
o Added a static flag for the debugging technique that inserts
instructions to stub dead slots on the stack and crashes when
a stubbed value is loaded into a pointer-typed LocalReg.
o C back end expects to see return continuations before their call sites.
Sorted the flowgraphs appropriately after splitting.
o PrimOp calling conventions are special -- unlimited registers, no stack
Yet another calling convention...
o More void value problems: if the RHS of a case arm is a void-typed variable,
don't try to return it.
o When calling some primOp, they may allocate memory; if so, we need to
do a heap check when we return from the call.
Diffstat (limited to 'compiler/codeGen/StgCmm.hs')
-rw-r--r-- | compiler/codeGen/StgCmm.hs | 81 |
1 files changed, 30 insertions, 51 deletions
diff --git a/compiler/codeGen/StgCmm.hs b/compiler/codeGen/StgCmm.hs index 56cd1d5555..0fc6c4c5a8 100644 --- a/compiler/codeGen/StgCmm.hs +++ b/compiler/codeGen/StgCmm.hs @@ -104,43 +104,25 @@ variable. -} cgTopBinding :: DynFlags -> (StgBinding,[(Id,[Id])]) -> FCode () cgTopBinding dflags (StgNonRec id rhs, _srts) = do { id' <- maybeExternaliseId dflags id - --; mapM_ (mkSRT [id']) srts - ; (id,info) <- cgTopRhs id' rhs - ; addBindC id info -- Add the *un-externalised* Id to the envt, - -- so we find it when we look up occurrences + ; info <- cgTopRhs id' rhs + ; addBindC (cg_id info) info -- Add the *un-externalised* Id to the envt, + -- so we find it when we look up occurrences } cgTopBinding dflags (StgRec pairs, _srts) = do { let (bndrs, rhss) = unzip pairs ; bndrs' <- mapFCs (maybeExternaliseId dflags) bndrs ; let pairs' = zip bndrs' rhss - --; mapM_ (mkSRT bndrs') srts ; fixC (\ new_binds -> do { addBindsC new_binds ; mapFCs ( \ (b,e) -> cgTopRhs b e ) pairs' }) ; return () } ---mkSRT :: [Id] -> (Id,[Id]) -> FCode () ---mkSRT these (id,ids) --- | null ids = nopC --- | otherwise --- = do { ids <- mapFCs remap ids --- ; id <- remap id --- ; emitRODataLits (mkSRTLabel (idName id) (idCafInfo id)) --- (map (\id -> CmmLabel $ mkClosureLabel (idName id) (idCafInfo id)) ids) --- } --- where --- -- Sigh, better map all the ids against the environment in --- -- case they've been externalised (see maybeExternaliseId below). --- remap id = case filter (==id) these of --- (id':_) -> returnFC id' --- [] -> do { info <- getCgIdInfo id; return (cgIdInfoId info) } - -- 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) +cgTopRhs :: Id -> StgRhs -> FCode CgIdInfo -- The Id is passed along for setting up a binding... -- It's already been externalised if necessary @@ -153,7 +135,6 @@ cgTopRhs bndr (StgRhsClosure cc bi fvs upd_flag srt args body) forkStatics (cgTopRhsClosure bndr cc bi upd_flag srt args body) - --------------------------------------------------------------- -- Module initialisation code --------------------------------------------------------------- @@ -213,14 +194,17 @@ mkModuleInit way cost_centre_info this_mod main_mod imported_mods hpc_info -- In this way, Hpc enabled modules can interact seamlessly with -- not Hpc enabled moduled, provided Main is compiled with Hpc. - ; emitSimpleProc real_init_lbl $ withFreshLabel "ret_block" $ \retId -> catAGraphs - [ check_already_done retId + ; updfr_sz <- getUpdFrameOff + ; tail <- getCode (pushUpdateFrame imports + (do updfr_sz' <- getUpdFrameOff + emit $ mkReturn (ret_e updfr_sz') [] (pop_ret_loc updfr_sz'))) + ; emitSimpleProc real_init_lbl $ (withFreshLabel "ret_block" $ \retId -> catAGraphs + [ check_already_done retId updfr_sz , init_prof , init_hpc - , catAGraphs $ map (registerImport way) all_imported_mods - , mkBranch retId ] + , tail]) -- Make the "plain" procedure jump to the "real" init procedure - ; emitSimpleProc plain_init_lbl jump_to_init + ; emitSimpleProc plain_init_lbl (jump_to_init updfr_sz) -- When compiling the module in which the 'main' function lives, -- (that is, this_mod == main_mod) @@ -233,14 +217,14 @@ mkModuleInit way cost_centre_info this_mod main_mod imported_mods hpc_info ; whenC (this_mod == main_mod) - (emitSimpleProc plain_main_init_lbl rec_descent_init) + (emitSimpleProc plain_main_init_lbl (rec_descent_init updfr_sz)) } where plain_init_lbl = mkPlainModuleInitLabel this_mod real_init_lbl = mkModuleInitLabel this_mod way plain_main_init_lbl = mkPlainModuleInitLabel rOOT_MAIN - jump_to_init = mkJump (mkLblExpr real_init_lbl) [] + jump_to_init updfr_sz = mkJump (mkLblExpr real_init_lbl) [] updfr_sz -- Main refers to GHC.TopHandler.runIO, so make sure we call the @@ -249,34 +233,30 @@ mkModuleInit way cost_centre_info this_mod main_mod imported_mods hpc_info | this_mod == main_mod = [gHC_TOP_HANDLER] | otherwise = [] all_imported_mods = imported_mods ++ extra_imported_mods + imports = map (\mod -> mkLblExpr (mkModuleInitLabel mod way)) + (filter (gHC_PRIM /=) all_imported_mods) mod_reg_val = CmmLoad (mkLblExpr moduleRegdLabel) bWord - check_already_done retId + check_already_done retId updfr_sz = mkCmmIfThenElse (cmmNeWord (CmmLit zeroCLit) mod_reg_val) - (mkLabel retId Nothing <*> mkReturn []) mkNop + (mkLabel retId emptyStackInfo + <*> mkReturn (ret_e updfr_sz) [] (pop_ret_loc updfr_sz)) mkNop <*> -- Set mod_reg to 1 to record that we've been here mkStore (mkLblExpr moduleRegdLabel) (CmmLit (mkIntCLit 1)) -- The return-code pops the work stack by - -- incrementing Sp, and then jumpd to the popped item - ret_code = mkAssign spReg (cmmRegOffW spReg 1) - <*> mkJump (CmmLoad (cmmRegOffW spReg (-1)) bWord) [] - - rec_descent_init = if opt_SccProfilingOn || isHpcUsed hpc_info - then jump_to_init - else ret_code - ------------------------ -registerImport :: String -> Module -> CmmAGraph -registerImport way mod - | mod == gHC_PRIM - = mkNop - | otherwise -- Push the init procedure onto the work stack - = mkCmmCall init_lbl [] [] NoC_SRT - where - init_lbl = mkLblExpr $ mkModuleInitLabel mod way + -- incrementing Sp, and then jumps to the popped item + ret_e updfr_sz = CmmLoad (CmmStackSlot (CallArea Old) updfr_sz) gcWord + ret_code updfr_sz = mkJump (ret_e updfr_sz) [] (pop_ret_loc updfr_sz) + -- mkAssign spReg (cmmRegOffW spReg 1) <*> + -- mkJump (CmmLoad (cmmRegOffW spReg (-1)) bWord) [] updfr_sz + pop_ret_loc updfr_sz = updfr_sz - widthInBytes (typeWidth bWord) + rec_descent_init updfr_sz = + if opt_SccProfilingOn || isHpcUsed hpc_info + then jump_to_init updfr_sz + else ret_code updfr_sz --------------------------------------------------------------- -- Generating static stuff for algebraic data types @@ -351,8 +331,7 @@ cgDataCon data_con (dyn_cl_info, arg_things) = layOutDynConstr data_con arg_reps emit_info cl_info ticky_code - = do { code_blks <- getCode (mk_code ticky_code) - ; emitClosureCodeAndInfoTable cl_info [] code_blks } + = emitClosureAndInfoTable cl_info [] $ mk_code ticky_code mk_code ticky_code = -- NB: We don't set CC when entering data (WDP 94/06) |