Skip to content

Commit

Permalink
The heap_consistency_check to reproduce hipe bug
Browse files Browse the repository at this point in the history
  • Loading branch information
sverker committed Mar 22, 2011
1 parent 9e675cd commit 9ce8b21
Show file tree
Hide file tree
Showing 3 changed files with 203 additions and 1 deletion.
22 changes: 22 additions & 0 deletions erts/emulator/beam/erl_bif_info.c
Original file line number Diff line number Diff line change
Expand Up @@ -3127,12 +3127,34 @@ BIF_RETTYPE error_logger_warning_map_0(BIF_ALIST_0)

static erts_smp_atomic_t available_internal_state;

static void sverk_break(void)
{
}

BIF_RETTYPE erts_debug_get_internal_state_1(BIF_ALIST_1)
{
/*
* NOTE: Only supposed to be used for testing, and debugging.
*/
Eterm sverk = BIF_ARG_1, sverk_tail;
if (is_list(BIF_ARG_1)) {
sverk = CAR(list_val(BIF_ARG_1));
sverk_tail = CDR(list_val(BIF_ARG_1));
}
if (ERTS_IS_ATOM_STR("heap_consistency_check", sverk)) {
extern void heap_consistency_check(Process*);
if (is_list(BIF_ARG_1)) {
erts_fprintf(stderr, "SVERK: %T\r\n", BIF_ARG_1);
}
heap_consistency_check(BIF_P);
if (is_list(BIF_ARG_1) && is_list(sverk_tail)
&& ERTS_IS_ATOM_STR("break",CAR(list_val(sverk_tail)))) {
erts_fprintf(stderr, "SVERK: calling break point\r\n");
sverk_break();
}

BIF_RET(am_ok);
}
if (!erts_smp_atomic_read(&available_internal_state)) {
BIF_ERROR(BIF_P, EXC_UNDEF);
}
Expand Down
139 changes: 139 additions & 0 deletions erts/emulator/beam/erl_gc.c
Original file line number Diff line number Diff line change
Expand Up @@ -2519,3 +2519,142 @@ erts_check_off_heap(Process *p)
}

#endif

//#ifdef DEBUG
static void heap_consistency_check_fail(Eterm term)
{
erts_fprintf(stderr, "heap_consistency_check FAILED(%u): %T\r\n",
(int)getpid() + (int)pthread_self(), term);
abort();
}


static void heap_consistency_check_ptr_old(Process* p, Eterm* ptr, Eterm term)
{
unsigned i;
if (in_area(ptr, p->old_heap, (p->old_htop - p->old_heap)*sizeof(Eterm))) {
return;
}

for (i = 0; i < module_code_size(); i++) {
Module* mod = module_code(i);
if (mod != NULL) {
Eterm* literals;
Uint lit_sz;

if (mod->code_length != 0) {
literals = (Eterm *) mod->code[MI_LITERALS_START];
lit_sz = (Eterm *) mod->code[MI_LITERALS_END] - literals;
if (in_area(ptr, literals, lit_sz*sizeof(Eterm))) return;
}
if (mod->old_code_length != 0) {
literals = (Eterm *) mod->old_code[MI_LITERALS_START];
lit_sz = (Eterm *) mod->old_code[MI_LITERALS_END] - literals;
if (in_area(ptr, literals, lit_sz*sizeof(Eterm))) return;
}
}
}
#ifdef HIPE
{
extern int hipe_is_constant(Eterm*); /* hipe_bif0.c */
if (hipe_is_constant(ptr)) {
return;
}
}
#endif
heap_consistency_check_fail(term);
}

static void heap_consistency_check_ptr_new(Process* p, Eterm* ptr, Eterm term)
{
if (in_area(ptr, p->heap, (p->htop - p->heap)*sizeof(Eterm))) {
return;
}
heap_consistency_check_ptr_old(p, ptr, term);
}

void heap_consistency_check(Process* p); // SVERK

