X-Git-Url: http://git.megacz.com/?p=ghc-hetmet.git;a=blobdiff_plain;f=compiler%2Fcmm%2FCmmCPS.hs;h=10f0efcd4d047b78ebd1a7f3ab58b8df13775c31;hp=4c1d025c8a497965e186ae853e2825b1010c5d65;hb=308af7d2ef52f02f28d8cea8142e49c278166198;hpb=53a82428d5e18a016dbc6b604d88577e7dc916e5 diff --git a/compiler/cmm/CmmCPS.hs b/compiler/cmm/CmmCPS.hs index 4c1d025..10f0efc 100644 --- a/compiler/cmm/CmmCPS.hs +++ b/compiler/cmm/CmmCPS.hs @@ -8,6 +8,8 @@ import PprCmm import Dataflow (fixedpoint) import CmmLive +import CmmCPSData +import CmmProcPoint import MachOp import ForeignCall @@ -45,25 +47,6 @@ import Data.List -- and heap memory (not sure if that's usefull at all though, but it may -- be worth exploring the design space). -data BrokenBlock - = BrokenBlock { - brokenBlockId :: BlockId, -- Like a CmmBasicBlock - brokenBlockEntry :: BlockEntryInfo, - -- How this block can be entered - - brokenBlockStmts :: [CmmStmt], - -- Like a CmmBasicBlock - -- (but without the last statement) - - brokenBlockTargets :: [BlockId], - -- Blocks that this block could - -- branch to one either by conditional - -- branches or via the last statement - - brokenBlockExit :: FinalStmt - -- How the block can be left - } - continuationLabel (Continuation _ _ l _ _) = l data Continuation = Continuation @@ -80,44 +63,6 @@ data Continuation = -- to a label. To jump to the first block in a Proc, -- use the appropriate CLabel. -data BlockEntryInfo - = FunctionEntry -- Beginning of a function - CLabel -- The function name - CmmFormals -- Aguments to function - - | ContinuationEntry -- Return point of a call - CmmFormals -- return values (argument to continuation) - -- TODO: - -- | ProcPointEntry -- no return values, but some live might end up as params or possibly in the frame - - | ControlEntry -- A label in the input - --- Final statement in a BlokenBlock --- Constructors and arguments match those in Cmm, --- but are restricted to branches, returns, jumps, calls and switches -data FinalStmt - = FinalBranch - BlockId -- next block (must be a ControlEntry) - - | FinalReturn - CmmActuals -- return values - - | FinalJump - CmmExpr -- the function to call - CmmActuals -- arguments to call - - | FinalCall - BlockId -- next block after call (must be a ContinuationEntry) - CmmCallTarget -- the function to call - CmmFormals -- results from call (redundant with ContinuationEntry) - CmmActuals -- arguments to call - (Maybe [GlobalReg]) -- registers that must be saved (TODO) - - | FinalSwitch - CmmExpr [Maybe BlockId] -- Table branch - - -- TODO: | ProcPointExit (needed?) - -- Describes the layout of a stack frame for a continuation data StackFormat = StackFormat @@ -129,75 +74,7 @@ data StackFormat -- A block can be a continuation of another block (w/ or w/o joins) -- A block can be an entry to a function -blocksToBlockEnv :: [BrokenBlock] -> BlockEnv BrokenBlock -blocksToBlockEnv blocks = listToUFM $ map (\b -> (brokenBlockId b, b)) blocks - ----------------------------------------------------------------------------- -calculateOwnership :: UniqSet BlockId -> [BrokenBlock] -> BlockEnv (UniqSet BlockId) -calculateOwnership proc_points blocks = - fixedpoint dependants update (map brokenBlockId blocks) emptyUFM - where - blocks_ufm :: BlockEnv BrokenBlock - blocks_ufm = blocksToBlockEnv blocks - - dependants :: BlockId -> [BlockId] - dependants ident = - brokenBlockTargets $ lookupWithDefaultUFM - blocks_ufm unknown_block ident - - update :: BlockId -> Maybe BlockId - -> BlockEnv (UniqSet BlockId) -> Maybe (BlockEnv (UniqSet BlockId)) - update ident cause owners = - case (cause, ident `elementOfUniqSet` proc_points) of - (Nothing, True) -> Just $ addToUFM owners ident (unitUniqSet ident) - (Nothing, False) -> Nothing - (Just cause', True) -> Nothing - (Just cause', False) -> - if (sizeUniqSet old) == (sizeUniqSet new) - then Nothing - else Just $ addToUFM owners ident new - where - old = lookupWithDefaultUFM owners emptyUniqSet ident - new = old `unionUniqSets` lookupWithDefaultUFM owners emptyUniqSet cause' - - unknown_block = panic "unknown BlockId in selectStackFormat" - -calculateProcPoints :: [BrokenBlock] -> UniqSet BlockId -calculateProcPoints blocks = calculateProcPoints' init_proc_points blocks - where - init_proc_points = mkUniqSet $ - map brokenBlockId $ - filter always_proc_point blocks - always_proc_point BrokenBlock { - brokenBlockEntry = FunctionEntry _ _ } = True - always_proc_point BrokenBlock { - brokenBlockEntry = ContinuationEntry _ } = True - always_proc_point _ = False - -calculateProcPoints' :: UniqSet BlockId -> [BrokenBlock] -> UniqSet BlockId -calculateProcPoints' old_proc_points blocks = - if sizeUniqSet old_proc_points == sizeUniqSet new_proc_points - then old_proc_points - else calculateProcPoints' new_proc_points blocks - where - owners = calculateOwnership old_proc_points blocks - new_proc_points = unionManyUniqSets (old_proc_points:(map (calculateProcPoints'' owners) blocks)) - -calculateProcPoints'' :: BlockEnv (UniqSet BlockId) -> BrokenBlock -> UniqSet BlockId -calculateProcPoints'' owners block = - unionManyUniqSets (map (f parent_id) child_ids) - where - parent_id = brokenBlockId block - child_ids = brokenBlockTargets block - -- TODO: name for f - f parent_id child_id = - if needs_proc_point - then unitUniqSet child_id - else emptyUniqSet - where - parent_owners = lookupWithDefaultUFM owners emptyUniqSet parent_id - child_owners = lookupWithDefaultUFM owners emptyUniqSet child_id - needs_proc_point = not $ isEmptyUniqSet $ child_owners `minusUniqSet` parent_owners collectNonProcPointTargets :: UniqSet BlockId -> BlockEnv BrokenBlock @@ -216,10 +93,10 @@ collectNonProcPointTargets proc_points blocks current_targets block = -- TODO: remove redundant uniqSetToList new_targets = current_targets `unionUniqSets` (mkUniqSet targets) -buildContinuation :: +procPointToContinuation :: UniqSet BlockId -> BlockEnv BrokenBlock -> BlockId -> Continuation -buildContinuation proc_points blocks start = +procPointToContinuation proc_points blocks start = Continuation is_entry info_table clabel params body where children = (collectNonProcPointTargets proc_points blocks (unitUniqSet start) start) `delOneFromUniqSet` start @@ -242,60 +119,8 @@ buildContinuation proc_points blocks start = -------------------------------------------------------------------------------- -- For now just select the continuation orders in the order they are in the set with no gaps -selectStackFormat :: BlockEnv CmmLive -> [BrokenBlock] -> BlockEnv StackFormat -selectStackFormat live blocks = - fixedpoint dependants update (map brokenBlockId blocks) emptyUFM - where - blocks_ufm :: BlockEnv BrokenBlock - blocks_ufm = listToUFM $ map (\b -> (brokenBlockId b, b)) blocks - - dependants :: BlockId -> [BlockId] - dependants ident = - brokenBlockTargets $ lookupWithDefaultUFM - blocks_ufm unknown_block ident - - update :: BlockId -> Maybe BlockId - -> BlockEnv StackFormat -> Maybe (BlockEnv StackFormat) - update ident cause formats = - if ident `elemUFM` formats - then Nothing -- Blocks only need to be updated once - else case (cause, - brokenBlockEntry $ lookupWithDefaultUFM blocks_ufm - unknown_block ident) of - -- Propagate only to blocks entered by branches - -- (not function entry blocks or continuation entry blocks) - (Just cause_name, ControlEntry) -> - Just $ addToUFM formats ident cause_format - where cause_format = lookupWithDefaultUFM - formats unknown_block - cause_name - -- Do initial calculates for function blocks - (Nothing, FunctionEntry _ _) -> - Just $ - addToUFM formats ident $ - StackFormat ident 0 [] - -- Do initial calculates for continuation blocks - (Nothing, ContinuationEntry _) -> - Just $ - addToUFM formats ident $ - live_to_format ident $ - lookupWithDefaultUFM live unknown_block ident - _ -> Nothing - - unknown_block = panic "unknown BlockId in selectStackFormat" - - live_to_format :: BlockId -> CmmLive -> StackFormat - live_to_format label live = - foldl extend_format - (StackFormat label retAddrSizeW []) - (uniqSetToList live) - - extend_format :: StackFormat -> LocalReg -> StackFormat - extend_format (StackFormat block size offsets) reg = - StackFormat block (slot_size reg + size) ((CmmLocal reg, size) : offsets) - -selectStackFormat2 :: BlockEnv CmmLive -> [Continuation] -> [(CLabel, StackFormat)] -selectStackFormat2 live continuations = +selectStackFormat :: BlockEnv CmmLive -> [Continuation] -> [(CLabel, StackFormat)] +selectStackFormat live continuations = map (\c -> (continuationLabel c, selectStackFormat' c)) continuations where selectStackFormat' (Continuation True info_table label formals blocks) = @@ -317,44 +142,45 @@ selectStackFormat2 live continuations = extend_format (StackFormat label size offsets) reg = StackFormat label (slot_size reg + size) ((CmmLocal reg, size) : offsets) - unknown_block = panic "unknown BlockId in selectStackFormat" - -slot_size reg = ((machRepByteWidth (localRegRep reg) - 1) `div` wORD_SIZE) + 1 + slot_size :: LocalReg -> Int + slot_size reg = ((machRepByteWidth (localRegRep reg) - 1) `div` wORD_SIZE) + 1 -constructContinuation :: [(CLabel, StackFormat)] -> Continuation -> CmmTop -constructContinuation formats (Continuation is_entry info label formals blocks) = - CmmProc info label formals (map (constructContinuation2' label formats) blocks) + unknown_block = panic "unknown BlockId in selectStackFormat" -constructContinuation2' :: CLabel -> [(CLabel, StackFormat)] -> BrokenBlock - -> CmmBasicBlock -constructContinuation2' curr_ident formats (BrokenBlock ident entry stmts _ exit) = - BasicBlock ident (prefix++stmts++postfix) +continuationToProc :: [(CLabel, StackFormat)] -> Continuation -> CmmTop +continuationToProc formats (Continuation is_entry info label formals blocks) = + CmmProc info label formals (map (continuationToProc' label formats) blocks) where - curr_format = maybe unknown_block id $ lookup curr_ident formats - unknown_block = panic "unknown BlockId in constructContinuation" - prefix = case entry of - ControlEntry -> [] - FunctionEntry _ _ -> [] - ContinuationEntry formals -> - unpack_continuation curr_format - postfix = case exit of - FinalBranch next -> [CmmBranch next] - FinalSwitch expr targets -> [CmmSwitch expr targets] - FinalReturn arguments -> - exit_function curr_format - (CmmLoad (CmmReg spReg) wordRep) - arguments - FinalJump target arguments -> - exit_function curr_format target arguments - -- TODO: do something about global saves - FinalCall next (CmmForeignCall target CmmCallConv) + continuationToProc' :: CLabel -> [(CLabel, StackFormat)] -> BrokenBlock + -> CmmBasicBlock + continuationToProc' curr_ident formats (BrokenBlock ident entry stmts _ exit) = + BasicBlock ident (prefix++stmts++postfix) + where + curr_format = maybe unknown_block id $ lookup curr_ident formats + unknown_block = panic "unknown BlockId in continuationToProc" + prefix = case entry of + ControlEntry -> [] + FunctionEntry _ _ -> [] + ContinuationEntry formals -> + unpack_continuation curr_format + postfix = case exit of + FinalBranch next -> [CmmBranch next] + FinalSwitch expr targets -> [CmmSwitch expr targets] + FinalReturn arguments -> + exit_function curr_format + (CmmLoad (CmmReg spReg) wordRep) + arguments + FinalJump target arguments -> + exit_function curr_format target arguments + -- TODO: do something about global saves + FinalCall next (CmmForeignCall target CmmCallConv) results arguments saves -> pack_continuation curr_format cont_format ++ [CmmJump target arguments] where cont_format = maybe unknown_block id $ lookup (mkReturnPtLabel $ getUnique next) formats - FinalCall next _ results arguments saves -> panic "unimplemented CmmCall" + FinalCall next _ results arguments saves -> panic "unimplemented CmmCall" -------------------------------------------------------------------------------- -- Functions that generate CmmStmt sequences @@ -505,9 +331,7 @@ cmmBlockFromBrokenBlock (BrokenBlock ident _ stmts _ exit) = cpsProc :: UniqSupply -> CmmTop -> [CmmTop] cpsProc uniqSupply x@(CmmData _ _) = [x] -cpsProc uniqSupply x@(CmmProc info_table ident params blocks) = - --[CmmProc info_table ident params cps_blocks] - cps_continuations +cpsProc uniqSupply x@(CmmProc info_table ident params blocks) = cps_procs where uniqes :: [[Unique]] uniqes = map uniqsFromSupply $ listSplitUniqSupply uniqSupply @@ -525,25 +349,21 @@ cpsProc uniqSupply x@(CmmProc info_table ident params blocks) = proc_points :: UniqSet BlockId proc_points = calculateProcPoints broken_blocks - continuations :: [Continuation] - continuations = map (buildContinuation proc_points (blocksToBlockEnv broken_blocks)) (uniqSetToList proc_points) - -- TODO: insert proc point code here -- * Branches and switches to proc points may cause new blocks to be created -- (or proc points could leave behind phantom blocks that just jump to them) -- * Proc points might get some live variables passed as arguments - -- TODO: let blocks_with_live = map (cmmLivenessComment live . snd) broken_blocks - - --procs = groupBlocksIntoContinuations live broken_blocks + continuations :: [Continuation] + continuations = map (procPointToContinuation proc_points (blocksToBlockEnv broken_blocks)) (uniqSetToList proc_points) -- Select the stack format on entry to each block - formats2 :: [(CLabel, StackFormat)] - formats2 = selectStackFormat2 live continuations + formats :: [(CLabel, StackFormat)] + formats = selectStackFormat live continuations -- Do the actual CPS transform - cps_continuations :: [CmmTop] - cps_continuations = map (constructContinuation formats2) continuations + cps_procs :: [CmmTop] + cps_procs = map (continuationToProc formats) continuations -------------------------------------------------------------------------------- cmmCPS :: DynFlags