Skip to content

Commit bfb2d9e

Browse files
committed
fixup: apply code review
1 parent 39c06bb commit bfb2d9e

File tree

1 file changed

+60
-70
lines changed

1 file changed

+60
-70
lines changed

erts/emulator/beam/erl_gc.c

Lines changed: 60 additions & 70 deletions
Original file line numberDiff line numberDiff line change
@@ -3839,63 +3839,50 @@ erts_max_heap_size(Eterm arg, Uint *max_heap_size, Uint *max_heap_flags)
38393839
return 1;
38403840
}
38413841

3842-
typedef struct debug_binary {
3842+
typedef struct binary_range_info {
38433843
BinRef *bin_ref;
3844+
/* pairs of start and end offsets for each reference to the binary */
38443845
ErtsDynamicWStack ws;
3845-
} DebugBinary;
3846+
} BinaryRangeInfo;
38463847

3847-
static void gather_binaries(DebugBinary *bins, Uint count, Eterm *start, Eterm *stop) {
3848+
static void gather_binaries(BinaryRangeInfo *range_infos, const Uint count,
3849+
const Eterm *start, const Eterm *stop) {
38483850
Eterm* tp = start;
38493851
while (tp < stop) {
38503852
Eterm val = *tp++;
38513853

3852-
switch (primary_tag(val)) {
3853-
case TAG_PRIMARY_IMMED1:
3854-
case TAG_PRIMARY_LIST:
3855-
case TAG_PRIMARY_BOXED:
3856-
break;
3857-
case TAG_PRIMARY_HEADER:
3858-
if (header_is_transparent(val)) {
3859-
continue;
3860-
}
3861-
switch (thing_subtag(val)) {
3862-
case SUB_BITS_SUBTAG:
3863-
{
3864-
const ErlSubBits *sb = (ErlSubBits*)(tp-1);
3865-
const BinRef *underlying = (BinRef*)boxed_val(sb->orig);
3866-
if (thing_subtag(underlying->thing_word) != HEAP_BITS_SUBTAG) {
3867-
for (Uint i = 0; i < count; i++) {
3868-
DebugBinary* b = &bins[i];
3869-
if (b->bin_ref == underlying) {
3870-
WSTACK_PUSH2(b->ws.ws, sb->start, sb->end);
3871-
break;
3872-
}
3854+
if (primary_tag(val) == TAG_PRIMARY_HEADER &&
3855+
!header_is_transparent(val)) {
3856+
3857+
if (thing_subtag(val) == SUB_BITS_SUBTAG) {
3858+
const ErlSubBits *sb = (ErlSubBits*)(tp-1);
3859+
const BinRef *underlying = (BinRef*)boxed_val(sb->orig);
3860+
if (thing_subtag(underlying->thing_word) != HEAP_BITS_SUBTAG) {
3861+
for (Uint i = 0; i < count; i++) {
3862+
BinaryRangeInfo* info = &range_infos[i];
3863+
if (info->bin_ref == underlying) {
3864+
WSTACK_PUSH2(info->ws.ws, sb->start, sb->end);
3865+
break;
38733866
}
38743867
}
38753868
}
3876-
ERTS_FALLTHROUGH();
3877-
default:
3878-
{
3879-
tp += header_arity(val);
3880-
}
3881-
break;
38823869
}
3883-
break;
3870+
tp += header_arity(val);
38843871
}
38853872
}
38863873
}
38873874

38883875
Eterm
38893876
erts_gather_binaries(ErtsHeapFactory *hfact, Process *rp) {
3890-
#define PSTACK_TYPE DebugBinary
3891-
PSTACK_DECLARE(binaries, 16);
3877+
#define PSTACK_TYPE BinaryRangeInfo
3878+
PSTACK_DECLARE(range_infos, 16);
38923879

38933880
union erl_off_heap_ptr u;
38943881
Eterm res = NIL;
38953882
Eterm tuple;
38963883
union erts_tmp_aligned_offheap tmp;
38973884
Uint binaries_count;
3898-
DebugBinary* binariesp;
3885+
BinaryRangeInfo* range_infosp;
38993886

39003887
ErlHeapFragment* bp;
39013888
ErtsMessage* mp;
@@ -3906,32 +3893,34 @@ erts_gather_binaries(ErtsHeapFactory *hfact, Process *rp) {
39063893
for (u.hdr = MSO(rp).first; u.hdr; u.hdr = u.hdr->next) {
39073894
erts_align_offheap(&u, &tmp);
39083895
if (u.hdr->thing_word == HEADER_BIN_REF) {
3909-
DebugBinary* bin = PSTACK_PUSH(binaries);
3910-
bin->bin_ref = u.br;
3911-
WSTACK_INIT(&bin->ws, ERTS_ALC_T_ESTACK);
3896+
BinaryRangeInfo* info = PSTACK_PUSH(range_infos);
3897+
info->bin_ref = u.br;
3898+
WSTACK_INIT(&info->ws, ERTS_ALC_T_ESTACK);
39123899
}
39133900
}
39143901

39153902
for (u.hdr = rp->wrt_bins; u.hdr; u.hdr = u.hdr->next) {
39163903
erts_align_offheap(&u, &tmp);
39173904
if (u.hdr->thing_word == HEADER_BIN_REF) {
3918-
DebugBinary* bin = PSTACK_PUSH(binaries);
3919-
bin->bin_ref = u.br;
3920-
WSTACK_INIT(&bin->ws, ERTS_ALC_T_ESTACK);
3905+
BinaryRangeInfo* info = PSTACK_PUSH(range_infos);
3906+
info->bin_ref = u.br;
3907+
WSTACK_INIT(&info->ws, ERTS_ALC_T_ESTACK);
39213908
}
39223909
}
3923-
binariesp = (DebugBinary*)binaries.pstart;
3924-
binaries_count = PSTACK_COUNT(binaries);
3910+
3911+
range_infosp = (BinaryRangeInfo*)range_infos.pstart;
3912+
binaries_count = PSTACK_COUNT(range_infos);
39253913

39263914
if (rp->abandoned_heap) {
39273915
heap = get_orig_heap(rp, &htop, NULL);
3928-
gather_binaries(binariesp, binaries_count, heap, htop);
3916+
gather_binaries(range_infosp, binaries_count, heap, htop);
39293917
}
39303918

3931-
if (OLD_HEAP(rp))
3932-
gather_binaries(binariesp, binaries_count, OLD_HEAP(rp), OLD_HTOP(rp) /*OLD_HEND(p)*/);
3919+
if (OLD_HEAP(rp)) {
3920+
gather_binaries(range_infosp, binaries_count, OLD_HEAP(rp), OLD_HTOP(rp) /*OLD_HEND(p)*/);
3921+
}
39333922

3934-
gather_binaries(binariesp, binaries_count, HEAP_START(rp), HEAP_TOP(rp));
3923+
gather_binaries(range_infosp, binaries_count, HEAP_START(rp), HEAP_TOP(rp));
39353924

39363925
mp = rp->msg_frag;
39373926
bp = rp->mbuf;
@@ -3947,19 +3936,19 @@ erts_gather_binaries(ErtsHeapFactory *hfact, Process *rp) {
39473936
search_heap_frags:
39483937

39493938
while (bp) {
3950-
gather_binaries(binariesp, binaries_count,
3939+
gather_binaries(range_infosp, binaries_count,
39513940
bp->mem, bp->mem + bp->used_size);
39523941
bp = bp->next;
39533942
}
39543943
}
39553944

39563945
for (Uint i = 0; i < binaries_count; i++) {
3957-
DebugBinary b = binariesp[i];
3946+
BinaryRangeInfo info = range_infosp[i];
39583947
sz += 2 /* cons */ + 6 /* tuple (ptr, sz, refc, binary, subs) */;
3959-
erts_bld_uword(NULL, &sz, (UWord) b.bin_ref->val);
3960-
erts_bld_uint(NULL, &sz, b.bin_ref->val->orig_size);
3948+
erts_bld_uword(NULL, &sz, (UWord) info.bin_ref->val);
3949+
erts_bld_uint(NULL, &sz, info.bin_ref->val->orig_size);
39613950
sz += ERL_REFC_BITS_SIZE;
3962-
for (UWord *bits = b.ws.ws.wstart; bits < b.ws.ws.wsp; bits += 2) {
3951+
for (UWord *bits = info.ws.ws.wstart; bits < info.ws.ws.wsp; bits += 2) {
39633952
sz += 2 /* cons */ + 3 /* tuple*/;
39643953
erts_bld_uword(NULL, &sz, bits[0]);
39653954
erts_bld_uword(NULL, &sz, bits[1]);
@@ -3969,38 +3958,39 @@ erts_gather_binaries(ErtsHeapFactory *hfact, Process *rp) {
39693958
hp = erts_produce_heap(hfact, sz, 2);
39703959

39713960
for (Uint i = 0; i < binaries_count; i++) {
3972-
DebugBinary b = binariesp[i];
3973-
Eterm bitslist = NIL;
3974-
Eterm val = erts_bld_uword(&hp, NULL, (UWord)b.bin_ref->val);
3975-
Eterm orig_size = erts_bld_uint(&hp, NULL, b.bin_ref->val->orig_size);
3961+
const BinaryRangeInfo *info = &range_infosp[i];
3962+
Eterm range_list = NIL;
3963+
Eterm val = erts_bld_uword(&hp, NULL, (UWord)info->bin_ref->val);
3964+
Eterm orig_size = erts_bld_uint(&hp, NULL, info->bin_ref->val->orig_size);
39763965
Eterm bitstring;
3977-
for (UWord *bits = b.ws.ws.wstart; bits < b.ws.ws.wsp; bits += 2) {
3978-
Eterm offset = erts_bld_uword(&hp, NULL, bits[0]);
3979-
Eterm size = erts_bld_uword(&hp, NULL, bits[1]);
3980-
Eterm tuple = TUPLE2(hp, offset, size);
3966+
Eterm refc = make_small(erts_refc_read(&info->bin_ref->val->intern.refc, 1));
3967+
for (UWord *range_infos = info->ws.ws.wstart; range_infos < info->ws.ws.wsp; range_infos += 2) {
3968+
Eterm start = erts_bld_uword(&hp, NULL, range_infos[0]);
3969+
Eterm end = erts_bld_uword(&hp, NULL, range_infos[1]);
3970+
Eterm tuple = TUPLE2(hp, start, end);
39813971
hp += 3;
3982-
bitslist = CONS(hp, tuple, bitslist);
3972+
range_list = CONS(hp, tuple, range_list);
39833973
hp += 2;
39843974
}
3985-
erts_refc_inc(&b.bin_ref->val->intern.refc, 1);
3975+
WSTACK_DESTROY(info->ws.ws);
3976+
3977+
erts_refc_inc(&info->bin_ref->val->intern.refc, 1);
39863978
bitstring = erts_wrap_refc_bitstring(
39873979
&hfact->off_heap->first,
39883980
&hfact->off_heap->overhead,
3989-
&hp, b.bin_ref->val, (byte*)b.bin_ref->val->orig_bytes,
3990-
0, b.bin_ref->val->orig_size * 8);
3991-
WSTACK_DESTROY(b.ws.ws);
3992-
tuple = TUPLE5(hp, val,
3993-
orig_size,
3994-
/* We subtract the bump we did above when copying the binary */
3995-
make_small(erts_refc_read(&b.bin_ref->val->intern.refc, 1) - 1),
3996-
bitstring, bitslist);
3981+
&hp,
3982+
info->bin_ref->val,
3983+
(byte*)info->bin_ref->val->orig_bytes,
3984+
0,
3985+
NBITS(info->bin_ref->val->orig_size));
3986+
tuple = TUPLE5(hp, val, orig_size, refc, bitstring, range_list);
39973987
hp += 6;
39983988
res = CONS(hp, tuple, res);
39993989
hp += 2;
40003990

40013991
}
40023992

4003-
PSTACK_DESTROY(binaries);
3993+
PSTACK_DESTROY(range_infos);
40043994
#undef PSTACK_TYPE
40053995

40063996
return res;

0 commit comments

Comments
 (0)