]> Joshua Wise's Git repositories - snipe.git/blame - codegen/liveness.sml
Initial import of l4c
[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
JW
9 structure OperSet : ORD_SET
10 where type Key.ord_key = x86.oper;
11 structure LiveMap : ORD_MAP
12 where type Key.ord_key = int;
13
14 type live = int * OperSet.set
0a24e44d 15 type pseudoasm = x86.insn list
6ade8b0a
JW
16 type livenesses = OperSet.set LiveMap.map
17
0a24e44d 18 type ident = int
6ade8b0a
JW
19 datatype pred = DEF of x86.oper | USE of x86.oper | SUCC of ident | ISMOVE
20
21 type predicates = pred list LiveMap.map
22
23 val uses : pred list -> x86.oper list
24 val succs : pred list -> ident list
25 val defs : pred list -> x86.oper list
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
36 structure X = x86
6ade8b0a
JW
37
38 structure OperSet = x86.OperSet
39 structure LiveMap = x86.LiveMap
12aa4087 40
6ade8b0a 41 type live = int * OperSet.set
0a24e44d 42 type pseudoasm = X.insn list
6ade8b0a
JW
43 type numasm = X.insn LiveMap.map
44 type livenesses = OperSet.set LiveMap.map
0a24e44d
JW
45
46 type ident = int
6ade8b0a
JW
47 datatype pred = DEF of X.oper | USE of X.oper | SUCC of ident | ISMOVE
48
49 type predicates = pred list LiveMap.map
0a24e44d
JW
50
51 (* val number : pseudoasm -> numasm
52 * numbers the instructions!
53 *)
54
55 fun number instrs =
56 let
57 val nums = List.tabulate (List.length instrs, (fn i => i))
58 in
6ade8b0a
JW
59 foldr
60 LiveMap.insert'
61 LiveMap.empty
62 (ListPair.zip (nums,instrs))
0a24e44d
JW
63 end
64
65 (* val defusesucc : numasm -> (ident * pred list) list
66 * generates def/use/succ predicates according to rules
67 *)
68
69 fun defusesucc l =
70 let
71 fun findlabel (lb) =
72 Option.valOf
6ade8b0a
JW
73 (LiveMap.foldri (fn (n, X.LABEL lb', NONE) => if (Label.compare (lb, lb') = EQUAL) then SOME n else NONE
74 | (_, _, old) => old) NONE l)
0a24e44d
JW
75
76 (* val defhit/usehit : X.oper -> pred list
77 * helper functions to discard constant operands *)
6ade8b0a
JW
78 fun defhit (X.REG a) = [DEF(X.REG a)]
79 | defhit (X.TEMP a) = [DEF(X.TEMP a)]
1144856b
JW
80 | defhit (X.REL(o1, o2)) = usehit o1 @ usehit o2
81 | defhit (X.OSIZE(s, oo)) = defhit oo
6ade8b0a
JW
82 | defhit (_) = nil
83
1144856b 84 and usehit (X.REG a) = [USE(X.REG a)]
6ade8b0a 85 | usehit (X.TEMP a) = [USE(X.TEMP a)]
1144856b
JW
86 | usehit (X.REL(o1, o2)) = usehit o1 @ usehit o2
87 | usehit (X.OSIZE(s, oo)) = usehit oo
6ade8b0a 88 | usehit (_) = nil
0a24e44d 89
6ade8b0a
JW
90 fun callhit 0 = nil
91 | callhit 1 = USE(X.REG(X.EDI))::(callhit 0)
92 | callhit 2 = USE(X.REG(X.ESI))::(callhit 1)
93 | callhit 3 = USE(X.REG(X.EDX))::(callhit 2)
94 | callhit 4 = USE(X.REG(X.ECX))::(callhit 3)
95 | callhit 5 = USE(X.REG(X.R8D))::(callhit 4)
96 | callhit 6 = USE(X.REG(X.R9D))::(callhit 5)
97 | callhit _ = callhit 6
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.MOV(dest, src)) = (defhit dest @ usehit src @ [SUCC(n+1), ISMOVE])
1144856b 106 | gendef (n, X.LEA(dest, src)) = (defhit dest @ usehit src @ [SUCC(n+1)])
6ade8b0a
JW
107 | gendef (n, X.SUB(dest, src)) = (defhit dest @ usehit dest @ usehit src @ [SUCC(n+1)])
108 | gendef (n, X.IMUL(dest, src)) = (defhit dest @ usehit dest @ usehit src @ [SUCC(n+1)])
109 | gendef (n, X.IMUL3(dest, src, _)) = (defhit dest @ usehit src @ [SUCC(n+1)])
110 | gendef (n, X.ADD(dest, src)) = (defhit dest @ usehit dest @ usehit src @ [SUCC(n+1)])
111 | gendef (n, X.IDIV(src)) = (usehit src @ [DEF(X.REG(X.EAX)), DEF(X.REG(X.EDX)),
0a24e44d
JW
112 USE(X.REG(X.EAX)), USE(X.REG(X.EDX)),
113 SUCC(n+1)])
6ade8b0a
JW
114 | gendef (n, X.CLTD) = ([USE(X.REG(X.EAX)), DEF(X.REG(X.EDX)), SUCC(n+1)])
115 | gendef (n, X.SAL(dest, shft)) = (defhit dest @ usehit shft @ usehit dest @ [SUCC(n+1)])
116 | gendef (n, X.SAR(dest, shft)) = (defhit dest @ usehit shft @ usehit dest @ [SUCC(n+1)])
117 | gendef (n, X.NEG(src)) = (defhit src @ usehit src @ [SUCC(n+1)])
118 | gendef (n, X.NOT(src)) = (defhit src @ usehit src @ [SUCC(n+1)])
119 | gendef (n, X.AND(dest, src)) = (defhit dest @ usehit dest @ usehit src @ [SUCC(n+1)])
120 | gendef (n, X.OR(dest, src)) = (defhit dest @ usehit dest @ usehit src @ [SUCC(n+1)])
121 | gendef (n, X.XOR(dest, src)) = (defhit dest @ usehit dest @ usehit src @ [SUCC(n+1)])
122 | gendef (n, X.CMP(dest, src)) = (usehit dest @ usehit src @ [SUCC(n+1)])
123 | gendef (n, X.TEST(dest, src)) = (usehit dest @ usehit src @ [SUCC(n+1)])
124 | gendef (n, X.SETcc(_,dest)) = (defhit dest @ [SUCC(n+1)])
125 | gendef (n, X.CALL(_, a)) = (callhit a @ [DEF(X.REG(X.EAX)), DEF(X.REG(X.ECX)), DEF(X.REG(X.EDX)),
126 DEF(X.REG(X.EDI)), DEF(X.REG(X.ESI)), DEF(X.REG(X.R8D)),
127 DEF(X.REG(X.R9D)), DEF(X.REG(X.R10D)), DEF(X.REG(X.R11D)), SUCC(n+1)])
128 | gendef (n, X.MOVZB(dest, src)) = (defhit dest @ usehit src @ [SUCC(n+1)])
129 | gendef (n, X.RET) = ([USE (X.REG X.EAX)])
130 | gendef (n, X.LABEL l) = ([SUCC (n+1)])
131 | gendef (n, X.JMP l) = ([SUCC (findlabel l)])
132 | gendef (n, X.Jcc (_,l)) = ([SUCC (n+1), SUCC (findlabel l)])
0a24e44d 133 in
6ade8b0a 134 LiveMap.mapi gendef l
0a24e44d
JW
135 end
136
6ade8b0a 137 (* val uselive : (int * pred list) list -> OperSet.set LiveMap.map
0a24e44d
JW
138 * generates liveness for 'use' rules to get the iterative analyzer started
139 *)
140 fun uselive preds =
6ade8b0a
JW
141 LiveMap.mapi
142 (fn (n, pl) =>
143 foldr
144 (fn (USE (l), set) => OperSet.add (set, l)
145 | (_, set) => set)
146 OperSet.empty
147 pl
0a24e44d 148 )
6ade8b0a 149 preds
0a24e44d 150
6ade8b0a 151 (* val subsetlive : OperSet.set LiveMap.map * OperSet.set LiveMap.map -> bool
0a24e44d
JW
152 * true if first is subset of second
153 *)
154
155 fun subsetlive (l1,l2) =
6ade8b0a
JW
156 LiveMap.foldri
157 (fn (_, _, false) => false
158 | (n, set1, _) => case LiveMap.find (l2, n)
159 of NONE => false
160 | SOME set2 => OperSet.isSubset (set1, set2))
161 true
162 l1
163
164 (* val succs : pred list -> int list
165 * generates a list of lines that succeed a line given the predicates
166 * for that line
167 *)
168 fun succs (SUCC(a)::l') = a::(succs l')
169 | succs (_::l') = succs l'
170 | succs nil = nil
171
172 fun defs (DEF(a)::l) = a::(defs l)
173 | defs (_::l) = defs l
174 | defs nil = nil
175
176 fun uses (USE(a)::l) = a::(defs l)
177 | uses (_::l) = defs l
178 | uses nil = nil
179
180 fun ismove l = List.exists (fn ISMOVE => true | _ => false) l
0a24e44d 181
6ade8b0a 182 (* val liveiter : OperSet.set LiveMap.map -> (int * pred list) list -> OperSet.set LiveMap.map
0a24e44d
JW
183 * iteratively generates livenesses from def/use/succ rules
184 * it must be fed a liveness list generated from the use rule as it only
185 * processes the second rule :
12aa4087 186 *
0a24e44d
JW
187 * use(l',x)
188 * !def(l,x)
189 * succ(l,l')
190 * --------------
191 * live(l,x)
12aa4087 192 *)
0a24e44d 193
6ade8b0a 194 fun liveiter livemap preds =
12aa4087 195 let
0a24e44d 196
6ade8b0a
JW
197
198
199 (* val lives : int list -> OperSet.set LiveMap.map -> OperSet.set
0a24e44d
JW
200 * scans l for live variables in succeeding lines *)
201 fun lives l' idents =
6ade8b0a
JW
202 let
203 val lines = List.mapPartial (fn a => LiveMap.find (l', a)) idents
204 in
205 foldr
206 (fn (set', set) => OperSet.union (set', set))
207 OperSet.empty
208 lines
209 end
12aa4087 210
0a24e44d
JW
211 (* val isndef : X.oper -> pred list -> bool
212 * checks to see if x is defined in a predicate list *)
6ade8b0a
JW
213 fun isndef (X.STACKARG(_)) _ = false
214 | isndef x (DEF(y)::l') = not (X.opereq (x,y)) andalso isndef x l'
215 | isndef x (a::l') = isndef x l'
0a24e44d
JW
216 | isndef x nil = true
217
6ade8b0a
JW
218 (* val liveadd : live -> OperSet.set LiveMap.map -> OperSet.set LiveMap.map *)
219 fun liveadd (n,oper) map = case LiveMap.find (map, n)
220 of SOME(x) => LiveMap.insert (map, n, OperSet.add (x, oper))
221 | NONE => LiveMap.insert (map, n, OperSet.singleton oper)
0a24e44d
JW
222
223 (* this does the dirty work!
224 * for each line, checks if the live variables in succeeding lines are
225 * not defined here; if so, it accumulates them onto the inital list
226 *
227 * changing the first foldr to a foldl slows down liveness by a factor
228 * of at least 100 on cedar-anastulate.l2
229 *)
6ade8b0a
JW
230 val newl = LiveMap.foldri
231 (fn (n, a, b) => OperSet.foldr
0a24e44d
JW
232 (fn (a',b') => if (isndef a' a) then liveadd (n, a') b' else b')
233 b
234 (lives b (succs a))
235 )
6ade8b0a
JW
236 livemap
237 preds
12aa4087 238 in
6ade8b0a
JW
239 if subsetlive (newl, livemap)
240 then livemap
241 else liveiter newl preds
12aa4087 242 end
0a24e44d 243
6ade8b0a
JW
244 fun dustostring (DEF(a)) = "DEF(" ^ X.prettyprint_oper X.Long a ^ ")"
245 | dustostring (USE(a)) = "USE(" ^ X.prettyprint_oper X.Long a ^ ")"
246 | dustostring (SUCC(a)) = "SUCC(" ^ Int.toString a ^ ")"
247 | dustostring ISMOVE = "ISMOVE"
248
0a24e44d
JW
249 (* val liveness : pseudoasm -> livenesses
250 * analyzes liveness of variables in the given pseudo-asm
251 *)
252
253 fun liveness instrs =
12aa4087 254 let
0a24e44d 255 val preds = defusesucc (number instrs)
6ade8b0a
JW
256(* val (_,l) = ListPair.unzip preds
257 val () = print (
258 String.concatWith "\n" (
259 List.map
260 (fn a => String.concatWith ", " (List.map dustostring a))
261 l
262 )
263 )*)
0a24e44d 264 val init = uselive preds
6ade8b0a 265 val initmap = LiveMap.foldri (fn (n,a,b) => LiveMap.insert (b, n, a)) LiveMap.empty init
12aa4087 266 in
6ade8b0a
JW
267 (preds, liveiter initmap preds)
268 end
269
270 fun prettyprint (set) =
271 OperSet.foldr
272 (fn (oper, s) => (X.prettyprint_oper X.Long oper) ^ ", " ^ s)
273 "-\n"
274 set
275
276 fun listify map =
277 let
278 val maxln = LiveMap.foldri (fn (a, _, b) => Int.max (a, b)) 0 map
279 val nums = List.tabulate (maxln+1, fn x => x)
280 in
281 List.map (fn num => valOf (LiveMap.find (map, num)) handle Option => OperSet.empty) nums
12aa4087
JW
282 end
283end
This page took 0.051453 seconds and 4 git commands to generate.