Fixed liveness analysis to use a slower but more correct solution
[ghc-hetmet.git] / compiler / cmm / Dataflow.hs
1 module Dataflow (mapCmmTop, onBasicBlock, cmmLivenessComment, cmmLiveness) where
2
3 import Cmm
4 import PprCmm ()
5
6 import UniqSet
7 import UniqFM
8
9 import FastString
10 import Outputable
11
12 import Maybes
13
14 import Data.List
15 import Data.Maybe
16
17 cmmBranchSources :: [(BlockId, [BlockId])] -> [(BlockId, [BlockId])]
18 cmmBranchSources input =
19     [(target, [s | (s, ts) <- input, target `elem` ts])
20      | target <- targets] where
21         targets = nub [t | (s, ts) <- input, t <- ts]
22
23 cmmBranchTargets :: CmmBasicBlock -> UniqSet BlockId
24 cmmBranchTargets (BasicBlock _ stmts) =
25     mkUniqSet $ concatMap target stmts where
26         target (CmmBranch ident) = [ident]
27         target (CmmCondBranch _ ident) = [ident]
28         target (CmmSwitch _ blocks) = mapMaybe id blocks
29         target _ = []
30
31 --------------------------------------------------------------------------------
32
33 -- This should really be a state monad, but that is not in the core libraries
34 -- so we'll hack around it here.
35 -- The monad we're using is: type State a = s -> s
36
37 -- The variables that were made live and killed respectively
38 type CmmLive = UniqSet LocalReg
39 addLive new_live live = live `unionUniqSets` new_live
40 addKilled new_killed live = live `minusUniqSet` new_killed
41
42 -- Calculate the live and killed registers for a local block
43 cmmBlockLive :: UniqFM {-BlockId-} CmmLive -> CmmBasicBlock -> CmmLive
44 cmmBlockLive other_live (BasicBlock _ stmts) =
45     foldr ((.) . (cmmStmtLive other_live)) id stmts emptyUniqSet
46
47 -- Helper for cmmLocalLiveness
48 cmmStmtLive :: UniqFM {-BlockId-} CmmLive -> CmmStmt -> (CmmLive -> CmmLive)
49 cmmStmtLive _ (CmmNop) = id
50 cmmStmtLive _ (CmmComment _) = id
51 cmmStmtLive _ (CmmAssign reg expr) =
52     cmmExprLive expr . reg_liveness where
53         reg_liveness =
54             case reg of
55               (CmmLocal reg') -> addKilled $ unitUniqSet reg'
56               (CmmGlobal _) -> id
57 cmmStmtLive _ (CmmStore expr1 expr2) =
58     cmmExprLive expr2 . cmmExprLive expr1
59 cmmStmtLive _ (CmmCall target results arguments _) =
60     target_liveness .
61     foldr ((.) . cmmExprLive) id (map fst arguments) .
62     addKilled (mkUniqSet $ only_local_regs results) where
63         only_local_regs [] = []
64         only_local_regs ((CmmGlobal _,_):args) = only_local_regs args
65         only_local_regs ((CmmLocal r,_):args) = r:only_local_regs args
66         target_liveness =
67             case target of
68               (CmmForeignCall target _) -> cmmExprLive target
69               (CmmPrim _) -> id
70 cmmStmtLive other_live (CmmBranch target) = addLive (lookupWithDefaultUFM other_live emptyUniqSet target)
71 cmmStmtLive other_live (CmmCondBranch expr target) = cmmExprLive expr . addLive (lookupWithDefaultUFM other_live emptyUniqSet target)
72 cmmStmtLive other_live (CmmSwitch expr targets) =
73     cmmExprLive expr .
74     (foldr ((.) . (addLive . lookupWithDefaultUFM other_live emptyUniqSet)) id (mapCatMaybes id targets))
75 cmmStmtLive _ (CmmJump expr params) =
76     const (cmmExprLive expr (mkUniqSet params))
77
78 --------
79
80 -- Helper for cmmLocalLiveness
81 cmmExprLive :: CmmExpr -> (CmmLive -> CmmLive)
82 cmmExprLive expr = addLive (mkUniqSet $ expr_liveness expr) where
83     expr_liveness (CmmLit _) = []
84     expr_liveness (CmmLoad expr _) = expr_liveness expr
85     expr_liveness (CmmReg reg) = reg_liveness reg
86     expr_liveness (CmmMachOp _ exprs) = concatMap expr_liveness exprs
87     expr_liveness (CmmRegOff reg _) = reg_liveness reg
88     reg_liveness (CmmLocal reg) = [reg]
89     reg_liveness (CmmGlobal _) = []
90
91 cmmBlockUpdate ::
92     UniqFM {-BlockId-} CmmBasicBlock
93     -> BlockId
94     -> Maybe BlockId
95     -> UniqFM {-BlockId-} CmmLive
96     -> Maybe (UniqFM {-BlockId-} CmmLive)
97 cmmBlockUpdate blocks node _ state =
98     let old_live = lookupWithDefaultUFM state emptyUniqSet node
99         block = lookupWithDefaultUFM blocks (panic "unknown block id during liveness analysis") node
100         new_live = cmmBlockLive state block
101     in if (sizeUniqSet old_live) == (sizeUniqSet new_live)
102        then Nothing
103        else Just $ addToUFM state node new_live
104
105 cmmBlockDependants :: UniqFM {-BlockId-} (UniqSet BlockId) -> BlockId -> [BlockId]
106 cmmBlockDependants sources ident =
107     uniqSetToList $ lookupWithDefaultUFM sources emptyUFM ident
108
109 cmmBlockSourcesAndTargets ::
110     [CmmBasicBlock]
111     -> (UniqFM {-BlockId-} (UniqSet BlockId), UniqFM (UniqSet BlockId))
112 cmmBlockSourcesAndTargets blocks = foldr aux (emptyUFM, emptyUFM) blocks where
113     aux block (sourcesUFM, targetsUFM)  =
114         (foldUniqSet add_source_edges sourcesUFM targets,
115          addToUFM_Acc unionUniqSets id targetsUFM ident targets) where
116             add_source_edges t ufm =
117                 addToUFM_Acc (flip addOneToUniqSet) unitUniqSet ufm t ident
118             targets = cmmBranchTargets block
119             ident = blockId block
120
121 cmmBlockNames :: [CmmBasicBlock] -> UniqFM {-BlockId-} CmmBasicBlock
122 cmmBlockNames blocks = listToUFM $ map block_name blocks where
123     block_name b = (blockId b, b)
124
125 cmmLiveness :: [CmmBasicBlock] -> UniqFM {-BlockId-} CmmLive
126 cmmLiveness blocks =
127     fixedpoint (cmmBlockDependants sources) (cmmBlockUpdate blocks')
128                (map blockId blocks) emptyUFM where
129                    (sources, targets) = cmmBlockSourcesAndTargets blocks
130                    blocks' = cmmBlockNames blocks
131
132 cmmLivenessComment ::
133     UniqFM {-BlockId-} (UniqSet LocalReg)
134     -> CmmBasicBlock -> CmmBasicBlock
135 cmmLivenessComment live (BasicBlock ident stmts) =
136     BasicBlock ident stmts' where
137         stmts' = (CmmComment $ mkFastString $ showSDoc $ ppr $ live'):stmts
138         live' = map CmmLocal $ uniqSetToList $ lookupWithDefaultUFM live emptyUniqSet ident
139
140 onBasicBlock f (CmmProc ds ident args blocks) = CmmProc ds ident args (f blocks)
141 onBasicBlock f x = x
142
143 mapCmmTop f (Cmm xs) = Cmm (map f xs)
144
145 --------------------------------------------------------------------------------
146
147 -- Solve a fixed-point of a dataflow problem.
148 -- O(N+H*E) calls to update where
149 --   N = number of nodes,
150 --   E = number of edges,
151 --   H = maximum height of the lattice for any particular node.
152 -- dependants: map from nodes to those who's value depend on the argument node
153 -- update:
154 --   Given the node which needs to be updated, and
155 --   which node caused that node to need to be updated,
156 --   update the state.
157 --   (The causing node will be 'Nothing' if this is the initial update.)
158 --   Must return 'Nothing' if no change,
159 --   otherwise returrn 'Just' of the new state
160 -- nodes: a set of nodes that initially need updating
161 -- state: some sort of state (usually a map)
162 --        containing the initial value for each node
163 --
164 -- Sketch for proof of complexity:
165 -- Note that the state is threaded through the entire execution.
166 -- Also note that the height of the latice at any particular node
167 -- is the number of times 'update' can return non-Nothing for a particular node.
168 -- Every call (except for the top level one) must be caused by a non-Nothing
169 -- result and each non-Nothing result causes as many calls as it has
170 -- out-going edges.  Thus any particular node, n, may cause in total
171 -- at most H*out(n) further calls.  When summed over all nodes,
172 -- that is H*E.  The N term of the complexity is from the initial call
173 -- when 'update' will be passed 'Nothing'.
174 fixedpoint ::
175     (node -> [node])
176     -> (node -> Maybe node -> s -> Maybe s)
177     -> [node] -> s -> s
178 fixedpoint dependants update nodes state =
179     foldr (fixedpoint' Nothing) state nodes where
180         fixedpoint' cause node state =
181             case update node cause state of
182               Nothing -> state
183               Just state' ->
184                   foldr (fixedpoint' (Just node)) state' (dependants node)