]> Joshua Wise's Git repositories - snipe.git/blame_incremental - codegen/liveness.sml
Propagate strings through the blarg backend.
[snipe.git] / codegen / liveness.sml
... / ...
CommitLineData
1(* L3 Compiler
2 * Turns pseudoasm into liveness-annotated pseudoasm
3 * Author: Chris Lu <czl@andrew.cmu.edu>
4 * Author: Joshua Wise <jwise@andrew.cmu.edu>
5 *)
6
7signature LIVENESS =
8sig
9 structure OperSet : ORD_SET
10 where type Key.ord_key = Blarg.oper;
11 structure LiveMap : ORD_MAP
12 where type Key.ord_key = int;
13
14 type live = int * OperSet.set
15 type pseudoasm = Blarg.insn list
16 type livenesses = OperSet.set LiveMap.map
17
18 type ident = int
19 datatype pred = DEF of Blarg.oper | USE of Blarg.oper | SUCC of ident | ISMOVE
20
21 type predicates = pred list LiveMap.map
22
23 val uses : pred list -> Blarg.oper list
24 val succs : pred list -> ident list
25 val defs : pred list -> Blarg.oper list
26 val ismove : pred list -> bool
27
28 val liveness : pseudoasm -> predicates * livenesses
29 val listify : livenesses -> OperSet.set list
30 val prettyprint : OperSet.set -> string
31end
32
33structure Liveness :> LIVENESS =
34struct
35 structure T = Temp
36 structure X = Blarg
37
38 structure OperSet = Blarg.OperSet
39 structure LiveMap = Blarg.LiveMap
40 structure LabelMap = SplayMapFn(struct
41 type ord_key = Label.label
42 val compare = Label.compare
43 end)
44
45 type live = int * OperSet.set
46 type pseudoasm = X.insn list
47 type numasm = X.insn LiveMap.map
48 type livenesses = OperSet.set LiveMap.map
49
50 type ident = int
51 datatype pred = DEF of X.oper | USE of X.oper | SUCC of ident | ISMOVE
52
53 type predicates = pred list LiveMap.map
54
55 (* val number : pseudoasm -> numasm
56 * numbers the instructions!
57 *)
58
59 fun number instrs =
60 let
61 val nums = List.tabulate (List.length instrs, (fn i => i))
62 in
63 foldr
64 LiveMap.insert'
65 LiveMap.empty
66 (ListPair.zip (nums,instrs))
67 end
68
69 (* val defusesucc : numasm -> (ident * pred list) list
70 * generates def/use/succ predicates according to rules
71 *)
72 fun defusesucc l =
73 let
74 val labelmap = LiveMap.foldri
75 (fn (n, a, b) => LabelMap.insert(b, a, n))
76 (LabelMap.empty)
77 (LiveMap.mapPartial (fn (X.LABEL lb) => SOME(lb) | _ => NONE) l)
78
79 fun findlabel (lb) = valOf (LabelMap.find (labelmap, lb))
80
81 (* val defhit/usehit : X.oper -> pred list
82 * helper functions to discard constant operands *)
83 fun defhit (X.REG X.PC) = raise ErrorMsg.InternalError "cannot define PC"
84 | defhit (X.REG a) = [DEF(X.REG a)]
85 | defhit (X.TEMP a) = [DEF(X.TEMP a)]
86 | defhit (_) = nil
87
88 and usehit (X.REG a) = [USE(X.REG a)]
89 | usehit (X.TEMP a) = [USE(X.TEMP a)]
90 | usehit (_) = nil
91
92 fun callhit 0 = nil
93 | callhit 1 = USE(X.REG(X.R0))::(callhit 0)
94 | callhit 2 = USE(X.REG(X.R1))::(callhit 1)
95 | callhit 3 = USE(X.REG(X.R2))::(callhit 2)
96 | callhit 4 = USE(X.REG(X.R3))::(callhit 3)
97 | callhit _ = callhit 4
98
99 (* val gendef : ident * X.insn -> ident * pred list
100 * generates the def/use/succ predicates for a single insn
101 *)
102 fun gendef (n, X.DIRECTIVE(_)) = ([SUCC (n+1)])
103 | gendef (n, X.COMMENT(_)) = ([SUCC (n+1)])
104 | gendef (n, X.LIVEIGN (_)) = ([SUCC (n+1)])
105 | gendef (n, X.LABEL l) = ([SUCC (n+1)])
106 | gendef (n, X.INSN(X.NV, _)) = ([SUCC (n+1)])
107 | gendef (n, X.INSN(_, X.MOVLIT(dest, _))) = (defhit dest @ [SUCC(n+1), ISMOVE])
108 | gendef (n, X.INSN(_, X.MOVSYM(dest, sym))) = (defhit dest @ [SUCC(n+1), ISMOVE])
109 | gendef (n, X.INSN(_, X.MOVSTR(dest, str))) = (defhit dest @ [SUCC(n+1), ISMOVE])
110 | gendef (n, X.INSN(X.AL, X.MOVLBL(X.REG X.PC, l))) = ([SUCC (findlabel l)])
111 | gendef (n, X.INSN(_, X.MOVLBL(X.REG X.PC, l))) = ([SUCC (n+1), SUCC (findlabel l)])
112 | gendef (n, X.INSN(_, X.MOVLBL(_, _))) = raise ErrorMsg.InternalError "MOVLBL with target neq PC"
113 | gendef (n, X.INSN(_, X.LDR(dest, src))) = (defhit dest @ usehit src @ [SUCC (n+1), ISMOVE])
114 | gendef (n, X.INSN(_, X.STO(dest, src))) = (usehit dest @ usehit src @ [SUCC (n+1)])
115 | gendef (n, X.INSN(_, X.MOV(dest, src))) = (defhit dest @ usehit src @ [SUCC (n+1), ISMOVE])
116 | gendef (n, X.INSN(_, X.MOVS(dest, src))) = (usehit src @ [SUCC (n+1)])
117 | gendef (n, X.INSN(_, X.ADD(dest, src))) = (defhit dest @ usehit dest @ usehit src @ [SUCC (n+1)])
118 | gendef (n, X.INSN(_, X.ADDS(dest, src))) = (usehit dest @ usehit src @ [SUCC (n+1)])
119 | gendef (n, X.INSN(_, X.SUB(dest, src))) = (defhit dest @ usehit dest @ usehit src @ [SUCC (n+1)])
120 | gendef (n, X.INSN(_, X.SUBS(dest, src))) = (usehit dest @ usehit src @ [SUCC (n+1)])
121 | gendef (n, X.INSN(_, X.AND(dest, src))) = (defhit dest @ usehit dest @ usehit src @ [SUCC (n+1)])
122 | gendef (n, X.INSN(_, X.ANDS(dest, src))) = (usehit dest @ usehit src @ [SUCC (n+1)])
123 | gendef (n, X.INSN(_, X.NOT(dest, src))) = (defhit dest @ usehit src @ [SUCC (n+1)])
124 | gendef (n, X.INSN(_, X.NOTS(dest, src))) = (usehit src @ [SUCC (n+1)])
125 | gendef (n, X.INSN(_, X.PUSH(X.REG X.SP, src))) = (usehit src @ [SUCC (n+1)])
126 | gendef (n, X.INSN(_, X.PUSH(_, _))) = raise ErrorMsg.InternalError "PUSH with sp != SP"
127 | gendef (n, X.INSN(X.AL, X.POP(X.REG X.SP, X.REG X.PC))) = ([USE (X.REG X.R0)]) (* kind of like 'ret' *)
128 | gendef (n, X.INSN(_, X.POP(X.REG X.SP, X.REG X.PC))) = ([USE (X.REG X.R0), SUCC(n+1)])
129 | gendef (n, X.INSN(_, X.POP(X.REG X.SP, src))) = (defhit src @ [SUCC (n+1)])
130 | gendef (n, X.INSN(_, X.POP(_, _))) = raise ErrorMsg.InternalError "POP with sp != SP"
131 | gendef (n, X.INSN(_, X.CALL(X.REG X.SP, src, a))) = (callhit a @
132 usehit src @
133 [DEF(X.REG(X.R0)), DEF(X.REG(X.R1)), DEF(X.REG(X.R2)), DEF(X.REG(X.R3)),
134 DEF(X.REG(X.R4)), DEF(X.REG(X.R5)),
135 SUCC(n+1)]
136 )
137 | gendef (n, X.INSN(_, X.CALL(_, _, _))) = raise ErrorMsg.InternalError "CALL with sp != SP"
138 | gendef (n, X.INSN(_, X.SHR(dest, src))) = (defhit dest @ usehit dest @ usehit src @ [SUCC (n+1)])
139 | gendef (n, X.INSN(_, X.SHL(dest, src))) = (defhit dest @ usehit dest @ usehit src @ [SUCC (n+1)])
140 in
141 LiveMap.mapi gendef l
142 end
143
144 (* val uselive : (int * pred list) list -> OperSet.set LiveMap.map
145 * generates liveness for 'use' rules to get the iterative analyzer started
146 *)
147 fun uselive preds =
148 LiveMap.mapi
149 (fn (n, pl) =>
150 foldr
151 (fn (USE (l), set) => OperSet.add (set, l)
152 | (_, set) => set)
153 OperSet.empty
154 pl
155 )
156 preds
157
158 (* val subsetlive : OperSet.set LiveMap.map * OperSet.set LiveMap.map -> bool
159 * true if first is subset of second
160 *)
161
162 fun subsetlive (l1,l2) =
163 LiveMap.foldri
164 (fn (_, _, false) => false
165 | (n, set1, _) => case LiveMap.find (l2, n)
166 of NONE => false
167 | SOME set2 => OperSet.isSubset (set1, set2))
168 true
169 l1
170
171 (* val succs : pred list -> int list
172 * generates a list of lines that succeed a line given the predicates
173 * for that line
174 *)
175 fun succs (SUCC(a)::l') = a::(succs l')
176 | succs (_::l') = succs l'
177 | succs nil = nil
178
179 fun defs (DEF(a)::l) = a::(defs l)
180 | defs (_::l) = defs l
181 | defs nil = nil
182
183 fun uses (USE(a)::l) = a::(defs l)
184 | uses (_::l) = defs l
185 | uses nil = nil
186
187 fun ismove l = List.exists (fn ISMOVE => true | _ => false) l
188
189 (* val liveiter : OperSet.set LiveMap.map -> (int * pred list) list -> OperSet.set LiveMap.map
190 * iteratively generates livenesses from def/use/succ rules
191 * it must be fed a liveness list generated from the use rule as it only
192 * processes the second rule :
193 *
194 * use(l',x)
195 * !def(l,x)
196 * succ(l,l')
197 * --------------
198 * live(l,x)
199 *)
200
201 fun liveiter livemap preds =
202 let
203
204
205
206 (* val lives : int list -> OperSet.set LiveMap.map -> OperSet.set
207 * scans l for live variables in succeeding lines *)
208 fun lives l' idents =
209 let
210 val lines = List.mapPartial (fn a => LiveMap.find (l', a)) idents
211 in
212 foldr
213 (fn (set', set) => OperSet.union (set', set))
214 OperSet.empty
215 lines
216 end
217
218 (* val isndef : X.oper -> pred list -> bool
219 * checks to see if x is defined in a predicate list *)
220 fun isndef (X.STACKARG(_)) _ = false
221 | isndef x (DEF(y)::l') = not (X.opereq (x,y)) andalso isndef x l'
222 | isndef x (a::l') = isndef x l'
223 | isndef x nil = true
224
225 (* val liveadd : live -> OperSet.set LiveMap.map -> OperSet.set LiveMap.map *)
226 fun liveadd (n,oper) map = case LiveMap.find (map, n)
227 of SOME(x) => LiveMap.insert (map, n, OperSet.add (x, oper))
228 | NONE => LiveMap.insert (map, n, OperSet.singleton oper)
229
230 (* this does the dirty work!
231 * for each line, checks if the live variables in succeeding lines are
232 * not defined here; if so, it accumulates them onto the inital list
233 *
234 * changing the first foldr to a foldl slows down liveness by a factor
235 * of at least 100 on cedar-anastulate.l2
236 *)
237 val newl = LiveMap.foldri
238 (fn (n, a, b) => OperSet.foldr
239 (fn (a',b') => if (isndef a' a) then liveadd (n, a') b' else b')
240 b
241 (lives b (succs a))
242 )
243 livemap
244 preds
245 in
246 if subsetlive (newl, livemap)
247 then livemap
248 else liveiter newl preds
249 end
250
251 fun dustostring (DEF(a)) = "DEF(" ^ X.pp_oper a ^ ")"
252 | dustostring (USE(a)) = "USE(" ^ X.pp_oper a ^ ")"
253 | dustostring (SUCC(a)) = "SUCC(" ^ Int.toString a ^ ")"
254 | dustostring ISMOVE = "ISMOVE"
255
256 (* val liveness : pseudoasm -> livenesses
257 * analyzes liveness of variables in the given pseudo-asm
258 *)
259
260 fun liveness instrs =
261 let
262 val preds = defusesucc (number instrs)
263(* val (_,l) = ListPair.unzip preds
264 val () = print (
265 String.concatWith "\n" (
266 List.map
267 (fn a => String.concatWith ", " (List.map dustostring a))
268 l
269 )
270 )*)
271 val init = uselive preds
272 val initmap = LiveMap.foldri (fn (n,a,b) => LiveMap.insert (b, n, a)) LiveMap.empty init
273 in
274 (preds, liveiter initmap preds)
275 end
276
277 fun prettyprint (set) =
278 OperSet.foldr
279 (fn (oper, s) => (X.pp_oper oper) ^ ", " ^ s)
280 "-\n"
281 set
282
283 fun listify map =
284 let
285 val maxln = LiveMap.foldri (fn (a, _, b) => Int.max (a, b)) 0 map
286 val nums = List.tabulate (maxln+1, fn x => x)
287 in
288 List.map (fn num => valOf (LiveMap.find (map, num)) handle Option => OperSet.empty) nums
289 end
290end
This page took 0.025118 seconds and 4 git commands to generate.