Second working draft of a CPS algorithm for C--.
[ghc-hetmet.git] / compiler / cmm / Dataflow.hs
1 module Dataflow {-(fixedpoint, cmmLivenessComment, cmmLiveness, CmmLive)-} 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
40 type BlockEntryLiveness = BlockEnv CmmLive      -- The variables live on entry to each block
41
42 addLive new_live live = live `unionUniqSets` new_live
43 addKilled new_killed live = live `minusUniqSet` new_killed
44
45 -- Calculate the live and killed registers for a local block
46 cmmBlockLive :: UniqFM {-BlockId-} CmmLive -> CmmBasicBlock -> CmmLive
47 cmmBlockLive other_live (BasicBlock _ stmts) =
48     foldr ((.) . (cmmStmtLive other_live)) id stmts emptyUniqSet
49
50 -- Helper for cmmLocalLiveness
51 cmmStmtLive :: UniqFM {-BlockId-} CmmLive -> CmmStmt -> (CmmLive -> CmmLive)
52 cmmStmtLive _ (CmmNop) = id
53 cmmStmtLive _ (CmmComment _) = id
54 cmmStmtLive _ (CmmAssign reg expr) =
55     cmmExprLive expr . reg_liveness where
56         reg_liveness =
57             case reg of
58               (CmmLocal reg') -> addKilled $ unitUniqSet reg'
59               (CmmGlobal _) -> id
60 cmmStmtLive _ (CmmStore expr1 expr2) =
61     cmmExprLive expr2 . cmmExprLive expr1
62 cmmStmtLive _ (CmmCall target results arguments _) =
63     target_liveness .
64     foldr ((.) . cmmExprLive) id (map fst arguments) .
65     addKilled (mkUniqSet $ only_local_regs results) where
66         only_local_regs [] = []
67         only_local_regs ((CmmGlobal _,_):args) = only_local_regs args
68         only_local_regs ((CmmLocal r,_):args) = r:only_local_regs args
69         target_liveness =
70             case target of
71               (CmmForeignCall target _) -> cmmExprLive target
72               (CmmPrim _) -> id
73 cmmStmtLive other_live (CmmBranch target) = addLive (lookupWithDefaultUFM other_live emptyUniqSet target)
74 cmmStmtLive other_live (CmmCondBranch expr target) = cmmExprLive expr . addLive (lookupWithDefaultUFM other_live emptyUniqSet target)
75 cmmStmtLive other_live (CmmSwitch expr targets) =
76     cmmExprLive expr .
77     (foldr ((.) . (addLive . lookupWithDefaultUFM other_live emptyUniqSet)) id (mapCatMaybes id targets))
78 cmmStmtLive _ (CmmJump expr params) =
79     const (cmmExprLive expr $ foldr ((.) . cmmExprLive) id (map fst params) $ emptyUniqSet)
80 cmmStmtLive _ (CmmReturn params) =
81     const (foldr ((.) . cmmExprLive) id (map fst params) $ emptyUniqSet)
82
83 --------
84
85 -- Helper for cmmLocalLiveness
86 cmmExprLive :: CmmExpr -> (CmmLive -> CmmLive)
87 cmmExprLive expr = addLive (mkUniqSet $ expr_liveness expr) where
88     expr_liveness (CmmLit _) = []
89     expr_liveness (CmmLoad expr _) = expr_liveness expr
90     expr_liveness (CmmReg reg) = reg_liveness reg
91     expr_liveness (CmmMachOp _ exprs) = concatMap expr_liveness exprs
92     expr_liveness (CmmRegOff reg _) = reg_liveness reg
93     reg_liveness (CmmLocal reg) = [reg]
94     reg_liveness (CmmGlobal _) = []
95
96 cmmBlockUpdate ::
97     UniqFM {-BlockId-} CmmBasicBlock
98     -> BlockId
99     -> Maybe BlockId
100     -> UniqFM {-BlockId-} CmmLive
101     -> Maybe (UniqFM {-BlockId-} CmmLive)
102 cmmBlockUpdate blocks node _ state =
103     let old_live = lookupWithDefaultUFM state (panic "unknown block id during liveness analysis") node
104         block = lookupWithDefaultUFM blocks (panic "unknown block id during liveness analysis") node
105         new_live = cmmBlockLive state block
106     in if (sizeUniqSet old_live) == (sizeUniqSet new_live)
107        then Nothing
108        else Just $ addToUFM state node new_live
109
110 cmmBlockDependants :: UniqFM {-BlockId-} (UniqSet BlockId) -> BlockId -> [BlockId]
111 cmmBlockDependants sources ident =
112     uniqSetToList $ lookupWithDefaultUFM sources emptyUniqSet ident
113
114 cmmBlockSourcesAndTargets ::
115     [CmmBasicBlock]
116     -> (UniqFM {-BlockId-} (UniqSet BlockId), UniqFM (UniqSet BlockId))
117 cmmBlockSourcesAndTargets blocks = foldr aux (emptyUFM, emptyUFM) blocks where
118     aux block (sourcesUFM, targetsUFM)  =
119         (foldUniqSet add_source_edges sourcesUFM targets,
120          addToUFM_Acc unionUniqSets id targetsUFM ident targets) where
121             add_source_edges t ufm =
122                 addToUFM_Acc (flip addOneToUniqSet) unitUniqSet ufm t ident
123             targets = cmmBranchTargets block
124             ident = blockId block
125
126 cmmBlockNames :: [CmmBasicBlock] -> UniqFM {-BlockId-} CmmBasicBlock
127 cmmBlockNames blocks = listToUFM $ map block_name blocks where
128     block_name b = (blockId b, b)
129
130 cmmLiveness :: [CmmBasicBlock] -> BlockEnv CmmLive
131 cmmLiveness blocks =
132     fixedpoint (cmmBlockDependants sources) (cmmBlockUpdate blocks')
133                (map blockId blocks) (listToUFM [(blockId b, emptyUniqSet) | b <- blocks]) where
134                    (sources, targets) = cmmBlockSourcesAndTargets blocks
135                    blocks' = cmmBlockNames blocks
136
137 cmmLivenessComment ::
138     UniqFM {-BlockId-} (UniqSet LocalReg)
139     -> CmmBasicBlock -> CmmBasicBlock
140 cmmLivenessComment live (BasicBlock ident stmts) =
141     BasicBlock ident stmts' where
142         stmts' = (CmmComment $ mkFastString $ showSDoc $ ppr $ live'):stmts
143         live' = map CmmLocal $ uniqSetToList $ lookupWithDefaultUFM live emptyUniqSet ident
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)