Skip to content

Commit 2a38cd6

Browse files
committed
Merge branch 'john/erts/fix-call_error_handler-crash/OTP-19577/ERIERL-1220' into john/erts/fix-call_error_handler-crash-26/OTP-19577/ERIERL-1220
* john/erts/fix-call_error_handler-crash/OTP-19577/ERIERL-1220: erts: Fix crash when invoking non-existent error_handler
2 parents 412bff5 + 8815c05 commit 2a38cd6

File tree

5 files changed

+57
-69
lines changed

5 files changed

+57
-69
lines changed

erts/emulator/beam/beam_common.c

Lines changed: 7 additions & 60 deletions
Original file line numberDiff line numberDiff line change
@@ -1322,46 +1322,6 @@ call_error_handler(Process* p, const ErtsCodeMFA *mfa, Eterm* reg, Eterm func)
13221322
return ep;
13231323
}
13241324

1325-
static Export*
1326-
apply_setup_error_handler(Process* p, Eterm module, Eterm function, Uint arity, Eterm* reg)
1327-
{
1328-
Export* ep;
1329-
1330-
/*
1331-
* Find the export table index for the error handler. Return NULL if
1332-
* there is no error handler module.
1333-
*/
1334-
1335-
if ((ep = erts_active_export_entry(erts_proc_get_error_handler(p),
1336-
am_undefined_function, 3)) == NULL) {
1337-
return NULL;
1338-
} else {
1339-
int i;
1340-
Uint sz = 2*arity;
1341-
Eterm* hp;
1342-
Eterm args = NIL;
1343-
1344-
/*
1345-
* Always copy args from registers to a new list; this ensures
1346-
* that we have the same behaviour whether or not this was
1347-
* called from apply or fixed_apply (any additional last
1348-
* THIS-argument will be included, assuming that arity has been
1349-
* properly adjusted).
1350-
*/
1351-
1352-
hp = HAlloc(p, sz);
1353-
for (i = arity-1; i >= 0; i--) {
1354-
args = CONS(hp, reg[i], args);
1355-
hp += 2;
1356-
}
1357-
reg[0] = module;
1358-
reg[1] = function;
1359-
reg[2] = args;
1360-
}
1361-
1362-
return ep;
1363-
}
1364-
13651325
static ERTS_INLINE void
13661326
apply_bif_error_adjustment(Process *p, Export *ep,
13671327
Eterm *reg, Uint arity,
@@ -1536,18 +1496,13 @@ apply(Process* p, Eterm* reg, ErtsCodePtr I, Uint stack_offset)
15361496
goto error;
15371497
}
15381498

1539-
/*
1540-
* Get the index into the export table, or failing that the export
1541-
* entry for the error handler.
1542-
*
1543-
* Note: All BIFs have export entries; thus, no special case is needed.
1544-
*/
1499+
/* Call the referenced function, if any: should the function not be found,
1500+
* create a stub entry which in turn calls the error handler. */
1501+
ep = erts_export_get_or_make_stub(module, function, arity);
15451502

1546-
if ((ep = erts_active_export_entry(module, function, arity)) == NULL) {
1547-
if ((ep = apply_setup_error_handler(p, module, function, arity, reg)) == NULL) goto error;
1548-
}
15491503
apply_bif_error_adjustment(p, ep, reg, arity, I, stack_offset);
15501504
DTRACE_GLOBAL_CALL_FROM_EXPORT(p, ep);
1505+
15511506
return ep;
15521507
}
15531508

@@ -1582,17 +1537,9 @@ fixed_apply(Process* p, Eterm* reg, Uint arity,
15821537
return apply(p, reg, I, stack_offset);
15831538
}
15841539

1585-
/*
1586-
* Get the index into the export table, or failing that the export
1587-
* entry for the error handler module.
1588-
*
1589-
* Note: All BIFs have export entries; thus, no special case is needed.
1590-
*/
1591-
1592-
if ((ep = erts_active_export_entry(module, function, arity)) == NULL) {
1593-
if ((ep = apply_setup_error_handler(p, module, function, arity, reg)) == NULL)
1594-
goto error;
1595-
}
1540+
/* Call the referenced function, if any: should the function not be found,
1541+
* create a stub entry which in turn calls the error handler. */
1542+
ep = erts_export_get_or_make_stub(module, function, arity);
15961543

15971544
apply_bif_error_adjustment(p, ep, reg, arity, I, stack_offset);
15981545
DTRACE_GLOBAL_CALL_FROM_EXPORT(p, ep);

erts/emulator/beam/emu/beam_emu.c

Lines changed: 9 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -531,19 +531,25 @@ void process_main(ErtsSchedulerData *esdp)
531531
* code[3]: &&call_error_handler
532532
* code[4]: Not used
533533
*/
534+
const ErtsCodeMFA *mfa;
534535
Export *error_handler;
535536