void heap_consistency_check(Process* p)
{
Eterm* hp;
Eterm* htop;
const unsigned hist_len = 16;
Eterm* hp_hist[hist_len];
unsigned ix = 0;

ErtsGcQuickSanityCheck(p);

/* New heap */
htop = p->htop;
hp = p->heap;
while (hp < htop) {
Eterm* ptr;
Eterm val;

hp_hist[(ix++) % hist_len] = hp;
val = *hp;
switch (primary_tag(val)) {
case TAG_PRIMARY_BOXED:
ptr = boxed_val(val);
heap_consistency_check_ptr_new(p, ptr, val);
hp++;
break;
case TAG_PRIMARY_LIST:
ptr = list_val(val);
heap_consistency_check_ptr_new(p, ptr, val);
hp++;
break;
case TAG_PRIMARY_HEADER:
if (header_is_thing(val)) {
Eterm* next_hp = hp + 1 + thing_arityval(val);
if (next_hp > htop) {
heap_consistency_check_fail(am_atom_put("thingy_new",10));
}
hp = next_hp;
}
else hp++;
break;
default:
hp++;
}
}

/* Old heap */
htop = p->old_htop;
hp = p->old_heap;
ix = 0;
while (hp < htop) {
Eterm* ptr;
Eterm val;

hp_hist[(ix++) % hist_len] = hp;
val = *hp;
switch (primary_tag(val)) {
case TAG_PRIMARY_BOXED:
ptr = boxed_val(val);
heap_consistency_check_ptr_old(p, ptr, val);
hp++;
break;
case TAG_PRIMARY_LIST:
ptr = list_val(val);
heap_consistency_check_ptr_old(p, ptr, val);
hp++;
break;
case TAG_PRIMARY_HEADER:
if (header_is_thing(val)) {
Eterm* next_hp = hp + 1 + thing_arityval(val);
if (next_hp > htop) {
heap_consistency_check_fail(am_atom_put("thingy_old",10));
}
hp = next_hp;
}
else hp++;
break;
default:
hp++;
}
}

}
//#endif /* DEBUG */
43 changes: 42 additions & 1 deletion erts/emulator/hipe/hipe_bif0.c
Original file line number Diff line number Diff line change
Expand Up @@ -292,7 +292,7 @@ BIF_RETTYPE hipe_bifs_bitarray_sub_2(BIF_ALIST_2)
* BIFs for SML-like mutable arrays and reference cells.
* For now, limited to containing immediate data.
*/
#if 1 /* use bignums as carriers, easier on the gc */
#if 1
#define make_array_header(sz) make_pos_bignum_header((sz))
#define array_header_arity(h) header_arity((h))
#define make_array(hp) make_big((hp))
Expand Down Expand Up @@ -505,6 +505,9 @@ BIF_RETTYPE hipe_bifs_constants_size_0(BIF_ALIST_0)
*/
struct const_term {
HashBucket bucket;
//#ifdef DEBUG
Eterm* mem_end;
//#endif
Eterm val; /* tagged pointer to mem[0] */
Eterm mem[1]; /* variable size */
};
Expand Down Expand Up @@ -534,6 +537,9 @@ static void *const_term_alloc(void *tmpl)
size = size_object(obj);

p = (struct const_term*)constants_alloc(size + (offsetof(struct const_term, mem)/sizeof(Eterm)));
//#ifdef DEBUG
p->mem_end = p->mem + size;
//#endif

/* I have absolutely no idea if having a private 'off_heap'
works or not. _Some_ off_heap object is required for
Expand Down Expand Up @@ -573,6 +579,38 @@ BIF_RETTYPE hipe_bifs_merge_term_1(BIF_ALIST_1)
BIF_RET(val);
}

//#ifdef DEBUG
struct hipe_is_constant_iter
{
Eterm* termp;
int was_found;
};

static void hipe_is_constant_callback(void* bucket, void* arg)
{
struct const_term* ct = (struct const_term*)bucket;
struct hipe_is_constant_iter* iter = (struct hipe_is_constant_iter*)arg;
if (ct->mem <= iter->termp && iter->termp < ct->mem_end) {
iter->was_found = 1;
}
}

int hipe_is_constant(Eterm* termp)
{
int is1, is2;
struct hipe_is_constant_iter iter;
iter.termp = termp;
iter.was_found = 0;
hash_foreach(&const_term_table, hipe_is_constant_callback, &iter);
is1 = iter.was_found;

is2 = (hipe_constants_start <= termp && termp < hipe_constants_next);
ASSERT(is1 == is2);

return is1;
}
//#endif /* DEBUG */

struct mfa {
Eterm mod;
Eterm fun;
Expand Down Expand Up @@ -1849,8 +1887,10 @@ BIF_RETTYPE hipe_bifs_check_crc_1(BIF_ALIST_1)

if (!term_to_Uint(BIF_ARG_1, &crc))
BIF_ERROR(BIF_P, BADARG);

if (crc == HIPE_SYSTEM_CRC)
BIF_RET(am_true);

BIF_RET(am_false);
}

Expand All @@ -1861,6 +1901,7 @@ BIF_RETTYPE hipe_bifs_system_crc_1(BIF_ALIST_1)
if (!term_to_Uint(BIF_ARG_1, &crc))
BIF_ERROR(BIF_P, BADARG);
crc ^= (HIPE_SYSTEM_CRC ^ HIPE_LITERALS_CRC);

BIF_RET(Uint_to_term(crc, BIF_P));
}

Expand Down

0 comments on commit 9ce8b21

Please sign in to comment.