File 1051-erts-Marginally-shrink-process-structure.patch of Package erlang

From cd7a62219173f205ad74f53800bdbf80abc8ac19 Mon Sep 17 00:00:00 2001
From: =?UTF-8?q?John=20H=C3=B6gberg?= <john@erlang.org>
Date: Fri, 12 May 2023 15:58:43 +0200
Subject: [PATCH] erts: Marginally shrink process structure

The process structure is now 32 bytes smaller on 64-bit platforms,
most of it was accomplished by reordering but some changes in
data sizes were made, hence the sweeping changes in the JIT.
---
 erts/emulator/beam/code_ix.h                  |  2 +-
 erts/emulator/beam/erl_bif_trace.c            |  4 +-
 erts/emulator/beam/erl_process.h              | 88 ++++++++++---------
 erts/emulator/beam/erl_ptab.h                 |  4 +-
 erts/emulator/beam/erl_trace.c                | 33 +++----
 erts/emulator/beam/erl_trace.h                |  8 +-
 erts/emulator/beam/jit/arm/beam_asm.hpp       | 42 ++++++---
 .../emulator/beam/jit/arm/beam_asm_global.cpp |  4 +-
 .../emulator/beam/jit/arm/beam_asm_module.cpp |  6 +-
 erts/emulator/beam/jit/arm/instr_bif.cpp      | 19 ++--
 erts/emulator/beam/jit/arm/instr_call.cpp     |  2 +-
 erts/emulator/beam/jit/arm/instr_common.cpp   |  8 +-
 erts/emulator/beam/jit/arm/instr_fun.cpp      | 10 +--
 .../beam/jit/arm/instr_guard_bifs.cpp         | 12 +--
 erts/emulator/beam/jit/arm/instr_msg.cpp      | 10 +--
 erts/emulator/beam/jit/arm/ops.tab            |  4 +-
 erts/emulator/beam/jit/arm/process_main.cpp   | 22 ++---
 erts/emulator/beam/jit/beam_jit_common.cpp    | 10 +--
 erts/emulator/beam/jit/beam_jit_common.hpp    | 10 +--
 erts/emulator/beam/jit/beam_jit_main.cpp      |  1 +
 erts/emulator/beam/jit/x86/beam_asm.hpp       |  6 +-
 .../emulator/beam/jit/x86/beam_asm_global.cpp |  4 +-
 .../emulator/beam/jit/x86/beam_asm_module.cpp |  6 +-
 erts/emulator/beam/jit/x86/instr_bif.cpp      | 27 +++---
 erts/emulator/beam/jit/x86/instr_call.cpp     |  4 +-
 erts/emulator/beam/jit/x86/instr_common.cpp   |  6 +-
 erts/emulator/beam/jit/x86/instr_msg.cpp      | 10 +--
 erts/emulator/beam/jit/x86/instr_trace.cpp    |  5 +-
 erts/emulator/beam/jit/x86/ops.tab            |  4 +-
 erts/emulator/beam/jit/x86/process_main.cpp   | 22 ++---
 30 files changed, 208 insertions(+), 185 deletions(-)

diff --git a/erts/emulator/beam/code_ix.h b/erts/emulator/beam/code_ix.h
index 54ceefcc9b..1c04721523 100644
--- a/erts/emulator/beam/code_ix.h
+++ b/erts/emulator/beam/code_ix.h
@@ -87,7 +87,7 @@ typedef unsigned ErtsCodeIndex;
 typedef struct ErtsCodeMFA_ {
     Eterm module;
     Eterm function;
-    Uint  arity;
+    byte arity;
 } ErtsCodeMFA;
 
 /*
diff --git a/erts/emulator/beam/erl_bif_trace.c b/erts/emulator/beam/erl_bif_trace.c
index 9f79607d97..9e6e14f6fd 100644
--- a/erts/emulator/beam/erl_bif_trace.c
+++ b/erts/emulator/beam/erl_bif_trace.c
@@ -837,7 +837,7 @@ Eterm trace_info_2(BIF_ALIST_2)
 }
 
 static Eterm
-build_trace_flags_term(Eterm **hpp, Uint *szp, Uint trace_flags)
+build_trace_flags_term(Eterm **hpp, Uint *szp, Uint32 trace_flags)
 {
 
 #define ERTS_TFLAG__(F, FN)                             \
@@ -955,7 +955,7 @@ static Eterm
 trace_info_pid(Process* p, Eterm pid_spec, Eterm key)
 {
     Eterm tracer;
-    Uint trace_flags = am_false;
+    Uint32 trace_flags = 0;
     Eterm* hp;
 
     if (pid_spec == am_new || pid_spec == am_new_processes) {
diff --git a/erts/emulator/beam/erl_process.h b/erts/emulator/beam/erl_process.h
index a0fe781bb1..e5975b952e 100644
--- a/erts/emulator/beam/erl_process.h
+++ b/erts/emulator/beam/erl_process.h
@@ -1007,11 +1007,11 @@ typedef struct ErtsProcSysTaskQs_ ErtsProcSysTaskQs;
 struct process {
     ErtsPTabElementCommon common; /* *Need* to be first in struct */
 
-    /* Place fields that are frequently used from loaded BEAMASM
-     * instructions near the beginning of this struct so that a
-     * shorter instruction can be used to access them.
-     */
+    /* Place fields that are frequently used from BEAMASM instructions near the
+     * beginning of this struct so that a shorter instruction can be used to
+     * access them. */
 
+    /* These are paired to exploit the STP instruction in the ARM JIT. */
     Eterm *htop;                /* Heap top */
     Eterm *stop;                /* Stack top */
 
