From 46c6eedd8e6bf105e94f5c8fba54a694487d6896 Mon Sep 17 00:00:00 2001 From: Daniel Gorin <danielgo@meta.com> Date: Tue, 1 Apr 2025 09:17:40 +0100 Subject: [PATCH 1/7] erl_debugger: Add skeleton module We add a new erl_debugger module to the kernel application, that will provides an API for writing debuggers. Here we set up the general interface, with a stub for "setting a breakpoint" as the only debugging primitive. In the next commits we first implement the "breakpoint" primitive, and later add additional ones. About the general design: - A node needs to have debugging support enabled on startup with the `+D` option and this can't be enabled afterwards. This gives admins a way to prevent processes from blocking on prod due to an accidental debugger usage, etc. - Debugging primitives based on code instrumentation can be individually enabled/disabled, etc. - A debugger is an Erlang process; there can be at most one debugger process per node. - The system will communicate with the debugger process via `debugger_events` messages. For now we introduce only one message for notifying that a process hit a breakpoint --- erts/emulator/Makefile.in | 2 +- erts/emulator/beam/atom.names | 2 + erts/emulator/beam/bif.tab | 13 +- erts/emulator/beam/erl_bif_info.c | 11 + erts/emulator/beam/erl_debugger.c | 300 ++++++++++++++++++++++ erts/emulator/beam/erl_debugger.h | 32 +++ erts/emulator/beam/erl_init.c | 32 +++ erts/emulator/beam/erl_lock_check.c | 1 + erts/emulator/test/Makefile | 1 + erts/emulator/test/erl_debugger_SUITE.erl | 176 +++++++++++++ erts/etc/common/erlexec.c | 10 + erts/preloaded/ebin/erts_internal.beam | Bin 10052 -> 10376 bytes erts/preloaded/src/erts_internal.erl | 26 ++ lib/kernel/doc/docs.exs | 9 +- lib/kernel/src/Makefile | 1 + lib/kernel/src/erl_debugger.erl | 173 +++++++++++++ lib/kernel/src/kernel.app.src | 1 + 17 files changed, 786 insertions(+), 4 deletions(-) create mode 100644 erts/emulator/beam/erl_debugger.c create mode 100644 erts/emulator/beam/erl_debugger.h create mode 100644 erts/emulator/test/erl_debugger_SUITE.erl create mode 100644 lib/kernel/src/erl_debugger.erl diff --git a/erts/emulator/Makefile.in b/erts/emulator/Makefile.in index 9b6bbf06d39d..63ef13425a0f 100644 --- a/erts/emulator/Makefile.in +++ b/erts/emulator/Makefile.in @@ -1117,7 +1117,7 @@ RUN_OBJS += \ $(OBJDIR)/erl_trace.o $(OBJDIR)/copy.o \ $(OBJDIR)/utils.o $(OBJDIR)/bif.o \ $(OBJDIR)/io.o $(OBJDIR)/erl_printf_term.o\ - $(OBJDIR)/erl_debug.o \ + $(OBJDIR)/erl_debug.o $(OBJDIR)/erl_debugger.o \ $(OBJDIR)/erl_message.o $(OBJDIR)/erl_proc_sig_queue.o \ $(OBJDIR)/erl_process_dict.o $(OBJDIR)/erl_process_lock.o \ $(OBJDIR)/erl_port_task.o $(OBJDIR)/erl_arith.o \ diff --git a/erts/emulator/beam/atom.names b/erts/emulator/beam/atom.names index 0595e1d26e16..3cb20e2452f3 100644 --- a/erts/emulator/beam/atom.names +++ b/erts/emulator/beam/atom.names @@ -215,6 +215,7 @@ atom current_location atom current_stacktrace atom data atom debug_flags +atom debugger_event atom decentralized_counters atom decimals atom default @@ -406,6 +407,7 @@ atom Le='=<' atom legacy atom lf atom line +atom line_breakpoint atom line_counters atom line_delimiter atom line_length diff --git a/erts/emulator/beam/bif.tab b/erts/emulator/beam/bif.tab index 84c90a3f2e7f..73e2a2866141 100644 --- a/erts/emulator/beam/bif.tab +++ b/erts/emulator/beam/bif.tab @@ -416,7 +416,7 @@ bif erl_ddll:monitor/2 bif erl_ddll:demonitor/1 # -# Bifs in the re module +# Bifs in the re module # bif re:version/0 bif re:compile/1 @@ -597,7 +597,7 @@ bif erlang:dt_get_tag_data/0 bif erlang:dt_spread_tag/1 bif erlang:dt_restore_tag/1 -# These are dummies even with enabled dynamic trace unless vm probes are enabled. +# These are dummies even with enabled dynamic trace unless vm probes are enabled. # They are also internal, for dtrace tags sent to the VM's own drivers (efile) bif erlang:dt_prepend_vm_tag_data/1 bif erlang:dt_append_vm_tag_data/1 @@ -811,3 +811,12 @@ bif erts_internal:processes_next/1 bif code:get_debug_info/1 bif erlang:exit/3 bif erlang:link/2 + +bif erl_debugger:supported/0 +bif erl_debugger:instrumentations/0 +bif erl_debugger:toggle_instrumentations/1 +bif erl_debugger:register/1 +bif erl_debugger:unregister/2 +bif erl_debugger:whereis/0 +bif erl_debugger:breakpoint/3 +bif erts_internal:notify_breakpoint_hit/3 diff --git a/erts/emulator/beam/erl_bif_info.c b/erts/emulator/beam/erl_bif_info.c index 21a771008d0e..d3601a2c1aa5 100644 --- a/erts/emulator/beam/erl_bif_info.c +++ b/erts/emulator/beam/erl_bif_info.c @@ -55,6 +55,7 @@ #include "beam_load.h" #include "erl_md5.h" #include "erl_iolist.h" +#include "erl_debugger.h" #ifdef ERTS_ENABLE_LOCK_COUNT #include "erl_lock_count.h" @@ -4501,6 +4502,9 @@ BIF_RETTYPE erts_debug_get_internal_state_1(BIF_ALIST_1) return am_undefined; #endif } + else if (ERTS_IS_ATOM_STR("debugger_support", BIF_ARG_1)) { + return erts_debugger_flags & ERTS_DEBUGGER_ENABLED ? am_true : am_false; + } } else if (is_tuple(BIF_ARG_1)) { Eterm* tp = tuple_val(BIF_ARG_1); @@ -5375,6 +5379,13 @@ BIF_RETTYPE erts_debug_set_internal_state_2(BIF_ALIST_2) BIF_RET(am_true); } } + } else if (ERTS_IS_ATOM_STR("debugger_support", BIF_ARG_1)) { + if (BIF_ARG_2 == am_true) { + erts_debugger_flags |= ERTS_DEBUGGER_ENABLED; + BIF_RET(am_ok); + } + + BIF_RET(am_badarg); } } diff --git a/erts/emulator/beam/erl_debugger.c b/erts/emulator/beam/erl_debugger.c new file mode 100644 index 000000000000..a08c8e8dd18c --- /dev/null +++ b/erts/emulator/beam/erl_debugger.c @@ -0,0 +1,300 @@ +/* + * Copyright (c) Meta Platforms, Inc. and affiliates. + * + * Licensed under the Apache License, Version 2.0 (the "License"); + * you may not use this file except in compliance with the License. + * You may obtain a copy of the License at + * + * http://www.apache.org/licenses/LICENSE-2.0 + * + * Unless required by applicable law or agreed to in writing, software + * distributed under the License is distributed on an "AS IS" BASIS, + * WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied. + * See the License for the specific language governing permissions and + * limitations under the License. + */ + +#ifdef HAVE_CONFIG_H +# include "config.h" +#endif + +#include "global.h" +#include "bif.h" +#include "erl_debugger.h" +#include "erl_map.h" + +static erts_rwmtx_t debugger_rwmtx; + +Uint erts_debugger_flags = /* -D: enable debugger, -Dxxxx for features */ + (~ERTS_DEBUGGER_ENABLED & ERTS_DEBUGGER_LINE_BREAKPOINTS); + +#define BIF_UNDEF_IF_NO_DEBUGGER_SUPPORT() do { \ + if (!ERTS_DEBUGGER_IS_ENABLED(0)) { \ + BIF_ERROR(BIF_P, EXC_UNDEF); \ + } \ +} while(0) + +/* Protected by debugger lock. */ +static Eterm debugger_pid = NIL; +static Uint32 debugger_ref = 0; + + +void erts_init_debugger(void) +{ + erts_rwmtx_init(&debugger_rwmtx, "debugger", NIL, + ERTS_LOCK_FLAGS_PROPERTY_STATIC | ERTS_LOCK_FLAGS_CATEGORY_DEBUG); +} + +/* Capabilities */ + +BIF_RETTYPE +erl_debugger_supported_0(BIF_ALIST_0) { + int supported = ERTS_DEBUGGER_IS_ENABLED(0); + BIF_RET(supported ? am_true : am_false); +} + +BIF_RETTYPE +erl_debugger_instrumentations_0(BIF_ALIST_0) +{ + Eterm *hp; + int line_bp = ERTS_DEBUGGER_IS_ENABLED(ERTS_DEBUGGER_LINE_BREAKPOINTS); + + BIF_UNDEF_IF_NO_DEBUGGER_SUPPORT(); + + hp = HAlloc(BIF_P, MAP1_SZ); + return MAP1(hp, am_line_breakpoint, line_bp ? am_true : am_false); +} + +BIF_RETTYPE +erl_debugger_toggle_instrumentations_1(BIF_ALIST_1) +{ + const int instr_count = 1; + const struct {Eterm key; Uint flag;} instrumentations[] = { + {am_line_breakpoint, ERTS_DEBUGGER_LINE_BREAKPOINTS}, + }; + + Eterm toggles; + int count_ok = 0; + int new_flags; + + BIF_UNDEF_IF_NO_DEBUGGER_SUPPORT(); + + erts_rwmtx_rwlock(&debugger_rwmtx); + new_flags = erts_debugger_flags; + + toggles = BIF_ARG_1; + if (!is_map(toggles)) { + goto badarg; + } + + for(int i=0; i < instr_count; i++) { + const Eterm *val = erts_maps_get(instrumentations[i].key, toggles); + if (val) { + if (*val == am_true) { + new_flags |= instrumentations[i].flag; + } else if (*val == am_false) { + new_flags &= ~instrumentations[i].flag; + } else { + goto badarg; + } + count_ok++; + } + } + + if (count_ok != erts_map_size(toggles)) { + goto badarg; + } + + erts_debugger_flags = new_flags; + erts_rwmtx_rwunlock(&debugger_rwmtx); + + return am_ok; + + badarg: { + erts_rwmtx_rwunlock(&debugger_rwmtx); + BIF_ERROR(BIF_P, BADARG); + } +} + +/* Debugger registration */ + +BIF_RETTYPE +erl_debugger_register_1(BIF_ALIST_1) +{ + Eterm result_tag, result_val; + + BIF_UNDEF_IF_NO_DEBUGGER_SUPPORT(); + + if (is_not_internal_pid(BIF_ARG_1)) { + BIF_ERROR(BIF_P, BADARG); + } + + erts_rwmtx_rwlock(&debugger_rwmtx); + + if (is_internal_pid(debugger_pid) && erts_proc_lookup(debugger_pid)) { + result_tag = am_error; + result_val = am_already_exists; + goto end; + } + + debugger_pid = BIF_ARG_1; + debugger_ref = erts_sched_local_random(debugger_ref); + + result_tag = am_ok; + result_val = make_small(debugger_ref); + + end: { + Eterm *hp = HAlloc(BIF_P, 3); + Eterm result = TUPLE2(hp, result_tag, result_val); + + erts_rwmtx_rwunlock(&debugger_rwmtx); + BIF_RET(result); + } +} + +BIF_RETTYPE +erl_debugger_unregister_2(BIF_ALIST_2) +{ + BIF_UNDEF_IF_NO_DEBUGGER_SUPPORT(); + + if (is_not_internal_pid(BIF_ARG_1)) { + BIF_ERROR(BIF_P, BADARG); + } + + if (is_not_small(BIF_ARG_2)) { + BIF_ERROR(BIF_P, BADARG); + } + + erts_rwmtx_rwlock(&debugger_rwmtx); + + if (debugger_pid == BIF_ARG_1) { + if (make_small(debugger_ref) != BIF_ARG_2) { + erts_rwmtx_rwunlock(&debugger_rwmtx); + BIF_ERROR(BIF_P, BADARG); + } + + debugger_pid = NIL; + } + + erts_rwmtx_rwunlock(&debugger_rwmtx); + BIF_RET(am_ok); +} + + +BIF_RETTYPE +erl_debugger_whereis_0(BIF_ALIST_0) +{ + BIF_UNDEF_IF_NO_DEBUGGER_SUPPORT(); + + if (is_internal_pid(debugger_pid) && erts_proc_lookup(debugger_pid)) { + BIF_RET(debugger_pid); + } + + BIF_RET(am_undefined); +} + +/* Debugger events */ + +int +erts_send_debugger_event(Process *c_p, Eterm event) +{ + Process *debugger = NULL; + int event_sent = 0; + ErtsProcLocks initial_locks = 0, locks = 0; + + erts_rwmtx_rlock(&debugger_rwmtx); + + if (debugger_pid == NIL) { + goto end; + } + + debugger = erts_proc_lookup(debugger_pid); + if (debugger) { + Eterm *hp, event_copy, msg; + Uint event_sz; + ErtsMessage *mp; + ErlOffHeap *ohp; + + if (c_p == debugger) { + locks = initial_locks = ERTS_PROC_LOCK_MAIN; + } + + event_sz = is_immed(event) ? 0 : size_object(event); + mp = erts_alloc_message_heap(debugger, &locks, + 4 + event_sz, + &hp, &ohp); + ERL_MESSAGE_TOKEN(mp) = am_undefined; + + event_copy = is_immed(event) ? event : copy_struct(event, event_sz, + &hp, ohp); + msg = TUPLE3(hp, + am_debugger_event, make_small(debugger_ref), + event_copy); + + erts_queue_proc_message(debugger, debugger, locks, mp, msg); + event_sent = 1; + } + + end:{ + ErtsProcLocks acquired_locks = locks & ~initial_locks; + if (debugger && acquired_locks) { + erts_proc_unlock(debugger, acquired_locks); + } + + erts_rwmtx_runlock(&debugger_rwmtx); + return event_sent; + } +} + +/* Line breakpoints */ + +BIF_RETTYPE +erl_debugger_breakpoint_3(BIF_ALIST_3) { + BIF_UNDEF_IF_NO_DEBUGGER_SUPPORT(); + + /* TO BE IMPLEMENTED */ + BIF_ERROR(BIF_P, EXC_UNDEF); +} + +BIF_RETTYPE +erts_internal_notify_breakpoint_hit_3(BIF_ALIST_3) { + Eterm mfa, *mfav, line, resume_fun; + + BIF_UNDEF_IF_NO_DEBUGGER_SUPPORT(); + + mfa = BIF_ARG_1; + if (is_not_tuple_arity(BIF_ARG_1, 3)) { + BIF_ERROR(BIF_P, BADARG); + } + + mfav = tuple_val(mfa); + if (is_not_atom(mfav[1]) || is_not_atom(mfav[2]) || is_not_small(mfav[3])) { + BIF_ERROR(BIF_P, BADARG); + } + + line = BIF_ARG_2; + if (is_not_small(line)) { + BIF_ERROR(BIF_P, BADARG); + } + + resume_fun = BIF_ARG_3; + if (is_not_any_fun(resume_fun) || + fun_arity((ErlFunThing*) fun_val(resume_fun)) != 0 ) { + BIF_ERROR(BIF_P, BADARG); + } + + if (BIF_P->common.id == debugger_pid) { + BIF_RET(am_abort); + } else { + Eterm pid = BIF_P->common.id; + Eterm *hp = HAlloc(BIF_P, 6); + + Eterm bp_event = TUPLE5(hp, am_breakpoint, pid, mfa, line, resume_fun); + + if (!erts_send_debugger_event(BIF_P, bp_event)) { + BIF_RET(am_noproc); + } + } + + BIF_RET(am_ok); +} diff --git a/erts/emulator/beam/erl_debugger.h b/erts/emulator/beam/erl_debugger.h new file mode 100644 index 000000000000..2d2084747da8 --- /dev/null +++ b/erts/emulator/beam/erl_debugger.h @@ -0,0 +1,32 @@ +/* + * Copyright (c) Meta Platforms, Inc. and affiliates. + * + * Licensed under the Apache License, Version 2.0 (the "License"); + * you may not use this file except in compliance with the License. + * You may obtain a copy of the License at + * + * http://www.apache.org/licenses/LICENSE-2.0 + * + * Unless required by applicable law or agreed to in writing, software + * distributed under the License is distributed on an "AS IS" BASIS, + * WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied. + * See the License for the specific language governing permissions and + * limitations under the License. + */ + +#ifndef _ERL_DEBUGGER_H_ +#define _ERL_DEBUGGER_H_ + +#define ERTS_DEBUGGER_ENABLED ((Uint)1 << 0) +#define ERTS_DEBUGGER_LINE_BREAKPOINTS ((Uint)1 << 1) + +#define ERTS_DEBUGGER_IS_ENABLED(Flgs) \ + ((erts_debugger_flags & (Flgs | ERTS_DEBUGGER_ENABLED)) == \ + (Flgs | ERTS_DEBUGGER_ENABLED)) + +extern Uint erts_debugger_flags; + +void erts_init_debugger(void); +int erts_send_debugger_event(Process *c_p, Eterm event); + +#endif /* _ERL_DEBUGGER_H */ diff --git a/erts/emulator/beam/erl_init.c b/erts/emulator/beam/erl_init.c index 772c2e52396b..1296bb453052 100644 --- a/erts/emulator/beam/erl_init.c +++ b/erts/emulator/beam/erl_init.c @@ -54,6 +54,7 @@ #include "beam_load.h" #include "erl_global_literals.h" #include "erl_iolist.h" +#include "erl_debugger.h" #include "jit/beam_asm.h" @@ -274,6 +275,7 @@ erl_init(int ncpu, H_MIN_SIZE = erts_next_heap_size(H_MIN_SIZE, 0); BIN_VH_MIN_SIZE = erts_next_heap_size(BIN_VH_MIN_SIZE, 0); + erts_init_debugger(); erts_init_trace(); erts_code_ix_init(); erts_init_fun_table(); @@ -553,6 +555,8 @@ __decl_noreturn void __noreturn erts_usage(void) erts_fprintf(stderr, " no_time_warp | single_time_warp | multi_time_warp\n"); erts_fprintf(stderr, "\n"); + erts_fprintf(stderr, "-D enable debugging support\n"); + erts_fprintf(stderr, "-Dibpl bool enable or disable instrumentation for breakpoints on lines (default true)\n"); erts_fprintf(stderr, "-d don't write a crash dump for internally detected errors\n"); erts_fprintf(stderr, " (halt(String) will still produce a crash dump)\n"); erts_fprintf(stderr, "-dcg set the limit for the number of decentralized counter groups\n"); @@ -1627,6 +1631,34 @@ erl_start(int argc, char **argv) } break; } + case 'D': + if (sys_strcmp(argv[i]+1, "D") == 0) { + erts_debugger_flags |= ERTS_DEBUGGER_ENABLED; + } else if (argv[i][2] == 'i') { + const char *instr_opt = argv[i]+1; + Uint flag; + + if (sys_strcmp(instr_opt, "Dibpl") == 0) { + flag = ERTS_DEBUGGER_LINE_BREAKPOINTS; + arg = get_arg(argv[i]+6, argv[i+1], &i); + } else { + erts_fprintf(stderr, "Unknown instrumentation option %s\n", instr_opt); + erts_usage(); + } + + if (sys_strcmp(arg, "true") == 0) { + erts_debugger_flags |= flag; + } else if (sys_strcmp(arg, "false") == 0) { + erts_debugger_flags &= ~flag; + } else { + erts_fprintf(stderr, "%s expected `true' or `false' but got: `%s'\n", instr_opt, arg); + erts_usage(); + } + } else { + erts_fprintf(stderr, "Unknown option %s\n", argv[i]+1); + erts_usage(); + } + break; case 'd': /* * Never produce crash dumps for internally detected diff --git a/erts/emulator/beam/erl_lock_check.c b/erts/emulator/beam/erl_lock_check.c index 3ec2b1dffa18..894c511ba783 100644 --- a/erts/emulator/beam/erl_lock_check.c +++ b/erts/emulator/beam/erl_lock_check.c @@ -102,6 +102,7 @@ static erts_lc_lock_order_t erts_lock_order[] = { {"old_code", "address"}, {"nif_call_tab", NULL}, {"nodes_monitors", NULL}, + {"debugger", NULL}, {"meta_name_tab", "address"}, {"resource_monitors", "address"}, {"driver_list", NULL}, diff --git a/erts/emulator/test/Makefile b/erts/emulator/test/Makefile index 302d06dde697..f43a3353922d 100644 --- a/erts/emulator/test/Makefile +++ b/erts/emulator/test/Makefile @@ -62,6 +62,7 @@ MODULES= \ dummy \ dump_SUITE \ efile_SUITE \ + erl_debugger_SUITE \ erts_debug_SUITE \ estone_SUITE \ erl_link_SUITE \ diff --git a/erts/emulator/test/erl_debugger_SUITE.erl b/erts/emulator/test/erl_debugger_SUITE.erl new file mode 100644 index 000000000000..c3f6a95d1ebc --- /dev/null +++ b/erts/emulator/test/erl_debugger_SUITE.erl @@ -0,0 +1,176 @@ +%% +%% +%% Copyright (c) Meta Platforms, Inc. and affiliates. +%% +%% Licensed under the Apache License, Version 2.0 (the "License"); +%% you may not use this file except in compliance with the License. +%% You may obtain a copy of the License at +%% +%% http://www.apache.org/licenses/LICENSE-2.0 +%% +%% Unless required by applicable law or agreed to in writing, software +%% distributed under the License is distributed on an "AS IS" BASIS, +%% WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied. +%% See the License for the specific language governing permissions and +%% limitations under the License. +%% +%% + +-module(erl_debugger_SUITE). + +-export([all/0, groups/0, suite/0]). +-export([init_per_suite/1, end_per_suite/1]). +-export([init_per_group/2, end_per_group/2]). + +% Test cases +-export([test_supported_returns_false/1]). +-export([test_all_functions_fail_with_undef/1]). +-export([test_supported_returns_true/1]). +-export([test_can_toggle_instrumentations/1]). +-export([test_toggle_instrumentations_validates_input/1]). +-export([test_register_and_unregister_debugger/1]). +-export([test_debugger_unregistered_when_dead/1]). + +-include_lib("stdlib/include/assert.hrl"). + +suite() -> + [{ct_hooks,[ts_install_cth]}, + {timetrap, {seconds, 20}}]. + +all() -> + [ + {group, debugger_support_disabled}, + {group, debugger_support_enabled}, + {group, instrumentations}, + {group, registration} + ]. + +groups() -> + [ + {debugger_support_disabled, [], [ + test_supported_returns_false, + test_all_functions_fail_with_undef + ]}, + {debugger_support_enabled, [], [ + test_supported_returns_true + ]}, + {instrumentations, [], [ + test_can_toggle_instrumentations, + test_toggle_instrumentations_validates_input + ]}, + {registration, [], [ + test_register_and_unregister_debugger, + test_debugger_unregistered_when_dead + ]} + ]. + +init_per_suite(Config) -> + erts_debug:set_internal_state(available_internal_state, true), + Config. + +end_per_suite(_Config) -> + erts_debug:set_internal_state(available_internal_state, false), + ok. + +init_per_group(debugger_support_disabled, Config) -> + Config; +init_per_group(_Group, Config) -> + erts_debug:set_internal_state(debugger_support, true), + Config. + +end_per_group(_Group, _Config) -> + ok. + +%% Support tests +test_supported_returns_false(_Config) -> + false = erl_debugger:supported(), + ok. + +test_supported_returns_true(_Config) -> + true = erl_debugger:supported(), + ok. + +test_all_functions_fail_with_undef(_Config) -> + Allowed = [{module_info, 0}, {module_info, 1}, {supported, 0}], + [ + ?assertError( + undef, + erl_debugger:M([dummy || _ <- lists:seq(1, A)]), + lists:flatten(io_lib:format("Didn't fail erl_debugger:~p/~p", [M, A])) + ) + || {M, A} <- erl_debugger:module_info(exports), + not lists:member({M, A}, Allowed) + ], + ok. + +%% Instrumentation toggling tests +test_can_toggle_instrumentations(_Config) -> + #{line_breakpoint := true} = erl_debugger:instrumentations(), + + ok = erl_debugger:toggle_instrumentations(#{}), + #{line_breakpoint := true} = erl_debugger:instrumentations(), + + ok = erl_debugger:toggle_instrumentations(#{line_breakpoint => false}), + #{line_breakpoint := false} = erl_debugger:instrumentations(), + + ok = erl_debugger:toggle_instrumentations(#{line_breakpoint => true}), + #{line_breakpoint := true} = erl_debugger:instrumentations(), + ok. + +test_toggle_instrumentations_validates_input(_Config) -> + ?assertError(badarg, erl_debugger:toggle_instrumentations([])), + ?assertError(badarg, erl_debugger:toggle_instrumentations(#{line_breakpoint => faux})), + ?assertError(badarg, erl_debugger:toggle_instrumentations(#{foo => true})), + ?assertError(badarg, erl_debugger:toggle_instrumentations(#{line_breakpoint => true, foo => true})), + ok. + +%% Registration tests + +test_register_and_unregister_debugger(_Config) -> + undefined = erl_debugger:whereis(), + + Me = self(), + AnotherProc = erlang:spawn_link(fun() -> receive after infinity -> ok end end), + + {ok, Session1} = erl_debugger:register(Me), + Me = erl_debugger:whereis(), + + {error, already_exists} = erl_debugger:register(Me), + {error, already_exists} = erl_debugger:register(AnotherProc), + Me = erl_debugger:whereis(), + + ok = erl_debugger:unregister(Me, Session1), + undefined = erl_debugger:whereis(), + + {ok, Session2} = erl_debugger:register(Me), + Me = erl_debugger:whereis(), + BadSession = Session2 + 1, + {'EXIT', {badarg, _}} = catch erl_debugger:unregister(Me, BadSession), + ok = erl_debugger:unregister(Me, Session2), + undefined = erl_debugger:whereis(), + + {ok, Session3} = erl_debugger:register(AnotherProc), + AnotherProc = erl_debugger:whereis(), + erl_debugger:unregister(AnotherProc, Session3), + undefined = erl_debugger:whereis(), + ok. + +test_debugger_unregistered_when_dead(_Config) -> + Me = self(), + {Debugger, MonRef} = erlang:spawn_monitor(fun() -> receive after infinity -> ok end end), + + {ok, _Session} = erl_debugger:register(Debugger), + Debugger = erl_debugger:whereis(), + + exit(Debugger, boom), + receive + {'DOWN', MonRef, process, Debugger, boom} -> ok + after 2_000 -> error(didnt_die) + end, + + undefined = erl_debugger:whereis(), + + {ok, Session2} = erl_debugger:register(Me), + Me = erl_debugger:whereis(), + ok = erl_debugger:unregister(Me, Session2), + ok. diff --git a/erts/etc/common/erlexec.c b/erts/etc/common/erlexec.c index 1ebec55df0e1..2a74f078f523 100644 --- a/erts/etc/common/erlexec.c +++ b/erts/etc/common/erlexec.c @@ -886,6 +886,16 @@ int main(int argc, char **argv) add_Eargs(argv[i+1]); i++; break; + case 'D': + if (argv[i][2] != 'i') { + goto the_default; + } + NEXT_ARG_CHECK(); + argv[i][0] = '-'; + add_Eargs(argv[i]); + add_Eargs(argv[i+1]); + i++; + break; case 'I': if (argv[i][2] == 'O' && (argv[i][3] == 't' || argv[i][3] == 'p')) { if (argv[i][4] != '\0') diff --git a/erts/preloaded/ebin/erts_internal.beam b/erts/preloaded/ebin/erts_internal.beam index d27c9c9a20ceda910030e0d9f1470cd7a7d5c0dc..796b99394c1b500f40f0e3bfc26f36c8dcf96f40 100644 GIT binary patch delta 1029 zcmYLHYiv|i5WaWsg7=h4Hr=hO35CU7^iJ1n*LDMjJ~%Dy;-s~JtSH9V(v;#@+}5%U zB@(wNN=FbMCFs(H)Jnmqw1gFuNJ_v5Dn`X(RD34>uttAKi~cZ%^;|V}l5gglZ|2N7 zIhl7F`&Oo6%kQ{F)2!Z_y6W2-D6vk{^uM%e`%}@&PAYbaJz`J{i&w-kaa@dvQ{r9m zo;W8y664~6_*#4;ei6Sy0eGPZ=7I$PHrx!QPzDuH2@((*U=1`w8?1+R*Z^Iy5qcoC z1-8PYupRo~N!S5T!E=y-eQ*GV;V5L`EjS5h;e9v{pTXzw9sCFra0PNG(2w&lgbNU` z7)vmMr5MG9xCqO!3YTC#HsC5;jrZWa*oN!zA?(6l+=|cOvp9em9Kx6IARfZQDLjrR za11}d)A$K~isN_zzru_7J^p|{;RH_N6#kBX;1$e~PHvh>g7WEVnoWgt4HeN`3ef^8 zrkiLnl~WzXsF9Y_owS<nqb6#n4b(xMw2_juiF)W^+CnMnrN?L+ZKpokMX9H0fHL$V z4bdTbnMP=oj?o+RCY_*@G)AZB44tL7=^TAb=V_e2pfBkneM=McGhL!dp20JDHs8nr zp2H;^;ZlzBLayc-UdFd^JvZ<QUdea!8eYpSO#A>RxtllfW`2Yp=O=iFk9TrE@8;+E z1s>vqJjzFSxZiYzXVm9%xt8p$t|@c=U`yA!we6i9lt`L|iH;<-ZEl*Dn(n9m;#oyy zrq7-hOQLpLcfyX?+R~0zwN!<rYKJ_|A}KqnmTZ}do!Qn|5nsyu%~g=MSL)W{{AMZ3 zLNXYY-dbtIh4hWOuhN=5iz3Qt0gvZZ&Fc^Ni~~V`Bwiam>^4-F43){CA-zFa=6%h- z!tD!1Yt!Z>cf^)qyUNH5ABpQ$x!<ld!ghsmSKKoaFO+#<qoCQVTNT&ZsdC+_yv|m> zY9#)DVM*GYRL>fS=$4dcjI=q`=n3dnby`zuM$@etSzt7J%<FY)>A#vsx74G(jvO$9 zx>c7pFRR}D>QpRW3;6ySt$7ViTb1mJJO6+WcB+{DaNe+v`&6zgm<kSe)%7?<_v?zc zDr6K?U9bI*J86w_0}5)SE>+yC;LZ-t-{ua*x)aV7a}=DZ`xRV@##D67rJvpv%Z6?U G=zjyWdp9fq delta 713 zcmYjPTS$~)6#VxR?WaC$YA<OaO1URfR1ES~mT4UEf+ZPI8L^v=sH>J%Qf?O&kKM1} z8fB>wRA8+oiIR~PMr9h6U7?4JdeO4p6#I>!28J^;hk2X&?7mD_YS!8)O$$v}m9jD; z9VHG;GyKs0;g>GQW~^#ZXVeANqOK~B>QLRPM?Fw|YCt_!Luy#PQE$~(^^L4FhXN>& z7EvgL(GrTJD2k(aT25;yjdE!V*~vkmLMo*)sw7txxoAJtQXSQk&|x}3Zfc^-)I#la zlkQR%_0vNdr04X4-qR-<rAeCN**ur$b1;W+DBC!kBRG<yIfj>VEGKXxGpBJj=kNyJ z$aZ$HlS{dpU3`p>b0fRCnJ;lGxA8R>cW@_n^CP~;Px%=S@i4#U5&pm*`7@95IDh8} z{>hU(#nUjtjM?ylH+<j+e*_>9!3cp3i?Ix`NXBZUBLnM@gH6~Bpb*6<K^e+XflBN_ z751ST2XGLzsKXJsj-nB6TtqY4a0S<K10LMQ9dx1#-RMCt`f(ovc!EI;;U!*S1n)44 zFBrqPn8YkTvQQStJPDTwiIixGkrk38DUvEIX_6^fvR-l}Pqs?F6iB)3kP6u)d*zVS zh+b}xlX6PV$~jFtZ8e6?@|&KXc6gGE6PDQaVyC^L$dQMV?auLh$IiU}yq4^=>tpdR z(zjuq8HkQs`gjucTkL7|j`X)_Mqe+tX0XL2`I<7VmSBS|zVT0HHP{l8Onx(QkR`<A w=?n50qMG!gL8nFMj5en1F3r(2^Lbrw)9Kc!{|yO$wdUy!t}%NGLW2yy0T*!fg#Z8m diff --git a/erts/preloaded/src/erts_internal.erl b/erts/preloaded/src/erts_internal.erl index 07a3c4b5ccd4..344a3be05f77 100644 --- a/erts/preloaded/src/erts_internal.erl +++ b/erts/preloaded/src/erts_internal.erl @@ -131,6 +131,8 @@ -export([processes_next/1]). +-export([breakpoint/4, notify_breakpoint_hit/3]). + %% %% Await result of send to port %% @@ -1172,3 +1174,27 @@ system_monitor(_Session, _MonitorPid, _Options) -> -spec processes_next(integer()) -> {integer(), [pid()]} | 'none'. processes_next(_IterRef) -> erlang:nif_error(undefined). + +%% +%% Internal implementation of breakpoints +%% +-spec breakpoint(Module, Function, Arity, Line) -> ok when + Module :: atom(), + Function :: atom(), + Arity:: arity(), + Line :: pos_integer(). +breakpoint(Module, Function, Arity, Line) -> + Me = self(), + ResumeRef = make_ref(), + ResumeAction = fun() -> Me ! ResumeRef, ok end, + case notify_breakpoint_hit({Module, Function, Arity}, Line, ResumeAction) of + ok -> receive ResumeRef -> ok end; + _ -> ok + end. + +-spec notify_breakpoint_hit(MFA, Line, ResumeAction) -> ok | term() when + MFA :: mfa(), + Line :: pos_integer(), + ResumeAction :: fun(() -> ok). +notify_breakpoint_hit(_, _, _) -> + erlang:nif_error(undefined). diff --git a/lib/kernel/doc/docs.exs b/lib/kernel/doc/docs.exs index 08b13c1300b2..bac0d2cc4875 100644 --- a/lib/kernel/doc/docs.exs +++ b/lib/kernel/doc/docs.exs @@ -1,6 +1,13 @@ [ groups_for_modules: [ - "Code & System": [:application, :code, :erl_ddll, :error_handler, :heart, :os], + "Code & System": [ + :application, + :code, + :erl_ddll, + :erl_debugger, + :error_handler, + :heart, + :os], Distribution: [ :net_adm, :net_kernel, diff --git a/lib/kernel/src/Makefile b/lib/kernel/src/Makefile index 0e8b85d007d8..5363fc35df0b 100644 --- a/lib/kernel/src/Makefile +++ b/lib/kernel/src/Makefile @@ -68,6 +68,7 @@ MODULES = \ erl_boot_server \ erl_compile_server \ erl_ddll \ + erl_debugger \ erl_distribution \ erl_erts_errors \ erl_epmd \ diff --git a/lib/kernel/src/erl_debugger.erl b/lib/kernel/src/erl_debugger.erl new file mode 100644 index 000000000000..ad9c993094f0 --- /dev/null +++ b/lib/kernel/src/erl_debugger.erl @@ -0,0 +1,173 @@ +%% +%% Copyright (c) Meta Platforms, Inc. and affiliates. +%% +%% Licensed under the Apache License, Version 2.0 (the "License"); +%% you may not use this file except in compliance with the License. +%% You may obtain a copy of the License at +%% +%% http://www.apache.org/licenses/LICENSE-2.0 +%% +%% Unless required by applicable law or agreed to in writing, software +%% distributed under the License is distributed on an "AS IS" BASIS, +%% WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied. +%% See the License for the specific language governing permissions and +%% limitations under the License. +%% +-module(erl_debugger). +-moduledoc """ +Erlang debugger support (EXPERIMENTAL). + +This module exposes low-level functionality for the implementation +of a debugger for Erlang. + +Any local process can register itself as the debugger for a node, but +there can be at most one such process registered at any given time. +Using the BIFs in this module, a debugger can: + + - set breakpoints; + - get notified on debugger events such as a process hitting a breakpoint; + - resume processes paused on breakpoints + +At the moment, the API is highly experimental; so don't depend on it, +or otherwise expect frequent incompatible changes. +""". + +%% Public API +-export([supported/0]). +-export([instrumentations/0, toggle_instrumentations/1]). +-export([register/1, unregister/2, whereis/0]). +-export([breakpoint/3]). + + +%% Types + +-export_type([session/0, event_message/0, event/0]). + +-doc """ +Debugger session identifier. + +It is attached to all debugger events. +""". +-opaque session() :: integer(). + +-doc """ +The debugger process will receive debugger-event messages, wrapped in +an envelope of this type. +""". +-type event_message() :: + {debugger_event, session(), event()}. + +-doc """ +Debugger events. + +Here are the possible events: + + * `{breakpoint, Pid, {M,F,A}, Line, Resume}`: process Pid hit a breakpoint + on module `M`, at the given `Line`. The debugger can resume the process + by executing `Resume()`. +""". +-type event() :: + {breakpoint, pid(), mfa(), Line :: pos_integer(), Resume :: fun(() -> ok)} . + +-export_type([instrumentation/0]). + +-doc """ +Debugging instrumentations that can be applied on module loading. + + - `line_breakpoint`: Allows setting breakpoints at the beginning + of executable lines +""". +-type instrumentation() :: line_breakpoint. + +%% Capabilities + +-doc """ +Returns `true` if the emulator supports debugging. + +The debugger can only be used if the `+D` argument was passed +to the emulator on start-up. +""". +-spec supported() -> boolean(). +supported() -> + erlang:nif_error(undef). + +-doc """ +Returns the instrumentations that will be applied on module loading. + +Modules that are already loaded may have had a different set of +instrumentations applied. +""". +-spec instrumentations() -> #{instrumentation() => boolean()}. +instrumentations() -> + erlang:nif_error(undef). + +-doc """ +Updates the instrumentations that will be applied on module loading. + +Modules that are already loaded will keep the instrumentation they +had at their time of loading. +""". +-spec toggle_instrumentations(Toggle) -> ok when + Toggle :: #{instrumentation() => boolean()}. +toggle_instrumentations(_) -> + erlang:nif_error(undef). + +%% Registration + +-doc """ +Register the given process as the debugger. + +If the registration succeeds, it returns `{ok, Session}`, where `Session` +is a token that will be included in every message sent to the process. + +Returns `{error, already_exists}` if some process is currently +registered as debugger. +""". +-spec register(Pid) -> {ok, session()} | {error, already_exists} when + Pid :: pid(). +register(_) -> + erlang:nif_error(undef). + +-doc """ +Unregisters the given process. + +The session given on registration needs to be provided. +""". +-spec unregister(Pid, Session) -> ok when + Pid :: pid, + Session :: session(). +unregister(_, _) -> + erlang:nif_error(undef). + +-doc """ +Returns the pid of the registered debugger. +""". +-spec whereis() -> undefined | pid(). +whereis() -> + erlang:nif_error(undef). + + +%% Breakpoints + +-doc """ +Sets or clear a breakpoint on the given Module/Line. + +When a process hits a breakpoint, it will pause and a `breakpoint` +message is sent to the registered debugger. + +Returns `ok` on success. It can fail with the following reasons: + - `{badkey, Module}`: The given module is not loaded. + - `{unsupported, Module}`: The module was loaded without support + for line breakpoints. + - `{badkey, Line}`: The line is not relevant; it could refer to a comment, + not existing in the module source, and so on. + - `{unsupported, Line}`: It is not possible to set a breakpoint in + in the given line; for example, if it refers to a function head. +""". +-spec breakpoint(Module, Line, Flag) -> ok | {error, Reason} when + Module :: module(), + Line :: pos_integer(), + Flag :: boolean(), + Reason :: {unsupported, Module | Line} | {badkey, Module | Line}. +breakpoint(_, _, _) -> + erlang:nif_error(undef). diff --git a/lib/kernel/src/kernel.app.src b/lib/kernel/src/kernel.app.src index 03cb36e8f32d..58180b4a637a 100644 --- a/lib/kernel/src/kernel.app.src +++ b/lib/kernel/src/kernel.app.src @@ -33,6 +33,7 @@ dist_util, erl_boot_server, erl_compile_server, + erl_debugger, erl_distribution, erl_erts_errors, erl_reply, From 441e1eb176d48b30e9c877c23743af02f9b95e30 Mon Sep 17 00:00:00 2001 From: Daniel Gorin <danielgo@meta.com> Date: Tue, 1 Apr 2025 09:26:47 +0100 Subject: [PATCH 2/7] Process debug_line instruction only when instrumenting breakpoints On module loading, `debug_line` are currently ignored. Now, when debugger support is enabled (and the line-breakpoint instrumentation enabled), we emit a `i_debug_line` instruction. For now, we only use it to add entries to the line-table, the actual breakpoint instrumentation is introduced next. --- erts/emulator/beam/beam_code.h | 5 ++ erts/emulator/beam/emu/beam_emu.c | 1 + erts/emulator/beam/emu/emu_load.c | 97 ++++++++++++++------- erts/emulator/beam/emu/ops.tab | 7 +- erts/emulator/beam/emu/predicates.tab | 6 ++ erts/emulator/beam/erl_debugger.h | 6 +- erts/emulator/beam/jit/arm/instr_common.cpp | 7 +- erts/emulator/beam/jit/arm/ops.tab | 6 +- erts/emulator/beam/jit/arm/predicates.tab | 6 ++ erts/emulator/beam/jit/asm_load.c | 12 ++- erts/emulator/beam/jit/x86/instr_common.cpp | 7 +- erts/emulator/beam/jit/x86/ops.tab | 6 +- erts/emulator/beam/jit/x86/predicates.tab | 6 ++ erts/emulator/utils/beam_makeops | 1 + lib/compiler/test/beam_debug_info_SUITE.erl | 4 +- 15 files changed, 129 insertions(+), 48 deletions(-) diff --git a/erts/emulator/beam/beam_code.h b/erts/emulator/beam/beam_code.h index f9a77b4b01ba..20eda6e7d2c7 100644 --- a/erts/emulator/beam/beam_code.h +++ b/erts/emulator/beam/beam_code.h @@ -107,6 +107,11 @@ typedef struct beam_code_header { const BeamDebugTab *debug; #endif + /* + * Debugging instrumentation to use while loading the module + */ + Uint debugger_flags; + /* * Pointer to the module MD5 sum (16 bytes) */ diff --git a/erts/emulator/beam/emu/beam_emu.c b/erts/emulator/beam/emu/beam_emu.c index b1c25df6dc03..cfccaf4e5f36 100644 --- a/erts/emulator/beam/emu/beam_emu.c +++ b/erts/emulator/beam/emu/beam_emu.c @@ -580,6 +580,7 @@ void process_main(ErtsSchedulerData *esdp) OpCase(label_L): OpCase(on_load): OpCase(line_I): + OpCase(i_debug_line_It): OpCase(i_nif_padding): erts_exit(ERTS_ERROR_EXIT, "meta op\n"); diff --git a/erts/emulator/beam/emu/emu_load.c b/erts/emulator/beam/emu/emu_load.c index 964f9d78e5a8..f3087d189d64 100644 --- a/erts/emulator/beam/emu/emu_load.c +++ b/erts/emulator/beam/emu/emu_load.c @@ -29,6 +29,7 @@ #include "beam_load.h" #include "erl_version.h" #include "beam_bp.h" +#include "erl_debugger.h" #define CodeNeed(w) do { \ ASSERT(ci <= codev_size); \ @@ -77,6 +78,7 @@ int beam_load_prepare_emit(LoaderState *stp) { hdr->literal_area = NULL; hdr->md5_ptr = NULL; hdr->are_nifs = NULL; + hdr->debugger_flags = erts_debugger_flags; stp->code_hdr = hdr; @@ -817,6 +819,44 @@ new_string_patch(LoaderState* stp, int pos) stp->string_patches = p; } +static int add_line_entry(LoaderState *stp, + int pos, + BeamInstr item, + int insert_duplicates) { + int is_duplicate; + unsigned int li; + + if (!stp->line_instr) { + return 0; + } + + if (item >= stp->beam.lines.item_count) { + BeamLoadError2(stp, "line instruction index overflow (%u/%u)", + item, stp->beam.lines.item_count); + } + + li = stp->current_li; + is_duplicate = li && (stp->line_instr[li-1].loc == item); + + if (insert_duplicates || !is_duplicate || + li <= stp->func_line[stp->function_number - 1]) { + + if (li >= stp->beam.lines.instruction_count) { + BeamLoadError2(stp, "line instruction table overflow (%u/%u)", + li, stp->beam.lines.instruction_count); + } + + stp->line_instr[li].pos = pos; + stp->line_instr[li].loc = item; + stp->current_li++; + } + + return 0; + +load_error: + return -1; +} + int beam_load_emit_op(LoaderState *stp, BeamOp *tmp_op) { /* The size of the loaded func_info instruction is needed by both the nif * functionality and line instructions. */ @@ -1447,40 +1487,37 @@ int beam_load_emit_op(LoaderState *stp, BeamOp *tmp_op) { break; case op_line_I: - if (stp->line_instr) { - BeamInstr item = code[ci-1]; - unsigned int li; - if (item >= stp->beam.lines.item_count) { - BeamLoadError2(stp, "line instruction index overflow (%u/%u)", - item, stp->beam.lines.item_count); - } - li = stp->current_li; - if (li >= stp->beam.lines.instruction_count) { - BeamLoadError2(stp, "line instruction table overflow (%u/%u)", - li, stp->beam.lines.instruction_count); - } + { + int pos = ci-2; - if (ci - 2 == stp->last_func_start) { - /* - * This line instruction directly follows the func_info - * instruction. Its address must be adjusted to point to - * func_info instruction. - */ - stp->line_instr[li].pos = stp->last_func_start - FUNC_INFO_SZ; - stp->line_instr[li].loc = item; - stp->current_li++; - } else if (li <= stp->func_line[stp->function_number - 1] || - stp->line_instr[li-1].loc != item) { + if (pos == stp->last_func_start) { /* - * Only store the location if it is different - * from the previous location in the same function. - */ - stp->line_instr[li].pos = ci - 2; - stp->line_instr[li].loc = item; - stp->current_li++; + * This line instruction directly follows the func_info + * instruction. Its address must be adjusted to point to + * func_info instruction. + */ + pos = stp->last_func_start - FUNC_INFO_SZ; } + + /* We'll save some memory by not inserting a line entry that + * is equal to the previous one. */ + if (add_line_entry(stp, pos, code[ci-1], 0)) { + goto load_error; + } + ci -= 2; /* Get rid of the instruction */ + } + break; + + case op_i_debug_line_It: + /* Each i_debug_line is a distinct instrumentation point and we don't + * want to miss a single one of them (so they all can be selected), + * so allow duplicates here. + */ + if (add_line_entry(stp, ci-3, code[ci-2], 1)) { + goto load_error; } - ci -= 2; /* Get rid of the instruction */ + + ci -= 3; /* Get rid of the instruction */ break; /* End of code found. */ diff --git a/erts/emulator/beam/emu/ops.tab b/erts/emulator/beam/emu/ops.tab index f31dac7f1931..340ca5fdd864 100644 --- a/erts/emulator/beam/emu/ops.tab +++ b/erts/emulator/beam/emu/ops.tab @@ -97,7 +97,12 @@ line I executable_line _Id _Line => _ -debug_line a u u u => _ +debug_line a==am_entry u u u => _ +debug_line _Kind Loc _Index Live | instrumenting_line_breakpoints() => + i_debug_line Loc Live +debug_line _Kind _Loc _Index _Live => _ + +i_debug_line I t # For the JIT, the init_yregs/1 instruction allows generation of better code. # For the BEAM interpreter, though, it will probably be more efficient to diff --git a/erts/emulator/beam/emu/predicates.tab b/erts/emulator/beam/emu/predicates.tab index 759b43658fe5..72f1a4ed5cd9 100644 --- a/erts/emulator/beam/emu/predicates.tab +++ b/erts/emulator/beam/emu/predicates.tab @@ -83,3 +83,9 @@ pred.negation_is_small(Int) { !(Int.val & ~((((BeamInstr)1) << ((sizeof(Sint)*8)-1))-1)) && IS_SSMALL(-((Sint)Int.val)); } + +// Test whether we are loading a module with line-breakpoint support +pred.instrumenting_line_breakpoints() { + return ERTS_DEBUGGER_IS_ENABLED_IN(S->code_hdr->debugger_flags, + ERTS_DEBUGGER_LINE_BREAKPOINTS); +} diff --git a/erts/emulator/beam/erl_debugger.h b/erts/emulator/beam/erl_debugger.h index 2d2084747da8..4b90cb128013 100644 --- a/erts/emulator/beam/erl_debugger.h +++ b/erts/emulator/beam/erl_debugger.h @@ -20,9 +20,11 @@ #define ERTS_DEBUGGER_ENABLED ((Uint)1 << 0) #define ERTS_DEBUGGER_LINE_BREAKPOINTS ((Uint)1 << 1) +#define ERTS_DEBUGGER_IS_ENABLED_IN(Var, Flgs) \ + ((Var & (Flgs | ERTS_DEBUGGER_ENABLED)) == (Flgs | ERTS_DEBUGGER_ENABLED)) + #define ERTS_DEBUGGER_IS_ENABLED(Flgs) \ - ((erts_debugger_flags & (Flgs | ERTS_DEBUGGER_ENABLED)) == \ - (Flgs | ERTS_DEBUGGER_ENABLED)) + ERTS_DEBUGGER_IS_ENABLED_IN(erts_debugger_flags, Flgs) extern Uint erts_debugger_flags; diff --git a/erts/emulator/beam/jit/arm/instr_common.cpp b/erts/emulator/beam/jit/arm/instr_common.cpp index 5903f63161cb..df75303387ac 100644 --- a/erts/emulator/beam/jit/arm/instr_common.cpp +++ b/erts/emulator/beam/jit/arm/instr_common.cpp @@ -3187,9 +3187,8 @@ void BeamModuleAssembler::emit_coverage(void *coverage, Uint index, Uint size) { } } -void BeamModuleAssembler::emit_debug_line(const ArgAtom &Kind, - const ArgWord &Loc, - const ArgWord &Index, - const ArgWord &Live) { +void BeamModuleAssembler::emit_i_debug_line(const ArgWord &Loc, + const ArgWord &Index, + const ArgWord &Live) { emit_validate(Live); } diff --git a/erts/emulator/beam/jit/arm/ops.tab b/erts/emulator/beam/jit/arm/ops.tab index ddbcc87363a9..8a73ff8c214e 100644 --- a/erts/emulator/beam/jit/arm/ops.tab +++ b/erts/emulator/beam/jit/arm/ops.tab @@ -92,7 +92,11 @@ line I executable_line I I debug_line a==am_entry u u u => _ -debug_line a I I t +debug_line _Kind Loc Index Live | instrumenting_line_breakpoints() => + i_debug_line Loc Index Live +debug_line _Kind _Loc _Index _Live => _ + +i_debug_line I I t allocate t t allocate_heap t I t diff --git a/erts/emulator/beam/jit/arm/predicates.tab b/erts/emulator/beam/jit/arm/predicates.tab index b98a7e331760..6266f62c319b 100644 --- a/erts/emulator/beam/jit/arm/predicates.tab +++ b/erts/emulator/beam/jit/arm/predicates.tab @@ -161,3 +161,9 @@ pred.is_exit_bif(Bif) { } } } + +// Test whether we are loading a module with line-breakpoint support +pred.instrumenting_line_breakpoints() { + return ERTS_DEBUGGER_IS_ENABLED_IN(S->load_hdr->debugger_flags, + ERTS_DEBUGGER_LINE_BREAKPOINTS); +} diff --git a/erts/emulator/beam/jit/asm_load.c b/erts/emulator/beam/jit/asm_load.c index 585c4f3cdcae..3af1bf5bd970 100644 --- a/erts/emulator/beam/jit/asm_load.c +++ b/erts/emulator/beam/jit/asm_load.c @@ -29,6 +29,7 @@ #include "beam_load.h" #include "erl_version.h" #include "beam_bp.h" +#include "erl_debugger.h" #include "beam_asm.h" @@ -68,6 +69,7 @@ int beam_load_prepare_emit(LoaderState *stp) { hdr->literal_area = NULL; hdr->md5_ptr = NULL; hdr->are_nifs = NULL; + hdr->debugger_flags = erts_debugger_flags; stp->coverage = hdr->coverage = NULL; stp->line_coverage_valid = hdr->line_coverage_valid = NULL; @@ -706,11 +708,15 @@ int beam_load_emit_op(LoaderState *stp, BeamOp *tmp_op) { } break; } - case op_debug_line_aIIt: { + case op_i_debug_line_IIt: { BeamFile_DebugItem *items = stp->beam.debug.items; - Uint location_index = tmp_op->a[1].val; - Sint index = tmp_op->a[2].val - 1; + Uint location_index = tmp_op->a[0].val; + Sint index = tmp_op->a[1].val - 1; + /* Each i_debug_line is a distinct instrumentation point and we don't + * want to miss a single one of them (so they all can be selected), + * so allow duplicates here. + */ if (add_line_entry(stp, location_index, 1)) { goto load_error; } diff --git a/erts/emulator/beam/jit/x86/instr_common.cpp b/erts/emulator/beam/jit/x86/instr_common.cpp index 47c0b0332f87..084f45dbd6de 100644 --- a/erts/emulator/beam/jit/x86/instr_common.cpp +++ b/erts/emulator/beam/jit/x86/instr_common.cpp @@ -3335,9 +3335,8 @@ void BeamModuleAssembler::emit_coverage(void *coverage, Uint index, Uint size) { } } -void BeamModuleAssembler::emit_debug_line(const ArgAtom &Kind, - const ArgWord &Loc, - const ArgWord &Index, - const ArgWord &Live) { +void BeamModuleAssembler::emit_i_debug_line(const ArgWord &Loc, + const ArgWord &Index, + const ArgWord &Live) { emit_validate(Live); } diff --git a/erts/emulator/beam/jit/x86/ops.tab b/erts/emulator/beam/jit/x86/ops.tab index 01fd88e39207..da7a86203213 100644 --- a/erts/emulator/beam/jit/x86/ops.tab +++ b/erts/emulator/beam/jit/x86/ops.tab @@ -92,7 +92,11 @@ line I executable_line I I debug_line a==am_entry u u u => _ -debug_line a I I t +debug_line _Kind Loc Index Live | instrumenting_line_breakpoints() => + i_debug_line Loc Index Live +debug_line _Kind _Loc _Index _Live => _ + +i_debug_line I I t allocate t t allocate_heap t I t diff --git a/erts/emulator/beam/jit/x86/predicates.tab b/erts/emulator/beam/jit/x86/predicates.tab index f106ca687696..580ff1baec9b 100644 --- a/erts/emulator/beam/jit/x86/predicates.tab +++ b/erts/emulator/beam/jit/x86/predicates.tab @@ -155,3 +155,9 @@ pred.is_exit_bif(Bif) { } } } + +// Test whether we are loading a module with line-breakpoint support +pred.instrumenting_line_breakpoints() { + return ERTS_DEBUGGER_IS_ENABLED_IN(S->load_hdr->debugger_flags, + ERTS_DEBUGGER_LINE_BREAKPOINTS); +} diff --git a/erts/emulator/utils/beam_makeops b/erts/emulator/utils/beam_makeops index 9585ea569962..d9693cd2f0d5 100755 --- a/erts/emulator/utils/beam_makeops +++ b/erts/emulator/utils/beam_makeops @@ -861,6 +861,7 @@ sub emulator_output { print '#include "erl_binary.h"', "\n"; print '#include "beam_transform_helpers.h"', "\n"; print '#include "erl_global_literals.h"', "\n"; + print '#include "erl_debugger.h"', "\n"; print "\n"; print "const char tag_to_letter[] = {\n "; diff --git a/lib/compiler/test/beam_debug_info_SUITE.erl b/lib/compiler/test/beam_debug_info_SUITE.erl index c4b96ebb8d82..16377e0414c4 100644 --- a/lib/compiler/test/beam_debug_info_SUITE.erl +++ b/lib/compiler/test/beam_debug_info_SUITE.erl @@ -65,7 +65,7 @@ end_per_group(_GroupName, Config) -> Config. smoke(_Config) -> - {ok, Peer, Node} = ?CT_PEER(#{}), + {ok, Peer, Node} = ?CT_PEER(#{args => ["+D"]}), TestBeams0 = get_unique_beam_files(), TestBeams = compiler_beams() ++ TestBeams0, @@ -83,7 +83,7 @@ smoke(_Config) -> """, io:put_chars(S), - HasDbgSupport = erlang:system_info(emu_flavor) =:= jit, + HasDbgSupport = erl_debugger:supported() andalso erlang:system_info(emu_flavor) =:= jit, test_lib:p_run(fun(Beam) -> do_smoke(Beam, Node, HasDbgSupport) From f225b1ceb9b65c12166f6681ac15f2cd09f04863 Mon Sep 17 00:00:00 2001 From: Daniel Gorin <danielgo@meta.com> Date: Thu, 27 Mar 2025 15:55:16 +0000 Subject: [PATCH 3/7] erl_process: Refactor logic to print internal functions in stack traces The logic was duplicated and out of sync. We want to add another internal function for dealing with breakpoints, so better to have all in one place --- erts/emulator/beam/erl_process.c | 29 ++++++++++++++++----------- erts/emulator/beam/erl_process.h | 1 + erts/emulator/beam/erl_process_dump.c | 11 +--------- erts/emulator/beam/hash.h | 2 +- erts/emulator/beam/sys.h | 2 +- erts/emulator/beam/utils.c | 2 +- 6 files changed, 22 insertions(+), 25 deletions(-) diff --git a/erts/emulator/beam/erl_process.c b/erts/emulator/beam/erl_process.c index 4e202e7a1400..85972aea0779 100644 --- a/erts/emulator/beam/erl_process.c +++ b/erts/emulator/beam/erl_process.c @@ -14852,23 +14852,28 @@ erts_program_counter_info(fmtfn_t to, void *to_arg, Process *p) } } +const char* +erts_internal_fun_description_from_pc(ErtsCodePtr x) { + if (x == beam_exit) { + return "<terminate process>"; + } else if (x == beam_continue_exit) { + return "<continue terminate process>"; + } else if (x == beam_normal_exit) { + return "<terminate process normally>"; + } else if (x == 0) { + return "invalid"; + } + else { + return "unknown function"; + } +} + static void print_function_from_pc(fmtfn_t to, void *to_arg, ErtsCodePtr x) { const ErtsCodeMFA *cmfa = erts_find_function_from_pc(x); if (cmfa == NULL) { - if (x == beam_exit) { - erts_print(to, to_arg, "<terminate process>"); - } else if (x == beam_continue_exit) { - erts_print(to, to_arg, "<continue terminate process>"); - } else if (x == beam_normal_exit) { - erts_print(to, to_arg, "<terminate process normally>"); - } - else if (x == 0) { - erts_print(to, to_arg, "invalid"); - } else { - erts_print(to, to_arg, "unknown function"); - } + erts_print(to, to_arg, erts_internal_fun_description_from_pc(x)); } else { const char *mfa_raw, *pc_raw; diff --git a/erts/emulator/beam/erl_process.h b/erts/emulator/beam/erl_process.h index 2c4b36a4d7d3..dd01c530bec8 100644 --- a/erts/emulator/beam/erl_process.h +++ b/erts/emulator/beam/erl_process.h @@ -2148,6 +2148,7 @@ void erts_print_scheduler_info(fmtfn_t to, void *to_arg, ErtsSchedulerData *esdp void erts_print_run_queue_info(fmtfn_t, void *to_arg, ErtsRunQueue*); void erts_dump_extended_process_state(fmtfn_t to, void *to_arg, erts_aint32_t psflg); void erts_dump_process_state(fmtfn_t to, void *to_arg, erts_aint32_t psflg); +const char* erts_internal_fun_description_from_pc(ErtsCodePtr); #define ERTS_PI_FLAG_SINGELTON (1 << 0) #define ERTS_PI_FLAG_ALWAYS_WRAP (1 << 1) diff --git a/erts/emulator/beam/erl_process_dump.c b/erts/emulator/beam/erl_process_dump.c index e463da15f5d1..d120ae92b603 100644 --- a/erts/emulator/beam/erl_process_dump.c +++ b/erts/emulator/beam/erl_process_dump.c @@ -442,16 +442,7 @@ print_function_from_pc(fmtfn_t to, void *to_arg, ErtsCodePtr x) const ErtsCodeMFA* cmfa = erts_find_function_from_pc(x); if (cmfa == NULL) { - if (x == beam_exit) { - erts_print(to, to_arg, "<terminate process>"); - } else if (x == beam_continue_exit) { - erts_print(to, to_arg, "<continue terminate process>"); - } else if (x == beam_normal_exit) { - erts_print(to, to_arg, "<terminate process normally>"); - } - else { - erts_print(to, to_arg, "unknown function"); - } + erts_print(to, to_arg, erts_internal_fun_description_from_pc(x)); } else { const char *mfa_addr, *cp_addr; diff --git a/erts/emulator/beam/hash.h b/erts/emulator/beam/hash.h index 73dfc65de911..7fa6ef9e1668 100644 --- a/erts/emulator/beam/hash.h +++ b/erts/emulator/beam/hash.h @@ -37,7 +37,7 @@ typedef void (*HFREE_FUN)(void*); /* Meta functions */ typedef void* (*HMALLOC_FUN)(int,size_t); typedef void (*HMFREE_FUN)(int,void*); -typedef int (*HMPRINT_FUN)(fmtfn_t,void*,char*, ...); +typedef int (*HMPRINT_FUN)(fmtfn_t,void*,const char*, ...); typedef void (*HFOREACH_FUN)(void *, void *); /* diff --git a/erts/emulator/beam/sys.h b/erts/emulator/beam/sys.h index 15d10aa435d1..cbe96be654f0 100644 --- a/erts/emulator/beam/sys.h +++ b/erts/emulator/beam/sys.h @@ -704,7 +704,7 @@ typedef struct { size_t size; } erts_print_sn_buf; -int erts_print(fmtfn_t to, void *arg, char *format, ...); /* in utils.c */ +int erts_print(fmtfn_t to, void *arg, const char *format, ...); /* in utils.c */ int erts_putc(fmtfn_t to, void *arg, char); /* in utils.c */ /* logger stuff is declared here instead of in global.h, so sys files diff --git a/erts/emulator/beam/utils.c b/erts/emulator/beam/utils.c index 2e79c1a413b1..638dbcf0b38b 100644 --- a/erts/emulator/beam/utils.c +++ b/erts/emulator/beam/utils.c @@ -403,7 +403,7 @@ int erts_fit_in_bits_uint(Uint value) } int -erts_print(fmtfn_t to, void *arg, char *format, ...) +erts_print(fmtfn_t to, void *arg, const char *format, ...) { int res; va_list arg_list; From 55aabeb271c6e782b427544639ea58f2faa2ad94 Mon Sep 17 00:00:00 2001 From: Daniel Gorin <danielgo@meta.com> Date: Thu, 27 Mar 2025 15:55:16 +0000 Subject: [PATCH 4/7] erl_debugger: Add instrumentation for line-breakpoints We add trampolines on each debug_line instruction, similar to the ones used on function entry. The main difference is that we need to save all live X-registers on the stack before calling `erts_internal:breakpoint/4`, and thus may require a GC. --- erts/emulator/beam/beam_bp.c | 64 +++++++++++ erts/emulator/beam/beam_bp.h | 7 ++ erts/emulator/beam/beam_common.h | 1 + erts/emulator/beam/emu/beam_emu.c | 5 + erts/emulator/beam/emu/instrs.tab | 46 ++++++++ erts/emulator/beam/emu/ops.tab | 6 +- erts/emulator/beam/erl_process.c | 2 + .../beam/jit/arm/beam_asm_global.hpp.pl | 19 ++-- .../emulator/beam/jit/arm/beam_asm_module.cpp | 90 +++++++++++++++ erts/emulator/beam/jit/arm/instr_common.cpp | 15 +++ erts/emulator/beam/jit/arm/ops.tab | 3 +- erts/emulator/beam/jit/beam_asm.h | 1 + erts/emulator/beam/jit/beam_jit_main.cpp | 3 + .../beam/jit/x86/beam_asm_global.hpp.pl | 20 ++-- .../emulator/beam/jit/x86/beam_asm_module.cpp | 107 ++++++++++++++++++ erts/emulator/beam/jit/x86/instr_common.cpp | 15 +++ erts/emulator/beam/jit/x86/ops.tab | 3 +- 17 files changed, 387 insertions(+), 20 deletions(-) diff --git a/erts/emulator/beam/beam_bp.c b/erts/emulator/beam/beam_bp.c index d2481ca93052..e6cb308c9e04 100644 --- a/erts/emulator/beam/beam_bp.c +++ b/erts/emulator/beam/beam_bp.c @@ -1492,6 +1492,70 @@ int erts_is_call_break(Process *p, ErtsTraceSession *session, int is_time, return 1; } +const Export * +erts_line_breakpoint_hit__prepare_call(Process* c_p, ErtsCodePtr pc, Uint live, Eterm *regs, UWord *stk) { + FunctionInfo fi; + const Export *ep; + + ASSERT(live <= MAX_REG); + + /* + * Search the error_handler module + */ + ep = erts_find_function(am_erts_internal, am_breakpoint, 4, + erts_active_code_ix()); + if (ep == NULL) { + /* No error handler */ + return NULL; + } + + /* + * Find breakpoint location + */ + erts_lookup_function_info(&fi, pc, 1); + if (!fi.mfa) { + return NULL; + } + + if (ep->info.mfa.module == fi.mfa->module + && ep->info.mfa.function == fi.mfa->function + && ep->info.mfa.arity == fi.mfa->arity) { + /* Cycle breaker */ + return NULL; + } + + /* + * Save live regs on the stack + */ + for(int i = 0; i < live; i++) { + *(stk++) = regs[i]; + } + + regs[0] = fi.mfa->module; + regs[1] = fi.mfa->function; + regs[2] = make_small(fi.mfa->arity); + regs[3] = make_small(LOC_LINE(fi.loc)); + + return ep; +} + +Uint +erts_line_breakpoint_hit__cleanup(Eterm *regs, UWord *stk) { + int i = 0; + + /* + * Restore X-registers + */ + while(is_not_CP(*stk)) { + regs[i++] = *(stk++); + } + + /* + * Return number of registers restored + */ + return i; +} + const ErtsCodeInfo * erts_find_local_func(const ErtsCodeMFA *mfa) { const BeamCodeHeader *code_hdr; diff --git a/erts/emulator/beam/beam_bp.h b/erts/emulator/beam/beam_bp.h index 46acd9dc38f3..0533a33878aa 100644 --- a/erts/emulator/beam/beam_bp.h +++ b/erts/emulator/beam/beam_bp.h @@ -187,6 +187,13 @@ void erts_clear_memory_break(BpFunctions *f); Eterm erts_make_bp_session_list(ErtsHeapFactory*, const ErtsCodeInfo*, Eterm tail); +const Export *erts_line_breakpoint_hit__prepare_call(Process* c_p, + ErtsCodePtr pc, + Uint live, + Eterm *regs, + UWord *stk); +Uint erts_line_breakpoint_hit__cleanup(Eterm *regs, UWord *stk); + const ErtsCodeInfo *erts_find_local_func(const ErtsCodeMFA *mfa); #if ERTS_GLB_INLINE_INCL_FUNC_DEF diff --git a/erts/emulator/beam/beam_common.h b/erts/emulator/beam/beam_common.h index 01559107bf39..f9308fa509f0 100644 --- a/erts/emulator/beam/beam_common.h +++ b/erts/emulator/beam/beam_common.h @@ -285,6 +285,7 @@ extern ErtsCodePtr beam_bif_export_trap; extern ErtsCodePtr beam_export_trampoline; extern ErtsCodePtr beam_continue_exit; extern ErtsCodePtr beam_unloaded_fun; +extern ErtsCodePtr beam_i_line_breakpoint_cleanup; extern ErtsCodePtr beam_return_to_trace; /* OpCode(i_return_to_trace) */ extern ErtsCodePtr beam_return_trace; /* OpCode(i_return_trace) */ diff --git a/erts/emulator/beam/emu/beam_emu.c b/erts/emulator/beam/emu/beam_emu.c index cfccaf4e5f36..892ef2cdce58 100644 --- a/erts/emulator/beam/emu/beam_emu.c +++ b/erts/emulator/beam/emu/beam_emu.c @@ -119,6 +119,8 @@ ErtsCodePtr beam_exit; static BeamInstr beam_continue_exit_[1]; ErtsCodePtr beam_continue_exit; +static BeamInstr beam_i_line_breakpoint_cleanup_[1]; +ErtsCodePtr beam_i_line_breakpoint_cleanup; /* NOTE These should be the only variables containing trace instructions. ** Sometimes tests are for the instruction value, and sometimes @@ -689,6 +691,9 @@ init_emulator_finish(void) beam_continue_exit_[0] = BeamOpCodeAddr(op_continue_exit); beam_continue_exit = (ErtsCodePtr)&beam_continue_exit_[0]; + beam_i_line_breakpoint_cleanup_[0] = BeamOpCodeAddr(op_i_line_breakpoint_cleanup); + beam_i_line_breakpoint_cleanup = (ErtsCodePtr)&beam_i_line_breakpoint_cleanup_[0]; + beam_return_to_trace_[0] = BeamOpCodeAddr(op_i_return_to_trace); beam_return_to_trace = (ErtsCodePtr)&beam_return_to_trace_[0]; diff --git a/erts/emulator/beam/emu/instrs.tab b/erts/emulator/beam/emu/instrs.tab index a108298f27fb..c1140e3736ec 100644 --- a/erts/emulator/beam/emu/instrs.tab +++ b/erts/emulator/beam/emu/instrs.tab @@ -1260,6 +1260,52 @@ raw_raise() { } } +i_disabled_line_breakpoint(_Live) { + /* NOP while the breakpoint is disabled */ +} + +i_enabled_line_breakpoint(Live) { + const Export *ep; + + /* prepare return address for i_line_breakpoint_cleanup */ + $AH(0, 0, $Live); + $SAVE_CONTINUATION_POINTER($NEXT_INSTRUCTION); + + /* prepare frame to save xregs */ + $AH($Live, 0, $Live); + + HEAVY_SWAPOUT; + ep = erts_line_breakpoint_hit__prepare_call(c_p, I, $Live, reg, E+1); + HEAVY_SWAPIN; + + if (ep == NULL) { + /* We are not calling an Erlang function to handle the breakpoint, + so we need to deallocate and continue */ + E += $Live + 2; + $NEXT0(); + } else { + $SAVE_CONTINUATION_POINTER((BeamInstr *) beam_i_line_breakpoint_cleanup); + $NEXT(ep->dispatch.addresses[erts_active_code_ix()]); + } +} + +i_line_breakpoint_cleanup() { + int live_xregs; + + HEAVY_SWAPOUT; + live_xregs = erts_line_breakpoint_hit__cleanup(reg, E+1); + HEAVY_SWAPIN; + + /* deallocate saved xregs and return-address that brought us here */ + E += live_xregs + 1; // AH added one more slot for the CP + + $RETURN(); + + /* remove return address to next instruction and dispatch */ + E += 1; + Goto(*I); +} + // Psuedo-instruction for signalling lambda load errors. Never actually runs. i_lambda_error(Dummy) { diff --git a/erts/emulator/beam/emu/ops.tab b/erts/emulator/beam/emu/ops.tab index 340ca5fdd864..97c7391425bd 100644 --- a/erts/emulator/beam/emu/ops.tab +++ b/erts/emulator/beam/emu/ops.tab @@ -44,6 +44,9 @@ i_generic_breakpoint i_debug_breakpoint i_call_trace_return i_return_to_trace +i_disabled_line_breakpoint t +i_enabled_line_breakpoint t +i_line_breakpoint_cleanup i_yield trace_jump W %hot @@ -99,7 +102,7 @@ executable_line _Id _Line => _ debug_line a==am_entry u u u => _ debug_line _Kind Loc _Index Live | instrumenting_line_breakpoints() => - i_debug_line Loc Live + i_debug_line Loc Live | i_disabled_line_breakpoint Live debug_line _Kind _Loc _Index _Live => _ i_debug_line I t @@ -1612,4 +1615,3 @@ i_update_record_in_place t xy xy t s i_update_record_continue t s i_update_record_in_place_done - diff --git a/erts/emulator/beam/erl_process.c b/erts/emulator/beam/erl_process.c index 85972aea0779..83f100dc75ff 100644 --- a/erts/emulator/beam/erl_process.c +++ b/erts/emulator/beam/erl_process.c @@ -14860,6 +14860,8 @@ erts_internal_fun_description_from_pc(ErtsCodePtr x) { return "<continue terminate process>"; } else if (x == beam_normal_exit) { return "<terminate process normally>"; + } else if (x == beam_i_line_breakpoint_cleanup) { + return "<breakpoint>"; } else if (x == 0) { return "invalid"; } diff --git a/erts/emulator/beam/jit/arm/beam_asm_global.hpp.pl b/erts/emulator/beam/jit/arm/beam_asm_global.hpp.pl index 45ab1d0af9fe..0570b53002b2 100644 --- a/erts/emulator/beam/jit/arm/beam_asm_global.hpp.pl +++ b/erts/emulator/beam/jit/arm/beam_asm_global.hpp.pl @@ -85,6 +85,7 @@ i_get_map_element_hash_shared i_length_guard_shared i_length_body_shared + i_line_breakpoint_trampoline_shared i_loop_rec_shared i_test_yield_shared i_bxor_body_shared @@ -118,29 +119,31 @@ update_map_single_exact_body_shared ); +my @internal_labels = ( + # Labels exported from within process_main + 'context_switch', + 'context_switch_simplified', + 'do_schedule', -# Labels exported from within process_main -my @process_main_labels = qw( - context_switch - context_switch_simplified - do_schedule + # Labels exported from within i_line_breakpoint_trampoline_shared + 'i_line_breakpoint_cleanup', ); my $decl_enums = - gen_list(' %s,', @beam_global_funcs, '', @process_main_labels); + gen_list(' %s,', @beam_global_funcs, '', @internal_labels); my $decl_emit_funcs = gen_list(' void emit_%s(void);', @beam_global_funcs); my $decl_get_funcs = gen_list(' void (*get_%s(void))() { return get(%s); }', - @beam_global_funcs, '', @process_main_labels); + @beam_global_funcs, '', @internal_labels); my $decl_emitPtrs = gen_list(' {%s, &BeamGlobalAssembler::emit_%s},', @beam_global_funcs); my $decl_label_names = - gen_list(' {%s, "%s"},', @beam_global_funcs, '', @process_main_labels); + gen_list(' {%s, "%s"},', @beam_global_funcs, '', @internal_labels); sub gen_list { my ($format, @strings) = @_; diff --git a/erts/emulator/beam/jit/arm/beam_asm_module.cpp b/erts/emulator/beam/jit/arm/beam_asm_module.cpp index 87eaed90e024..c7327b9f9df3 100644 --- a/erts/emulator/beam/jit/arm/beam_asm_module.cpp +++ b/erts/emulator/beam/jit/arm/beam_asm_module.cpp @@ -23,6 +23,10 @@ #include <float.h> #include "beam_asm.hpp" +extern "C" { +#include "beam_bp.h" +} + using namespace asmjit; #ifdef BEAMASM_DUMP_SIZES @@ -254,6 +258,92 @@ void BeamModuleAssembler::emit_i_breakpoint_trampoline() { BEAM_ASM_FUNC_PROLOGUE_SIZE); } +void BeamGlobalAssembler::emit_i_line_breakpoint_trampoline_shared() { + Label exit_trampoline = a.newLabel(); + Label dealloc_and_exit_trampoline = a.newLabel(); + Label after_gc_check = a.newLabel(); + Label dispatch_call = a.newLabel(); + + const auto &saved_live = TMP_MEM1q; + const auto &saved_pc = TMP_MEM2q; + const auto &saved_stack_needed = TMP_MEM3q; + + emit_enter_erlang_frame(); + + /* NB. TMP1 = live */ + a.str(TMP1, saved_live); /* stash live */ + + /* Pass return address of trampoline, will be used to find current function info */ + a.sub(ARG1, a64::x30, imm(8)); /* ARG1 := pc */ + a.str(ARG1, saved_pc); /* Stash pc */ + + /* START allocate live live */ + a.mov(ARG4, TMP1); /* ARG4 := live */ + a.lsl(TMP1, TMP1, imm(3)); /* TMP1 := stack-needed = live * sizeof(Eterm) */ + a.str(TMP1, saved_stack_needed); /* stash stack-needed */ + a.add(ARG3, TMP1, imm(S_RESERVED * 8)); /* ARG3 := stack-needed + S_RESERVED * sizeof(Eterm) */ + + a.add(ARG3, ARG3, HTOP); + a.cmp(ARG3, E); + a.b_ls(after_gc_check); + + /* gc needed */ + aligned_call(labels[garbage_collect]); + a.ldr(TMP1, saved_stack_needed); /* TMP1 := (stashed) stack-needed */ + a.bind(after_gc_check); + + a.sub(E, E, TMP1); + /* END allocate live live */ + + a.mov(ARG1, c_p); + a.ldr(ARG2, saved_pc); /* pc */ + a.ldr(ARG3, saved_live); + load_x_reg_array(ARG4); + a.mov(ARG5, E); /* stk */ + + emit_enter_runtime<Update::eXRegs>(); + runtime_call<const Export* (*)(Process*, ErtsCodePtr, Uint, Eterm *, UWord *), erts_line_breakpoint_hit__prepare_call>(); + emit_leave_runtime<Update::eXRegs>(); + + /* If non-null, ARG1 points to error_handler:breakpoint/4 */ + a.cbnz(ARG1, dispatch_call); + a.ldr(ARG1, saved_stack_needed); /* ARG1 := (stashed) stack-needed */ + a.b(dealloc_and_exit_trampoline); + + a.bind(dispatch_call); + erlang_call(emit_setup_dispatchable_call(ARG1)); + + a.bind(labels[i_line_breakpoint_cleanup]); + load_x_reg_array(ARG1); + a.mov(ARG2, E); /* stk */ + + emit_enter_runtime<Update::eXRegs>(); + runtime_call<Uint (*)(Eterm *, UWord *), erts_line_breakpoint_hit__cleanup>(); + emit_leave_runtime<Update::eXRegs>(); + + a.lsl(ARG1, ARG1, imm(3)); /* ARG1 = stack-needed */ + + a.bind(dealloc_and_exit_trampoline); /* ASUMES ARG1 = stack-needed */ + a.add(E, E, ARG1); + + a.bind(exit_trampoline); + emit_leave_erlang_frame(); + a.ret(a64::x30); +} + +void BeamModuleAssembler::emit_i_line_breakpoint_trampoline() { + /* This prologue is used to implement line-breakpoints. The "b next" can + * be replaced by nops when the breakpoint is enabled, which will instead + * trigger the breakpoint when control goes through here */ + Label next = a.newLabel(); + a.b(next); + + a.bl(resolve_fragment(ga->get_i_line_breakpoint_trampoline_shared(), + disp128MB)); + + a.bind(next); +} + static void i_emit_nyi(const char *msg) { erts_exit(ERTS_ERROR_EXIT, "NYI: %s\n", msg); } diff --git a/erts/emulator/beam/jit/arm/instr_common.cpp b/erts/emulator/beam/jit/arm/instr_common.cpp index df75303387ac..7791e3963ad6 100644 --- a/erts/emulator/beam/jit/arm/instr_common.cpp +++ b/erts/emulator/beam/jit/arm/instr_common.cpp @@ -3191,4 +3191,19 @@ void BeamModuleAssembler::emit_i_debug_line(const ArgWord &Loc, const ArgWord &Index, const ArgWord &Live) { emit_validate(Live); + + /* + * We store live in TMP1, which will be used in case the line-breakpoint + * is enabled in the trampoline that follows. Doing it here keeps the. + * trampoline logic simpler + */ + ASSERT(Live.get() <= MAX_ARG); + mov_imm(TMP1, Live.get()); + + /* The trampoline code for a line-breakpoint needs to be aligned to + * a word, so that changing the code at runtime to enable the breakpoint + * happens atomically. Notice this is emitted before the current offset + * is added to the line-table. + */ + a.align(AlignMode::kCode, 8); } diff --git a/erts/emulator/beam/jit/arm/ops.tab b/erts/emulator/beam/jit/arm/ops.tab index 8a73ff8c214e..120e770b2381 100644 --- a/erts/emulator/beam/jit/arm/ops.tab +++ b/erts/emulator/beam/jit/arm/ops.tab @@ -93,10 +93,11 @@ executable_line I I debug_line a==am_entry u u u => _ debug_line _Kind Loc Index Live | instrumenting_line_breakpoints() => - i_debug_line Loc Index Live + i_debug_line Loc Index Live | i_line_breakpoint_trampoline debug_line _Kind _Loc _Index _Live => _ i_debug_line I I t +i_line_breakpoint_trampoline allocate t t allocate_heap t I t diff --git a/erts/emulator/beam/jit/beam_asm.h b/erts/emulator/beam/jit/beam_asm.h index 5adefe541c8a..cf216ddf88ac 100644 --- a/erts/emulator/beam/jit/beam_asm.h +++ b/erts/emulator/beam/jit/beam_asm.h @@ -70,6 +70,7 @@ void beamasm_emit_coverage(void *instance, void *coverage, Uint index, Uint size); +void beamasm_emit_align(void *instance, uint32_t alignment); ErtsCodePtr beamasm_get_code(void *ba, int label); ErtsCodePtr beamasm_get_lambda(void *ba, int index); const byte *beamasm_get_rodata(void *ba, char *label); diff --git a/erts/emulator/beam/jit/beam_jit_main.cpp b/erts/emulator/beam/jit/beam_jit_main.cpp index dc6451f0b09c..fb6be5a46fe0 100644 --- a/erts/emulator/beam/jit/beam_jit_main.cpp +++ b/erts/emulator/beam/jit/beam_jit_main.cpp @@ -59,6 +59,7 @@ ErtsCodePtr beam_continue_exit; ErtsCodePtr beam_save_calls_export; ErtsCodePtr beam_save_calls_fun; ErtsCodePtr beam_unloaded_fun; +ErtsCodePtr beam_i_line_breakpoint_cleanup; /* NOTE These should be the only variables containing trace instructions. ** Sometimes tests are for the instruction value, and sometimes @@ -391,6 +392,8 @@ void beamasm_init() { beam_unloaded_fun = (ErtsCodePtr)bga->get_unloaded_fun(); + beam_i_line_breakpoint_cleanup = (ErtsCodePtr)bga->get_i_line_breakpoint_cleanup(); + beamasm_metadata_late_init(); } diff --git a/erts/emulator/beam/jit/x86/beam_asm_global.hpp.pl b/erts/emulator/beam/jit/x86/beam_asm_global.hpp.pl index 72b0082ef1dd..35e26e678b99 100755 --- a/erts/emulator/beam/jit/x86/beam_asm_global.hpp.pl +++ b/erts/emulator/beam/jit/x86/beam_asm_global.hpp.pl @@ -82,6 +82,7 @@ i_load_nif_shared i_length_guard_shared i_length_body_shared + i_line_breakpoint_trampoline_shared i_loop_rec_shared i_test_yield_shared int_div_rem_body_shared @@ -116,28 +117,31 @@ update_map_single_exact_body_shared ); -# Labels exported from within process_main -my @process_main_labels = qw( - context_switch - context_switch_simplified - do_schedule +my @internal_labels = ( + # Labels exported from within process_main + 'context_switch', + 'context_switch_simplified', + 'do_schedule', + + # Labels exported from within i_line_breakpoint_trampoline_shared + 'i_line_breakpoint_cleanup', ); my $decl_enums = - gen_list(' %s,', @beam_global_funcs, '', @process_main_labels); + gen_list(' %s,', @beam_global_funcs, '', @internal_labels); my $decl_emit_funcs = gen_list(' void emit_%s(void);', @beam_global_funcs); my $decl_get_funcs = gen_list(' void (*get_%s(void))() { return get(%s); }', - @beam_global_funcs, '', @process_main_labels); + @beam_global_funcs, '', @internal_labels); my $decl_emitPtrs = gen_list(' {%s, &BeamGlobalAssembler::emit_%s},', @beam_global_funcs); my $decl_label_names = - gen_list(' {%s, "%s"},', @beam_global_funcs, '', @process_main_labels); + gen_list(' {%s, "%s"},', @beam_global_funcs, '', @internal_labels); sub gen_list { my ($format, @strings) = @_; diff --git a/erts/emulator/beam/jit/x86/beam_asm_module.cpp b/erts/emulator/beam/jit/x86/beam_asm_module.cpp index bea4d0987406..ac7e6639f391 100644 --- a/erts/emulator/beam/jit/x86/beam_asm_module.cpp +++ b/erts/emulator/beam/jit/x86/beam_asm_module.cpp @@ -22,6 +22,10 @@ #include <float.h> #include "beam_asm.hpp" +extern "C" { +#include "beam_bp.h" +} + using namespace asmjit; #ifdef BEAMASM_DUMP_SIZES @@ -229,6 +233,109 @@ void BeamModuleAssembler::emit_i_breakpoint_trampoline() { BEAM_ASM_FUNC_PROLOGUE_SIZE); } +void BeamGlobalAssembler::emit_i_line_breakpoint_trampoline_shared() { + Label exit_trampoline = a.newLabel(); + Label dealloc_and_exit_trampoline = a.newLabel(); + Label after_gc_check = a.newLabel(); + Label dispatch_call = a.newLabel(); + + emit_enter_frame(); + + const auto &saved_live = TMP_MEM1q; + const auto &saved_pc = TMP_MEM2q; + const auto &saved_stack_needed = TMP_MEM3q; + + /* NB. TMP1 = live */ + a.mov(saved_live, TMP1); /* stash live */ + + /* Pass address of trampoline, will be used to find current function info */ + a.mov(TMP2, x86::qword_ptr(x86::rsp)); + a.sub(TMP2, imm(8)); /* TMP2:= pc */ + a.mov(saved_pc, TMP2); /* Stash pc */ + + /* START allocate live live */ + #if !defined(NATIVE_ERLANG_STACK) + const int cp_space = CP_SIZE; + #else + const int cp_space = 0; + #endif + + a.mov(ARG4, TMP1); /* ARG4 := live */ + a.lea(RET, x86::ptr_abs(cp_space * 8, TMP1, 3)); + /* lea RET, [cp_space * 8 + (TMP1 << 3)] + RET:= stack-needed = (live + cp_space) * sizeof(Eterm) */ + a.mov(saved_stack_needed, RET); /* stash stack-needed */ + + a.lea(ARG3, x86::ptr(RET, S_RESERVED * 8)); + /* ARG3 := stack-needed + S_RESERVED * sizeof(Eterm); */ + + a.lea(ARG3, x86::qword_ptr(HTOP, ARG3)); + a.cmp(ARG3, E); + a.short_().jbe(after_gc_check); + + /* gc needed */ + fragment_call(labels[garbage_collect]); + a.mov(RET, saved_stack_needed); /* RET := (stashed) stack-needed */ + a.bind(after_gc_check); + + a.sub(E, RET); + + #if !defined(NATIVE_ERLANG_STACK) + a.mov(getCPRef(), imm(NIL)); + #endif + /* END allocate live live */ + + a.mov(ARG1, c_p); + a.mov(ARG2, saved_pc); /* pc */ + a.mov(ARG3, saved_live); /* live */ + load_x_reg_array(ARG4); /* reg */ + a.lea(ARG5, x86::qword_ptr(E, cp_space * 8)); /* stk (skipping CP, if needed) */ + + emit_enter_runtime(); + runtime_call<const Export* (*)(Process*, ErtsCodePtr, Uint, Eterm *, UWord *), erts_line_breakpoint_hit__prepare_call>(); + emit_leave_runtime(); + + /* If non-null, RET points to error_handler:breakpoint/4 */ + a.test(RET, RET); + a.jnz(dispatch_call); + a.mov(RET, saved_stack_needed); /* RET := (stashed) stack-needed */ + a.jmp(dealloc_and_exit_trampoline); + + a.bind(dispatch_call); + erlang_call(emit_setup_dispatchable_call(RET), ARG1); + + a.bind(labels[i_line_breakpoint_cleanup]); + load_x_reg_array(ARG1); /* reg */ + a.lea(ARG2, x86::qword_ptr(E, cp_space * 8)); /* stk (skipping CP, if needed) */ + + emit_enter_runtime(); + runtime_call<Uint (*)(Eterm *, UWord *), erts_line_breakpoint_hit__cleanup>(); + emit_leave_runtime(); + + a.lea(RET, x86::ptr_abs(cp_space * 8, RET, 3)); /* RET := stack-needed */ + + a.bind(dealloc_and_exit_trampoline); /* ASSUMES RET = stack-needed */ + a.add(E, RET); + + a.bind(exit_trampoline); + emit_leave_frame(); + a.ret(); +} + +void BeamModuleAssembler::emit_i_line_breakpoint_trampoline() { + /* This prologue is used to implement line-breakpoints. The "jmp next" can + * be replaced by nops when the breakpoint is enabled, which will instead + * trigger the breakpoint when control goes through here */ + Label next = a.newLabel(); + a.short_().jmp(next); + + auto fragment = ga->get_i_line_breakpoint_trampoline_shared(); + aligned_call(resolve_fragment(fragment)); + + a.bind(next); +} + + static void i_emit_nyi(char *msg) { erts_exit(ERTS_ERROR_EXIT, "NYI: %s\n", msg); } diff --git a/erts/emulator/beam/jit/x86/instr_common.cpp b/erts/emulator/beam/jit/x86/instr_common.cpp index 084f45dbd6de..1d517b0daa66 100644 --- a/erts/emulator/beam/jit/x86/instr_common.cpp +++ b/erts/emulator/beam/jit/x86/instr_common.cpp @@ -3339,4 +3339,19 @@ void BeamModuleAssembler::emit_i_debug_line(const ArgWord &Loc, const ArgWord &Index, const ArgWord &Live) { emit_validate(Live); + + /* + * We store live in TMP1, which will be used in case the line-breakpoint + * is enabled in the trampoline that follows. Doing it here keeps the. + * trampoline logic simpler + */ + ASSERT(Live.get() <= MAX_ARG); + a.mov(TMP1, imm(Live.get())); + + /* The trampoline code for a line-breakpoint needs to be aligned to + * a word, so that changing the code at runtime to enable the breakpoint + * happens atomically. Notice this is emitted before the current offset + * is added to the line-table. + */ + a.align(AlignMode::kCode, 8); } diff --git a/erts/emulator/beam/jit/x86/ops.tab b/erts/emulator/beam/jit/x86/ops.tab index da7a86203213..ec50c719c6e2 100644 --- a/erts/emulator/beam/jit/x86/ops.tab +++ b/erts/emulator/beam/jit/x86/ops.tab @@ -93,10 +93,11 @@ executable_line I I debug_line a==am_entry u u u => _ debug_line _Kind Loc Index Live | instrumenting_line_breakpoints() => - i_debug_line Loc Index Live + i_debug_line Loc Index Live | i_line_breakpoint_trampoline debug_line _Kind _Loc _Index _Live => _ i_debug_line I I t +i_line_breakpoint_trampoline allocate t t allocate_heap t I t From 897d32b152e5638fb614afa9d832c9adf881e63e Mon Sep 17 00:00:00 2001 From: Daniel Gorin <danielgo@meta.com> Date: Thu, 27 Mar 2025 15:55:16 +0000 Subject: [PATCH 5/7] beamasm: Factor out logic to flip breakpoint trampolines We want to reuse the logic currently use to flip beakpoints for tracing, etc. However, at the moment, the functions where this happens not only change the code, but also set some flags value that are specific to those cases.. We factor out this part of the code to their own functions. In doing so, we observe that for x86-64, the code was referring to `BEAM_ASM_FUNC_PROLOGUE_SIZE` to determine the offset to use when "disabling" a breakpoint that doesn't seem relevant. The value is indeed 6 (see, e.g., the assertion on the "enabling" case), and this corresponds to: - 1 byte for the NOP 0x90 due to call alignment - 1 byte for the opcode of a `CALL` - 4 bytes for the 32-bit offset of the call target --- erts/emulator/beam/jit/beam_asm.h | 78 +++++++++++++++++++------------ 1 file changed, 47 insertions(+), 31 deletions(-) diff --git a/erts/emulator/beam/jit/beam_asm.h b/erts/emulator/beam/jit/beam_asm.h index cf216ddf88ac..1fb511187460 100644 --- a/erts/emulator/beam/jit/beam_asm.h +++ b/erts/emulator/beam/jit/beam_asm.h @@ -176,67 +176,83 @@ static inline enum erts_asm_bp_flag erts_asm_bp_get_flags( return (enum erts_asm_bp_flag)ci_exec->u.metadata.breakpoint_flag; } -static inline void erts_asm_bp_set_flag(ErtsCodeInfo *ci_rw, - const ErtsCodeInfo *ci_exec, - enum erts_asm_bp_flag flag) { - ASSERT(flag != ERTS_ASM_BP_FLAG_NONE); - (void)ci_exec; - - if (ci_rw->u.metadata.breakpoint_flag == ERTS_ASM_BP_FLAG_NONE) { +static inline void erts_asm_bp_enable(ErtsCodePtr rw_p) { # if defined(__aarch64__) - Uint32 volatile *rw_code = (Uint32 *)erts_codeinfo_to_code(ci_rw); + Uint32 volatile *rw_code = (Uint32 *)rw_p; /* B .next, .enabled: BL breakpoint_handler, .next: */ - ASSERT(rw_code[1] == 0x14000002); + ASSERT(rw_code[0] == 0x14000002); /* Reroute the initial jump instruction to `.enabled`. */ - rw_code[1] = 0x14000001; + rw_code[0] = 0x14000001; # else /* x86_64 */ - byte volatile *rw_code = (byte *)erts_codeinfo_to_code(ci_rw); + byte volatile *rw_code = (byte *)rw_p; /* SHORT JMP .next, NOP, .enabled: CALL breakpoint_handler, .next: */ ASSERT(rw_code[0] == 0xEB && rw_code[1] == 0x06 && rw_code[2] == 0x90 && rw_code[3] == 0xE8); /* Reroute the initial jump instruction to `.enabled`. */ - rw_code[1] = 1; + rw_code[1] = 0x01; # endif - } - ci_rw->u.metadata.breakpoint_flag |= flag; } -static inline void erts_asm_bp_unset_flag(ErtsCodeInfo *ci_rw, - const ErtsCodeInfo *ci_exec, - enum erts_asm_bp_flag flag) { - ASSERT(flag != ERTS_ASM_BP_FLAG_NONE); - (void)ci_exec; - - ci_rw->u.metadata.breakpoint_flag &= ~flag; - - if (ci_rw->u.metadata.breakpoint_flag == ERTS_ASM_BP_FLAG_NONE) { - /* We've removed the last flag, route the branch instruction back - * past the prologue. */ +static inline void erts_asm_bp_disable(ErtsCodePtr rw_p) { # if defined(__aarch64__) - Uint32 volatile *rw_code = (Uint32 *)erts_codeinfo_to_code(ci_rw); + Uint32 volatile *rw_code = (Uint32 *)rw_p; /* B .enabled, .enabled: BL breakpoint_handler, .next: */ - ASSERT(rw_code[1] == 0x14000001); + ASSERT(rw_code[0] == 0x14000001); /* Reroute the initial jump instruction back to `.next`. */ - ERTS_CT_ASSERT(BEAM_ASM_FUNC_PROLOGUE_SIZE == sizeof(Uint32[3])); - rw_code[1] = 0x14000002; + rw_code[0] = 0x14000002; # else /* x86_64 */ - byte volatile *rw_code = (byte *)erts_codeinfo_to_code(ci_rw); + byte volatile *rw_code = (byte *)rw_p; /* SHORT JMP .enabled, NOP, .enabled: CALL breakpoint_handler, .next: */ ASSERT(rw_code[0] == 0xEB && rw_code[1] == 0x01 && rw_code[2] == 0x90 && rw_code[3] == 0xE8); /* Reroute the initial jump instruction back to `.next`. */ - rw_code[1] = BEAM_ASM_FUNC_PROLOGUE_SIZE - 2; + rw_code[1] = 0x06; # endif +} + +static inline void erts_asm_bp_set_flag(ErtsCodeInfo *ci_rw, + const ErtsCodeInfo *ci_exec, + enum erts_asm_bp_flag flag) { + ASSERT(flag != ERTS_ASM_BP_FLAG_NONE); + (void)ci_exec; + + if (ci_rw->u.metadata.breakpoint_flag == ERTS_ASM_BP_FLAG_NONE) { + ErtsCodePtr rw_p = erts_codeinfo_to_code(ci_rw); +# if defined(__aarch64__) + rw_p = (ErtsCodePtr)((Uint32 *)rw_p + 1); +# endif + erts_asm_bp_enable(rw_p); + } + + ci_rw->u.metadata.breakpoint_flag |= flag; +} + +static inline void erts_asm_bp_unset_flag(ErtsCodeInfo *ci_rw, + const ErtsCodeInfo *ci_exec, + enum erts_asm_bp_flag flag) { + ASSERT(flag != ERTS_ASM_BP_FLAG_NONE); + (void)ci_exec; + + ci_rw->u.metadata.breakpoint_flag &= ~flag; + + if (ci_rw->u.metadata.breakpoint_flag == ERTS_ASM_BP_FLAG_NONE) { + /* We've removed the last flag, route the branch instruction back + * past the prologue. */ + ErtsCodePtr rw_p = erts_codeinfo_to_code(ci_rw); +# if defined(__aarch64__) + rw_p = (ErtsCodePtr)((Uint32 *)rw_p + 1); +# endif + erts_asm_bp_disable(rw_p); } } From 69313b9260fb8031d423b3c6c03d56293c0a850d Mon Sep 17 00:00:00 2001 From: Daniel Gorin <danielgo@meta.com> Date: Thu, 27 Mar 2025 15:55:16 +0000 Subject: [PATCH 6/7] erl_debugger: implement erl_debugger:breakpoint/3 BIF --- erts/emulator/beam/atom.names | 1 + erts/emulator/beam/beam_bp.c | 63 +++ erts/emulator/beam/beam_bp.h | 10 + erts/emulator/beam/beam_ranges.c | 50 +++ erts/emulator/beam/erl_debugger.c | 140 ++++++- erts/emulator/beam/global.h | 3 + .../beam/jit/arm/beam_asm_global.hpp.pl | 2 + .../emulator/beam/jit/arm/beam_asm_module.cpp | 80 ++++ erts/emulator/beam/jit/beam_asm.h | 3 + erts/emulator/beam/jit/beam_jit_main.cpp | 4 + .../beam/jit/x86/beam_asm_global.hpp.pl | 3 + .../emulator/beam/jit/x86/beam_asm_module.cpp | 56 +++ erts/emulator/test/erl_debugger_SUITE.erl | 376 +++++++++++++++++- .../test/erl_debugger_SUITE_data/foo.erl | 23 ++ .../test/erl_debugger_SUITE_data/gc_test.erl | 13 + .../erl_debugger_SUITE_data/inlined_funs.erl | 18 + .../many_live_xregs.erl | 45 +++ .../test/erl_debugger_SUITE_data/ping.erl | 6 + 18 files changed, 888 insertions(+), 8 deletions(-) create mode 100644 erts/emulator/test/erl_debugger_SUITE_data/foo.erl create mode 100644 erts/emulator/test/erl_debugger_SUITE_data/gc_test.erl create mode 100644 erts/emulator/test/erl_debugger_SUITE_data/inlined_funs.erl create mode 100644 erts/emulator/test/erl_debugger_SUITE_data/many_live_xregs.erl create mode 100644 erts/emulator/test/erl_debugger_SUITE_data/ping.erl diff --git a/erts/emulator/beam/atom.names b/erts/emulator/beam/atom.names index 3cb20e2452f3..d309e8f6b3ba 100644 --- a/erts/emulator/beam/atom.names +++ b/erts/emulator/beam/atom.names @@ -766,6 +766,7 @@ atom unloaded atom unloaded_only atom unload_cancelled atom unsafe +atom unsupported atom value atom version atom visible diff --git a/erts/emulator/beam/beam_bp.c b/erts/emulator/beam/beam_bp.c index e6cb308c9e04..314226541786 100644 --- a/erts/emulator/beam/beam_bp.c +++ b/erts/emulator/beam/beam_bp.c @@ -1492,6 +1492,69 @@ int erts_is_call_break(Process *p, ErtsTraceSession *session, int is_time, return 1; } +void erts_install_line_breakpoint(struct erl_module_instance *mi, ErtsCodePtr cp_exec) { + ErtsCodePtr cp_rw; + + erts_unseal_module(mi); + cp_rw = erts_writable_code_ptr(mi, cp_exec); + +#ifdef BEAMASM + erts_asm_bp_enable(cp_rw); +#else +{ + BeamInstr volatile *pc = (BeamInstr*)cp_rw; + BeamInstr instr = *pc; + BeamInstr br = BeamOpCodeAddr(op_i_enabled_line_breakpoint_t); + + /* The following write is not protected by any lock. + * See note in erts_install_breakpoints(). + */ + instr = BeamSetCodeAddr(instr, br); + *pc = instr; +} +#endif + + erts_seal_module(mi); +} + +void erts_uninstall_line_breakpoint(struct erl_module_instance *mi, ErtsCodePtr cp_exec) { + ErtsCodePtr cp_rw; + + erts_unseal_module(mi); + cp_rw = erts_writable_code_ptr(mi, cp_exec); + +#ifdef BEAMASM + erts_asm_bp_disable(cp_rw); +#else +{ + BeamInstr volatile *pc = (BeamInstr*)cp_rw; + BeamInstr instr = *pc; + BeamInstr br = BeamOpCodeAddr(op_i_disabled_line_breakpoint_t); + + /* The following write is not protected by any lock. + * See note in erts_install_breakpoints(). + */ + instr = BeamSetCodeAddr(instr, br); + *pc = instr; +} +#endif + + erts_seal_module(mi); +} + +enum erts_is_line_breakpoint erts_is_line_breakpoint_code(ErtsCodePtr p) { +#ifdef BEAMASM + return beamasm_is_line_breakpoint_trampoline(p); +#else + const UWord instr = *(UWord *)p; + if (BeamIsOpCode(instr, op_i_disabled_line_breakpoint_t)) + return IS_DISABLED_LINE_BP; + if (BeamIsOpCode(instr, op_i_enabled_line_breakpoint_t)) + return IS_ENABLED_LINE_BP; + return IS_NOT_LINE_BP; +#endif +} + const Export * erts_line_breakpoint_hit__prepare_call(Process* c_p, ErtsCodePtr pc, Uint live, Eterm *regs, UWord *stk) { FunctionInfo fi; diff --git a/erts/emulator/beam/beam_bp.h b/erts/emulator/beam/beam_bp.h index 0533a33878aa..2cf948428bee 100644 --- a/erts/emulator/beam/beam_bp.h +++ b/erts/emulator/beam/beam_bp.h @@ -116,6 +116,12 @@ typedef struct { BpFunction* matching; /* Matching functions */ } BpFunctions; +enum erts_is_line_breakpoint { + IS_NOT_LINE_BP = 0, + IS_ENABLED_LINE_BP = 1, + IS_DISABLED_LINE_BP = 2, + }; + /* ** Function interface exported from beam_bp.c */ @@ -187,6 +193,10 @@ void erts_clear_memory_break(BpFunctions *f); Eterm erts_make_bp_session_list(ErtsHeapFactory*, const ErtsCodeInfo*, Eterm tail); +void erts_install_line_breakpoint(struct erl_module_instance *, ErtsCodePtr); +void erts_uninstall_line_breakpoint(struct erl_module_instance *, ErtsCodePtr); +enum erts_is_line_breakpoint erts_is_line_breakpoint_code(ErtsCodePtr); + const Export *erts_line_breakpoint_hit__prepare_call(Process* c_p, ErtsCodePtr pc, Uint live, diff --git a/erts/emulator/beam/beam_ranges.c b/erts/emulator/beam/beam_ranges.c index 56cc106c5417..2a4c2a3a245c 100644 --- a/erts/emulator/beam/beam_ranges.c +++ b/erts/emulator/beam/beam_ranges.c @@ -364,3 +364,53 @@ lookup_loc(FunctionInfo* fi, const void* pc, } } } + +ErtsCodePtr +erts_find_next_code_for_line(const BeamCodeHeader* code_hdr, + unsigned int line, + unsigned int *start_from) +{ + const BeamCodeLineTab *lt = code_hdr->line_table; + const UWord num_functions = code_hdr->num_functions; + unsigned int line_index = -1; + unsigned int num_lines; + + if (lt == NULL) { + return NULL; + } + + num_lines = lt->func_tab[num_functions] - lt->func_tab[0]; + + /* NB. While at the moment lt->loc_tab is sorted (except at + * the edges, since module_info/0,1, etc have no line info), + * there's no strong guarantee this will be sorted in general, + * as the compiler could reorder functions, code with no + * dependencies, etc. So we do a linear-search here. + */ + if (lt->loc_size == 2) { + for(unsigned int i=*start_from; i<num_lines; i++) { + int curr_line = LOC_LINE(lt->loc_tab.p2[i]); + if (curr_line == line) { + line_index = i; + *start_from = i+1; + break; + } + } + } else { + for(unsigned int i=*start_from; i<num_lines; i++) { + int curr_line = LOC_LINE(lt->loc_tab.p4[i]); + if (curr_line == line) { + line_index = i; + *start_from = i+1; + break; + } + } + } + + if (line_index == -1) { + *start_from = 0; + return NULL; + } + + return lt->func_tab[0][line_index]; +} diff --git a/erts/emulator/beam/erl_debugger.c b/erts/emulator/beam/erl_debugger.c index a08c8e8dd18c..5fd0f0e150e0 100644 --- a/erts/emulator/beam/erl_debugger.c +++ b/erts/emulator/beam/erl_debugger.c @@ -18,7 +18,9 @@ # include "config.h" #endif + #include "global.h" +#include "beam_bp.h" #include "bif.h" #include "erl_debugger.h" #include "erl_map.h" @@ -248,12 +250,146 @@ erts_send_debugger_event(Process *c_p, Eterm event) /* Line breakpoints */ +/* Protected by code modification permission */ +static struct { + ErtsCodeBarrier barrier; + Process* process; + + Module *module; + ErtsCodePtr first_target; + unsigned int search_next_from; + unsigned int line; + int enable; + int stage; +} finish_line_bp; + +static void line_breakpoint_finisher(void *ignored) +{ + ERTS_LC_ASSERT(erts_has_code_mod_permission()); + + (void)ignored; + + if (finish_line_bp.stage++ == 0) { + struct erl_module_instance *mi = &finish_line_bp.module->curr; + const BeamCodeHeader *code_hdr = finish_line_bp.module->curr.code_hdr; + ErtsCodePtr cp_exec = finish_line_bp.first_target; + unsigned int start_from = finish_line_bp.search_next_from; + unsigned int line = finish_line_bp.line; + + do { + enum erts_is_line_breakpoint curr = erts_is_line_breakpoint_code(cp_exec); + if (finish_line_bp.enable && curr == IS_DISABLED_LINE_BP) { + erts_install_line_breakpoint(mi, cp_exec); + } else if (!finish_line_bp.enable && curr == IS_ENABLED_LINE_BP) { + erts_uninstall_line_breakpoint(mi, cp_exec); + } + cp_exec = erts_find_next_code_for_line(code_hdr, + line, + &start_from); + } while (cp_exec); + + erts_schedule_code_barrier(&finish_line_bp.barrier, + line_breakpoint_finisher, NULL); + } else { + Process* p = finish_line_bp.process; + + erts_release_code_mod_permission(); + + erts_proc_lock(p, ERTS_PROC_LOCK_STATUS); + if (!ERTS_PROC_IS_EXITING(p)) { + erts_resume(p, ERTS_PROC_LOCK_STATUS); + } + erts_proc_unlock(p, ERTS_PROC_LOCK_STATUS); + erts_proc_dec_refc(p); + } +} + BIF_RETTYPE erl_debugger_breakpoint_3(BIF_ALIST_3) { + Eterm module_name, line_term, enable; + int line, found_at_least_once = 0; + Eterm error_type, error_source; + const BeamCodeHeader *code_hdr; + BIF_UNDEF_IF_NO_DEBUGGER_SUPPORT(); - /* TO BE IMPLEMENTED */ - BIF_ERROR(BIF_P, EXC_UNDEF); + module_name = BIF_ARG_1; + if (is_not_atom(module_name)) { + BIF_ERROR(BIF_P, BADARG); + } + + line_term = BIF_ARG_2; + if (is_not_small(line_term)) { + BIF_ERROR(BIF_P, BADARG); + } + line = signed_val(line_term); + + if (line <= 0) { + BIF_ERROR(BIF_P, BADARG); + } + + enable = BIF_ARG_3; + if (enable != am_true && enable != am_false) { + BIF_ERROR(BIF_P, BADARG); + } + + if (!erts_try_seize_code_mod_permission(BIF_P)) { + ERTS_BIF_YIELD3(BIF_TRAP_EXPORT(BIF_erl_debugger_breakpoint_3), + BIF_P, BIF_ARG_1, BIF_ARG_2, BIF_ARG_3); + } + + finish_line_bp.process = BIF_P; + finish_line_bp.enable = (enable == am_true); + finish_line_bp.stage = 0; + finish_line_bp.module = erts_get_module(module_name, + erts_active_code_ix()); + finish_line_bp.line = line; + finish_line_bp.search_next_from = 0; + + if (!finish_line_bp.module) { + error_type = am_badkey, error_source = module_name; + goto error; + } + + code_hdr = finish_line_bp.module->curr.code_hdr; + if (!ERTS_DEBUGGER_IS_ENABLED_IN(code_hdr->debugger_flags, + ERTS_DEBUGGER_LINE_BREAKPOINTS)) { + error_type = am_unsupported, error_source = module_name; + goto error; + } + + do { + finish_line_bp.first_target = erts_find_next_code_for_line(code_hdr, + line, + &finish_line_bp.search_next_from); + found_at_least_once |= !!(finish_line_bp.first_target); + } while (finish_line_bp.first_target && + !erts_is_line_breakpoint_code(finish_line_bp.first_target)); + + if (!finish_line_bp.first_target) { + if (found_at_least_once) { + error_type = am_unsupported, error_source = line_term; + } else { + error_type = am_badkey, error_source = line_term; + } + goto error; + } + + erts_schedule_code_barrier(&finish_line_bp.barrier, + line_breakpoint_finisher, NULL); + erts_proc_inc_refc(BIF_P); + erts_suspend(BIF_P, ERTS_PROC_LOCK_MAIN, NULL); + ERTS_BIF_YIELD_RETURN(BIF_P, am_ok); + + { + Eterm *hp1, *hp2; + error: + erts_release_code_mod_permission(); + + hp1 = HAlloc(BIF_P, 6); + hp2 = hp1 + 3; + return TUPLE2(hp2, am_error, TUPLE2(hp1, error_type, error_source)); + } } BIF_RETTYPE diff --git a/erts/emulator/beam/global.h b/erts/emulator/beam/global.h index 1d0ba3ce63ec..237a26022a94 100644 --- a/erts/emulator/beam/global.h +++ b/erts/emulator/beam/global.h @@ -988,6 +988,9 @@ Eterm erts_preload_module(Process *c_p, ErtsProcLocks c_p_locks, const byte *code, Uint size); void init_load(void); const ErtsCodeMFA* erts_find_function_from_pc(ErtsCodePtr pc); +ErtsCodePtr erts_find_next_code_for_line(const BeamCodeHeader* code_hdr, + unsigned int line, + unsigned int *start_from); Eterm* erts_build_mfa_item(FunctionInfo* fi, Eterm* hp, Eterm args, Eterm* mfa_p, Eterm loc_tail); void erts_set_current_function(FunctionInfo* fi, const ErtsCodeMFA* mfa); diff --git a/erts/emulator/beam/jit/arm/beam_asm_global.hpp.pl b/erts/emulator/beam/jit/arm/beam_asm_global.hpp.pl index 0570b53002b2..c60c98fbcd95 100644 --- a/erts/emulator/beam/jit/arm/beam_asm_global.hpp.pl +++ b/erts/emulator/beam/jit/arm/beam_asm_global.hpp.pl @@ -212,6 +212,8 @@ sub gen_list { return ptrs[lbl]; } + enum erts_is_line_breakpoint is_line_breakpoint_trampoline(ErtsCodePtr); + $decl_get_funcs }; diff --git a/erts/emulator/beam/jit/arm/beam_asm_module.cpp b/erts/emulator/beam/jit/arm/beam_asm_module.cpp index c7327b9f9df3..bf10523e2197 100644 --- a/erts/emulator/beam/jit/arm/beam_asm_module.cpp +++ b/erts/emulator/beam/jit/arm/beam_asm_module.cpp @@ -19,6 +19,7 @@ */ #include <algorithm> +#include <cstring> #include <sstream> #include <float.h> @@ -344,6 +345,85 @@ void BeamModuleAssembler::emit_i_line_breakpoint_trampoline() { a.bind(next); } +enum erts_is_line_breakpoint BeamGlobalAssembler::is_line_breakpoint_trampoline(ErtsCodePtr addr) { + auto pc = static_cast<const int32_t *>(addr); + enum erts_is_line_breakpoint line_bp_type; + + /* The b and bl opcodes take 6 bits, the remaining 26 bits are a + * a signed offset, given in 32-bit words. */ + const auto opcode6_mask = 0xFC000000; + const auto b_opcode = 0x14000000; + const auto bl_opcode = 0x94000000; + + int32_t instr = *pc; + switch (instr) + /* B .next .enabled: BL breakpoint_handler, .next: */ + case b_opcode | 2: + line_bp_type = IS_DISABLED_LINE_BP; + break; + + /* B .enabled .enabled: BL breakpoint_handler, .next: */ + case b_opcode | 1: + line_bp_type = IS_ENABLED_LINE_BP; + break; + + default: + return IS_NOT_LINE_BP; + } + + instr = *++pc; + + /* We expect a bl here. The target is a signed 26-bit offset */ + if ((instr & opcode6_mask) != bl_opcode) { + return IS_NOT_LINE_BP; + } + const int32_t bl_offset = (instr << 6) >> 6; + + /* Offset is expressed in 32-bit words, not bytes */ + pc = pc + bl_offset; + + const auto expected_target = get_i_line_breakpoint_trampoline_shared(); + if (pc == (const int32_t *)expected_target) return line_bp_type; + + /* Now we expect to be in a veneer, that will encode a jump + * to the actual function based on the distance to the pc + * This can be a direct branch if close enough or branch-to-register after + * loading the expected_address (see emit_veneer() method) */ + instr = *pc; + + if ((instr & opcode6_mask) == b_opcode) { + /* using relative branch when expected_target is close enough */ + const int32_t b_offset = (instr << 6) >> 6; + return (pc + b_offset == (const int32_t*) expected_target) + ? line_bp_type + : IS_NOT_LINE_BP; + } + + const auto super_tmp_reg = SUPER_TMP.id(); + /* we expect to see up to four MOVs into SUPER_TMP to load expected_address, + * followed by a `br SUPER_TMP` */ + auto mov_opcode = 0xD2800000 | super_tmp_reg; /* movz SUPER_TMP, #0, lsl #0 */ + + uint64_t expected_target_addr = (uint64_t) expected_target; + for(int32_t hw = 0; hw < 4; hw++){ + uint32_t chunk = expected_target_addr & 0xFFFF; + expected_target_addr >>= 16; + if (chunk == 0) continue; + + if ((uint32_t) instr != (mov_opcode | (hw << 21) | (chunk << 5))) { + return IS_NOT_LINE_BP; + } + + instr = *++pc; + mov_opcode = 0xF2800000 | super_tmp_reg; /* movk SUPER_TMP, #0, lsl #0 */ + }; + + const int32_t expected_br_instr = 0xd61f0000 | (super_tmp_reg << 5); /* br SUPER_TMP */ + return (instr == expected_br_instr) + ? line_bp_type + : IS_NOT_LINE_BP; +} + static void i_emit_nyi(const char *msg) { erts_exit(ERTS_ERROR_EXIT, "NYI: %s\n", msg); } diff --git a/erts/emulator/beam/jit/beam_asm.h b/erts/emulator/beam/jit/beam_asm.h index 1fb511187460..a1fac0572e8a 100644 --- a/erts/emulator/beam/jit/beam_asm.h +++ b/erts/emulator/beam/jit/beam_asm.h @@ -25,6 +25,7 @@ # include "bif.h" # include "erl_fun.h" # include "erl_process.h" +# include "beam_bp.h" # include "beam_code.h" # include "beam_file.h" # include "beam_common.h" @@ -107,6 +108,8 @@ char *beamasm_get_base(void *instance); /* Return current instruction offset, for line information. */ size_t beamasm_get_offset(void *ba); +enum erts_is_line_breakpoint beamasm_is_line_breakpoint_trampoline(ErtsCodePtr addr); + void beamasm_unseal_module(const void *executable_region, void *writable_region, size_t size); diff --git a/erts/emulator/beam/jit/beam_jit_main.cpp b/erts/emulator/beam/jit/beam_jit_main.cpp index fb6be5a46fe0..bd09df30a28f 100644 --- a/erts/emulator/beam/jit/beam_jit_main.cpp +++ b/erts/emulator/beam/jit/beam_jit_main.cpp @@ -692,4 +692,8 @@ extern "C" BeamModuleAssembler *ba = static_cast<BeamModuleAssembler *>(instance); ba->patchStrings(rw_base, string_table); } + + enum erts_is_line_breakpoint beamasm_is_line_breakpoint_trampoline(ErtsCodePtr addr) { + return bga->is_line_breakpoint_trampoline(addr); + } } diff --git a/erts/emulator/beam/jit/x86/beam_asm_global.hpp.pl b/erts/emulator/beam/jit/x86/beam_asm_global.hpp.pl index 35e26e678b99..774e517fc94c 100755 --- a/erts/emulator/beam/jit/x86/beam_asm_global.hpp.pl +++ b/erts/emulator/beam/jit/x86/beam_asm_global.hpp.pl @@ -207,6 +207,9 @@ sub gen_list { return ptrs[lbl]; } + enum erts_is_line_breakpoint is_line_breakpoint_trampoline(ErtsCodePtr); + + $decl_get_funcs }; diff --git a/erts/emulator/beam/jit/x86/beam_asm_module.cpp b/erts/emulator/beam/jit/x86/beam_asm_module.cpp index ac7e6639f391..8d2936685ec0 100644 --- a/erts/emulator/beam/jit/x86/beam_asm_module.cpp +++ b/erts/emulator/beam/jit/x86/beam_asm_module.cpp @@ -19,6 +19,7 @@ */ #include <algorithm> +#include <cstring> #include <float.h> #include "beam_asm.hpp" @@ -335,6 +336,61 @@ void BeamModuleAssembler::emit_i_line_breakpoint_trampoline() { a.bind(next); } +enum erts_is_line_breakpoint BeamGlobalAssembler::is_line_breakpoint_trampoline(ErtsCodePtr addr) { + auto pc = static_cast<const char*>(addr); + uint64_t word; + enum erts_is_line_breakpoint line_bp_type; + std::memcpy(&word, pc, sizeof(word)); + + /* If addr is a trampoline, first two-bytes are either a JMP SHORT with + * offset 1 (breakpoint enabled), or offset 6 (breakpoint disabled). */ + const auto jmp_short_opcode = 0x00EB; + if ((word & 0xFF) != jmp_short_opcode) { + return IS_NOT_LINE_BP; + } + word >>= 8; + switch (word & 0xFF) { + case 1: + line_bp_type = IS_ENABLED_LINE_BP; + break; + case 6: + line_bp_type = IS_DISABLED_LINE_BP; + break; + default: + return IS_NOT_LINE_BP; + } + word >>= 8; + pc += 2; + + /* We expect an aligned call here, because we align the trampoline to 8 bytes, + * we expect a NOP to align the call. The target is a 32-bit offset from the + * call return address (i.e. addr + 2 + 5) */ + const auto aligned_call_opcode = 0xE890; + if ((word & 0xFFFF) != aligned_call_opcode) { + return IS_NOT_LINE_BP; + } + word >>= 16; + const auto call_offset = (static_cast<int64_t>(word) << 32) >> 32; + pc += 6 + call_offset; + + const auto expected_target = (const char*)get_i_line_breakpoint_trampoline_shared(); + if (pc == expected_target) return line_bp_type; + + /* The call target must be to an an entry in the dispatch-table + * that comes at the end of the module, which contains a + * "JMP i_line_breakpoint_trampoline_shared" */ + std::memcpy(&word, pc, sizeof(word)); + + const auto jmp_opcode = 0xE940; + if ((word & 0xFFFF) != jmp_opcode) { + return IS_NOT_LINE_BP; + } + word >>= 16; + const int32_t jmp_offset = (static_cast<int64_t>(word) << 32) >> 32; + pc += 6 + jmp_offset; + + return pc == expected_target ? line_bp_type : IS_NOT_LINE_BP; +} static void i_emit_nyi(char *msg) { erts_exit(ERTS_ERROR_EXIT, "NYI: %s\n", msg); diff --git a/erts/emulator/test/erl_debugger_SUITE.erl b/erts/emulator/test/erl_debugger_SUITE.erl index c3f6a95d1ebc..168b7774e849 100644 --- a/erts/emulator/test/erl_debugger_SUITE.erl +++ b/erts/emulator/test/erl_debugger_SUITE.erl @@ -21,17 +21,35 @@ -export([all/0, groups/0, suite/0]). -export([init_per_suite/1, end_per_suite/1]). -export([init_per_group/2, end_per_group/2]). +-export([init_per_testcase/2, end_per_testcase/2]). -% Test cases +%% Debugger support test cases -export([test_supported_returns_false/1]). -export([test_all_functions_fail_with_undef/1]). -export([test_supported_returns_true/1]). + +%% Instrumentation test cases -export([test_can_toggle_instrumentations/1]). -export([test_toggle_instrumentations_validates_input/1]). + +%% Registration test cases -export([test_register_and_unregister_debugger/1]). -export([test_debugger_unregistered_when_dead/1]). +%% Line-breakpoint test-cases +-export([test_setting_bp_fails_on_module_not_found/1]). +-export([test_setting_bp_fails_on_module_loaded_without_line_bp_instrumentation/1]). +-export([test_setting_bp_fails_on_non_existent_line/1]). +-export([test_setting_bp_fails_on_nonexecutable_line/1]). +-export([test_setting_bp_fails_on_unsupported_lines/1]). +-export([test_stops_and_notifies_debugger_process/1]). +-export([test_works_with_inlined_functions/1]). +-export([test_works_with_large_number_of_live_xregs/1]). +-export([test_works_with_a_huge_stack_depth_which_should_require_gc/1]). +-export([test_avoids_blocking_debugger/1]). + -include_lib("stdlib/include/assert.hrl"). +-include_lib("common_test/include/ct.hrl"). suite() -> [{ct_hooks,[ts_install_cth]}, @@ -42,7 +60,8 @@ all() -> {group, debugger_support_disabled}, {group, debugger_support_enabled}, {group, instrumentations}, - {group, registration} + {group, registration}, + {group, line_breakpoints} ]. groups() -> @@ -61,6 +80,18 @@ groups() -> {registration, [], [ test_register_and_unregister_debugger, test_debugger_unregistered_when_dead + ]}, + {line_breakpoints, [], [ + test_setting_bp_fails_on_module_not_found, + test_setting_bp_fails_on_module_loaded_without_line_bp_instrumentation, + test_setting_bp_fails_on_non_existent_line, + test_setting_bp_fails_on_nonexecutable_line, + test_setting_bp_fails_on_unsupported_lines, + test_stops_and_notifies_debugger_process, + test_works_with_inlined_functions, + test_works_with_large_number_of_live_xregs, + test_works_with_a_huge_stack_depth_which_should_require_gc, + test_avoids_blocking_debugger ]} ]. @@ -72,7 +103,7 @@ end_per_suite(_Config) -> erts_debug:set_internal_state(available_internal_state, false), ok. -init_per_group(debugger_support_disabled, Config) -> +init_per_group(debugger_support_disabled , Config) -> Config; init_per_group(_Group, Config) -> erts_debug:set_internal_state(debugger_support, true), @@ -81,6 +112,110 @@ init_per_group(_Group, Config) -> end_per_group(_Group, _Config) -> ok. +init_per_testcase(test_works_with_inlined_functions, _Config) -> + % TODO(T202887216) unskip once this is fixed + {skip, "+beam_debug_info is currently blocking inline annotations"}; +init_per_testcase(_TC, Config) -> + erl_debugger:supported() andalso + erl_debugger:toggle_instrumentations(#{line_breakpoint => false}), + + NoAutoRegisterGroups = #{ + debugger_support_disabled => [], + debugger_support_enabled => [], + instrumentation => [], + registration => [] + }, + case current_group(Config) of + {ok, Group} when not is_map_key(Group, NoAutoRegisterGroups) -> + {ok, DebuggerSession} = erl_debugger:register(self()), + [{debugger_session, DebuggerSession} | Config]; + _ -> + Config + end. + +end_per_testcase(_TC, Config) -> + erl_debugger:supported() andalso + erl_debugger:toggle_instrumentations(#{line_breakpoint => false}), + + case proplists:get_value(debugger_session, Config, undefined) of + undefined -> + ok; + DebuggerSession -> + ok = erl_debugger:unregister(self(), DebuggerSession) + end, + + ErlFixtures = filelib:wildcard("*.erl", ?config(data_dir, Config)), + [unload_fixture(FixtureFile) || FixtureFile <- ErlFixtures], + ok. + +unload_fixture(FixtureFile) -> + FixtureModule = list_to_atom(filename:basename(FixtureFile, "erl")), + case erlang:module_loaded(FixtureModule) of + false -> ok; + true -> + true = code:delete(FixtureModule), + code:purge(FixtureModule) + end. + +current_group(Config) -> + GroupProps = ?config(tc_group_properties, Config), + case proplists:get_value(name, GroupProps, []) of + [] -> undefined; + Group -> {ok, Group} + end. + +%% Helper macros +-define(expectReceive(Expected), + begin + (fun () -> + receive + __Actual__ = Expected -> __Actual__ + after 2_000 -> + receive + __Actual__ = Expected -> + __Actual__; + __NextMessage__ -> + error({timeout_receiving, ??Expected, {next_message, __NextMessage__}}) + after 0 -> + error({timeout_receiving, ??Expected, nothing_received}) + end + end + end)() + end +). + + +-define(expectDebuggerEvent(Session, Expected), + begin + (fun() -> + {debugger_event, _, __Actual__} = + ?expectReceive({debugger_event, Session, Expected}), + __Actual__ + end)() + end +). + +-define(assertBreakpointHit(Session, MFA, Line), + begin + (fun() -> + {breakpoint, __Pid__, _, _, __Resume__} = + ?expectDebuggerEvent(Session, {breakpoint, _, MFA, Line, _}), + {__Pid__, __Resume__} + end)() + end +). + +-define(assertMailboxEmpty(), + begin + (fun() -> + receive + __Unexpected__ -> error({mailbox_not_empty, __Unexpected__}) + after 0 -> ok + end + end)() + end +). + %% Support tests test_supported_returns_false(_Config) -> false = erl_debugger:supported(), @@ -105,6 +240,12 @@ test_all_functions_fail_with_undef(_Config) -> %% Instrumentation toggling tests test_can_toggle_instrumentations(_Config) -> + #{line_breakpoint := false} = erl_debugger:instrumentations(), + + ok = erl_debugger:toggle_instrumentations(#{}), + #{line_breakpoint := false} = erl_debugger:instrumentations(), + + ok = erl_debugger:toggle_instrumentations(#{line_breakpoint => true}), #{line_breakpoint := true} = erl_debugger:instrumentations(), ok = erl_debugger:toggle_instrumentations(#{}), @@ -112,9 +253,6 @@ test_can_toggle_instrumentations(_Config) -> ok = erl_debugger:toggle_instrumentations(#{line_breakpoint => false}), #{line_breakpoint := false} = erl_debugger:instrumentations(), - - ok = erl_debugger:toggle_instrumentations(#{line_breakpoint => true}), - #{line_breakpoint := true} = erl_debugger:instrumentations(), ok. test_toggle_instrumentations_validates_input(_Config) -> @@ -174,3 +312,229 @@ test_debugger_unregistered_when_dead(_Config) -> Me = erl_debugger:whereis(), ok = erl_debugger:unregister(Me, Session2), ok. + +%% Line-breakpoint tests + +test_setting_bp_fails_on_module_not_found(_Config) -> + Mod = non_existent_module, + Actual = erl_debugger:breakpoint(Mod, 42, true), + Expected = {error, {badkey, Mod}}, + + Expected = Actual, + ok. + + +test_setting_bp_fails_on_module_loaded_without_line_bp_instrumentation(Config) -> + Mod = foo, + erl_debugger:toggle_instrumentations(#{line_breakpoint => false}), + compile_and_load_module(Config, Mod, [beam_debug_info]), + + Actual = erl_debugger:breakpoint(Mod, 42, true), + Expected = {error, {unsupported, Mod}}, + + Expected = Actual, + ok. + +test_setting_bp_fails_on_non_existent_line(Config) -> + Mod = foo, + erl_debugger:toggle_instrumentations(#{line_breakpoint => true}), + compile_and_load_module(Config, Mod, [beam_debug_info]), + + BogusLine = 100_000, + Actual = erl_debugger:breakpoint(Mod, BogusLine, true), + Expected = {error, {badkey, BogusLine}}, + + Expected = Actual, + ok. + +test_setting_bp_fails_on_nonexecutable_line(Config) -> + Mod = foo, + erl_debugger:toggle_instrumentations(#{line_breakpoint => true}), + compile_and_load_module(Config, Mod, [beam_debug_info]), + + BogusLine = 1, + Actual = erl_debugger:breakpoint(Mod, BogusLine, true), + Expected = {error, {badkey, BogusLine}}, + + Expected = Actual, + ok. + +test_setting_bp_fails_on_unsupported_lines(Config) -> + Mod = foo, + erl_debugger:toggle_instrumentations(#{line_breakpoint => true}), + compile_and_load_module(Config, Mod, [line_coverage]), + + % NB. This line is currently unsupported since it is a + % function header (for go/1). + UnsupportedLine = 6, + Actual = erl_debugger:breakpoint(Mod, UnsupportedLine, true), + Expected = {error, {unsupported, UnsupportedLine}}, + + Expected = Actual, + ok. + +test_stops_and_notifies_debugger_process(Config) -> + Session = ?config(debugger_session, Config), + erl_debugger:toggle_instrumentations(#{line_breakpoint => true}), + compile_and_load_module(Config, foo, [beam_debug_info]), + + [ok = erl_debugger:breakpoint(foo, Line, true) || Line <- [7, 10, 12, 18, 19]], + + TestCaseProcess = self(), + Pid = erlang:spawn(fun() -> foo:go(TestCaseProcess) end), + + {Pid, Resume1} = ?assertBreakpointHit(Session, {foo, go, 1}, 7), + ?assertMailboxEmpty(), + ok = Resume1(), + ?expectReceive({executed, Pid, {foo, go, 1}, {line, 7}}), + + ?expectReceive({executed, Pid, {foo, go, 1}, {line, 8}}), % no bp set on line 8 + + {Pid, Resume2} = ?assertBreakpointHit(Session, {foo, go, 1}, 10), + ?assertMailboxEmpty(), + ok = Resume2(), + % NB. no breadcrum on line 10 + + {Pid, Resume3} = ?assertBreakpointHit(Session, {foo, do_stuff, 1}, 18), + ?assertMailboxEmpty(), + ok = Resume3(), + ?expectReceive({executed, Pid, {foo, do_stuff, 1}, {line, 18}}), + + {Pid, Resume4} = ?assertBreakpointHit(Session, {foo, do_stuff, 1}, 19), + ?assertMailboxEmpty(), + ok = Resume4(), + ?expectReceive({executed, Pid, {foo, do_stuff, 1}, {line, 19}}), + + {Pid, Resume5} = ?assertBreakpointHit(Session, {foo, go, 1}, 12), + ?assertMailboxEmpty(), + ok = Resume5(), + ?expectReceive({executed, Pid, {foo, go, 1}, {line, 12}}), + + ?expectReceive({done, Pid}), + ok. + +test_works_with_inlined_functions(Config) -> + Session = ?config(debugger_session, Config), + erl_debugger:toggle_instrumentations(#{line_breakpoint => true}), + + compile_and_load_module(Config, inlined_funs, [beam_debug_info]), + + % Sets a brekpoint inside a function that is inlined away and called + % several times from go/2. This means we will have several occurrences + % of the line with the breakpoint, and we want to ensure they all + % get a breakpoint set + Line = 14, + ok = erl_debugger:breakpoint(inlined_funs, Line, true), + + TestCaseProcess = self(), + X0 = 42, + Pid = erlang:spawn(fun() -> inlined_funs:go(TestCaseProcess, X0) end), + + {Pid, Resume1} = ?assertBreakpointHit(Session, {inlined_funs, go, 2}, Line), + ?assertMailboxEmpty(), + ok = Resume1(), + ?expectReceive({executed, Pid, {inlined_funs, f, 2}, {line, Line}}), + + {Pid, Resume2} = ?assertBreakpointHit(Session, {inlined_funs, go, 2}, Line), + ?assertMailboxEmpty(), + ok = Resume2(), + ?expectReceive({executed, Pid, {inlined_funs, f, 2}, {line, Line}}), + + ExpectedResult = X0 + 2, + ?expectReceive({done, Pid, ExpectedResult}), + ok. + +test_works_with_large_number_of_live_xregs(Config) -> + Session = ?config(debugger_session, Config), + erl_debugger:toggle_instrumentations(#{line_breakpoint => true}), + + compile_and_load_module(Config, many_live_xregs, [beam_debug_info]), + + Line = 16, + ok = erl_debugger:breakpoint(many_live_xregs, Line, true), + + TestCaseProcess = self(), + N = 10, + + Pid = erlang:spawn(fun() -> + Res = erlang:apply(many_live_xregs, many_args, [N, 0 | lists:seq(1, 98)]), + TestCaseProcess ! {result, self(), Res} + end), + + [ + begin + {Pid, Resume} = ?assertBreakpointHit(Session, {many_live_xregs, many_args, 100}, Line), + ?assertMailboxEmpty(), + ok = Resume() + end + || _ <- lists:seq(0,N) + ], + + ExpectedResult = (98 * (98+1) div 2) * N, + ?expectReceive({result, Pid, ExpectedResult}), + ok. + +test_works_with_a_huge_stack_depth_which_should_require_gc(Config) -> + Session = ?config(debugger_session, Config), + erl_debugger:toggle_instrumentations(#{line_breakpoint => true}), + compile_and_load_module(Config, gc_test, [beam_debug_info]), + + Line = 12, + ok = erl_debugger:breakpoint(gc_test, Line, true), + + N = 100_000, + + TC = self(), + Pid = erlang:spawn(fun() -> + gc_test:go({max_recursion_depth, N}), + TC ! {done, self()} + end), + + [ + begin + {Pid, Resume} = ?assertBreakpointHit(Session, {gc_test, go, 1}, Line), + ?assertMailboxEmpty(), + ok = Resume() + end + || _ <- lists:seq(1,N) + ], + + ?expectReceive({done, Pid}), + ok. + +test_avoids_blocking_debugger(Config) -> + Session = ?config(debugger_session, Config), + erl_debugger:toggle_instrumentations(#{line_breakpoint => true}), + compile_and_load_module(Config, ping, [beam_debug_info]), + + Line = 5, + ok = erl_debugger:breakpoint(ping, Line, true), + + TestCaseProcess = self(), + + % Sanity-check: the breakpoint is hit if called by another process + Pid = erlang:spawn(fun() -> ping:ping(TestCaseProcess) end), + {Pid, Resume1} = ?assertBreakpointHit(Session, {ping, ping, 1}, Line), + ?assertMailboxEmpty(), + ok = Resume1(), + ?expectReceive({pong, Pid}), + + ?assertMailboxEmpty(), + + % Call directly from the current process (the registered debugger), the + % breakpoint should be ignored + ping:ping(TestCaseProcess), + + ?expectReceive({pong, TestCaseProcess}), + ?assertMailboxEmpty(), + ok. + +%% Helpers + +compile_and_load_module(Config, Mod, Opts) when is_atom(Mod), is_list(Opts) -> + Data = proplists:get_value(data_dir, Config), + File = filename:join(Data, atom_to_list(Mod) ++ ".erl"), + + {ok, Mod, Code} = compile:file(File, [binary, report | Opts]), + {module, Mod} = code:load_binary(Mod, "", Code), + ok. diff --git a/erts/emulator/test/erl_debugger_SUITE_data/foo.erl b/erts/emulator/test/erl_debugger_SUITE_data/foo.erl new file mode 100644 index 000000000000..a2468f366b9e --- /dev/null +++ b/erts/emulator/test/erl_debugger_SUITE_data/foo.erl @@ -0,0 +1,23 @@ +-module(foo). +-export([go/1]). + +-define(breadcrumb(Pid), breadcrumb(Pid, {?MODULE, ?FUNCTION_NAME, ?FUNCTION_ARITY}, ?LINE)). + +go(Pid) -> + ?breadcrumb(Pid), + ?breadcrumb(Pid), + + do_stuff(Pid), + + ?breadcrumb(Pid), + + Pid ! {done, self()}, + ok. + +do_stuff(Pid) -> + ?breadcrumb(Pid), + ?breadcrumb(Pid), + ok. + +breadcrumb(Pid, MFA, Line) -> + Pid ! {executed, self(), MFA, {line, Line}}. diff --git a/erts/emulator/test/erl_debugger_SUITE_data/gc_test.erl b/erts/emulator/test/erl_debugger_SUITE_data/gc_test.erl new file mode 100644 index 000000000000..c592590884e8 --- /dev/null +++ b/erts/emulator/test/erl_debugger_SUITE_data/gc_test.erl @@ -0,0 +1,13 @@ +-module(gc_test). +-export([go/1]). + +%% NB. If N is high enough, we will eventually need to do a GC to +%% grow the stack. Since we will set a breakpoint before the +%% recursive call, we will be forced to the GC while processing +%% the breakpoint +go({max_recursion_depth, 0}) -> + 1; +go({max_recursion_depth, N}) -> + N_1 = N-1, + Acc = ?MODULE:go({max_recursion_depth, N_1}), + Acc + 1. diff --git a/erts/emulator/test/erl_debugger_SUITE_data/inlined_funs.erl b/erts/emulator/test/erl_debugger_SUITE_data/inlined_funs.erl new file mode 100644 index 000000000000..735b37b5a61c --- /dev/null +++ b/erts/emulator/test/erl_debugger_SUITE_data/inlined_funs.erl @@ -0,0 +1,18 @@ +-module(inlined_funs). +-export([go/2]). + +-compile({inline, [f/2]}). + +-define(breadcrumb(Pid), breadcrumb(Pid, {?MODULE, ?FUNCTION_NAME, ?FUNCTION_ARITY}, ?LINE)). + +go(Pid, X0) -> + X1 = f(Pid, X0), + X2 = f(Pid, X1), + Pid ! {done, self(), X2}. + +f(Pid, X) -> + ?breadcrumb(Pid), + X + 1. + +breadcrumb(Pid, MFA, Line) -> + Pid ! {executed, self(), MFA, {line, Line}}. diff --git a/erts/emulator/test/erl_debugger_SUITE_data/many_live_xregs.erl b/erts/emulator/test/erl_debugger_SUITE_data/many_live_xregs.erl new file mode 100644 index 000000000000..9eaedc668992 --- /dev/null +++ b/erts/emulator/test/erl_debugger_SUITE_data/many_live_xregs.erl @@ -0,0 +1,45 @@ +-module(many_live_xregs). +-export([many_args/100]). + +many_args( + X00, X01, X02, X03, X04, X05, X06, X07, X08, X09, + X10, X11, X12, X13, X14, X15, X16, X17, X18, X19, + X20, X21, X22, X23, X24, X25, X26, X27, X28, X29, + X30, X31, X32, X33, X34, X35, X36, X37, X38, X39, + X40, X41, X42, X43, X44, X45, X46, X47, X48, X49, + X50, X51, X52, X53, X54, X55, X56, X57, X58, X59, + X60, X61, X62, X63, X64, X65, X66, X67, X68, X69, + X70, X71, X72, X73, X74, X75, X76, X77, X78, X79, + X80, X81, X82, X83, X84, X85, X86, X87, X88, X89, + X90, X91, X92, X93, X94, X95, X96, X97, X98, X99 +) -> + Acc = X01, + case X00 of + 0 -> X01; + _ -> + SumX02toX99 = lists:sum([ + X02, X03, X04, X05, X06, X07, X08, X09, + X10, X11, X12, X13, X14, X15, X16, X17, X18, X19, + X20, X21, X22, X23, X24, X25, X26, X27, X28, X29, + X30, X31, X32, X33, X34, X35, X36, X37, X38, X39, + X40, X41, X42, X43, X44, X45, X46, X47, X48, X49, + X50, X51, X52, X53, X54, X55, X56, X57, X58, X59, + X60, X61, X62, X63, X64, X65, X66, X67, X68, X69, + X70, X71, X72, X73, X74, X75, X76, X77, X78, X79, + X80, X81, X82, X83, X84, X85, X86, X87, X88, X89, + X90, X91, X92, X93, X94, X95, X96, X97, X98, X99 + ]), + many_args( + X00-1, + Acc + SumX02toX99, + X02, X03, X04, X05, X06, X07, X08, X09, + X10, X11, X12, X13, X14, X15, X16, X17, X18, X19, + X20, X21, X22, X23, X24, X25, X26, X27, X28, X29, + X30, X31, X32, X33, X34, X35, X36, X37, X38, X39, + X40, X41, X42, X43, X44, X45, X46, X47, X48, X49, + X50, X51, X52, X53, X54, X55, X56, X57, X58, X59, + X60, X61, X62, X63, X64, X65, X66, X67, X68, X69, + X70, X71, X72, X73, X74, X75, X76, X77, X78, X79, + X80, X81, X82, X83, X84, X85, X86, X87, X88, X89, + X90, X91, X92, X93, X94, X95, X96, X97, X98, X99) + end. diff --git a/erts/emulator/test/erl_debugger_SUITE_data/ping.erl b/erts/emulator/test/erl_debugger_SUITE_data/ping.erl new file mode 100644 index 000000000000..44ac5095b19f --- /dev/null +++ b/erts/emulator/test/erl_debugger_SUITE_data/ping.erl @@ -0,0 +1,6 @@ +-module(ping). +-export([ping/1]). + +ping(Pid) -> + Pid ! {pong, self()}, + ok. From 93f4ca9f552aff9859ed0de328486a44992dbea8 Mon Sep 17 00:00:00 2001 From: Daniel Gorin <danielgo@meta.com> Date: Thu, 27 Mar 2025 15:55:16 +0000 Subject: [PATCH 7/7] erl_debugger: add support for inspecting registers and stack frames --- erts/emulator/beam/atom.names | 1 + erts/emulator/beam/bif.tab | 4 + erts/emulator/beam/erl_debugger.c | 384 ++++++++++++++++++ erts/emulator/test/erl_debugger_SUITE.erl | 356 +++++++++++++++- .../erl_debugger_SUITE_data/call_stacks.erl | 40 ++ lib/kernel/src/erl_debugger.erl | 106 +++++ 6 files changed, 873 insertions(+), 18 deletions(-) create mode 100644 erts/emulator/test/erl_debugger_SUITE_data/call_stacks.erl diff --git a/erts/emulator/beam/atom.names b/erts/emulator/beam/atom.names index d309e8f6b3ba..76a0771c35c5 100644 --- a/erts/emulator/beam/atom.names +++ b/erts/emulator/beam/atom.names @@ -690,6 +690,7 @@ atom siginfo atom silent atom size atom skip +atom slots atom spawn_executable atom spawn_driver atom spawn_init diff --git a/erts/emulator/beam/bif.tab b/erts/emulator/beam/bif.tab index 73e2a2866141..43a1232839f9 100644 --- a/erts/emulator/beam/bif.tab +++ b/erts/emulator/beam/bif.tab @@ -820,3 +820,7 @@ bif erl_debugger:unregister/2 bif erl_debugger:whereis/0 bif erl_debugger:breakpoint/3 bif erts_internal:notify_breakpoint_hit/3 +bif erl_debugger:stack_frames/2 +bif erl_debugger:peek_stack_frame_slot/4 +bif erl_debugger:xregs_count/1 +bif erl_debugger:peek_xreg/3 diff --git a/erts/emulator/beam/erl_debugger.c b/erts/emulator/beam/erl_debugger.c index 5fd0f0e150e0..f57f659aa064 100644 --- a/erts/emulator/beam/erl_debugger.c +++ b/erts/emulator/beam/erl_debugger.c @@ -21,7 +21,10 @@ #include "global.h" #include "beam_bp.h" +#include "beam_catches.h" +#include "beam_common.h" #include "bif.h" +#include "big.h" #include "erl_debugger.h" #include "erl_map.h" @@ -434,3 +437,384 @@ erts_internal_notify_breakpoint_hit_3(BIF_ALIST_3) { BIF_RET(am_ok); } + +/* Inspecting stack-frames and X registers */ + +static Process* +suspended_proc_lock(Eterm pid, ErtsProcLocks locks) { + erts_aint32_t state; + erts_aint32_t fail_state = ERTS_PSFLG_FREE | ERTS_PSFLG_RUNNING; + Process *rp = erts_proc_lookup_raw(pid); + + if (!rp) { + return NULL; + } + + state = erts_atomic32_read_nob(&rp -> state); + if (state & fail_state) { + return NULL; + } + + if (!(state & ERTS_PSFLG_SUSPENDED)) { + return NULL; + } + + erts_proc_lock(rp, locks); + state = erts_atomic32_read_nob(&rp -> state); + + if (!(state & ERTS_PSFLG_SUSPENDED)) { + erts_proc_unlock(rp, locks); + rp = NULL; + } + + return rp; +} + +static Eterm +stack_frame_fun_info(Process *c_p, ErtsCodePtr pc, Process *rp, int is_return_addr) { + Eterm fun_info; + FunctionInfo fi; + + if (!is_return_addr) { + if (pc != beam_run_process) { + erts_lookup_function_info(&fi, pc, 1); + } else { + fi.mfa = rp->current; + fi.loc = LINE_INVALID_LOCATION; + } + } else { + ErtsCodePtr return_address = pc; + ErtsCodePtr approx_caller_addr; + + ASSERT(pc != beam_run_process); + +#ifdef BEAMASM + /* Some instructions can be shorter than one word (e.g. call in x86_64), + * so we subtract just one byte from the return address to avoid + * over-shooting the caller. + * */ + approx_caller_addr = ((char*)return_address) - 1; +#else + approx_caller_addr = ((char*)return_address) - sizeof(UWord); +#endif + + erts_lookup_function_info(&fi, approx_caller_addr, 1); + } + + if (fi.mfa == NULL) { + const char *fname = erts_internal_fun_description_from_pc(pc); + fun_info = am_atom_put(fname, sys_strlen(fname)); + } else { + Eterm *hp, mfa, line; + int mfa_arity = 3; + + hp = HAlloc(c_p, MAP2_SZ + (mfa_arity + 1)); + + mfa = make_tuple(hp); + *hp++ = make_arityval(mfa_arity); + *hp++ = fi.mfa->module; + *hp++ = fi.mfa->function; + *hp++ = make_small(fi.mfa->arity); + + line = fi.loc == LINE_INVALID_LOCATION + ? am_undefined + : make_small(LOC_LINE(fi.loc)); + + fun_info = MAP2(hp, am_function, mfa, am_line, line); + } + + return fun_info; +} + +static Eterm +make_value_or_too_large_tuple(Process *p, Eterm val, Uint max_size) { + Uint val_size; + int tup_arity = 2; + Eterm result, *hp; + + hp = HAlloc(p, tup_arity + 1); + result = make_tuple(hp); + *hp++ = make_arityval(tup_arity); + + val_size = size_object(val); + if (val_size <= max_size) { + *hp++ = am_value; + *hp++ = copy_object(val, p); + } else { + *hp++ = ERTS_MAKE_AM("too_large"); + *hp++ = make_small(val_size); + } + + return result; +} + +static Eterm +make_catch_tuple(Process *c_p, ErtsCodePtr catch_addr) { + int tup_arity = 2; + Eterm result, *hp; + + hp = HAlloc(c_p, tup_arity + 1); + result = make_tuple(hp); + *hp++ = make_arityval(tup_arity); + + *hp++ = ERTS_MAKE_AM("catch"); + *hp++ = stack_frame_fun_info(c_p, catch_addr, NULL, 0); + + return result; +} + +BIF_RETTYPE +erl_debugger_stack_frames_2(BIF_ALIST_2) +{ + Eterm pid; + Process *rp = NULL; + int frame_no, max_term_size = -1; + Eterm result = NIL, yregs; + + BIF_UNDEF_IF_NO_DEBUGGER_SUPPORT(); + + pid = BIF_ARG_1; + if (is_not_internal_pid(pid)) { + BIF_ERROR(BIF_P, BADARG); + } + + if (pid == BIF_P->common.id) { + BIF_ERROR(BIF_P, BADARG); + } + + if (is_small(BIF_ARG_2)) { + max_term_size = signed_val(BIF_ARG_2); + } + + if (max_term_size < 0) { + BIF_ERROR(BIF_P, BADARG); + } + + rp = suspended_proc_lock(pid, ERTS_PROC_LOCK_MAIN); + if (!rp) { + BIF_RET(am_running); + } + + frame_no = 0; + yregs = NIL; + for(Eterm *sp = STACK_START(rp) - 1; rp->stop - 1 <= sp; sp--) { + int is_last_iter = (rp->stop - 1 == sp); + int tup_arity; + Eterm *hp, x; + + // On the last iteration, past the stack end, x is the current pc, + // so we get the location of the current stack-frame + x = is_last_iter ? (Eterm) rp->i : *sp; + + if (is_CP(x)) { + int is_return_addr = !is_last_iter; + int frame_info_map_sz; + ErtsCodePtr code_ptr = cp_val(x); + Eterm this_frame, frame_info_map, addr; + + if (!is_last_iter) { + // Typically, we'd call erts_frame_layout() to find the + // actual return address. However, this assumes we are traversing + // the stack in the opposite direction as we do here. So instead + // we inline the logic here + if (ERTS_UNLIKELY(erts_frame_layout == ERTS_FRAME_LAYOUT_FP_RA)) { + ASSERT(cp_val(sp[0]) == NULL || sp < (Eterm*)cp_val(sp[0])); + + x = *--sp; + code_ptr = cp_val(x); + } + } + + addr = erts_make_integer((Uint) code_ptr, BIF_P); + + tup_arity = 3; + frame_info_map_sz = MAP2_SZ; + hp = HAlloc(BIF_P, + 2 /* cons */ + + (tup_arity + 1) /* this_frame */ + + frame_info_map_sz /* frame_info_map */); + + frame_info_map = MAP2(hp, am_code, addr, am_slots, yregs); + hp += frame_info_map_sz; + + this_frame = make_tuple(hp); + *hp++ = make_arityval(tup_arity); + *hp++ = make_small(frame_no++); + *hp++ = stack_frame_fun_info(BIF_P, code_ptr, rp, is_return_addr); + *hp++ = frame_info_map; + + result = CONS(hp, this_frame, result); + + yregs = NIL; + } else { + Eterm yreg_info; + + if (is_catch(x)) { + yreg_info = make_catch_tuple(BIF_P, catch_pc(x)); + } else { + yreg_info = make_value_or_too_large_tuple(BIF_P, x, max_term_size); + } + + hp = HAlloc(BIF_P, 2 /* cons */); + yregs = CONS(hp, yreg_info, yregs); + } + } + + erts_proc_unlock(rp, ERTS_PROC_LOCK_MAIN); + + return result; +} + +BIF_RETTYPE +erl_debugger_peek_stack_frame_slot_4(BIF_ALIST_4) +{ + Eterm pid; + Process *rp = NULL; + int frame_no = -1, yreg_no = -1, max_term_size = -1; + int current_frame, yreg_count; + Eterm result = am_undefined; + + BIF_UNDEF_IF_NO_DEBUGGER_SUPPORT(); + + pid = BIF_ARG_1; + if (is_not_internal_pid(pid)) { + BIF_ERROR(BIF_P, BADARG); + } + + if (pid == BIF_P->common.id) { + BIF_ERROR(BIF_P, BADARG); + } + + if (is_small(BIF_ARG_2)) { + frame_no = signed_val(BIF_ARG_2); + } + + if (is_small(BIF_ARG_3)) { + yreg_no = signed_val(BIF_ARG_3); + } + + if (is_small(BIF_ARG_4)) { + max_term_size = signed_val(BIF_ARG_4); + } + + if (frame_no < 0 || yreg_no < 0 || max_term_size < 0) { + BIF_ERROR(BIF_P, BADARG); + } + + rp = suspended_proc_lock(pid, ERTS_PROC_LOCK_MAIN); + if (!rp) { + BIF_RET(am_running); + } + + current_frame = 0, yreg_count = 0; + for(Eterm *sp = STACK_START(rp) - 1; rp->stop - 1 <= sp; sp--) { + Eterm x; + + // On the last iteration, past the stack end, x is the current pc, + // so we get the location of the current stack-frame + x = rp->stop <= sp ? *sp : (Eterm) rp->i; + + if (is_not_CP(x)) { + yreg_count++; + } else if (current_frame != frame_no) { + current_frame++; + yreg_count = 0; + } else if (yreg_no >= yreg_count) { + result = am_undefined; + break; + } else { + Eterm val = sp[yreg_no + 1]; + + if (is_catch(val)) { + result = make_catch_tuple(BIF_P, catch_pc(val)); + } else { + result = make_value_or_too_large_tuple(BIF_P, val, max_term_size); + } + + break; + } + } + + erts_proc_unlock(rp, ERTS_PROC_LOCK_MAIN); + + return result; +} + +BIF_RETTYPE +erl_debugger_xregs_count_1(BIF_ALIST_1) { + Eterm result, pid; + Process *rp = NULL; + + BIF_UNDEF_IF_NO_DEBUGGER_SUPPORT(); + + pid = BIF_ARG_1; + if (is_not_internal_pid(pid)) { + BIF_ERROR(BIF_P, BADARG); + } + + if (pid == BIF_P->common.id) { + BIF_ERROR(BIF_P, BADARG); + } + + rp = suspended_proc_lock(pid, ERTS_PROC_LOCK_MAIN); + if (!rp) { + BIF_RET(am_running); + } + + result = make_small(rp->arity); + erts_proc_unlock(rp, ERTS_PROC_LOCK_MAIN); + + return result; +} + +BIF_RETTYPE +erl_debugger_peek_xreg_3(BIF_ALIST_3) +{ + Eterm result, pid; + int xreg_no, max_term_size; + Process *rp = NULL; + + BIF_UNDEF_IF_NO_DEBUGGER_SUPPORT(); + + pid = BIF_ARG_1; + if (is_not_internal_pid(pid)) { + BIF_ERROR(BIF_P, BADARG); + } + + if (pid == BIF_P->common.id) { + BIF_ERROR(BIF_P, BADARG); + } + + if (is_small(BIF_ARG_2)) { + xreg_no = signed_val(BIF_ARG_2); + if (xreg_no < 0) { + BIF_ERROR(BIF_P, BADARG); + } + } else { + BIF_ERROR(BIF_P, BADARG); + } + + if (is_small(BIF_ARG_3)) { + max_term_size = signed_val(BIF_ARG_3); + if (max_term_size < 0) { + BIF_ERROR(BIF_P, BADARG); + } + } else { + BIF_ERROR(BIF_P, BADARG); + } + + rp = suspended_proc_lock(pid, ERTS_PROC_LOCK_MAIN); + if (!rp) { + BIF_RET(am_running); + } + + if (xreg_no >= (int) rp->arity) { + result = am_undefined; + } else { + Eterm val = rp->arg_reg[xreg_no]; + result = make_value_or_too_large_tuple(BIF_P, val, max_term_size); + } + + erts_proc_unlock(rp, ERTS_PROC_LOCK_MAIN); + return result; +} diff --git a/erts/emulator/test/erl_debugger_SUITE.erl b/erts/emulator/test/erl_debugger_SUITE.erl index 168b7774e849..3f58940a4f37 100644 --- a/erts/emulator/test/erl_debugger_SUITE.erl +++ b/erts/emulator/test/erl_debugger_SUITE.erl @@ -42,11 +42,23 @@ -export([test_setting_bp_fails_on_non_existent_line/1]). -export([test_setting_bp_fails_on_nonexecutable_line/1]). -export([test_setting_bp_fails_on_unsupported_lines/1]). --export([test_stops_and_notifies_debugger_process/1]). --export([test_works_with_inlined_functions/1]). --export([test_works_with_large_number_of_live_xregs/1]). --export([test_works_with_a_huge_stack_depth_which_should_require_gc/1]). --export([test_avoids_blocking_debugger/1]). +-export([test_hitting_bp_stops_and_notifies_debugger_process/1]). +-export([test_bps_work_with_inlined_functions/1]). +-export([test_bps_work_with_large_number_of_live_xregs/1]). +-export([test_bps_work_with_a_huge_stack_depth_which_should_require_gc/1]). +-export([test_hitting_bp_avoids_blocking_debugger/1]). + +%% Stack-frame tests +-export([test_stack_frames_returns_running_if_not_suspended/1]). +-export([test_stack_frames_returns_frames/1]). +-export([test_stack_frames_returns_y_regs_controlled_by_size/1]). +-export([test_stack_frames_returns_catch/1]). +-export([test_stack_frames_returns_breakpoint_frame/1]). +-export([test_stack_frames_works_with_hibernate/1]). + +%% Register tests +-export([test_peek_stack_frame_slot_works/1]). +-export([test_peek_xreg_works/1]). -include_lib("stdlib/include/assert.hrl"). -include_lib("common_test/include/ct.hrl"). @@ -61,7 +73,9 @@ all() -> {group, debugger_support_enabled}, {group, instrumentations}, {group, registration}, - {group, line_breakpoints} + {group, line_breakpoints}, + {group, stack_frames}, + {group, registers} ]. groups() -> @@ -87,11 +101,23 @@ groups() -> test_setting_bp_fails_on_non_existent_line, test_setting_bp_fails_on_nonexecutable_line, test_setting_bp_fails_on_unsupported_lines, - test_stops_and_notifies_debugger_process, - test_works_with_inlined_functions, - test_works_with_large_number_of_live_xregs, - test_works_with_a_huge_stack_depth_which_should_require_gc, - test_avoids_blocking_debugger + test_hitting_bp_stops_and_notifies_debugger_process, + test_bps_work_with_inlined_functions, + test_bps_work_with_large_number_of_live_xregs, + test_bps_work_with_a_huge_stack_depth_which_should_require_gc, + test_hitting_bp_avoids_blocking_debugger + ]}, + {stack_frames, [], [ + test_stack_frames_returns_running_if_not_suspended, + test_stack_frames_returns_frames, + test_stack_frames_returns_y_regs_controlled_by_size, + test_stack_frames_returns_catch, + test_stack_frames_returns_breakpoint_frame, + test_stack_frames_works_with_hibernate + ]}, + {registers, [], [ + test_peek_stack_frame_slot_works, + test_peek_xreg_works ]} ]. @@ -112,7 +138,7 @@ init_per_group(_Group, Config) -> end_per_group(_Group, _Config) -> ok. -init_per_testcase(test_works_with_inlined_functions, _Config) -> +init_per_testcase(test_bps_work_with_inlined_functions, _Config) -> % TODO(T202887216) unskip once this is fixed {skip, "+beam_debug_info is currently blocking inline annotations"}; init_per_testcase(_TC, Config) -> @@ -362,7 +388,7 @@ test_setting_bp_fails_on_nonexecutable_line(Config) -> test_setting_bp_fails_on_unsupported_lines(Config) -> Mod = foo, erl_debugger:toggle_instrumentations(#{line_breakpoint => true}), - compile_and_load_module(Config, Mod, [line_coverage]), + compile_and_load_module(Config, Mod, [beam_debug_info]), % NB. This line is currently unsupported since it is a % function header (for go/1). @@ -373,7 +399,7 @@ test_setting_bp_fails_on_unsupported_lines(Config) -> Expected = Actual, ok. -test_stops_and_notifies_debugger_process(Config) -> +test_hitting_bp_stops_and_notifies_debugger_process(Config) -> Session = ?config(debugger_session, Config), erl_debugger:toggle_instrumentations(#{line_breakpoint => true}), compile_and_load_module(Config, foo, [beam_debug_info]), @@ -413,7 +439,7 @@ test_stops_and_notifies_debugger_process(Config) -> ?expectReceive({done, Pid}), ok. -test_works_with_inlined_functions(Config) -> +test_bps_work_with_inlined_functions(Config) -> Session = ?config(debugger_session, Config), erl_debugger:toggle_instrumentations(#{line_breakpoint => true}), @@ -444,7 +470,7 @@ test_works_with_inlined_functions(Config) -> ?expectReceive({done, Pid, ExpectedResult}), ok. -test_works_with_large_number_of_live_xregs(Config) -> +test_bps_work_with_large_number_of_live_xregs(Config) -> Session = ?config(debugger_session, Config), erl_debugger:toggle_instrumentations(#{line_breakpoint => true}), @@ -474,7 +500,7 @@ test_works_with_large_number_of_live_xregs(Config) -> ?expectReceive({result, Pid, ExpectedResult}), ok. -test_works_with_a_huge_stack_depth_which_should_require_gc(Config) -> +test_bps_work_with_a_huge_stack_depth_which_should_require_gc(Config) -> Session = ?config(debugger_session, Config), erl_debugger:toggle_instrumentations(#{line_breakpoint => true}), compile_and_load_module(Config, gc_test, [beam_debug_info]), @@ -502,7 +528,7 @@ test_works_with_a_huge_stack_depth_which_should_require_gc(Config) -> ?expectReceive({done, Pid}), ok. -test_avoids_blocking_debugger(Config) -> +test_hitting_bp_avoids_blocking_debugger(Config) -> Session = ?config(debugger_session, Config), erl_debugger:toggle_instrumentations(#{line_breakpoint => true}), compile_and_load_module(Config, ping, [beam_debug_info]), @@ -529,6 +555,283 @@ test_avoids_blocking_debugger(Config) -> ?assertMailboxEmpty(), ok. +%% Stack-frames tests +test_stack_frames_returns_running_if_not_suspended(_Config) -> + P = erlang:spawn_link(fun() -> receive _ -> ok end end), + running = erl_debugger:stack_frames(P, 1), + + true = erlang:suspend_process(P), + [_ | _] = erl_debugger:stack_frames(P, 1), + + true = erlang:resume_process(P), + wait_for_process_status(P, waiting), + + running = erl_debugger:stack_frames(P, 1), + + P ! done, + ok. + +-define(IS_ADDR(Addr), is_integer(Addr) andalso Addr > 0). + +test_stack_frames_returns_frames(Config) -> + erl_debugger:toggle_instrumentations(#{line_breakpoint => true}), + + Mod = call_stacks, + compile_and_load_module(Config, Mod, [beam_debug_info]), + + % To sync from Mod:base_level() + erlang:register(?MODULE, self()), + + % Launch a process, sync at a known location and suspend it + % so we can inspect the stack + P = erlang:spawn(Mod, three_levels, [42, 13]), + ?expectReceive({sync, P}), + wait_for_process_status(P, waiting), + erlang:suspend_process(P), + + Actual = erl_debugger:stack_frames(P, 1), + ?assertMatch( + [ + {4, #{function := {Mod, base_level, 1}, line := 18}, #{slots := [_Y0], code := Addr4}}, + {3, #{function := {Mod, one_level, 1}, line := 13}, #{slots := [], code := Addr3}}, + {2, #{function := {Mod, two_levels, 2}, line := 9}, #{slots := [], code := Addr2}}, + {1, #{function := {Mod, three_levels, 2}, line := 5}, #{slots := [], code := Addr1}}, + {0, '<terminate process normally>', #{slots := [], code := Addr0}} + ] when ?IS_ADDR(Addr0) + andalso ?IS_ADDR(Addr1) + andalso ?IS_ADDR(Addr2) + andalso ?IS_ADDR(Addr3) + andalso ?IS_ADDR(Addr4), + Actual + ), + ok. + +test_stack_frames_returns_y_regs_controlled_by_size(Config) -> + erl_debugger:toggle_instrumentations(#{line_breakpoint => true}), + + Mod = call_stacks, + compile_and_load_module(Config, Mod, [beam_debug_info]), + + % To sync from Mod:base_level() + erlang:register(?MODULE, self()), + + Line = 23, + + % Get the var mapping for Line, so that we ensure we are + % returning Y-registers in the right order + YRegMap = #{ + YRegNo => Var + || {L, {_, SymMap}} <- code:get_debug_info(Mod), + L == Line, + {Var, {y, YRegNo}} <- SymMap + }, + + P = erlang:spawn(Mod, args_as_yvars, [foo, [1,2,3,4,5], ~"hellooooooooo"]), + ?expectReceive({sync, P}), + erlang:suspend_process(P), + + CheckVarsSize = fun(Size, ExpectedVars) -> + case erl_debugger:stack_frames(P, Size) of + [{1, #{function := {Mod, args_as_yvars, 3}, line := Line}, #{slots := YRegs}} | _] -> + ActualVars = #{ + maps:get(YRegNo, YRegMap) => YRegVal + || {YRegNo, YRegVal} <- lists:enumerate(0, YRegs) + }, + ?assertEqual(ExpectedVars, ActualVars) + end + end, + + ExpectedListSize = 10, + ExpectedBinSize = 4, % TODO: we are currently counting only heap space + + % Immediate values are free, we get them even with size 0 + CheckVarsSize(0, #{ + ~"X" => {value, foo}, + ~"Y" => {too_large, ExpectedListSize}, + ~"Z" => {too_large, ExpectedBinSize} + }), + + % Size limit is respected + CheckVarsSize(min(ExpectedListSize, ExpectedBinSize) - 1, #{ + ~"X" => {value, foo}, + ~"Y" => {too_large, ExpectedListSize}, + ~"Z" => {too_large, ExpectedBinSize} + }), + CheckVarsSize(min(ExpectedListSize, ExpectedBinSize), #{ + ~"X" => {value, foo}, + ~"Y" => {too_large, ExpectedListSize}, + ~"Z" => {value, ~"hellooooooooo"} + }), + CheckVarsSize(max(ExpectedListSize, ExpectedBinSize), #{ + ~"X" => {value, foo}, + ~"Y" => {value, [1,2,3,4,5]}, + ~"Z" => {value, ~"hellooooooooo"} + }), + + ok. + +test_stack_frames_returns_catch(Config) -> + erl_debugger:toggle_instrumentations(#{line_breakpoint => true}), + + Mod = call_stacks, + compile_and_load_module(Config, Mod, [beam_debug_info]), + + % To sync from Mod:base_level() + erlang:register(?MODULE, self()), + + P = erlang:spawn(Mod, call_with_catches, [42]), + ?expectReceive({sync, P}), + erlang:suspend_process(P), + + Actual = erl_debugger:stack_frames(P, 0), + ?assertMatch( + [ + {2, + #{function := {call_stacks, call_with_catches_aux, 1}, line := 33}, + #{slots := [ + {value, 43}, + {'catch', #{function := {call_stacks, call_with_catches_aux, 1}, line := 33}} + ]} + }, + {1, + #{function := {call_stacks, call_with_catches, 1}, line := 27}, + #{slots := [ + {value, 42}, + {'catch', #{function := {call_stacks, call_with_catches, 1}, line := 27}} + ]} + }, + {0, '<terminate process normally>', #{slots := []}} + ], + Actual + ), + ok. + +test_stack_frames_returns_breakpoint_frame(Config) -> + Session = ?config(debugger_session, Config), + erl_debugger:toggle_instrumentations(#{line_breakpoint => true}), + + Mod = call_stacks, + compile_and_load_module(Config, Mod, [beam_debug_info]), + + Line = 5, + erl_debugger:breakpoint(Mod, Line, true), + + P = erlang:spawn(Mod, three_levels, [42, 13]), + + {P, _Resume} = ?assertBreakpointHit(Session, {Mod, three_levels, 2}, Line), + erlang:suspend_process(P), + + Actual = erl_debugger:stack_frames(P, 0), + ?assertMatch( + [ + {3, #{function := {erts_internal,breakpoint, 4}}, _}, + {2, '<breakpoint>', #{slots := [_SavedX0 = {value, 42}, _SavedX1 = {value, 13}]}}, + {1, #{function := {call_stacks, three_levels, 2}, line := 5}, #{slots := []}}, + {0, '<terminate process normally>', #{slots := []}} + ], + Actual + ), + ok. + +test_stack_frames_works_with_hibernate(Config) -> + % NB. This testcase should cover all BIFs using beam_run_process internally, + % e.g. when a process is suspended while starting to execute `erlang:apply(M, F, A)` + + erl_debugger:toggle_instrumentations(#{line_breakpoint => true}), + + Mod = call_stacks, + compile_and_load_module(Config, Mod, [beam_debug_info]), + + % To sync from Mod:base_level() + erlang:register(?MODULE, self()), + + P = erlang:spawn(Mod, sync_and_hibernate, []), + ?expectReceive({sync, P}), + erlang:suspend_process(P), + + Actual = erl_debugger:stack_frames(P, 0), + ?assertMatch( + [ + {1, #{function := {erlang, hibernate, 3}, line := undefined}, #{slots := []}}, + {0, '<terminate process normally>', #{slots := []}} + ], + Actual + ), + ok. + +%% Registers tests +test_peek_stack_frame_slot_works(Config) -> + erl_debugger:toggle_instrumentations(#{line_breakpoint => true}), + + Mod = call_stacks, + compile_and_load_module(Config, Mod, [beam_debug_info]), + + % To sync from Mod:base_level() + erlang:register(?MODULE, self()), + + P = erlang:spawn(fun () -> + catch Mod:args_as_yvars(foo, [1,2,3,4,5], ~"hellooooooooo") + end), + ?expectReceive({sync, P}), + + % While not suspended, return running + running = erl_debugger:peek_stack_frame_slot(P, 0, 0, 0), + + erlang:suspend_process(P), + MaxYRegSize = lists:max([ + N + || {_FrameId, _Fun, #{slots := Slots}} <- erl_debugger:stack_frames(P, 0), + {too_large, N} <- Slots + ]), + + CheckItMatchesStackFrames = fun(MaxSize) -> + StackFrames = erl_debugger:stack_frames(P, MaxSize), + [ + ?assertEqual( + SlotVal, + erl_debugger:peek_stack_frame_slot(P, FrameId, SlotNo, MaxSize), + #{frame => FrameId, slot => SlotNo, size => MaxSize} + ) + || {FrameId, _, #{slots := Slots}} <- StackFrames, + {SlotNo, SlotVal} <- lists:enumerate(0, Slots) + ], + ok + end, + + [CheckItMatchesStackFrames(MaxSize) || MaxSize <- lists:seq(0, MaxYRegSize)], + ok. + +test_peek_xreg_works(Config) -> + erl_debugger:toggle_instrumentations(#{line_breakpoint => true}), + + Mod = call_stacks, + compile_and_load_module(Config, Mod, [beam_debug_info]), + + % To sync from Mod:base_level() + erlang:register(?MODULE, self()), + + P = erlang:spawn(Mod, sync_and_hibernate, []), + ?expectReceive({sync, P}), + + % While the process ir running, no results + running = erl_debugger:xregs_count(P), + running = erl_debugger:peek_xreg(P, 0, 0), + + % suspend the process, so we can inspect it + erlang:suspend_process(P), + + % We are paused in a call to erlang:hibernate/3, only X0,X1,X2 are live, + % we the arguments to the call + 3 = erl_debugger:xregs_count(P), + {value, Mod} = erl_debugger:peek_xreg(P, 0, 0), + {value, three_levels} = erl_debugger:peek_xreg(P, 1, 0), + {too_large, ListSize} = erl_debugger:peek_xreg(P, 2, 0), + + % The size control works + {too_large, ListSize} = erl_debugger:peek_xreg(P, 2, ListSize - 1), + {value, [10, 20]} = erl_debugger:peek_xreg(P, 2, ListSize), + ok. + %% Helpers compile_and_load_module(Config, Mod, Opts) when is_atom(Mod), is_list(Opts) -> @@ -538,3 +841,20 @@ compile_and_load_module(Config, Mod, Opts) when is_atom(Mod), is_list(Opts) -> {ok, Mod, Code} = compile:file(File, [binary, report | Opts]), {module, Mod} = code:load_binary(Mod, "", Code), ok. + +wait_for_process_status(P, Status) -> + wait_for_process_status(P, Status, 2_000). + +wait_for_process_status(_, _, Timeout) when Timeout =< 0 -> + error(timeout_waiting_for_status); +wait_for_process_status(P, Status, Timeout) when is_integer(Timeout) -> + T0 = erlang:system_time(millisecond), + + case erlang:process_info(P, status) of + {status, Status} -> + ok; + _ -> + T1 = erlang:system_time(millisecond), + Elapsed = T1 - T0, + wait_for_process_status(P, Status, Timeout - Elapsed) + end. diff --git a/erts/emulator/test/erl_debugger_SUITE_data/call_stacks.erl b/erts/emulator/test/erl_debugger_SUITE_data/call_stacks.erl new file mode 100644 index 000000000000..288ae5415400 --- /dev/null +++ b/erts/emulator/test/erl_debugger_SUITE_data/call_stacks.erl @@ -0,0 +1,40 @@ +-module(call_stacks). +-export([three_levels/2, args_as_yvars/3, call_with_catches/1, sync_and_hibernate/0]). + +three_levels(X, Y) -> + Foo = two_levels(X + 1, Y * 2), + Foo + 3. + +two_levels(X, Y) -> + Bar = one_level(X * Y), + Bar * 21. + +one_level(X) -> + Hey = base_level(X * 5), + Hey + 1. + +base_level(X) -> + erl_debugger_SUITE ! {sync, self()}, + receive continue -> ok end, + X * 25. + +args_as_yvars(X, Y, Z) -> + erl_debugger_SUITE ! {sync, self()}, + receive continue -> ok end, + {X, Y, Z}. + +call_with_catches(X) -> + Y = catch call_with_catches_aux(X + 1), + {X, Y}. + +call_with_catches_aux(Z) -> + try + erl_debugger_SUITE ! {sync, self()}, + receive continue -> ok end + catch _:_ -> + error({bam, Z}) + end. + +sync_and_hibernate() -> + erl_debugger_SUITE ! {sync, self()}, + erlang:hibernate(?MODULE, three_levels, [10, 20]). diff --git a/lib/kernel/src/erl_debugger.erl b/lib/kernel/src/erl_debugger.erl index ad9c993094f0..2e4fba423edb 100644 --- a/lib/kernel/src/erl_debugger.erl +++ b/lib/kernel/src/erl_debugger.erl @@ -25,6 +25,7 @@ there can be at most one such process registered at any given time. Using the BIFs in this module, a debugger can: - set breakpoints; + - inspect internal process state, such registers, stack-frames; - get notified on debugger events such as a process hitting a breakpoint; - resume processes paused on breakpoints @@ -37,6 +38,8 @@ or otherwise expect frequent incompatible changes. -export([instrumentations/0, toggle_instrumentations/1]). -export([register/1, unregister/2, whereis/0]). -export([breakpoint/3]). +-export([stack_frames/2, peek_stack_frame_slot/4]). +-export([xregs_count/1, peek_xreg/3]). %% Types @@ -69,6 +72,53 @@ Here are the possible events: -type event() :: {breakpoint, pid(), mfa(), Line :: pos_integer(), Resume :: fun(() -> ok)} . + +-export_type([stack_frame/0, stack_frame_fun/0, stack_frame_info/0, stack_frame_slot/0, reg_val/0]). + +-doc """ +A stack-frame, including the value of each slot. +""". +-type stack_frame() :: + {FrameNo :: non_neg_integer(), stack_frame_fun(), stack_frame_info()}. + +-doc """ +What is running in each stack frame, including special VM frames. +""". +-type stack_frame_fun() :: + #{function := mfa(), line := pos_integer() | undefined} + | '<terminate process>' + | '<continue terminate process>' + | '<terminate process normally>' + | '<breakpoint>' + | 'unknown function'. + +-doc """ +Extra information about a stack-frame. + + - `slots`: Y-registers (in order `[Y0,...Yk])`, followed by exception-handlers. + - `code`: Memory address of the next instruction to execute in this frame. +""". +-type stack_frame_info() :: #{ + slots := [stack_frame_slot()], + code := pos_integer() +}. + +-doc """ +The contents of a stack frame slot can be a Y register +or an exception handler. +""". +-type stack_frame_slot() :: + reg_val() | {'catch', stack_frame_fun()}. + +-doc """ +The value of an X or a Y register, provided it fits within the requested +size. + +If it is too large, then size of the term. +""". +-type reg_val() :: + {value, term()} | {too_large, Size :: pos_integer()}. + -export_type([instrumentation/0]). -doc """ @@ -171,3 +221,59 @@ Returns `ok` on success. It can fail with the following reasons: Reason :: {unsupported, Module | Line} | {badkey, Module | Line}. breakpoint(_, _, _) -> erlang:nif_error(undef). + + +%% Stack frames + +-doc """ +Get the all the stack-frames for a suspended process. + +If the given process is not in a suspended state, returns `running`. +Otherwise, a list of [stack frames](t:stack_frame/0) including the +content of each slot is returned. For slots containing terms, +`MaxTermSize` controls the maximum size of values that are allowed to +be returned (to avoid accidentally blowing the heap of the caller). +""". +-spec stack_frames(Pid, MaxTermSize) -> running | [stack_frame()] when + Pid :: pid(), + MaxTermSize :: non_neg_integer(). +stack_frames(_, _) -> + erlang:nif_error(undef). + +-doc """ +Gets the value of a slot in a suspended process stack-frame. + +Returns `running` if the process is not suspended, and `undefined` +if the frame or the slot does not exist for that process. +Otherwise, returns the slot, that can be a term, if its size is less +than `MaxTermSize`, or an exeption handler. +""". +-spec peek_stack_frame_slot(Pid, FrameNo, Slot, MaxSize) -> + running | undefined | stack_frame_slot() when + Pid :: pid(), + FrameNo :: pos_integer(), + Slot :: non_neg_integer(), + MaxSize :: non_neg_integer(). +peek_stack_frame_slot(_, _, _, _) -> + erlang:nif_error(undef). + +%% Process registers + +-doc """ +Get the number of X registers currently in use by a suspended process. +""". +-spec xregs_count(Pid) -> running | non_neg_integer() when + Pid :: pid(). +xregs_count(_) -> + erlang:nif_error(undef). + +-doc """ +Get the value of an X register for a suspended process. +""". +-spec peek_xreg(Pid, Reg, MaxSize) -> + running | undefined | reg_val() when + Pid :: pid(), + Reg :: non_neg_integer(), + MaxSize :: non_neg_integer(). +peek_xreg(_, _, _) -> + erlang:nif_error(undef).