File 0524-Fix-spurious-badfun-exception.patch of Package erlang

From 68db01831a2621a3076e382c8b5d5ca2de51412e Mon Sep 17 00:00:00 2001
From: =?UTF-8?q?Bj=C3=B6rn=20Gustavsson?= <bjorn@erlang.org>
Date: Tue, 30 Sep 2025 13:39:38 +0200
Subject: [PATCH] Fix spurious badfun exception

---
 erts/emulator/beam/jit/arm/instr_fun.cpp   |  3 +-
 erts/emulator/beam/jit/beam_jit_common.cpp |  4 +-
 erts/emulator/beam/jit/beam_jit_common.hpp |  3 +-
 erts/emulator/beam/jit/x86/instr_fun.cpp   |  3 +-
 erts/emulator/test/fun_SUITE.erl           | 76 +++++++++++++++++++++-
 5 files changed, 82 insertions(+), 7 deletions(-)

diff --git a/erts/emulator/beam/jit/arm/instr_fun.cpp b/erts/emulator/beam/jit/arm/instr_fun.cpp
index 458538f7c6..2c5a02bdbf 100644
--- a/erts/emulator/beam/jit/arm/instr_fun.cpp
+++ b/erts/emulator/beam/jit/arm/instr_fun.cpp
@@ -42,7 +42,8 @@ void BeamGlobalAssembler::emit_unloaded_fun() {
     load_x_reg_array(ARG2);
     a.lsr(ARG3, ARG3, imm(FUN_HEADER_ARITY_OFFS));
     /* ARG4 has already been set. */
-    runtime_call<4>(beam_jit_handle_unloaded_fun);
+    a.mov(ARG5, active_code_ix);
+    runtime_call<5>(beam_jit_handle_unloaded_fun);
 
     emit_leave_runtime<Update::eHeapAlloc | Update::eXRegs |
                        Update::eReductions | Update::eCodeIndex>();
diff --git a/erts/emulator/beam/jit/beam_jit_common.cpp b/erts/emulator/beam/jit/beam_jit_common.cpp
index aac4239485..d32f513d13 100644
--- a/erts/emulator/beam/jit/beam_jit_common.cpp
+++ b/erts/emulator/beam/jit/beam_jit_common.cpp
@@ -1284,8 +1284,8 @@ Eterm beam_jit_build_argument_list(Process *c_p, const Eterm *regs, int arity) {
 Export *beam_jit_handle_unloaded_fun(Process *c_p,
                                      Eterm *reg,
                                      int arity,
-                                     Eterm fun_thing) {
-    ErtsCodeIndex code_ix = erts_active_code_ix();
+                                     Eterm fun_thing,
+                                     ErtsCodeIndex code_ix) {
     Eterm module, args;
     ErlFunThing *funp;
     ErlFunEntry *fe;
diff --git a/erts/emulator/beam/jit/beam_jit_common.hpp b/erts/emulator/beam/jit/beam_jit_common.hpp
index 71fe634e8f..87d5588083 100644
--- a/erts/emulator/beam/jit/beam_jit_common.hpp
+++ b/erts/emulator/beam/jit/beam_jit_common.hpp
@@ -654,7 +654,8 @@ Eterm beam_jit_build_argument_list(Process *c_p, const Eterm *regs, int arity);
 Export *beam_jit_handle_unloaded_fun(Process *c_p,
                                      Eterm *reg,
                                      int arity,
-                                     Eterm fun_thing);
+                                     Eterm fun_thing,
+                                     ErtsCodeIndex code_ix);
 
 bool beam_jit_is_list_of_immediates(Eterm term);
 bool beam_jit_is_shallow_boxed(Eterm term);
diff --git a/erts/emulator/beam/jit/x86/instr_fun.cpp b/erts/emulator/beam/jit/x86/instr_fun.cpp
index 29afe3d318..db6751e68f 100644
--- a/erts/emulator/beam/jit/x86/instr_fun.cpp
+++ b/erts/emulator/beam/jit/x86/instr_fun.cpp
@@ -38,7 +38,8 @@ void BeamGlobalAssembler::emit_unloaded_fun() {
     load_x_reg_array(ARG2);
     a.shr(ARG3, imm(FUN_HEADER_ARITY_OFFS));
     /* ARG4 has already been set. */
-    runtime_call<4>(beam_jit_handle_unloaded_fun);
+    a.mov(ARG5, active_code_ix);
+    runtime_call<5>(beam_jit_handle_unloaded_fun);
 
     emit_leave_runtime<Update::eHeapAlloc | Update::eReductions |
                        Update::eCodeIndex>();
diff --git a/erts/emulator/test/fun_SUITE.erl b/erts/emulator/test/fun_SUITE.erl
index 8f8a282feb..9b916a4b63 100644
--- a/erts/emulator/test/fun_SUITE.erl
+++ b/erts/emulator/test/fun_SUITE.erl
@@ -28,10 +28,14 @@
 	 fun_to_port/1,t_phash/1,t_phash2/1,md5/1,
 	 refc/1,refc_ets/1,refc_dist/1,
 	 const_propagation/1,t_arity/1,t_is_function2/1,
-	 t_fun_info/1,t_fun_info_mfa/1,t_fun_to_list/1]).
+	 t_fun_info/1,t_fun_info_mfa/1,t_fun_to_list/1,
+         spurious_badfun/1]).
 
 -export([nothing/0]).
 
