]> Joshua Wise's Git repositories - snipe.git/blame_incremental - codegen/liveness.sml
Initial import of l4c
[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 = x86.oper;
11 structure LiveMap : ORD_MAP
12 where type Key.ord_key = int;
13
14 type live = int * OperSet.set
15 type pseudoasm = x86.insn list
16 type livenesses = OperSet.set LiveMap.map
17
18 type ident = int
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
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 = x86
37
38 structure OperSet = x86.OperSet
39 structure LiveMap = x86.LiveMap
40
41 type live = int * OperSet.set
42 type pseudoasm = X.insn list
43 type numasm = X.insn LiveMap.map
44 type livenesses = OperSet.set LiveMap.map
45
46 type ident = int
47 datatype pred = DEF of X.oper | USE of X.oper | SUCC of ident | ISMOVE
48
49 type predicates = pred list LiveMap.map
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
59 foldr
60 LiveMap.insert'
61 LiveMap.empty
62 (ListPair.zip (nums,instrs))
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
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)
75
76 (* val defhit/usehit : X.oper -> pred list
77 * helper functions to discard constant operands *)
78 fun defhit (X.REG a) = [DEF(X.REG a)]
79 | defhit (X.TEMP a) = [DEF(X.TEMP a)]
80 | defhit (X.REL(o1, o2)) = usehit o1 @ usehit o2
81 | defhit (X.OSIZE(s, oo)) = defhit oo
82 | defhit (_) = nil
83
84 and usehit (X.REG a) = [USE(X.REG a)]
85 | usehit (X.TEMP a) = [USE(X.TEMP a)]
86 | usehit (X.REL(o1, o2)) = usehit o1 @ usehit o2
87 | usehit (X.OSIZE(s, oo)) = usehit oo
88 | usehit (_) = nil
89
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
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(_)) = (nil)
103 | gendef (n, X.COMMENT(_)) = (nil)
104 | gendef (n, X.LIVEIGN (_)) = ([SUCC (n+1)])
105 | gendef (n, X.MOV(dest, src)) = (defhit dest @ usehit src @ [SUCC(n+1), ISMOVE])
106 | gendef (n, X.LEA(dest, src)) = (defhit dest @ usehit src @ [SUCC(n+1)])
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)),
112 USE(X.REG(X.EAX)), USE(X.REG(X.EDX)),
113 SUCC(n+1)])
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)])
133 in
134 LiveMap.mapi gendef l
135 end
136
137 (* val uselive : (int * pred list) list -> OperSet.set LiveMap.map
138 * generates liveness for 'use' rules to get the iterative analyzer started
139 *)
140 fun uselive preds =
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
148 )
149 preds
150
151 (* val subsetlive : OperSet.set LiveMap.map * OperSet.set LiveMap.map -> bool
152 * true if first is subset of second
153 *)
154
155 fun subsetlive (l1,l2) =
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
181
182 (* val liveiter : OperSet.set LiveMap.map -> (int * pred list) list -> OperSet.set LiveMap.map
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 :
186 *
187 * use(l',x)
188 * !def(l,x)
189 * succ(l,l')
190 * --------------
191 * live(l,x)
192 *)
193
194 fun liveiter livemap preds =
195 let
196
197
198
199 (* val lives : int list -> OperSet.set LiveMap.map -> OperSet.set
200 * scans l for live variables in succeeding lines *)
201 fun lives l' idents =
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
210
211 (* val isndef : X.oper -> pred list -> bool
212 * checks to see if x is defined in a predicate list *)
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'
216 | isndef x nil = true
217
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)
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 *)
230 val newl = LiveMap.foldri
231 (fn (n, a, b) => OperSet.foldr
232 (fn (a',b') => if (isndef a' a) then liveadd (n, a') b' else b')
233 b
234 (lives b (succs a))
235 )
236 livemap
237 preds
238 in
239 if subsetlive (newl, livemap)
240 then livemap
241 else liveiter newl preds
242 end
243
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
249 (* val liveness : pseudoasm -> livenesses
250 * analyzes liveness of variables in the given pseudo-asm
251 *)
252
253 fun liveness instrs =
254 let
255 val preds = defusesucc (number instrs)
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 )*)
264 val init = uselive preds
265 val initmap = LiveMap.foldri (fn (n,a,b) => LiveMap.insert (b, n, a)) LiveMap.empty init
266 in
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
282 end
283end
This page took 0.021185 seconds and 4 git commands to generate.