ajout Weak.get_copy

Assert -> CAMLassert
suppression des conjonctions dans les Assert


git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@3279 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
master
Damien Doligez 2000-08-23 17:10:03 +00:00
parent 7f2c1ed367
commit 3a43e16ae2
9 changed files with 62 additions and 18 deletions

View File

@ -52,7 +52,8 @@ value alloc_small (mlsize_t wosize, tag_t tag)
{ {
value result; value result;
Assert (wosize > 0 && wosize <= Max_young_wosize); Assert (wosize > 0)
Assert (wosize <= Max_young_wosize);
Assert (tag < 256); Assert (tag < 256);
Alloc_small (result, wosize, tag); Alloc_small (result, wosize, tag);
return result; return result;

View File

@ -216,17 +216,20 @@ void debugger(enum event_kind event)
switch(getch(dbg_in)) { switch(getch(dbg_in)) {
case REQ_SET_EVENT: case REQ_SET_EVENT:
pos = getword(dbg_in); pos = getword(dbg_in);
Assert(pos >= 0 && pos < code_size); Assert (pos >= 0);
Assert (pos < code_size);
set_instruction(start_code + pos / sizeof(opcode_t), EVENT); set_instruction(start_code + pos / sizeof(opcode_t), EVENT);
break; break;
case REQ_SET_BREAKPOINT: case REQ_SET_BREAKPOINT:
pos = getword(dbg_in); pos = getword(dbg_in);
Assert(pos >= 0 && pos < code_size); Assert (pos >= 0);
Assert (pos < code_size);
set_instruction(start_code + pos / sizeof(opcode_t), BREAK); set_instruction(start_code + pos / sizeof(opcode_t), BREAK);
break; break;
case REQ_RESET_INSTR: case REQ_RESET_INSTR:
pos = getword(dbg_in); pos = getword(dbg_in);
Assert(pos >= 0 && pos < code_size); Assert (pos >= 0);
Assert (pos < code_size);
pos = pos / sizeof(opcode_t); pos = pos / sizeof(opcode_t);
set_instruction(start_code + pos, saved_code[pos]); set_instruction(start_code + pos, saved_code[pos]);
break; break;

View File

@ -45,7 +45,8 @@ void final_update (void)
Assert (young == old); Assert (young == old);
Assert (young <= active); Assert (young <= active);
for (i = 0; i < old; i++){ for (i = 0; i < old; i++){
Assert (Is_block (final_table[i].val) && Is_in_heap (final_table[i].val)); Assert (Is_block (final_table[i].val));
Assert (Is_in_heap (final_table[i].val));
if (Is_white_val (final_table[i].val)){ if (Is_white_val (final_table[i].val)){
struct final f = final_table[i]; struct final f = final_table[i];
final_table[i] = final_table[--old]; final_table[i] = final_table[--old];
@ -147,7 +148,8 @@ value final_register (value f, value v) /* ML */
if (final_table == NULL){ if (final_table == NULL){
unsigned long new_size = 30; unsigned long new_size = 30;
final_table = stat_alloc (new_size * sizeof (struct final)); final_table = stat_alloc (new_size * sizeof (struct final));
Assert (old == 0 && young == 0); Assert (old == 0);
Assert (young == 0);
active = size = new_size; active = size = new_size;
}else{ }else{
unsigned long new_size = size * 2; unsigned long new_size = size * 2;

View File

@ -47,7 +47,8 @@ extern unsigned long percent_max; /* see compact.c */
/* Check that [v]'s header looks good. [v] must be a block in the heap. */ /* Check that [v]'s header looks good. [v] must be a block in the heap. */
static void check_head (value v) static void check_head (value v)
{ {
Assert (Is_block (v) && Is_in_heap (v)); Assert (Is_block (v));
Assert (Is_in_heap (v));
Assert (Wosize_val (v) != 0); Assert (Wosize_val (v) != 0);
Assert (Color_hd (Hd_val (v)) != Caml_blue); Assert (Color_hd (Hd_val (v)) != Caml_blue);
@ -83,7 +84,8 @@ static void check_block (char *hp)
/* not true when check_urgent_gc is called by alloc or alloc_string: /* not true when check_urgent_gc is called by alloc or alloc_string:
lastbyte = Bosize_val (v) - 1; lastbyte = Bosize_val (v) - 1;
i = Byte (v, lastbyte); i = Byte (v, lastbyte);
Assert (i >= 0 && i < sizeof (value)); Assert (i >= 0);
Assert (i < sizeof (value));
Assert (Byte (v, lastbyte - i) == 0); Assert (Byte (v, lastbyte - i) == 0);
*/ */
break; break;

View File

@ -181,7 +181,9 @@ static void intern_rec(value *dest)
case CODE_SHARED8: case CODE_SHARED8:
ofs = read8u(); ofs = read8u();
read_shared: read_shared:
Assert(ofs > 0 && ofs <= obj_counter && intern_obj_table != NULL); Assert (ofs > 0);
Assert (ofs <= obj_counter);
Assert (intern_obj_table != NULL);
v = intern_obj_table[obj_counter - ofs]; v = intern_obj_table[obj_counter - ofs];
break; break;
case CODE_SHARED16: case CODE_SHARED16:

View File

@ -737,7 +737,8 @@ value interprete(code_t prog, asize_t prog_size)
uint32 sizes = *pc++; uint32 sizes = *pc++;
if (Is_block(accu)) { if (Is_block(accu)) {
long index = Tag_val(accu); long index = Tag_val(accu);
Assert(index >= 0 && index < (sizes >> 16)); Assert (index >= 0);
Assert (index < (sizes >> 16));
pc += pc[(sizes & 0xFFFF) + index]; pc += pc[(sizes & 0xFFFF) + index];
} else { } else {
long index = Long_val(accu); long index = Long_val(accu);

View File

@ -21,7 +21,7 @@
#ifdef DEBUG #ifdef DEBUG
void failed_assert (char * expr, char * file, int line) void caml_failed_assert (char * expr, char * file, int line)
{ {
fprintf (stderr, "file %s; line %d ### Assertion failed: %s\n", fprintf (stderr, "file %s; line %d ### Assertion failed: %s\n",
file, line, expr); file, line, expr);
@ -148,7 +148,7 @@ char *aligned_malloc (asize_t size, int modulo, void **block)
{ {
char *raw_mem; char *raw_mem;
unsigned long aligned_mem; unsigned long aligned_mem;
Assert (modulo < Page_size); Assert (modulo < Page_size);
raw_mem = (char *) malloc (size + Page_size); raw_mem = (char *) malloc (size + Page_size);
if (raw_mem == NULL) return NULL; if (raw_mem == NULL) return NULL;
*block = raw_mem; *block = raw_mem;

View File

@ -45,10 +45,10 @@ typedef char * addr;
/* Assertions */ /* Assertions */
#ifdef DEBUG #ifdef DEBUG
#define Assert(x) if (!(x)) failed_assert ( #x , __FILE__, __LINE__) #define CAMLassert(x) if (!(x)) caml_failed_assert ( #x , __FILE__, __LINE__)
void failed_assert (char *, char *, int) Noreturn; void caml_failed_assert (char *, char *, int) Noreturn;
#else #else
#define Assert(x) #define CAMLassert(x)
#endif #endif
void fatal_error (char *) Noreturn; void fatal_error (char *) Noreturn;
@ -96,4 +96,9 @@ char *aligned_malloc (asize_t, int, void **);
#endif #endif
#ifndef CAML_AVOID_CONFLICTS
#define Assert CAMLassert
#endif
#endif /* _misc_ */ #endif /* _misc_ */

View File

@ -27,7 +27,7 @@ value weak_create (value len) /* ML */
value res; value res;
size = Long_val (len) + 1; size = Long_val (len) + 1;
if (size > Max_wosize) invalid_argument ("Weak.create"); if (size <= 0 || size > Max_wosize) invalid_argument ("Weak.create");
res = alloc_shr (size, Abstract_tag); res = alloc_shr (size, Abstract_tag);
for (i = 1; i < size; i++) Field (res, i) = 0; for (i = 1; i < size; i++) Field (res, i) = 0;
Field (res, 0) = weak_list_head; Field (res, 0) = weak_list_head;
@ -44,7 +44,7 @@ value weak_set (value ar, value n, value el) /* ML */
Assert (Is_in_heap (ar)); Assert (Is_in_heap (ar));
if (offset < 1 || offset >= Wosize_val (ar)) invalid_argument ("Weak.set"); if (offset < 1 || offset >= Wosize_val (ar)) invalid_argument ("Weak.set");
Field (ar, offset) = 0; Field (ar, offset) = 0;
if (el != None_val){ Assert (Wosize_val (el) == 1); if (el != None_val){ Assert (Wosize_val (el) == 1);
Modify (&Field (ar, offset), Field (el, 0)); Modify (&Field (ar, offset), Field (el, 0));
} }
return Val_unit; return Val_unit;
@ -74,10 +74,38 @@ value weak_get (value ar, value n) /* ML */
#undef Setup_for_gc #undef Setup_for_gc
#undef Restore_after_gc #undef Restore_after_gc
value weak_get_copy (value ar, value n) /* ML */
{
CAMLparam2 (ar, n);
mlsize_t offset = Long_val (n) + 1;
CAMLlocal2 (res, elt);
value v; /* Caution: this is NOT a local root. */
Assert (Is_in_heap (ar));
if (offset < 1 || offset >= Wosize_val (ar)) invalid_argument ("Weak.get");
v = Field (ar, offset);
if (v == 0) CAMLreturn (None_val);
elt = alloc (Wosize_val (v), Tag_val (v)); /* The GC may erase or move v. */
v = Field (ar, offset);
if (v == 0) CAMLreturn (None_val);
if (Tag_val (v) < No_scan_tag){
mlsize_t i;
for (i = 0; i < Wosize_val (v); i++){
Store_field (elt, i, Field (v, i));
}
}else{
memmove (Bp_val (elt), Bp_val (v), Bosize_val (v));
}
res = alloc_small (1, Some_tag);
Field (res, 0) = elt;
CAMLreturn (res);
}
value weak_check (value ar, value n) /* ML */ value weak_check (value ar, value n) /* ML */
{ {
mlsize_t offset = Long_val (n) + 1; mlsize_t offset = Long_val (n) + 1;
Assert (Is_in_heap (ar)); Assert (Is_in_heap (ar));
if (offset < 1 || offset >= Wosize_val (ar)) invalid_argument ("Weak.get"); if (offset < 1 || offset >= Wosize_val (ar)) invalid_argument ("Weak.get");
return Val_bool (Field (ar, offset) != 0); return Val_bool (Field (ar, offset) != 0);
} }