Sign Up
Log In
Log In
or
Sign Up
Places
All Projects
Status Monitor
Collapse sidebar
home:Ledest:erlang:26
erlang
1261-emulator-Remove-vestiges-of-special-handli...
Overview
Repositories
Revisions
Requests
Users
Attributes
Meta
File 1261-emulator-Remove-vestiges-of-special-handling-of-x-0.patch of Package erlang
From f53c6f4fc8da66fadd90f6a2d85b317cc52641e8 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Bj=C3=B6rn=20Gustavsson?= <bjorn@erlang.org> Date: Sat, 10 Jun 2023 13:21:55 +0200 Subject: [PATCH] emulator: Remove vestiges of special handling of x(0) In the BEAM emulator, X register 0 (`x(0)`) used to be specially handled by the macro `r(0)` so that it could be placed in a CPU register. That made sense for platforms with many registers such as Sparc and PowerPC. For the register-starved x86_64 platform it is not possible to allocate a CPU register for `x(0)`. Therefore, in 1f996cc46a8c93 (part of Erlang/OTP 19), the special handling of `x(0)` was removed. Removing that special case simplified the code in many places. Get rid of the vestiges of the special handling of `x(0)`. While at it, also re-introduce the `REG_xregs` attribute for the variable holding the pointer to the X registers. --- erts/emulator/beam/beam_common.h | 1 - erts/emulator/beam/emu/beam_emu.c | 8 ++++---- erts/emulator/beam/emu/bif_instrs.tab | 22 +++++++++++----------- erts/emulator/beam/emu/bs_instrs.tab | 2 +- erts/emulator/beam/emu/instrs.tab | 16 ++++++++-------- erts/emulator/beam/emu/msg_instrs.tab | 2 +- erts/emulator/beam/emu/trace_instrs.tab | 6 +++--- erts/emulator/utils/beam_makeops | 2 +- 8 files changed, 29 insertions(+), 30 deletions(-) diff --git a/erts/emulator/beam/beam_common.h b/erts/emulator/beam/beam_common.h index ee7a41c9b8..3c93d580a6 100644 --- a/erts/emulator/beam/beam_common.h +++ b/erts/emulator/beam/beam_common.h @@ -111,7 +111,6 @@ do { \ #define x(N) reg[N] #define y(N) E[N] -#define r(N) x(N) #define Q(N) (N*sizeof(Eterm *)) #define l(N) (freg[N].fd) diff --git a/erts/emulator/beam/emu/beam_emu.c b/erts/emulator/beam/emu/beam_emu.c index 0c91c1ec83..c2081ab3d0 100644 --- a/erts/emulator/beam/emu/beam_emu.c +++ b/erts/emulator/beam/emu/beam_emu.c @@ -266,10 +266,10 @@ void process_main(ErtsSchedulerData *esdp) ERTS_DECLARE_DUMMY(Eterm pid); #endif - /* Pointer to X registers: x(1)..x(N); reg[0] is used when doing GC, - * in all other cases x0 is used. + /* + * Pointer to X registers: x(0)..x(N). */ - register Eterm* reg = NULL; + register Eterm* reg REG_xregs = NULL; /* * Top of heap (next free location); grows upwards. @@ -552,7 +552,7 @@ void process_main(ErtsSchedulerData *esdp) if (I == 0) { goto do_schedule; } else { - ASSERT(!is_value(r(0))); + ASSERT(!is_value(x(0))); SWAPIN; Goto(*I); } diff --git a/erts/emulator/beam/emu/bif_instrs.tab b/erts/emulator/beam/emu/bif_instrs.tab index d1ec68168a..ef26fd4756 100644 --- a/erts/emulator/beam/emu/bif_instrs.tab +++ b/erts/emulator/beam/emu/bif_instrs.tab @@ -281,8 +281,8 @@ call_light_bif(Bif, Exp) { } ERTS_MSACC_SET_STATE_CACHED_M_X(ERTS_MSACC_STATE_EMULATOR); if (ERTS_LIKELY(is_value(result))) { - r(0) = result; - CHECK_TERM(r(0)); + x(0) = result; + CHECK_TERM(x(0)); $NEXT0(); } else if (c_p->freason == TRAP) { /* @@ -385,8 +385,8 @@ call_light_bif_only(Bif, Exp) { /* * Success. Store the result and return to the caller. */ - r(0) = result; - CHECK_TERM(r(0)); + x(0) = result; + CHECK_TERM(x(0)); $return(); } else if (c_p->freason == TRAP) { /* @@ -426,15 +426,15 @@ send() { PRE_BIF_SWAPOUT(c_p); c_p->fcalls = FCALLS - 1; - result = erl_send(c_p, r(0), x(1)); + result = erl_send(c_p, x(0), x(1)); ERTS_VERIFY_UNUSED_TEMP_ALLOC(c_p); ERTS_REQ_PROC_MAIN_LOCK(c_p); PROCESS_MAIN_CHK_LOCKS(c_p); HTOP = HEAP_TOP(c_p); FCALLS = c_p->fcalls; if (ERTS_LIKELY(is_value(result))) { - r(0) = result; - CHECK_TERM(r(0)); + x(0) = result; + CHECK_TERM(x(0)); } else if (c_p->freason == TRAP) { $SAVE_CONTINUATION_POINTER($NEXT_INSTRUCTION); SET_I(c_p->i); @@ -605,8 +605,8 @@ nif_bif.epilogue() { FCALLS = c_p->fcalls; ERTS_DBG_CHK_REDS(c_p, FCALLS); if (ERTS_LIKELY(is_value(nif_bif_result))) { - r(0) = nif_bif_result; - CHECK_TERM(r(0)); + x(0) = nif_bif_result; + CHECK_TERM(x(0)); $RETURN(); Goto(*I); } else if (c_p->freason == TRAP) { @@ -632,13 +632,13 @@ i_load_nif() { Eterm result; PRE_BIF_SWAPOUT(c_p); - result = erts_load_nif(c_p, I, r(0), r(1)); + result = erts_load_nif(c_p, I, x(0), x(1)); erts_release_code_mod_permission(); ERTS_REQ_PROC_MAIN_LOCK(c_p); SWAPIN; if (ERTS_LIKELY(is_value(result))) { - r(0) = result; + x(0) = result; $NEXT0(); } else { static ErtsCodeMFA mfa = {am_erlang, am_load_nif, 2}; diff --git a/erts/emulator/beam/emu/bs_instrs.tab b/erts/emulator/beam/emu/bs_instrs.tab index a42c2eb331..9a1360c26e 100644 --- a/erts/emulator/beam/emu/bs_instrs.tab +++ b/erts/emulator/beam/emu/bs_instrs.tab @@ -738,7 +738,7 @@ i_bs_private_append(Fail, Unit, Size, Src, Dst) { bs_init_writable() { HEAVY_SWAPOUT; - r(0) = erts_bs_init_writable(c_p, r(0)); + x(0) = erts_bs_init_writable(c_p, x(0)); HEAVY_SWAPIN; } diff --git a/erts/emulator/beam/emu/instrs.tab b/erts/emulator/beam/emu/instrs.tab index 88e6da9bf1..e675eadf99 100644 --- a/erts/emulator/beam/emu/instrs.tab +++ b/erts/emulator/beam/emu/instrs.tab @@ -311,7 +311,7 @@ apply_last(Arity, Deallocate) { APPLY_FUN(Next) { HEAVY_SWAPOUT; - $Next = apply_fun(c_p, r(0), x(1), reg); + $Next = apply_fun(c_p, x(0), x(1), reg); HEAVY_SWAPIN; if (ERTS_UNLIKELY(next == NULL)) { @@ -378,7 +378,7 @@ return() { //| -no_next DTRACE_RETURN_FROM_PC(c_p, I); $RETURN(); - CHECK_TERM(r(0)); + CHECK_TERM(x(0)); HEAP_SPACE_VERIFIED(0); $DISPATCH_RETURN(); @@ -1129,11 +1129,11 @@ catch_end(Y) { * x3 = Exception class */ $try_end($Y); - if (is_non_value(r(0))) { + if (is_non_value(x(0))) { ASSERT(c_p->fvalue == NIL); ASSERT(c_p->ftrace == NIL); if (x(3) == am_throw) { - r(0) = x(1); + x(0) = x(1); } else { if (x(3) == am_error) { SWAPOUT; @@ -1150,11 +1150,11 @@ catch_end(Y) { SWAPIN; $MAYBE_EXIT_AFTER_GC(); } - r(0) = TUPLE2(HTOP, am_EXIT, x(1)); + x(0) = TUPLE2(HTOP, am_EXIT, x(1)); HTOP += 3; } } - CHECK_TERM(r(0)); + CHECK_TERM(x(0)); } try_end(Y) { @@ -1164,10 +1164,10 @@ try_end(Y) { try_case(Y) { $try_end($Y); - ASSERT(is_non_value(r(0))); + ASSERT(is_non_value(x(0))); ASSERT(c_p->fvalue == NIL); ASSERT(c_p->ftrace == NIL); - r(0) = x(3); + x(0) = x(3); } try_case_end(Src) { diff --git a/erts/emulator/beam/emu/msg_instrs.tab b/erts/emulator/beam/emu/msg_instrs.tab index ef733ae80a..00c7291257 100644 --- a/erts/emulator/beam/emu/msg_instrs.tab +++ b/erts/emulator/beam/emu/msg_instrs.tab @@ -136,7 +136,7 @@ i_loop_rec(Dest) { ASSERT(msgp == erts_msgq_peek_msg(c_p)); ASSERT(ERTS_SIG_IS_INTERNAL_MSG(msgp)); - r(0) = ERL_MESSAGE_TERM(msgp); + x(0) = ERL_MESSAGE_TERM(msgp); } remove_message() { diff --git a/erts/emulator/beam/emu/trace_instrs.tab b/erts/emulator/beam/emu/trace_instrs.tab index 9b0b377ed7..14ac98a311 100644 --- a/erts/emulator/beam/emu/trace_instrs.tab +++ b/erts/emulator/beam/emu/trace_instrs.tab @@ -24,7 +24,7 @@ return_trace() { SWAPOUT; /* Needed for shared heap */ ERTS_UNREQ_PROC_MAIN_LOCK(c_p); - erts_trace_return(c_p, mfa, r(0), ERTS_TRACER_FROM_ETERM(E+2)/* tracer */); + erts_trace_return(c_p, mfa, x(0), ERTS_TRACER_FROM_ETERM(E+2)/* tracer */); ERTS_REQ_PROC_MAIN_LOCK(c_p); SWAPIN; E += 1 + BEAM_RETURN_TRACE_FRAME_SZ; @@ -135,10 +135,10 @@ i_perf_counter() { ts = erts_sys_perf_counter(); if (IS_SSMALL(ts)) { - r(0) = make_small((Sint)ts); + x(0) = make_small((Sint)ts); } else { $GC_TEST(0, ERTS_SINT64_HEAP_SIZE(ts), 0); - r(0) = make_big(HTOP); + x(0) = make_big(HTOP); #if defined(ARCH_32) if (ts >= (((Uint64) 1) << 32)) { *HTOP = make_pos_bignum_header(2); diff --git a/erts/emulator/utils/beam_makeops b/erts/emulator/utils/beam_makeops index 796fff7182..a3d18bfbe0 100755 --- a/erts/emulator/utils/beam_makeops +++ b/erts/emulator/utils/beam_makeops @@ -1728,7 +1728,7 @@ sub code_gen { last SWITCH; }; /r/ and do { - push(@f, "r(0)"); + push(@f, "x(0)"); last SWITCH; }; /[lxyS]/ and do { -- 2.35.3
Locations
Projects
Search
Status Monitor
Help
OpenBuildService.org
Documentation
API Documentation
Code of Conduct
Contact
Support
@OBShq
Terms
openSUSE Build Service is sponsored by
The Open Build Service is an
openSUSE project
.
Sign Up
Log In
Places
Places
All Projects
Status Monitor