X-Git-Url: http://git.megacz.com/?p=ghc-hetmet.git;a=blobdiff_plain;f=compiler%2Fcmm%2FCmmCPS.hs;h=f6a677a8fe4a022ea090a80cd81fbaf22c2269c2;hp=534346edb6d014b24852b547e23a56dfb2a57f4d;hb=d436c70d43fb905c63220040168295e473f4b90a;hpb=bb66ce578f2ef5cbeb35de9719f0839a32fbeb35 diff --git a/compiler/cmm/CmmCPS.hs b/compiler/cmm/CmmCPS.hs index 534346e..f6a677a 100644 --- a/compiler/cmm/CmmCPS.hs +++ b/compiler/cmm/CmmCPS.hs @@ -6,6 +6,7 @@ module CmmCPS ( #include "HsVersions.h" +import BlockId import Cmm import CmmLint import PprCmm @@ -18,7 +19,6 @@ import CmmCPSGen import CmmUtils import ClosureInfo -import MachOp import CLabel import SMRep import Constants @@ -28,7 +28,6 @@ import ErrUtils import Maybes import Outputable import UniqSupply -import UniqFM import UniqSet import Unique @@ -82,11 +81,11 @@ cpsProc :: UniqSupply -- multiple output procedures -- Data blocks don't need to be CPS transformed -cpsProc uniqSupply proc@(CmmData _ _) = [proc] +cpsProc _ proc@(CmmData _ _) = [proc] -- Empty functions just don't work with the CPS algorithm, but -- they don't need the transformation anyway so just output them directly -cpsProc uniqSupply proc@(CmmProc _ _ _ []) +cpsProc _ proc@(CmmProc _ _ _ (ListGraph [])) = pprTrace "cpsProc: unexpected empty proc" (ppr proc) [proc] -- CPS transform for those procs that actually need it @@ -97,7 +96,7 @@ cpsProc uniqSupply proc@(CmmProc _ _ _ []) -- * Now break each block into a bunch of blocks (at call sites); -- all but the first will be ContinuationEntry -- -cpsProc uniqSupply (CmmProc info ident params blocks) = cps_procs +cpsProc uniqSupply (CmmProc info ident params (ListGraph blocks)) = cps_procs where -- We need to be generating uniques for several things. -- We could make this function monadic to handle that @@ -110,7 +109,7 @@ cpsProc uniqSupply (CmmProc info ident params blocks) = cps_procs block_uniques = uniques proc_uniques = map (map (map uniqsFromSupply . listSplitUniqSupply) . listSplitUniqSupply) $ listSplitUniqSupply uniqSupply2 - stack_use = CmmLocal (LocalReg stack_use_unique (cmmRegRep spReg) KindPtr) + stack_use = CmmLocal (LocalReg stack_use_unique (cmmRegType spReg)) stack_check_block_id = BlockId stack_check_block_unique stack_check_block = make_stack_check stack_check_block_id info stack_use (blockId $ head blocks) @@ -182,6 +181,8 @@ cpsProc uniqSupply (CmmProc info ident params blocks) = cps_procs cps_procs :: [CmmTop] cps_procs = zipWith (continuationToProc formats' stack_use) proc_uniques continuations' +make_stack_check :: BlockId -> CmmInfo -> CmmReg -> BlockId + -> GenBasicBlock CmmStmt make_stack_check stack_check_block_id info stack_use next_block_id = BasicBlock stack_check_block_id $ check_stmts ++ [CmmBranch next_block_id] @@ -192,7 +193,7 @@ make_stack_check stack_check_block_id info stack_use next_block_id = -- then great, well check the stack. CmmInfo (Just gc_block) _ _ -> [CmmCondBranch - (CmmMachOp (MO_U_Lt $ cmmRegRep spReg) + (CmmMachOp (MO_U_Lt (typeWidth (cmmRegType spReg))) [CmmReg stack_use, CmmReg spLimReg]) gc_block] -- If we aren't given a stack check handler, @@ -212,7 +213,7 @@ collectNonProcPointTargets proc_points blocks current_targets new_blocks = new_targets (map (:[]) targets) where - blocks' = map (lookupWithDefaultUFM blocks (panic "TODO")) new_blocks + blocks' = map (lookupWithDefaultBEnv blocks (panic "TODO")) new_blocks targets = -- Note the subtlety that since the extra branch after a call -- will always be to a block that is a proc-point, @@ -234,8 +235,8 @@ gatherBlocksIntoContinuation live proc_points blocks start = Continuation info_table clabel params is_gc_cont body where children = (collectNonProcPointTargets proc_points blocks (unitUniqSet start) [start]) `minusUniqSet` (unitUniqSet start) - start_block = lookupWithDefaultUFM blocks unknown_block start - children_blocks = map (lookupWithDefaultUFM blocks unknown_block) (uniqSetToList children) + start_block = lookupWithDefaultBEnv blocks unknown_block start + children_blocks = map (lookupWithDefaultBEnv blocks unknown_block) (uniqSetToList children) unknown_block = panic "unknown block in gatherBlocksIntoContinuation" body = start_block : children_blocks @@ -261,7 +262,7 @@ gatherBlocksIntoContinuation live proc_points blocks start = ContinuationEntry args _ _ -> args ControlEntry -> uniqSetToList $ - lookupWithDefaultUFM live unknown_block start + lookupWithDefaultBEnv live unknown_block start -- it's a proc-point, pass lives in parameter registers -------------------------------------------------------------------------------- @@ -275,7 +276,7 @@ selectContinuationFormat live continuations = where -- User written continuations selectContinuationFormat' (Continuation - (Right (CmmInfo _ _ (CmmInfoTable _ _ (ContInfo format srt)))) + (Right (CmmInfo _ _ (CmmInfoTable _ _ _ (ContInfo format _)))) label formals _ _) = (formals, Just label, format) -- Either user written non-continuation code @@ -283,13 +284,13 @@ selectContinuationFormat live continuations = selectContinuationFormat' (Continuation (Right _) _ formals _ _) = (formals, Nothing, []) -- CPS generated continuations - selectContinuationFormat' (Continuation (Left srt) label formals _ blocks) = + selectContinuationFormat' (Continuation (Left _) label formals _ blocks) = -- TODO: assumes the first block is the entry block let ident = brokenBlockId $ head blocks -- TODO: CLabel isn't a uniquable, but we need a better way than this in (formals, Just label, map Just $ uniqSetToList $ - lookupWithDefaultUFM live unknown_block ident) + lookupWithDefaultBEnv live unknown_block ident) unknown_block = panic "unknown BlockId in selectContinuationFormat" @@ -322,7 +323,7 @@ processFormats formats update_frame continuations = update_size [] = 0 update_size (expr:exprs) = width + update_size exprs where - width = machRepByteWidth (cmmExprRep expr) `quot` wORD_SIZE + width = (widthInBytes $ typeWidth $ cmmExprType expr) `quot` wORD_SIZE -- TODO: it would be better if we had a machRepWordWidth -- TODO: get rid of "+ 1" etc. @@ -332,7 +333,7 @@ processFormats formats update_frame continuations = stack_size (Nothing:formats) = 1 + stack_size formats -- one dead word stack_size (Just reg:formats) = width + stack_size formats where - width = machRepByteWidth (localRegRep reg) `quot` wORD_SIZE + width = (widthInBytes $ typeWidth $ localRegType reg) `quot` wORD_SIZE -- TODO: it would be better if we had a machRepWordWidth continuationMaxStack :: [(CLabel, ContinuationFormat)] @@ -352,14 +353,14 @@ continuationMaxStack formats (Continuation _ label _ False blocks) = map stmt_arg_size (brokenBlockStmts block)) final_arg_size (FinalReturn args) = - argumentsSize (cmmExprRep . fst) args + argumentsSize (cmmExprType . hintlessCmm) args final_arg_size (FinalJump _ args) = - argumentsSize (cmmExprRep . fst) args - final_arg_size (FinalCall next _ _ args _ _ True) = 0 + argumentsSize (cmmExprType . hintlessCmm) args + final_arg_size (FinalCall _ _ _ _ _ _ True) = 0 final_arg_size (FinalCall next _ _ args _ _ False) = -- We have to account for the stack used when we build a frame -- for the *next* continuation from *this* continuation - argumentsSize (cmmExprRep . fst) args + + argumentsSize (cmmExprType . hintlessCmm) args + continuation_frame_size next_format where next_format = maybe unknown_format id $ lookup next' formats @@ -368,7 +369,7 @@ continuationMaxStack formats (Continuation _ label _ False blocks) = final_arg_size _ = 0 stmt_arg_size (CmmJump _ args) = - argumentsSize (cmmExprRep . fst) args + argumentsSize (cmmExprType . hintlessCmm) args stmt_arg_size (CmmCall _ _ _ (CmmSafe _) _) = panic "Safe call in processFormats" stmt_arg_size (CmmReturn _) = @@ -381,24 +382,25 @@ applyContinuationFormat :: [(CLabel, ContinuationFormat)] -> Continuation CmmInfo -- User written continuations -applyContinuationFormat formats (Continuation - (Right (CmmInfo gc update_frame (CmmInfoTable prof tag (ContInfo _ srt)))) - label formals is_gc blocks) = - Continuation (CmmInfo gc update_frame (CmmInfoTable prof tag (ContInfo format srt))) +applyContinuationFormat formats + (Continuation (Right (CmmInfo gc update_frame + (CmmInfoTable clos prof tag (ContInfo _ srt)))) + label formals is_gc blocks) = + Continuation (CmmInfo gc update_frame (CmmInfoTable clos prof tag (ContInfo format srt))) label formals is_gc blocks where format = continuation_stack $ maybe unknown_block id $ lookup label formats unknown_block = panic "unknown BlockId in applyContinuationFormat" -- Either user written non-continuation code or CPS generated proc-point -applyContinuationFormat formats (Continuation +applyContinuationFormat _ (Continuation (Right info) label formals is_gc blocks) = Continuation info label formals is_gc blocks -- CPS generated continuations applyContinuationFormat formats (Continuation (Left srt) label formals is_gc blocks) = - Continuation (CmmInfo gc Nothing (CmmInfoTable prof tag (ContInfo (continuation_stack $ format) srt))) + Continuation (CmmInfo gc Nothing (CmmInfoTable undefined prof tag (ContInfo (continuation_stack $ format) srt))) label formals is_gc blocks where gc = Nothing -- Generated continuations never need a stack check