diff options
-rw-r--r-- | byterun/fix_code.c | 4 | ||||
-rw-r--r-- | byterun/fix_code.h | 4 | ||||
-rw-r--r-- | byterun/gc.h | 11 | ||||
-rw-r--r-- | byterun/gc_ctrl.c | 19 | ||||
-rw-r--r-- | byterun/interp.a | 3 | ||||
-rw-r--r-- | byterun/interp.c | 16 | ||||
-rw-r--r-- | byterun/major_gc.c | 13 |
7 files changed, 35 insertions, 35 deletions
diff --git a/byterun/fix_code.c b/byterun/fix_code.c index 37543ace7..d00e77bce 100644 --- a/byterun/fix_code.c +++ b/byterun/fix_code.c @@ -78,8 +78,8 @@ void fixup_endianness(code, len) #ifdef THREADED_CODE -void ** instr_table; -void * instr_base; +char ** instr_table; +char * instr_base; void thread_code (code_t code, asize_t len) { diff --git a/byterun/fix_code.h b/byterun/fix_code.h index 5efcce96a..e6149b091 100644 --- a/byterun/fix_code.h +++ b/byterun/fix_code.h @@ -30,8 +30,8 @@ void fixup_endianness P((code_t code, asize_t len)); void set_instruction P((code_t pos, opcode_t instr)); #ifdef THREADED_CODE -extern void ** instr_table; -extern void * instr_base; +extern char ** instr_table; +extern char * instr_base; void thread_code P((code_t code, asize_t len)); #endif diff --git a/byterun/gc.h b/byterun/gc.h index a54f06589..09e9ef197 100644 --- a/byterun/gc.h +++ b/byterun/gc.h @@ -17,9 +17,6 @@ #include "mlvalues.h" -/* Defined in [major_gc.c]. */ -extern unsigned free_mem_percent_min, free_mem_percent_max; - #define White (0 << 8) #define Gray (1 << 8) #define Blue (2 << 8) @@ -33,10 +30,10 @@ extern unsigned free_mem_percent_min, free_mem_percent_max; #define Is_blue_hd(hd) (Color_hd (hd) == Blue) #define Is_black_hd(hd) (Color_hd (hd) == Black) -#define Whitehd_hd(hd) ((hd) & ~Black) -#define Grayhd_hd(hd) (((hd) & ~Black) | Gray) -#define Blackhd_hd(hd) ((hd) | Black) -#define Bluehd_hd(hd) (((hd) & ~Black) | Blue) +#define Whitehd_hd(hd) (((hd) & ~Black)/*| White*/) +#define Grayhd_hd(hd) (((hd) & ~Black) | Gray) +#define Blackhd_hd(hd) (((hd)/*& ~Black*/)| Black) +#define Bluehd_hd(hd) (((hd) & ~Black) | Blue) /* This depends on the layout of the header. See [mlvalues.h]. */ #define Make_header(wosize, tag, color) \ diff --git a/byterun/gc_ctrl.c b/byterun/gc_ctrl.c index 419a1f4a1..6b889e76e 100644 --- a/byterun/gc_ctrl.c +++ b/byterun/gc_ctrl.c @@ -132,7 +132,7 @@ value gc_get(v) /* ML */ static int norm_pfree (p) int p; { - if (p < 1) return p = 1; + if (p < 1) p = 1; return p; } @@ -157,6 +157,8 @@ value gc_set(v) /* ML */ value v; { int newpf; + asize_t newheapincr; + asize_t newminsize; verb_gc = Bool_val (Field (v, 3)); @@ -166,17 +168,18 @@ value gc_set(v) /* ML */ gc_message ("New space overhead: %d%%\n", percent_free); } - if (Bsize_wsize (Long_val (Field (v, 1))) != major_heap_increment){ - major_heap_increment = norm_heapincr (Bsize_wsize (Long_val (Field(v,1)))); + newheapincr = norm_heapincr (Bsize_wsize (Long_val (Field (v, 1)))); + if (newheapincr != major_heap_increment){ + major_heap_increment = newheapincr; gc_message ("New heap increment size: %ldk\n", major_heap_increment/1024); } /* Minor heap size comes last because it will trigger a minor collection (thus invalidating [v]) and it can raise [Out_of_memory]. */ - if (Bsize_wsize (Long_val (Field (v, 0))) != minor_heap_size){ - long new_size = norm_minsize (Bsize_wsize (Long_val (Field (v, 0)))); - gc_message ("New minor heap size: %ldk\n", new_size/1024); - set_minor_heap_size (new_size); + newminsize = norm_minsize (Bsize_wsize (Long_val (Field (v, 0)))); + if (newminsize != minor_heap_size){ + gc_message ("New minor heap size: %ldk\n", newminsize/1024); + set_minor_heap_size (newminsize); } return Val_unit; } @@ -213,7 +216,7 @@ void init_gc (minor_size, major_incr, percent_fr, verb) { #ifdef DEBUG verb_gc = 1; - gc_message ("*** camlrun: debug mode ***\n", 0); + gc_message ("*** O'Caml runtime: debug mode ***\n", 0); #endif verb_gc = verb; set_minor_heap_size (Bsize_wsize (norm_minsize (minor_size))); diff --git a/byterun/interp.a b/byterun/interp.a index a51028e07..3c28066c5 100644 --- a/byterun/interp.a +++ b/byterun/interp.a @@ -41,7 +41,7 @@ import (cprim): data import (raise_zero_divide, fatal_error_arg): code import (thread_code): code - import (instr_table): data + import (instr_table, instr_base): data import (callback_depth): data msg record @@ -114,6 +114,7 @@ initial_callback_depth_ equ $00 BNE.S noinit ; == NULL => init LEA.L table(PC), A0 MOVE.L A0, (instr_table).L + CLR.L (instr_base).L MOVEQ.L #1, D0 Call_setup ; 2eme copie: "lbl_1B88" LEA.L local_var_size_(A7), A7 diff --git a/byterun/interp.c b/byterun/interp.c index 5af51bdd4..39a6b0a27 100644 --- a/byterun/interp.c +++ b/byterun/interp.c @@ -50,15 +50,15 @@ sp is a local copy of the global variable extern_sp. */ #ifdef THREADED_CODE # define Instruct(name) lbl_##name # if defined(ARCH_SIXTYFOUR) && !defined(ARCH_CODE32) -# define Jumptbl_base &&lbl_ACC0 +# define Jumptbl_base ((char *) &&lbl_ACC0) # else -# define Jumptbl_base ((void *) 0) -# define jumptbl_base ((void *) 0) +# define Jumptbl_base ((char *) 0) +# define jumptbl_base ((char *) 0) # endif # ifdef DEBUG # define Next goto next_instr # else -# define Next goto *(jumptbl_base + *pc++) +# define Next goto *(void *)(jumptbl_base + *pc++) # endif #else # define Instruct(name) case name @@ -153,9 +153,9 @@ value interprete(prog, prog_size) #endif #if defined(THREADED_CODE) && defined(ARCH_SIXTYFOUR) && !defined(ARCH_CODE32) #ifdef JUMPTBL_BASE_REG - register void * jumptbl_base JUMPTBL_BASE_REG; + register char * jumptbl_base JUMPTBL_BASE_REG; #else - register void * jumptbl_base; + register char * jumptbl_base; #endif #endif value env; @@ -176,7 +176,7 @@ value interprete(prog, prog_size) if (prog == NULL) { /* Interpreter is initializing */ #ifdef THREADED_CODE - instr_table = jumptable; + instr_table = (char **) jumptable; instr_base = Jumptbl_base; #endif return Val_unit; @@ -210,7 +210,7 @@ value interprete(prog, prog_size) Assert(sp >= stack_low); Assert(sp <= stack_high); #endif - goto *(jumptbl_base + *pc++); /* Jump to the first instruction */ + goto *(void *)(jumptbl_base + *pc++); /* Jump to the first instruction */ #else while(1) { #ifdef DEBUG diff --git a/byterun/major_gc.c b/byterun/major_gc.c index c3806a91f..29664b2d0 100644 --- a/byterun/major_gc.c +++ b/byterun/major_gc.c @@ -266,16 +266,15 @@ void major_collection_slice () Amount of sweeping work for the GC cycle: SW = stat_heap_size Amount of marking work for this slice: - MS = MW * 2 * P - MS = 2 * (100 - percent_free) + MS = MW * P + MS = (100 - percent_free) * (allocated_words * 3 / percent_free / 2 + 100 * extra_heap_memory) Amount of sweeping work for this slice: - SS = SW * 2 * P - SS = 2 * 100 - * (allocated_words * 3 / percent_free / 2 - + 100 * extra_heap_memory) - This slice will either mark MS words or sweep SS words. + SS = SW * P + SS = 100 * (allocated_words * 3 / percent_free / 2 + + 100 * extra_heap_memory) + This slice will either mark 2*MS words or sweep 2*SS words. */ #define Margin 100 /* Make it a little faster to be on the safe side. */ |