File 3571-erts-Remove-some-process-VHEAP-macros.patch of Package erlang
From 443b37b28e6f5baa6dbee053206fa0328157cbc6 Mon Sep 17 00:00:00 2001
From: Sverker Eriksson <sverker@erlang.org>
Date: Thu, 18 Aug 2022 16:10:07 +0200
Subject: [PATCH 1/3] erts: Remove some process VHEAP macros
---
erts/emulator/beam/break.c | 8 +++----
erts/emulator/beam/emu/bs_instrs.tab | 2 +-
erts/emulator/beam/erl_bif_info.c | 6 ++---
erts/emulator/beam/erl_bits.c | 2 +-
erts/emulator/beam/erl_gc.c | 27 +++++++++++-----------
erts/emulator/beam/erl_process.h | 5 ----
erts/emulator/beam/external.c | 4 ++--
erts/emulator/beam/jit/beam_jit_common.cpp | 2 +-
8 files changed, 26 insertions(+), 30 deletions(-)
diff --git a/erts/emulator/beam/break.c b/erts/emulator/beam/break.c
index b19d9e4994..9efc797481 100644
--- a/erts/emulator/beam/break.c
+++ b/erts/emulator/beam/break.c
@@ -401,12 +401,12 @@ print_process_info(fmtfn_t to, void *to_arg, Process *p, ErtsProcLocks orig_lock
erts_print(to, to_arg, "OldHeap unused: %bpu\n",
(OLD_HEAP(p) == NULL) ? 0 : (OLD_HEND(p) - OLD_HTOP(p)) );
erts_print(to, to_arg, "BinVHeap: %b64u\n", p->off_heap.overhead);
- erts_print(to, to_arg, "OldBinVHeap: %b64u\n", BIN_OLD_VHEAP(p));
+ erts_print(to, to_arg, "OldBinVHeap: %b64u\n", p->bin_old_vheap);
erts_print(to, to_arg, "BinVHeap unused: %b64u\n",
- BIN_VHEAP_SZ(p) - p->off_heap.overhead);
- if (BIN_OLD_VHEAP_SZ(p) >= BIN_OLD_VHEAP(p)) {
+ p->bin_vheap_sz - p->off_heap.overhead);
+ if (p->bin_old_vheap_sz >= p->bin_old_vheap) {
erts_print(to, to_arg, "OldBinVHeap unused: %b64u\n",
- BIN_OLD_VHEAP_SZ(p) - BIN_OLD_VHEAP(p));
+ p->bin_old_vheap_sz - p->bin_old_vheap);
} else {
erts_print(to, to_arg, "OldBinVHeap unused: overflow\n");
}
diff --git a/erts/emulator/beam/emu/bs_instrs.tab b/erts/emulator/beam/emu/bs_instrs.tab
index 2d915a1fbd..66427cf3bf 100644
--- a/erts/emulator/beam/emu/bs_instrs.tab
+++ b/erts/emulator/beam/emu/bs_instrs.tab
@@ -125,7 +125,7 @@ BS_GET_UNCHECKED_FIELD_SIZE(Bits, Unit, Fail, Dst) {
TEST_BIN_VHEAP(VNh, Nh, Live) {
Uint need = $Nh;
if ((E - HTOP < (need + S_RESERVED)) ||
- (MSO(c_p).overhead + $VNh >= BIN_VHEAP_SZ(c_p))) {
+ (MSO(c_p).overhead + $VNh >= c_p->bin_vheap_sz)) {
$GC_SWAPOUT();
PROCESS_MAIN_CHK_LOCKS(c_p);
FCALLS -= erts_garbage_collect_nobump(c_p, need, reg, $Live, FCALLS);
diff --git a/erts/emulator/beam/erl_bif_info.c b/erts/emulator/beam/erl_bif_info.c
index b7642f2212..a0abf8d50f 100644
--- a/erts/emulator/beam/erl_bif_info.c
+++ b/erts/emulator/beam/erl_bif_info.c
@@ -1866,9 +1866,9 @@ process_info_aux(Process *c_p,
case ERTS_PI_IX_MIN_BIN_VHEAP_SIZE: {
Uint hsz = 0;
- (void) erts_bld_uint(NULL, &hsz, MIN_VHEAP_SIZE(rp));
+ (void) erts_bld_uint(NULL, &hsz, rp->min_vheap_size);
hp = erts_produce_heap(hfact, hsz, reserve_size);
- res = erts_bld_uint(&hp, NULL, MIN_VHEAP_SIZE(rp));
+ res = erts_bld_uint(&hp, NULL, rp->min_vheap_size);
break;
}
@@ -1951,7 +1951,7 @@ process_info_aux(Process *c_p,
t = TUPLE2(hp, am_min_heap_size, make_small(MIN_HEAP_SIZE(rp))); hp += 3;
res = CONS(hp, t, res); hp += 2;
- t = TUPLE2(hp, am_min_bin_vheap_size, make_small(MIN_VHEAP_SIZE(rp))); hp += 3;
+ t = TUPLE2(hp, am_min_bin_vheap_size, make_small(rp->min_vheap_size)); hp += 3;
res = CONS(hp, t, res); hp += 2;
t = erts_max_heap_size_map(MAX_HEAP_SIZE_GET(rp), MAX_HEAP_SIZE_FLAGS_GET(rp), &hp, NULL);
diff --git a/erts/emulator/beam/erl_gc.c b/erts/emulator/beam/erl_gc.c
index 582f3c7485..88f09c7f7c 100644
--- a/erts/emulator/beam/erl_gc.c
+++ b/erts/emulator/beam/erl_gc.c
@@ -1421,7 +1421,7 @@ minor_collection(Process* p, ErlHeapFragment *live_hf_end,
if (OLD_HEAP(p) &&
((mature_size <= OLD_HEND(p) - OLD_HTOP(p)) &&
- ((BIN_OLD_VHEAP_SZ(p) > BIN_OLD_VHEAP(p))) ) ) {
+ ((p->bin_old_vheap_sz > p->bin_old_vheap)) ) ) {
Eterm *prev_old_htop;
Uint stack_size, size_after, adjust_size, need_after, new_sz, new_mature;
@@ -2940,7 +2940,7 @@ sweep_off_heap(Process *p, int fullsweep)
Uint oheap_sz = 0;
Uint64 bin_vheap = 0;
#ifdef DEBUG
- Uint64 orig_bin_old_vheap = BIN_OLD_VHEAP(p);
+ Uint64 orig_bin_old_vheap = p->bin_old_vheap;
int seen_mature = 0;
#endif
Uint shrink_ncandidates;
@@ -2976,7 +2976,7 @@ sweep_off_heap(Process *p, int fullsweep)
if (to_new_heap) {
bin_vheap += ptr->size / sizeof(Eterm);
} else {
- BIN_OLD_VHEAP(p) += ptr->size / sizeof(Eterm);
+ p->bin_old_vheap += ptr->size / sizeof(Eterm);
}
ASSERT(!(((ProcBin*)ptr)->flags & (PB_ACTIVE_WRITER|PB_IS_WRITABLE)));
break;
@@ -2990,7 +2990,7 @@ sweep_off_heap(Process *p, int fullsweep)
if (to_new_heap)
bin_vheap += size / sizeof(Eterm);
else
- BIN_OLD_VHEAP(p) += size / sizeof(Eterm); /* for binary gc (words)*/
+ p->bin_old_vheap += size / sizeof(Eterm); /* for binary gc (words)*/
/* fall through... */
}
default:
@@ -3056,7 +3056,7 @@ sweep_off_heap(Process *p, int fullsweep)
#ifdef DEBUG
if (fullsweep) {
ASSERT(ptr == NULL);
- ASSERT(BIN_OLD_VHEAP(p) == orig_bin_old_vheap);
+ ASSERT(p->bin_old_vheap == orig_bin_old_vheap);
}
else {
/* The rest of the list resides on the old heap and needs no
@@ -3104,7 +3104,7 @@ sweep_off_heap(Process *p, int fullsweep)
if (!on_old_heap) {
bin_vheap += pb->size / sizeof(Eterm);
} else {
- BIN_OLD_VHEAP(p) += pb->size / sizeof(Eterm);
+ p->bin_old_vheap += pb->size / sizeof(Eterm);
}
}
else {
@@ -3202,11 +3202,12 @@ sweep_off_heap(Process *p, int fullsweep)
}
if (fullsweep) {
- ASSERT(BIN_OLD_VHEAP(p) == orig_bin_old_vheap);
- BIN_OLD_VHEAP(p) = 0;
- BIN_OLD_VHEAP_SZ(p) = next_vheap_size(p, MSO(p).overhead, BIN_OLD_VHEAP_SZ(p));
+ ASSERT(p->bin_old_vheap == orig_bin_old_vheap);
+ p->bin_old_vheap = 0;
+ p->bin_old_vheap_sz = next_vheap_size(p, MSO(p).overhead,
+ p->bin_old_vheap_sz);
}
- BIN_VHEAP_SZ(p) = next_vheap_size(p, bin_vheap, BIN_VHEAP_SZ(p));
+ p->bin_vheap_sz = next_vheap_size(p, bin_vheap, p->bin_vheap_sz);
MSO(p).overhead = bin_vheap;
}
@@ -3634,9 +3635,9 @@ erts_process_gc_info(Process *p, Uint *sizep, Eterm **hpp,
OLD_HEAP(p) ? OLD_HTOP(p) - OLD_HEAP(p) : 0,
HEAP_TOP(p) - HEAP_START(p),
MSO(p).overhead,
- BIN_VHEAP_SZ(p),
- BIN_OLD_VHEAP(p),
- BIN_OLD_VHEAP_SZ(p)
+ p->bin_vheap_sz,
+ p->bin_old_vheap,
+ p->bin_old_vheap_sz
};
Eterm res = THE_NON_VALUE;
diff --git a/erts/emulator/beam/erl_process.h b/erts/emulator/beam/erl_process.h
index bd281a2f65..36b483acf4 100644
--- a/erts/emulator/beam/erl_process.h
+++ b/erts/emulator/beam/erl_process.h
@@ -993,11 +993,6 @@ typedef struct ErtsProcSysTaskQs_ ErtsProcSysTaskQs;
# define MSO(p) (p)->off_heap
# define MIN_HEAP_SIZE(p) (p)->min_heap_size
-# define MIN_VHEAP_SIZE(p) (p)->min_vheap_size
-# define BIN_VHEAP_SZ(p) (p)->bin_vheap_sz
-# define BIN_OLD_VHEAP_SZ(p) (p)->bin_old_vheap_sz
-# define BIN_OLD_VHEAP(p) (p)->bin_old_vheap
-
# define MAX_HEAP_SIZE_GET(p) ((p)->max_heap_size >> 2)
# define MAX_HEAP_SIZE_SET(p, sz) ((p)->max_heap_size = ((sz) << 2) | \
MAX_HEAP_SIZE_FLAGS_GET(p))
diff --git a/erts/emulator/beam/external.c b/erts/emulator/beam/external.c
index d2bbaf607a..fe39809e34 100644
--- a/erts/emulator/beam/external.c
+++ b/erts/emulator/beam/external.c
@@ -1339,7 +1339,7 @@ static BIF_RETTYPE term_to_binary_trap_1(BIF_ALIST_1)
0, 0,bin, 0, ~((Uint) 0));
if (is_non_value(res)) {
if (erts_set_gc_state(BIF_P, 1)
- || MSO(BIF_P).overhead > BIN_VHEAP_SZ(BIF_P)) {
+ || MSO(BIF_P).overhead > BIF_P->bin_vheap_sz) {
ERTS_VBUMP_ALL_REDS(BIF_P);
}
if (Opts == am_undefined)
@@ -1354,7 +1354,7 @@ static BIF_RETTYPE term_to_binary_trap_1(BIF_ALIST_1)
BIF_TRAP1(&term_to_binary_trap_export,BIF_P,res);
} else {
if (erts_set_gc_state(BIF_P, 1)
- || MSO(BIF_P).overhead > BIN_VHEAP_SZ(BIF_P))
+ || MSO(BIF_P).overhead > BIF_P->bin_vheap_sz)
ERTS_BIF_YIELD_RETURN(BIF_P, res);
else
BIF_RET(res);
diff --git a/erts/emulator/beam/jit/beam_jit_common.cpp b/erts/emulator/beam/jit/beam_jit_common.cpp
index ab90d1d242..fdd918631f 100644
--- a/erts/emulator/beam/jit/beam_jit_common.cpp
+++ b/erts/emulator/beam/jit/beam_jit_common.cpp
@@ -690,7 +690,7 @@ static void test_bin_vheap(Process *c_p,
int need = Nh;
if (c_p->stop - c_p->htop < (need + S_RESERVED) ||
- MSO(c_p).overhead + VNh >= BIN_VHEAP_SZ(c_p)) {
+ MSO(c_p).overhead + VNh >= c_p->bin_vheap_sz) {
c_p->fcalls -=
erts_garbage_collect_nobump(c_p, need, reg, Live, c_p->fcalls);
}
--
2.35.3