2 * blargCPU instruction/operand internal representation and manipulation
3 * Author: Joshua Wise <jwise@andrew.cmu.edu>
4 * Author: Chris Lu <czl@andrew.cmu.edu>
11 R0 | R1 | R2 | R3 | R4 | R5 | R6 | R7 | R8 | R9 | R10 | R11 | R12 | FR | SP | PC
12 (* operands to instructions *)
13 datatype oper = REG of reg |
16 datatype pred = NV | NE | EQ | LT | GT | LE | GE | AL
19 MOVLIT of oper * word |
20 MOVSYM of oper * Symbol.symbol |
21 MOVLBL of oper * Label.label |
36 CALL of oper * oper * int |
43 LABEL of Label.label |
47 structure OperSet : ORD_SET
48 where type Key.ord_key = oper;
49 structure LiveMap : ORD_MAP
50 where type Key.ord_key = int;
52 val regcmp : reg * reg -> order
53 val cmpoper : oper * oper -> order
54 val opereq : oper * oper -> bool
55 val regname : reg -> string
56 val regtonum : reg -> int
57 val numtoreg : int -> reg
58 val predname : pred -> string
59 val pp_oper : oper -> string
60 val print : insn -> string
63 structure Blarg :> BLARG =
68 R0 | R1 | R2 | R3 | R4 | R5 | R6 | R7 | R8 | R9 | R10 | R11 | R12 | FR | SP | PC
69 (* operands to instructions *)
70 datatype oper = REG of reg |
73 datatype pred = NV | NE | EQ | LT | GT | LE | GE | AL
76 MOVLIT of oper * word |
77 MOVSYM of oper * Symbol.symbol |
78 MOVLBL of oper * Label.label |
93 CALL of oper * oper * int |
100 LABEL of Label.label |
104 type func = Ast.ident * insn list
106 (* gives name of reg *)
127 val (r, n) = valOf (List.find (fn (r, _) => r = reg) regnames)
132 fun predname NV = "nv"
141 (* gives number (color) associated with reg *)
156 | regtonum _ = raise ErrorMsg.InternalError ("regtonum: Invalid register")
158 (* gives reg associated with number (color) *)
172 | numtoreg n = raise ErrorMsg.InternalError ("numtoreg: Invalid register "^(Int.toString n))
174 (* register compare *)
175 fun regcmp (r1, r2) = Int.compare (regtonum r1, regtonum r2)
177 (* operand compare; arbitrary order imposed to make
178 * various things easier (e.g. liveness, for sorting)
180 fun cmpoper (REG reg1, REG reg2) = regcmp (reg1, reg2)
181 | cmpoper (TEMP temp1, TEMP temp2) = Temp.compare (temp1,temp2)
182 | cmpoper (REG _, _) = LESS
183 | cmpoper (_, _) = GREATER
185 fun opereq (REG a, REG b) = a = b
186 | opereq (TEMP a, TEMP b) = Temp.eq (a, b)
187 | opereq (_, _) = false
189 structure OperSet = ListSetFn (
192 val compare = cmpoper
195 structure LiveMap = SplayMapFn(struct
197 val compare = Int.compare
200 fun pp_oper (REG r) = "%" ^ (regname r)
201 | pp_oper (TEMP t) = (Temp.name t)
202 | pp_oper (STACKARG i) = "arg#"^Int.toString i
204 fun pp_insn pr (MOVLIT (d, w)) = "\tmov"^pr^" "^(pp_oper d)^", #"^(Word.toString w)^"\n"
205 | pp_insn pr (MOVSYM (d, s)) = "\tmov"^pr^" "^(pp_oper d)^", #"^(Symbol.name s)^"\n"
206 | pp_insn pr (MOVLBL (d, l)) = "\tmov"^pr^" "^(pp_oper d)^", #"^(Label.name l)^"\n"
207 | pp_insn pr (LDR (d, s)) = "\tldr"^pr^" "^(pp_oper d)^", ["^(pp_oper s)^"]\n"
208 | pp_insn pr (STO (d, s)) = "\tsto"^pr^" ["^(pp_oper d)^"], "^(pp_oper s)^"\n"
209 | pp_insn pr (MOV (d, s)) = "\tmov"^pr^" "^(pp_oper d)^", "^(pp_oper s)^"\n"
210 | pp_insn pr (MOVS (d, s)) = "\tmovs"^pr^" "^(pp_oper d)^", "^(pp_oper s)^"\n"
211 | pp_insn pr (ADD (d, s)) = "\tadd"^pr^" "^(pp_oper d)^", "^(pp_oper s)^"\n"
212 | pp_insn pr (ADDS (d, s)) = "\tadds"^pr^" "^(pp_oper d)^", "^(pp_oper s)^"\n"
213 | pp_insn pr (SUB (d, s)) = "\tsub"^pr^" "^(pp_oper d)^", "^(pp_oper s)^"\n"
214 | pp_insn pr (SUBS (d, s)) = "\tsubs"^pr^" "^(pp_oper d)^", "^(pp_oper s)^"\n"
215 | pp_insn pr (AND (d, s)) = "\tand"^pr^" "^(pp_oper d)^", "^(pp_oper s)^"\n"
216 | pp_insn pr (ANDS (d, s)) = "\tands"^pr^" "^(pp_oper d)^", "^(pp_oper s)^"\n"
217 | pp_insn pr (NOT (d, s)) = "\tnot"^pr^" "^(pp_oper d)^", "^(pp_oper s)^"\n"
218 | pp_insn pr (NOTS (d, s)) = "\tnots"^pr^" "^(pp_oper d)^", "^(pp_oper s)^"\n"
219 | pp_insn pr (PUSH (d, s)) = "\tpush"^pr^" "^(pp_oper d)^", "^(pp_oper s)^"\n"
220 | pp_insn pr (POP (d, s)) = "\tpop"^pr^" "^(pp_oper d)^", "^(pp_oper s)^"\n"
221 | pp_insn pr (CALL (d, s, n)) = "\tcall"^pr^" "^(pp_oper d)^", "^(pp_oper s)^" # ("^(Int.toString n)^" args)\n"
222 | pp_insn pr (SHR (d, s)) = "\tshr"^pr^" "^(pp_oper d)^", "^(pp_oper s)^"\n"
223 | pp_insn pr (SHL (d, s)) = "\tshl"^pr^" "^(pp_oper d)^", "^(pp_oper s)^"\n"
225 (* pretty prints the asm *)
226 fun print (DIRECTIVE(str)) = str ^ "\n"
227 | print (COMMENT(str)) = "// " ^ str ^ "\n"
228 | print (LABEL(l)) = Label.name l ^ ":\n"
229 | print (INSN (pred, insn)) = pp_insn (predname pred) insn
230 | print (LIVEIGN i) = print i