]>
Commit | Line | Data |
---|---|---|
1 | (* L3 Compiler | |
2 | * AST -> IR Translator | |
3 | * Author: Kaustuv Chaudhuri <kaustuv+@cs.cmu.edu> | |
4 | * Modified by: Alex Vaynberg <alv@andrew.cmu.edu> | |
5 | * Modified: Frank Pfenning <fp@cs.cmu.edu> | |
6 | * Modified: Chris Lu <czl@andrew.cmu.edu> | |
7 | * Modified: Joshua Wise <jwise@andrew.cmu.edu> | |
8 | *) | |
9 | ||
10 | signature TRANS = | |
11 | sig | |
12 | (* translate abstract syntax tree to IR tree *) | |
13 | val translate : Ast.program -> Tree.program | |
14 | end | |
15 | ||
16 | structure Trans :> TRANS = | |
17 | struct | |
18 | ||
19 | structure A = Ast | |
20 | structure T = Tree | |
21 | ||
22 | fun trans_oper A.PLUS = T.ADD | |
23 | | trans_oper A.MINUS = T.SUB | |
24 | | trans_oper A.TIMES = T.MUL | |
25 | | trans_oper A.DIVIDEDBY = T.DIV | |
26 | | trans_oper A.MODULO = T.MOD | |
27 | | trans_oper A.LSH = T.LSH | |
28 | | trans_oper A.RSH = T.RSH | |
29 | | trans_oper A.LOGOR = T.LOGOR | |
30 | | trans_oper A.LOGAND = T.LOGAND | |
31 | | trans_oper A.BITOR = T.BITOR | |
32 | | trans_oper A.BITXOR = T.BITXOR | |
33 | | trans_oper A.BITAND = T.BITAND | |
34 | | trans_oper A.NEQ = T.NEQ | |
35 | | trans_oper A.EQ = T.EQ | |
36 | | trans_oper A.LT = T.LT | |
37 | | trans_oper A.LE = T.LE | |
38 | | trans_oper A.GE = T.GE | |
39 | | trans_oper A.GT = T.GT | |
40 | | trans_oper _ = raise ErrorMsg.InternalError "expected AST binop, got AST unop" | |
41 | ||
42 | fun translate (defs, funcs) = | |
43 | let | |
44 | val funclist = Symbol.elemsi funcs | |
45 | val _ = Type.alignment_reset() | |
46 | val _ = Type.sizeof_reset() | |
47 | fun sizeof a = Type.sizeof defs a | |
48 | fun alignment a = Type.alignment defs a | |
49 | fun align t curpos = Type.align defs t curpos | |
50 | ||
51 | fun offset_s id (Type.Typedef(id')) = | |
52 | let | |
53 | val shit = Symbol.look' defs id' | |
54 | fun eat (Type.Struct(l)) = l | |
55 | | eat (Type.MarkedTypedef(a)) = eat (Mark.data a) | |
56 | fun offset_s' ((id1,t)::l') curofs = | |
57 | let | |
58 | val a = align t curofs | |
59 | in | |
60 | if Symbol.compare(id,id1) = EQUAL | |
61 | then a | |
62 | else offset_s' l' (a + sizeof t) | |
63 | end | |
64 | | offset_s' nil _ = raise ErrorMsg.InternalError "looking for offset of something that isn't in the structure" | |
65 | in | |
66 | offset_s' (eat shit) 0 | |
67 | end | |
68 | | offset_s _ _ = raise ErrorMsg.InternalError "cannot find offset into non-typedef" | |
69 | ||
70 | fun type_s id (Type.Typedef id') = | |
71 | let | |
72 | val td = | |
73 | case Type.defdata (Symbol.look' defs id') | |
74 | of Type.Struct d => d | |
75 | | _ => raise ErrorMsg.InternalError "data didn't return struct" | |
76 | fun type_s' ((id',t)::l) = | |
77 | if (Symbol.compare (id, id') = EQUAL) | |
78 | then t | |
79 | else type_s' l | |
80 | | type_s' nil = raise ErrorMsg.InternalError "struct member not found in type_s" | |
81 | in | |
82 | type_s' td | |
83 | end | |
84 | | type_s id _ = raise ErrorMsg.InternalError "cannot find internal type non-typedef" | |
85 | ||
86 | fun deref (Type.Pointer i) = i | |
87 | | deref (Type.Array i) = i | |
88 | | deref _ = raise ErrorMsg.InternalError "cannot deref non-pointer" | |
89 | ||
90 | fun trans_unop A.NEGATIVE = T.NEG | |
91 | | trans_unop A.BITNOT = T.BITNOT | |
92 | | trans_unop A.BANG = T.BANG | |
93 | | trans_unop _ = raise ErrorMsg.InternalError "expected AST unop, got AST binop" | |
94 | ||
95 | fun typeof' vartypes exp = TypeChecker.typeof (defs, funcs) vartypes NONE exp | |
96 | ||
97 | fun trans_exp env vartypes (A.Var(id)) = | |
98 | (* after type-checking, id must be declared; do not guard lookup *) | |
99 | T.TEMP (Symbol.look' env id) | |
100 | | trans_exp env vartypes (A.ConstExp c) = T.CONST(c) | |
101 | | trans_exp env vartypes (A.OpExp(oper, [e1, e2])) = | |
102 | T.BINOP(trans_oper oper, trans_exp env vartypes e1, trans_exp env vartypes e2) | |
103 | | trans_exp env vartypes (A.OpExp(oper, [e])) = | |
104 | T.UNOP(trans_unop oper, trans_exp env vartypes e) | |
105 | | trans_exp env vartypes (A.OpExp(oper, _)) = | |
106 | raise ErrorMsg.InternalError "expected one or two operands, got it in the oven" | |
107 | | trans_exp env vartypes (A.Marked(marked_exp)) = | |
108 | trans_exp env vartypes (Mark.data marked_exp) | |
109 | | trans_exp env vartypes (A.FuncCall(func, stms)) = | |
110 | T.CALL(func, | |
111 | List.map | |
112 | (fn exp => (trans_exp env vartypes exp)) | |
113 | stms) | |
114 | | trans_exp env vartypes (A.Member (exp, id)) = | |
115 | let | |
116 | val apk = T.BINOP (T.ADD, trans_exp env vartypes exp, T.CONST (Word32.fromInt (offset_s id (typeof' vartypes exp)))) | |
117 | val tipo = type_s id (typeof' vartypes exp) | |
118 | in | |
119 | if Type.issmall tipo | |
120 | then T.MEMORY(apk) | |
121 | else apk | |
122 | end | |
123 | | trans_exp env vartypes (A.DerefMember (exp, id)) = | |
124 | trans_exp env vartypes (A.Member (A.Dereference (exp), id)) | |
125 | | trans_exp env vartypes (A.Dereference(exp)) = | |
126 | if (Type.issmall (deref (typeof' vartypes exp))) | |
127 | then T.MEMORY(trans_exp env vartypes exp) | |
128 | else trans_exp env vartypes exp | |
129 | | trans_exp env vartypes (A.ArrIndex(exp1, exp2)) = | |
130 | let | |
131 | val asubk = T.BINOP(T.ADD, trans_exp env vartypes exp1, | |
132 | T.BINOP(T.MUL, trans_exp env vartypes exp2, | |
133 | T.CONST(Word32.fromInt(sizeof (deref (typeof' vartypes exp1)))))) | |
134 | val tipo = deref (typeof' vartypes exp1) | |
135 | val d = | |
136 | if not (Flag.isset Flags.safe) | |
137 | then asubk | |
138 | else T.COND (T.BINOP | |
139 | (T.BE, | |
140 | T.MEMORY (T.BINOP ( | |
141 | T.SUB, | |
142 | trans_exp env vartypes exp1, | |
143 | T.CONST 0w8)), | |
144 | trans_exp env vartypes exp2), | |
145 | T.NULLPTR, | |
146 | asubk) | |
147 | in | |
148 | if Type.issmall tipo | |
149 | then T.MEMORY(d) | |
150 | else d | |
151 | end | |
152 | | trans_exp env vartypes (A.New(tipo)) = | |
153 | let | |
154 | val t1 = T.TEMP (Temp.new "result") | |
155 | in | |
156 | T.STMVAR ( | |
157 | [T.MOVE (t1, T.ALLOC (T.CONST (Word32.fromInt(sizeof tipo)))), | |
158 | T.EFFECT (T.MEMORY (t1))], | |
159 | t1) | |
160 | end | |
161 | | trans_exp env vartypes (A.NewArr(tipo, exp)) = | |
162 | let | |
163 | val size = T.BINOP(T.MUL, trans_exp env vartypes exp, T.CONST(Word32.fromInt(sizeof tipo))) | |
164 | val t1 = T.TEMP (Temp.new "allocated address") | |
165 | val ts = T.TEMP (Temp.new "size") | |
166 | in | |
167 | if not (Flag.isset Flags.safe) | |
168 | then T.STMVAR ([T.MOVE (t1, T.ALLOC size), | |
169 | T.EFFECT (T.COND (T.BINOP (T.EQ, trans_exp env vartypes exp, T.CONST 0w0), T.CONST 0w0, T.MEMORY (t1)))], | |
170 | t1) | |
171 | else T.COND (T.BINOP(T.EQ, size, T.CONST 0w0), | |
172 | T.NULLPTR, | |
173 | T.STMVAR ( | |
174 | [T.MOVE(t1, | |
175 | T.COND( | |
176 | T.BINOP(T.LT, size, T.CONST 0w0), | |
177 | T.NULLPTR, | |
178 | T.ALLOC (T.BINOP (T.ADD, size, T.CONST 0w8))) | |
179 | ), | |
180 | T.MOVE(T.MEMORY (t1), trans_exp env vartypes exp)], | |
181 | T.BINOP(T.ADD, t1, T.CONST 0w8))) | |
182 | end | |
183 | | trans_exp env vartypes (A.Null) = T.NULLPTR | |
184 | | trans_exp env vartypes (A.Conditional(c,e1,e2)) = T.COND(trans_exp env vartypes c, trans_exp env vartypes e1, trans_exp env vartypes e2) | |
185 | ||
186 | (* anything else should be impossible *) | |
187 | ||
188 | (* trans_stms : Temp.temp Symbol.table -> (Label.label * Label.label) option -> A.stm list -> Tree.stm list | |
189 | * translates a statement to the corresponding IR | |
190 | * we pass around the environment and the current loop context, if any | |
191 | * (usually called ls, which contains a continue label and a break label) | |
192 | *) | |
193 | fun trans_stms vars vartypes ls (A.Assign(e1,e2)::stms) = T.MOVE(trans_exp vars vartypes e1, trans_exp vars vartypes e2)::(trans_stms vars vartypes ls stms) | |
194 | | trans_stms vars vartypes ls (A.AsnOp(oop,e1,e2)::stms) = | |
195 | let | |
196 | val te1 = trans_exp vars vartypes e1 | |
197 | val te2 = trans_exp vars vartypes e2 | |
198 | val t1 = T.TEMP (Temp.new "memory deref cache") | |
199 | in | |
200 | case te1 | |
201 | of T.MEMORY(m) => T.MOVE(t1, m) :: T.MOVE (T.MEMORY(t1), T.BINOP(trans_oper oop, T.MEMORY(t1), te2)) :: (trans_stms vars vartypes ls stms) | |
202 | | _ => T.MOVE(te1, T.BINOP(trans_oper oop, te1, te2)) :: (trans_stms vars vartypes ls stms) | |
203 | end | |
204 | | trans_stms vars vartypes ls (A.Return e::stms) = | |
205 | let | |
206 | val remainder = trans_stms vars vartypes ls stms | |
207 | in | |
208 | T.RETURN (trans_exp vars vartypes e) | |
209 | :: remainder | |
210 | end | |
211 | | trans_stms vars vartypes ls (A.If(e, s, NONE)::stms) = | |
212 | let | |
213 | val l = Label.new () | |
214 | val strans = trans_stms vars vartypes ls s | |
215 | val remainder = trans_stms vars vartypes ls stms | |
216 | in | |
217 | (T.JUMPIFN(trans_exp vars vartypes e, l) | |
218 | :: strans | |
219 | @ [T.LABEL (l)] | |
220 | @ remainder) | |
221 | end | |
222 | | trans_stms vars vartypes ls (A.If(e, s, SOME s2)::stms) = | |
223 | let | |
224 | val l = Label.new () | |
225 | val l2 = Label.new () | |
226 | val s1trans = trans_stms vars vartypes ls s | |
227 | val s2trans = trans_stms vars vartypes ls s2 | |
228 | val remainder = trans_stms vars vartypes ls stms | |
229 | in | |
230 | (T.JUMPIFN(trans_exp vars vartypes e, l) | |
231 | :: s1trans | |
232 | @ [T.JUMP (l2), T.LABEL (l)] | |
233 | @ s2trans | |
234 | @ [T.LABEL (l2)] | |
235 | @ remainder) | |
236 | end | |
237 | | trans_stms vars vartypes ls (A.For(s1, e, s2, s)::stms) = | |
238 | let | |
239 | val head = Label.new () | |
240 | val tail = Label.new () | |
241 | val loop = Label.new () | |
242 | val stm1 = if isSome s1 then trans_stms vars vartypes NONE [valOf s1] else nil | |
243 | val strans = trans_stms vars vartypes (SOME(loop,tail)) s | |
244 | val stm2 = if isSome s2 then trans_stms vars vartypes NONE [valOf s2] else nil | |
245 | val remainder = trans_stms vars vartypes ls stms | |
246 | in | |
247 | (stm1 | |
248 | @ [T.LABEL head, T.JUMPIFN(trans_exp vars vartypes e, tail)] | |
249 | @ strans | |
250 | @ [T.LABEL loop] | |
251 | @ stm2 | |
252 | @ [T.JUMP head, T.LABEL tail] | |
253 | @ remainder) | |
254 | end | |
255 | | trans_stms vars vartypes ls (A.While(e, s)::stms) = | |
256 | let | |
257 | val head = Label.new () | |
258 | val tail = Label.new () | |
259 | val strans = trans_stms vars vartypes (SOME(head,tail)) s | |
260 | val remainder = trans_stms vars vartypes ls stms | |
261 | in | |
262 | (T.LABEL head | |
263 | :: T.JUMPIFN(trans_exp vars vartypes e, tail) | |
264 | :: strans | |
265 | @ [T.JUMP head, T.LABEL tail] | |
266 | @ remainder) | |
267 | end | |
268 | | trans_stms vars vartypes ls (A.Effect(e)::stms) = (T.EFFECT (trans_exp vars vartypes e)) :: (trans_stms vars vartypes ls stms) | |
269 | | trans_stms vars vartypes (SOME(b,e)) (A.Break::stms) = | |
270 | let | |
271 | val remainder = trans_stms vars vartypes (SOME(b,e)) stms | |
272 | in | |
273 | ((T.JUMP e) :: remainder) | |
274 | end | |
275 | | trans_stms vars vartypes NONE (A.Break::_) = raise ErrorMsg.InternalError "Break from invalid location... should have been caught in typechecker" | |
276 | | trans_stms vars vartypes (SOME(b,e)) (A.Continue::stms) = | |
277 | let | |
278 | val remainder = trans_stms vars vartypes (SOME(b,e)) stms | |
279 | in | |
280 | ((T.JUMP b) :: remainder) | |
281 | end | |
282 | | trans_stms vars vartypes NONE (A.Continue::_) = raise ErrorMsg.InternalError "Continue from invalid location... should have been caught in typechecker" | |
283 | | trans_stms vars vartypes ls (A.Nop::stms) = trans_stms vars vartypes ls stms | |
284 | | trans_stms vars vartypes ls (A.MarkedStm m :: stms) = trans_stms vars vartypes ls ((Mark.data m) :: stms) | |
285 | | trans_stms vars vartypes _ nil = nil | |
286 | ||
287 | fun trans_funcs ((id, A.Extern(_, _))::l) = trans_funcs l | |
288 | | trans_funcs ((id, A.MarkedFunction a)::l) = trans_funcs ((id, Mark.data a)::l) | |
289 | | trans_funcs ((id, A.Function(t, args, vars, body))::l) = | |
290 | let | |
291 | val allvars = foldr | |
292 | (fn ((name, t),b) => | |
293 | Symbol.bind b (name, Temp.new (Symbol.name(name)))) | |
294 | Symbol.empty | |
295 | (args @ vars) | |
296 | val vartypes = foldr (fn ((i, t), b) => Symbol.bind b (i, t)) Symbol.empty (args @ vars) | |
297 | val b = trans_stms allvars vartypes NONE body | |
298 | val (argn,_) = ListPair.unzip args | |
299 | val numberedargs = ListPair.zip (List.tabulate (length argn, fn x => x), argn) | |
300 | val argmv = map | |
301 | (fn (n, argname) => T.MOVE(T.TEMP (Symbol.look' allvars argname), T.ARG (n))) | |
302 | numberedargs | |
303 | in | |
304 | (T.FUNCTION(id, argmv @ b)) :: (trans_funcs l) | |
305 | end | |
306 | | trans_funcs nil = nil | |
307 | ||
308 | in | |
309 | trans_funcs funclist | |
310 | end | |
311 | end |