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