Blue -> Caml_blue etc.

git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@2725 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
master
Damien Doligez 2000-01-02 16:10:00 +00:00
parent 44ee12deae
commit 794e9c495b
13 changed files with 57 additions and 56 deletions

View File

@ -278,7 +278,7 @@ void compact_heap (void)
* (word *) q = (word) Val_hp (newadr);
q = next;
}
*p = Make_header (Wosize_whsize (sz), t, White);
*p = Make_header (Wosize_whsize (sz), t, Caml_white);
if (infixes != NULL){
/* Rebuild the infix headers and revert the infix pointers. */
@ -292,7 +292,7 @@ void compact_heap (void)
* (word *) q = (word) Val_hp ((word *) newadr + (infixes - p));
q = next;
} Assert (Ecolor (q) == 1 || Ecolor (q) == 3);
*infixes = Make_header (infixes - p, Infix_tag, White);
*infixes = Make_header (infixes - p, Infix_tag, Caml_white);
infixes = (word *) q;
}
}
@ -303,7 +303,7 @@ void compact_heap (void)
*/
/* No pointers to the header and no infix header:
the object was free. */
*p = Make_header (Wosize_ehd (q), Tag_ehd (q), Blue);
*p = Make_header (Wosize_ehd (q), Tag_ehd (q), Caml_blue);
p += Whsize_ehd (q);
}
}
@ -323,14 +323,14 @@ void compact_heap (void)
chend = ch + Chunk_size (ch);
while ((char *) p < chend){
word q = *p;
if (Color_hd (q) == White){
if (Color_hd (q) == Caml_white){
size_t sz = Bhsize_hd (q);
char *newadr = compact_allocate (sz); Assert (newadr <= (char *)p);
/* bcopy (source, destination, length) */
bcopy (p, newadr, sz);
p += Wsize_bsize (sz);
}else{
Assert (Color_hd (q) == Blue);
Assert (Color_hd (q) == Caml_blue);
p += Whsize_hd (q);
}
}
@ -380,7 +380,7 @@ void compact_heap (void)
if (Chunk_size (ch) > Chunk_alloc (ch)){
header_t *p = (header_t *) (ch + Chunk_alloc (ch));
*p = Make_header (Wosize_bhsize (Chunk_size (ch) - Chunk_alloc (ch)),
0, White);
0, Caml_white);
fl_merge_block (Bp_hp (p));
}
ch = Chunk_next (ch);

View File

@ -317,7 +317,7 @@ static void extern_rec(value v)
if (tag < 16 && sz < 8) {
Write(PREFIX_SMALL_BLOCK + tag + (sz << 4));
} else {
writecode32(CODE_BLOCK32, hd & ~Black);
writecode32(CODE_BLOCK32, Whitehd_hd (hd));
}
size_32 += 1 + sz;
size_64 += 1 + sz;

View File

@ -126,7 +126,7 @@ void raise_sys_blocked_io(void)
void init_exceptions(void)
{
out_of_memory_bucket.hdr = Make_header(1, 0, White);
out_of_memory_bucket.hdr = Make_header(1, 0, Caml_white);
out_of_memory_bucket.exn = Field(global_data, OUT_OF_MEMORY_EXN);
register_global_root(&out_of_memory_bucket.exn);
}

View File

