Skip to content

Commit cdd2fce

Browse files
author
Erlang/OTP
committed
Merge branch 'john/erts/fix-call_error_handler-crash-26/OTP-19577/ERIERL-1220' into maint-27
* john/erts/fix-call_error_handler-crash-26/OTP-19577/ERIERL-1220: erts: Fix 8815c05 for emu and non-native stack erts: Fix crash when invoking non-existent error_handler
2 parents 36ad018 + d6c3173 commit cdd2fce

File tree

5 files changed

+74
-69
lines changed

5 files changed

+74
-69
lines changed

erts/emulator/beam/beam_common.c

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

1336-
static Export*
1337-
apply_setup_error_handler(Process* p, Eterm module, Eterm function, Uint arity, Eterm* reg)
1338-
{
1339-
Export* ep;
1340-
1341-
/*
1342-
* Find the export table index for the error handler. Return NULL if
1343-
* there is no error handler module.
1344-
*/
1345-
1346-
if ((ep = erts_active_export_entry(erts_proc_get_error_handler(p),
1347-
am_undefined_function, 3)) == NULL) {
1348-
return NULL;
1349-
} else {
1350-
int i;
1351-
Uint sz = 2*arity;
1352-
Eterm* hp;
1353-
Eterm args = NIL;
1354-
1355-
/*
1356-
* Always copy args from registers to a new list; this ensures
1357-
* that we have the same behaviour whether or not this was
1358-
* called from apply or fixed_apply (any additional last
1359-
* THIS-argument will be included, assuming that arity has been
1360-
* properly adjusted).
1361-
*/
1362-
1363-
hp = HAlloc(p, sz);
1364-
for (i = arity-1; i >= 0; i--) {
1365-
args = CONS(hp, reg[i], args);
1366-
hp += 2;
1367-
}
1368-
reg[0] = module;
1369-
reg[1] = function;
1370-
reg[2] = args;
1371-
}
1372-
1373-
return ep;
1374-
}
1375-
13761336
static ERTS_INLINE void
13771337
apply_bif_error_adjustment(Process *p, Export *ep,
13781338
Eterm *reg, Uint arity,
@@ -1547,18 +1507,13 @@ apply(Process* p, Eterm* reg, ErtsCodePtr I, Uint stack_offset)
15471507
goto error;
15481508
}
15491509

1550-
/*
1551-
* Get the index into the export table, or failing that the export
1552-
* entry for the error handler.
1553-
*
1554-
* Note: All BIFs have export entries; thus, no special case is needed.
1555-
*/
1510+
/* Call the referenced function, if any: should the function not be found,
1511+
* create a stub entry which in turn calls the error handler. */
1512+
ep = erts_export_get_or_make_stub(module, function, arity);
15561513

1557-
if ((ep = erts_active_export_entry(module, function, arity)) == NULL) {
1558-
if ((ep = apply_setup_error_handler(p, module, function, arity, reg)) == NULL) goto error;
1559-
}
15601514
apply_bif_error_adjustment(p, ep, reg, arity, I, stack_offset);
15611515
DTRACE_GLOBAL_CALL_FROM_EXPORT(p, ep);
1516+
15621517
return ep;
15631518
}
15641519

@@ -1593,17 +1548,9 @@ fixed_apply(Process* p, Eterm* reg, Uint arity,
15931548
return apply(p, reg, I, stack_offset);
15941549
}
15951550

1596-
/*
1597-
* Get the index into the export table, or failing that the export
1598-
* entry for the error handler module.
1599-
*
1600-
* Note: All BIFs have export entries; thus, no special case is needed.
1601-
*/
1602-
1603-
if ((ep = erts_active_export_entry(module, function, arity)) == NULL) {
1604-
if ((ep = apply_setup_error_handler(p, module, function, arity, reg)) == NULL)
1605-
goto error;
1606-
}
1551+
/* Call the referenced function, if any: should the function not be found,
1552+
* create a stub entry which in turn calls the error handler. */
1553+
ep = erts_export_get_or_make_stub(module, function, arity);
16071554

16081555
apply_bif_error_adjustment(p, ep, reg, arity, I, stack_offset);
16091556
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, cp_val(*E), 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
@@ -199,12 +199,15 @@ void BeamGlobalAssembler::emit_export_trampoline() {
199199

200200
a.bind(error_handler);
201201
{
202+
lea(ARG2, arm::Mem(ARG1, offsetof(Export, info.mfa)));
203+
a.str(ARG2, TMP_MEM1q);
204+
202205
emit_enter_runtime_frame();
203206
emit_enter_runtime<Update::eReductions | Update::eHeapAlloc |
204207
Update::eXRegs>();
205208

206-
lea(ARG2, arm::Mem(ARG1, offsetof(Export, info.mfa)));
207209
a.mov(ARG1, c_p);
210+
/* ARG2 set above */
208211
load_x_reg_array(ARG3);
209212
mov_imm(ARG4, am_undefined_function);
210213
runtime_call<4>(call_error_handler);
@@ -215,7 +218,8 @@ void BeamGlobalAssembler::emit_export_trampoline() {
215218
Update::eXRegs>();
216219
emit_leave_runtime_frame();
217220

218-
a.cbz(ARG1, labels[process_exit]);
221+
a.ldr(ARG4, TMP_MEM1q);
222+
a.cbz(ARG1, labels[raise_exception]);
219223

220224
branch(emit_setup_dispatchable_call(ARG1));
221225
}

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

Lines changed: 24 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -203,22 +203,42 @@ void BeamGlobalAssembler::emit_export_trampoline() {
203203

204204
a.bind(error_handler);
205205
{
206+
Label error;
207+
208+
#ifdef NATIVE_ERLANG_STACK
209+
error = labels[raise_exception];
210+
#else
211+
error = a.newLabel();
212+
#endif
213+
214+
a.lea(ARG2, x86::qword_ptr(RET, offsetof(Export, info.mfa)));
215+
a.mov(TMP_MEM1q, ARG2);
216+
206217
emit_enter_frame();
207218
emit_enter_runtime<Update::eReductions | Update::eHeapAlloc>();
208219

209220
a.mov(ARG1, c_p);
210-
a.lea(ARG2, x86::qword_ptr(RET, offsetof(Export, info.mfa)));
221+
/* ARG2 set above */
211222
load_x_reg_array(ARG3);
212223
mov_imm(ARG4, am_undefined_function);
213224
runtime_call<4>(call_error_handler);
214225

215226
emit_leave_runtime<Update::eReductions | Update::eHeapAlloc>();
227+
emit_leave_frame();
216228

229+
a.mov(ARG4, TMP_MEM1q);
217230
a.test(RET, RET);
218-
a.je(labels[process_exit]);
219-
220-
emit_leave_frame();
231+
a.je(error);
221232
a.jmp(emit_setup_dispatchable_call(RET));
233+
234+
#ifndef NATIVE_ERLANG_STACK
235+
a.bind(error);
236+
{
237+
a.push(getCPRef());
238+
a.mov(getCPRef(), imm(NIL));
239+
a.jmp(labels[raise_exception]);
240+
}
241+
#endif
222242
}
223243
}
224244

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)