Skip to content

Commit 8815c05

Browse files
committed
erts: Fix crash when invoking non-existent error_handler
1 parent 0418c10 commit 8815c05

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
@@ -1323,46 +1323,6 @@ call_error_handler(Process* p, const ErtsCodeMFA *mfa, Eterm* reg, Eterm func)
13231323
return ep;
13241324
}
13251325

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

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

1547-
if ((ep = erts_active_export_entry(module, function, arity)) == NULL) {
1548-
if ((ep = apply_setup_error_handler(p, module, function, arity, reg)) == NULL) goto error;
1549-
}
15501504
apply_bif_error_adjustment(p, ep, reg, arity, I, stack_offset);
15511505
DTRACE_GLOBAL_CALL_FROM_EXPORT(p, ep);
1506+
15521507
return ep;
15531508
}
15541509

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

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

15981545
apply_bif_error_adjustment(p, ep, reg, arity, I, stack_offset);
15991546
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
@@ -529,19 +529,25 @@ void process_main(ErtsSchedulerData *esdp)
529529
* code[3]: &&call_error_handler
530530
* code[4]: Not used
531531
*/
532+
const ErtsCodeMFA *mfa;
532533
Export *error_handler;
533534

534535
HEAVY_SWAPOUT;
535-
error_handler = call_error_handler(c_p, erts_code_to_codemfa(I),
536-
reg, am_undefined_function);
536+
mfa = erts_code_to_codemfa(I);
537+
error_handler = call_error_handler(c_p,
538+
mfa,
539+
reg,
540+
am_undefined_function);
537541
HEAVY_SWAPIN;
538542

539543
if (error_handler) {
540544
I = error_handler->dispatch.addresses[erts_active_code_ix()];
541545
Goto(*I);
542546
}
547+
548+
I = handle_error(c_p, I, reg, mfa);
549+
goto post_error_handling;
543550
}
544-
/* Fall through */
545551
OpCase(error_action_code): {
546552
handle_error:
547553
SWAPOUT;

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

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

208208
a.bind(error_handler);
209209
{
210+
lea(ARG2, arm::Mem(ARG1, offsetof(Export, info.mfa)));
211+
a.str(ARG2, TMP_MEM1q);
212+
210213
emit_enter_runtime_frame();
211214
emit_enter_runtime<Update::eReductions | Update::eStack |
212215
Update::eHeap | Update::eXRegs>();
213216

214-
lea(ARG2, arm::Mem(ARG1, offsetof(Export, info.mfa)));
215217
a.mov(ARG1, c_p);
218+
/* ARG2 set above */
216219
load_x_reg_array(ARG3);
217220
mov_imm(ARG4, am_undefined_function);
218221
runtime_call<4>(call_error_handler);
@@ -223,7 +226,8 @@ void BeamGlobalAssembler::emit_export_trampoline() {
223226
Update::eHeap | Update::eXRegs>();
224227
emit_leave_runtime_frame();
225228

226-
a.cbz(ARG1, labels[process_exit]);
229+
a.ldr(ARG4, TMP_MEM1q);
230+
a.cbz(ARG1, labels[raise_exception]);
227231

228232
branch(emit_setup_dispatchable_call(ARG1));
229233
}

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

Lines changed: 7 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -208,23 +208,26 @@ void BeamGlobalAssembler::emit_export_trampoline() {
208208

209209
a.bind(error_handler);
210210
{
211+
a.lea(ARG2, x86::qword_ptr(RET, offsetof(Export, info.mfa)));
212+
a.mov(TMP_MEM1q, ARG2);
213+
211214
emit_enter_frame();
212215
emit_enter_runtime<Update::eReductions | Update::eStack |
213216
Update::eHeap>();
214217

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

221224
emit_leave_runtime<Update::eReductions | Update::eStack |
222225
Update::eHeap>();
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)