Skip to content

Commit d3003db

Browse files
committed
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.
1 parent 5622305 commit d3003db

File tree

5 files changed

+87
-9
lines changed

5 files changed

+87
-9
lines changed

erts/emulator/beam/jit/arm/instr_fun.cpp

Lines changed: 5 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -44,8 +44,11 @@ void BeamGlobalAssembler::emit_unloaded_fun() {
4444
load_x_reg_array(ARG2);
4545
a.lsr(ARG3, ARG3, imm(FUN_HEADER_ARITY_OFFS));
4646
/* ARG4 has already been set. */
47-
runtime_call<const Export *(*)(Process *, Eterm *, int, Eterm),
48-
beam_jit_handle_unloaded_fun>();
47+
a.mov(ARG5, active_code_ix);
48+
49+
runtime_call<
50+
const Export *(*)(Process *, Eterm *, int, Eterm, ErtsCodeIndex),
51+
beam_jit_handle_unloaded_fun>();
4952

5053
emit_leave_runtime<Update::eHeapAlloc | Update::eXRegs |
5154
Update::eReductions | Update::eCodeIndex>();

erts/emulator/beam/jit/beam_jit_common.cpp

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -1302,8 +1302,8 @@ Eterm beam_jit_build_argument_list(Process *c_p, const Eterm *regs, int arity) {
13021302
const Export *beam_jit_handle_unloaded_fun(Process *c_p,
13031303
Eterm *reg,
13041304
int arity,
1305-
Eterm fun_thing) {
1306-
const ErtsCodeIndex code_ix = erts_active_code_ix();
1305+
Eterm fun_thing,
1306+
ErtsCodeIndex code_ix) {
13071307
const ErlFunEntry *fe;
13081308
const Export *ep;
13091309
Eterm module, args;

erts/emulator/beam/jit/beam_jit_common.hpp

Lines changed: 2 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -651,7 +651,8 @@ Eterm beam_jit_build_argument_list(Process *c_p, const Eterm *regs, int arity);
651651
const Export *beam_jit_handle_unloaded_fun(Process *c_p,
652652
Eterm *reg,
653653
int arity,
654-
Eterm fun_thing);
654+
Eterm fun_thing,
655+
ErtsCodeIndex code_ix);
655656

656657
bool beam_jit_is_list_of_immediates(Eterm term);
657658
bool beam_jit_is_shallow_boxed(Eterm term);

erts/emulator/beam/jit/x86/instr_fun.cpp

Lines changed: 4 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -40,9 +40,11 @@ void BeamGlobalAssembler::emit_unloaded_fun() {
4040
load_x_reg_array(ARG2);
4141
a.shr(ARG3, imm(FUN_HEADER_ARITY_OFFS));
4242
/* ARG4 has already been set. */
43+
a.mov(ARG5, active_code_ix);
4344

44-
runtime_call<const Export *(*)(Process *, Eterm *, int, Eterm),
45-
beam_jit_handle_unloaded_fun>();
45+
runtime_call<
46+
const Export *(*)(Process *, Eterm *, int, Eterm, ErtsCodeIndex),
47+
beam_jit_handle_unloaded_fun>();
4648

4749
emit_leave_runtime<Update::eHeapAlloc | Update::eReductions |
4850
Update::eCodeIndex>();

erts/emulator/test/fun_SUITE.erl

Lines changed: 74 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -29,10 +29,14 @@
2929
equality/1,ordering/1,
3030
fun_to_port/1,t_phash/1,t_phash2/1,md5/1,
3131
const_propagation/1,t_arity/1,t_is_function2/1,
32-
t_fun_info/1,t_fun_info_mfa/1,t_fun_to_list/1]).
32+
t_fun_info/1,t_fun_info_mfa/1,t_fun_to_list/1,
33+
spurious_badfun/1]).
3334

3435
-export([nothing/0]).
3536

37+
%% Callback for a process that uses this module as an error_handler module.
38+
-export([undefined_lambda/3]).
39+
3640
-include_lib("common_test/include/ct.hrl").
3741

3842
suite() ->
@@ -46,7 +50,8 @@ all() ->
4650
equality, ordering, fun_to_port, t_phash,
4751
t_phash2, md5,
4852
const_propagation, t_arity, t_is_function2, t_fun_info,
49-
t_fun_info_mfa,t_fun_to_list].
53+
t_fun_info_mfa,t_fun_to_list,
54+
spurious_badfun].
5055

5156
init_per_testcase(_TestCase, Config) ->
5257
Config.
@@ -743,6 +748,73 @@ verify_not_undef(Fun, Tag) ->
743748
{Tag,_} -> ok
744749
end.
745750

751+
%% Test for a race condition that occurred when multiple processes
752+
%% attempted to a call a fun whose defining module was not loaded.
753+
spurious_badfun(Config) ->
754+
Mod = ?FUNCTION_NAME,
755+
Dir = proplists:get_value(priv_dir, Config),
756+
File = filename:join(Dir, atom_to_list(Mod) ++ ".erl"),
757+
758+
Code = ~"""
759+
-module(spurious_badfun).
760+
-export([factory/0]).
761+
factory() ->
762+
fun() -> ok end.
763+
""",
764+
765+
ok = file:write_file(File, Code),
766+
767+
{ok,Mod,Bin} = compile:file(File, [binary]),
768+
{module,Mod} = erlang:load_module(Mod, Bin),
769+
Fun = Mod:factory(),
770+
771+
do_spurious_badfun(1000, Mod, Bin, Fun).
772+
773+
do_spurious_badfun(0, _Mod, _Bin, _Fun) ->
774+
ok;
775+
do_spurious_badfun(N, Mod, Bin, Fun) ->
776+
_ = catch erlang:purge_module(Mod),
777+
_ = erlang:delete_module(Mod),
778+
_ = catch erlang:purge_module(Mod),
779+
780+
Prepared = erlang:prepare_loading(Mod, Bin),
781+
782+
{Pid,Ref} = spawn_monitor(fun() -> call_fun(Fun) end),
783+
784+
ok = erlang:finish_loading([Prepared]),
785+
786+
receive
787+
{'DOWN',Ref,process,Pid,Result} ->
788+
normal = Result,
789+
do_spurious_badfun(N-1, Mod, Bin, Fun)
790+
end.
791+
792+
call_fun(Fun) ->
793+
%% Set up the current module as the error_handler for the current
794+
%% process.
795+
process_flag(error_handler, ?MODULE),
796+
797+
%% With the JIT, the following call would sometimes fail with a
798+
%% `badfun` exeception. The reason is that the native code and the
799+
%% C function beam_jit_handle_unloaded_fun() handling an unloaded
800+
%% fun would use different code indexes. The native code would
801+
%% "think" that the module for the fun was not loaded, while
802+
%% beam_jit_handle_unloaded_fun() function would "think" that the
803+
%% module was loaded and raise a badfun exception.
804+
Fun().
805+
806+
%% This is the error_handler callback for the process that is calling
807+
%% the fun.
808+
undefined_lambda(_Module, Fun, Args) ->
809+
%% If the parent process has finished loading the module, the
810+
%% following apply/2 call will succeed. Otherwise, this function
811+
%% will be called again.
812+
apply(Fun, Args).
813+
814+
%%%
815+
%%% Common utilities.
816+
%%%
817+
746818
id(X) ->
747819
X.
748820

0 commit comments

Comments
 (0)