home *** CD-ROM | disk | FTP | other *** search
-
- /* Copyright (C) 1988, 1989 Herve' Touati, Aquarius Project, UC Berkeley */
-
- /* Copyright Herve' Touati, Aquarius Project, UC Berkeley */
-
- extern void mark_from_base(Cell*);
- extern void mark_from_base_sweep(Cell*);
- extern void copy_from_base(Cell*);
-
- struct UpStack {
- Cell* sp;
- Cell* sp0;
- void init(Cell* p) {sp0 = sp = p;}
- Cell* bottom() {return sp0;}
- Cell* top() {return sp;}
- void push(Cell* val) {*sp++ = cell(val);}
- Cell* pop() {return cellp(*--sp);}
- int nonempty() {return (sp > sp0);}
- };
-
- struct DownStack {
- Cell* sp;
- Cell* sp0;
- void init(Cell* p) {sp0 = sp = p;}
- Cell* bottom() {return sp0;}
- Cell* top() {return sp;}
- void push(Cell* val) {*sp-- = cell(val);}
- Cell* pop() {return cellp(*++sp);}
- int nonempty() {return (sp < sp0);}
- };
-
- /* basic data structure to implement Cheney's copy algorithm */
- struct CopyStack {
- Cell* first;
- Cell* second;
- void init(Cell* p) {first = second = p;}
- Cell* top() {return first;}
- void push(Cell val) {*first++ = val;}
- Cell* pop() {return second++;}
- int nonempty() {return (first > second);}
- };
-
- inline Cell* max(Cell* a, Cell* b)
- {
- return (a > b) ? a : b;
- }
-
- inline Cell* min(Cell* a, Cell* b)
- {
- return (a < b) ? a : b;
- }
-
- extern void init_stats();
- extern void display_stat1(char*, int, int);
- extern void init_marking_table();
- extern CellPtr B2, HMIDDLE;
- extern unsigned char MARK;
-
- /* UTILITIES */
-
- inline int to_new_space(Cell* p)
- { return (p < H) && (p >= HMIN); }
-
- inline int pointer_to_new(Cell val)
- { return (get_tag(val) != TAGCONST && to_new_space(addr(val))); }
-
- /* better be sure p points to new space */
- inline Cell* reloc_addr(Cell* p)
- { return cellp(*p); }
-
- inline void set_reloc_addr(Cell* p, Cell* new_addr)
- { *p = cell(new_addr); }
-
- inline Cell check_and_relocate(Cell var)
- {
- int tag = get_tag(var);
- Cell* ptr = addr(var);
- if (tag != TAGCONST && to_new_space(ptr))
- return make_ptr(tag, reloc_addr(ptr));
- else
- return var;
- }
-
- /* suppose that p is an address to a location in new space */
- /* please do the check!! note: new space contain a relocation table. */
- overload relocate;
- inline Cell relocate(Cell var)
- { return make_ptr(get_tag(var), reloc_addr(addr(var))); }
-
- inline Cell relocate(int tag, Cell* p)
- { return make_ptr(tag, reloc_addr(p)); }
-
- inline void mark(Cell* p)
- { MKMIN[p - HMIN] = MARK; }
-
- inline int marked(Cell* p)
- { return (MKMIN[p - HMIN] == MARK); }
-
- inline int unmarked(Cell* p)
- { return (MKMIN[p - HMIN] != MARK); }
-
- extern void store_regs_in_env();
- extern void restore_top_env();
-
- struct Env {
- Cell* e;
- int size;
- int already_treated;
- void next() {
- size = instrp(e[P_ENV_OFFSET])->arg2; /* P points to the call instr */
- already_treated = 0;
- e = cellp(e[E_ENV_OFFSET]);
- }
- Env() {}
- Env(Cell* E) {init(E);}
- void init(Cell* E) {
- e = E;
- next();
- }
- void treated(int n) {already_treated = n;}
- void mark();
- void fast_copy();
- void mark_sweep();
- void update();
- };
-
- struct ChoiceRecord {
- Cell* tr;
- Cell* e;
- Cell* h;
- };
-
- struct Choice {
- Cell* b;
- Env already_done;
- Env preserved;
- Cell* tr;
- Choice(Cell*, Cell*);
- void next() {
- b = b + FIXED_CP_SIZE + b[SIZE_CP_OFFSET];
- preserved.init(cellp(b[E_CP_OFFSET]));
- }
- int last() { return (b >= B2); }
- void mark();
- void mark_sweep();
- void virtual_backtrack();
- void virtual_backtrack_sweep();
- void mark_preserved_envs();
- void mark_preserved_envs_sweep();
- void update();
- void update_preserved_envs();
- };
-
- extern void cp_to_cp_forward();
- extern void cp_to_cp_backward();
-
- /* The TRAIL STACK */
-
- enum {
- TRAIL_SKIP,
- TRAIL_KEEP,
- TRAIL_RELOC,
- TRAIL_IND_RELOC,
- TRAIL_COPY_RELOC,
- TRAIL_MARK
- };
-
- /* sort of a cp cache, with some control info. */
- /* the main point is to make sure that the TR entries are updated */
- /* after the former values are read */
- struct TrailCP {
- Cell* b;
- Cell* next_b;
- Cell* last_b;
- Cell* tr;
- Cell* next_tr;
- Cell* e;
- Cell* h;
- TrailCP(Cell* B2, Cell* B) {b = B2; last_b = B; init();}
- int nonempty() {return (b > last_b);}
- void init() {next_b = b;
- next_tr = cellp(b[TR_CP_OFFSET]);
- next();}
- void next() {b = next_b;
- e = cellp(b[E_CP_OFFSET]);
- h = cellp(b[H_CP_OFFSET]);
- tr = next_tr;
- next_b = b - (FIXED_CP_SIZE + b[SIZE_CP_OFFSET]);
- next_tr = cellp(next_b[TR_CP_OFFSET]);}
- void update_tr(Cell* tr) { next_b[TR_CP_OFFSET] = cell(tr); }
- int pass1_action(Cell* ptr) {
- if (ptr >= e || (ptr < E0 && ptr >= h))
- return TRAIL_SKIP;
- else if (ptr >= E2 || (ptr < E0 && ptr >= HMIN))
- return TRAIL_KEEP;
- else
- return (pointer_to_new(*ptr)) ? TRAIL_MARK : TRAIL_KEEP;
- }
- int pass2_action(Cell* ptr) {
- #ifdef WITH_VIRTUAL_BACK
- if (*ptr == make_ptr(TAGREF,ptr))
- return TRAIL_SKIP;
- else if (to_new_space(ptr)) {
- #else
- if (to_new_space(ptr)) {
- #endif
- if (unmarked(ptr))
- return TRAIL_SKIP;
- else
- return (ptr >= HMIDDLE) ? TRAIL_RELOC : TRAIL_COPY_RELOC;
- } else
- return TRAIL_IND_RELOC;
- }
- int pass2_action_sweep(Cell* ptr) {
- #ifdef WITH_VIRTUAL_BACK
- if (*ptr == make_ptr(TAGREF,ptr))
- return TRAIL_SKIP;
- else if (to_new_space(ptr)) {
- #else
- if (to_new_space(ptr)) {
- #endif
- if (unmarked(ptr))
- return TRAIL_SKIP;
- else
- return TRAIL_RELOC;
- } else
- return TRAIL_IND_RELOC;
- }
- };
-
- extern void gccontrol_pass2();
-
- enum {
- SHOULD_COPY,
- SHOULD_MARK,
- SHOULD_CHECK_MARK,
- SHOULD_RELOC,
- SHOULD_NEITHER,
- SHOULD_LEAVE
- };
-
- extern void mark_compact();
- extern void fast_copy();
- extern struct rusage gc_rusage;
- extern int getrusage(...);
- extern CellPtr H_entry_value;
- extern CellPtr H2_entry_value;
- extern CellPtr TR_entry_value;
- extern CellPtr TR2_entry_value;
-
- extern void gc_init();
- extern void global_sweep();
- extern void restore_cps();
- extern ChoiceRecord SAVED_CP;
- extern void gctrail_pass11();
- extern void compute_stats();
-