diff --git a/lib/debugger/src/dbg_ieval.erl b/lib/debugger/src/dbg_ieval.erl index 70600121b3ee..df725ed9e549 100644 --- a/lib/debugger/src/dbg_ieval.erl +++ b/lib/debugger/src/dbg_ieval.erl @@ -462,8 +462,9 @@ do_eval_function(Mod, Name, As0, Bs0, Called, Ieval0) -> trace(call, {Called, {Le,Li,Mod,Name,As0}}), Ieval = Ieval0#ieval{module=Mod,function=Name,arguments=As0}, case get_function(Mod, Name, As0, Called) of - Cs when is_list(Cs) -> - fnk_clauses(Cs, As0, erl_eval:new_bindings(), Ieval); + [{clause,FcLine,_,_,_}|_]=Cs -> + fnk_clauses(Cs, As0, erl_eval:new_bindings(), + Ieval#ieval{line=FcLine}); not_interpreted when Top -> % We are leaving interpreted code {value, {dbg_apply,Mod,Name,As0}, Bs0}; @@ -836,7 +837,7 @@ expr({safe_bif,Line,M,F,As0}, Bs0, #ieval{level=Le}=Ieval0) -> {As,Bs} = eval_list(As0, Bs0, Ieval1), trace(bif, {Le,Line,M,F,As}), Ieval2 = dbg_istk:push(Bs0, Ieval1, false), - Ieval = Ieval2#ieval{module=M,function=F,arguments=As}, + Ieval = Ieval2#ieval{module=M,function=F,arguments=As,line=-1}, {_,Value,_} = Res = safe_bif(M, F, As, Bs, Ieval), trace(return, {Le,Value}), dbg_istk:pop(), @@ -848,7 +849,7 @@ expr({bif,Line,M,F,As0}, Bs0, #ieval{level=Le}=Ieval0) -> {As,Bs} = eval_list(As0, Bs0, Ieval1), trace(bif, {Le,Line,M,F,As}), Ieval2 = dbg_istk:push(Bs0, Ieval1, false), - Ieval = Ieval2#ieval{module=M,function=F,arguments=As}, + Ieval = Ieval2#ieval{module=M,function=F,arguments=As,line=-1}, {_,Value,_} = Res = debugged_cmd({apply,M,F,As}, Bs, Ieval), trace(return, {Le,Value}), dbg_istk:pop(), diff --git a/lib/debugger/src/dbg_istk.erl b/lib/debugger/src/dbg_istk.erl index e0c4c61333c6..c6922a80e473 100644 --- a/lib/debugger/src/dbg_istk.erl +++ b/lib/debugger/src/dbg_istk.erl @@ -120,26 +120,27 @@ delayed_stacktrace() -> Stack0 = get(?STACK), fun(NumEntries) -> Stack = stacktrace(NumEntries, Stack0, []), - [ArityOnly || {ArityOnly,_} <- Stack] + [finalize(ArityOnly) || {ArityOnly,_} <- Stack] end. delayed_stacktrace(include_args, Ieval) -> - #ieval{module=Mod,function=Name,arguments=As} = Ieval, - Stack0 = [#e{mfa={Mod,Name,As}}|get(?STACK)], + #ieval{module=Mod,function=Name,arguments=As,line=Li} = Ieval, + Stack0 = [#e{mfa={Mod,Name,As},line=Li}|get(?STACK)], fun(NumEntries) -> case stacktrace(NumEntries, Stack0, []) of [] -> []; [{_,WithArgs}|Stack] -> - [WithArgs | [ArityOnly || {ArityOnly,_} <- Stack]] + [finalize(WithArgs) | + [finalize(ArityOnly) || {ArityOnly,_} <- Stack]] end end; delayed_stacktrace(no_args, Ieval) -> - #ieval{module=Mod,function=Name,arguments=As} = Ieval, - Stack0 = [#e{mfa={Mod,Name,As}}|get(?STACK)], + #ieval{module=Mod,function=Name,arguments=As,line=Li} = Ieval, + Stack0 = [#e{mfa={Mod,Name,As},line=Li}|get(?STACK)], fun(NumEntries) -> Stack = stacktrace(NumEntries, Stack0, []), - [ArityOnly || {ArityOnly,_} <- Stack] + [finalize(ArityOnly) || {ArityOnly,_} <- Stack] end. stacktrace(N, [#e{lc=true}|T], Acc) -> @@ -156,10 +157,19 @@ stacktrace(N, [E|T], [{P,_}|_]=Acc) when N > 0 -> stacktrace(_, _, Acc) -> lists:reverse(Acc). -normalize(#e{mfa={_,Fun,As}}) when is_function(Fun) -> - {{Fun,length(As),[]},{Fun,As,[]}}; -normalize(#e{mfa={M,F,As}}) -> - {{M,F,length(As),[]},{M,F,As,[]}}. +normalize(#e{mfa={M,Fun,As},line=Li}) when is_function(Fun) -> + Loc = {M,Li}, + {{Fun,length(As),Loc},{Fun,As,Loc}}; +normalize(#e{mfa={M,F,As},line=Li}) -> + Loc = {M,Li}, + {{M,F,length(As),Loc},{M,F,As,Loc}}. + +finalize({M,F,A,Loc}) -> {M,F,A,line(Loc)}; +finalize({Fun,A,Loc}) -> {Fun,A,line(Loc)}. + +line({Mod,Line}) when Line > 0 -> + [{file,atom_to_list(Mod)++".erl"},{line,Line}]; +line(_) -> []. %% bindings(SP) -> Bs %% SP = Le % stack pointer diff --git a/lib/debugger/test/exception_SUITE.erl b/lib/debugger/test/exception_SUITE.erl index 50c5e611d4d3..86554ab2d498 100644 --- a/lib/debugger/test/exception_SUITE.erl +++ b/lib/debugger/test/exception_SUITE.erl @@ -32,6 +32,19 @@ suite() -> [{ct_hooks,[ts_install_cth]}]. +%% Filler. +%% +%% +%% +%% +%% This is line 40. +even(N) when is_integer(N), N > 1, (N rem 2) == 0 -> + odd(N-1)++[N]. + +odd(N) when is_integer(N), N > 1, (N rem 2) == 1 -> + even(N-1)++[N]. + + all() -> cases(). @@ -389,19 +402,15 @@ raise(Conf) when is_list(Conf) -> odd_even(N, R) when is_integer(N), N > 1 -> odd_even(N-1, [if (N rem 2) == 0 -> - {?MODULE,even,1,[]}; + {?MODULE,even,1,[{file,?MODULE_STRING++".erl"}, + {line,42}]}; true -> - {?MODULE,odd,1,[]} + {?MODULE,odd,1,[{file,?MODULE_STRING++".erl"}, + {line,45}]} end|R]); odd_even(1, R) -> - [{?MODULE,odd,[1],[]}|R]. - -even(N) when is_integer(N), N > 1, (N rem 2) == 0 -> - odd(N-1)++[N]. - -odd(N) when is_integer(N), N > 1, (N rem 2) == 1 -> - even(N-1)++[N]. - + [{?MODULE,odd,[1],[{file,?MODULE_STRING++".erl"}, + {line,44}]}|R]. foo({value,Value}) -> Value; foo({'div',{A,B}}) ->