//************************************************************** // // Code generator SKELETON // // Read the comments carefully. Make sure to // initialize the base class tags in // `CgenClassTable::CgenClassTable' // // Add the label for the dispatch tables to // `IntEntry::code_def' // `StringEntry::code_def' // `BoolConst::code_def' // // Add code to emit everyting else that is needed // in `CgenClassTable::code' // // // The files as provided will produce code to begin the code // segments, declare globals, and emit constants. You must // fill in the rest. // //************************************************************** #include "cgen.h" #include "cgen_gc.h" #include "cool-tree.h" #include #include #include #include #include #include extern void emit_string_constant(ostream &str, char *s); extern int cgen_debug; // // Three symbols from the semantic analyzer (semant.cc) are used. // If e : No_type, then no code is generated for e. // Special code is generated for new SELF_TYPE. // The name "self" also generates code different from other references. // ////////////////////////////////////////////////////////////////////// // // Symbols // // For convenience, a large number of symbols are predefined here. // These symbols include the primitive type and method names, as well // as fixed names used by the runtime system. // ////////////////////////////////////////////////////////////////////// Symbol arg, arg2, Bool, concat, cool_abort, copy, Int, in_int, in_string, IO, length, Main, main_meth, No_class, No_type, Object, out_int, out_string, prim_slot, self, SELF_TYPE, Str, str_field, substr, type_name, val; // // Initializing the predefined symbols. // static void initialize_constants(void) { arg = idtable.add_string("arg"); arg2 = idtable.add_string("arg2"); Bool = idtable.add_string("Bool"); concat = idtable.add_string("concat"); cool_abort = idtable.add_string("abort"); copy = idtable.add_string("copy"); Int = idtable.add_string("Int"); in_int = idtable.add_string("in_int"); in_string = idtable.add_string("in_string"); IO = idtable.add_string("IO"); length = idtable.add_string("length"); Main = idtable.add_string("Main"); main_meth = idtable.add_string("main"); // _no_class is a symbol that can't be the name of any // user-defined class. No_class = idtable.add_string("_no_class"); No_type = idtable.add_string("_no_type"); Object = idtable.add_string("Object"); out_int = idtable.add_string("out_int"); out_string = idtable.add_string("out_string"); prim_slot = idtable.add_string("_prim_slot"); self = idtable.add_string("self"); SELF_TYPE = idtable.add_string("SELF_TYPE"); Str = idtable.add_string("String"); str_field = idtable.add_string("_str_field"); substr = idtable.add_string("substr"); type_name = idtable.add_string("type_name"); val = idtable.add_string("_val"); } static char *gc_init_names[] = {"_NoGC_Init", "_GenGC_Init", "_ScnGC_Init"}; static char *gc_collect_names[] = {"_NoGC_Collect", "_GenGC_Collect", "_ScnGC_Collect"}; // BoolConst is a class that implements code generation for operations // on the two booleans, which are given global names here. BoolConst falsebool(FALSE); BoolConst truebool(TRUE); static int rel_stack_depth; static int class_tag_count; //********************************************************* // // Define method for code generation // // This is the method called by the compiler driver // `cgtest.cc'. cgen takes an `ostream' to which the assembly will be // emmitted, and it passes this and the class list of the // code generator tree to the constructor for `CgenClassTable'. // That constructor performs all of the work of the code // generator. // //********************************************************* void program_class::cgen(ostream &os) { // spim wants comments to start with '#' os << "# start of generated code\n"; initialize_constants(); CgenClassTable *codegen_classtable = new CgenClassTable(classes, os); os << "\n# end of generated code\n"; } ////////////////////////////////////////////////////////////////////////////// // // emit_* procedures // // emit_X writes code for operation "X" to the output stream. // There is an emit_X for each opcode X, as well as emit_ functions // for generating names according to the naming conventions (see emit.h) // and calls to support functions defined in the trap handler. // // Register names and addresses are passed as strings. See `emit.h' // for symbolic names you can use to refer to the strings. // ////////////////////////////////////////////////////////////////////////////// #pragma region StaticEmitProcedures static void emit_load(char *dest_reg, int offset, char *source_reg, ostream &s) { s << LW << dest_reg << " " << offset * WORD_SIZE << "(" << source_reg << ")" << endl; } static void emit_store(char *source_reg, int offset, char *dest_reg, ostream &s) { s << SW << source_reg << " " << offset * WORD_SIZE << "(" << dest_reg << ")" << endl; } static void emit_load_imm(char *dest_reg, int val, ostream &s) { s << LI << dest_reg << " " << val << endl; } static void emit_load_address(char *dest_reg, char *address, ostream &s) { s << LA << dest_reg << " " << address << endl; } static void emit_partial_load_address(char *dest_reg, ostream &s) { s << LA << dest_reg << " "; } static void emit_load_bool(char *dest, const BoolConst &b, ostream &s) { emit_partial_load_address(dest, s); b.code_ref(s); s << endl; } static void emit_load_string(char *dest, StringEntry *str, ostream &s) { emit_partial_load_address(dest, s); str->code_ref(s); s << endl; } static void emit_load_int(char *dest, IntEntry *i, ostream &s) { emit_partial_load_address(dest, s); i->code_ref(s); s << endl; } static void emit_move(char *dest_reg, char *source_reg, ostream &s) { s << MOVE << dest_reg << " " << source_reg << endl; } static void emit_neg(char *dest, char *src1, ostream &s) { s << NEG << dest << " " << src1 << endl; } static void emit_add(char *dest, char *src1, char *src2, ostream &s) { s << ADD << dest << " " << src1 << " " << src2 << endl; } static void emit_addu(char *dest, char *src1, char *src2, ostream &s) { s << ADDU << dest << " " << src1 << " " << src2 << endl; } static void emit_addiu(char *dest, char *src1, int imm, ostream &s) { s << ADDIU << dest << " " << src1 << " " << imm << endl; } static void emit_div(char *dest, char *src1, char *src2, ostream &s) { s << DIV << dest << " " << src1 << " " << src2 << endl; } static void emit_mul(char *dest, char *src1, char *src2, ostream &s) { s << MUL << dest << " " << src1 << " " << src2 << endl; } static void emit_sub(char *dest, char *src1, char *src2, ostream &s) { s << SUB << dest << " " << src1 << " " << src2 << endl; } static void emit_sll(char *dest, char *src1, int num, ostream &s) { s << SLL << dest << " " << src1 << " " << num << endl; } static void emit_jalr(char *dest, ostream &s) { s << JALR << "\t" << dest << endl; } static void emit_jal(char *address, ostream &s) { s << JAL << address << endl; } static void emit_return(ostream &s) { s << RET << endl; } static void emit_gc_assign(ostream &s) { s << JAL << "_GenGC_Assign" << endl; } static void emit_disptable_ref(Symbol sym, ostream &s) { s << sym << DISPTAB_SUFFIX; } static void emit_init_ref(Symbol sym, ostream &s) { s << sym << CLASSINIT_SUFFIX; } static void emit_label_ref(int l, ostream &s) { s << "label" << l; } static void emit_protobj_ref(Symbol sym, ostream &s) { s << sym << PROTOBJ_SUFFIX; } static void emit_method_ref(Symbol classname, Symbol methodname, ostream &s) { s << classname << METHOD_SEP << methodname; } static void emit_label_def(int l, ostream &s) { emit_label_ref(l, s); s << ":" << endl; } static void emit_beqz(char *source, int label, ostream &s) { s << BEQZ << source << " "; emit_label_ref(label, s); s << endl; } static void emit_beq(char *src1, char *src2, int label, ostream &s) { s << BEQ << src1 << " " << src2 << " "; emit_label_ref(label, s); s << endl; } static void emit_bne(char *src1, char *src2, int label, ostream &s) { s << BNE << src1 << " " << src2 << " "; emit_label_ref(label, s); s << endl; } static void emit_bleq(char *src1, char *src2, int label, ostream &s) { s << BLEQ << src1 << " " << src2 << " "; emit_label_ref(label, s); s << endl; } static void emit_blt(char *src1, char *src2, int label, ostream &s) { s << BLT << src1 << " " << src2 << " "; emit_label_ref(label, s); s << endl; } static void emit_blti(char *src1, int imm, int label, ostream &s) { s << BLT << src1 << " " << imm << " "; emit_label_ref(label, s); s << endl; } static void emit_bgti(char *src1, int imm, int label, ostream &s) { s << BGT << src1 << " " << imm << " "; emit_label_ref(label, s); s << endl; } static void emit_branch(int l, ostream &s) { s << BRANCH; emit_label_ref(l, s); s << endl; } // // Push a register on the stack. The stack grows towards smaller addresses. // static void emit_push(char *reg, ostream &str) { emit_store(reg, 0, SP, str); emit_addiu(SP, SP, -4, str); rel_stack_depth++; } static void emit_pop(ostream &str) { emit_addiu(SP, SP, 4, str); rel_stack_depth--; } static void emit_pop(size_t count, ostream &str) { emit_addiu(SP, SP, 4 * count, str); rel_stack_depth -= count; } // // Fetch the integer value in an Int object. // Emits code to fetch the integer value of the Integer object pointed // to by register source into the register dest // static void emit_fetch_int(char *dest, char *source, ostream &s) { emit_load(dest, DEFAULT_OBJFIELDS, source, s); } // // Emits code to store the integer value contained in register source // into the Integer object pointed to by dest. // static void emit_store_int(char *source, char *dest, ostream &s) { emit_store(source, DEFAULT_OBJFIELDS, dest, s); } // // Fetch the boolean value in an Bool object. // Emits code to fetch the boolean value of the Bool object pointed // to by register source into the register dest // static void emit_fetch_bool(char *dest, char *source, ostream &s) { emit_load(dest, DEFAULT_OBJFIELDS, source, s); } static void emit_test_collector(ostream &s) { emit_push(ACC, s); emit_move(ACC, SP, s); // stack end emit_move(A1, ZERO, s); // allocate nothing s << JAL << gc_collect_names[cgen_Memmgr] << endl; emit_addiu(SP, SP, 4, s); emit_load(ACC, 0, SP, s); } static void emit_gc_check(char *source, ostream &s) { if (source != (char *)A1) emit_move(A1, source, s); s << JAL << "_gc_check" << endl; } /* | ........ | |------------| | param 2 | |------------| | param 1 | |------------| | old $fp |<----------- $sp before entry |------------| | old $s0 | |------------| | ret addr |<----------- current $fp |------------| | local 1 |<----------- $sp at entry |------------| | local 2 | |------------| | ........ | Throughout the code generated for expressions, I used 4 registers: $a0, $s0, $a1, $t1. According to MIPS calling conventions, only $s0 needs to be saved. Thus the callee pushes and pops $fp,$s0,$ra when entering and leaving the context. By default, self object is passed to called in $a0, so move it to $s0 */ static void emit_procedure_header(ostream &s) { /* addiu $sp $sp -12 sw $fp 12($sp) sw $s0 8($sp) sw $ra 4($sp) addiu $fp $sp 4 move $s0 $a0 */ emit_addiu(SP, SP, -12, s); emit_store(FP, 3, SP, s); emit_store(SELF, 2, SP, s); emit_store(RA, 1, SP, s); emit_addiu(FP, SP, 4, s); emit_move(SELF, ACC, s); rel_stack_depth = 0; } static void emit_procedure_footer(int nparams, ostream &s) { /* lw $fp 12($sp) lw $s0 8($sp) lw $ra 4($sp) addiu $sp $sp (12 + 4 * nparams) jr $ra */ emit_load(FP, 3, SP, s); emit_load(SELF, 2, SP, s); emit_load(RA, 1, SP, s); emit_addiu(SP, SP, 4 * (3 + nparams), s); emit_return(s); } #pragma endregion /////////////////////////////////////////////////////////////////////////////// // // coding strings, ints, and booleans // // Cool has three kinds of constants: strings, ints, and booleans. // This section defines code generation for each type. // // All string constants are listed in the global "stringtable" and have // type StringEntry. StringEntry methods are defined both for String // constant definitions and references. // // All integer constants are listed in the global "inttable" and have // type IntEntry. IntEntry methods are defined for Int // constant definitions and references. // // Since there are only two Bool values, there is no need for a table. // The two booleans are represented by instances of the class BoolConst, // which defines the definition and reference methods for Bools. // /////////////////////////////////////////////////////////////////////////////// #pragma region ConstantCoding // // Strings // void StringEntry::code_ref(ostream &s) { s << STRCONST_PREFIX << index; } // // Emit code for a constant String. // You should fill in the code naming the dispatch table. // void StringEntry::code_def(ostream &s, int stringclasstag) { IntEntryP lensym = inttable.add_int(len); // Add -1 eye catcher s << WORD << "-1" << endl; code_ref(s); s << LABEL // label << WORD << stringclasstag << endl // tag << WORD << (DEFAULT_OBJFIELDS + STRING_SLOTS + (len + 4) / 4) << endl // size << WORD << STRINGNAME << DISPTAB_SUFFIX << endl; // dispatch ptr s << WORD; lensym->code_ref(s); s << endl; // string length emit_string_constant(s, str); // ascii string s << ALIGN; // align to word } // // StrTable::code_string // Generate a string object definition for every string constant in the // stringtable. // void StrTable::code_string_table(ostream &s, int stringclasstag) { for (List *l = tbl; l; l = l->tl()) l->hd()->code_def(s, stringclasstag); } // // Ints // void IntEntry::code_ref(ostream &s) { s << INTCONST_PREFIX << index; } // // Emit code for a constant Integer. // You should fill in the code naming the dispatch table. // void IntEntry::code_def(ostream &s, int intclasstag) { // Add -1 eye catcher s << WORD << "-1" << endl; code_ref(s); s << LABEL // label << WORD << intclasstag << endl // class tag << WORD << (DEFAULT_OBJFIELDS + INT_SLOTS) << endl; // object size s << WORD << INTNAME << DISPTAB_SUFFIX << endl; // dispatch ptr s << WORD << str << endl; // integer value } // // IntTable::code_string_table // Generate an Int object definition for every Int constant in the // inttable. // void IntTable::code_string_table(ostream &s, int intclasstag) { for (List *l = tbl; l; l = l->tl()) l->hd()->code_def(s, intclasstag); } // // Bools // BoolConst::BoolConst(int i) : val(i) { assert(i == 0 || i == 1); } void BoolConst::code_ref(ostream &s) const { s << BOOLCONST_PREFIX << val; } // // Emit code for a constant Bool. // You should fill in the code naming the dispatch table. // void BoolConst::code_def(ostream &s, int boolclasstag) { // Add -1 eye catcher s << WORD << "-1" << endl; code_ref(s); s << LABEL // label << WORD << boolclasstag << endl // class tag << WORD << (DEFAULT_OBJFIELDS + BOOL_SLOTS) << endl; // object size s << WORD << BOOLNAME << DISPTAB_SUFFIX << endl; // dispatch ptr s << WORD << val << endl; // value (0 or 1) } #pragma endregion ////////////////////////////////////////////////////////////////////////////// // // CgenClassTable methods // ////////////////////////////////////////////////////////////////////////////// //*************************************************** // // Emit code to start the .data segment and to // declare the global names. // //*************************************************** void CgenClassTable::code_global_data() { Symbol main = idtable.lookup_string(MAINNAME); Symbol string = idtable.lookup_string(STRINGNAME); Symbol integer = idtable.lookup_string(INTNAME); Symbol boolc = idtable.lookup_string(BOOLNAME); str << "\t.data\n" << ALIGN; // // The following global names must be defined first. // str << GLOBAL << CLASSNAMETAB << endl; str << GLOBAL; emit_protobj_ref(main, str); str << endl; str << GLOBAL; emit_protobj_ref(integer, str); str << endl; str << GLOBAL; emit_protobj_ref(string, str); str << endl; str << GLOBAL; falsebool.code_ref(str); str << endl; str << GLOBAL; truebool.code_ref(str); str << endl; str << GLOBAL << INTTAG << endl; str << GLOBAL << BOOLTAG << endl; str << GLOBAL << STRINGTAG << endl; // // We also need to know the tag of the Int, String, and Bool classes // during code generation. // str << INTTAG << LABEL << WORD << intclasstag << endl; str << BOOLTAG << LABEL << WORD << boolclasstag << endl; str << STRINGTAG << LABEL << WORD << stringclasstag << endl; } //*************************************************** // // Emit code to start the .text segment and to // declare the global names. // //*************************************************** void CgenClassTable::code_global_text() { str << GLOBAL << HEAP_START << endl << HEAP_START << LABEL << WORD << 0 << endl << "\t.text" << endl << GLOBAL; emit_init_ref(idtable.add_string("Main"), str); str << endl << GLOBAL; emit_init_ref(idtable.add_string("Int"), str); str << endl << GLOBAL; emit_init_ref(idtable.add_string("String"), str); str << endl << GLOBAL; emit_init_ref(idtable.add_string("Bool"), str); str << endl << GLOBAL; emit_method_ref(idtable.add_string("Main"), idtable.add_string("main"), str); str << endl; } void CgenClassTable::code_bools(int boolclasstag) { falsebool.code_def(str, boolclasstag); truebool.code_def(str, boolclasstag); } void CgenClassTable::code_select_gc() { // // Generate GC choice constants (pointers to GC functions) // str << GLOBAL << "_MemMgr_INITIALIZER" << endl; str << "_MemMgr_INITIALIZER:" << endl; str << WORD << gc_init_names[cgen_Memmgr] << endl; str << GLOBAL << "_MemMgr_COLLECTOR" << endl; str << "_MemMgr_COLLECTOR:" << endl; str << WORD << gc_collect_names[cgen_Memmgr] << endl; str << GLOBAL << "_MemMgr_TEST" << endl; str << "_MemMgr_TEST:" << endl; str << WORD << (cgen_Memmgr_Test == GC_TEST) << endl; } //******************************************************** // // Emit code to reserve space for and initialize all of // the constants. Class names should have been added to // the string table (in the supplied code, is is done // during the construction of the inheritance graph), and // code for emitting string constants as a side effect adds // the string's length to the integer table. The constants // are emmitted by running through the stringtable and inttable // and producing code for each entry. // //******************************************************** void CgenClassTable::code_constants() { // // Add constants that are required by the code generator. // stringtable.add_string(""); inttable.add_string("0"); stringtable.code_string_table(str, stringclasstag); inttable.code_string_table(str, intclasstag); code_bools(boolclasstag); } void CgenClassTable::code_class_nameTable() { str << CLASSNAMETAB << LABEL; for (auto node : nodes) { auto name_entry = stringtable.lookup_string(node->name->get_string()); str << WORD; name_entry->code_ref(str); str << "\n"; } } void CgenClassTable::code_dispatchTable() { for (auto node : nodes) { str << node->name << DISPTAB_SUFFIX << LABEL; for (auto method_record : *node->get_methods()) { auto class_node = method_record.first; auto method = method_record.second; str << WORD << class_node->name << "." << method->name << "\n"; } } } void CgenClassTable::code_prototypeObject() { this->_int_default = inttable.lookup_string("0"); this->_str_default = stringtable.lookup_string(""); this->_bool_default = &falsebool; for (auto node : nodes) { str << WORD << "-1\n"; // GC tag str << node->name << PROTOBJ_SUFFIX << LABEL; // proto obj label str << WORD << node->get_class_tag() << endl; // class tag str << WORD << node->get_object_size() << endl; // object size str << WORD << node->get_name() << DISPTAB_SUFFIX << endl; // dispatch ptr for (auto attr_pair : *node->get_attributes()) { if (attr_pair.second->type_decl == Int) { str << WORD; _int_default->code_ref(str); str << endl; } else if (attr_pair.second->type_decl == Bool) { str << WORD; _bool_default->code_ref(str); str << endl; } else if (attr_pair.second->type_decl == Str) { str << WORD; _str_default->code_ref(str); str << endl; } else { // for other types(including _prim_slot type), set to void(null pointer) str << WORD; str << 0; str << endl; } } } } void CgenClassTable::code_objectTab() { str << CLASSOBJTAB << LABEL; for (auto node : nodes) { str << WORD << node->get_name() << PROTOBJ_SUFFIX << endl; str << WORD << node->get_name() << CLASSINIT_SUFFIX << endl; } } void CgenClassTable::gen_init_code() { for (auto node : nodes) { this->cur_class = node; str << node->get_name() << CLASSINIT_SUFFIX << LABEL; emit_procedure_header(str); if (node->get_parentnd() && node->get_parentnd()->name != No_class) { str << JAL << node->parent->get_string() << CLASSINIT_SUFFIX << endl; } auto attrs = node->get_attributes(); // attributes are available when initializing loctab.enterscope(); for (auto i = 0U; i < attrs->size(); ++i) { auto attr_pair = (*attrs)[i]; loctab.add(LocationTableItem(attr_pair.second->name, Attribute, i + DEFAULT_OBJFIELDS)); } for (auto i = 0U; i < attrs->size(); ++i) { auto attr_pair = (*attrs)[i]; if (attr_pair.first->name != node->name) continue; // base class initializer will handle inherited attributes // here we only deal with our new attributes if (is_no_expr(attr_pair.second->init)) continue; // we can safely skip for those attributes without initialization expr // because the default values are set in the prototype object, when // the object is created by Object.copy(), they will be set to correct // default values this->expr_type_decl = attr_pair.second->type_decl; attr_pair.second->init->code(str, this); emit_store(ACC, i + DEFAULT_OBJFIELDS, SELF, str); } loctab.exitscope(); emit_move(ACC, SELF, str); // remember to place the initialized object back to $a0, other code rely on // this behavior emit_procedure_footer(0, str); } } void CgenClassTable::gen_method_code() { for (auto node : nodes) { if (node->basic()) continue; this->cur_class = node; for (auto method_pair : *node->get_methods()) { if (method_pair.first->name != node->name) continue; // skip inherited methods auto method = method_pair.second; auto attrs = node->get_attributes(); // add attributes and formals to location table loctab.enterscope(); // add attributes for (auto i = 0U; i < attrs->size(); ++i) { auto attr_pair = (*attrs)[i]; loctab.add(LocationTableItem(attr_pair.second->name, Attribute, i + DEFAULT_OBJFIELDS)); } // add formals for (auto i = method->formals->first(); method->formals->more(i); i = method->formals->next(i)) { auto formal = static_cast(method->formals->nth(i)); loctab.add(LocationTableItem(formal->name, Stack, method->formals->len() - i + 3 - 1)); // &formal[i] = (4 * i + 12)($fp) } str << node->name << "." << method->name << LABEL; emit_procedure_header(str); method->expr->code(str, this); emit_procedure_footer(method->formals->len(), str); loctab.exitscope(); } } } CgenClassTable::CgenClassTable(Classes classes, ostream &s) : str(s) { enterscope(); if (cgen_debug) cout << "Building CgenClassTable" << endl; install_basic_classes(); install_classes(classes); build_inheritance_tree(); if (cgen_debug) dump_inheritance_tree(); root()->traverse_allocate_tag(); std::sort(nodes.begin(), nodes.end(), [](CgenNode *a, CgenNode *b) { return a->get_class_tag() < b->get_class_tag(); }); if (cgen_debug) { std::cerr << "Dump class tags:\n"; for (auto node : nodes) { std::cerr << node->name << ": " << node->get_class_tag() << "," << node->get_children_tag() << "\n"; } } // sort the vector is in tag order to generate correct class_objTab root()->traverse_generate_object(); // nodes[0] is the Object class stringclasstag = get_node(Str)->get_class_tag(); intclasstag = get_node(Int)->get_class_tag(); boolclasstag = get_node(Bool)->get_class_tag(); code(); exitscope(); } void CgenClassTable::install_basic_classes() { // The tree package uses these globals to annotate the classes built below. // curr_lineno = 0; Symbol filename = stringtable.add_string(""); // // A few special class names are installed in the lookup table but not // the class list. Thus, these classes exist, but are not part of the // inheritance hierarchy. // No_class serves as the parent of Object and the other special classes. // SELF_TYPE is the self class; it cannot be redefined or inherited. // prim_slot is a class known to the code generator. // it serves as the value type of Int, Boolean, String // addid(No_class, new CgenNode(class_(No_class, No_class, nil_Features(), filename), Trivial)); addid(SELF_TYPE, new CgenNode(class_(SELF_TYPE, No_class, nil_Features(), filename), Trivial)); addid(prim_slot, new CgenNode(class_(prim_slot, No_class, nil_Features(), filename), Trivial)); // // The Object class has no parent class. Its methods are // cool_abort() : Object aborts the program // type_name() : Str returns a string representation of class // name copy() : SELF_TYPE returns a copy of the object // // There is no need for method bodies in the basic classes---these // are already built in to the runtime system. // install_class(new CgenNode( class_( Object, No_class, append_Features( append_Features(single_Features(method(cool_abort, nil_Formals(), Object, no_expr())), single_Features(method(type_name, nil_Formals(), Str, no_expr()))), single_Features( method(copy, nil_Formals(), SELF_TYPE, no_expr()))), filename), Basic)); // // The IO class inherits from Object. Its methods are // out_string(Str) : SELF_TYPE writes a string to the output // out_int(Int) : SELF_TYPE " an int " " " // in_string() : Str reads a string from the input // in_int() : Int " an int " " " // install_class(new CgenNode( class_( IO, Object, append_Features( append_Features( append_Features( single_Features(method(out_string, single_Formals(formal(arg, Str)), SELF_TYPE, no_expr())), single_Features(method(out_int, single_Formals(formal(arg, Int)), SELF_TYPE, no_expr()))), single_Features( method(in_string, nil_Formals(), Str, no_expr()))), single_Features(method(in_int, nil_Formals(), Int, no_expr()))), filename), Basic)); // // The Int class has no methods and only a single attribute, the // "val" for the integer. // install_class(new CgenNode( class_(Int, Object, single_Features(attr(val, prim_slot, no_expr())), filename), Basic)); // // Bool also has only the "val" slot. // install_class(new CgenNode( class_(Bool, Object, single_Features(attr(val, prim_slot, no_expr())), filename), Basic)); // // The class Str has a number of slots and operations: // val ??? // str_field the string itself // length() : Int length of the string // concat(arg: Str) : Str string concatenation // substr(arg: Int, arg2: Int): Str substring // install_class(new CgenNode( class_(Str, Object, append_Features( append_Features( append_Features( append_Features( single_Features(attr(val, Int, no_expr())), single_Features( attr(str_field, prim_slot, no_expr()))), single_Features( method(length, nil_Formals(), Int, no_expr()))), single_Features(method(concat, single_Formals(formal(arg, Str)), Str, no_expr()))), single_Features( method(substr, append_Formals(single_Formals(formal(arg, Int)), single_Formals(formal(arg2, Int))), Str, no_expr()))), filename), Basic)); } // CgenClassTable::install_class // CgenClassTable::install_classes // // install_classes enters a list of classes in the symbol table. // void CgenClassTable::install_class(CgenNodeP nd) { Symbol name = nd->get_name(); if (probe(name)) { return; } // The class name is legal, so add it to the list of classes // and the symbol table. nodes.push_back(nd); addid(name, nd); } void CgenClassTable::install_classes(Classes cs) { for (int i = cs->first(); cs->more(i); i = cs->next(i)) install_class(new CgenNode(cs->nth(i), NotBasic)); } // // CgenClassTable::build_inheritance_tree // void CgenClassTable::build_inheritance_tree() { for (auto node : nodes) set_relations(node); } // // CgenClassTable::set_relations // // Takes a CgenNode and locates its, and its parent's, inheritance nodes // via the class table. Parent and child pointers are added as appropriate. // void CgenClassTable::set_relations(CgenNodeP nd) { CgenNode *parent_node = probe(nd->get_parent()); nd->set_parentnd(parent_node); parent_node->add_child(nd); } void CgenClassTable::dump_inheritance_tree() { CgenNode *object_node = nullptr; for (auto cur_node : nodes) { if (cur_node->name == Object) { object_node = cur_node; break; } } object_node->traverse_dump(0); } CgenNode *CgenClassTable::get_node(Symbol class_name) { for (auto node : nodes) { if (node->name == class_name) { return node; } } if (cgen_debug) std::cerr << "get_node " << class_name << " not found\n"; assert(0); return nullptr; } int CgenClassTable::get_method_index(Symbol class_name, Symbol method_name) { auto class_node = get_node(class_name); auto methods = class_node->get_methods(); for (size_t i = 0; i < methods->size(); ++i) { auto method = (*methods)[i]; if (method.second->name == method_name) { return i; } } assert(0); return -1; } void CgenClassTable::code() { if (cgen_debug) cout << "coding global data" << endl; code_global_data(); if (cgen_debug) cout << "choosing gc" << endl; code_select_gc(); if (cgen_debug) cout << "coding constants" << endl; code_constants(); if (cgen_debug) cout << "coding class_nameTab" << endl; code_class_nameTable(); if (cgen_debug) cout << "coding object table" << endl; code_objectTab(); if (cgen_debug) cout << "coding dispatch tables" << endl; code_dispatchTable(); if (cgen_debug) cout << "coding prototype objects" << endl; code_prototypeObject(); if (cgen_debug) cout << "coding global text" << endl; code_global_text(); #if 0 // test my symtab impl for (auto node : nodes) { auto attrs = *node->get_attributes(); auto methods = *node->get_methods(); std::cerr << node->name << std::endl; loctab.enterscope(); for (size_t i = 0; i < attrs.size(); ++ i) { auto attr = attrs[i]; loctab.add(LocationTableItem(attr->name, Attribute, i)); } loctab.enterscope(); for (size_t i = 0; i < methods.size(); ++ i) { auto method = methods[i]; loctab.add(LocationTableItem(method.second->name, Attribute, i)); } loctab.enterscope(); for (size_t i = 0; i < attrs.size(); ++ i) { auto attr = attrs[i]; loctab.add(LocationTableItem(attr->name, Attribute, i + 10000)); } // loctab.dump(); for (size_t i = 0; i < attrs.size(); ++ i) { auto attr = attrs[i]; assert(loctab.lookup(attr->name)); assert(loctab.lookup(attr->name)->offset == i + 10000); } loctab.exitscope(); for (size_t i = 0; i < attrs.size(); ++ i) { auto attr = attrs[i]; assert(loctab.lookup(attr->name) && loctab.lookup(attr->name)->offset == i); } loctab.exitscope(); for (size_t i = 0; i < attrs.size(); ++ i) { auto attr = attrs[i]; assert(loctab.lookup(attr->name) && loctab.lookup(attr->name)->offset == i); } loctab.exitscope(); for (size_t i = 0; i < attrs.size(); ++ i) { auto attr = attrs[i]; assert(loctab.lookup(attr->name) == nullptr); } } #endif if (cgen_debug) cout << "generating object initializers" << endl; gen_init_code(); if (cgen_debug) cout << "generating class methods" << endl; gen_method_code(); } /////////////////////////////////////////////////////////////////////// // // CgenNode methods // /////////////////////////////////////////////////////////////////////// #pragma region CgenNode CgenNode::CgenNode(Class_ nd, Basicness bstatus) : class__class((const class__class &)*nd), parentnd(NULL), basic_status(bstatus) { if (!(bstatus == Trivial)) stringtable.add_string( name->get_string()); // Add class name to string table } void CgenNode::add_child(CgenNodeP n) { children.push_back(n); } void CgenNode::set_parentnd(CgenNodeP p) { assert(parentnd == NULL); assert(p != NULL); parentnd = p; } void CgenNode::traverse_dump(int pad) { for (int i = 0; i < pad; ++i) std::cerr << " "; std::cerr << this->name << ":" << this->_class_tag << "\n"; for (auto child : children) { child->traverse_dump(pad + 2); } } void CgenNode::traverse_generate_object() { int parent_method_end = 0; if (parentnd) { // Inherit attrs & methods auto parent_attrs = parentnd->get_attributes(); for (auto attr : *parent_attrs) { this->attributes.push_back(attr); } auto parent_methods = parentnd->get_methods(); for (auto method : *parent_methods) { this->methods.push_back(method); } parent_method_end = this->methods.size(); } for (auto feature_i = features->first(); features->more(feature_i); feature_i = features->next(feature_i)) { auto feature = features->nth(feature_i); if (typeid(*feature) == typeid(attr_class)) { this->attributes.push_back( std::make_pair(static_cast(this), static_cast(feature))); // inherited attrs cannot be redefined, so simply add to list } else { auto method = static_cast(feature); auto overridden_flag = false; for (auto i = 0; i < parent_method_end; ++i) { if (this->methods[i].second->name == method->name) { this->methods[i] = std::make_pair(static_cast(this), method); // overridden method with the same name overridden_flag = true; break; } } if (!overridden_flag) { this->methods.push_back( std::make_pair(static_cast(this), method)); } } } if (cgen_debug) { std::cerr << "Object info -- " << this->name << "\n"; std::cerr << "Attributes:\n"; for (auto attr : attributes) { std::cerr << " " << attr.first->name << "." << attr.second->name << ":" << attr.second->type_decl << "\n"; } std::cerr << "Methods:\n"; for (auto method : methods) { std::cerr << " " << method.first->name << "." << method.second->name << ":" << method.second->return_type << "\n"; } std::cerr << "\n"; } for (auto child : children) { child->traverse_generate_object(); } } void CgenNode::traverse_allocate_tag() { this->_class_tag = class_tag_count++; for (auto child : children) { child->traverse_allocate_tag(); } this->_children_tag_range = class_tag_count - 1; } #pragma endregion //****************************************************************** // // Fill in the following methods to produce code for the // appropriate expression. You may add or remove parameters // as you wish, but if you do, remember to change the parameters // of the declarations in `cool-tree.h' Sample code for // constant integers, strings, and booleans are provided. // //***************************************************************** #pragma region ExpressionCoding /* Assignment actually does little. First evaluate its rhs. Then look up the lhs identifier's location and simply store into the location. */ void assign_class::code(ostream &s, CgenClassTable *classtab) { this->expr->code(s, classtab); auto loc = classtab->loctab.lookup(this->name); if (loc->location == Stack) { emit_store(ACC, loc->offset, FP, s); } else { emit_store(ACC, loc->offset, SELF, s); } } /* static dispatch is a little bit simpler than normal dispatch Intuitively, first evaluate all the parameter expression and push stack. Note that, by design, the caller doesn't clear up the params, the callee do the clear up on return. Then evaluate the expr before `.`, which serves as the self object when invoking the method. Thus it resides in $a0. Before the flow goes to the method, check whether the object is void. This is mentioned near the end of section 13 in the manual. If void, set $t1 and $a0 and call _dispatch_abort. Finally, invoke the method by looking up its address from the dispatch table and jalr. */ void static_dispatch_class::code(ostream &s, CgenClassTable *classtab) { int nparams = 0; for (auto actual_i = this->actual->first(); this->actual->more(actual_i); actual_i = this->actual->next(actual_i)) { auto actual_expr = this->actual->nth(actual_i); actual_expr->code(s, classtab); emit_push(ACC, s); // push param to stack ++ nparams; } this->expr->code(s, classtab); auto label_dispatch = classtab->alloc_label_index(); // use bne to save a label, because we'll never come back if abort emit_bne(ACC, ZERO, label_dispatch, s); // Prints the line number, from $t1, and filename, from $a0, at which the // dispatch occurred, and aborts. emit_partial_load_address(ACC, s); stringtable.lookup_string(classtab->cur_class->get_filename()->get_string()) ->code_ref(s); s << endl; emit_load_imm(T1, this->line_number, s); emit_jal("_dispatch_abort", s); // ready to call the method emit_label_def(label_dispatch, s); // load dispatch table emit_partial_load_address(T1, s); emit_disptable_ref(this->type_name, s); s << endl; // load method address emit_load(T1, classtab->get_method_index(this->type_name, this->name), T1, s); // call the method whose address is in $t1, with self object in $a0 emit_jalr(T1, s); rel_stack_depth -= nparams; } /* Normal dispatch is only different from static dispatch in deciding the dispatch table. Normal dispatch extract the dispatch table from the object's dispTab feild(offset 8) instead of querying method address at compile time. */ void dispatch_class::code(ostream &s, CgenClassTable *classtab) { int nparams = 0; for (auto actual_i = this->actual->first(); this->actual->more(actual_i); actual_i = this->actual->next(actual_i)) { auto actual_expr = this->actual->nth(actual_i); actual_expr->code(s, classtab); emit_push(ACC, s); // push param to stack ++ nparams; } this->expr->code(s, classtab); auto label_dispatch = classtab->alloc_label_index(); // use bne to save a label, because we'll never come back if abort emit_bne(ACC, ZERO, label_dispatch, s); // Prints the line number, from $t1, and filename, from $a0, at which the // dispatch occurred, and aborts. emit_partial_load_address(ACC, s); stringtable.lookup_string(classtab->cur_class->get_filename()->get_string()) ->code_ref(s); s << endl; emit_load_imm(T1, this->line_number, s); emit_jal("_dispatch_abort", s); // ready to call the method emit_label_def(label_dispatch, s); // load dispatch table emit_load(T1, DISPTABLE_OFFSET, ACC, s); // load method address int method_index = -1; if (this->expr->type == SELF_TYPE) { method_index = classtab->get_method_index(classtab->cur_class->name, this->name); // if the expr is SELF_TYPE, look up the method from current classs } else { method_index = classtab->get_method_index(this->expr->type, this->name); } emit_load(T1, method_index, T1, s); // call the method whose address is in $t1, with self object in $a0 emit_jalr(T1, s); rel_stack_depth -= nparams; } /* There's nothing special for if-then-else. Write at your convenience. Note that value of the predicate is a Bool object, not a boolean, so, dont forget to extract its value from the object */ void cond_class::code(ostream &s, CgenClassTable *classtab) { this->pred->code(s, classtab); emit_fetch_bool(ACC, ACC, s); // fetch the boolean value into $a0 auto label_false = classtab->alloc_label_index(); auto label_exit = classtab->alloc_label_index(); emit_beqz(ACC, label_false, s); // $a0==0, pred is false, goto else this->then_exp->code(s, classtab); // pred is true, eval then branch emit_branch(label_exit, s); // $a0 <- then, and we goto exit emit_label_def(label_false, s); // the label is preserved in advance so that we can define it here safely this->else_exp->code(s, classtab); // $a0 <- else emit_label_def(label_exit, s); } /* The code for loop is also straightforward. The only thing special is that, loop always evaluate to void, so remember to set $a0<-0 */ void loop_class::code(ostream &s, CgenClassTable *classtab) { auto label_predicate = classtab->alloc_label_index(); emit_label_def(label_predicate, s); // predefine a label and our loop could restart and check predicate from here this->pred->code(s, classtab); // check predicate, which sets $a0<-Bool object emit_fetch_bool(ACC, ACC, s); // extrace 0 or 1 from Bool object in $a0 auto label_exit = classtab->alloc_label_index(); emit_beqz(ACC, label_exit, s); // if predicate is false, goto exit this->body->code(s, classtab); // if predicate is true, move on with our loop emit_branch(label_predicate, s); // anyways, go back and check predicate emit_label_def(label_exit, s); emit_load_imm(ACC, 0, s); // whatever the case, loop expr evaluates to void! } /* I think type case is the most difficult part in this PA. It selects the closest ancestor of the expr's type, thus requiring hierarchy infomation available at runtime. Again, through reverse engineering (^_^) the reference compiler, I managed to find out a relatively simple way to embed hierarchy into the program. We may use the class tag to do this. In advance, allocate the class tags in pre-order traversal of the inheritance tree, and record for each node when all its children is allocated. In this way, every node has a range of tags covering itself and its children. When generating `case`, start from the leaves, because we need to match the closest ancestor. If the tag is in some range, then we can say it matches the branch. Besides the hierarchy problem, there are two runtime error here: a case statement has no match -> `_case_abort`; a case on a void object -> `_case_abort2`. Remember to set these two guys. */ void typcase_class::code(ostream &s, CgenClassTable *classtab) { this->expr->code(s, classtab); auto label_case = classtab->alloc_label_index(); // use bne to save a label, because we'll never come back if abort emit_bne(ACC, ZERO, label_case, s); // Prints the line number, from $t1, and filename, from $a0, at which the // type case occurred, and aborts. emit_load_imm(T1, this->line_number, s); emit_partial_load_address(ACC, s); stringtable.lookup_string(classtab->cur_class->get_filename()->get_string()) ->code_ref(s); s << endl; emit_jal("_case_abort2", s); // start type case here emit_label_def(label_case, s); // load class tag, if no error, object ref is in $a0 emit_load(T1, TAG_OFFSET, ACC, s); // generate a map to simplify branch search std::map sym_branch; for (auto branch_i = this->cases->first(); this->cases->more(branch_i); branch_i = this->cases->next(branch_i)) { auto branch = static_cast(this->cases->nth(branch_i)); sym_branch[branch->type_decl] = branch; } auto label_exit = classtab->alloc_label_index(); // generate the branches in reverse pre-order for (auto node_ritr = classtab->nodes.rbegin(); node_ritr != classtab->nodes.rend(); ++node_ritr) { auto node = *node_ritr; auto branch_itr = sym_branch.find(node->name); if (branch_itr == sym_branch.end()) continue; auto branch = branch_itr->second; auto label_branch = classtab->alloc_label_index(); // if expr's tag is not in the branch's children range, test next branch emit_blti(T1, node->get_class_tag(), label_branch, s); emit_bgti(T1, node->get_children_tag(), label_branch, s); // though maybe quite trivial(just bind another name), still push to stack // because we dont know whether $a0 is going to be overwritten emit_push(ACC, s); // allocate a new location classtab->loctab.enterscope(); classtab->loctab.add( LocationTableItem(branch->name, Stack, -rel_stack_depth)); // if expr's tag is in range, evaluate this branch branch->expr->code(s, classtab); classtab->loctab.exitscope(); emit_pop(s); // balance stack // already matched, the matching process ends here and go to exit emit_branch(label_exit, s); // the label for the next branch emit_label_def(label_branch, s); } // no match, the procedure's is in $a0, which remains unmodified if no branch // is taken, thus unnecessary to set it emit_jal("_case_abort", s); emit_label_def(label_exit, s); } /* For block expression, generate code expression by expression, nothing else */ void block_class::code(ostream &s, CgenClassTable *classtab) { for (auto expr_i = this->body->first(); this->body->more(expr_i); expr_i = this->body->next(expr_i)) { auto expr = this->body->nth(expr_i); expr->code(s, classtab); } } void let_class::code(ostream &s, CgenClassTable *classtab) { classtab->expr_type_decl = this->type_decl; this->init->code(s, classtab); emit_push(ZERO, s); // make space for let's new object emit_store(ACC, -rel_stack_depth, FP, s); // set initial value to the new ident classtab->loctab.enterscope(); classtab->loctab.add( LocationTableItem(this->identifier, Stack, -rel_stack_depth)); this->body->code(s, classtab); classtab->loctab.exitscope(); emit_pop(s); // balacnce stack // the value of let is body's value, so leave $a0 unmodified } /* Operations for Int objects is the most simple one, let's start here In previous stages, we have make sure that both ends are Int type. Thus, some hard-coded stuff is acceptable. First, we evaluate the left part and the result, the address of the Int object, is in $a0. In the very beginning, I think it is a good idea to keep it simple, so I'd prefer not to allocate temporary space on stack ahead. The solution here is to push $a0 to stack. Then evaluate the right part. At this time, we have addr(e1) on stack top and addr(e2) in $a0. According to imagination (>_<), the right thing to do is to extract the value attributes of the two Int objects (at offset 12), add them up, create a new Int object and set its value attribute to the result. Finally store the address of the new Int in $a0 as the return value. To actually perform these operations, assuming that we are not going to use any registers other than $a0 and $t0, we need to write some MIPS assembly. */ void plus_class::code(ostream &s, CgenClassTable *classtab) { this->e1->code(s, classtab); emit_fetch_int(ACC, ACC, s); // load value of e1 to a0 emit_push(ACC, s); // push the 32bit int value instead of object ref this->e2->code(s, classtab); emit_jal("Object.copy", s); // copy e2 as the new Int object emit_push(ACC, s); // save new object's addr, will need it later emit_fetch_int(ACC, ACC, s); // load value of e2 to a0 emit_load(T1, 2, SP, s); // load value of e1 to t1, remind we have pushed again, so -8($sp) is val(e1) emit_add(T1, T1, ACC, s); // $t1 <- val(e1) + val(e2) emit_load(ACC, 1, SP, s); // load new object addr emit_store_int(T1, ACC, s); // store result(now in $t1) to the object emit_pop(2, s); // maintain stack balance } /* Substraction is quite the same as addition, the only thing to note is to get the substraction order right. e1-e2 != e2-e1, but e1+e2 == e2+e1 */ void sub_class::code(ostream &s, CgenClassTable *classtab) { this->e1->code(s, classtab); emit_fetch_int(ACC, ACC, s); emit_push(ACC, s); this->e2->code(s, classtab); emit_jal("Object.copy", s); emit_push(ACC, s); emit_fetch_int(ACC, ACC, s); // $a0 <- val(e2) emit_load(T1, 2, SP, s); // $t1 <- val(e1) emit_sub(T1, T1, ACC, s); // $t1 <- val(e1),$t1 + val(e2),$a0 emit_load(ACC, 1, SP, s); emit_store_int(T1, ACC, s); emit_pop(2, s); } /* Thanks to pseudo-instruction in spim emulator, we dont need to deal with hi/lo registers by hand, so the overall code is just the same as addition */ void mul_class::code(ostream &s, CgenClassTable *classtab) { this->e1->code(s, classtab); emit_fetch_int(ACC, ACC, s); emit_push(ACC, s); this->e2->code(s, classtab); emit_jal("Object.copy", s); emit_push(ACC, s); emit_fetch_int(ACC, ACC, s); // $a0 <- val(e2) emit_load(T1, 2, SP, s); // $t1 <- val(e1) emit_mul(T1, T1, ACC, s); // $t1 <- val(e1),$t1 + val(e2),$a0 emit_load(ACC, 1, SP, s); emit_store_int(T1, ACC, s); emit_pop(2, s); } void divide_class::code(ostream &s, CgenClassTable *classtab) { this->e1->code(s, classtab); emit_fetch_int(ACC, ACC, s); emit_push(ACC, s); this->e2->code(s, classtab); emit_jal("Object.copy", s); emit_push(ACC, s); emit_fetch_int(ACC, ACC, s); // $a0 <- val(e2) emit_load(T1, 2, SP, s); // $t1 <- val(e1) emit_div(T1, T1, ACC, s); // $t1 <- val(e1),$t1 + val(e2),$a0 emit_load(ACC, 1, SP, s); emit_store_int(T1, ACC, s); emit_pop(2, s); } /* Things are even simpler for unary operations: No need for stack! Just copy the Int object in $a0 generated by e1 to $a0 (we dont need the e1's object any more), since we have a temp reg, fetch value into $t1, negate it and send it back to the new Int object. That's all! */ void neg_class::code(ostream &s, CgenClassTable *classtab) { this->e1->code(s, classtab); emit_jal("Object.copy", s); emit_fetch_int(T1, ACC, s); emit_neg(T1, T1, s); emit_store_int(T1, ACC, s); } /* Though involving two different types, it doesn't make things harder. We first deal with Int comparsion. Quite similar to arithmetic operations, evaluate and extract the value attributes from the sub-expressions. Things afterwards are different. We need a label and branch instruction to generate true or false for the expression. Since there are only 2 registers available, occupied by two operands, we need two labels (if more registers are available, then only 1 label should suffice). The logic looks like this: ......(evaluate e1, e2) if val(e1) < val(e2) goto label1; $a0 = bool_const0; goto label2; label1: $a0 = bool_const1; label2: ......(clean up the expression) */ void lt_class::code(ostream &s, CgenClassTable *classtab) { this->e1->code(s, classtab); emit_fetch_int(ACC, ACC, s); emit_push(ACC, s); // $sp+4 == val(e1) this->e2->code(s, classtab); emit_fetch_int(ACC, ACC, s); // $a0 <- val(e2) emit_load(T1, 1, SP, s); // $t1 <- val(e1) auto label_true = classtab->alloc_label_index(); auto label_exit = classtab->alloc_label_index(); emit_blt(T1, ACC, label_true, s); // after the branch, val(e2) in $a0 is no more needed, making space for result emit_load_bool(ACC, falsebool, s); // didn't jump in last instruction, so it is false emit_branch(label_exit, s); // dont want it to be overridden emit_label_def(label_true, s); // first branch goes to here emit_load_bool(ACC, truebool, s); // branch means true emit_label_def(label_exit, s); // second jump goes to here emit_pop(1, s); // cleanup anyway, only one push is made } /* <= operation is exactly the same as < operation except the operator */ void leq_class::code(ostream &s, CgenClassTable *classtab) { this->e1->code(s, classtab); emit_fetch_int(ACC, ACC, s); emit_push(ACC, s); this->e2->code(s, classtab); emit_fetch_int(ACC, ACC, s); emit_load(T1, 1, SP, s); auto label_true = classtab->alloc_label_index(); auto label_exit = classtab->alloc_label_index(); emit_bleq(T1, ACC, label_true, s); emit_load_bool(ACC, falsebool, s); emit_branch(label_exit, s); emit_label_def(label_true, s); emit_load_bool(ACC, truebool, s); emit_label_def(label_exit, s); emit_pop(1, s); } /* Unary Bool operation `not` is more complicated than its Int counterpart It uses branch, in that we doesn't want to generate bool objects other than the two predefined constants. */ void comp_class::code(ostream &s, CgenClassTable *classtab) { this->e1->code(s, classtab); // this must be a Bool object in $a0 emit_fetch_bool(T1, ACC, s); // extract boolean value 0 or 1 to $t1 emit_load_bool(ACC, truebool, s); // default load true(assume val(e1)==false) auto label_index = classtab->alloc_label_index(); emit_beqz(T1, label_index, s); // val(e1)==false, skip the next load emit_load_bool(ACC, falsebool, s); // val(e1)==true, load false to $a0 emit_label_def(label_index, s); // no clean up needed, just exit here } /* Equality operator is much more complicated than others. According to the manual, when comparing two objects, their pointersn first get compared. If they resides in the same address, they are definitely equal, return true at once. Otherwise, call primitive procedure `equality_test`. As the Runtime System tour says, it accepts 2 params which resides in $t1 and $t2. The procedure checks the following condition: typeid($t1) in {Int, Bool, String} && typeid($t1)==typeid($t2) && value($1) == value($t2) The return value is in $a0. If condition is true, $a0<-$a0, else $a0<-$a1, where $a0, $a1 remain unmodified until return. Utilizing this feature, we can set $a0<-truebool, $a1<-falsebool before calling the procedure. Understanding the stuff above, the assembly is just there. */ void eq_class::code(ostream &s, CgenClassTable *classtab) { this->e1->code(s, classtab); emit_push(ACC, s); // e1 can evaluate to anything, so simply push the ref this->e2->code(s, classtab); // $a0<-&e2 emit_load(T1, 1, SP, s); // $t1<-&e1 emit_move(T2, ACC, s); // $t2<-&e2 // there's no choice but to break our 2 register rule ~_~ emit_load_bool(ACC, truebool, s); // load true in advance in case &e1==&e2 auto label_exit = classtab->alloc_label_index(); emit_beq(T1, T2, label_exit, s); // if &e1==&e2, then we are done here emit_load_bool(A1, falsebool, s); // prepare a false choice for equality_test emit_jal("equality_test", s); // at this point, $t1=&e1, $t2=&e2, $a0=true, $a1=false. ready to call // $a0 will be either true or false, so just keep it as the result emit_label_def(label_exit, s); emit_pop(1, s); // balance stack, 1 push in this expression } void int_const_class::code(ostream &s, CgenClassTable *classtab) { // // Need to be sure we have an IntEntry *, not an arbitrary Symbol // emit_load_int(ACC, inttable.lookup_string(token->get_string()), s); } void string_const_class::code(ostream &s, CgenClassTable *classtab) { emit_load_string(ACC, stringtable.lookup_string(token->get_string()), s); } void bool_const_class::code(ostream &s, CgenClassTable *classtab) { emit_load_bool(ACC, BoolConst(val), s); } /* Create a normal type object is quite simple, which could be done by 3 instructions: la $a0, T_protoObj call Object.copy call T_init Create SELF_TYPE object is very very tricky, because the real type is decided at run time. I managed to get this done by looking at the target code generated by the reference compiler. We need a table indexed by class tag, which contains T[i]_protoObj and T[i]_init. When creating such objects, we look up the actual protoObj and init method by the self object's class tag. This involves dereferencing pointers for multiple times, which is hard to get right. */ void new__class::code(ostream &s, CgenClassTable *classtab) { if (this->type_name == SELF_TYPE) { // first get the class tag at offset 0, $a0 <- 0($s0) emit_load(ACC, 0, SELF, s); // load the address of class_objTab, $t1 <- &class_objTab emit_load_address(T1, CLASSOBJTAB, s); // convert class tag to index, index = tag * 8, $a0 <- $a0 << 3 emit_sll(ACC, ACC, 3, s); // get the address of so_protoObj, $a0 <- $t1 + $a0(base + index) emit_addu(ACC, ACC, T1, s); // save index on stack, we are to use $a0 for param emit_push(ACC, s); // get the so_protoObj, $a0 <- 0($a0) emit_load(ACC, 0, ACC, s); // call Object.copy emit_jal("Object.copy", s); // recover the addresss of so_protoObj, $t1 <- stack top emit_load(T1, 1, SP, s); emit_pop(s); // pop // load address of so_init, $t1 <- 4($t1) emit_load(T1, 1, T1, s); // with $a0 storing the new object's ref, call so_init whose address is in // $t1, which accepts $a0 as the parameter emit_jalr(T1, s); // initialized brand new object already has its ref in $a0 } else { // load address: $a0 <- T_protObj emit_partial_load_address(ACC, s); emit_protobj_ref(this->type_name, s); s << endl; // call Object.copy emit_jal("Object.copy", s); // call T_init s << JAL; emit_init_ref(this->type_name, s); s << endl; // initialized brand new object already has its ref in $a0 } } /* `isvoid` operation is quite simple and stack-operation free, since we only test the reference is zero or not. A straightforward beqz should suffice. */ void isvoid_class::code(ostream &s, CgenClassTable *classtab) { this->e1->code(s, classtab); emit_move(T1, ACC, s); // $t1 <- &e1 emit_load_bool(ACC, truebool, s); auto label_exit = classtab->alloc_label_index(); emit_beqz(T1, label_exit, s); // &e1 == nullptr ?, if so skip the next load false emit_load_bool(ACC, falsebool, s); emit_label_def(label_exit, s); } /* No_expr means the init expression is omitted. However, the object has to be assigned to some value. CgenClassTable::expr_type_decl is set for this method to generate a propriate default initial value. */ void no_expr_class::code(ostream &s, CgenClassTable *classtab) { if (classtab->expr_type_decl == Int) { emit_load_int(ACC, classtab->int_default(), s); } else if (classtab->expr_type_decl == Bool) { emit_load_bool(ACC, *classtab->bool_default(), s); } else if (classtab->expr_type_decl == Str) { emit_load_string(ACC, classtab->str_default(), s); } else if (classtab->expr_type_decl == prim_slot) { assert(0); // basic type should not get attrs init } else { assert(classtab->expr_type_decl); emit_move(ACC, ZERO, s); } } /* ObjectID simply perform a load from store to $a0 Note that `self` is not in location table, add a special case and $a0<-$s0 */ void object_class::code(ostream &s, CgenClassTable *classtab) { if (this->name == self) { emit_move(ACC, SELF, s); } else { auto loc = classtab->loctab.lookup(this->name); if (loc->location == Stack) emit_load(ACC, loc->offset, FP, s); else emit_load(ACC, loc->offset, SELF, s); } } #pragma endregion