@ -36,7 +36,7 @@ static struct {
header_t h;
value first_bp;
value filler2; /* Make sure the sentinel is never adjacent to any block. */
} sentinel = {0, Make_header (0, 0, Blue), 0, 0};
} sentinel = {0, Make_header (0, 0, Caml_blue), 0, 0};
#define Fl_head ((char *) (&(sentinel.first_bp)))
static char *fl_prev = Fl_head; /* Current allocation pointer. */
@ -97,9 +97,9 @@ static char *allocate_block (mlsize_t wh_sz, char *prev, char *cur)
/* In case 1, the following creates the empty block correctly.
In case 0, it gives an invalid header to the block. The function
calling [fl_allocate] will overwrite it. */
Hd_op (cur) = Make_header (0, 0, White);
Hd_op (cur) = Make_header (0, 0, Caml_white);
}else{ /* Case 2. */
Hd_op (cur) = Make_header (Wosize_hd (h) - wh_sz, 0, Blue);
Hd_op (cur) = Make_header (Wosize_hd (h) - wh_sz, 0, Caml_blue);
}
fl_prev = prev;
return cur + Bosize_hd (h) - Bsize_wsize (wh_sz);
@ -186,7 +186,7 @@ char *fl_merge_block (char *bp)
/* If [last_fragment] and [bp] are adjacent, merge them. */
if (last_fragment == Hp_bp (bp)){
hd = Make_header (Whsize_bp (bp), 0, White);
hd = Make_header (Whsize_bp (bp), 0, Caml_white);
bp = last_fragment;
Hd_bp (bp) = hd;
fl_cur_size += Whsize_wosize (0);
@ -201,7 +201,7 @@ char *fl_merge_block (char *bp)
Next (prev) = next_cur;
if (fl_prev == cur) fl_prev = prev;
hd = Make_header (Wosize_hd (hd) + cur_whsz, 0, Blue);
hd = Make_header (Wosize_hd (hd) + cur_whsz, 0, Caml_blue);
Hd_bp (bp) = hd;
adj = bp + Bosize_hd (hd);
#ifdef DEBUG
@ -214,7 +214,7 @@ char *fl_merge_block (char *bp)
/* If [prev] and [bp] are adjacent merge them, else insert [bp] into
the free-list if it is big enough. */
if (prev + Bosize_bp (prev) == Hp_bp (bp)){
Hd_bp (prev) = Make_header (Wosize_bp (prev) + Whsize_hd (hd), 0, Blue);
Hd_bp (prev) = Make_header (Wosize_bp (prev) + Whsize_hd (hd), 0, Caml_blue);
#ifdef DEBUG
Hd_bp (bp) = not_random ();
#endif

View File

@ -18,23 +18,23 @@
#include "mlvalues.h"
#define White (0 << 8)
#define Gray (1 << 8)
#define Blue (2 << 8)
#define Black (3 << 8)
#define Caml_white (0 << 8)
#define Caml_gray (1 << 8)
#define Caml_blue (2 << 8)
#define Caml_black (3 << 8)
#define Color_hd(hd) ((color_t) ((hd) & Black))
#define Color_hd(hd) ((color_t) ((hd) & Caml_black))
#define Color_hp(hp) Color_hd (Hd_hp (hp))
#define Is_white_hd(hd) (Color_hd (hd) == White)
#define Is_gray_hd(hd) (Color_hd (hd) == Gray)
#define Is_blue_hd(hd) (Color_hd (hd) == Blue)
#define Is_black_hd(hd) (Color_hd (hd) == Black)
#define Is_white_hd(hd) (Color_hd (hd) == Caml_white)
#define Is_gray_hd(hd) (Color_hd (hd) == Caml_gray)
#define Is_blue_hd(hd) (Color_hd (hd) == Caml_blue)
#define Is_black_hd(hd) (Color_hd (hd) == Caml_black)
#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)
#define Whitehd_hd(hd) (((hd) & ~Caml_black)/*| Caml_white*/)
#define Grayhd_hd(hd) (((hd) & ~Caml_black) | Caml_gray)
#define Blackhd_hd(hd) (((hd)/*& ~Caml_black*/)| Caml_black)
#define Bluehd_hd(hd) (((hd) & ~Caml_black) | Caml_blue)
/* This depends on the layout of the header. See [mlvalues.h]. */
#define Make_header(wosize, tag, color) \
@ -44,10 +44,10 @@
#define Color_val(val) (Color_hd (Hd_val (val)))
#define Is_white_val(val) (Color_val(val) == White)
#define Is_gray_val(val) (Color_val(val) == Gray)
#define Is_blue_val(val) (Color_val(val) == Blue)
#define Is_black_val(val) (Color_val(val) == Black)
#define Is_white_val(val) (Color_val(val) == Caml_white)
#define Is_gray_val(val) (Color_val(val) == Caml_gray)
#define Is_blue_val(val) (Color_val(val) == Caml_blue)
#define Is_black_val(val) (Color_val(val) == Caml_black)
#endif /* _gc_ */

View File

@ -48,7 +48,7 @@ static void check_head (value v)
Assert (Is_block (v) && Is_in_heap (v));
Assert (Wosize_val (v) != 0);
Assert (Color_hd (Hd_val (v)) != Blue);
Assert (Color_hd (Hd_val (v)) != Caml_blue);
Assert (Is_in_heap (v));
if (Tag_val (v) == Infix_tag){
int offset = Wsize_bsize (Infix_offset_val (v));
@ -136,14 +136,15 @@ static value heap_stats (int returnstats)
cur_hd = Hd_hp (cur_hp);
Assert (Next (cur_hp) <= chunk_end);
switch (Color_hd (cur_hd)){
case White:
case Caml_white:
if (Wosize_hd (cur_hd) == 0){
++fragments;
Assert (prev_hp == NULL
|| (Color_hp (prev_hp) != Blue && Wosize_hp (prev_hp) > 0)
|| (Color_hp (prev_hp) != Caml_blue
&& Wosize_hp (prev_hp) > 0)
|| cur_hp == gc_sweep_hp);
Assert (Next (cur_hp) == chunk_end
|| (Color_hp (Next (cur_hp)) != Blue
|| (Color_hp (Next (cur_hp)) != Caml_blue
&& Wosize_hp (Next (cur_hp)) > 0)
|| Next (cur_hp) == gc_sweep_hp);
}else{
@ -156,7 +157,7 @@ static value heap_stats (int returnstats)
}
}
break;
case Gray: case Black:
case Caml_gray: case Caml_black:
Assert (Wosize_hd (cur_hd) > 0);
++ live_blocks;
live_words += Whsize_hd (cur_hd);
@ -164,7 +165,7 @@ static value heap_stats (int returnstats)
check_block (cur_hp);
#endif
break;
case Blue:
case Caml_blue:
Assert (Wosize_hd (cur_hd) > 0);
++ free_blocks;
free_words += Whsize_hd (cur_hd);
@ -172,10 +173,10 @@ static value heap_stats (int returnstats)
largest_free = Whsize_hd (cur_hd);
}
Assert (prev_hp == NULL
|| (Color_hp (prev_hp) != Blue && Wosize_hp (prev_hp) > 0)
|| (Color_hp (prev_hp) != Caml_blue && Wosize_hp (prev_hp) > 0)
|| cur_hp == gc_sweep_hp);
Assert (Next (cur_hp) == chunk_end
|| (Color_hp (Next (cur_hp)) != Blue
|| (Color_hp (Next (cur_hp)) != Caml_blue
&& Wosize_hp (Next (cur_hp)) > 0)
|| Next (cur_hp) == gc_sweep_hp);
break;

View File

@ -280,7 +280,7 @@ static void intern_alloc(mlsize_t whsize, mlsize_t num_objects)
intern_block = alloc(wosize, String_tag);
intern_header = Hd_val(intern_block);
intern_color = Color_hd(intern_header);
Assert (intern_color == White || intern_color == Black);
Assert (intern_color == Caml_white || intern_color == Caml_black);
intern_dest = (header_t *) Hp_val(intern_block);
intern_extra_block = NULL;
}
@ -302,7 +302,7 @@ static void intern_add_to_heap(mlsize_t whsize)
Assert(intern_dest <= end_extra_block);
if (intern_dest < end_extra_block)
*intern_dest =
Make_header(Wosize_whsize(end_extra_block - intern_dest), 0, White);
Make_header(Wosize_whsize(end_extra_block-intern_dest), 0, Caml_white);
add_to_heap(intern_extra_block);
}
}

View File

@ -507,7 +507,7 @@ value interprete(code_t prog, asize_t prog_size)
*--sp = accu;
p++;
for (i = 1; i < nfuncs; i++) {
*p = Make_header(i * 2, Infix_tag, Black); /* color irrelevant? Yes. */
*p = Make_header(i * 2, Infix_tag, Caml_white); /* color irrelevant. */
p++;
*p = (value) (pc + pc[i]);
*--sp = (value) p;

View File

@ -185,7 +185,7 @@ static void update_weak_pointers (void)
mlsize_t sz, i;
while (cur != NULL){
if (Color_val (cur) == White){
if (Color_val (cur) == Caml_white){
*prev = Field (cur, 0);
cur = (value *) *prev;
}else{
@ -216,18 +216,18 @@ static void sweep_slice (long int work)
work -= Whsize_hd (hd);
gc_sweep_hp += Bhsize_hd (hd);
switch (Color_hd (hd)){
case White:
case Caml_white:
if (Tag_hd (hd) == Final_tag){
Final_fun (Val_hp (hp)) (Val_hp (hp));
}
gc_sweep_hp = fl_merge_block (Bp_hp (hp));
break;
case Blue:
case Caml_blue:
/* Only the blocks of the free-list are blue. See [freelist.c]. */
fl_merge = Bp_hp (hp);
break;
default: /* Gray or Black */
Assert(Color_hd(hd) == Black);
default: /* gray or black */
Assert (Color_hd (hd) == Caml_black);
Hd_hp (hp) = Whitehd_hd (hd);
break;
}
@ -379,7 +379,7 @@ void init_major_heap (asize_t heap_size)
page_table [i] = In_heap;
}
Hd_hp (heap_start) = Make_header (Wosize_bhsize (stat_heap_size), 0, Blue);
Hd_hp (heap_start) = Make_header (Wosize_bhsize (stat_heap_size), 0, Caml_blue);
fl_init_merge ();
fl_merge_block (Bp_hp (heap_start));
gc_phase = Phase_idle;

View File

@ -157,7 +157,7 @@ static char *expand_heap (mlsize_t request)
return NULL;
}
Assert (Wosize_bhsize (malloc_request) >= request);
Hd_hp (mem) = Make_header (Wosize_bhsize (malloc_request), 0, Blue);
Hd_hp (mem) = Make_header (Wosize_bhsize (malloc_request), 0, Caml_blue);
if (add_to_heap (mem) != 0){
free (mem);
@ -212,11 +212,11 @@ color_t allocation_color (void *hp)
{
if (gc_phase == Phase_mark
|| (gc_phase == Phase_sweep && (addr)hp >= (addr)gc_sweep_hp)){
return Black;
return Caml_black;
}else{
Assert (gc_phase == Phase_idle
|| (gc_phase == Phase_sweep && (addr)hp < (addr)gc_sweep_hp));
return White;
return Caml_white;
}
}
@ -242,11 +242,11 @@ value alloc_shr (mlsize_t wosize, tag_t tag)
/* Inline expansion of allocation_color. */
if (gc_phase == Phase_mark
|| (gc_phase == Phase_sweep && (addr)hp >= (addr)gc_sweep_hp)){
Hd_hp (hp) = Make_header (wosize, tag, Black);
Hd_hp (hp) = Make_header (wosize, tag, Caml_black);
}else{
Assert (gc_phase == Phase_idle
|| (gc_phase == Phase_sweep && (addr)hp < (addr)gc_sweep_hp));
Hd_hp (hp) = Make_header (wosize, tag, White);
Hd_hp (hp) = Make_header (wosize, tag, Caml_white);
}
Assert (Hd_hp (hp) == Make_header (wosize, tag, allocation_color (hp)));
allocated_words += Whsize_wosize (wosize);

View File

@ -54,7 +54,7 @@ color_t allocation_color (void *hp);
Restore_after_gc; \
young_ptr -= Bhsize_wosize (wosize); \
} \
Hd_hp (young_ptr) = Make_header ((wosize), (tag), Black); \
Hd_hp (young_ptr) = Make_header ((wosize), (tag), Caml_black); \
(result) = Val_hp (young_ptr); \
}

View File

@ -104,7 +104,7 @@ value obj_truncate (value v, value newsize) /* ML */
if (new_wosize <= 0 || new_wosize > wosize) invalid_argument ("Obj.truncate");
if (new_wosize == wosize) return Val_unit;
Field (v, new_wosize) =
Make_header (Wosize_whsize (wosize-new_wosize), 0, White);
Make_header (Wosize_whsize (wosize-new_wosize), 0, Caml_white);
Hd_val (v) = Make_header (new_wosize, tag, color);
return Val_unit;
}

View File

@ -55,7 +55,7 @@ header_t atom_table[256];
static void init_atoms(void)
{
int i;
for(i = 0; i < 256; i++) atom_table[i] = Make_header(0, i, White);
for(i = 0; i < 256; i++) atom_table[i] = Make_header(0, i, Caml_white);
}
/* Read the trailer of a bytecode file */