+ offset_s' (eat shit) 0
+ end
+ | offset_s _ _ = raise ErrorMsg.InternalError "cannot find offset into non-typedef"
+
+ fun type_s id (Type.Typedef id') =
+ let
+ val td =
+ case Type.defdata (Symbol.look' defs id')
+ of Type.Struct d => d
+ | _ => raise ErrorMsg.InternalError "data didn't return struct"
+ fun type_s' ((id',t)::l) =
+ if (Symbol.compare (id, id') = EQUAL)
+ then t
+ else type_s' l
+ | type_s' nil = raise ErrorMsg.InternalError "struct member not found in type_s"
+ in
+ type_s' td
+ end
+ | type_s id _ = raise ErrorMsg.InternalError "cannot find internal type non-typedef"
+
+ fun deref (Type.Pointer i) = i
+ | deref (Type.Array i) = i
+ | deref _ = raise ErrorMsg.InternalError "cannot deref non-pointer"
+
+ fun trans_unop A.NEGATIVE = T.NEG
+ | trans_unop A.BITNOT = T.BITNOT
+ | trans_unop A.BANG = T.BANG
+ | trans_unop _ = raise ErrorMsg.InternalError "expected AST unop, got AST binop"
+
+ fun typeof' vartypes exp = TypeChecker.typeof (defs, funcs) vartypes NONE exp
+
+ fun trans_exp env vartypes (A.Var(id)) =
+ (* after type-checking, id must be declared; do not guard lookup *)
+ T.TEMP (Symbol.look' env id)
+ | trans_exp env vartypes (A.Cast (ty, e)) = trans_exp env vartypes e (* lurrr *)
+ | trans_exp env vartypes (A.ConstExp c) = T.CONST(c)
+ | trans_exp env vartypes (A.StringExp s) = T.STRING(Stringref.new s)
+ | trans_exp env vartypes (A.OpExp(oper, [e1, e2])) =
+ T.BINOP(trans_oper oper, trans_exp env vartypes e1, trans_exp env vartypes e2)
+ | trans_exp env vartypes (A.OpExp(oper, [e])) =
+ T.UNOP(trans_unop oper, trans_exp env vartypes e)
+ | trans_exp env vartypes (A.OpExp(oper, _)) =
+ raise ErrorMsg.InternalError "expected one or two operands, got it in the oven"
+ | trans_exp env vartypes (A.Marked(marked_exp)) =
+ trans_exp env vartypes (Mark.data marked_exp)
+ | trans_exp env vartypes (A.FuncCall(func, stms)) =
+ T.CALL(func,
+ List.map
+ (fn exp => (trans_exp env vartypes exp))
+ stms)
+ | trans_exp env vartypes (A.Member (exp, id)) =
+ let
+ val apk = T.BINOP (T.ADD, trans_exp env vartypes exp, T.CONST (Word32.fromInt (offset_s id (typeof' vartypes exp))))
+ val tipo = type_s id (typeof' vartypes exp)
+ in
+ if Type.issmall tipo
+ then T.MEMORY(apk)
+ else apk
+ end
+ | trans_exp env vartypes (A.DerefMember (exp, id)) =
+ trans_exp env vartypes (A.Member (A.Dereference (exp), id))
+ | trans_exp env vartypes (A.Dereference(exp)) =
+ if (Type.issmall (deref (typeof' vartypes exp)))
+ then T.MEMORY(trans_exp env vartypes exp)
+ else trans_exp env vartypes exp
+ | trans_exp env vartypes (A.ArrIndex(exp1, exp2)) =
+ let
+ val asubk = T.BINOP(T.ADD, trans_exp env vartypes exp1,
+ if sizeof (deref (typeof' vartypes exp1)) = 1
+ then trans_exp env vartypes exp2
+ else T.BINOP(T.MUL, trans_exp env vartypes exp2,
+ T.CONST(Word32.fromInt(sizeof (deref (typeof' vartypes exp1))))
+ )
+ )
+ val tipo = deref (typeof' vartypes exp1)
+ val d =
+ if not (Flag.isset Flags.safe)
+ then asubk
+ else T.COND (T.BINOP
+ (T.BE,
+ T.MEMORY (T.BINOP (
+ T.SUB,
+ trans_exp env vartypes exp1,
+ T.CONST 0w8)),
+ trans_exp env vartypes exp2),
+ T.NULLPTR,
+ asubk)
+ in
+ if Type.issmall tipo
+ then T.MEMORY(d)
+ else d
+ end
+ | trans_exp env vartypes (A.New(tipo)) =
+ let
+ val t1 = T.TEMP (Temp.new "result")
+ in
+ T.STMVAR (
+ [T.MOVE (t1, T.ALLOC (T.CONST (Word32.fromInt(sizeof tipo)))),
+ T.EFFECT (T.MEMORY (t1))],
+ t1)
+ end
+ | trans_exp env vartypes (A.NewArr(tipo, exp)) =
+ let
+ val size = if (sizeof tipo) = 1
+ then trans_exp env vartypes exp
+ else T.BINOP(T.MUL, trans_exp env vartypes exp, T.CONST(Word32.fromInt(sizeof tipo)))
+ val t1 = T.TEMP (Temp.new "allocated address")
+ val ts = T.TEMP (Temp.new "size")
+ in
+ if not (Flag.isset Flags.safe)
+ then T.STMVAR ([T.MOVE (t1, T.ALLOC size),
+ T.EFFECT (T.COND (T.BINOP (T.EQ, trans_exp env vartypes exp, T.CONST 0w0), T.CONST 0w0, T.MEMORY (t1)))],
+ t1)
+ else T.COND (T.BINOP(T.EQ, size, T.CONST 0w0),
+ T.NULLPTR,
+ T.STMVAR (
+ [T.MOVE(t1,
+ T.COND(
+ T.BINOP(T.LT, size, T.CONST 0w0),
+ T.NULLPTR,
+ T.ALLOC (T.BINOP (T.ADD, size, T.CONST 0w8)))
+ ),
+ T.MOVE(T.MEMORY (t1), trans_exp env vartypes exp)],
+ T.BINOP(T.ADD, t1, T.CONST 0w8)))
+ end
+ | trans_exp env vartypes (A.Null) = T.NULLPTR
+ | 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)
+
+ (* anything else should be impossible *)
+
+ (* trans_stms : Temp.temp Symbol.table -> (Label.label * Label.label) option -> A.stm list -> Tree.stm list
+ * translates a statement to the corresponding IR
+ * we pass around the environment and the current loop context, if any
+ * (usually called ls, which contains a continue label and a break label)
+ *)
+ 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)
+ | trans_stms vars vartypes ls (A.AsnOp(oop,e1,e2)::stms) =
+ let
+ val te1 = trans_exp vars vartypes e1
+ val te2 = trans_exp vars vartypes e2
+ val t1 = T.TEMP (Temp.new "memory deref cache")
+ in
+ case te1
+ 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)
+ | _ => T.MOVE(te1, T.BINOP(trans_oper oop, te1, te2)) :: (trans_stms vars vartypes ls stms)
+ end
+ | trans_stms vars vartypes ls (A.Return e::stms) =
+ let
+ val remainder = trans_stms vars vartypes ls stms
+ in
+ T.RETURN (trans_exp vars vartypes e)
+ :: remainder
+ end
+ | trans_stms vars vartypes ls (A.If(e, s, NONE)::stms) =
+ let
+ val l = Label.new ()
+ val strans = trans_stms vars vartypes ls s
+ val remainder = trans_stms vars vartypes ls stms
+ in
+ (T.JUMPIFN(trans_exp vars vartypes e, l)