2 * Takes a list of mappings of temporaries to colors and a pseudoasm listing,
3 * then produces x86 code.
4 * Author: Chris Lu <czl@andrew.cmu.edu>
5 * Author: Joshua Wise <jwise@andrew.cmu.edu>
10 type colorings = (Temp.temp * int) list
11 type asm = Blarg.insn list
13 val solidify : colorings -> asm -> asm
16 structure Solidify :> SOLIDIFY =
21 type colorings = (Temp.temp * int) list
22 type asm = Blarg.insn list
26 structure TempMap = SplayMapFn(struct
27 type ord_key = Temp.temp
28 val compare = Temp.compare
32 fun solidify (regmap : colorings) (instrs : asm) : asm =
34 (* r11 and r12 is reserved for spilling *)
35 val maxreg = X.regtonum X.R10
41 val tempnums = List.foldr (fn ((t,n),b) => TempMap.insert(b,t,n)) (TempMap.empty) regmap
42 fun temptonum (t: T.temp) : int = valOf (TempMap.find (tempnums, t))
44 fun temptoreg (t: T.temp) : Blarg.reg =
45 numtoreg (temptonum t)
46 handle Option => raise ErrorMsg.InternalError ("Uncolored temp "^(Temp.name t)^", agh!")
51 (* Determine which need to be saved. *)
52 val opsused = (map (fn (_, n) => X.REG (numtoreg n handle Spilled => X.R12)) regmap) @ [X.REG X.R11]
53 val saveregs = X.OperSet.intersection (
54 X.OperSet.addList (X.OperSet.empty, opsused),
63 val savelist = X.OperSet.listItems saveregs
64 val nsave = length savelist
66 val numreg = foldr (Int.max) 0 (map (fn (_, n) => n) regmap) (* Number of registers used. *)
67 val nspilled = Int.max (numreg - maxreg, 0) (* Number of spilled registers. *)
68 fun isspilled (X.TEMP temp) = (temptonum temp) > maxreg (* Whether a register is spilled *)
69 | isspilled (X.STACKARG _) = true
72 val stacksz = (nspilled + nsave) * 1
73 fun stackpos (reg: int) = stacksz - (reg - maxreg + nsave) * 1 (* Stack position of some register number *)
76 [X.INSN (X.AL, X.MOVLIT (X.REG X.R4, Word.fromInt stacksz)),
77 X.INSN (X.AL, X.SUB (X.REG X.SP, X.REG X.R4))] @
81 [X.INSN (X.AL, X.MOVLIT (X.REG X.R4, Word.fromInt (stacksz - 1*(num+1)))),
82 X.INSN (X.AL, X.ADD (X.REG X.R4, X.REG X.SP)),
83 X.INSN (X.AL, X.STO (X.REG X.R4, reg))])
84 (List.tabulate (nsave, fn x => x), savelist)
91 [X.INSN (X.AL, X.MOVLIT (X.REG X.R4, Word.fromInt (stacksz - 1*(num+1)))),
92 X.INSN (X.AL, X.ADD (X.REG X.R4, X.REG X.SP)),
93 X.INSN (X.AL, X.LDR (reg, X.REG X.R4))])
94 (List.tabulate (nsave, fn x => x), savelist)
97 [X.INSN (X.AL, X.MOVLIT (X.REG X.R4, Word.fromInt stacksz)),
98 X.INSN (X.AL, X.ADD (X.REG X.SP, X.REG X.R4))]
99 val endlbl = Label.new()
101 fun spill (X.TEMP temp, xreg: Blarg.reg) = (* Spill a register if need be. *)
103 val base = X.REG X.SP
104 val offs = Word.fromInt (stackpos (temptonum temp))
106 if (isspilled (X.TEMP temp))
107 then raise ErrorMsg.InternalError "unspill not supported" (*[X.MOV ((X.REL (base, offs, 0w1), Tm.Quad), (X.REG xreg, Tm.Quad))]*)
110 | spill (X.STACKARG _, _) = raise ErrorMsg.InternalError "Cannot spill to a stack arg"
111 | spill _ = nil (* Nothing else can be spilled. *)
112 fun unspill (X.TEMP temp, xreg: Blarg.reg) = (* Unspill a register if need be. *)
114 val base = X.REG X.SP
115 val offs = Word.fromInt (stackpos (temptonum temp))
117 if (isspilled (X.TEMP temp))
118 then raise ErrorMsg.InternalError "unspill not supported" (*[X.MOV ((X.REG xreg, Tm.Quad), (X.REL (base, offs, 0w1), Tm.Quad))]*)
121 | unspill (X.STACKARG arg, xreg) =
123 val base = X.REG X.SP
124 val offs = Word.fromInt (stacksz + 8 + (arg * 8))
126 (*[X.MOV ((X.REG xreg, s), (X.REL (base, offs, 0w1), s))]*)
127 raise ErrorMsg.InternalError "unspill from stack not supported"
131 fun unspill_ops (op1, op2) =
132 case (isspilled op1, isspilled op2)
133 of (false, false) => []
134 | (true, false) => unspill (op1, spillreg1)
135 | (false, true) => unspill (op2, spillreg2)
136 | (true, true) => unspill (op1, spillreg1) @ unspill (op2, spillreg2)
138 fun respill_ops (op1, op2) =
139 case (isspilled op1, isspilled op2) (* no instruction writes back to op2 *)
141 | (true, _) => spill (op1, spillreg1)
145 of (X.TEMP temp) => if isspilled op1
146 then (X.REG spillreg1)
147 else X.REG (temptoreg temp)
148 | (X.STACKARG arg) => X.REG spillreg1
151 fun real_ops (op1, op2) =
153 of (X.TEMP temp) => if isspilled op1
154 then (X.REG spillreg1)
155 else X.REG (temptoreg temp)
156 | (X.STACKARG arg) => X.REG spillreg1
159 of (X.TEMP temp) => if isspilled op2
160 then (X.REG spillreg2)
161 else X.REG (temptoreg temp)
162 | (X.STACKARG arg) => X.REG spillreg2
165 fun whack_insn (pred, insn, op1, op2) =
166 (map (fn i => X.INSN (pred, i)) (unspill_ops (op1, op2))) @
167 [ X.INSN (pred, insn (real_ops (op1, op2))) ] @
168 (map (fn i => X.INSN (pred, i)) (respill_ops (op1, op2)))
170 fun transform (X.DIRECTIVE s) = [X.DIRECTIVE s]
171 | transform (X.COMMENT s) = [X.COMMENT s]
172 | transform (X.LABEL l) = [X.LABEL l]
173 | transform (X.LIVEIGN a) = transform a
175 (* god the special cases are going to suck *)
176 | transform (X.INSN (pred, X.MOVLIT (op1, w))) =
177 [ X.INSN (pred, X.MOVLIT (real_op1 op1, w)) ] @
179 then spill (op1, spillreg1)
181 | transform (X.INSN (pred, X.MOVSYM (op1, w))) =
182 [ X.INSN (pred, X.MOVSYM (real_op1 op1, w)) ] @
184 then spill (op1, spillreg1)
186 | transform (X.INSN (pred, X.MOVLBL (op1, w))) =
187 [ X.INSN (pred, X.MOVLBL (real_op1 op1, w)) ] @
189 then spill (op1, spillreg1)
192 (* and here comes the boilerplate *)
193 | transform (X.INSN (pred, X.LDR (op1, op2))) = whack_insn (pred, X.LDR, op1, op2)
194 | transform (X.INSN (pred, X.STO (op1, op2))) = whack_insn (pred, X.STO, op1, op2)
195 | transform (X.INSN (pred, X.MOV (op1, op2))) = whack_insn (pred, X.MOV, op1, op2)
196 | transform (X.INSN (pred, X.MOVS (op1, op2))) = whack_insn (pred, X.MOVS, op1, op2)
197 | transform (X.INSN (pred, X.ADD (op1, op2))) = whack_insn (pred, X.ADD, op1, op2)
198 | transform (X.INSN (pred, X.ADDS (op1, op2))) = whack_insn (pred, X.ADDS, op1, op2)
199 | transform (X.INSN (pred, X.SUB (op1, op2))) = whack_insn (pred, X.SUB, op1, op2)
200 | transform (X.INSN (pred, X.SUBS (op1, op2))) = whack_insn (pred, X.SUBS, op1, op2)
201 | transform (X.INSN (pred, X.AND (op1, op2))) = whack_insn (pred, X.AND, op1, op2)
202 | transform (X.INSN (pred, X.ANDS (op1, op2))) = whack_insn (pred, X.ANDS, op1, op2)
203 | transform (X.INSN (pred, X.NOT (op1, op2))) = whack_insn (pred, X.NOT, op1, op2)
204 | transform (X.INSN (pred, X.NOTS (op1, op2))) = whack_insn (pred, X.NOTS, op1, op2)
205 | transform (X.INSN (pred, X.PUSH (op1, op2))) = if isspilled op2
206 then raise ErrorMsg.InternalError "PUSH on spilled op2 is not possible"
207 else [ X.INSN (pred, X.PUSH (real_ops (op1, op2))) ]
208 | transform (X.INSN (pred, X.POP (X.REG X.SP, X.REG X.PC))) = [ X.INSN (pred, X.MOVLBL (X.REG X.PC, endlbl)) ] (* optimize epilogue? *)
209 | transform (X.INSN (pred, X.POP (op1, op2))) = if isspilled op2
210 then raise ErrorMsg.InternalError "POP on spilled op2 is not possible"
211 else [ X.INSN (pred, X.POP (real_ops (op1, op2))) ]
212 | transform (X.INSN (pred, X.CALL (op1, op2, i))) = if isspilled op2
213 then raise ErrorMsg.InternalError "CALL on spilled op2 is not possible"
214 else [ X.INSN (pred, X.CALL ((fn (x, y) => (x, y, i)) (real_ops (op1, op2)))) ]
215 | transform (X.INSN (pred, X.SHR (op1, op2))) = whack_insn (pred, X.SHR, op1, op2)
216 | transform (X.INSN (pred, X.SHL (op1, op2))) = whack_insn (pred, X.SHL, op1, op2)
217 (*| transform _ = raise ErrorMsg.InternalError "unimplemented"*)
219 (*if (nsave < 2) then
220 List.concat (prologue :: (map transform instrs))
223 List.concat (prologue ::
224 ((map transform instrs) @
227 [X.INSN (X.AL, X.POP (X.REG X.SP, X.REG X.PC))]