+%% Callback for a process that uses this module as an error_handler module.
+-export([undefined_lambda/3]).
+
 -include_lib("common_test/include/ct.hrl").
 
 suite() ->
@@ -45,7 +49,8 @@ all() ->
      equality, ordering, fun_to_port, t_phash,
      t_phash2, md5, refc, refc_ets, refc_dist,
      const_propagation, t_arity, t_is_function2, t_fun_info,
-     t_fun_info_mfa,t_fun_to_list].
+     t_fun_info_mfa,t_fun_to_list,
+     spurious_badfun].
 
 init_per_testcase(_TestCase, Config) ->
     Config.
@@ -902,6 +907,73 @@ verify_not_undef(Fun, Tag) ->
 	{Tag,_} -> ok
     end.
 
+%% Test for a race condition that occurred when multiple processes
+%% attempted to a call a fun whose defining module was not loaded.
+spurious_badfun(Config) ->
+    Mod = ?FUNCTION_NAME,
+    Dir = proplists:get_value(priv_dir, Config),
+    File = filename:join(Dir, atom_to_list(Mod) ++ ".erl"),
+
+    Code = ~"""
+    -module(spurious_badfun).
+    -export([factory/0]).
+    factory() ->
+        fun() -> ok end.
+    """,
+
+    ok = file:write_file(File, Code),
+
+    {ok,Mod,Bin} = compile:file(File, [binary]),
+    {module,Mod} = erlang:load_module(Mod, Bin),
+    Fun = Mod:factory(),
+
+    do_spurious_badfun(1000, Mod, Bin, Fun).
+
+do_spurious_badfun(0, _Mod, _Bin, _Fun) ->
+    ok;
+do_spurious_badfun(N, Mod, Bin, Fun) ->
+    _ = catch erlang:purge_module(Mod),
+    _ = erlang:delete_module(Mod),
+    _ = catch erlang:purge_module(Mod),
+
+    Prepared = erlang:prepare_loading(Mod, Bin),
+
+    {Pid,Ref} = spawn_monitor(fun() -> call_fun(Fun) end),
+
+    ok = erlang:finish_loading([Prepared]),
+
+    receive
+        {'DOWN',Ref,process,Pid,Result} ->
+            normal = Result,
+            do_spurious_badfun(N-1, Mod, Bin, Fun)
+    end.
+
+call_fun(Fun) ->
+    %% Set up the current module as the error_handler for the current
+    %% process.
+    process_flag(error_handler, ?MODULE),
+
+    %% With the JIT, the following call would sometimes fail with a
+    %% `badfun` exeception. The reason is that the native code and the
+    %% C function beam_jit_handle_unloaded_fun() handling an unloaded
+    %% fun would use different code indexes. The native code would
+    %% "think" that the module for the fun was not loaded, while
+    %% beam_jit_handle_unloaded_fun() function would "think" that the
+    %% module was loaded and raise a badfun exception.
+    Fun().
+
+%% This is the error_handler callback for the process that is calling
+%% the fun.
+undefined_lambda(_Module, Fun, Args) ->
+    %% If the parent process has finished loading the module, the
+    %% following apply/2 call will succeed. Otherwise, this function
+    %% will be called again.
+    apply(Fun, Args).
+
+%%%
+%%% Common utilities.
+%%%
+
 id(X) ->
     X.
 
-- 
2.51.0

openSUSE Build Service is sponsored by