Skip to content

Commit 0109edc

Browse files
author
Erlang/OTP
committed
Merge branch 'bjorn/erts/spurious-badfun/27/OTP-19803' into maint-27
* bjorn/erts/spurious-badfun/27/OTP-19803: Fix spurious badfun exception
2 parents dbca62f + 68db018 commit 0109edc

File tree

5 files changed

+82
-7
lines changed

5 files changed

+82
-7
lines changed

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

Lines changed: 2 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -42,7 +42,8 @@ void BeamGlobalAssembler::emit_unloaded_fun() {
4242
load_x_reg_array(ARG2);
4343
a.lsr(ARG3, ARG3, imm(FUN_HEADER_ARITY_OFFS));
4444
/* ARG4 has already been set. */
45-
runtime_call<4>(beam_jit_handle_unloaded_fun);
45+
a.mov(ARG5, active_code_ix);
46+
runtime_call<5>(beam_jit_handle_unloaded_fun);
4647

4748
emit_leave_runtime<Update::eHeapAlloc | Update::eXRegs |
4849
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
@@ -1284,8 +1284,8 @@ Eterm beam_jit_build_argument_list(Process *c_p, const Eterm *regs, int arity) {
12841284
Export *beam_jit_handle_unloaded_fun(Process *c_p,
12851285
Eterm *reg,
12861286
int arity,
1287-
Eterm fun_thing) {
1288-
ErtsCodeIndex code_ix = erts_active_code_ix();
1287+
Eterm fun_thing,
1288+
ErtsCodeIndex code_ix) {
12891289
Eterm module, args;
12901290
ErlFunThing *funp;
12911291
ErlFunEntry *fe;

erts/emulator/beam/jit/beam_jit_common.hpp

Lines changed: 2 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -654,7 +654,8 @@ Eterm beam_jit_build_argument_list(Process *c_p, const Eterm *regs, int arity);
654654
Export *beam_jit_handle_unloaded_fun(Process *c_p,
655655
Eterm *reg,
656656
int arity,
657-
Eterm fun_thing);
657+
Eterm fun_thing,
658+
ErtsCodeIndex code_ix);
658659

659660
bool beam_jit_is_list_of_immediates(Eterm term);
660661
bool beam_jit_is_shallow_boxed(Eterm term);

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

Lines changed: 2 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -38,7 +38,8 @@ void BeamGlobalAssembler::emit_unloaded_fun() {
3838
load_x_reg_array(ARG2);
3939
a.shr(ARG3, imm(FUN_HEADER_ARITY_OFFS));
4040
/* ARG4 has already been set. */
41-
runtime_call<4>(beam_jit_handle_unloaded_fun);
41+
a.mov(ARG5, active_code_ix);
42+
runtime_call<5>(beam_jit_handle_unloaded_fun);
4243

4344
emit_leave_runtime<Update::eHeapAlloc | Update::eReductions |
4445
Update::eCodeIndex>();

erts/emulator/test/fun_SUITE.erl

Lines changed: 74 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -28,10 +28,14 @@
2828
fun_to_port/1,t_phash/1,t_phash2/1,md5/1,
2929
refc/1,refc_ets/1,refc_dist/1,
3030
const_propagation/1,t_arity/1,t_is_function2/1,
31-
t_fun_info/1,t_fun_info_mfa/1,t_fun_to_list/1]).
31+
t_fun_info/1,t_fun_info_mfa/1,t_fun_to_list/1,
32+
spurious_badfun/1]).
3233

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

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

3741
suite() ->
@@ -45,7 +49,8 @@ all() ->
4549
equality, ordering, fun_to_port, t_phash,
4650
t_phash2, md5, refc, refc_ets, refc_dist,
4751
const_propagation, t_arity, t_is_function2, t_fun_info,
48-
t_fun_info_mfa,t_fun_to_list].
52+
t_fun_info_mfa,t_fun_to_list,
53+
spurious_badfun].
4954

5055
init_per_testcase(_TestCase, Config) ->
5156
Config.
@@ -902,6 +907,73 @@ verify_not_undef(Fun, Tag) ->
902907
{Tag,_} -> ok
903908
end.
904909

910+
%% Test for a race condition that occurred when multiple processes
911+
%% attempted to a call a fun whose defining module was not loaded.
912+
spurious_badfun(Config) ->
913+
Mod = ?FUNCTION_NAME,
914+
Dir = proplists:get_value(priv_dir, Config),
915+
File = filename:join(Dir, atom_to_list(Mod) ++ ".erl"),
916+
917+
Code = ~"""
918+
-module(spurious_badfun).
919+
-export([factory/0]).
920+
factory() ->
921+
fun() -> ok end.
922+
""",
923+
924+
ok = file:write_file(File, Code),
925+
926+
{ok,Mod,Bin} = compile:file(File, [binary]),
927+
{module,Mod} = erlang:load_module(Mod, Bin),
928+
Fun = Mod:factory(),
929+
930+
do_spurious_badfun(1000, Mod, Bin, Fun).
931+
932+
do_spurious_badfun(0, _Mod, _Bin, _Fun) ->
933+
ok;
934+
do_spurious_badfun(N, Mod, Bin, Fun) ->
935+
_ = catch erlang:purge_module(Mod),
936+
_ = erlang:delete_module(Mod),
937+
_ = catch erlang:purge_module(Mod),
938+
939+
Prepared = erlang:prepare_loading(Mod, Bin),
940+
941+
{Pid,Ref} = spawn_monitor(fun() -> call_fun(Fun) end),
942+
943+
ok = erlang:finish_loading([Prepared]),
944+
945+
receive
946+
{'DOWN',Ref,process,Pid,Result} ->
947+
normal = Result,
948+
do_spurious_badfun(N-1, Mod, Bin, Fun)
949+
end.
950+
951+
call_fun(Fun) ->
952+
%% Set up the current module as the error_handler for the current
953+
%% process.
954+
process_flag(error_handler, ?MODULE),
955+
956+
%% With the JIT, the following call would sometimes fail with a
957+
%% `badfun` exeception. The reason is that the native code and the
958+
%% C function beam_jit_handle_unloaded_fun() handling an unloaded
959+
%% fun would use different code indexes. The native code would
960+
%% "think" that the module for the fun was not loaded, while
961+
%% beam_jit_handle_unloaded_fun() function would "think" that the
962+
%% module was loaded and raise a badfun exception.
963+
Fun().
964+
965+
%% This is the error_handler callback for the process that is calling
966+
%% the fun.
967+
undefined_lambda(_Module, Fun, Args) ->
968+
%% If the parent process has finished loading the module, the
969+
%% following apply/2 call will succeed. Otherwise, this function
970+
%% will be called again.
971+
apply(Fun, Args).
972+
973+
%%%
974+
%%% Common utilities.
975+
%%%
976+
905977
id(X) ->
906978
X.
907979

0 commit comments

Comments
 (0)