]> Joshua Wise's Git repositories - snipe.git/blame - codegen/liveness.sml
woo it generated some code
[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 *)
6ade8b0a
JW
102 fun gendef (n, X.DIRECTIVE(_)) = (nil)
103 | gendef (n, X.COMMENT(_)) = (nil)
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"
130 | gendef (n, X.INSN(_, X.CALL(X.REG X.SP, src, a))) = (callhit a @ usehit src @ [DEF(X.REG(X.R0)), DEF(X.REG(X.R1)), DEF(X.REG(X.R2)),
131 DEF(X.REG(X.R3)), SUCC(n+1)])
132 | gendef (n, X.INSN(_, X.CALL(_, _, _))) = raise ErrorMsg.InternalError "CALL with sp != SP"
133 | gendef (n, X.INSN(_, X.SHR(dest, src))) = (defhit dest @ usehit dest @ usehit src @ [SUCC (n+1)])
134 | gendef (n, X.INSN(_, X.SHL(dest, src))) = (defhit dest @ usehit dest @ usehit src @ [SUCC (n+1)])
0a24e44d 135 in
6ade8b0a 136 LiveMap.mapi gendef l
0a24e44d
JW
137 end
138
6ade8b0a 139 (* val uselive : (int * pred list) list -> OperSet.set LiveMap.map
0a24e44d
JW
140 * generates liveness for 'use' rules to get the iterative analyzer started
141 *)
142 fun uselive preds =
6ade8b0a
JW
143 LiveMap.mapi
144 (fn (n, pl) =>
145 foldr
146 (fn (USE (l), set) => OperSet.add (set, l)
147 | (_, set) => set)
148 OperSet.empty
149 pl
0a24e44d 150 )
6ade8b0a 151 preds
0a24e44d 152
6ade8b0a 153 (* val subsetlive : OperSet.set LiveMap.map * OperSet.set LiveMap.map -> bool
0a24e44d
JW
154 * true if first is subset of second
155 *)
156
157 fun subsetlive (l1,l2) =
6ade8b0a
JW
158 LiveMap.foldri
159 (fn (_, _, false) => false
160 | (n, set1, _) => case LiveMap.find (l2, n)
161 of NONE => false
162 | SOME set2 => OperSet.isSubset (set1, set2))
163 true
164 l1
165
166 (* val succs : pred list -> int list
167 * generates a list of lines that succeed a line given the predicates
168 * for that line
169 *)
170 fun succs (SUCC(a)::l') = a::(succs l')
171 | succs (_::l') = succs l'
172 | succs nil = nil
173
174 fun defs (DEF(a)::l) = a::(defs l)
175 | defs (_::l) = defs l
176 | defs nil = nil
177
178 fun uses (USE(a)::l) = a::(defs l)
179 | uses (_::l) = defs l
180 | uses nil = nil
181
182 fun ismove l = List.exists (fn ISMOVE => true | _ => false) l
0a24e44d 183
6ade8b0a 184 (* val liveiter : OperSet.set LiveMap.map -> (int * pred list) list -> OperSet.set LiveMap.map
0a24e44d
JW
185 * iteratively generates livenesses from def/use/succ rules
186 * it must be fed a liveness list generated from the use rule as it only
187 * processes the second rule :
12aa4087 188 *
0a24e44d
JW
189 * use(l',x)
190 * !def(l,x)
191 * succ(l,l')
192 * --------------
193 * live(l,x)
12aa4087 194 *)
0a24e44d 195
6ade8b0a 196 fun liveiter livemap preds =
12aa4087 197 let
0a24e44d 198
6ade8b0a
JW
199
200
201 (* val lives : int list -> OperSet.set LiveMap.map -> OperSet.set
0a24e44d
JW
202 * scans l for live variables in succeeding lines *)
203 fun lives l' idents =
6ade8b0a
JW
204 let
205 val lines = List.mapPartial (fn a => LiveMap.find (l', a)) idents
206 in
207 foldr
208 (fn (set', set) => OperSet.union (set', set))
209 OperSet.empty
210 lines
211 end
12aa4087 212
0a24e44d
JW
213 (* val isndef : X.oper -> pred list -> bool
214 * checks to see if x is defined in a predicate list *)
6ade8b0a 215 fun isndef (X.STACKARG(_)) _ = false
f716a180 216 | isndef x (DEF(y)::l') = not (X.opereq (x,y)) andalso isndef x l'
6ade8b0a 217 | isndef x (a::l') = isndef x l'
0a24e44d
JW
218 | isndef x nil = true
219
6ade8b0a
JW
220 (* val liveadd : live -> OperSet.set LiveMap.map -> OperSet.set LiveMap.map *)
221 fun liveadd (n,oper) map = case LiveMap.find (map, n)
222 of SOME(x) => LiveMap.insert (map, n, OperSet.add (x, oper))
223 | NONE => LiveMap.insert (map, n, OperSet.singleton oper)
0a24e44d
JW
224
225 (* this does the dirty work!
226 * for each line, checks if the live variables in succeeding lines are
227 * not defined here; if so, it accumulates them onto the inital list
228 *
229 * changing the first foldr to a foldl slows down liveness by a factor
230 * of at least 100 on cedar-anastulate.l2
231 *)
6ade8b0a
JW
232 val newl = LiveMap.foldri
233 (fn (n, a, b) => OperSet.foldr
0a24e44d
JW
234 (fn (a',b') => if (isndef a' a) then liveadd (n, a') b' else b')
235 b
236 (lives b (succs a))
237 )
6ade8b0a
JW
238 livemap
239 preds
12aa4087 240 in
6ade8b0a
JW
241 if subsetlive (newl, livemap)
242 then livemap
243 else liveiter newl preds
12aa4087 244 end
0a24e44d 245
f716a180
JW
246 fun dustostring (DEF(a)) = "DEF(" ^ X.pp_oper a ^ ")"
247 | dustostring (USE(a)) = "USE(" ^ X.pp_oper a ^ ")"
6ade8b0a
JW
248 | dustostring (SUCC(a)) = "SUCC(" ^ Int.toString a ^ ")"
249 | dustostring ISMOVE = "ISMOVE"
250
0a24e44d
JW
251 (* val liveness : pseudoasm -> livenesses
252 * analyzes liveness of variables in the given pseudo-asm
253 *)
254
255 fun liveness instrs =
12aa4087 256 let
0a24e44d 257 val preds = defusesucc (number instrs)
6ade8b0a
JW
258(* val (_,l) = ListPair.unzip preds
259 val () = print (
260 String.concatWith "\n" (
261 List.map
262 (fn a => String.concatWith ", " (List.map dustostring a))
263 l
264 )
265 )*)
0a24e44d 266 val init = uselive preds
6ade8b0a 267 val initmap = LiveMap.foldri (fn (n,a,b) => LiveMap.insert (b, n, a)) LiveMap.empty init
12aa4087 268 in
6ade8b0a
JW
269 (preds, liveiter initmap preds)
270 end
271
272 fun prettyprint (set) =
273 OperSet.foldr
f716a180 274 (fn (oper, s) => (X.pp_oper oper) ^ ", " ^ s)
6ade8b0a
JW
275 "-\n"
276 set
277
278 fun listify map =
279 let
280 val maxln = LiveMap.foldri (fn (a, _, b) => Int.max (a, b)) 0 map
281 val nums = List.tabulate (maxln+1, fn x => x)
282 in
283 List.map (fn num => valOf (LiveMap.find (map, num)) handle Option => OperSet.empty) nums
12aa4087
JW
284 end
285end
This page took 0.088541 seconds and 4 git commands to generate.