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