File 0169-Fix-spurious-badfun-exception.patch of Package erlang
From d3003dbd1dcdd100885b8c923a6a8eb7a63d9514 Mon Sep 17 00:00:00 2001
From: =?UTF-8?q?Bj=C3=B6rn=20Gustavsson?= <bjorn@erlang.org>
Date: Mon, 29 Sep 2025 15:09:58 +0200
Subject: [PATCH] Fix spurious badfun exception
When multiple processes called the same fun whose defining module
was not loaded, a `badfun` exception could sometimes occcur in
one of the calling processes. This would only happen with the JIT
runtime system.
---
erts/emulator/beam/jit/arm/instr_fun.cpp | 7 +-
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 | 6 +-
erts/emulator/test/fun_SUITE.erl | 76 +++++++++++++++++++++-
5 files changed, 87 insertions(+), 9 deletions(-)
diff --git a/erts/emulator/beam/jit/arm/instr_fun.cpp b/erts/emulator/beam/jit/arm/instr_fun.cpp
index 203834d4be..a5bbb6f57a 100644
--- a/erts/emulator/beam/jit/arm/instr_fun.cpp
+++ b/erts/emulator/beam/jit/arm/instr_fun.cpp
@@ -44,8 +44,11 @@ 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<const Export *(*)(Process *, Eterm *, int, Eterm),
- beam_jit_handle_unloaded_fun>();
+ a.mov(ARG5, active_code_ix);
+
+ runtime_call<
+ const Export *(*)(Process *, Eterm *, int, Eterm, ErtsCodeIndex),
+ 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 f0f12e340f..fe629d3107 100644
--- a/erts/emulator/beam/jit/beam_jit_common.cpp
+++ b/erts/emulator/beam/jit/beam_jit_common.cpp
@@ -1302,8 +1302,8 @@ Eterm beam_jit_build_argument_list(Process *c_p, const Eterm *regs, int arity) {
const Export *beam_jit_handle_unloaded_fun(Process *c_p,
Eterm *reg,
int arity,
- Eterm fun_thing) {
- const ErtsCodeIndex code_ix = erts_active_code_ix();
+ Eterm fun_thing,
+ ErtsCodeIndex code_ix) {
const ErlFunEntry *fe;
const Export *ep;
Eterm module, args;
diff --git a/erts/emulator/beam/jit/beam_jit_common.hpp b/erts/emulator/beam/jit/beam_jit_common.hpp
index c0d0a9800c..a005560257 100644
--- a/erts/emulator/beam/jit/beam_jit_common.hpp
+++ b/erts/emulator/beam/jit/beam_jit_common.hpp
@@ -651,7 +651,8 @@ Eterm beam_jit_build_argument_list(Process *c_p, const Eterm *regs, int arity);
const 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 e57d5f360e..53416576fe 100644
--- a/erts/emulator/beam/jit/x86/instr_fun.cpp
+++ b/erts/emulator/beam/jit/x86/instr_fun.cpp
@@ -40,9 +40,11 @@ void BeamGlobalAssembler::emit_unloaded_fun() {
load_x_reg_array(ARG2);
a.shr(ARG3, imm(FUN_HEADER_ARITY_OFFS));
/* ARG4 has already been set. */
+ a.mov(ARG5, active_code_ix);
- runtime_call<const Export *(*)(Process *, Eterm *, int, Eterm),
- beam_jit_handle_unloaded_fun>();
+ runtime_call<
+ const Export *(*)(Process *, Eterm *, int, Eterm, ErtsCodeIndex),
+ 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 b6d00c00a8..9e76badd9b 100644
--- a/erts/emulator/test/fun_SUITE.erl
+++ b/erts/emulator/test/fun_SUITE.erl
@@ -29,10 +29,14 @@
equality/1,ordering/1,
fun_to_port/1,t_phash/1,t_phash2/1,md5/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() ->
@@ -46,7 +50,8 @@ all() ->
equality, ordering, fun_to_port, t_phash,
t_phash2, md5,
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.
@@ -743,6 +748,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