Sign Up
Log In
Log In
or
Sign Up
Places
All Projects
Status Monitor
Collapse sidebar
home:Ledest:erlang:26
erlang
3701-Add-and-use-proc_lib-set-and-get-_label-1....
Overview
Repositories
Revisions
Requests
Users
Attributes
Meta
File 3701-Add-and-use-proc_lib-set-and-get-_label-1.patch of Package erlang
From c4ae0577032b9bf12317eac2f54f24aa76094123 Mon Sep 17 00:00:00 2001 From: Dan Gudmundsson <dgud@erlang.org> Date: Fri, 6 Oct 2023 10:10:17 +0200 Subject: [PATCH] Add (and use) proc_lib:set(and get)_label/1 Make it possible for the user to set a process label which can be used in tools and crash reports to identity processes but it doesn't have to be unique, as an registered name needs to be. The process label can any term, for example {worker, 1..N}, {pool_process, 1..N} or something entirely different to identify process that use general code. While at it optimize fetching process info, so we don't have to (rpc:) call the process_info(..) several times. --- lib/kernel/test/logger_legacy_SUITE.erl | 2 + lib/observer/doc/src/observer_ug.xml | 2 + lib/observer/src/etop_txt.erl | 3 +- lib/observer/src/observer_pro_wx.erl | 73 ++++-- lib/observer/src/observer_procinfo.erl | 36 ++- lib/observer/src/observer_wx.erl | 10 +- lib/runtime_tools/src/appmon_info.erl | 19 +- lib/runtime_tools/src/observer_backend.erl | 37 ++- lib/runtime_tools/src/runtime_tools.app.src | 4 +- lib/stdlib/doc/src/proc_lib.xml | 28 +++ lib/stdlib/src/c.erl | 54 ++++- lib/stdlib/src/proc_lib.erl | 237 ++++++++++++-------- lib/stdlib/src/stdlib.app.src | 2 +- lib/stdlib/test/proc_lib_SUITE.erl | 24 +- 14 files changed, 395 insertions(+), 136 deletions(-) diff --git a/lib/kernel/test/logger_legacy_SUITE.erl b/lib/kernel/test/logger_legacy_SUITE.erl index 0e46ec3ee3..2d891eb7f2 100644 --- a/lib/kernel/test/logger_legacy_SUITE.erl +++ b/lib/kernel/test/logger_legacy_SUITE.erl @@ -190,6 +190,7 @@ sasl_reports(Config) -> [[{initial_call,_}, {pid,ChPid}, {registered_name,[]}, + {process_label, undefined}, {error_info,{error,{badmatch,b},_}}, {ancestors,_}, {message_queue_len,_}, @@ -203,6 +204,7 @@ sasl_reports(Config) -> {reductions,_}], [{neighbour,[{pid,Neighbour}, {registered_name,_}, + {process_label, undefined}, {initial_call,_}, {current_function,_}, {ancestors,_}, diff --git a/lib/observer/doc/src/observer_ug.xml b/lib/observer/doc/src/observer_ug.xml index 348e613c85..f6b1ca02df 100644 --- a/lib/observer/doc/src/observer_ug.xml +++ b/lib/observer/doc/src/observer_ug.xml @@ -163,6 +163,8 @@ <taglist> <tag>Pid</tag> <item><p>The process identifier.</p></item> + <tag>Description</tag> + <item><p>Registered name, <seemfa marker="stdlib:proc_lib#set_label/1">process label</seemfa> or initial function.</p></item> <tag>Reds</tag> <item><p>The number of reductions executed on the process. This can be presented as accumulated values or as values since the last update.</p></item> diff --git a/lib/observer/src/etop_txt.erl b/lib/observer/src/etop_txt.erl index e91db7d0f2..957427687d 100644 --- a/lib/observer/src/etop_txt.erl +++ b/lib/observer/src/etop_txt.erl @@ -225,7 +225,8 @@ proc_format(Modifier, #field_widths{init_func = InitFunc, reds = Reds, "~" ++ i2l(MsgQ) ++ "w " "~-" ++ i2l(CurrFunc) ++ Modifier ++ "s~n". - +to_string(Other,_Modifier) when is_binary(Other) -> + Other; to_string({M,F,A},Modifier) -> io_lib:format("~w:~"++Modifier++"w/~w",[M,F,A]); to_string(Other,Modifier) -> diff --git a/lib/observer/src/observer_pro_wx.erl b/lib/observer/src/observer_pro_wx.erl index 8f67491d58..94c84fdfa1 100644 --- a/lib/observer/src/observer_pro_wx.erl +++ b/lib/observer/src/observer_pro_wx.erl @@ -165,7 +165,7 @@ create_list_box(Panel, Holder) -> end, Scale = observer_wx:get_scale(), ListItems = [{"Pid", ?wxLIST_FORMAT_CENTRE, Scale*120}, - {"Name or Initial Func", ?wxLIST_FORMAT_LEFT, Scale*200}, + {"Description", ?wxLIST_FORMAT_LEFT, Scale*200}, %% {"Time", ?wxLIST_FORMAT_CENTRE, Scale*50}, {"Reds", ?wxLIST_FORMAT_RIGHT, Scale*100}, {"Memory", ?wxLIST_FORMAT_RIGHT, Scale*100}, @@ -665,29 +665,61 @@ merge_fun(Col) -> fun(A,B) -> lists:keymerge(KeyField, A, B) end. +%% Assumes that there are many undescribed MFA processes. +%% So we sort them separately, to not create temporary bin-strings +%% that will create a lot of garbage + sort_name(#etop_proc_info{name={_,_,_}=A}, #etop_proc_info{name={_,_,_}=B}) -> A =< B; sort_name(#etop_proc_info{name=A}, #etop_proc_info{name=B}) when is_atom(A), is_atom(B) -> A =< B; -sort_name(#etop_proc_info{name=Reg}, #etop_proc_info{name={M,_F,_A}}) - when is_atom(Reg) -> - Reg < M; -sort_name(#etop_proc_info{name={M,_,_}}, #etop_proc_info{name=Reg}) - when is_atom(Reg) -> - M < Reg. +sort_name(#etop_proc_info{name=A}, #etop_proc_info{name=B}) + when is_binary(A), is_binary(B) -> + A =< B; +sort_name(#etop_proc_info{name=A}, #etop_proc_info{name=B}) + when is_binary(A), is_atom(B) -> + A =< atom_to_binary(B); +sort_name(#etop_proc_info{name=A}, #etop_proc_info{name=B}) + when is_binary(B), is_atom(A) -> + atom_to_binary(A) =< B; +sort_name(_, #etop_proc_info{name={_,_,_}}) -> + true; +sort_name(#etop_proc_info{name={_,_,_}}, _) -> + false. + +%% sort_name(#etop_proc_info{name=Reg}, #etop_proc_info{name={M,_F,_A}}) +%% when is_atom(Reg) -> +%% Reg < M; +%% sort_name(#etop_proc_info{name={M,_,_}}, #etop_proc_info{name=Reg}) +%% when is_atom(Reg) -> +%% M < Reg. sort_name_rev(#etop_proc_info{name={_,_,_}=A}, #etop_proc_info{name={_,_,_}=B}) -> A >= B; sort_name_rev(#etop_proc_info{name=A}, #etop_proc_info{name=B}) when is_atom(A), is_atom(B) -> A >= B; -sort_name_rev(#etop_proc_info{name=Reg}, #etop_proc_info{name={M,_F,_A}}) - when is_atom(Reg) -> - Reg >= M; -sort_name_rev(#etop_proc_info{name={M,_,_}}, #etop_proc_info{name=Reg}) - when is_atom(Reg) -> - M >= Reg. +sort_name_rev(#etop_proc_info{name=A}, #etop_proc_info{name=B}) + when is_binary(A), is_binary(B) -> + A >= B; +sort_name_rev(#etop_proc_info{name=A}, #etop_proc_info{name=B}) + when is_binary(A), is_atom(B) -> + A >= atom_to_binary(B); +sort_name_rev(#etop_proc_info{name=A}, #etop_proc_info{name=B}) + when is_binary(B), is_atom(A) -> + atom_to_binary(A) >= B; +sort_name_rev(_, #etop_proc_info{name={_,_,_}}) -> + false; +sort_name_rev(#etop_proc_info{name={_,_,_}}, _) -> + true. + +%% sort_name_rev(#etop_proc_info{name=Reg}, #etop_proc_info{name={M,_F,_A}}) +%% when is_atom(Reg) -> +%% Reg >= M; +%% sort_name_rev(#etop_proc_info{name={M,_,_}}, #etop_proc_info{name=Reg}) +%% when is_atom(Reg) -> +%% M >= Reg. %%%%%%%%%%%%%%%%%%%%%%%%%%%%%% @@ -707,6 +739,7 @@ get_pids(From, Indices, ProcInfo) -> get_name_or_pid(From, Indices, ProcInfo) -> Get = fun(#etop_proc_info{name=Name}) when is_atom(Name) -> Name; + (#etop_proc_info{name=Name}) when is_atom(Name) -> Name; (#etop_proc_info{pid=Pid}) -> Pid end, Processes = [Get(array:get(I, ProcInfo)) || I <- Indices], @@ -718,6 +751,20 @@ get_row(From, Row, pid, Info) -> false -> {ok, get_procinfo_data(?COL_PID, array:get(Row, Info))} end, From ! {self(), Pid}; +get_row(From, Row, ?COL_NAME, Info) -> + String = case Row >= array:size(Info) of + true -> + ""; + false -> + ProcInfo = array:get(Row, Info), + case get_procinfo_data(?COL_NAME, ProcInfo) of + Name when is_binary(Name) -> + Name; + AtomOrMFA -> + observer_lib:to_str(AtomOrMFA) + end + end, + From ! {self(), String}; get_row(From, Row, Col, Info) -> Data = case Row >= array:size(Info) of true -> diff --git a/lib/observer/src/observer_procinfo.erl b/lib/observer/src/observer_procinfo.erl index a22f76a4c7..2b12f53062 100644 --- a/lib/observer/src/observer_procinfo.erl +++ b/lib/observer/src/observer_procinfo.erl @@ -54,12 +54,8 @@ start(Process, ParentFrame, Parent) -> init([Pid, ParentFrame, Parent]) -> try Table = ets:new(observer_expand,[set,public]), - Title=case observer_wx:try_rpc(node(Pid), erlang, process_info, [Pid, registered_name]) of - [] -> io_lib:format("~p",[Pid]); - {registered_name, Registered} -> io_lib:format("~tp (~p)",[Registered, Pid]); - undefined -> throw(process_undefined) - end, - Scale = observer_wx:get_scale(), + Title = get_name(Pid), + Scale = observer_wx:get_scale(), Frame=wxFrame:new(ParentFrame, ?wxID_ANY, [atom_to_list(node(Pid)), $:, Title], [{style, ?wxDEFAULT_FRAME_STYLE}, {size, {Scale * 850, Scale * 600}}]), MenuBar = wxMenuBar:new(), @@ -449,6 +445,34 @@ filter_monitor_info() -> [Id || {_Type, Id} <- Ms] % Type is process or port end. +%% NOTE: intentionally throws error +get_name(Pid) -> + case observer_wx:try_rpc(node(Pid), erlang, process_info, [Pid, registered_name]) of + [] -> + case observer_wx:try_rpc(node(Pid), proc_lib, get_label, [Pid]) of + {error, _} -> + io_lib:format("~w",[Pid]); + undefined -> + io_lib:format("~w",[Pid]); + Label -> + format_label(Label, Pid) + end; + {registered_name, Registered} -> + io_lib:format("~0.tp ~w",[Registered, Pid]); + undefined -> + throw(process_undefined) + end. + +format_label(Id, Pid) when is_list(Id); is_binary(Id) -> + case unicode:characters_to_binary(Id) of + {error, _, _} -> + io_lib:format("~0.tp ~w", [Id, Pid]); + BinString -> + io_lib:format("~ts ~w", [BinString, Pid]) + end; +format_label(Id, Pid) -> + io_lib:format("~0.tp ~w", [Id, Pid]). + stringify_bins(Data) -> Bins = proplists:get_value(binary, Data), [lists:flatten(io_lib:format("<< ~s, refc ~w>>", [observer_lib:to_str({bytes,Sz}),Refc])) diff --git a/lib/observer/src/observer_wx.erl b/lib/observer/src/observer_wx.erl index 530f8c2a6f..8dab4a5248 100644 --- a/lib/observer/src/observer_wx.erl +++ b/lib/observer/src/observer_wx.erl @@ -557,16 +557,16 @@ code_change(_, _, State) -> %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% try_rpc(Node, Mod, Func, Args) -> - case - rpc:call(Node, Mod, Func, Args) of - {badrpc, Reason} -> + try erpc:call(Node, Mod, Func, Args) + catch + error:{erpc, Reason} -> error_logger:error_report([{node, Node}, {call, {Mod, Func, Args}}, {reason, {badrpc, Reason}}]), observer ! {nodedown, Node}, error({badrpc, Reason}); - Res -> - Res + Class:Reason -> + {error, {Class,Reason}} end. return_to_localnode(Frame, Node) -> diff --git a/lib/runtime_tools/src/appmon_info.erl b/lib/runtime_tools/src/appmon_info.erl index ad08a6c66f..d5f3858936 100644 --- a/lib/runtime_tools/src/appmon_info.erl +++ b/lib/runtime_tools/src/appmon_info.erl @@ -710,7 +710,14 @@ format(P) when is_pid(P), node(P) /= node() -> format(P) when is_pid(P) -> case process_info(P, registered_name) of {registered_name, Name} -> atom_to_list(Name); - _ -> pid_to_list(P) + _ -> + %% Needs to be unique + case proc_lib:get_label(P) of + undefined -> + pid_to_list(P); + Label -> + format_label(Label, P) + end end; format(P) when is_port(P) -> case erlang:port_info(P, id) of @@ -722,6 +729,16 @@ format(X) -> io:format("What: ~p~n", [X]), "???". +format_label(Id, Pid) when is_list(Id); is_binary(Id) -> + case unicode:characters_to_binary(Id) of + {error, _, _} -> + io_lib:format("~0.tp ~w", [Id, Pid]); + BinString -> + io_lib:format("~ts ~w", [BinString, Pid]) + end; +format_label(Id, Pid) -> + io_lib:format("~0.tp ~w", [Id, Pid]). + %%---------------------------------------------------------------------- %%********************************************************************** diff --git a/lib/runtime_tools/src/observer_backend.erl b/lib/runtime_tools/src/observer_backend.erl index ccd2240a99..492a289d24 100644 --- a/lib/runtime_tools/src/observer_backend.erl +++ b/lib/runtime_tools/src/observer_backend.erl @@ -575,15 +575,21 @@ etop_memi() -> etop_collect([P|Ps], Acc) when P =:= self() -> etop_collect(Ps, Acc); etop_collect([P|Ps], Acc) -> - Fs = [registered_name,initial_call,memory,reductions,current_function,message_queue_len], + Fs = [registered_name,initial_call, + {dictionary, '$initial_call'}, {dictionary, '$process_label'}, + memory,reductions,current_function,message_queue_len], case process_info(P, Fs) of undefined -> etop_collect(Ps, Acc); - [{registered_name,Reg},{initial_call,Initial},{memory,Mem}, - {reductions,Reds},{current_function,Current},{message_queue_len,Qlen}] -> - Name = case Reg of - [] -> initial_call(Initial, P); - _ -> Reg + [{registered_name,Reg},{initial_call,Initial}, + {{dictionary, '$initial_call'}, DictInitial}, + {{dictionary, '$process_label'}, ProcId}, + {memory,Mem},{reductions,Reds}, + {current_function,Current},{message_queue_len,Qlen} + ] -> + Name = if Reg /= "" -> Reg; + ProcId /= undefined -> id_to_binary(ProcId); + true -> initial_call(Initial, DictInitial) end, Info = #etop_proc_info{pid=P,mem=Mem,reds=Reds,name=Name, cf=Current,mq=Qlen}, @@ -591,8 +597,23 @@ etop_collect([P|Ps], Acc) -> end; etop_collect([], Acc) -> Acc. -initial_call({proc_lib, init_p, _}, Pid) -> - proc_lib:translate_initial_call(Pid); +id_to_binary(Id) when is_list(Id); is_binary(Id) -> + case unicode:characters_to_binary(Id) of + {error, _, _} -> + unicode:characters_to_binary(io_lib:format("~0.tp", [Id])); + BinString -> + BinString + end; +id_to_binary(TermId) -> + unicode:characters_to_binary(io_lib:format("~0.tp", [TermId])). + +initial_call({proc_lib, init_p, _}, DictInitial) -> + case DictInitial of + {_,_,_} = MFA -> + MFA; + undefined -> %% Fetch the default initial call + proc_lib:translate_initial_call([]) + end; initial_call(Initial, _Pid) -> Initial. diff --git a/lib/runtime_tools/src/runtime_tools.app.src b/lib/runtime_tools/src/runtime_tools.app.src index 6daa698cb8..10309fae0a 100644 --- a/lib/runtime_tools/src/runtime_tools.app.src +++ b/lib/runtime_tools/src/runtime_tools.app.src @@ -29,5 +29,5 @@ {applications, [kernel, stdlib]}, {env, []}, {mod, {runtime_tools, []}}, - {runtime_dependencies, ["stdlib-3.13","mnesia-4.12","kernel-8.1", - "erts-11.0"]}]}. + {runtime_dependencies, ["stdlib-5.2","mnesia-4.12","kernel-8.1", + "erts-14.2"]}]}. diff --git a/lib/stdlib/doc/src/proc_lib.xml b/lib/stdlib/doc/src/proc_lib.xml index a064c8341e..8d1a466dad 100644 --- a/lib/stdlib/doc/src/proc_lib.xml +++ b/lib/stdlib/doc/src/proc_lib.xml @@ -159,6 +159,17 @@ </desc> </func> + <func> + <name name="get_label" arity="1" since="OTP 26.2"/> + <fsummary>Returns the user-set process label.</fsummary> + <desc> + <p>Returns either <c>undefined</c> or the label for the process + <anno>Pid</anno> set with <seemfa marker="#set_label/1"> + <c>proc_lib:set_label/1</c></seemfa>. + </p> + </desc> + </func> + <func> <name name="hibernate" arity="3" since=""/> <fsummary>Hibernate a process until a message is sent to it.</fsummary> @@ -329,6 +340,23 @@ init(Parent) -> </desc> </func> + <func> + <name name="set_label" arity="1" since="OTP 26.2"/> + <fsummary>Set process label.</fsummary> + <desc> + <p>Set a label for the current process. + The primary purpose is to aid in debugging unregistered processes. + The process label can be used in tools and crash reports to identify processes + but it doesn't have to be unique or an atom, as a registered name needs to be. + The process label can be any term, for example <c>{worker_process, 1..N}</c>. + </p> + <p> + Use <seemfa marker="#get_label/1"> + <c>proc_lib:get_label/1</c></seemfa> to lookup the process description. + </p> + </desc> + </func> + <func> <name name="spawn" arity="1" since=""/> <name name="spawn" arity="2" since=""/> diff --git a/lib/stdlib/src/c.erl b/lib/stdlib/src/c.erl index 88573d1df1..f95852b890 100644 --- a/lib/stdlib/src/c.erl +++ b/lib/stdlib/src/c.erl @@ -672,7 +672,22 @@ mfa_string(X) -> w(X). display_info(Pid) -> - case pinfo(Pid) of + PInfo0 = pinfo(Pid, [initial_call, current_function, reductions, message_queue_len, + heap_size, stack_size, registered_name, + {dictionary, '$process_label'}, + {dictionary, '$initial_call'}]), + PInfo = case PInfo0 of + PInfo0 when is_list(PInfo0) -> + PInfo0; + {badrpc, {'EXIT', {badarg, _}}} -> + patch_old_pinfo(pinfo(Pid, [initial_call, current_function, + reductions, message_queue_len, + heap_size, stack_size, registered_name, + dictionary])); + _ -> + undefined + end, + case PInfo of undefined -> {0,0,0,0}; Info -> Call = initial_call(Info), @@ -689,10 +704,7 @@ display_info(Pid) -> iformat(w(Pid), mfa_string(Call), w(HS), w(Reds), w(LM)), - iformat(case fetch(registered_name, Info) of - 0 -> ""; - X -> io_lib:format("~tw", [X]) - end, + iformat(fetch_label(fetch(registered_name, Info), Info), mfa_string(Curr), w(SS), "", @@ -700,6 +712,24 @@ display_info(Pid) -> {Reds, LM, HS, SS} end. +fetch_label([], Info) -> + case fetch({dictionary, '$process_label'}, Info) of + undefined -> ""; + Id -> format_label(Id) + end; +fetch_label(Reg, _) -> + Reg. + +format_label(Id) when is_list(Id); is_binary(Id) -> + case unicode:characters_to_binary(Id) of + {error, _, _} -> + io_lib:format("~0.tp", [Id]); + BinString -> + BinString + end; +format_label(TermId) -> + io_lib:format("~0.tp", [TermId]). + %% We have to do some assumptions about the initial call. %% If the initial call is proc_lib:init_p/3,5 we can find more information %% calling the function proc_lib:initial_call/1. @@ -728,6 +758,20 @@ pinfo(Pid) -> false -> process_info(Pid) end. +pinfo(Pid, What) -> + case is_alive() of + true -> rpc:call(node(Pid), erlang, process_info, [Pid, What]); + false -> process_info(Pid, What) + end. + +patch_old_pinfo(undefined) -> + undefined; +patch_old_pinfo(KeyList0) -> + {value, {dictionary, Dict}, KeyList} = lists:keytake(dictionary, 1, KeyList0), + PD = proplists:get_value('$process_label', Dict, undefined), + IC = proplists:get_value('$initial_call', Dict, undefined), + [{'$process_label', PD}, {'$initial_call', IC} | KeyList]. + fetch(Key, Info) -> case lists:keyfind(Key, 1, Info) of {_, Val} -> Val; diff --git a/lib/stdlib/src/proc_lib.erl b/lib/stdlib/src/proc_lib.erl index 9c7235b954..faa6b0ca9f 100644 --- a/lib/stdlib/src/proc_lib.erl +++ b/lib/stdlib/src/proc_lib.erl @@ -35,6 +35,7 @@ init_p/3,init_p/5,format/1,format/2,format/3,report_cb/2, initial_call/1, translate_initial_call/1, + set_label/1, get_label/1, stop/1, stop/3]). %% Internal exports. @@ -522,6 +523,32 @@ translate_initial_call(DictOrPid) -> {?MODULE,init_p,5} end. +%% ----------------------------------------------------- +%% [get] set_label/1 +%% Add and fetch process id's to aid in debugging +%% ----------------------------------------------------- + +-spec set_label(Label) -> ok when + Label :: term(). +set_label(Label) -> + put('$process_label', Label), + ok. + +-spec get_label(Pid) -> undefined | term() when + Pid :: pid(). +get_label(Pid) -> + case Pid == self() of + true -> + get('$process_label'); + false -> + try get_process_info(Pid, {dictionary, '$process_label'}) of + {process_label, Id} -> Id; + _ -> undefined + catch _:_ -> %% Old Node + undefined + end + end. + %% ----------------------------------------------------- %% Fetch the initial call information exactly as stored %% in the process dictionary. @@ -530,26 +557,26 @@ translate_initial_call(DictOrPid) -> raw_initial_call({X,Y,Z}) when is_integer(X), is_integer(Y), is_integer(Z) -> raw_initial_call(c:pid(X,Y,Z)); raw_initial_call(Pid) when is_pid(Pid) -> - case get_process_info(Pid, dictionary) of - {dictionary,Dict} -> - raw_init_call(Dict); - _ -> - false + case get_dictionary(Pid, '$initial_call') of + {_,_,_}=MFA -> MFA; + _ -> false end; raw_initial_call(ProcInfo) when is_list(ProcInfo) -> - case lists:keyfind(dictionary, 1, ProcInfo) of - {dictionary,Dict} -> - raw_init_call(Dict); - _ -> - false - end. - -raw_init_call(Dict) -> - case lists:keyfind('$initial_call', 1, Dict) of - {_,{_,_,_}=MFA} -> - MFA; - _ -> - false + case lists:keyfind({dictionary, '$initial_call'}, 1, ProcInfo) of + {{dictionary,_}, {_,_,_}=MFA} -> + MFA; + false -> + case lists:keyfind(dictionary, 1, ProcInfo) of + {dictionary,Dict} -> + case lists:keyfind('$initial_call', 1, Dict) of + {_,{_,_,_}=MFA} -> + MFA; + _ -> + false + end; + _ -> + false + end end. %% ----------------------------------------------------- @@ -596,31 +623,26 @@ my_info(Class, Reason, StartF, Stacktrace) -> my_info_1(Class, Reason, Stacktrace)]. my_info_1(Class, Reason, Stacktrace) -> + Keys = [registered_name, dictionary, message_queue_len, + links, trap_exit, status, heap_size, stack_size, reductions], + PInfo = get_process_info(self(), Keys), + {dictionary, Dict} = lists:keyfind(dictionary,1,PInfo), [{pid, self()}, - get_process_info(self(), registered_name), + lists:keyfind(registered_name,1,PInfo), + {process_label, get_label(self())}, {error_info, {Class,Reason,Stacktrace}}, - get_ancestors(self()), - get_process_info(self(), message_queue_len), + {ancestors, get_ancestors()}, + lists:keyfind(message_queue_len,1,PInfo), get_messages(self()), - get_process_info(self(), links), - get_cleaned_dictionary(self()), - get_process_info(self(), trap_exit), - get_process_info(self(), status), - get_process_info(self(), heap_size), - get_process_info(self(), stack_size), - get_process_info(self(), reductions) + lists:keyfind(links, 1, PInfo), + {dictionary, cleaned_dict(Dict)}, + lists:keyfind(trap_exit, 1, PInfo), + lists:keyfind(status, 1, PInfo), + lists:keyfind(heap_size, 1, PInfo), + lists:keyfind(stack_size, 1, PInfo), + lists:keyfind(reductions, 1, PInfo) ]. --spec get_ancestors(pid()) -> {'ancestors', [pid()]}. - -get_ancestors(Pid) -> - case get_dictionary(Pid,'$ancestors') of - {'$ancestors',Ancestors} -> - {ancestors,Ancestors}; - _ -> - {ancestors,[]} - end. - %% The messages and the dictionary are possibly limited too much if %% some error handles output the messages or the dictionary using ~P %% or ~W with depth greater than the depth used here (the depth of @@ -654,12 +676,6 @@ receive_messages(N) -> [] end. -get_cleaned_dictionary(Pid) -> - case get_process_info(Pid,dictionary) of - {dictionary,Dict} -> {dictionary,cleaned_dict(Dict)}; - _ -> {dictionary,[]} - end. - cleaned_dict(Dict) -> CleanDict = clean_dict(Dict), error_logger:limit_term(CleanDict). @@ -668,65 +684,107 @@ clean_dict([{'$ancestors',_}|Dict]) -> clean_dict(Dict); clean_dict([{'$initial_call',_}|Dict]) -> clean_dict(Dict); +clean_dict([{'$process_label',_}|Dict]) -> + clean_dict(Dict); clean_dict([E|Dict]) -> [E|clean_dict(Dict)]; clean_dict([]) -> []. get_dictionary(Pid,Tag) -> - case get_process_info(Pid,dictionary) of - {dictionary,Dict} -> - case lists:keysearch(Tag,1,Dict) of - {value,Value} -> Value; - _ -> undefined - end; + try get_process_info(Pid, {dictionary, Tag}) of + {{dictionary,Tag},Value} -> + Value; _ -> undefined + catch _:_ -> %% rpc to old node + case get_process_info(Pid,dictionary) of + {dictionary,Dict} -> + case lists:keysearch(Tag,1,Dict) of + {value,Value} -> Value; + _ -> undefined + end; + _ -> + undefined + end end. linked_info(Pid) -> make_neighbour_reports1(neighbours(Pid)). make_neighbour_reports1([P|Ps]) -> - ReportBody = make_neighbour_report(P), - %% - %% Process P might have been deleted. - %% - case lists:member(undefined, ReportBody) of - true -> - make_neighbour_reports1(Ps); - false -> - [{neighbour, ReportBody}|make_neighbour_reports1(Ps)] - end; + %% + %% Process P might have been deleted. + %% + case make_neighbour_report(P) of + undefined -> + make_neighbour_reports1(Ps); + ReportBody -> + [{neighbour, ReportBody}|make_neighbour_reports1(Ps)] + end; make_neighbour_reports1([]) -> - []. + []. %% Do not include messages or process dictionary, even if %% error_logger_format_depth is unlimited. make_neighbour_report(Pid) -> - [{pid, Pid}, - get_process_info(Pid, registered_name), - get_initial_call(Pid), - get_process_info(Pid, current_function), - get_ancestors(Pid), - get_process_info(Pid, message_queue_len), - %% get_messages(Pid), - get_process_info(Pid, links), - %% get_cleaned_dictionary(Pid), - get_process_info(Pid, trap_exit), - get_process_info(Pid, status), - get_process_info(Pid, heap_size), - get_process_info(Pid, stack_size), - get_process_info(Pid, reductions), - get_process_info(Pid, current_stacktrace) - ]. - -get_initial_call(Pid) -> - case get_dictionary(Pid, '$initial_call') of - {'$initial_call', {M, F, A}} -> + Keys = [registered_name, + initial_call, current_function, + message_queue_len, links, trap_exit, + status, heap_size, stack_size, reductions, + current_stacktrace + ], + ProcInfo = get_process_info(Pid, Keys), + + DictKeys = [{dictionary, '$process_label'}, + {dictionary, '$initial_call'}, + {dictionary, '$ancestors'}], + + DictInfo = try get_process_info(Pid, DictKeys) + catch _:_ -> %% old node + get_process_info(Pid, dictionary) + end, + case ProcInfo =:= undefined orelse DictInfo =:= undefined of + true -> undefined; + false -> + [{pid, Pid}, + lists:keyfind(registered_name,1,ProcInfo), + dict_find_info('$process_label', DictInfo, undefined), + get_initial_call(DictInfo, ProcInfo), + lists:keyfind(current_function, 1, ProcInfo), + dict_find_info('$ancestors', DictInfo, []), + lists:keyfind(message_queue_len, 1, ProcInfo), + lists:keyfind(links, 1, ProcInfo), + lists:keyfind(trap_exit, 1, ProcInfo), + lists:keyfind(status, 1, ProcInfo), + lists:keyfind(heap_size, 1, ProcInfo), + lists:keyfind(stack_size, 1, ProcInfo), + lists:keyfind(reductions, 1, ProcInfo), + lists:keyfind(current_stacktrace, 1, ProcInfo) + ] + end. + +get_initial_call(DictInfo, ProcInfo) -> + case dict_find_info('$initial_call', DictInfo, undefined) of + {initial_call, {M, F, A}} -> {initial_call, {M, F, make_dummy_args(A, [])}}; - _ -> - get_process_info(Pid, initial_call) + _R -> + lists:keyfind(initial_call, 1, ProcInfo) + end. + +dict_find_info(DictKey, Dict, Default) -> + [$$|KeyList] = atom_to_list(DictKey), + InfoKey = list_to_existing_atom(KeyList), + case lists:keyfind({dictionary, DictKey}, 1, Dict) of + false -> + case lists:keyfind(DictKey, 1, Dict) of + {DictKey, V} -> {InfoKey, V}; + false -> {InfoKey, Default} + end; + {{dictionary,DictKey}, undefined} -> + {InfoKey,Default}; + {{dictionary,DictKey}, V} -> + {InfoKey,V} end. %% neighbours(Pid) = list of Pids @@ -781,14 +839,14 @@ no_trap([]) -> []. get_process_info(Pid, Tag) -> - translate_process_info(Tag, catch proc_info(Pid, Tag)). + translate_process_info(Tag, catch proc_info(Pid, Tag)). -translate_process_info(registered_name, []) -> - {registered_name, []}; +translate_process_info({dictionary, '$process_label'} = Tag, {Tag, Value}) -> + {process_label, Value}; translate_process_info(_ , {'EXIT', _}) -> - undefined; + undefined; translate_process_info(_, Result) -> - Result. + Result. %%% ----------------------------------------------------------- %%% Misc. functions @@ -801,7 +859,6 @@ get_my_name() -> end. -spec get_ancestors() -> [pid()]. - get_ancestors() -> case get('$ancestors') of A when is_list(A) -> A; @@ -998,6 +1055,8 @@ format_report(Rep, Indent0, Extra, Limit) -> format_rep([{initial_call,InitialCall}|Rep], Indent, Extra, Limit) -> [format_mfa(Indent, InitialCall, Extra, Limit)| format_rep(Rep, Indent, Extra, Limit)]; +format_rep([{process_label,undefined}|Rep], Indent, Extra, Limit) -> + format_rep(Rep, Indent, Extra, Limit); format_rep([{Tag,Data}|Rep], Indent, Extra, Limit) -> [format_tag(Indent, Tag, Data, Extra, Limit)| format_rep(Rep, Indent, Extra, Limit)]; diff --git a/lib/stdlib/src/stdlib.app.src b/lib/stdlib/src/stdlib.app.src index 932d05e895..e3609aff48 100644 --- a/lib/stdlib/src/stdlib.app.src +++ b/lib/stdlib/src/stdlib.app.src @@ -116,6 +116,6 @@ dets]}, {applications, [kernel]}, {env, []}, - {runtime_dependencies, ["sasl-3.0","kernel-9.2","erts-13.1","crypto-4.5", + {runtime_dependencies, ["sasl-3.0","kernel-9.2","erts-14.2","crypto-4.5", "compiler-5.0"]} ]}. diff --git a/lib/stdlib/test/proc_lib_SUITE.erl b/lib/stdlib/test/proc_lib_SUITE.erl index 5db6d88a15..f3fafb2bc8 100644 --- a/lib/stdlib/test/proc_lib_SUITE.erl +++ b/lib/stdlib/test/proc_lib_SUITE.erl @@ -30,8 +30,8 @@ sync_start_monitor/1, sync_start_monitor_link/1, sync_start_timeout/1, sync_start_link_timeout/1, sync_start_monitor_link_timeout/1, - spawn_opt/1, sp1/0, sp2/0, sp3/1, sp4/2, sp5/1, sp6/1, sp7/1, - sp8/1, sp9/1, sp10/1, + spawn_opt/1, sp1/0, sp1_with_label/0, sp2/0, sp3/1, sp4/2, + sp5/1, sp6/1, sp7/1, sp8/1, sp9/1, sp10/1, '\x{447}'/0, hibernate/1, stop/1, t_format/1, t_format_arbitrary/1]). -export([ otp_6345/1, init_dont_hang/1]). @@ -135,11 +135,18 @@ crash_1(_Config) -> ct:sleep(100), {?MODULE,sp2,[]} = proc_lib:initial_call(Pid4), {?MODULE,sp2,0} = proc_lib:translate_initial_call(Pid4), + {test, sp2} = proc_lib:get_label(Pid4), + %% Check this, if changed fix c.erl and runtime_tools + %% which uses the 'internal' dictionary name as an optimization. + {_, {test, sp2}} = process_info(Pid4, {dictionary, '$process_label'}), + Pid4 ! die, Exp4 = [{initial_call,{?MODULE,sp2,[]}}, + {process_label, {test, sp2}}, {ancestors,[self()]}, {error_info,{exit,die,{stacktrace}}}], - Links4 = [[{initial_call,{?MODULE,sp1,[]}}, + Links4 = [[{initial_call,{?MODULE,sp1_with_label,[]}}, + {process_label, {test, sp1_with_label}}, {ancestors,[Pid4,self()]}]], analyse_crash(Pid4, Exp4, Links4), @@ -380,13 +387,20 @@ spawn_opt(Config) when is_list(Config) -> sp1() -> - receive + receive die -> exit(die); _ -> sp1() end. +sp1_with_label() -> + ok = proc_lib:set_label({test, ?FUNCTION_NAME}), + sp1(). + sp2() -> - _Pid = proc_lib:spawn_link(?MODULE, sp1, []), + ok = proc_lib:set_label({test, ?FUNCTION_NAME}), + {test, ?FUNCTION_NAME} = proc_lib:get_label(self()), + + _Pid = proc_lib:spawn_link(?MODULE, sp1_with_label, []), receive die -> exit(die); _ -> sp1() -- 2.43.0
Locations
Projects
Search
Status Monitor
Help
OpenBuildService.org
Documentation
API Documentation
Code of Conduct
Contact
Support
@OBShq
Terms
openSUSE Build Service is sponsored by
The Open Build Service is an
openSUSE project
.
Sign Up
Log In
Places
Places
All Projects
Status Monitor