]> Joshua Wise's Git repositories - snipe.git/blame - trans/trans.sml
Add cast syntax.
[snipe.git] / trans / trans.sml
CommitLineData
6ade8b0a 1(* L3 Compiler
12aa4087
JW
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>
0a24e44d
JW
6 * Modified: Chris Lu <czl@andrew.cmu.edu>
7 * Modified: Joshua Wise <jwise@andrew.cmu.edu>
12aa4087
JW
8 *)
9
10signature TRANS =
11sig
12 (* translate abstract syntax tree to IR tree *)
5c79bb68 13 val translate : Ast.program -> Tree.program
12aa4087
JW
14end
15
16structure Trans :> TRANS =
17struct
18
19 structure A = Ast
20 structure T = Tree
0a24e44d 21
12aa4087
JW
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
0a24e44d
JW
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"
12aa4087 41
1144856b 42 fun translate (defs, funcs) =
6ade8b0a 43 let
1144856b 44 val funclist = Symbol.elemsi funcs
5c79bb68
JW
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
1144856b 50
5c79bb68 51 fun offset_s id (Type.Typedef(id')) =
1144856b
JW
52 let
53 val shit = Symbol.look' defs id'
5c79bb68
JW
54 fun eat (Type.Struct(l)) = l
55 | eat (Type.MarkedTypedef(a)) = eat (Mark.data a)
1144856b
JW
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
5c79bb68 62 else offset_s' l' (a + sizeof t)
1144856b
JW
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
5c79bb68 70 fun type_s id (Type.Typedef id') =
1144856b
JW
71 let
72 val td =
5c79bb68
JW
73 case Type.defdata (Symbol.look' defs id')
74 of Type.Struct d => d
1144856b
JW
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
5c79bb68
JW
86 fun deref (Type.Pointer i) = i
87 | deref (Type.Array i) = i
1144856b 88 | deref _ = raise ErrorMsg.InternalError "cannot deref non-pointer"
6ade8b0a
JW
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"
1144856b
JW
94
95 fun typeof' vartypes exp = TypeChecker.typeof (defs, funcs) vartypes NONE exp
6ade8b0a 96
1144856b 97 fun trans_exp env vartypes (A.Var(id)) =
6ade8b0a
JW
98 (* after type-checking, id must be declared; do not guard lookup *)
99 T.TEMP (Symbol.look' env id)
e63d3705 100 | trans_exp env vartypes (A.Cast (ty, e)) = trans_exp env vartypes e (* lurrr *)
1144856b 101 | trans_exp env vartypes (A.ConstExp c) = T.CONST(c)
a83f1d60 102 | trans_exp env vartypes (A.StringExp s) = T.STRING(Stringref.new s)
1144856b
JW
103 | trans_exp env vartypes (A.OpExp(oper, [e1, e2])) =
104 T.BINOP(trans_oper oper, trans_exp env vartypes e1, trans_exp env vartypes e2)
105 | trans_exp env vartypes (A.OpExp(oper, [e])) =
106 T.UNOP(trans_unop oper, trans_exp env vartypes e)
107 | trans_exp env vartypes (A.OpExp(oper, _)) =
6ade8b0a 108 raise ErrorMsg.InternalError "expected one or two operands, got it in the oven"
1144856b
JW
109 | trans_exp env vartypes (A.Marked(marked_exp)) =
110 trans_exp env vartypes (Mark.data marked_exp)
111 | trans_exp env vartypes (A.FuncCall(func, stms)) =
112 T.CALL(func,
113 List.map
141a7120
JW
114 (fn exp => (trans_exp env vartypes exp))
115 stms)
1144856b
JW
116 | trans_exp env vartypes (A.Member (exp, id)) =
117 let
118 val apk = T.BINOP (T.ADD, trans_exp env vartypes exp, T.CONST (Word32.fromInt (offset_s id (typeof' vartypes exp))))
5c79bb68 119 val tipo = type_s id (typeof' vartypes exp)
1144856b 120 in
5c79bb68 121 if Type.issmall tipo
141a7120 122 then T.MEMORY(apk)
1144856b
JW
123 else apk
124 end
125 | trans_exp env vartypes (A.DerefMember (exp, id)) =
126 trans_exp env vartypes (A.Member (A.Dereference (exp), id))
127 | trans_exp env vartypes (A.Dereference(exp)) =
5c79bb68 128 if (Type.issmall (deref (typeof' vartypes exp)))
141a7120 129 then T.MEMORY(trans_exp env vartypes exp)
1144856b
JW
130 else trans_exp env vartypes exp
131 | trans_exp env vartypes (A.ArrIndex(exp1, exp2)) =
132 let
133 val asubk = T.BINOP(T.ADD, trans_exp env vartypes exp1,
2ab9671f
JW
134 if sizeof (deref (typeof' vartypes exp1)) = 1
135 then trans_exp env vartypes exp2
136 else T.BINOP(T.MUL, trans_exp env vartypes exp2,
137 T.CONST(Word32.fromInt(sizeof (deref (typeof' vartypes exp1))))
138 )
139 )
5c79bb68
JW
140 val tipo = deref (typeof' vartypes exp1)
141 val d =
142 if not (Flag.isset Flags.safe)
143 then asubk
144 else T.COND (T.BINOP
145 (T.BE,
146 T.MEMORY (T.BINOP (
147 T.SUB,
148 trans_exp env vartypes exp1,
141a7120 149 T.CONST 0w8)),
5c79bb68
JW
150 trans_exp env vartypes exp2),
151 T.NULLPTR,
152 asubk)
1144856b 153 in
5c79bb68 154 if Type.issmall tipo
141a7120 155 then T.MEMORY(d)
5c79bb68 156 else d
1144856b
JW
157 end
158 | trans_exp env vartypes (A.New(tipo)) =
5c79bb68 159 let
141a7120 160 val t1 = T.TEMP (Temp.new "result")
5c79bb68
JW
161 in
162 T.STMVAR (
163 [T.MOVE (t1, T.ALLOC (T.CONST (Word32.fromInt(sizeof tipo)))),
141a7120 164 T.EFFECT (T.MEMORY (t1))],
5c79bb68
JW
165 t1)
166 end
1144856b 167 | trans_exp env vartypes (A.NewArr(tipo, exp)) =
5c79bb68 168 let
2ab9671f
JW
169 val size = if (sizeof tipo) = 1
170 then trans_exp env vartypes exp
171 else T.BINOP(T.MUL, trans_exp env vartypes exp, T.CONST(Word32.fromInt(sizeof tipo)))
141a7120
JW
172 val t1 = T.TEMP (Temp.new "allocated address")
173 val ts = T.TEMP (Temp.new "size")
5c79bb68
JW
174 in
175 if not (Flag.isset Flags.safe)
176 then T.STMVAR ([T.MOVE (t1, T.ALLOC size),
141a7120 177 T.EFFECT (T.COND (T.BINOP (T.EQ, trans_exp env vartypes exp, T.CONST 0w0), T.CONST 0w0, T.MEMORY (t1)))],
5c79bb68
JW
178 t1)
179 else T.COND (T.BINOP(T.EQ, size, T.CONST 0w0),
180 T.NULLPTR,
181 T.STMVAR (
182 [T.MOVE(t1,
183 T.COND(
184 T.BINOP(T.LT, size, T.CONST 0w0),
185 T.NULLPTR,
186 T.ALLOC (T.BINOP (T.ADD, size, T.CONST 0w8)))
187 ),
141a7120 188 T.MOVE(T.MEMORY (t1), trans_exp env vartypes exp)],
5c79bb68
JW
189 T.BINOP(T.ADD, t1, T.CONST 0w8)))
190 end
191 | trans_exp env vartypes (A.Null) = T.NULLPTR
192 | 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)
12aa4087 193
6ade8b0a
JW
194 (* anything else should be impossible *)
195
196 (* trans_stms : Temp.temp Symbol.table -> (Label.label * Label.label) option -> A.stm list -> Tree.stm list
197 * translates a statement to the corresponding IR
198 * we pass around the environment and the current loop context, if any
199 * (usually called ls, which contains a continue label and a break label)
200 *)
5c79bb68 201 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)
1144856b 202 | trans_stms vars vartypes ls (A.AsnOp(oop,e1,e2)::stms) =
6ade8b0a 203 let
1144856b
JW
204 val te1 = trans_exp vars vartypes e1
205 val te2 = trans_exp vars vartypes e2
141a7120 206 val t1 = T.TEMP (Temp.new "memory deref cache")
6ade8b0a 207 in
1144856b 208 case te1
141a7120 209 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)
5c79bb68 210 | _ => T.MOVE(te1, T.BINOP(trans_oper oop, te1, te2)) :: (trans_stms vars vartypes ls stms)
6ade8b0a 211 end
1144856b 212 | trans_stms vars vartypes ls (A.Return e::stms) =
6ade8b0a 213 let
1144856b 214 val remainder = trans_stms vars vartypes ls stms
6ade8b0a 215 in
141a7120 216 T.RETURN (trans_exp vars vartypes e)
6ade8b0a
JW
217 :: remainder
218 end
1144856b 219 | trans_stms vars vartypes ls (A.If(e, s, NONE)::stms) =
6ade8b0a
JW
220 let
221 val l = Label.new ()
1144856b
JW
222 val strans = trans_stms vars vartypes ls s
223 val remainder = trans_stms vars vartypes ls stms
6ade8b0a 224 in
1144856b 225 (T.JUMPIFN(trans_exp vars vartypes e, l)
0a24e44d
JW
226 :: strans
227 @ [T.LABEL (l)]
6ade8b0a
JW
228 @ remainder)
229 end
1144856b 230 | trans_stms vars vartypes ls (A.If(e, s, SOME s2)::stms) =
6ade8b0a
JW
231 let
232 val l = Label.new ()
0a24e44d 233 val l2 = Label.new ()
1144856b
JW
234 val s1trans = trans_stms vars vartypes ls s
235 val s2trans = trans_stms vars vartypes ls s2
236 val remainder = trans_stms vars vartypes ls stms
6ade8b0a 237 in
1144856b 238 (T.JUMPIFN(trans_exp vars vartypes e, l)
0a24e44d
JW
239 :: s1trans
240 @ [T.JUMP (l2), T.LABEL (l)]
241 @ s2trans
242 @ [T.LABEL (l2)]
6ade8b0a
JW
243 @ remainder)
244 end
1144856b 245 | trans_stms vars vartypes ls (A.For(s1, e, s2, s)::stms) =
6ade8b0a
JW
246 let
247 val head = Label.new ()
248 val tail = Label.new ()
249 val loop = Label.new ()
1144856b
JW
250 val stm1 = if isSome s1 then trans_stms vars vartypes NONE [valOf s1] else nil
251 val strans = trans_stms vars vartypes (SOME(loop,tail)) s
252 val stm2 = if isSome s2 then trans_stms vars vartypes NONE [valOf s2] else nil
253 val remainder = trans_stms vars vartypes ls stms
6ade8b0a
JW
254 in
255 (stm1
1144856b 256 @ [T.LABEL head, T.JUMPIFN(trans_exp vars vartypes e, tail)]
6ade8b0a
JW
257 @ strans
258 @ [T.LABEL loop]
259 @ stm2
260 @ [T.JUMP head, T.LABEL tail]
261 @ remainder)
262 end
1144856b 263 | trans_stms vars vartypes ls (A.While(e, s)::stms) =
6ade8b0a
JW
264 let
265 val head = Label.new ()
266 val tail = Label.new ()
1144856b
JW
267 val strans = trans_stms vars vartypes (SOME(head,tail)) s
268 val remainder = trans_stms vars vartypes ls stms
6ade8b0a
JW
269 in
270 (T.LABEL head
1144856b 271 :: T.JUMPIFN(trans_exp vars vartypes e, tail)
6ade8b0a
JW
272 :: strans
273 @ [T.JUMP head, T.LABEL tail]
274 @ remainder)
275 end
5c79bb68 276 | trans_stms vars vartypes ls (A.Effect(e)::stms) = (T.EFFECT (trans_exp vars vartypes e)) :: (trans_stms vars vartypes ls stms)
1144856b 277 | trans_stms vars vartypes (SOME(b,e)) (A.Break::stms) =
6ade8b0a 278 let
1144856b 279 val remainder = trans_stms vars vartypes (SOME(b,e)) stms
6ade8b0a
JW
280 in
281 ((T.JUMP e) :: remainder)
282 end
1144856b
JW
283 | trans_stms vars vartypes NONE (A.Break::_) = raise ErrorMsg.InternalError "Break from invalid location... should have been caught in typechecker"
284 | trans_stms vars vartypes (SOME(b,e)) (A.Continue::stms) =
6ade8b0a 285 let
1144856b 286 val remainder = trans_stms vars vartypes (SOME(b,e)) stms
6ade8b0a
JW
287 in
288 ((T.JUMP b) :: remainder)
289 end
1144856b
JW
290 | trans_stms vars vartypes NONE (A.Continue::_) = raise ErrorMsg.InternalError "Continue from invalid location... should have been caught in typechecker"
291 | trans_stms vars vartypes ls (A.Nop::stms) = trans_stms vars vartypes ls stms
292 | trans_stms vars vartypes ls (A.MarkedStm m :: stms) = trans_stms vars vartypes ls ((Mark.data m) :: stms)
293 | trans_stms vars vartypes _ nil = nil
12aa4087 294
1144856b
JW
295 fun trans_funcs ((id, A.Extern(_, _))::l) = trans_funcs l
296 | trans_funcs ((id, A.MarkedFunction a)::l) = trans_funcs ((id, Mark.data a)::l)
297 | trans_funcs ((id, A.Function(t, args, vars, body))::l) =
6ade8b0a 298 let
1144856b
JW
299 val allvars = foldr
300 (fn ((name, t),b) =>
141a7120 301 Symbol.bind b (name, Temp.new (Symbol.name(name))))
1144856b
JW
302 Symbol.empty
303 (args @ vars)
304 val vartypes = foldr (fn ((i, t), b) => Symbol.bind b (i, t)) Symbol.empty (args @ vars)
305 val b = trans_stms allvars vartypes NONE body
6ade8b0a
JW
306 val (argn,_) = ListPair.unzip args
307 val numberedargs = ListPair.zip (List.tabulate (length argn, fn x => x), argn)
308 val argmv = map
141a7120 309 (fn (n, argname) => T.MOVE(T.TEMP (Symbol.look' allvars argname), T.ARG (n)))
6ade8b0a
JW
310 numberedargs
311 in
312 (T.FUNCTION(id, argmv @ b)) :: (trans_funcs l)
313 end
314 | trans_funcs nil = nil
1144856b 315
6ade8b0a 316 in
1144856b 317 trans_funcs funclist
6ade8b0a 318 end
12aa4087 319end
This page took 0.056967 seconds and 4 git commands to generate.