536537
HEAVY_SWAPOUT;
537-
error_handler = call_error_handler(c_p, erts_code_to_codemfa(I),
538-
reg, am_undefined_function);
538+
mfa = erts_code_to_codemfa(I);
539+
error_handler = call_error_handler(c_p,
540+
mfa,
541+
reg,
542+
am_undefined_function);
539543
HEAVY_SWAPIN;
540544

541545
if (error_handler) {
542546
I = error_handler->dispatch.addresses[erts_active_code_ix()];
543547
Goto(*I);
544548
}
549+
550+
I = handle_error(c_p, I, reg, mfa);
551+
goto post_error_handling;
545552
}
546-
/* Fall through */
547553
OpCase(error_action_code): {
548554
handle_error:
549555
SWAPOUT;

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

Lines changed: 6 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -209,12 +209,15 @@ void BeamGlobalAssembler::emit_export_trampoline() {
209209

210210
a.bind(error_handler);
211211
{
212+
lea(ARG2, arm::Mem(ARG1, offsetof(Export, info.mfa)));
213+
a.str(ARG2, TMP_MEM1q);
214+
212215
emit_enter_runtime_frame();
213216
emit_enter_runtime<Update::eReductions | Update::eHeapAlloc |
214217
Update::eXRegs>();
215218

216-
lea(ARG2, arm::Mem(ARG1, offsetof(Export, info.mfa)));
217219
a.mov(ARG1, c_p);
220+
/* ARG2 set above */
218221
load_x_reg_array(ARG3);
219222
mov_imm(ARG4, am_undefined_function);
220223
runtime_call<4>(call_error_handler);
@@ -225,7 +228,8 @@ void BeamGlobalAssembler::emit_export_trampoline() {
225228
Update::eXRegs>();
226229
emit_leave_runtime_frame();
227230

228-
a.cbz(ARG1, labels[process_exit]);
231+
a.ldr(ARG4, TMP_MEM1q);
232+
a.cbz(ARG1, labels[raise_exception]);
229233

230234
branch(emit_setup_dispatchable_call(ARG1));
231235
}

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

Lines changed: 7 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -210,21 +210,24 @@ void BeamGlobalAssembler::emit_export_trampoline() {
210210

211211
a.bind(error_handler);
212212
{
213+
a.lea(ARG2, x86::qword_ptr(RET, offsetof(Export, info.mfa)));
214+
a.mov(TMP_MEM1q, ARG2);
215+
213216
emit_enter_frame();
214217
emit_enter_runtime<Update::eReductions | Update::eHeapAlloc>();
215218

216219
a.mov(ARG1, c_p);
217-
a.lea(ARG2, x86::qword_ptr(RET, offsetof(Export, info.mfa)));
220+
/* ARG2 set above */
218221
load_x_reg_array(ARG3);
219222
mov_imm(ARG4, am_undefined_function);
220223
runtime_call<4>(call_error_handler);
221224

222225
emit_leave_runtime<Update::eReductions | Update::eHeapAlloc>();
226+
emit_leave_frame();
223227

228+
a.mov(ARG4, TMP_MEM1q);
224229
a.test(RET, RET);
225-
a.je(labels[process_exit]);
226-
227-
emit_leave_frame();
230+
a.je(labels[raise_exception]);
228231
a.jmp(emit_setup_dispatchable_call(RET));
229232
}
230233
}

erts/emulator/test/hello_SUITE_data/hello.erl

Lines changed: 28 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -772,6 +772,34 @@ test_apply_errors() ->
772772
[{M,whatever,[42],_}|_] = Stk2
773773
end,
774774

775+
%% ERIERL-1220: Set a bad error handler on purpose, this used to crash the
776+
%% emulator.
777+
erlang:process_flag(error_handler, this_module_does_not_exist),
778+
779+
try known_bad_module:whatever(42) of
780+
_ ->
781+
error(expected_failure)
782+
catch
783+
error:undef:Stk3 ->
784+
[{known_bad_module,whatever,[42],_}|_] = Stk3
785+
end,
786+
787+
try M:whatever(42) of
788+
_ ->
789+
error(expected_failure)
790+
catch
791+
error:undef:Stk4 ->
792+
[{bad_module,whatever,[42],_}|_] = Stk4
793+
end,
794+
795+
try apply(M, whatever, id([42])) of
796+
_ ->
797+
error(expected_failure)
798+
catch
799+
error:undef:Stk5 ->
800+
[{bad_module,whatever,[42],_}|_] = Stk5
801+
end,
802+
775803
erlang:process_flag(error_handler, OldErrorHandler),
776804
ok.
777805

0 commit comments

Comments
 (0)