home *** CD-ROM | disk | FTP | other *** search
-
- /* Copyright (C) 1988, 1989 Herve' Touati, Aquarius Project, UC Berkeley */
-
- /* Copyright Herve' Touati, Aquarius Project, UC Berkeley */
-
- #include <stream.h>
- #include <ctype.h>
- #include "tags.h"
- #include "instr.h"
- #include "hash_table.h"
- #include "string_table.h"
- #include "scan.h"
- #include "inst_args.h"
- #include "memory.h"
- #include "basics.h"
-
- InstrArg* instr_args[ARG_LAST];
-
- void init_instr_args(Scan& scanner) {
- int i = 0;
- #define use(String,ARGID,NAME)\
- instr_args[i] = new NAME;\
- instr_args[i]->init(scanner);\
- instr_args[i++]->name = String;
- #include "list_inst_args.h"
- #undef use
- }
-
- extern int atoi(const char*);
-
- int Var::fill(char* s)
- {
- return atoi(++s) - 1;
- }
-
- int Label::fill(char* s)
- {
- return (*s == '_') ? atoi(++s) : LABEL_FAIL;
- }
-
- void Label::print(int value)
- {
- if (instrp(value) == FP0)
- cout << "fail";
- else
- printf("_%d", instrp(value) - P0 + 1);
- }
-
- int Label::update(int label)
- {
- int addr = label_table->get(label);
- return (int) ((label_table->status == HASH_MISS) ? FP0 : P0 + addr -1);
- }
-
- void Label::init(Scan&)
- {
- label_table = new HashTable;
- }
-
- int Int::fill(char* s)
- {
- return atoi(s);
- }
-
- int Const::fill(char* s)
- {
- Cell Val;
- if (*s == '&' && isdigit(*(s + 1))) {
- Val = make_int(atoi(++s));
- } else {
- Val = make_atom(symbol_table->intern(s));
- }
- return Val;
- }
-
- void Const::print(int value)
- {
- if (is_atom(value))
- cout << get_string(value);
- else
- cout << "&" << get_int(value);
- }
-
- void BuiltIn::init(Scan& ST)
- {
- name_to_ID = new HashTable;
- exec_to_ID = new HashTable;
- built_in_table = new BuiltInEntry[LAST_BUILT_IN];
- symbol_table = &ST;
- #define NAMES
- #define use(ID,NAME,FUNCTION) {\
- int value = symbol_table->intern(NAME);\
- name_to_ID->bind(value, ID);\
- built_in_table[ID].name = value;\
- extern void FUNCTION();\
- built_in_table[ID].exec = &FUNCTION;\
- exec_to_ID->bind((int) &FUNCTION, ID);\
- }
- #include "built_ins.h"
- #undef use
- #undef NAMES
- }
-
- PF BuiltIn::get_exec(int name)
- {
- int ID = name_to_ID->get(name);
- if (name_to_ID->status == HASH_MISS) return 0;
- return built_in_table[ID].exec;
- }
-
- void Table::print(int value)
- {
- HashTable* table = (HashTable*) TableOfTables->get(value);
- table->reset();
- HashTableEntry* e;
- while (e = table->next()) {
- cout << "\n\t";
- instr_args[ARG_CONST]->print(e->key);
- cout << " -> ";
- instr_args[ARG_LABEL]->print(e->value);
- }
- }
-
- int Table::fill(char* s)
- {
- Int to_size;
- int table_size = (to_size.fill(s) + 1)/ 2;
- HashTable* table = new HashTable(table_size + 2);
-
- /* first, get rid of the table label */
- scanner->next_line();
-
- /* the main loop */
- /* can continue as long as no tcdr sign is encountered */
- int can_continue = 1;
- for (int i = 0; can_continue && i < table_size; i++) {
- scanner->next_line();
- int constant = instr_args[ARG_CONST]->fill(scanner->p[0]);
- can_continue = (*scanner->p[1] == '\0');
- scanner->next_line();
- int label = instr_args[ARG_LABEL]->fill(scanner->p[0]);
- label = instr_args[ARG_LABEL]->update(label);
- table->bind(constant, label);
- }
-
- /* scan the entries up to the end */
- for (; i < table_size; i++) {
- scanner->next_line();
- scanner->next_line();
- }
- scanner->status = SCAN_INSTR;
- TableOfTables->bind(table_count, (int) table);
- return table_count++;
- }
-
- HashTable* Proc::get_table()
- {
- return proc_name_table;
- }
-
- int Proc::update(int name)
- {
- int addr = proc_addr_table->get(name);
- if (proc_addr_table->status == HASH_MISS) {
- status = UNRESOLVED_ADDRESSES;
- return 0;
- }
- return (int) (P0 + addr -1);
- }
-
- int Proc::get_arity(int addr)
- {
- addr = instrp(addr) - P0 + 1;
- int name = proc_name_table->get(addr);
- return symbol_table->get_arity(name);
- }
-
- void Proc::print(int addr)
- {
- if (addr == 0) {printf("-???-"); return;}
- addr = instrp(addr) - P0 + 1;
- int name = proc_name_table->get(addr);
- int arity = symbol_table->get_arity(name);
- printf("%s(#%d,@%d)", (char*) name, arity, addr);
- }
-
- void Proc::print_proc_table()
- {
- proc_name_table->reset();
- HashTableEntry* e;
- while (e = proc_name_table->next()) {
- cout << "\n\t";
- print((int) (P0 + e->key - 1));
- }
- cout << "\n";
- }
-
- /* proc_addr_table: key->name, value->addr(as offset in code space) */
- /* proc_name_table: key->addr(as offset in code space), value->name */
- void Proc::init(Scan& ST)
- {
- symbol_table = &ST;
- proc_addr_table = new HashTable;
- proc_name_table = new HashTable;
- status = NO_UNRESOLVED_ADDRESSES;
- }
-