@@ -1019,64 +1019,63 @@ struct process {
     Eterm *frame_pointer;       /* Frame pointer */
 #endif
 
-    Sint fcalls;		/* Number of reductions left to execute.
-				 * Only valid for the current process.
-				 */
-    Uint freason;		/* Reason for detected failure */
-    Eterm fvalue;		/* Exit & Throw value (failure reason) */
+    /* These are paired to exploit the STP instruction in the ARM JIT. */
+    Uint freason;               /* Reason for detected failure. */
+    Eterm fvalue;               /* Exit & Throw value (failure reason) */
+
+    Sint32 fcalls;              /* Number of reductions left to execute.
+                                 * Only valid for the current process while it
+                                 * is executing. */
+
+    Uint32 flags;               /* Trap exit, etc */
 
     /* End of frequently used fields by BEAMASM code. */
 
-    Eterm* heap;		/* Heap start */
-    Eterm* hend;		/* Heap end */
+    Uint32 rcount;              /* Suspend count */
+    byte schedule_count;        /* Times left to reschedule a low prio process */
+
+    /* Saved x registers. */
+    byte arity;                 /* Number of live argument registers (only
+                                 * valid when process is *not* running). */
+    byte max_arg_reg;           /* Maximum number of argument registers
+                                 * available. */
+    Eterm* arg_reg;             /* Pointer to argument registers. */
+    Eterm def_arg_reg[6];       /* Default array for argument registers. */
+
+    Eterm* heap;                /* Heap start */
+    Eterm* hend;                /* Heap end */
     Eterm* abandoned_heap;
-    Uint heap_sz;		/* Size of heap in words */
+    Uint heap_sz;               /* Size of heap in words */
     Uint min_heap_size;         /* Minimum size of heap (in words). */
     Uint min_vheap_size;        /* Minimum size of virtual heap (in words). */
     Uint max_heap_size;         /* Maximum size of heap (in words). */
 
-    /*
-     * Saved x registers.
-     */
-    Uint arity;			/* Number of live argument registers (only valid
-				 * when process is *not* running).
-				 */
-    Eterm* arg_reg;		/* Pointer to argument registers. */
-    unsigned max_arg_reg;	/* Maximum number of argument registers available. */
-    Eterm def_arg_reg[6];	/* Default array for argument registers. */
-
     ErtsCodePtr i;              /* Program counter. */
-    Sint catches;		/* Number of catches on stack */
-    Uint32 rcount;		/* suspend count */
-    int  schedule_count;	/* Times left to reschedule a low prio process */
-    Uint reds;			/* No of reductions for this process  */
-    Uint32 flags;		/* Trap exit, etc */
-    Eterm group_leader;		/* Pid in charge (can be boxed) */
-    Eterm ftrace;		/* Latest exception stack trace dump */
+    Sint catches;               /* Number of catches on stack */
+    Uint reds;                  /* No of reductions for this process  */
+    Eterm group_leader;         /* Pid in charge (can be boxed) */
+    Eterm ftrace;               /* Latest exception stack trace dump */
 
-    Process *next;		/* Pointer to next process in run queue */
+    Process *next;              /* Pointer to next process in run queue */
 
-    Sint64 uniq;                /* Used for process unique integer */
+    Sint64 uniq;                 /* Used for process unique integer */
     ErtsSignalPrivQueues sig_qs; /* Signal queues */
-    ErtsBifTimers *bif_timers;	/* Bif timers aiming at this process */
+    ErtsBifTimers *bif_timers;   /* Bif timers aiming at this process */
 
-    ProcDict  *dictionary;       /* Process dictionary, may be NULL */
+    ProcDict *dictionary;        /* Process dictionary, may be NULL */
 
     Uint seq_trace_clock;
     Uint seq_trace_lastcnt;
     Eterm seq_trace_token;	/* Sequential trace token (tuple size 5 see below) */
 
-#ifdef USE_VM_PROBES
-    Eterm dt_utag;              /* Place to store the dynamic trace user tag */
-    Uint dt_utag_flags;         /* flag field for the dt_utag */
-#endif
     union {
         struct process *real_proc;
-	void *terminate;
-	ErtsCodeMFA initial;	/* Initial module(0), function(1), arity(2),
+        void *terminate;
+        ErtsCodeMFA initial;	/* Initial module(0), function(1), arity(2),
                                    often used instead of pointer to funcinfo
                                    instruction. */
     } u;
+
     const ErtsCodeMFA* current; /* Current Erlang function, part of the
                                  * funcinfo:
                                  *
@@ -1089,7 +1088,7 @@ struct process {
     /*
      * Information mainly for post-mortem use (erl crash dump).
      */
-    Eterm parent;		/* Pid of process that created this process. */
+    Eterm parent;               /* Pid of process that created this process. */
 
     Uint32 static_flags;        /* Flags that do *not* change */
 
@@ -1097,12 +1096,12 @@ struct process {
      * architectures, have gone to.
      */
 
+    Uint16 gen_gcs;             /* Number of (minor) generational GCs. */
+    Uint16 max_gen_gcs;         /* Max minor gen GCs before fullsweep. */
     Eterm *high_water;
     Eterm *old_hend;            /* Heap pointers for generational GC. */
     Eterm *old_htop;
     Eterm *old_heap;
-    Uint16 gen_gcs;		/* Number of (minor) generational GCs. */
-    Uint16 max_gen_gcs;		/* Max minor gen GCs before fullsweep. */
     ErlOffHeap off_heap;	/* Off-heap data updated by copy_struct(). */
     struct erl_off_heap_header* wrt_bins; /* Writable binaries */
     ErlHeapFragment* mbuf;	/* Pointer to heap fragment list */
@@ -1128,6 +1127,11 @@ struct process {
     ErtsSchedulerData *scheduler_data;
     erts_atomic_t run_queue;
 
+#ifdef USE_VM_PROBES
+    Eterm dt_utag;              /* Place to store the dynamic trace user tag */
+    Uint dt_utag_flags;         /* flag field for the dt_utag */
+#endif
+
 #ifdef CHECK_FOR_HOLES
     Eterm* last_htop;		/* No need to scan the heap below this point. */
     ErlHeapFragment* last_mbuf;	/* No need to scan beyond this mbuf. */
diff --git a/erts/emulator/beam/erl_ptab.h b/erts/emulator/beam/erl_ptab.h
index a95b81162a..3c9edd5460 100644
--- a/erts/emulator/beam/erl_ptab.h
+++ b/erts/emulator/beam/erl_ptab.h
@@ -59,8 +59,6 @@ typedef struct {
 	erts_atomic_t atmc;
 	Sint sint;
     } refc;
-    ErtsTracer tracer;
-    Uint trace_flags;
     erts_atomic_t timer;
     union {
 	/* --- While being alive --- */
@@ -78,6 +76,8 @@ typedef struct {
 	/* --- While being released --- */
 	ErtsThrPrgrLaterOp release;
     } u;
+    ErtsTracer tracer;
+    Uint32 trace_flags;
 } ErtsPTabElementCommon;
 
 typedef struct ErtsPTabDeletedElement_ ErtsPTabDeletedElement;
diff --git a/erts/emulator/beam/erl_trace.c b/erts/emulator/beam/erl_trace.c
index 2dd6c99d4c..8e41691561 100644
--- a/erts/emulator/beam/erl_trace.c
+++ b/erts/emulator/beam/erl_trace.c
@@ -66,9 +66,9 @@
 Export exp_send, exp_receive, exp_timeout;
 
 static ErtsTracer system_seq_tracer;
-static Uint default_proc_trace_flags;
+static Uint32 default_proc_trace_flags;
 static ErtsTracer default_proc_tracer;
-static Uint default_port_trace_flags;
+static Uint32 default_port_trace_flags;
 static ErtsTracer default_port_tracer;
 
 static Eterm system_monitor;
@@ -485,8 +485,8 @@ erts_get_system_seq_tracer(void)
 }
 
 static ERTS_INLINE void
-get_default_tracing(Uint *flagsp, ErtsTracer *tracerp,
-                    Uint *default_trace_flags,
+get_default_tracing(Uint32 *flagsp, ErtsTracer *tracerp,
+                    Uint32 *default_trace_flags,
                     ErtsTracer *default_tracer)
 {
     if (!(*default_trace_flags & TRACEE_FLAGS))
@@ -531,9 +531,9 @@ get_default_tracing(Uint *flagsp, ErtsTracer *tracerp,
 }
 
 static ERTS_INLINE void
-erts_change_default_tracing(int setflags, Uint flags,
+erts_change_default_tracing(int setflags, Uint32 flags,
                             const ErtsTracer tracer,
-                            Uint *default_trace_flags,
+                            Uint32 *default_trace_flags,
                             ErtsTracer *default_tracer)
 {
     if (setflags)
@@ -547,31 +547,31 @@ erts_change_default_tracing(int setflags, Uint flags,
 }
 
 void
-erts_change_default_proc_tracing(int setflags, Uint flagsp,
+erts_change_default_proc_tracing(int setflags, Uint32 flags,
                                  const ErtsTracer tracer)
 {
     erts_rwmtx_rwlock(&sys_trace_rwmtx);
     erts_change_default_tracing(
-        setflags, flagsp, tracer,
+        setflags, flags, tracer,
         &default_proc_trace_flags,
         &default_proc_tracer);
     erts_rwmtx_rwunlock(&sys_trace_rwmtx);
 }
 
 void
-erts_change_default_port_tracing(int setflags, Uint flagsp,
+erts_change_default_port_tracing(int setflags, Uint32 flags,
                                  const ErtsTracer tracer)
 {
     erts_rwmtx_rwlock(&sys_trace_rwmtx);
     erts_change_default_tracing(
-        setflags, flagsp, tracer,
+        setflags, flags, tracer,
         &default_port_trace_flags,
         &default_port_tracer);
     erts_rwmtx_rwunlock(&sys_trace_rwmtx);
 }
 
 void
-erts_get_default_proc_tracing(Uint *flagsp, ErtsTracer *tracerp)
+erts_get_default_proc_tracing(Uint32 *flagsp, ErtsTracer *tracerp)
 {
     erts_rwmtx_rlock(&sys_trace_rwmtx);
     *tracerp = erts_tracer_nil; /* initialize */
@@ -583,7 +583,7 @@ erts_get_default_proc_tracing(Uint *flagsp, ErtsTracer *tracerp)
 }
 
 void
-erts_get_default_port_tracing(Uint *flagsp, ErtsTracer *tracerp)
+erts_get_default_port_tracing(Uint32 *flagsp, ErtsTracer *tracerp)
 {
     erts_rwmtx_rlock(&sys_trace_rwmtx);
     *tracerp = erts_tracer_nil; /* initialize */
@@ -976,7 +976,8 @@ erts_trace_return(Process* p, ErtsCodeMFA *mfa,
 {
     Eterm* hp;
     Eterm mfa_tuple;
-    Uint meta_flags, *tracee_flags;
+    Uint32 meta_flags;
+    Uint32 *tracee_flags;
 
     ASSERT(tracer);
     if (ERTS_TRACER_COMPARE(*tracer, erts_tracer_true)) {
@@ -1031,7 +1032,8 @@ erts_trace_exception(Process* p, ErtsCodeMFA *mfa, Eterm class, Eterm value,
 {
     Eterm* hp;
     Eterm mfa_tuple, cv;
-    Uint meta_flags, *tracee_flags;
+    Uint32 meta_flags;
+    Uint32 *tracee_flags;
 
     ASSERT(tracer);
     if (ERTS_TRACER_COMPARE(*tracer, erts_tracer_true)) {
@@ -1097,7 +1099,8 @@ erts_call_trace(Process* p, ErtsCodeInfo *info, Binary *match_spec,
     int i;
     Uint32 return_flags;
     Eterm pam_result = am_true;
-    Uint meta_flags, *tracee_flags;
+    Uint32 meta_flags;
+    Uint32 *tracee_flags;
     ErtsTracerNif *tnif = NULL;
     Eterm transformed_args[MAX_ARG];
     ErtsTracer pre_ms_tracer = erts_tracer_nil;
diff --git a/erts/emulator/beam/erl_trace.h b/erts/emulator/beam/erl_trace.h
index e67011e46b..3701c4390d 100644
--- a/erts/emulator/beam/erl_trace.h
+++ b/erts/emulator/beam/erl_trace.h
@@ -77,12 +77,12 @@ ErtsTracer erts_set_system_seq_tracer(Process *c_p,
                                       ErtsProcLocks c_p_locks,
                                       ErtsTracer new_);
 ErtsTracer erts_get_system_seq_tracer(void);
-void erts_change_default_proc_tracing(int setflags, Uint flagsp,
+void erts_change_default_proc_tracing(int setflags, Uint32 flags,
                                       const ErtsTracer tracerp);
-void erts_get_default_proc_tracing(Uint *flagsp, ErtsTracer *tracerp);
-void erts_change_default_port_tracing(int setflags, Uint flagsp,
+void erts_get_default_proc_tracing(Uint32 *flagsp, ErtsTracer *tracerp);
+void erts_change_default_port_tracing(int setflags, Uint32 flags,
                                       const ErtsTracer tracerp);
-void erts_get_default_port_tracing(Uint *flagsp, ErtsTracer *tracerp);
+void erts_get_default_port_tracing(Uint32 *flagsp, ErtsTracer *tracerp);
 void erts_set_system_monitor(Eterm monitor);
 Eterm erts_get_system_monitor(void);
 int erts_is_tracer_valid(Process* p);
diff --git a/erts/emulator/beam/jit/arm/beam_asm.hpp b/erts/emulator/beam/jit/arm/beam_asm.hpp
index 8ef609f4b2..a35c4a543f 100644
--- a/erts/emulator/beam/jit/arm/beam_asm.hpp
+++ b/erts/emulator/beam/jit/arm/beam_asm.hpp
@@ -81,7 +81,7 @@ protected:
 
     const arm::Gp E = a64::x20;
     const arm::Gp c_p = a64::x21;
-    const arm::Gp FCALLS = a64::x22;
+    const arm::Gp FCALLS = a64::w22;
     const arm::Gp HTOP = a64::x23;
 
     /* Local copy of the active code index.
@@ -686,13 +686,23 @@ protected:
         a.cmp(SUPER_TMP, imm(TAG_PRIMARY_IMMED1));
     }
 
+    arm::Gp follow_size(const arm::Gp &reg, const arm::Gp &size) {
+        ASSERT(reg.isGpX());
+
+        if (size.isGpW()) {
+            return reg.w();
+        }
+
+        return reg;
+    }
+
     template<typename T>
     void mov_imm(arm::Gp to, T value) {
         static_assert(std::is_integral<T>::value || std::is_pointer<T>::value);
         if (value) {
             a.mov(to, imm(value));
         } else {
-            a.mov(to, ZERO);
+            a.mov(to, follow_size(ZERO, to));
         }
     }
 
@@ -716,8 +726,10 @@ protected:
                 a.sub(to, src, imm(val & 0xFFF000));
             }
         } else {
-            mov_imm(SUPER_TMP, val);
-            a.sub(to, src, SUPER_TMP);
+            arm::Gp super_tmp = follow_size(SUPER_TMP, to);
+
+            mov_imm(super_tmp, val);
+            a.sub(to, src, super_tmp);
         }
     }
 
@@ -736,8 +748,10 @@ protected:
                 a.add(to, src, imm(val & 0xFFF000));
             }
         } else {
-            mov_imm(SUPER_TMP, val);
-            a.add(to, src, SUPER_TMP);
+            arm::Gp super_tmp = follow_size(SUPER_TMP, to);
+
+            mov_imm(super_tmp, val);
+            a.add(to, src, super_tmp);
         }
     }
 
@@ -747,8 +761,10 @@ protected:
         } else if (Support::isUInt12(-val)) {
             a.adds(to, src, imm(-val));
         } else {
-            mov_imm(SUPER_TMP, val);
-            a.subs(to, src, SUPER_TMP);
+            arm::Gp super_tmp = follow_size(SUPER_TMP, to);
+
+            mov_imm(super_tmp, val);
+            a.subs(to, src, super_tmp);
         }
     }
 
@@ -757,13 +773,11 @@ protected:
             a.cmp(src, imm(val));
         } else if (Support::isUInt12(-val)) {
             a.cmn(src, imm(-val));
-        } else if (src.isGpW()) {
-            mov_imm(SUPER_TMP.w(), val);
-            a.cmp(src, SUPER_TMP.w());
         } else {
-            ERTS_ASSERT(src.isGpX());
-            mov_imm(SUPER_TMP, val);
-            a.cmp(src, SUPER_TMP);
+            arm::Gp super_tmp = follow_size(SUPER_TMP, src);
+
+            mov_imm(super_tmp, val);
+            a.cmp(src, super_tmp);
         }
     }
 
diff --git a/erts/emulator/beam/jit/arm/beam_asm_global.cpp b/erts/emulator/beam/jit/arm/beam_asm_global.cpp
index a4d20a9356..1ec8ffa51a 100644
--- a/erts/emulator/beam/jit/arm/beam_asm_global.cpp
+++ b/erts/emulator/beam/jit/arm/beam_asm_global.cpp
@@ -115,9 +115,9 @@ void BeamGlobalAssembler::emit_garbage_collect() {
     /* ARG2 is already loaded. */
     load_x_reg_array(ARG3);
     /* ARG4 (live registers) is already loaded. */
-    a.mov(ARG5, FCALLS);
+    a.mov(ARG5.w(), FCALLS);
     runtime_call<5>(erts_garbage_collect_nobump);
-    a.sub(FCALLS, FCALLS, ARG1);
+    a.sub(FCALLS, FCALLS, ARG1.w());
 
     emit_leave_runtime<Update::eStack | Update::eHeap | Update::eXRegs>();
     emit_leave_runtime_frame();
diff --git a/erts/emulator/beam/jit/arm/beam_asm_module.cpp b/erts/emulator/beam/jit/arm/beam_asm_module.cpp
index 57f5746a8c..276a560ca9 100644
--- a/erts/emulator/beam/jit/arm/beam_asm_module.cpp
+++ b/erts/emulator/beam/jit/arm/beam_asm_module.cpp
@@ -315,6 +315,7 @@ void BeamGlobalAssembler::emit_i_func_info_shared() {
     /* a64::x30 now points 4 bytes into the ErtsCodeInfo struct for the
      * function. Put the address of the MFA into ARG1. */
     a.add(ARG1, a64::x30, offsetof(ErtsCodeInfo, mfa) - 4);
+
     mov_imm(TMP1, EXC_FUNCTION_CLAUSE);
     a.str(TMP1, arm::Mem(c_p, offsetof(Process, freason)));
     a.str(ARG1, arm::Mem(c_p, offsetof(Process, current)));
@@ -329,7 +330,7 @@ void BeamModuleAssembler::emit_i_func_info(const ArgWord &Label,
                                            const ArgAtom &Module,
                                            const ArgAtom &Function,
                                            const ArgWord &Arity) {
-    ErtsCodeInfo info;
+    ErtsCodeInfo info = {};
 
     /* `op_i_func_info_IaaI` is used in various places in the emulator, so this
      * label is always encoded as a word, even though the signature ought to
@@ -339,7 +340,6 @@ void BeamModuleAssembler::emit_i_func_info(const ArgWord &Label,
     info.mfa.module = Module.get();
     info.mfa.function = Function.get();
     info.mfa.arity = Arity.get();
-    info.gen_bp = NULL;
 
     comment("%T:%T/%d", info.mfa.module, info.mfa.function, info.mfa.arity);
 
@@ -395,7 +395,7 @@ void BeamModuleAssembler::bind_veneer_target(const Label &target) {
         ASSERT(veneer.target == target);
 
         if (!code.isLabelBound(veneer.anchor)) {
-            ASSERT(a.offset() <= veneer.latestOffset);
+            ASSERT((ssize_t)a.offset() <= veneer.latestOffset);
             a.bind(veneer.anchor);
 
             /* TODO: remove from pending stubs? */
diff --git a/erts/emulator/beam/jit/arm/instr_bif.cpp b/erts/emulator/beam/jit/arm/instr_bif.cpp
index d12ea50cef..191f91235d 100644
--- a/erts/emulator/beam/jit/arm/instr_bif.cpp
+++ b/erts/emulator/beam/jit/arm/instr_bif.cpp
@@ -254,7 +254,7 @@ void BeamGlobalAssembler::emit_i_length_common(Label fail, int state_size) {
         a.add(ARG2, ARG2, imm(state_size));
 
         a.str(ZERO, arm::Mem(c_p, offsetof(Process, current)));
-        a.str(ARG2, arm::Mem(c_p, offsetof(Process, arity)));
+        a.strb(ARG2.w(), arm::Mem(c_p, offsetof(Process, arity)));
 
         /* We'll find our way back through the entry address (ARG3). */
         a.b(labels[context_switch_simplified]);
@@ -360,9 +360,6 @@ static Eterm debug_call_light_bif(Process *c_p,
  * ARG8 = BIF pointer
  */
 void BeamGlobalAssembler::emit_call_light_bif_shared() {
-    /* We use the HTOP, FCALLS, and XREG1 registers as they are not
-     * used on the runtime-stack and are caller save. */
-
     arm::Mem entry_mem = TMP_MEM1q, export_mem = TMP_MEM2q,
              mbuf_mem = TMP_MEM3q;
 
@@ -539,7 +536,7 @@ void BeamGlobalAssembler::emit_call_light_bif_shared() {
             a.ldr(ARG2, mbuf_mem);
             load_x_reg_array(ARG4);
             a.ldr(ARG5, export_mem);
-            a.ldr(ARG5, arm::Mem(ARG5, offsetof(Export, info.mfa.arity)));
+            a.ldrb(ARG5.w(), arm::Mem(ARG5, offsetof(Export, info.mfa.arity)));
             runtime_call<5>(erts_gc_after_bif_call_lhf);
 
             emit_leave_runtime<Update::eReductions | Update::eStack |
@@ -558,9 +555,9 @@ void BeamGlobalAssembler::emit_call_light_bif_shared() {
 
     a.bind(yield);
     {
-        a.ldr(ARG2, arm::Mem(ARG4, offsetof(Export, info.mfa.arity)));
+        a.ldrb(ARG2.w(), arm::Mem(ARG4, offsetof(Export, info.mfa.arity)));
         lea(ARG4, arm::Mem(ARG4, offsetof(Export, info.mfa)));
-        a.str(ARG2, arm::Mem(c_p, offsetof(Process, arity)));
+        a.strb(ARG2.w(), arm::Mem(c_p, offsetof(Process, arity)));
         a.str(ARG4, arm::Mem(c_p, offsetof(Process, current)));
 
         /* We'll find our way back through ARG3 (entry address). */
@@ -701,8 +698,8 @@ void BeamGlobalAssembler::emit_call_bif_shared(void) {
     emit_enter_runtime_frame();
     a.str(ARG2, arm::Mem(c_p, offsetof(Process, current)));
     /* `call_bif` wants arity in ARG5. */
-    a.ldr(ARG5, arm::Mem(ARG2, offsetof(ErtsCodeMFA, arity)));
-    a.str(ARG5, arm::Mem(c_p, offsetof(Process, arity)));
+    a.ldr(ARG5.w(), arm::Mem(ARG2, offsetof(ErtsCodeMFA, arity)));
+    a.strb(ARG5.w(), arm::Mem(c_p, offsetof(Process, arity)));
     a.str(ARG3, arm::Mem(c_p, offsetof(Process, i)));
 
     /* The corresponding leave can be found in the epilogue. */
@@ -891,8 +888,8 @@ void BeamGlobalAssembler::emit_call_nif_yield_helper() {
         int mfa_offset = sizeof(ErtsCodeMFA);
         int arity_offset = offsetof(ErtsCodeMFA, arity) - mfa_offset;
 
-        a.ldur(TMP1, arm::Mem(ARG3, arity_offset));
-        a.str(TMP1, arm::Mem(c_p, offsetof(Process, arity)));
+        a.ldur(TMP1.w(), arm::Mem(ARG3, arity_offset));
+        a.strb(TMP1.w(), arm::Mem(c_p, offsetof(Process, arity)));
 
         a.sub(TMP1, ARG3, imm(mfa_offset));
         a.str(TMP1, arm::Mem(c_p, offsetof(Process, current)));
diff --git a/erts/emulator/beam/jit/arm/instr_call.cpp b/erts/emulator/beam/jit/arm/instr_call.cpp
index 8f755df54b..2d9d4f3f8a 100644
--- a/erts/emulator/beam/jit/arm/instr_call.cpp
+++ b/erts/emulator/beam/jit/arm/instr_call.cpp
@@ -29,7 +29,7 @@ void BeamGlobalAssembler::emit_dispatch_return() {
     a.mov(ARG3, a64::x30);
     a.str(ZERO, arm::Mem(c_p, offsetof(Process, current)));
     mov_imm(TMP1, 1);
-    a.str(TMP1, arm::Mem(c_p, offsetof(Process, arity)));
+    a.strb(TMP1.w(), arm::Mem(c_p, offsetof(Process, arity)));
     a.b(labels[context_switch_simplified]);
 }
 
diff --git a/erts/emulator/beam/jit/arm/instr_common.cpp b/erts/emulator/beam/jit/arm/instr_common.cpp
index e4e50712cc..7d15197ce1 100644
--- a/erts/emulator/beam/jit/arm/instr_common.cpp
+++ b/erts/emulator/beam/jit/arm/instr_common.cpp
@@ -78,8 +78,8 @@ void BeamModuleAssembler::emit_error(int reason) {
 void BeamModuleAssembler::emit_error(int reason, const ArgSource &Src) {
     auto src = load_source(Src, TMP2);
 
-    ERTS_CT_ASSERT_FIELD_PAIR(Process, freason, fvalue);
     mov_imm(TMP1, reason);
+    ERTS_CT_ASSERT_FIELD_PAIR(Process, freason, fvalue);
     a.stp(TMP1, src.reg, arm::Mem(c_p, offsetof(Process, freason)));
     emit_raise_exception();
 }
@@ -240,7 +240,7 @@ void BeamModuleAssembler::emit_normal_exit() {
 
     mov_imm(TMP1, EXC_NORMAL);
     a.str(TMP1, arm::Mem(c_p, offsetof(Process, freason)));
-    a.str(ZERO, arm::Mem(c_p, offsetof(Process, arity)));
+    a.strb(ZERO.w(), arm::Mem(c_p, offsetof(Process, arity)));
     a.mov(ARG1, c_p);
     mov_imm(ARG2, am_normal);
     runtime_call<2>(erts_do_exit_process);
@@ -2489,8 +2489,8 @@ void BeamGlobalAssembler::emit_i_test_yield_shared() {
     a.add(ARG3, ARG3, imm(TEST_YIELD_RETURN_OFFSET));
 
     a.str(ARG2, arm::Mem(c_p, offsetof(Process, current)));
-    a.ldr(ARG2, arm::Mem(ARG2, offsetof(ErtsCodeMFA, arity)));
-    a.str(ARG2, arm::Mem(c_p, offsetof(Process, arity)));
+    a.ldr(ARG2.w(), arm::Mem(ARG2, offsetof(ErtsCodeMFA, arity)));
+    a.strb(ARG2.w(), arm::Mem(c_p, offsetof(Process, arity)));
 
     a.b(labels[context_switch_simplified]);
 }
diff --git a/erts/emulator/beam/jit/arm/instr_fun.cpp b/erts/emulator/beam/jit/arm/instr_fun.cpp
index f2e0792f26..c7a32188cb 100644
--- a/erts/emulator/beam/jit/arm/instr_fun.cpp
+++ b/erts/emulator/beam/jit/arm/instr_fun.cpp
@@ -80,8 +80,8 @@ void BeamGlobalAssembler::emit_handle_call_fun_error() {
     a.bind(bad_fun);
     {
         mov_imm(TMP1, EXC_BADFUN);
-        a.str(TMP1, arm::Mem(c_p, offsetof(Process, freason)));
-        a.str(ARG4, arm::Mem(c_p, offsetof(Process, fvalue)));
+        ERTS_CT_ASSERT_FIELD_PAIR(Process, freason, fvalue);
+        a.stp(TMP1, ARG4, arm::Mem(c_p, offsetof(Process, freason)));
 
         a.mov(ARG2, ARG5);
         mov_imm(ARG4, nullptr);
@@ -126,8 +126,8 @@ void BeamGlobalAssembler::emit_handle_call_fun_error() {
         }
 
         a.mov(TMP1, imm(EXC_BADARITY));
-        a.str(TMP1, arm::Mem(c_p, offsetof(Process, freason)));
-        a.str(ARG1, arm::Mem(c_p, offsetof(Process, fvalue)));
+        ERTS_CT_ASSERT_FIELD_PAIR(Process, freason, fvalue);
+        a.stp(TMP1, ARG1, arm::Mem(c_p, offsetof(Process, freason)));
 
         a.ldr(ARG2, TMP_MEM2q);
         mov_imm(ARG4, nullptr);
@@ -206,7 +206,7 @@ void BeamModuleAssembler::emit_i_make_fun3(const ArgLambda &Lambda,
     const ssize_t num_free = NumFree.get();
     ssize_t i;
 
-    ASSERT(num_free == env.size());
+    ASSERT(num_free == (ssize_t)env.size());
 
     a.mov(ARG1, c_p);
     mov_arg(ARG2, Lambda);
diff --git a/erts/emulator/beam/jit/arm/instr_guard_bifs.cpp b/erts/emulator/beam/jit/arm/instr_guard_bifs.cpp
index c24ca4831f..3077c8df84 100644
--- a/erts/emulator/beam/jit/arm/instr_guard_bifs.cpp
+++ b/erts/emulator/beam/jit/arm/instr_guard_bifs.cpp
@@ -833,8 +833,8 @@ void BeamModuleAssembler::emit_bif_is_map_key(const ArgWord &Bif,
 void BeamGlobalAssembler::emit_handle_map_get_badmap() {
     static ErtsCodeMFA mfa = {am_erlang, am_map_get, 2};
     mov_imm(TMP1, BADMAP);
-    a.str(TMP1, arm::Mem(c_p, offsetof(Process, freason)));
-    a.str(ARG1, arm::Mem(c_p, offsetof(Process, fvalue)));
+    ERTS_CT_ASSERT_FIELD_PAIR(Process, freason, fvalue);
+    a.stp(TMP1, ARG1, arm::Mem(c_p, offsetof(Process, freason)));
     a.mov(XREG0, ARG2);
     a.mov(XREG1, ARG1);
     mov_imm(ARG4, &mfa);
@@ -844,8 +844,8 @@ void BeamGlobalAssembler::emit_handle_map_get_badmap() {
 void BeamGlobalAssembler::emit_handle_map_get_badkey() {
     static ErtsCodeMFA mfa = {am_erlang, am_map_get, 2};
     mov_imm(TMP1, BADKEY);
-    a.str(TMP1, arm::Mem(c_p, offsetof(Process, freason)));
-    a.str(ARG2, arm::Mem(c_p, offsetof(Process, fvalue)));
+    ERTS_CT_ASSERT_FIELD_PAIR(Process, freason, fvalue);
+    a.stp(TMP1, ARG2, arm::Mem(c_p, offsetof(Process, freason)));
     a.mov(XREG0, ARG2);
     a.mov(XREG1, ARG1);
     mov_imm(ARG4, &mfa);
@@ -939,8 +939,8 @@ void BeamModuleAssembler::emit_bif_map_get(const ArgLabel &Fail,
 void BeamGlobalAssembler::emit_handle_map_size_error() {
     static ErtsCodeMFA mfa = {am_erlang, am_map_size, 1};
     mov_imm(TMP1, BADMAP);
-    a.str(TMP1, arm::Mem(c_p, offsetof(Process, freason)));
-    a.str(XREG0, arm::Mem(c_p, offsetof(Process, fvalue)));
+    ERTS_CT_ASSERT_FIELD_PAIR(Process, freason, fvalue);
+    a.stp(TMP1, XREG0, arm::Mem(c_p, offsetof(Process, freason)));
     mov_imm(ARG4, &mfa);
     a.b(labels[raise_exception]);
 }
diff --git a/erts/emulator/beam/jit/arm/instr_msg.cpp b/erts/emulator/beam/jit/arm/instr_msg.cpp
index dd99af59c2..4b8f098fd0 100644
--- a/erts/emulator/beam/jit/arm/instr_msg.cpp
+++ b/erts/emulator/beam/jit/arm/instr_msg.cpp
@@ -180,7 +180,7 @@ void BeamGlobalAssembler::emit_i_loop_rec_shared() {
 
         a.str(ZERO, message_ptr);
         a.mov(ARG1, c_p);
-        a.mov(ARG2, FCALLS);
+        a.mov(ARG2.w(), FCALLS);
         mov_imm(ARG3, 0);
         lea(ARG4, message_ptr);
         lea(ARG5, get_out);
@@ -198,7 +198,7 @@ void BeamGlobalAssembler::emit_i_loop_rec_shared() {
          * index. */
         emit_leave_runtime<Update::eHeapAlloc | Update::eCodeIndex>(0);
 
-        a.sub(FCALLS, FCALLS, ARG1);
+        a.sub(FCALLS, FCALLS, ARG1.w());
 
         /* Need to spill message_ptr to ARG1 as check_is_distributed uses it. */
         a.ldr(ARG1, message_ptr);
@@ -227,7 +227,7 @@ void BeamGlobalAssembler::emit_i_loop_rec_shared() {
         a.ldr(TMP1.w(), flags);
         a.and_(TMP1, TMP1, imm(~F_DELAY_GC));
         a.str(TMP1.w(), flags);
-        a.str(ZERO, arm::Mem(c_p, offsetof(Process, arity)));
+        a.strb(ZERO.w(), arm::Mem(c_p, offsetof(Process, arity)));
         a.str(ZERO, arm::Mem(c_p, offsetof(Process, current)));
 
         a.b(labels[do_schedule]);
@@ -282,10 +282,10 @@ void BeamModuleAssembler::emit_remove_message() {
     emit_enter_runtime();
 
     a.mov(ARG1, c_p);
-    a.mov(ARG2, FCALLS);
+    a.mov(ARG2.w(), FCALLS);
     a.mov(ARG5, active_code_ix);
     runtime_call<5>(beam_jit_remove_message);
-    a.mov(FCALLS, ARG1);
+    a.mov(FCALLS, ARG1.w());
 
     emit_leave_runtime();
 }
diff --git a/erts/emulator/beam/jit/arm/ops.tab b/erts/emulator/beam/jit/arm/ops.tab
index 3e1317bb9d..627e228734 100644
--- a/erts/emulator/beam/jit/arm/ops.tab
+++ b/erts/emulator/beam/jit/arm/ops.tab
@@ -898,7 +898,7 @@ int_func_start Func_Label Func_Line M F A |
     func_line Func_Line |
     aligned_label Func_Label u=8 |
     i_func_info Func_Label M F A |
-      aligned_label Entry_Label u=8 |
+      aligned_label Entry_Label u=4 |
       i_breakpoint_trampoline |
       line Entry_Line |
       call_bif_mfa M F A
@@ -909,7 +909,7 @@ int_func_start Func_Label Func_Line M F A |
     func_line Func_Line |
     aligned_label Func_Label u=8 |
     i_func_info Func_Label M F A |
-      aligned_label Entry_Label u=8 |
+      aligned_label Entry_Label u=4 |
       i_breakpoint_trampoline |
       line Entry_Line |
       i_test_yield
diff --git a/erts/emulator/beam/jit/arm/process_main.cpp b/erts/emulator/beam/jit/arm/process_main.cpp
index 8b7ddfa17d..dd766323f8 100644
--- a/erts/emulator/beam/jit/arm/process_main.cpp
+++ b/erts/emulator/beam/jit/arm/process_main.cpp
@@ -28,6 +28,8 @@ extern "C"
 #include "export.h"
 }
 
+#undef x
+
 #if defined(DEBUG) || defined(ERTS_ENABLE_LOCK_CHECK)
 static Process *erts_debug_schedule(ErtsSchedulerData *esdp,
                                     Process *c_p,
@@ -93,7 +95,7 @@ void BeamGlobalAssembler::emit_process_main() {
     {
         /* Figure out reds_used. def_arg_reg[5] = REDS_IN */
         a.ldr(TMP1, arm::Mem(c_p, offsetof(Process, def_arg_reg[5])));
-        a.sub(ARG3, TMP1, FCALLS);
+        a.sub(ARG3.w(), TMP1.w(), FCALLS);
         a.b(schedule_next);
     }
 
@@ -106,10 +108,10 @@ void BeamGlobalAssembler::emit_process_main() {
     {
         Sint arity_offset = offsetof(ErtsCodeMFA, arity) - sizeof(ErtsCodeMFA);
 
-        a.ldur(TMP1, arm::Mem(ARG3, arity_offset));
-        a.str(TMP1, arm::Mem(c_p, offsetof(Process, arity)));
+        a.ldur(TMP1.w(), arm::Mem(ARG3, arity_offset));
+        a.strb(TMP1.w(), arm::Mem(c_p, offsetof(Process, arity)));
 
-        a.sub(TMP1, ARG3, imm((Uint)sizeof(ErtsCodeMFA)));
+        a.sub(TMP1, ARG3, imm(sizeof(ErtsCodeMFA)));
         a.str(TMP1, arm::Mem(c_p, offsetof(Process, current)));
 
         /* !! Fall through !! */
@@ -139,7 +141,7 @@ void BeamGlobalAssembler::emit_process_main() {
 
             a.adr(TMP1, labels[process_exit]);
             a.str(TMP1, arm::Mem(c_p, offsetof(Process, i)));
-            a.str(ZERO, arm::Mem(c_p, offsetof(Process, arity)));
+            a.strb(ZERO.w(), arm::Mem(c_p, offsetof(Process, arity)));
             a.str(ZERO, arm::Mem(c_p, offsetof(Process, current)));
             a.b(do_schedule_local);
         }
@@ -147,8 +149,8 @@ void BeamGlobalAssembler::emit_process_main() {
         a.bind(not_exiting);
 
         /* Figure out reds_used. def_arg_reg[5] = REDS_IN */
-        a.ldr(TMP1, arm::Mem(c_p, offsetof(Process, def_arg_reg[5])));
-        a.sub(FCALLS, TMP1, FCALLS);
+        a.ldr(TMP1.w(), arm::Mem(c_p, offsetof(Process, def_arg_reg[5])));
+        a.sub(FCALLS, TMP1.w(), FCALLS);
 
         comment("Copy out X registers");
         a.mov(ARG1, c_p);
@@ -156,7 +158,7 @@ void BeamGlobalAssembler::emit_process_main() {
         runtime_call<2>(copy_out_registers);
 
         /* Restore reds_used from FCALLS */
-        a.mov(ARG3, FCALLS);
+        a.mov(ARG3.w(), FCALLS);
 
         /* !! Fall through !! */
     }
@@ -223,10 +225,10 @@ void BeamGlobalAssembler::emit_process_main() {
 
         /* Setup reduction counting */
         a.ldr(FCALLS, arm::Mem(c_p, offsetof(Process, fcalls)));
-        a.str(FCALLS, arm::Mem(c_p, offsetof(Process, def_arg_reg[5])));
+        a.str(FCALLS.x(), arm::Mem(c_p, offsetof(Process, def_arg_reg[5])));
 
 #ifdef DEBUG
-        a.str(FCALLS, a64::Mem(c_p, offsetof(Process, debug_reds_in)));
+        a.str(FCALLS.x(), a64::Mem(c_p, offsetof(Process, debug_reds_in)));
 #endif
 
         comment("check whether save calls is on");
diff --git a/erts/emulator/beam/jit/beam_jit_common.cpp b/erts/emulator/beam/jit/beam_jit_common.cpp
index 3200f75407..1ef228fa31 100644
--- a/erts/emulator/beam/jit/beam_jit_common.cpp
+++ b/erts/emulator/beam/jit/beam_jit_common.cpp
@@ -1106,11 +1106,11 @@ ErtsMessage *beam_jit_decode_dist(Process *c_p, ErtsMessage *msgp) {
 }
 
 /* Remove a (matched) message from the message queue. */
-Sint beam_jit_remove_message(Process *c_p,
-                             Sint FCALLS,
-                             Eterm *HTOP,
-                             Eterm *E,
-                             Uint32 active_code_ix) {
+Sint32 beam_jit_remove_message(Process *c_p,
+                               Sint32 FCALLS,
+                               Eterm *HTOP,
+                               Eterm *E,
+                               Uint32 active_code_ix) {
     ErtsMessage *msgp;
 
     ERTS_CHK_MBUF_SZ(c_p);
diff --git a/erts/emulator/beam/jit/beam_jit_common.hpp b/erts/emulator/beam/jit/beam_jit_common.hpp
index c7b9f0ade0..b6f7239fae 100644
--- a/erts/emulator/beam/jit/beam_jit_common.hpp
+++ b/erts/emulator/beam/jit/beam_jit_common.hpp
@@ -616,11 +616,11 @@ Eterm beam_jit_bs_get_integer(Process *c_p,
                               Uint Live);
 
 ErtsMessage *beam_jit_decode_dist(Process *c_p, ErtsMessage *msgp);
-Sint beam_jit_remove_message(Process *c_p,
-                             Sint FCALLS,
-                             Eterm *HTOP,
-                             Eterm *E,
-                             Uint32 active_code_ix);
+Sint32 beam_jit_remove_message(Process *c_p,
+                               Sint32 FCALLS,
+                               Eterm *HTOP,
+                               Eterm *E,
+                               Uint32 active_code_ix);
 
 void beam_jit_bs_construct_fail_info(Process *c_p,
                                      Uint packed_error_info,
diff --git a/erts/emulator/beam/jit/beam_jit_main.cpp b/erts/emulator/beam/jit/beam_jit_main.cpp
index 0cd732039f..3862663877 100644
--- a/erts/emulator/beam/jit/beam_jit_main.cpp
+++ b/erts/emulator/beam/jit/beam_jit_main.cpp
@@ -268,6 +268,7 @@ void beamasm_init() {
     ERTS_CT_ASSERT(offsetof(Process, fcalls) < 128);
     ERTS_CT_ASSERT(offsetof(Process, freason) < 128);
     ERTS_CT_ASSERT(offsetof(Process, fvalue) < 128);
+    ERTS_CT_ASSERT(offsetof(Process, flags) < 128);
 
 #ifdef ERLANG_FRAME_POINTERS
     ERTS_CT_ASSERT(offsetof(Process, frame_pointer) < 128);
diff --git a/erts/emulator/beam/jit/x86/beam_asm.hpp b/erts/emulator/beam/jit/x86/beam_asm.hpp
index c7f085ee62..dc34ef4635 100644
--- a/erts/emulator/beam/jit/x86/beam_asm.hpp
+++ b/erts/emulator/beam/jit/x86/beam_asm.hpp
@@ -93,7 +93,7 @@ protected:
 #endif
 
     const x86::Gp c_p = x86::r13;
-    const x86::Gp FCALLS = x86::r14;
+    const x86::Gp FCALLS = x86::r14d;
     const x86::Gp HTOP = x86::r15;
 
     /* Local copy of the active code index.
@@ -690,7 +690,7 @@ protected:
         }
 
         if (Spec & Update::eReductions) {
-            a.mov(x86::qword_ptr(c_p, offsetof(Process, fcalls)), FCALLS);
+            a.mov(x86::dword_ptr(c_p, offsetof(Process, fcalls)), FCALLS);
         }
 
 #ifdef NATIVE_ERLANG_STACK
@@ -747,7 +747,7 @@ protected:
         }
 
         if (Spec & Update::eReductions) {
-            a.mov(FCALLS, x86::qword_ptr(c_p, offsetof(Process, fcalls)));
+            a.mov(FCALLS, x86::dword_ptr(c_p, offsetof(Process, fcalls)));
         }
 
         if (Spec & Update::eCodeIndex) {
diff --git a/erts/emulator/beam/jit/x86/beam_asm_global.cpp b/erts/emulator/beam/jit/x86/beam_asm_global.cpp
index 7fdfddf276..3c689639e0 100644
--- a/erts/emulator/beam/jit/x86/beam_asm_global.cpp
+++ b/erts/emulator/beam/jit/x86/beam_asm_global.cpp
@@ -125,9 +125,9 @@ void BeamGlobalAssembler::emit_garbage_collect() {
 
     a.mov(ARG1, c_p);
     load_x_reg_array(ARG3);
-    a.mov(ARG5, FCALLS);
+    a.mov(ARG5d, FCALLS);
     runtime_call<5>(erts_garbage_collect_nobump);
-    a.sub(FCALLS, RET);
+    a.sub(FCALLS, RETd);
 
     emit_leave_runtime<Update::eStack | Update::eHeap>();
 
diff --git a/erts/emulator/beam/jit/x86/beam_asm_module.cpp b/erts/emulator/beam/jit/x86/beam_asm_module.cpp
index bc8a11e15e..7eb4e2d6be 100644
--- a/erts/emulator/beam/jit/x86/beam_asm_module.cpp
+++ b/erts/emulator/beam/jit/x86/beam_asm_module.cpp
@@ -285,7 +285,8 @@ void BeamGlobalAssembler::emit_i_func_info_shared() {
 
     a.add(ARG1, imm(offsetof(ErtsCodeInfo, mfa)));
 
-    a.mov(x86::qword_ptr(c_p, offsetof(Process, freason)), EXC_FUNCTION_CLAUSE);
+    a.mov(x86::qword_ptr(c_p, offsetof(Process, freason)),
+          imm(EXC_FUNCTION_CLAUSE));
     a.mov(x86::qword_ptr(c_p, offsetof(Process, current)), ARG1);
 
     mov_imm(ARG2, 0);
@@ -297,7 +298,7 @@ void BeamModuleAssembler::emit_i_func_info(const ArgWord &Label,
                                            const ArgAtom &Module,
                                            const ArgAtom &Function,
                                            const ArgWord &Arity) {
-    ErtsCodeInfo info;
+    ErtsCodeInfo info = {};
 
     /* `op_i_func_info_IaaI` is used in various places in the emulator, so this
      * label is always encoded as a word, even though the signature ought to
@@ -307,7 +308,6 @@ void BeamModuleAssembler::emit_i_func_info(const ArgWord &Label,
     info.mfa.module = Module.get();
     info.mfa.function = Function.get();
     info.mfa.arity = Arity.get();
-    info.gen_bp = NULL;
 
     comment("%T:%T/%d", info.mfa.module, info.mfa.function, info.mfa.arity);
 
diff --git a/erts/emulator/beam/jit/x86/instr_bif.cpp b/erts/emulator/beam/jit/x86/instr_bif.cpp
index 46a514fd34..b13ff53f68 100644
--- a/erts/emulator/beam/jit/x86/instr_bif.cpp
+++ b/erts/emulator/beam/jit/x86/instr_bif.cpp
@@ -285,7 +285,7 @@ x86::Mem BeamGlobalAssembler::emit_i_length_common(Label fail, int state_size) {
         a.add(x86::rsp, imm(sizeof(UWord)));
 
         a.mov(x86::qword_ptr(c_p, offsetof(Process, current)), imm(0));
-        a.mov(x86::qword_ptr(c_p, offsetof(Process, arity)), ARG2);
+        a.mov(x86::byte_ptr(c_p, offsetof(Process, arity)), ARG2.r8());
         a.jmp(labels[context_switch_simplified]);
     }
 
@@ -572,7 +572,8 @@ void BeamGlobalAssembler::emit_call_light_bif_shared() {
         {
             a.mov(ARG2, mbuf_mem);
             a.mov(ARG5, export_mem);
-            a.mov(ARG5, x86::qword_ptr(ARG5, offsetof(Export, info.mfa.arity)));
+            a.movzx(ARG5d,
+                    x86::byte_ptr(ARG5, offsetof(Export, info.mfa.arity)));
 
             emit_enter_runtime<Update::eReductions | Update::eStack |
                                Update::eHeap>();
@@ -609,9 +610,9 @@ void BeamGlobalAssembler::emit_call_light_bif_shared() {
 
     a.bind(yield);
     {
-        a.mov(ARG2, x86::qword_ptr(ARG4, offsetof(Export, info.mfa.arity)));
+        a.movzx(ARG2d, x86::byte_ptr(ARG4, offsetof(Export, info.mfa.arity)));
         a.lea(ARG4, x86::qword_ptr(ARG4, offsetof(Export, info.mfa)));
-        a.mov(x86::qword_ptr(c_p, offsetof(Process, arity)), ARG2);
+        a.mov(x86::byte_ptr(c_p, offsetof(Process, arity)), ARG2.r8());
         a.mov(x86::qword_ptr(c_p, offsetof(Process, current)), ARG4);
 
         /* We'll find our way back through ARG3 (entry address). */
@@ -706,14 +707,14 @@ void BeamGlobalAssembler::emit_bif_nif_epilogue(void) {
         comment("yield");
 
         comment("test trap to hibernate");
-        a.mov(ARG1, x86::qword_ptr(c_p, offsetof(Process, flags)));
-        a.mov(ARG2, ARG1);
-        a.and_(ARG2, imm(F_HIBERNATE_SCHED));
+        a.mov(ARG1d, x86::dword_ptr(c_p, offsetof(Process, flags)));
+        a.mov(ARG2d, ARG1d);
+        a.and_(ARG2d, imm(F_HIBERNATE_SCHED));
         a.short_().je(trap);
 
         comment("do hibernate trap");
-        a.and_(ARG1, imm(~F_HIBERNATE_SCHED));
-        a.mov(x86::qword_ptr(c_p, offsetof(Process, flags)), ARG1);
+        a.and_(ARG1d, imm(~F_HIBERNATE_SCHED));
+        a.mov(x86::dword_ptr(c_p, offsetof(Process, flags)), ARG1d);
         a.jmp(labels[do_schedule]);
     }
 
@@ -759,8 +760,8 @@ void BeamGlobalAssembler::emit_call_bif_shared(void) {
 
     a.mov(x86::qword_ptr(c_p, offsetof(Process, current)), ARG2);
     /* `call_bif` wants arity in ARG5. */
-    a.mov(ARG5, x86::qword_ptr(ARG2, offsetof(ErtsCodeMFA, arity)));
-    a.mov(x86::qword_ptr(c_p, offsetof(Process, arity)), ARG5);
+    a.movzx(ARG5d, x86::byte_ptr(ARG2, offsetof(ErtsCodeMFA, arity)));
+    a.mov(x86::byte_ptr(c_p, offsetof(Process, arity)), ARG5.r8());
     a.mov(x86::qword_ptr(c_p, offsetof(Process, i)), ARG3);
 
     /* The corresponding leave can be found in the epilogue. */
@@ -963,8 +964,8 @@ void BeamGlobalAssembler::emit_call_nif_yield_helper() {
         int mfa_offset = -(int)sizeof(ErtsCodeMFA);
         int arity_offset = mfa_offset + (int)offsetof(ErtsCodeMFA, arity);
 
-        a.mov(ARG1, x86::qword_ptr(ARG3, arity_offset));
-        a.mov(x86::qword_ptr(c_p, offsetof(Process, arity)), ARG1);
+        a.movzx(ARG1d, x86::byte_ptr(ARG3, arity_offset));
+        a.mov(x86::byte_ptr(c_p, offsetof(Process, arity)), ARG1.r8());
 
         a.lea(ARG1, x86::qword_ptr(ARG3, mfa_offset));
         a.mov(x86::qword_ptr(c_p, offsetof(Process, current)), ARG1);
diff --git a/erts/emulator/beam/jit/x86/instr_call.cpp b/erts/emulator/beam/jit/x86/instr_call.cpp
index 367e10e294..e77e291b53 100644
--- a/erts/emulator/beam/jit/x86/instr_call.cpp
+++ b/erts/emulator/beam/jit/x86/instr_call.cpp
@@ -33,8 +33,8 @@ void BeamGlobalAssembler::emit_dispatch_return() {
     /* ARG3 already contains the place to jump to. */
 #endif
 
-    a.mov(x86::qword_ptr(c_p, offsetof(Process, current)), 0);
-    a.mov(x86::qword_ptr(c_p, offsetof(Process, arity)), 1);
+    a.mov(x86::qword_ptr(c_p, offsetof(Process, current)), imm(0));
+    a.mov(x86::byte_ptr(c_p, offsetof(Process, arity)), imm(1));
     a.jmp(labels[context_switch_simplified]);
 }
 
diff --git a/erts/emulator/beam/jit/x86/instr_common.cpp b/erts/emulator/beam/jit/x86/instr_common.cpp
index 99e67c40b2..4a78bad1a9 100644
--- a/erts/emulator/beam/jit/x86/instr_common.cpp
+++ b/erts/emulator/beam/jit/x86/instr_common.cpp
@@ -270,7 +270,7 @@ void BeamModuleAssembler::emit_normal_exit() {
     emit_proc_lc_unrequire();
 
     a.mov(x86::qword_ptr(c_p, offsetof(Process, freason)), imm(EXC_NORMAL));
-    a.mov(x86::qword_ptr(c_p, offsetof(Process, arity)), imm(0));
+    a.mov(x86::byte_ptr(c_p, offsetof(Process, arity)), imm(0));
     a.mov(ARG1, c_p);
     mov_imm(ARG2, am_normal);
     runtime_call<2>(erts_do_exit_process);
@@ -2495,8 +2495,8 @@ void BeamGlobalAssembler::emit_i_test_yield_shared() {
 
     a.lea(ARG2, x86::qword_ptr(ARG3, mfa_offset));
     a.mov(x86::qword_ptr(c_p, offsetof(Process, current)), ARG2);
-    a.mov(ARG2, x86::qword_ptr(ARG2, offsetof(ErtsCodeMFA, arity)));
-    a.mov(x86::qword_ptr(c_p, offsetof(Process, arity)), ARG2);
+    a.movzx(ARG2d, x86::byte_ptr(ARG2, offsetof(ErtsCodeMFA, arity)));
+    a.mov(x86::byte_ptr(c_p, offsetof(Process, arity)), ARG2.r8());
 
     a.jmp(labels[context_switch_simplified]);
 }
diff --git a/erts/emulator/beam/jit/x86/instr_msg.cpp b/erts/emulator/beam/jit/x86/instr_msg.cpp
index d015d3b71b..e68c7d4080 100644
--- a/erts/emulator/beam/jit/x86/instr_msg.cpp
+++ b/erts/emulator/beam/jit/x86/instr_msg.cpp
@@ -187,7 +187,7 @@ void BeamGlobalAssembler::emit_i_loop_rec_shared() {
 
         a.mov(message_ptr, imm(0));
         a.mov(ARG1, c_p);
-        a.mov(ARG2, FCALLS);
+        a.mov(ARG2d, FCALLS);
         mov_imm(ARG3, 0);
         a.lea(ARG4, message_ptr);
         a.lea(ARG5, get_out);
@@ -205,7 +205,7 @@ void BeamGlobalAssembler::emit_i_loop_rec_shared() {
          * index. */
         emit_leave_runtime<Update::eHeapAlloc | Update::eCodeIndex>();
 
-        a.sub(FCALLS, RET);
+        a.sub(FCALLS, RETd);
 
         /* Need to spill message_ptr to ARG1 as check_is_distributed uses it */
         a.mov(ARG1, message_ptr);
@@ -232,7 +232,7 @@ void BeamGlobalAssembler::emit_i_loop_rec_shared() {
         /* We either ran out of reductions or received an exit signal; schedule
          * ourselves out. The yield address (`c_p->i`) was set on ingress. */
         a.and_(x86::dword_ptr(c_p, offsetof(Process, flags)), imm(~F_DELAY_GC));
-        a.mov(x86::qword_ptr(c_p, offsetof(Process, arity)), imm(0));
+        a.mov(x86::byte_ptr(c_p, offsetof(Process, arity)), imm(0));
         a.mov(x86::qword_ptr(c_p, offsetof(Process, current)), imm(0));
 
         emit_unwind_frame();
@@ -294,10 +294,10 @@ void BeamModuleAssembler::emit_remove_message() {
     emit_enter_runtime();
 
     a.mov(ARG1, c_p);
-    a.mov(ARG2, FCALLS);
+    a.mov(ARG2d, FCALLS);
     a.mov(ARG5, active_code_ix);
     runtime_call<5>(beam_jit_remove_message);
-    a.mov(FCALLS, RET);
+    a.mov(FCALLS, RETd);
 
     emit_leave_runtime();
 }
diff --git a/erts/emulator/beam/jit/x86/instr_trace.cpp b/erts/emulator/beam/jit/x86/instr_trace.cpp
index f6d7937f4e..16f7721624 100644
--- a/erts/emulator/beam/jit/x86/instr_trace.cpp
+++ b/erts/emulator/beam/jit/x86/instr_trace.cpp
@@ -240,9 +240,8 @@ void BeamModuleAssembler::emit_i_hibernate() {
     a.test(RET, RET);
     a.je(error);
 
-    a.mov(ARG1, x86::qword_ptr(c_p, offsetof(Process, flags)));
-    a.and_(ARG1, imm(~F_HIBERNATE_SCHED));
-    a.mov(x86::qword_ptr(c_p, offsetof(Process, flags)), ARG1);
+    a.and_(x86::dword_ptr(c_p, offsetof(Process, flags)),
+           imm(~F_HIBERNATE_SCHED));
     a.jmp(resolve_fragment(ga->get_do_schedule()));
 
     a.bind(error);
diff --git a/erts/emulator/beam/jit/x86/ops.tab b/erts/emulator/beam/jit/x86/ops.tab
index 042b66dd53..696de4dee7 100644
--- a/erts/emulator/beam/jit/x86/ops.tab
+++ b/erts/emulator/beam/jit/x86/ops.tab
@@ -858,7 +858,7 @@ int_func_start Func_Label Func_Line M F A |
     func_line Func_Line |
     aligned_label Func_Label u=8 |
     i_func_info Func_Label M F A |
-      aligned_label Entry_Label u=8 |
+      aligned_label Entry_Label u=4 |
       i_breakpoint_trampoline |
       line Entry_Line |
       call_bif_mfa M F A
@@ -868,7 +868,7 @@ int_func_start Func_Label Func_Line M F A |
     func_line Func_Line |
     aligned_label Func_Label u=8 |
     i_func_info Func_Label M F A |
-      aligned_label Entry_Label u=8 |
+      aligned_label Entry_Label u=4 |
       i_breakpoint_trampoline |
       line Entry_Line |
       i_test_yield
diff --git a/erts/emulator/beam/jit/x86/process_main.cpp b/erts/emulator/beam/jit/x86/process_main.cpp
index 210aecb0c2..a40a5c0614 100644
--- a/erts/emulator/beam/jit/x86/process_main.cpp
+++ b/erts/emulator/beam/jit/x86/process_main.cpp
@@ -119,7 +119,7 @@ void BeamGlobalAssembler::emit_process_main() {
     {
         /* Figure out reds_used. def_arg_reg[5] = REDS_IN */
         a.mov(ARG3, x86::qword_ptr(c_p, offsetof(Process, def_arg_reg[5])));
-        a.sub(ARG3, FCALLS);
+        a.sub(ARG3d, FCALLS);
 
         a.jmp(schedule_next);
     }
@@ -129,8 +129,8 @@ void BeamGlobalAssembler::emit_process_main() {
     {
         Sint arity_offset = offsetof(ErtsCodeMFA, arity) - sizeof(ErtsCodeMFA);
 
-        a.mov(ARG1, x86::qword_ptr(ARG3, arity_offset));
-        a.mov(x86::qword_ptr(c_p, offsetof(Process, arity)), ARG1);
+        a.movzx(ARG1d, x86::byte_ptr(ARG3, arity_offset));
+        a.mov(x86::byte_ptr(c_p, offsetof(Process, arity)), ARG1.r8());
 
         a.lea(ARG1, x86::qword_ptr(ARG3, -(Sint)sizeof(ErtsCodeMFA)));
         a.mov(x86::qword_ptr(c_p, offsetof(Process, current)), ARG1);
@@ -182,7 +182,7 @@ void BeamGlobalAssembler::emit_process_main() {
 
             a.lea(ARG1, x86::qword_ptr(labels[process_exit]));
             a.mov(x86::qword_ptr(c_p, offsetof(Process, i)), ARG1);
-            a.mov(x86::qword_ptr(c_p, offsetof(Process, arity)), imm(0));
+            a.mov(x86::byte_ptr(c_p, offsetof(Process, arity)), imm(0));
             a.mov(x86::qword_ptr(c_p, offsetof(Process, current)), imm(0));
             a.jmp(do_schedule_local);
         }
@@ -190,17 +190,17 @@ void BeamGlobalAssembler::emit_process_main() {
 
         /* Figure out reds_used. def_arg_reg[5] = REDS_IN */
         a.mov(ARG3, x86::qword_ptr(c_p, offsetof(Process, def_arg_reg[5])));
-        a.sub(ARG3, FCALLS);
+        a.sub(ARG3d, FCALLS);
 
         /* Spill reds_used to FCALLS as we no longer need that value */
-        a.mov(FCALLS, ARG3);
+        a.mov(FCALLS, ARG3d);
 
         a.mov(ARG1, c_p);
         load_x_reg_array(ARG2);
         runtime_call<2>(copy_out_registers);
 
         /* Restore reds_used from FCALLS */
-        a.mov(ARG3, FCALLS);
+        a.mov(ARG3d, FCALLS);
 
         /* !! Fall through !! */
     }
@@ -274,11 +274,13 @@ void BeamGlobalAssembler::emit_process_main() {
         runtime_call<2>(copy_in_registers);
 
         /* Setup reduction counting */
-        a.mov(FCALLS, x86::qword_ptr(c_p, offsetof(Process, fcalls)));
-        a.mov(x86::qword_ptr(c_p, offsetof(Process, def_arg_reg[5])), FCALLS);
+        a.mov(FCALLS, x86::dword_ptr(c_p, offsetof(Process, fcalls)));
+        a.mov(x86::qword_ptr(c_p, offsetof(Process, def_arg_reg[5])),
+              FCALLS.r64());
 
 #ifdef DEBUG
-        a.mov(x86::qword_ptr(c_p, offsetof(Process, debug_reds_in)), FCALLS);
+        a.mov(x86::qword_ptr(c_p, offsetof(Process, debug_reds_in)),
+              FCALLS.r64());
 #endif
 
         /* Check whether save calls is on */
-- 
2.35.3

openSUSE Build Service is sponsored by