diff --git a/erts/emulator/beam/atom.names b/erts/emulator/beam/atom.names index d64282d4d62f..6fb9d5bb6fea 100644 --- a/erts/emulator/beam/atom.names +++ b/erts/emulator/beam/atom.names @@ -169,6 +169,7 @@ atom call_time atom call_trace_return atom caller atom caller_line +atom calls atom capture atom case_clause atom caseless @@ -317,6 +318,7 @@ atom flush_timeout atom force atom format_bs_fail atom format_cpu_topology +atom frame_size atom free atom fullsweep_after atom function @@ -771,6 +773,7 @@ atom unload_cancelled atom unsafe atom unsupported atom value +atom vars atom version atom visible atom wait_release_literal_area_switch diff --git a/erts/emulator/beam/beam_bif_load.c b/erts/emulator/beam/beam_bif_load.c index dfbc75f9b6a3..ff422501e31b 100644 --- a/erts/emulator/beam/beam_bif_load.c +++ b/erts/emulator/beam/beam_bif_load.c @@ -35,6 +35,7 @@ #include "beam_bp.h" #include "beam_catches.h" #include "erl_binary.h" +#include "erl_map.h" #include "erl_nif.h" #include "erl_bits.h" #include "erl_thr_progress.h" @@ -1261,7 +1262,7 @@ BIF_RETTYPE code_get_debug_info_1(BIF_ALIST_1) const BeamCodeHeader* hdr; const BeamCodeLineTab* lt; const BeamDebugTab* debug; - Sint i; + Sint i, j; Uint alloc_size; Eterm result = NIL; Eterm* hp; @@ -1290,29 +1291,55 @@ BIF_RETTYPE code_get_debug_info_1(BIF_ALIST_1) alloc_size = 0; for (i = 0; i < debug->item_count; i++) { - /* [ {Line, {FrameSize, Pairs}} ] */ - alloc_size += 2 + 3 + 3; + Uint num_vars = debug->items[i].num_vars; + Uint num_calls_terms = debug->items[i].num_calls_terms; + + /* [ {Line, #{frame_size => FrameSize, vars => Pairs, calls => Calls}} ] */ + alloc_size += 2 + 3 + MAP3_SZ; + /* Pairs = [{Name, Value}], where Value is an atom or 2-tuple. * * Assume they are all 2-tuples and HRelease() the excess * later. */ - alloc_size += debug->items[i].num_vars * (2 + 3 + 3); + alloc_size += num_vars * (2 + 3 + 3); + + /* Calls = [mfa() | {atom(), arity()} | binary() */ + for(j=0; j < num_calls_terms; j++) { + Eterm curr = debug->items[i].first[num_vars + j]; + + alloc_size += 2; /* cons */ + if (is_integer(curr)) { + if (unsigned_val(curr) <= MAX_ARG) { + /* mfa() */ + alloc_size += 4; + j+=2; + } else { + /* {atom, arity()} */ + alloc_size += 3; + j+=1; + } + } + } } hp = HAlloc(BIF_P, alloc_size); hend = hp + alloc_size; for (i = debug->item_count-1; i >= 0; i--) { - BeamDebugItem* items = &debug->items[i]; - Sint frame_size = items->frame_size; - Uint num_vars = items->num_vars; - Eterm *tp = &items->first[2 * (num_vars - 1)]; + BeamDebugItem* item = &debug->items[i]; + Sint frame_size = item->frame_size; + Uint num_vars = item->num_vars; + Uint num_calls_terms = item->num_calls_terms; + Eterm *tp; Uint32 location_index, location; Eterm frame_size_term; Eterm var_list = NIL; + Eterm calls_list = NIL; Eterm tmp; + int last_vars_idx = 2 * (num_vars - 1); + int last_calls_term_idx = 2 * num_vars + (num_calls_terms - 1); - location_index = items->location_index; + location_index = item->location_index; if (location_index == ERTS_UINT32_MAX) { continue; @@ -1337,6 +1364,7 @@ BIF_RETTYPE code_get_debug_info_1(BIF_ALIST_1) break; } + tp = &item->first[last_vars_idx]; while (num_vars-- != 0) { Eterm val; Eterm tag; @@ -1367,8 +1395,39 @@ BIF_RETTYPE code_get_debug_info_1(BIF_ALIST_1) hp += 2; } - tmp = TUPLE2(hp, frame_size_term, var_list); - hp += 3; + tp = &item->first[last_calls_term_idx]; + while(num_calls_terms != 0) { + if (num_calls_terms > 1 && is_integer(tp[-1])) { + Uint arity = unsigned_val(tp[-1]) - (MAX_ARG+1); + ASSERT(arity >= 0 && arity <= MAX_ARG); + + tmp = TUPLE2(hp, tp[0], make_small(arity)); + hp += 3; + + num_calls_terms -= 2; + tp -= 2; + } else if (num_calls_terms > 2 && + is_integer(tp[-2]) && unsigned_val(tp[-2]) <= MAX_ARG) { + tmp = TUPLE3(hp, tp[-1], tp[0], tp[-2]); + hp += 4; + + num_calls_terms -= 3; + tp -= 3; + } else { + tmp = tp[0]; + num_calls_terms -= 1; + tp -= 1; + } + + calls_list = CONS(hp, tmp, calls_list); + hp += 2; + } + + tmp = MAP3(hp, + am_frame_size, frame_size_term, + am_vars, var_list, + am_calls, calls_list); + hp += MAP3_SZ; tmp = TUPLE2(hp, make_small(LOC_LINE(location)), tmp); hp += 3; diff --git a/erts/emulator/beam/beam_code.h b/erts/emulator/beam/beam_code.h index 10dd5fe72761..a66697427c45 100644 --- a/erts/emulator/beam/beam_code.h +++ b/erts/emulator/beam/beam_code.h @@ -157,6 +157,7 @@ typedef struct { Uint32 location_index; Sint16 frame_size; Uint16 num_vars; + Uint32 num_calls_terms; Eterm *first; } BeamDebugItem; diff --git a/erts/emulator/beam/beam_file.c b/erts/emulator/beam/beam_file.c index af807d97d06f..c56ad07254d1 100644 --- a/erts/emulator/beam/beam_file.c +++ b/erts/emulator/beam/beam_file.c @@ -670,10 +670,184 @@ static int parse_type_chunk(BeamFile *beam, IFF_Chunk *chunk) { } } +static void init_debug_item(BeamFile_DebugItem *item, Eterm *tp) { + item->location_index = -1; + item->frame_size = -1; + item->num_vars = 0; + item->num_calls_terms = 0; + item->first = tp; +} + +static int parse_debug_chunk_frame_size(const BeamOpArg *arg, BeamFile_DebugItem *item) { + switch (arg->type) { + case TAG_n: + item->frame_size = BEAMFILE_FRAMESIZE_NONE; + break; + case TAG_a: + if (arg->val != am_entry) { + goto error; + } else { + item->frame_size = BEAMFILE_FRAMESIZE_ENTRY; + } + break; + case TAG_u: + if (arg->val > ERTS_SINT32_MAX) { + goto error; + } + item->frame_size = arg->val; + break; + default: + goto error; + } + + return 1; + + error: + return 0; +} + +static int parse_debug_chunk_var_mappings(int args_count, const BeamOpArg *args, BeamFile_DebugItem *item, + Eterm *tp, byte* lp, const BeamFile *beam) { + Sint32 num_vars; + + if (args_count % 2 != 0) { + goto error; + } + + num_vars = args_count / 2; + + item->num_vars = num_vars; + + while (args_count > 0) { + Eterm var_name; + + switch (args[0].type) { + case TAG_i: + *tp++ = make_small(args[0].val); + *lp++ = 0; + break; + case TAG_q: + var_name = beamfile_get_literal(beam, args[0].val); + if (is_not_bitstring(var_name) || + TAIL_BITS(bitstring_size(var_name))) { + goto error; + } + *tp++ = args[0].val; + *lp++ = 1; + break; + default: + goto error; + } + + *lp = 0; + switch (args[1].type) { + case TAG_i: + *tp = make_small(args[1].val); + break; + case TAG_a: + *tp = args[1].val; + break; + case TAG_n: + *tp = NIL; + break; + case TAG_x: + *tp = make_loader_x_reg(args[1].val); + break; + case TAG_y: + *tp = make_loader_y_reg(args[1].val); + break; + case TAG_q: + *tp = args[1].val; + *lp = 1; + break; + default: + goto error; + } + + tp++, lp++; + args += 2; + args_count -= 2; + } + + return 1; + + error: + return 0; +} + +static int parse_debug_chunk_calls(int args_count, const BeamOpArg *args, BeamFile_DebugItem *item, + Eterm *tp, byte* lp, const BeamFile *beam) { + int arity; + unsigned expected=0; + + item->num_calls_terms = args_count; + + for(;args_count > 0; args++,args_count--) { + Eterm var_name; + + switch (args[0].type) { + case TAG_u: + if(expected > 0) { + goto error; + } + + arity = args[0].val; + + if (arity > MAX_ARG) { + arity -= (MAX_ARG + 1); + expected = 1; + } else { + expected = 2; + } + + if (arity < 0 || arity > MAX_ARG) { + goto error; + } + + *tp++ = make_small(args[0].val); + *lp++ = 0; + break; + case TAG_a: + if (expected == 0) { + goto error; + } + *tp++ = args[0].val; + *lp++ = 0; + expected--; + break; + case TAG_q: + var_name = beamfile_get_literal(beam, args[0].val); + if (is_not_bitstring(var_name) || + TAIL_BITS(bitstring_size(var_name))) { + goto error; + } + *tp++ = args[0].val; + *lp++ = 1; + + /* if expected == 0, this is a call to a variable */ + if (expected > 0) { + expected --; + } + break; + default: + goto error; + } + } + + if (expected > 0) { + goto error; + } + + return 1; + + error: + return 0; +} + static int parse_debug_chunk_data(BeamFile *beam, BeamReader *p_reader) { Sint32 count; - Sint32 total_num_vars; - int i; + Sint32 total_num_terms; + int i=-1, last_entry = INT_MAX; BeamOpAllocator op_allocator; BeamCodeReader *op_reader; BeamOp* op = NULL; @@ -682,7 +856,7 @@ static int parse_debug_chunk_data(BeamFile *beam, BeamReader *p_reader) { byte *lp; LoadAssert(beamreader_read_i32(p_reader, &count)); - LoadAssert(beamreader_read_i32(p_reader, &total_num_vars)); + LoadAssert(beamreader_read_i32(p_reader, &total_num_terms)); beamopallocator_init(&op_allocator); @@ -694,26 +868,26 @@ static int parse_debug_chunk_data(BeamFile *beam, BeamReader *p_reader) { op_reader->first = 1; op_reader->reader = *p_reader; - if (count < 0 || total_num_vars < 0) { + if (count < 0 || total_num_terms < 0) { goto error; } debug->item_count = count; - debug->term_count = 2 * total_num_vars; + debug->term_count = total_num_terms; debug->items = erts_alloc(ERTS_ALC_T_PREPARED_CODE, count * sizeof(BeamFile_DebugItem)); debug->terms = erts_alloc(ERTS_ALC_T_PREPARED_CODE, - 2 * total_num_vars * sizeof(Eterm)); + total_num_terms * sizeof(Eterm)); debug->is_literal = erts_alloc(ERTS_ALC_T_PREPARED_CODE, - 2 * total_num_vars * sizeof(Eterm)); + total_num_terms * sizeof(Eterm)); tp = debug->terms; lp = debug->is_literal; - for (i = 0; i < count; i++) { + while(count > 0 || total_num_terms > 0) { BeamOpArg *arg; - int extra_args; - Sint32 num_vars; + int entry_type, extra_args; + int skip=0; if (!beamcodereader_next(op_reader, &op)) { goto error; @@ -722,116 +896,79 @@ static int parse_debug_chunk_data(BeamFile *beam, BeamReader *p_reader) { goto error; } - debug->items[i].location_index = -1; - arg = op->a; - - /* Process frame size. */ - switch (arg->type) { - case TAG_n: - debug->items[i].frame_size = BEAMFILE_FRAMESIZE_NONE; - break; - case TAG_a: - if (arg->val != am_entry) { - goto error; - } else { - debug->items[i].frame_size = BEAMFILE_FRAMESIZE_ENTRY; - } - break; - case TAG_u: - if (arg->val > ERTS_SINT32_MAX) { - goto error; - } - debug->items[i].frame_size = arg->val; - break; - default: + if (arg->type != TAG_u || arg->val > ERTS_SINT32_MAX) { goto error; } - + entry_type = arg->val; arg++; - /* Get and check the number of extra arguments. */ - if (arg->type != TAG_u) { - goto error; - } - extra_args = arg->val; - - arg++; - - if (extra_args % 2 != 0) { - goto error; - } - - /* Process the list of variable mappings. */ - - num_vars = extra_args / 2; - if (num_vars > total_num_vars) { - goto error; - } - total_num_vars -= num_vars; + if (entry_type == BEAMFILE_DEBUG_INFO_ENTRY_FRAME_SIZE) { + /* frame-size entry is mandatory and delimits items */ + if (count == 0) { + goto error; + } + i++, count--, last_entry=entry_type; - debug->items[i].num_vars = num_vars; - debug->items[i].first = tp; + init_debug_item(&debug->items[i], tp); + if (!parse_debug_chunk_frame_size(arg, &debug->items[i])) { + goto error; + } + } else { + if (entry_type < last_entry) { + goto error; + } + last_entry=entry_type; - while (extra_args > 0) { - Eterm var_name; + /* Get and check the number of extra arguments. */ + if (arg->type != TAG_u) { + goto error; + } + extra_args = arg->val; + arg++; - switch (arg[0].type) { - case TAG_i: - *tp++ = make_small(arg[0].val); - *lp++ = 0; + if (extra_args > total_num_terms) { + goto error; + } + total_num_terms -= extra_args; + + switch(entry_type) { + case BEAMFILE_DEBUG_INFO_ENTRY_VAR_MAPPINGS: + if (!parse_debug_chunk_var_mappings(extra_args, + arg, + &debug->items[i], + tp, + lp, + beam)) { + goto error; + } break; - case TAG_q: - var_name = beamfile_get_literal(beam, arg[0].val); - if (is_not_bitstring(var_name) || - TAIL_BITS(bitstring_size(var_name))) { + case BEAMFILE_DEBUG_INFO_ENTRY_CALLS: + if (!parse_debug_chunk_calls(extra_args, + arg, + &debug->items[i], + tp, + lp, + beam)) { goto error; } - *tp++ = arg[0].val; - *lp++ = 1; break; default: - goto error; + /* unknown entry type, ignore */ + debug->term_count -= extra_args; + skip = 1; } - *lp = 0; - switch (arg[1].type) { - case TAG_i: - *tp = make_small(arg[1].val); - break; - case TAG_a: - *tp = arg[1].val; - break; - case TAG_n: - *tp = NIL; - break; - case TAG_x: - *tp = make_loader_x_reg(arg[1].val); - break; - case TAG_y: - *tp = make_loader_y_reg(arg[1].val); - break; - case TAG_q: - *tp = arg[1].val; - *lp = 1; - break; - default: - goto error; + if (!skip) { + tp += extra_args; + lp += extra_args; } - - tp++, lp++; - arg += 2; - extra_args -= 2; } beamopallocator_free_op(&op_allocator, op); op = NULL; } - if (total_num_vars != 0) { - goto error; - } - beamcodereader_close(op_reader); beamopallocator_dtor(&op_allocator); @@ -855,6 +992,11 @@ static int parse_debug_chunk_data(BeamFile *beam, BeamReader *p_reader) { debug->terms = NULL; } + if (debug->is_literal) { + erts_free(ERTS_ALC_T_PREPARED_CODE, debug->is_literal); + debug->is_literal = NULL; + } + return 0; } @@ -866,7 +1008,7 @@ static int parse_debug_chunk(BeamFile *beam, IFF_Chunk *chunk) { LoadAssert(beamreader_read_i32(&reader, &version)); - if (version == 0) { + if (version == 1) { return parse_debug_chunk_data(beam, &reader); } else { /* Silently ignore chunk of wrong version. */ diff --git a/erts/emulator/beam/beam_file.h b/erts/emulator/beam/beam_file.h index d362a3337d1f..f48cbf168795 100644 --- a/erts/emulator/beam/beam_file.h +++ b/erts/emulator/beam/beam_file.h @@ -152,6 +152,11 @@ typedef struct { BeamType *entries; } BeamFile_TypeTable; + +#define BEAMFILE_DEBUG_INFO_ENTRY_FRAME_SIZE 0 +#define BEAMFILE_DEBUG_INFO_ENTRY_VAR_MAPPINGS 1 +#define BEAMFILE_DEBUG_INFO_ENTRY_CALLS 2 + #define BEAMFILE_FRAMESIZE_ENTRY (-2) #define BEAMFILE_FRAMESIZE_NONE (-1) @@ -159,6 +164,7 @@ typedef struct { Uint32 location_index; Sint32 frame_size; Sint32 num_vars; + Sint32 num_calls_terms; Eterm *first; } BeamFile_DebugItem; diff --git a/erts/emulator/beam/jit/asm_load.c b/erts/emulator/beam/jit/asm_load.c index acc124b21c9a..44ad79290ee1 100644 --- a/erts/emulator/beam/jit/asm_load.c +++ b/erts/emulator/beam/jit/asm_load.c @@ -922,12 +922,14 @@ static const BeamDebugTab *finish_debug_table(LoaderState *stp, for (i = 0; i < item_count; i++) { Uint num_vars = debug->items[i].num_vars; + Uint num_calls_terms = debug->items[i].num_calls_terms; debug_tab_items[i].location_index = debug->items[i].location_index; debug_tab_items[i].frame_size = debug->items[i].frame_size; debug_tab_items[i].num_vars = num_vars; + debug_tab_items[i].num_calls_terms = num_calls_terms; debug_tab_items[i].first = debug_tab_terms; - debug_tab_terms += 2 * num_vars; + debug_tab_terms += 2 * num_vars + num_calls_terms; } return debug_tab_ro; diff --git a/erts/emulator/test/erl_debugger_SUITE.erl b/erts/emulator/test/erl_debugger_SUITE.erl index ebab471c2514..134cd48c676c 100644 --- a/erts/emulator/test/erl_debugger_SUITE.erl +++ b/erts/emulator/test/erl_debugger_SUITE.erl @@ -650,7 +650,7 @@ test_stack_frames_returns_y_regs_controlled_by_size(Config) -> %% returning Y-registers in the right order. YRegMap = #{ YRegNo => Var - || {L, {_, SymMap}} <- code:get_debug_info(Mod), + || {L, #{vars := SymMap}} <- code:get_debug_info(Mod), L == Line, {Var, {y, YRegNo}} <- SymMap }, diff --git a/lib/compiler/src/beam_asm.erl b/lib/compiler/src/beam_asm.erl index 3c2b364c5b79..f49fb09d2c2b 100644 --- a/lib/compiler/src/beam_asm.erl +++ b/lib/compiler/src/beam_asm.erl @@ -35,7 +35,12 @@ -include("beam_opcodes.hrl"). -include("beam_asm.hrl"). --define(BEAM_DEBUG_INFO_VERSION, 0). +-define(BEAM_DEBUG_INFO_VERSION, 1). +-define(BEAM_DEBUG_INFO_ENTRY_FRAME_SIZE, 0). +-define(BEAM_DEBUG_INFO_ENTRY_VAR_MAPPINGS, 1). +-define(BEAM_DEBUG_INFO_ENTRY_CALLS, 2). + +-define(MAX_ARGUMENTS, 255). %% Common types for describing operands for BEAM instructions. -type src() :: beam_reg() | @@ -411,17 +416,18 @@ build_beam_debug_info_1(ExtraChunks0, Dict0) -> DebugTab1 = [{Index,Info} || Index := Info <- maps:iterator(DebugTab0, ordered)], DebugTab = build_bdi_fill_holes(DebugTab1), - NumVars = lists:sum([length(Vs) || {_,Vs} <- DebugTab]), - {Contents0,Dict} = build_bdi(DebugTab, Dict0), - NumItems = length(Contents0), + NumItems = length(DebugTab), + BdiInstrs = [Instr || Item <- DebugTab, Instr <- build_bdi_instrs(Item), Instr /= none], + NumTerms = lists:sum([length(Ts) || {_call,_,{list, Ts}} <- BdiInstrs]), + {Contents0, Dict} = lists:mapfoldl(fun make_op/2, Dict0, BdiInstrs), Contents1 = iolist_to_binary(Contents0), 0 = NumItems bsr 31, %Assertion. - 0 = NumVars bsr 31, %Assertion. + 0 = NumTerms bsr 31, %Assertion. Contents = <>, ExtraChunks = [{~"DbgB",Contents}|ExtraChunks0], {ExtraChunks,Dict}. @@ -435,39 +441,57 @@ build_bdi_fill_holes([{I0,Item}|[{I1,_}|_]=T]) -> I1 -> [Item|build_bdi_fill_holes(T)]; Next -> - NewPair = {Next,{none,[]}}, + NewPair = {Next,#{frame_size => none, vars => []}}, [Item|build_bdi_fill_holes([NewPair|T])] end. -build_bdi([{FrameSize0,Vars0}|Items], Dict0) -> +build_bdi_instrs(#{frame_size:=FrameSize0, vars:=Vars0}=Info) -> %% The debug information utilizes the encoding machinery for BEAM - %% instructions. The debug information for `debug_line` - %% instructions is translated to: - %% - %% {call,FrameSize,{list,[VariableName,Where,...]}} - %% - %% Where: + %% instructions. Each entry in the the debug information for + %% `debug_line` instructions (frame size, var mappings, etc) is + %% translated to: %% - %% FrameSize := 'none' | 0..1023 - %% VariableName := binary() - %% Where := {x,0..1023} | {y,0..1023} | {literal,_} | - %% {integer,_} | {atom,_} | {float,_} | nil + %% {call,EntryCode,EntryEncoding} %% %% The only reason the `call` instruction is used is because it %% has two operands. %% + %% The only mandatory entry is "frame size", as it will be used + %% as an item delimiter when loading. + %% + %% Encodings (which must be sent in this order): + %% + %% * ENTRY_FRAME_SIZE: 'none' | 'entry' | 0..1023 + %% * ENTRY_VAR_MAPPINGS: {list,[VarName,VarLoc,...]}} + %% * ENTRY_CALLS: {list, [VarNameOrArity, VarNameOrAtom?, VarNameOrAtom?,....] + %% + %% Where: + %% + %% VarName := binary() + %% VarLoc := {x,0..1023} | {y,0..1023} | {literal,_} | + %% {integer,_} | {atom,_} | {float,_} | nil + %% VarNameOrArity := binary() | 0..511 (arity >= 256 denotes local call) + %% VarNameOrAtom := binary() | {atom,_} + %% %% The debug information in the following example: %% %% {debug_line,[...],1,1, %% {4, [{'Args',[{y,3}]}, %% {'Line',[{y,2}]}, - %% {'Live',[{x,0},{y,1}]}]}} + %% {'Live',[{x,0},{y,1}]}]}, + %% [{remote,'M',handle_call,3}, + %% {local,f,2}, + %% {var,'MyFun'}]} %% - %% will be translated to the following instruction: + %% will be translated to the following instructions: %% - %% {call,4,{list,[{literal,<<"Args">>},{y,3}, - %% {literal,<<"Line">>},{y,2}, - %% {literal,<<"Live">>},{y,1}]}} + %% {call,0,4} + %% {call,1,{list,[{literal,~"Args"},{y,3}, + %% {literal,~"Line"},{y,2}, + %% {literal,~"Live"},{y,1}]}} + %% {call,2,{list,[3,{literal, ~"M"}, {atom, handle_call}, + %% 258, {atom, f}, + %% {literal, ~"MyFun"}]}} %% %% Note that only one register is given for each variable. It %% is always the last register listed. @@ -477,27 +501,58 @@ build_bdi([{FrameSize0,Vars0}|Items], Dict0) -> entry -> {atom,entry}; _ -> FrameSize0 end, - Vars1 = case FrameSize0 of - entry -> - [[bdi_name_to_term(Name),Reg] || - {Name,[Reg]} <:- Vars0]; - _ -> - [[{literal,atom_to_binary(Name)},last(Regs)] || - {Name,[_|_]=Regs} <:- Vars0] - end, - Vars = append(Vars1), - Instr0 = {call,FrameSize,{list,Vars}}, - {Instr,Dict1} = make_op(Instr0, Dict0), - {Tail,Dict2} = build_bdi(Items, Dict1), - {[Instr|Tail],Dict2}; -build_bdi([], Dict) -> - {[],Dict}. + FrameSizeInstr = {call,?BEAM_DEBUG_INFO_ENTRY_FRAME_SIZE,FrameSize}, + + VarMappingsInstr = + case Vars0 of + [] -> + none; + _ -> + Vars = case FrameSize0 of + entry -> + [[bdi_name_to_term(Name),Reg] || + {Name,[Reg]} <:- Vars0]; + _ -> + [[{literal,atom_to_binary(Name)},last(Regs)] || + {Name,[_|_]=Regs} <:- Vars0] + end, + {call,?BEAM_DEBUG_INFO_ENTRY_VAR_MAPPINGS,{list,append(Vars)}} + end, + + CallsInstr = + case maps:get(calls, Info, []) of + [] -> + none; + Calls -> + {call,?BEAM_DEBUG_INFO_ENTRY_CALLS,{list,bdi_encode_calls(Calls)}} + end, + + [FrameSizeInstr, VarMappingsInstr, CallsInstr]. bdi_name_to_term(Int) when is_integer(Int) -> {integer,Int}; bdi_name_to_term(Atom) when is_atom(Atom) -> {literal,atom_to_binary(Atom)}. +bdi_encode_calls([{remote, M0, F0, A}|Rest]) when A>=0,A= + M = bdi_encode_var_or_atom(M0), + F = bdi_encode_var_or_atom(F0), + [A,M,F | bdi_encode_calls(Rest)]; +bdi_encode_calls([{local, F0, A0}|Rest]) when A0>=0,A0= + A = A0 + (?MAX_ARGUMENTS + 1), + F = bdi_encode_var_or_atom(F0), + [A,F | bdi_encode_calls(Rest)]; +bdi_encode_calls([{var, _}=V0|Rest]) -> + V = bdi_encode_var_or_atom(V0), + [V | bdi_encode_calls(Rest)]; +bdi_encode_calls([]) -> + []. + +bdi_encode_var_or_atom({var, V}) when is_binary(V) -> + {literal, V}; +bdi_encode_var_or_atom({atom, A}) when is_atom(A) -> + {atom, A}. + %%% %%% Functions for assembling BEAM instruction. %%% @@ -677,7 +732,7 @@ flag_to_bit(unsigned)-> 16#00; %%flag_to_bit(exact) -> 16#08; flag_to_bit(native) -> 16#10; flag_to_bit({anno,_}) -> 0. - + encode_list([H|T], Dict0, Acc) when not is_list(H) -> {Enc,Dict} = encode_arg(H, Dict0), encode_list(T, Dict, [Acc,Enc]); diff --git a/lib/compiler/src/beam_block.erl b/lib/compiler/src/beam_block.erl index c79e144b5cc9..22468c533815 100644 --- a/lib/compiler/src/beam_block.erl +++ b/lib/compiler/src/beam_block.erl @@ -181,7 +181,7 @@ collect({swap,D1,D2}) -> collect({make_fun3,F,I,U,D,{list,Ss}}) -> {set,[D],Ss,{make_fun3,F,I,U}}; collect(_) -> error. -collect_debug_line({debug_line,_Loc,_Index,_Live,{_,Vars}}=I) -> +collect_debug_line({debug_line,_Loc,_Index,_Live,#{vars:=Vars}}=I) -> Ss = flatmap(fun({_Name,Regs}) -> Regs end, Vars), {set,[],Ss,I}. diff --git a/lib/compiler/src/beam_dict.erl b/lib/compiler/src/beam_dict.erl index b129da09cb4f..0a70c7438b48 100644 --- a/lib/compiler/src/beam_dict.erl +++ b/lib/compiler/src/beam_dict.erl @@ -39,7 +39,7 @@ -type index() :: non_neg_integer(). -type frame_size() :: 'none' | 'entry' | non_neg_integer(). --type debug_info() :: {frame_size(), list()}. +-type debug_info() :: #{frame_size := frame_size(), vars := list(), calls := list()}. -type atom_tab() :: #{atom() => index()}. -type import_tab() :: gb_trees:tree(mfa(), index()). diff --git a/lib/compiler/src/beam_flatten.erl b/lib/compiler/src/beam_flatten.erl index d0d8261a8062..c4ecb4ecc113 100644 --- a/lib/compiler/src/beam_flatten.erl +++ b/lib/compiler/src/beam_flatten.erl @@ -79,8 +79,7 @@ norm_allocate({nozero,Ns,Nh,Inits}, Regs) -> norm_debug_line({debug_line,Location,Index,Live,Info}) -> Kind = case Info of - {entry,_} -> entry; - {_,_} -> line + #{frame_size := entry} -> entry; + _ -> line end, {debug_line,{atom,Kind},Location,Index,Live,Info}. - diff --git a/lib/compiler/src/beam_ssa_codegen.erl b/lib/compiler/src/beam_ssa_codegen.erl index 1f274580f575..3eaced3a77cb 100644 --- a/lib/compiler/src/beam_ssa_codegen.erl +++ b/lib/compiler/src/beam_ssa_codegen.erl @@ -152,7 +152,7 @@ fix_debug_line(Is0, Live, #cg{debug_info=true}) -> {line,_}=Li, {func_info,_,_,_}=Fi, {label,_}=Entry, - {debug_line,Location,Index,Live,{none,Args0}}|Is] -> + {debug_line,Location,Index,Live,#{frame_size:=none, vars:=Args0}=Info0}|Is] -> %% Mark this debug_line instruction as being the %% very first instruction in the function. RegToVar = #{Reg => Var || {Var,[{x,_}=Reg|_]} <- Args0}, @@ -163,7 +163,8 @@ fix_debug_line(Is0, Live, #cg{debug_info=true}) -> #{} -> {I,[X]} end end || I <- lists:seq(1, Live)], - DbgLine = {debug_line,Location,Index,Live,{entry,Args}}, + Info=Info0#{frame_size:=entry,vars:=Args}, + DbgLine = {debug_line,Location,Index,Live,Info}, [FiLbl,Li,Fi,Entry,DbgLine|Is]; _ -> Is0 @@ -1009,49 +1010,50 @@ add_debug_info(Linear0, Args, #cg{regs=Regs,debug_info=true}) -> Linear = anno_defined_regs(Linear0, Def0, Regs), FrameSzMap = #{0 => none}, VarMap = #{}, - add_debug_info_blk(Linear, Regs, FrameSzMap, VarMap); + CallTargets = collect_call_targets(Linear, #{}), + add_debug_info_blk(Linear, Regs, CallTargets, FrameSzMap, VarMap); add_debug_info(Linear, _Args, #cg{debug_info=false}) -> Linear. add_debug_info_blk([{L,#cg_blk{is=Is0,last=Last}=Blk0}|Bs], - Regs, FrameSzMap0, VarMap0) -> + Regs, CallTargets, FrameSzMap0, VarMap0) -> FrameSize0 = map_get(L, FrameSzMap0), {Is,VarMap,FrameSize} = - add_debug_info_is(Is0, Regs, FrameSize0, VarMap0, []), + add_debug_info_is(Is0, Regs, CallTargets, FrameSize0, VarMap0, []), Successors = successors(Last), FrameSzMap = foldl(fun(Succ, Acc) -> Acc#{Succ => FrameSize} end, FrameSzMap0, Successors), Blk = Blk0#cg_blk{is=Is}, - [{L,Blk}|add_debug_info_blk(Bs, Regs, FrameSzMap, VarMap)]; -add_debug_info_blk([], _Regs, _FrameSzMap, _VarMap) -> + [{L,Blk}|add_debug_info_blk(Bs, Regs, CallTargets, FrameSzMap, VarMap)]; +add_debug_info_blk([], _Regs, _CallTargets, _FrameSzMap, _VarMap) -> []. add_debug_info_is([#cg_alloc{stack=FrameSize}=I|Is], - Regs, FrameSize0, VarMap, Acc) -> + Regs, CallTargets, FrameSize0, VarMap, Acc) -> if is_integer(FrameSize) -> - add_debug_info_is(Is, Regs, FrameSize, VarMap, [I|Acc]); + add_debug_info_is(Is, Regs, CallTargets, FrameSize, VarMap, [I|Acc]); true -> - add_debug_info_is(Is, Regs, FrameSize0, VarMap, [I|Acc]) + add_debug_info_is(Is, Regs, CallTargets, FrameSize0, VarMap, [I|Acc]) end; add_debug_info_is([#cg_set{anno=#{was_phi := true},op=copy}=I|Is], - Regs, FrameSize, VarMap, Acc) -> + Regs, CallTargets, FrameSize, VarMap, Acc) -> %% This copy operation originates from a phi node. The source and %% destination are not equivalent and must not be added to VarMap. - add_debug_info_is(Is, Regs, FrameSize, VarMap, [I|Acc]); + add_debug_info_is(Is, Regs, CallTargets, FrameSize, VarMap, [I|Acc]); add_debug_info_is([#cg_set{anno=Anno,op=copy,dst=#b_var{name=Dst}, args=[#b_var{name=Src}]}=I|Is], - Regs, FrameSize, VarMap0, Acc) -> + Regs, CallTargets, FrameSize, VarMap0, Acc) -> VarMap = case Anno of #{delayed_yreg_copy := true} -> VarMap0#{Src => [Dst]}; #{} -> VarMap0#{Dst => [Src]} end, - add_debug_info_is(Is, Regs, FrameSize, VarMap, [I|Acc]); + add_debug_info_is(Is, Regs, CallTargets, FrameSize, VarMap, [I|Acc]); add_debug_info_is([#cg_set{anno=Anno0,op=debug_line,args=[Index]}=I0|Is], - Regs, FrameSize, VarMap, Acc) -> + Regs, CallTargets, FrameSize, VarMap, Acc) -> #{def_regs := DefRegs, alias := Alias, literals := Literals0, @@ -1071,12 +1073,23 @@ add_debug_info_is([#cg_set{anno=Anno0,op=debug_line,args=[Index]}=I0|Is], S3 = sofs:relation_to_family(S2), S = sort(Literals ++ sofs:to_external(S3)), Live = max(NumLive0, num_live(DefRegs, Regs)), - Info = {FrameSize,S}, + Loc = maps:get(location, Anno0, undefined), + Info0 = #{frame_size => FrameSize, vars => S}, + Info = + case maps:get(Loc, CallTargets, []) of + [] -> + Info0; + Targets0 -> + Targets = [T || T0 <- lists:reverse(Targets0), + T <- [format_call_target(T0, AliasMap)], + T /= none], + Info0#{calls => Targets} + end, I = I0#cg_set{args=[Index,#b_literal{val=Live},#b_literal{val=Info}]}, - add_debug_info_is(Is, Regs, FrameSize, VarMap, [I|Acc]); -add_debug_info_is([#cg_set{}=I|Is], Regs, FrameSize, VarMap, Acc) -> - add_debug_info_is(Is, Regs, FrameSize, VarMap, [I|Acc]); -add_debug_info_is([], _Regs, FrameSize, VarMap, Info) -> + add_debug_info_is(Is, Regs, CallTargets, FrameSize, VarMap, [I|Acc]); +add_debug_info_is([#cg_set{}=I|Is], Regs, CallTargets, FrameSize, VarMap, Acc) -> + add_debug_info_is(Is, Regs, CallTargets, FrameSize, VarMap, [I|Acc]); +add_debug_info_is([], _Regs, _CallTargets, FrameSize, VarMap, Info) -> {reverse(Info),VarMap,FrameSize}. get_original_names(#b_var{name=Name}, AliasMap) -> @@ -1127,6 +1140,120 @@ is_original_variable(Name) when is_atom(Name) -> is_original_variable(Name) when is_integer(Name) -> false. + +%% Collect all call targets and group them by location, so they cann later +%% be associated to the corresponding debug_line instruction + +collect_call_targets([{_,#cg_blk{is=Is}}|Bs], Acc0) -> + Acc = collect_call_targets_is(Is, Acc0), + collect_call_targets(Bs, Acc); +collect_call_targets([], Acc) -> + Acc. + +collect_call_targets_is([I=#cg_set{anno=Anno,op=call,args=Args}|Is], Acc0) -> + {Target, Acc1} = + case Args of + [Local=#b_local{} |_] -> + {Local, Acc0}; + + [MakeFun=#b_remote{mod=#b_literal{val=erlang}, + name=#b_literal{val=make_fun}, + arity=3}, M, F, #b_literal{val=A}] when is_integer(A) -> + Dst = I#cg_set.dst, + Remote = #b_remote{mod=M, name=F, arity=A}, + {MakeFun, Acc0#{{ref, Dst} => Remote}}; + [Apply=#b_remote{mod=#b_literal{val=erlang}, + name=#b_literal{val=apply}, + arity=3}, M, F, As] -> + Arity = + case As of + #b_literal{val=ArgList} when is_list(ArgList) -> + length(ArgList); + V=#b_var{} -> + case Acc0 of + #{{list, V} := L} -> length(L); + _ -> undefined + end; + _ -> undefined + end, + if + is_integer(Arity) -> + Remote = #b_remote{mod=M, name=F, arity=Arity}, + {Remote, Acc0}; + true -> + {Apply, Acc0} + end; + [Remote=#b_remote{}|_] -> + {Remote, Acc0}; + [Var=#b_var{} |_] -> + case Acc0 of + #{{ref, Var} := LocalOrRemote} -> {LocalOrRemote, Acc0}; + _ -> {Var, Acc0} + end; + _ -> + {invalid, Acc0} + end, + Acc = case Target of + invalid -> + Acc1; + _ -> + case Anno of + #{location := Loc} -> + maps:update_with(Loc, + fun(Prev) -> [Target | Prev] end, + [Target], + Acc1); + _ -> + Acc1 + end + end, + collect_call_targets_is(Is, Acc); +collect_call_targets_is([#cg_set{dst=Dst,op=make_fun,args=[Local]}|Is], Acc0) -> + Acc = Acc0#{{ref, Dst} => Local}, + collect_call_targets_is(Is, Acc); +collect_call_targets_is([#cg_set{dst=Dst,op=put_list,args=Args}|Is], Acc0) -> + Acc = Acc0#{{list, Dst} => Args}, + collect_call_targets_is(Is, Acc); +collect_call_targets_is([_|Is], Acc) -> + collect_call_targets_is(Is, Acc); +collect_call_targets_is([], Acc) -> + Acc. + +format_call_target(#b_remote{mod=M0,name=F0,arity=A}, VarAliases) -> + maybe + M = {_,_} ?= resolve_var_alias(M0, VarAliases), + F = {_,_} ?= resolve_var_alias(F0, VarAliases), + {remote, M,F,A} + end; +format_call_target(#b_local{name=F0,arity=A}, VarAliases) -> + maybe + F = {_,_} ?= resolve_var_alias(F0, VarAliases), + {local, F, A} + end; +format_call_target(#b_var{} = V, VarAliases) -> + resolve_var_alias(V, VarAliases). + +-spec resolve_var_alias(VarOrLit, VarAliases) -> none | AtomOrVar when + VarOrLit :: b_var() | b_literal() | XReg, + XReg :: {x, non_neg_integer()}, + AtomOrVar :: {var, binary()} | {atom, atom()}, + VarAliases :: #{beam_ssa:var_name() => [beam_ssa:var_name()]}. +resolve_var_alias(#b_var{name=V}, VarAliases) -> + case maps:get(V, VarAliases,[]) of + [Alias|_] when is_atom(Alias) -> + {var, atom_to_binary(Alias)}; + [Alias|_] when is_integer(Alias) -> + resolve_var_alias(#b_var{name=Alias}, VarAliases); + _ -> + none + end; +resolve_var_alias(#b_literal{val=Atom}, _VarAliases) when is_atom(Atom) -> + {atom, Atom}; +resolve_var_alias(#b_literal{}, _VarAliases) -> + none; +resolve_var_alias({x,_}, _VarAliases) -> + none. + %%% %%% Annotate `debug_line` instructions with all variables that have %%% been defined and are still available in a BEAM register. diff --git a/lib/compiler/src/beam_trim.erl b/lib/compiler/src/beam_trim.erl index d7898a2a950c..f31a00b9b1f6 100644 --- a/lib/compiler/src/beam_trim.erl +++ b/lib/compiler/src/beam_trim.erl @@ -321,11 +321,11 @@ remap_block([{set,Ds0,Ss0,Info}|Is], Remap) -> [{set,Ds,Ss,Info}|remap_block(Is, Remap)]; remap_block([], _) -> []. -remap_debug_info({FrameSize0,Vars0}, {Trim,Map}) -> +remap_debug_info(#{frame_size:=FrameSize0,vars:=Vars0}=Info0, {Trim,Map}) -> FrameSize = FrameSize0 - Trim, Vars = [{Name,[remap_arg(Arg, Trim, Map) || Arg <- Args]} || {Name,Args} <- Vars0], - {FrameSize,Vars}. + Info0#{frame_size := FrameSize, vars := Vars}. remap_args(Args, {Trim,Map}) -> [remap_arg(Arg, Trim, Map) || Arg <- Args]. diff --git a/lib/compiler/src/beam_validator.erl b/lib/compiler/src/beam_validator.erl index e89fecb38275..73cb3eb8356e 100644 --- a/lib/compiler/src/beam_validator.erl +++ b/lib/compiler/src/beam_validator.erl @@ -95,7 +95,7 @@ format_error(Error) -> %%% %%% Local functions follow. -%%% +%%% %%% %%% The validator follows. @@ -1271,7 +1271,7 @@ init_try_catch_branch(Kind, Dst, Fail, Vst0) -> #vst{current=St0} = Vst, #st{ct=Tags}=St0, St = St0#st{ct=[Tag|Tags]}, - + Vst#vst{current=St}. verify_has_map_fields(Lbl, Src, List, Vst) -> @@ -2187,11 +2187,11 @@ validate_select_tuple_arity(Fail, [], _, #vst{}=Vst) -> %% Validate debug information in `debug_line` instructions. %% -validate_debug_line({entry,Args}, Live, Vst) -> +validate_debug_line(#{frame_size:=entry, vars:=Args}, Live, Vst) -> do_validate_debug_line(none, Live, Vst), _ = [get_term_type(Reg, Vst) || {_Name,[Reg]} <:- Args], prune_x_regs(Live, Vst); -validate_debug_line({Stk,Vars}, Live, Vst0) -> +validate_debug_line(#{frame_size:=Stk, vars:=Vars}, Live, Vst0) -> do_validate_debug_line(Stk, Live, Vst0), Vst = prune_x_regs(Live, Vst0), _ = [validate_dbg_vars(Regs, Name, Vst) || {Name,Regs} <:- Vars], @@ -2864,15 +2864,15 @@ get_raw_type(#value_ref{}=Ref, #vst{current=#st{vs=Vs}}) -> get_raw_type(Src, #vst{current=#st{}}) -> get_literal_type(Src). -get_literal_type(nil) -> +get_literal_type(nil) -> beam_types:make_type_from_value([]); -get_literal_type({atom,A}) when is_atom(A) -> +get_literal_type({atom,A}) when is_atom(A) -> beam_types:make_type_from_value(A); -get_literal_type({float,F}) when is_float(F) -> +get_literal_type({float,F}) when is_float(F) -> beam_types:make_type_from_value(F); -get_literal_type({integer,I}) when is_integer(I) -> +get_literal_type({integer,I}) when is_integer(I) -> beam_types:make_type_from_value(I); -get_literal_type({literal,L}) -> +get_literal_type({literal,L}) -> beam_types:make_type_from_value(L); get_literal_type(T) -> error({not_literal,T}). diff --git a/lib/compiler/test/beam_debug_info_SUITE.erl b/lib/compiler/test/beam_debug_info_SUITE.erl index 092bacf2a0d5..7ac1e1bb3d5d 100644 --- a/lib/compiler/test/beam_debug_info_SUITE.erl +++ b/lib/compiler/test/beam_debug_info_SUITE.erl @@ -34,6 +34,8 @@ -export([all/0, suite/0,groups/0,init_per_suite/1, end_per_suite/1, init_per_group/2,end_per_group/2, smoke/1, + calls_reported_correctly/1, + calls_cornercase_reg_in_call/1, fixed_bugs/1, empty_module/1, call_in_call_args/1, @@ -43,6 +45,8 @@ suite() -> [{ct_hooks,[ts_install_cth]}]. all() -> [smoke, + calls_reported_correctly, + calls_cornercase_reg_in_call, {group,p}]. groups() -> @@ -207,7 +211,8 @@ debug_info_vars(DebugInfo, IndexToFunctionMap) -> Literals = family_union(Literals0), {Vars,Literals}. -debug_info_vars_1([{I,{_FrameSize,List}}|T], IndexToFunctionMap, VarAcc, LitAcc) -> +debug_info_vars_1([{I,Info}|T], IndexToFunctionMap, VarAcc, LitAcc) -> + List = maps:get(vars, Info, []), case debug_info_vars_2(List, [], []) of {[],[]} -> debug_info_vars_1(T, IndexToFunctionMap, VarAcc, LitAcc); @@ -528,13 +533,12 @@ get_debug_info(Mod, Beam) -> {error,_,_} -> [] end, - Op = beam_opcodes:opcode(call, 2), <> = DebugInfo0, - 0 = Version, - RawDebugInfo0 = decode_debug_info(DebugInfo1, Literals, Atoms, Op), + 1 = Version, + RawDebugInfo0 = decode_debug_info(DebugInfo1, Literals, Atoms), RawDebugInfo = lists:zip(lists:seq(1, length(RawDebugInfo0)), RawDebugInfo0), %% The cooked debug info has line numbers instead of indices. @@ -573,25 +577,69 @@ decode_literal_table(<<0:32,N:32,Tab/binary>>) -> Index <- lists:seq(0, N - 1) && <> <:= Tab}. -decode_debug_info(Code0, Literals, Atoms, Op) -> +decode_debug_info(Code0, Literals, Atoms) -> + Entries = decode_entries(Code0, Literals, Atoms), + {Infos, NextEntry} = lists:foldr( + fun + ({K, V}, {InfosN, NextN}) -> + Next = case NextN of + #{K := _} -> error({duplicated, K}); + _ -> NextN#{K => V} + end, + case K of + frame_size -> {[Next|InfosN], #{}}; + _ -> {InfosN, Next} + end + + end, + {[], #{}}, + Entries + ), + 0 = map_size(NextEntry), + Infos. + +decode_entries(<<>>, _Literals, _Atoms) -> + []; +decode_entries(Code0, Literals, Atoms) -> + {Entry, Code1} = decode_entry(Code0, Literals, Atoms), + [Entry|decode_entries(Code1, Literals, Atoms)]. + +decode_entry(Code0, Literals, Atoms) -> + Op = beam_opcodes:opcode(call, 2), case Code0 of <> -> - {FrameSize0,Code2} = decode_arg(Code1, Literals, Atoms), - FrameSize = case FrameSize0 of - nil -> none; - {atom,entry} -> entry; - _ -> FrameSize0 - end, - {{list,List0},Code3} = decode_arg(Code2, Literals, Atoms), - List = decode_list(List0), - [{FrameSize,List}|decode_debug_info(Code3, Literals, Atoms, Op)]; - <<>> -> - [] + {EntryType, Code2} = decode_arg(Code1, Literals, Atoms), + {Value, Code3} = decode_arg(Code2, Literals, Atoms), + Entry = case EntryType of + 0 -> + case Value of + nil -> + {frame_size, none}; + {atom,entry} -> + {frame_size, entry}; + _ when is_integer(Value), Value >= 0 -> + {frame_size, Value} + end; + + 1 -> + case Value of + {list,List} -> {vars, decode_var_mappings(List)} + end; + + 2 -> + case Value of + {list,List} -> {calls, decode_calls(List)} + end; + + _ -> + error({unknown_entry_type, EntryType}) + end, + {Entry, Code3} end. -decode_list([{integer,Var}|T]) when is_integer(Var) -> - decode_list([{literal,Var}|T]); -decode_list([{literal,Var},Where0|T]) -> +decode_var_mappings([{integer,Var}|T]) when is_integer(Var) -> + decode_var_mappings([{literal,Var}|T]); +decode_var_mappings([{literal,Var},Where0|T]) -> Where = case Where0 of {literal,Lit} -> {value,Lit}; {atom,A} -> {value,A}; @@ -600,8 +648,26 @@ decode_list([{literal,Var},Where0|T]) -> {x,_} -> Where0; {y,_} -> Where0 end, - [{Var,Where}|decode_list(T)]; -decode_list([]) -> []. + [{Var,Where}|decode_var_mappings(T)]; +decode_var_mappings([]) -> []. + +decode_calls([{literal, V}|Rest]) when is_binary(V) -> + [V|decode_calls(Rest)]; +decode_calls([A,M0,F0|Rest]) when A>=0, A=<255 -> + M = decode_var_or_atom(M0), + F = decode_var_or_atom(F0), + [{M,F,A}|decode_calls(Rest)]; +decode_calls([A0,F0|Rest]) when A0>=256, A0=<511-> + F = decode_var_or_atom(F0), + A = A0-256, + [{F,A}|decode_calls(Rest)]; +decode_calls([]) -> + []. + +decode_var_or_atom({literal, V}) when is_binary(V) -> + V; +decode_var_or_atom({atom, A}) when is_atom(A) -> + A. decode_args(0, Code, _Literals, _Atoms) -> {[],Code}; @@ -768,9 +834,8 @@ missing_vars(Config) -> DebugLines0 = [begin {location,_File,Line} = lists:keyfind(location, 1, Anno), {Kind,Line,FrameSz,[Name || {Name,_} <- Vars]} - end || {debug_line,{atom,Kind},Anno,_,_,{FrameSz,Vars}} <- Is], + end || {debug_line,{atom,Kind},Anno,_,_,#{frame_size:=FrameSz,vars:=Vars}} <- Is], DebugLines = lists:sort(DebugLines0), - io:format("~p\n", [DebugLines]), Expected = [{entry,3,entry,[1,2,3]}, {line,4,none,['X','Y','Z0']}, {line,6,none,['X','Y','Z0']}, @@ -783,6 +848,149 @@ missing_vars(Config) -> ok. +calls_reported_correctly(Config) -> + M = ?FUNCTION_NAME, + S = ~""" + -module(calls_reported_correctly). %L01 + -export([fixtures/1]). %L02 + -record(my_rec, {fld1 :: atom(), fld2 :: integer()}). %L03 + local() -> ok. %L04 %L04 + fixtures(F) -> %L05 + Y = 42, 'not':toplevel(a, b), %L06 + foo:bar(13, Y), Z = 43, %L07 + local(), %L08 + X = catch local(), %L09 + ok = foo:bar(Y), %L10 + case foo:blah() of ok -> local(); %L11 + _ -> foo:bar() %L12 + end, %L13 + try X = hey:ho(42), local() of %L14 + _ -> foo:bar() %L15 + catch %L16 + _:_ -> foo:blah() %L17 + end, %L18 + hey:ho(X) + foo:bar(Y), %L19 + self() ! foo:bar(Y), %L20 + {hey:ho(X), foo:bar(Y)}, %L21 + [hey:ho(X), foo:bar(Y) | pim:pam()], %L22 + #{hey:ho(X) => foo:bar(Y), blah => pim:pam()}, %L23 + #my_rec{fld1 = hey:ho(X), fld2 = foo:bar(Y)}, %L24 + X:handle_call(1,2,3), %L25 + foo:F(1,2,3), %L26 + X:F(), %L27 + F(), %L28 + G = bam, foo:G(42), %L29 + X:G(), %L30 + G(), % invalid call %L31 + (fun foo:bar/1)(Z), %L32 + Ref=fun foo:blah/2, Ref(X,Y), %L33 + (fun local/0)(), %L34 + erlang:apply(foo, bar, [true, 42]), %L35 + erlang:apply(foo, bar, [X, Y]), %L36 + [pim:pum(E) || L <- foo:bar(), E <- hey:ho(L)], %L37 + [ pim:pum(E) || %L38 + L <- foo:bar(), %L39 + E <- hey:ho(L)], %L40 + [ %L41 + pim:pum(E) || %L42 + L <- foo:bar(), %L43 + E <- hey:ho(L) %L44 + ], %L45 + H = fun(X) -> foo:bar(X) + 1 end, %L46, + H(42), %L47 + K = fun(X) -> %L48 + foo:bar(X) + 1 %L49 + end, %L50, + K(42). %L51 + """, + Expected = [ + {04, #{calls => []}}, + {06, #{calls => [{'not',toplevel,2}]}}, + {07, #{calls => [{foo, bar, 2}]}}, + {08, #{calls => [{local, 0}]}}, + {09, #{calls => [{local, 0}]}}, + {10, #{calls => [{foo, bar, 1}]}}, + {11, #{calls => [{foo, blah, 0}, {local, 0}]}}, + {12, #{calls => [{foo, bar, 0}]}}, + {14, #{calls => [{hey, ho, 1}, {local, 0}]}}, + {15, #{calls => [{foo, bar, 0}]}}, + {17, #{calls => [{foo, blah, 0}]}}, + {19, #{calls => [{hey, ho, 1}, {foo, bar, 1}]}}, + {20, #{calls => [{foo, bar, 1}, {erlang, '!', 2}]}}, + {21, #{calls => [{hey, ho, 1}, {foo, bar, 1}]}}, + {22, #{calls => [{hey, ho, 1}, {foo, bar, 1}, {pim, pam, 0}]}}, + {23, #{calls => [{hey, ho, 1}, {foo, bar, 1}, {pim, pam, 0}]}}, + {24, #{calls => [{hey, ho, 1}, {foo, bar, 1}]}}, + {25, #{calls => [{~"X", handle_call, 3}]}}, + {26, #{calls => [{foo, ~"F", 3}]}}, + {27, #{calls => [{~"X", ~"F", 0}]}}, + {28, #{calls => [~"F"]}}, + {29, #{calls => [{foo, bam, 1}]}}, + {30, #{calls => [{~"X", bam, 0}]}}, + {31, #{calls => []}}, + {32, #{calls => [{erlang, make_fun, 3}, {foo, bar, 1}]}}, + {33, #{calls => [{erlang, make_fun, 3}, {foo, blah, 2}]}}, + {34, #{calls => [{local, 0}]}}, + {35, #{calls => [{foo, bar, 2}]}}, + {36, #{calls => [{foo, bar, 2}]}}, + + % We currently can have a single entry for a debug_line, + % so the the other function calls, that end up + % inside the comprehension function, get no entry and no + % annotation + {37, #{calls => [{foo, bar, 0}, {'-fixtures/1-lc$^0/1-0-',1}]}}, + + % One call missing, still due to debug_line overlapping with + % main function + {38, #{calls => []}}, + {39, #{calls => [{foo, bar, 0}, {'-fixtures/1-lc$^2/1-2-',1}]}}, + {40, #{calls => [{hey, ho, 1}, {'-fixtures/1-lc$^3/1-3-',2}]}}, + + {41, #{calls => []}}, + {42, #{calls => [{pim, pum, 1}]}}, + {43, #{calls => [{foo, bar, 0}, {'-fixtures/1-lc$^4/1-4-',1}]}}, + {44, #{calls => [{hey, ho, 1}, {'-fixtures/1-lc$^5/1-5-',2}]}}, + + % Call inside closure missed due to debug_line conflict + {46, #{calls => []}}, + {47, #{calls => [{'-fixtures/1-fun-6-',1}]}}, + + {48, #{calls => []}}, + {49, #{calls => [{foo, bar, 1}]}}, + {51, #{calls => [{'-fixtures/1-fun-7-',1}]}} + ], + check_expected_calls(Config, M, S, Expected). + + +calls_cornercase_reg_in_call(Config) -> + M = ?FUNCTION_NAME, + S = ~""" + -module(calls_cornercase_reg_in_call). %L01 + -export([go/1]). %L02 + go(X) -> %L03 + try %L04 + Y = foo:bar(), %L05 + Z = Y:go(), %L06 + hey:ho(Y, X, Z) %L07 + catch _ -> ok %L08 + end. %L09 + """, + Expected = [ + {04, #{calls => []}}, + {05, #{calls => [{foo,bar,0}]}}, + + % The result from foo:bar() is in x0, which is + % passed directly in the `call` instruction as + % first argument, so we currently lose the + % connection with Z + % {06, #{calls => [{~"Y",go,0}]}}, + {06, #{calls => []}}, + + {07, #{calls => [{hey,ho,3}]}}, + {08, #{calls => []}} + ], + check_expected_calls(Config, M, S, Expected). + %%% %%% Common utility functions. @@ -800,3 +1008,28 @@ get_unique_beam_files() -> test_lib:get_unique_files(".beam", F). id(I) -> I. + +check_expected_calls(Config, Mod, ModSrc, Expected) -> + PrivDir = proplists:get_value(priv_dir, Config), + SrcName = filename:join(PrivDir, atom_to_list(Mod) ++ ".erl"), + BeamName = filename:join(PrivDir, atom_to_list(Mod) ++ ".beam"), + + ok = file:write_file(SrcName, ModSrc), + {ok,M,Beam} = compile:file(SrcName, [return_errors, beam_debug_info,binary]), + + {ok, Peer, Node} = ?CT_PEER(#{args => ["+D"]}), + + ok = erpc:call(Node, fun() -> + code:load_binary(Mod, BeamName, Beam), + + Actual = [{L, maps:with([calls], Item)} || + {L, Item} <:- code:get_debug_info(M)], + + [?assertEqual(ExpectedL, ActualL) || + ExpectedL <- Expected && ActualL <- Actual], + + ok + end), + + peer:stop(Peer), + ok. diff --git a/lib/kernel/src/code.erl b/lib/kernel/src/code.erl index cd06a6da1196..441696ebfd06 100644 --- a/lib/kernel/src/code.erl +++ b/lib/kernel/src/code.erl @@ -432,7 +432,10 @@ common reasons. | {'y',non_neg_integer()} | {value, _}. -nominal debug_value() :: {debug_name(), debug_source()}. --nominal debug_info() :: [{debug_line(), {debug_frame(), [debug_value()]}}]. +-nominal debug_call() :: mfa() | {LocalFun :: atom(), arity} | debug_name(). +-nominal debug_info() :: [{debug_line(), #{frame_size => debug_frame(), + vars => [debug_value()], + calls => [debug_call()]}}]. -export([coverage_support/0, get_coverage/2,