6909250efb10f9b71314d2dc7397a3846f306750
[ghc-hetmet.git] / compiler / cmm / CmmContFlowOpt.hs
1
2 module CmmContFlowOpt
3     ( runCmmOpts, cmmCfgOpts, cmmCfgOptsZ
4     , branchChainElimZ, removeUnreachableBlocksZ, predMap
5     , replaceLabelsZ
6     )
7 where
8
9 import BlockId
10 import Cmm
11 import CmmTx
12 import qualified ZipCfg as G
13 import ZipCfgCmmRep
14
15 import Maybes
16 import Monad
17 import Panic
18 import Prelude hiding (unzip, zip)
19 import Util
20 import UniqFM
21
22 ------------------------------------
23 mapProcs :: Tx (GenCmmTop d h s) -> Tx (GenCmm d h s)
24 mapProcs f (Cmm tops) = fmap Cmm (mapTx f tops)
25
26
27 ------------------------------------
28 cmmCfgOpts  :: Tx (ListGraph CmmStmt)
29 cmmCfgOptsZ :: Tx CmmGraph
30
31 cmmCfgOpts  = branchChainElim  -- boring, but will get more exciting later
32 cmmCfgOptsZ =
33   branchChainElimZ `seqTx` blockConcatZ `seqTx` removeUnreachableBlocksZ
34         -- Here branchChainElim can ultimately be replaced
35         -- with a more exciting combination of optimisations
36
37 runCmmOpts :: Tx g -> Tx (GenCmm d h g)
38 runCmmOpts opt = mapProcs (optGraph opt)
39
40 optGraph :: Tx g -> Tx (GenCmmTop d h g)
41 optGraph _   top@(CmmData {}) = noTx top
42 optGraph opt (CmmProc info lbl formals g) = fmap (CmmProc info lbl formals) (opt g)
43
44 ----------------------------------------------------------------
45 branchChainElim :: Tx (ListGraph CmmStmt)
46 -- Remove any basic block of the form L: goto L',
47 -- and replace L with L' everywhere else
48 branchChainElim (ListGraph blocks)
49   | null lone_branch_blocks     -- No blocks to remove
50   = noTx (ListGraph blocks)
51   | otherwise
52   = aTx (ListGraph new_blocks)
53   where
54     (lone_branch_blocks, others) = partitionWith isLoneBranch blocks
55     new_blocks = map (replaceLabels env) others
56     env = mkClosureBlockEnv lone_branch_blocks
57
58 isLoneBranch :: CmmBasicBlock -> Either (BlockId, BlockId) CmmBasicBlock
59 isLoneBranch (BasicBlock id [CmmBranch target]) | id /= target = Left (id, target)
60 isLoneBranch other_block                                       = Right other_block
61    -- An infinite loop is not a link in a branch chain!
62
63 replaceLabels :: BlockEnv BlockId -> CmmBasicBlock -> CmmBasicBlock
64 replaceLabels env (BasicBlock id stmts)
65   = BasicBlock id (map replace stmts)
66   where
67     replace (CmmBranch id)       = CmmBranch (lookup id)
68     replace (CmmCondBranch e id) = CmmCondBranch e (lookup id)
69     replace (CmmSwitch e tbl)    = CmmSwitch e (map (fmap lookup) tbl)
70     replace other_stmt           = other_stmt
71
72     lookup id = lookupBlockEnv env id `orElse` id 
73 ----------------------------------------------------------------
74 branchChainElimZ :: Tx CmmGraph
75 -- Remove any basic block of the form L: goto L',
76 -- and replace L with L' everywhere else
77 branchChainElimZ g@(G.LGraph eid _)
78   | null lone_branch_blocks     -- No blocks to remove
79   = noTx g
80   | otherwise
81   = aTx $ replaceLabelsZ env $ G.of_block_list eid (self_branches ++ others)
82   where
83     (lone_branch_blocks, others) = partitionWith isLoneBranchZ (G.to_block_list g)
84     env = mkClosureBlockEnv lone_branch_blocks
85     self_branches =
86         let loop_to (id, _) =
87                 if lookup id == id then
88                     Just (G.Block id (G.ZLast (G.mkBranchNode id)))
89                 else
90                     Nothing
91         in  mapMaybe loop_to lone_branch_blocks
92     lookup id = lookupBlockEnv env id `orElse` id 
93
94 isLoneBranchZ :: CmmBlock -> Either (BlockId, BlockId) CmmBlock
95 isLoneBranchZ (G.Block id (G.ZLast (G.LastOther (LastBranch target))))
96     | id /= target  = Left (id,target)
97 isLoneBranchZ other = Right other
98    -- An infinite loop is not a link in a branch chain!
99
100 replaceLabelsZ :: BlockEnv BlockId -> CmmGraph -> CmmGraph
101 replaceLabelsZ env = replace_eid . G.map_nodes id id last
102   where
103     replace_eid (G.LGraph eid blocks) = G.LGraph (lookup eid) blocks
104     last (LastBranch id)              = LastBranch (lookup id)
105     last (LastCondBranch e ti fi)     = LastCondBranch e (lookup ti) (lookup fi)
106     last (LastSwitch e tbl)           = LastSwitch e (map (fmap lookup) tbl)
107     last (LastCall tgt (Just id))     = LastCall tgt (Just $ lookup id) 
108     last exit_jump_return             = exit_jump_return
109     lookup id = lookupBlockEnv env id `orElse` id 
110
111 ----------------------------------------------------------------
112 -- Build a map from a block to its set of predecessors. Very useful.
113 predMap :: G.LastNode l => G.LGraph m l -> BlockEnv BlockSet
114 predMap g = G.fold_blocks add_preds emptyBlockEnv g -- find the back edges
115   where add_preds b env = foldl (add b) env (G.succs b)
116         add (G.Block bid _) env b' =
117           extendBlockEnv env b' $
118                 extendBlockSet (lookupBlockEnv env b' `orElse` emptyBlockSet) bid
119 ----------------------------------------------------------------
120 blockConcatZ  :: Tx CmmGraph
121 -- If a block B branches to a label L, and L has no other predecessors,
122 -- then we can splice the block starting with L onto the end of B.
123 -- Because this optmization can be inhibited by unreachable blocks,
124 -- we bundle it with a pass that drops unreachable blocks.
125 -- Order matters, so we work bottom up (reverse postorder DFS).
126 -- Note: This optimization does _not_ subsume branch chain elimination.
127 blockConcatZ = removeUnreachableBlocksZ  `seqTx` blockConcatZ'
128 blockConcatZ' :: Tx CmmGraph
129 blockConcatZ' g@(G.LGraph eid blocks) = tx $ G.LGraph eid blocks'
130   where (changed, blocks') = foldr maybe_concat (False, blocks) $ G.postorder_dfs g
131         maybe_concat b@(G.Block bid _) (changed, blocks') =
132           let unchanged = (changed, extendBlockEnv blocks' bid b)
133           in case G.goto_end $ G.unzip b of
134                (h, G.LastOther (LastBranch b')) ->
135                   if num_preds b' == 1 then
136                     (True, extendBlockEnv blocks' bid $ splice blocks' h b')
137                   else unchanged
138                _ -> unchanged
139         num_preds bid = liftM sizeBlockSet (lookupBlockEnv backEdges bid) `orElse` 0
140         backEdges = predMap g
141         splice blocks' h bid' =
142           case lookupBlockEnv blocks' bid' of
143             Just (G.Block _ t) -> G.zip $ G.ZBlock h t
144             Nothing -> panic "unknown successor block"
145         tx = if changed then aTx else noTx
146 ----------------------------------------------------------------
147 mkClosureBlockEnv :: [(BlockId, BlockId)] -> BlockEnv BlockId
148 mkClosureBlockEnv blocks = mkBlockEnv $ map follow blocks
149     where singleEnv = mkBlockEnv blocks
150           follow (id, next) = (id, endChain id next)
151           endChain orig id = case lookupBlockEnv singleEnv id of
152                                Just id' | id /= orig -> endChain orig id'
153                                _ -> id
154 ----------------------------------------------------------------
155 removeUnreachableBlocksZ :: Tx CmmGraph
156 removeUnreachableBlocksZ g@(G.LGraph id blocks) =
157       if length blocks' < sizeUFM blocks then aTx $ G.of_block_list id blocks'
158       else noTx g
159     where blocks' = G.postorder_dfs g