From 7b169140b2d37f43996b9d1a94877926a471d97d Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Bj=C3=B6rn=20Gustavsson?= Date: Tue, 2 May 2017 05:41:17 +0200 Subject: Warn for potentially unsafe use of get_stacktrace/0 erlang:get_stacktrace/0 returns the stacktrace for the latest exception. The problem is that the stacktrace is kept until the next exception occurs. If the last exception was a 'function_clause' or a 'badarg', the arguments for the call are also kept forever. The arguments can be terms of any size (potentially huge). In a future release, we would like to only allow erlang:get_stacktrace/0 from within a 'try' expression. That would make it possible to clear the stacktrace when the 'try' expression is exited. The 'catch' expression has no natural end where the stacktrace could be cleared. The stacktrace could be cleared at the end of the function that the 'catch' occurs in, but that would cause problems in the following scenario (from real life, but simplified): try ... catch _:_ -> io:format(...), io:format("~p\n", [erlang:get_stacktrace()]) end. %% In io.erl. format(Fmt, Args) -> Res = case ... of SomePattern -> catch... ...; SomeOtherPattern -> %% Output the formatted string here ... end, clear_stacktrace(), %% Inserted by compiler. Res. The call to io:format() would always clear the stacktrace before it could be retrieved. That problem could be solved by tightning the scope in which the stacktrace is kept, but the rules for how long erlang:get_stacktrace/0 would work would become complicated. Therefore, the solution we suggest for a future major release of OTP is that erlang:get_stacktrace/0 will return [] if it is called outside the 'catch' part of a 'try' expression. To help users prepare, introduce a warning when it is likely that erlang:get_stacktrace/0 will always return an empty list, for example in this code: catch error(foo), Stk = erlang:get_stacktrace() or in this code: try Expr catch _:_ -> ok end, Stk = erlang:get_stacktrace() --- lib/stdlib/src/erl_lint.erl | 73 ++++++++++++++++++++++++++++++++++++++------- 1 file changed, 63 insertions(+), 10 deletions(-) (limited to 'lib/stdlib/src') diff --git a/lib/stdlib/src/erl_lint.erl b/lib/stdlib/src/erl_lint.erl index 7c40058dd8..d53a31db0d 100644 --- a/lib/stdlib/src/erl_lint.erl +++ b/lib/stdlib/src/erl_lint.erl @@ -92,6 +92,14 @@ value_option(Flag, Default, On, OnVal, Off, OffVal, Opts) -> :: dict:dict(ta(), line()) }). + +%% Are we outside or inside a catch or try/catch? +-type catch_scope() :: 'none' + | 'after_old_catch' + | 'after_try' + | 'wrong_part_of_try' + | 'try_catch'. + %% Define the lint state record. %% 'called' and 'exports' contain {Line, {Function, Arity}}, %% the other function collections contain {Function, Arity}. @@ -135,7 +143,9 @@ value_option(Flag, Default, On, OnVal, Off, OffVal, Opts) -> types = dict:new() %Type definitions :: dict:dict(ta(), #typeinfo{}), exp_types=gb_sets:empty() %Exported types - :: gb_sets:set(ta()) + :: gb_sets:set(ta()), + catch_scope = none %Inside/outside try or catch + :: catch_scope() }). -type lint_state() :: #lint{}. @@ -223,7 +233,15 @@ format_error({redefine_old_bif_import,{F,A}}) -> format_error({redefine_bif_import,{F,A}}) -> io_lib:format("import directive overrides auto-imported BIF ~w/~w~n" " - use \"-compile({no_auto_import,[~w/~w]}).\" to resolve name clash", [F,A,F,A]); - +format_error({get_stacktrace,wrong_part_of_try}) -> + "erlang:get_stacktrace/0 used in the wrong part of 'try' expression. " + "(Use it in the block between 'catch' and 'end'.)"; +format_error({get_stacktrace,after_old_catch}) -> + "erlang:get_stacktrace/0 used following an old-style 'catch' " + "may stop working in a future release. (Use it inside 'try'.)"; +format_error({get_stacktrace,after_try}) -> + "erlang:get_stacktrace/0 used following a 'try' expression " + "may stop working in a future release. (Use it inside 'try'.)"; format_error({deprecated, MFA, ReplacementMFA, Rel}) -> io_lib:format("~s is deprecated and will be removed in ~s; use ~s", [format_mfa(MFA), Rel, format_mfa(ReplacementMFA)]); @@ -568,7 +586,10 @@ start(File, Opts) -> false, Opts)}, {missing_spec_all, bool_option(warn_missing_spec_all, nowarn_missing_spec_all, - false, Opts)} + false, Opts)}, + {get_stacktrace, + bool_option(warn_get_stacktrace, nowarn_get_stacktrace, + true, Opts)} ], Enabled1 = [Category || {Category,true} <- Enabled0], Enabled = ordsets:from_list(Enabled1), @@ -1405,8 +1426,9 @@ call_function(Line, F, A, #lint{usage=Usage0,called=Cd,func=Func,file=File}=St) %% function(Line, Name, Arity, Clauses, State) -> State. function(Line, Name, Arity, Cs, St0) -> - St1 = define_function(Line, Name, Arity, St0#lint{func={Name,Arity}}), - clauses(Cs, St1). + St1 = St0#lint{func={Name,Arity},catch_scope=none}, + St2 = define_function(Line, Name, Arity, St1), + clauses(Cs, St2). -spec define_function(line(), atom(), arity(), lint_state()) -> lint_state(). @@ -2338,22 +2360,24 @@ expr({call,Line,F,As}, Vt, St0) -> expr({'try',Line,Es,Scs,Ccs,As}, Vt, St0) -> %% Currently, we don't allow any exports because later %% passes cannot handle exports in combination with 'after'. - {Evt0,St1} = exprs(Es, Vt, St0), + {Evt0,St1} = exprs(Es, Vt, St0#lint{catch_scope=wrong_part_of_try}), TryLine = {'try',Line}, Uvt = vtunsafe(TryLine, Evt0, Vt), Evt1 = vtupdate(Uvt, Evt0), - {Sccs,St2} = icrt_clauses(Scs++Ccs, TryLine, vtupdate(Evt1, Vt), St1), + {Sccs,St2} = try_clauses(Scs, Ccs, TryLine, + vtupdate(Evt1, Vt), St1), Rvt0 = Sccs, Rvt1 = vtupdate(vtunsafe(TryLine, Rvt0, Vt), Rvt0), Evt2 = vtmerge(Evt1, Rvt1), {Avt0,St} = exprs(As, vtupdate(Evt2, Vt), St2), Avt1 = vtupdate(vtunsafe(TryLine, Avt0, Vt), Avt0), Avt = vtmerge(Evt2, Avt1), - {Avt,St}; + {Avt,St#lint{catch_scope=after_try}}; expr({'catch',Line,E}, Vt, St0) -> %% No new variables added, flag new variables as unsafe. {Evt,St} = expr(E, Vt, St0), - {vtupdate(vtunsafe({'catch',Line}, Evt, Vt), Evt),St}; + {vtupdate(vtunsafe({'catch',Line}, Evt, Vt), Evt), + St#lint{catch_scope=after_old_catch}}; expr({match,_Line,P,E}, Vt, St0) -> {Evt,St1} = expr(E, Vt, St0), {Pvt,Bvt,St2} = pattern(P, vtupdate(Evt, Vt), St1), @@ -3173,6 +3197,17 @@ is_module_dialyzer_option(Option) -> error_handling,race_conditions,no_missing_calls, specdiffs,overspecs,underspecs,unknown]). +%% try_catch_clauses(Scs, Ccs, In, ImportVarTable, State) -> +%% {UpdVt,State}. + +try_clauses(Scs, Ccs, In, Vt, St0) -> + {Csvt0,St1} = icrt_clauses(Scs, Vt, St0), + St2 = St1#lint{catch_scope=try_catch}, + {Csvt1,St3} = icrt_clauses(Ccs, Vt, St2), + Csvt = Csvt0 ++ Csvt1, + UpdVt = icrt_export(Csvt, Vt, In, St3), + {UpdVt,St3}. + %% icrt_clauses(Clauses, In, ImportVarTable, State) -> %% {UpdVt,State}. @@ -3657,7 +3692,8 @@ has_wildcard_field([]) -> false. check_remote_function(Line, M, F, As, St0) -> St1 = deprecated_function(Line, M, F, As, St0), St2 = check_qlc_hrl(Line, M, F, As, St1), - format_function(Line, M, F, As, St2). + St3 = check_get_stacktrace(Line, M, F, As, St2), + format_function(Line, M, F, As, St3). %% check_qlc_hrl(Line, ModName, FuncName, [Arg], State) -> State %% Add warning if qlc:q/1,2 has been called but qlc.hrl has not @@ -3706,6 +3742,23 @@ deprecated_function(Line, M, F, As, St) -> St end. +check_get_stacktrace(Line, erlang, get_stacktrace, [], St) -> + case St of + #lint{catch_scope=none} -> + St; + #lint{catch_scope=try_catch} -> + St; + #lint{catch_scope=Scope} -> + case is_warn_enabled(get_stacktrace, St) of + false -> + St; + true -> + add_warning(Line, {get_stacktrace,Scope}, St) + end + end; +check_get_stacktrace(_, _, _, _, St) -> + St. + -dialyzer({no_match, deprecated_type/5}). deprecated_type(L, M, N, As, St) -> -- cgit v1.2.3 From 890bc8dddd62b5e14fd9bd38ea3317e47cc0b716 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Bj=C3=B6rn=20Gustavsson?= Date: Wed, 17 May 2017 12:38:09 +0200 Subject: escript: Pick up stacktrace a soon as possible It happens to work today, but it is potentially unsafe to call io:format/2 before calling erlang:get_stacktrace/0. Make the code safe by calling erlang:get_stacktrace/0 directly after catching the exception. --- lib/stdlib/src/escript.erl | 3 ++- 1 file changed, 2 insertions(+), 1 deletion(-) (limited to 'lib/stdlib/src') diff --git a/lib/stdlib/src/escript.erl b/lib/stdlib/src/escript.erl index 6e8f780f7c..f2629a47c2 100644 --- a/lib/stdlib/src/escript.erl +++ b/lib/stdlib/src/escript.erl @@ -284,8 +284,9 @@ start(EscriptOptions) -> io:format("escript: ~s\n", [Str]), my_halt(127); _:Reason -> + Stk = erlang:get_stacktrace(), io:format("escript: Internal error: ~p\n", [Reason]), - io:format("~p\n", [erlang:get_stacktrace()]), + io:format("~p\n", [Stk]), my_halt(127) end. -- cgit v1.2.3 From 652486205f6bfd32721f618c1191422182e77553 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Bj=C3=B6rn=20Gustavsson?= Date: Wed, 17 May 2017 13:06:36 +0200 Subject: proc_lib: Don't call erlang:get_stacktrace/0 twice proc_lib calls erlang:get_stacktrace/0 twice, which is unnecessary, and potentially unsafe since there are calls to many functions in between. Any of the calls could potentially cause and catch an exception, invalidating the stacktrace. Only call erlang:get_stacktrace/0 once, and pass the result to the second place where it is needed. --- lib/stdlib/src/proc_lib.erl | 27 ++++++++++++++------------- 1 file changed, 14 insertions(+), 13 deletions(-) (limited to 'lib/stdlib/src') diff --git a/lib/stdlib/src/proc_lib.erl b/lib/stdlib/src/proc_lib.erl index 363705b0f4..2219467a8d 100644 --- a/lib/stdlib/src/proc_lib.erl +++ b/lib/stdlib/src/proc_lib.erl @@ -264,12 +264,12 @@ exit_p(Class, Reason, Stacktrace) -> case get('$initial_call') of {M,F,A} when is_atom(M), is_atom(F), is_integer(A) -> MFA = {M,F,make_dummy_args(A, [])}, - crash_report(Class, Reason, MFA), + crash_report(Class, Reason, MFA, Stacktrace), erlang:raise(exit, exit_reason(Class, Reason, Stacktrace), Stacktrace); _ -> %% The process dictionary has been cleared or %% possibly modified. - crash_report(Class, Reason, []), + crash_report(Class, Reason, [], Stacktrace), erlang:raise(exit, exit_reason(Class, Reason, Stacktrace), Stacktrace) end. @@ -499,24 +499,25 @@ trans_init(M, F, A) when is_atom(M), is_atom(F) -> %% Generate a crash report. %% ----------------------------------------------------- -crash_report(exit, normal, _) -> ok; -crash_report(exit, shutdown, _) -> ok; -crash_report(exit, {shutdown,_}, _) -> ok; -crash_report(Class, Reason, StartF) -> - OwnReport = my_info(Class, Reason, StartF), +crash_report(exit, normal, _, _) -> ok; +crash_report(exit, shutdown, _, _) -> ok; +crash_report(exit, {shutdown,_}, _, _) -> ok; +crash_report(Class, Reason, StartF, Stacktrace) -> + OwnReport = my_info(Class, Reason, StartF, Stacktrace), LinkReport = linked_info(self()), Rep = [OwnReport,LinkReport], error_logger:error_report(crash_report, Rep). -my_info(Class, Reason, []) -> - my_info_1(Class, Reason); -my_info(Class, Reason, StartF) -> - [{initial_call, StartF}|my_info_1(Class, Reason)]. +my_info(Class, Reason, [], Stacktrace) -> + my_info_1(Class, Reason, Stacktrace); +my_info(Class, Reason, StartF, Stacktrace) -> + [{initial_call, StartF}| + my_info_1(Class, Reason, Stacktrace)]. -my_info_1(Class, Reason) -> +my_info_1(Class, Reason, Stacktrace) -> [{pid, self()}, get_process_info(self(), registered_name), - {error_info, {Class,Reason,erlang:get_stacktrace()}}, + {error_info, {Class,Reason,Stacktrace}}, get_ancestors(self()), get_process_info(self(), messages), get_process_info(self(), links), -- cgit v1.2.3 From b57e89092409193457aa2ad026c895d5559d428d Mon Sep 17 00:00:00 2001 From: Hans Bolinder Date: Mon, 15 May 2017 14:16:52 +0200 Subject: stdlib: Add io_lib:limit_term/2 The term returned by io_lib:limit_term(Term, Depth) should return the same string if substituted for Term in io_lib:format("~P", [Term, Depth]) or io_lib:format("~W", [Term, Depth]). --- lib/stdlib/src/io_lib.erl | 115 ++++++++++++++++++++++++++++++++++++++++++++++ 1 file changed, 115 insertions(+) (limited to 'lib/stdlib/src') diff --git a/lib/stdlib/src/io_lib.erl b/lib/stdlib/src/io_lib.erl index 5ed2f4d888..9d447418f8 100644 --- a/lib/stdlib/src/io_lib.erl +++ b/lib/stdlib/src/io_lib.erl @@ -84,6 +84,8 @@ -export([write_unicode_string/1, write_unicode_char/1, deep_unicode_char_list/1]). +-export([limit_term/2]). + -export_type([chars/0, latin1_string/0, continuation/0, fread_error/0, fread_item/0, format_spec/0]). @@ -911,3 +913,116 @@ binrev(L) -> binrev(L, T) -> list_to_binary(lists:reverse(L, T)). + +-spec limit_term(term(), non_neg_integer()) -> term(). + +%% The intention is to mimic the depth limitation of io_lib:write() +%% and io_lib_pretty:print(). The leaves ('...') should never be +%% seen when printed with the same depth. Bitstrings are never +%% truncated, which is OK as long as they are not sent to other nodes. +limit_term(Term, Depth) -> + try test_limit(Term, Depth) of + ok -> Term + catch + throw:limit -> + limit(Term, Depth) + end. + +limit(_, 0) -> '...'; +limit([H|T]=L, D) -> + if + D =:= 1 -> '...'; + true -> + case printable_list(L) of + true -> L; + false -> + [limit(H, D-1)|limit_tail(T, D-1)] + end + end; +limit(Term, D) when is_map(Term) -> + limit_map(Term, D); +limit({}=T, _D) -> T; +limit(T, D) when is_tuple(T) -> + if + D =:= 1 -> '...'; + true -> + list_to_tuple([limit(element(1, T), D-1)| + limit_tail(tl(tuple_to_list(T)), D-1)]) + end; +limit(<<_/bitstring>>=Term, D) -> limit_bitstring(Term, D); +limit(Term, _D) -> Term. + +limit_tail([], _D) -> []; +limit_tail(_, 1) -> ['...']; +limit_tail([H|T], D) -> + [limit(H, D-1)|limit_tail(T, D-1)]; +limit_tail(Other, D) -> + limit(Other, D-1). + +%% Cannot limit maps properly since there is no guarantee that +%% maps:from_list() creates a map with the same internal ordering of +%% the selected associations as in Map. +limit_map(Map, D) -> + maps:from_list(erts_internal:maps_to_list(Map, D)). +%% maps:from_list(limit_map_body(erts_internal:maps_to_list(Map, D), D)). + +%% limit_map_body(_, 0) -> [{'...', '...'}]; +%% limit_map_body([], _) -> []; +%% limit_map_body([{K,V}], D) -> [limit_map_assoc(K, V, D)]; +%% limit_map_body([{K,V}|KVs], D) -> +%% [limit_map_assoc(K, V, D) | limit_map_body(KVs, D-1)]. + +%% limit_map_assoc(K, V, D) -> +%% {limit(K, D-1), limit(V, D-1)}. + +limit_bitstring(B, _D) -> B. %% Keeps all printable binaries. + +test_limit(_, 0) -> throw(limit); +test_limit([H|T]=L, D) when is_integer(D) -> + if + D =:= 1 -> throw(limit); + true -> + case printable_list(L) of + true -> ok; + false -> + test_limit(H, D-1), + test_limit_tail(T, D-1) + end + end; +test_limit(Term, D) when is_map(Term) -> + test_limit_map(Term, D); +test_limit({}, _D) -> ok; +test_limit(T, D) when is_tuple(T) -> + test_limit_tuple(T, 1, tuple_size(T), D); +test_limit(<<_/bitstring>>=Term, D) -> test_limit_bitstring(Term, D); +test_limit(_Term, _D) -> ok. + +test_limit_tail([], _D) -> ok; +test_limit_tail(_, 1) -> throw(limit); +test_limit_tail([H|T], D) -> + test_limit(H, D-1), + test_limit_tail(T, D-1); +test_limit_tail(Other, D) -> + test_limit(Other, D-1). + +test_limit_tuple(_T, I, Sz, _D) when I > Sz -> ok; +test_limit_tuple(_, _, _, 1) -> throw(limit); +test_limit_tuple(T, I, Sz, D) -> + test_limit(element(I, T), D-1), + test_limit_tuple(T, I+1, Sz, D-1). + +test_limit_map(_Map, _D) -> ok. +%% test_limit_map_body(erts_internal:maps_to_list(Map, D), D). + +%% test_limit_map_body(_, 0) -> throw(limit); +%% test_limit_map_body([], _) -> ok; +%% test_limit_map_body([{K,V}], D) -> test_limit_map_assoc(K, V, D); +%% test_limit_map_body([{K,V}|KVs], D) -> +%% test_limit_map_assoc(K, V, D), +%% test_limit_map_body(KVs, D-1). + +%% test_limit_map_assoc(K, V, D) -> +%% test_limit(K, D-1), +%% test_limit(V, D-1). + +test_limit_bitstring(_, _) -> ok. -- cgit v1.2.3 From a0659634674df165482487495f8d10c3d755c60c Mon Sep 17 00:00:00 2001 From: Hans Bolinder Date: Mon, 15 May 2017 14:21:12 +0200 Subject: stdlib: Limit the size of gen_server's error events The state of the gen_server is limited in error events before exiting (if the Kernel variable error_logger_format_depth is set). An alternative is to let the error_logger limit all messages (error_msg, format, warning_msg, info_msg), which would not limit reports and also add a smallish overhead to event logging. It is not decided if the alternative is to be implemented. --- lib/stdlib/src/gen_server.erl | 13 ++++++------- 1 file changed, 6 insertions(+), 7 deletions(-) (limited to 'lib/stdlib/src') diff --git a/lib/stdlib/src/gen_server.erl b/lib/stdlib/src/gen_server.erl index ba0a7ae8e5..460ea0ed16 100644 --- a/lib/stdlib/src/gen_server.erl +++ b/lib/stdlib/src/gen_server.erl @@ -107,8 +107,6 @@ %% Internal exports -export([init_it/6]). --import(error_logger, [format/2]). - %%%========================================================================= %%% API %%%========================================================================= @@ -864,11 +862,12 @@ error_info(Reason, Name, From, Msg, State, Debug) -> Reason end, {ClientFmt, ClientArgs} = client_stacktrace(From), - format("** Generic server ~p terminating \n" - "** Last message in was ~p~n" - "** When Server state == ~p~n" - "** Reason for termination == ~n** ~p~n" ++ ClientFmt, - [Name, Msg, State, Reason1] ++ ClientArgs), + LimitedState = error_logger:limit_term(State), + error_logger:format("** Generic server ~p terminating \n" + "** Last message in was ~p~n" + "** When Server state == ~p~n" + "** Reason for termination == ~n** ~p~n" ++ ClientFmt, + [Name, Msg, LimitedState, Reason1] ++ ClientArgs), sys:print_log(Debug), ok. client_stacktrace(undefined) -> -- cgit v1.2.3 From 86a74bfaefd570245740624d85659efa8821765b Mon Sep 17 00:00:00 2001 From: Hans Bolinder Date: Mon, 15 May 2017 14:33:27 +0200 Subject: stdlib: Limit the size of proc_lib's crash reports The size of the message queue and the dictionary is limited in crash reports. To avoid creating the potentially huge list of messages of the message queue, messages are received (if the Kernel variable error_logger_format_depth is set). The tag 'message_queue_len' has been added to the crash report. --- lib/stdlib/src/proc_lib.erl | 111 ++++++++++++++++++++++++++++++++++---------- 1 file changed, 86 insertions(+), 25 deletions(-) (limited to 'lib/stdlib/src') diff --git a/lib/stdlib/src/proc_lib.erl b/lib/stdlib/src/proc_lib.erl index 2219467a8d..b2856be805 100644 --- a/lib/stdlib/src/proc_lib.erl +++ b/lib/stdlib/src/proc_lib.erl @@ -1,7 +1,7 @@ %% %% %CopyrightBegin% %% -%% Copyright Ericsson AB 1996-2016. All Rights Reserved. +%% Copyright Ericsson AB 1996-2017. All Rights Reserved. %% %% Licensed under the Apache License, Version 2.0 (the "License"); %% you may not use this file except in compliance with the License. @@ -519,7 +519,8 @@ my_info_1(Class, Reason, Stacktrace) -> get_process_info(self(), registered_name), {error_info, {Class,Reason,Stacktrace}}, get_ancestors(self()), - get_process_info(self(), messages), + get_process_info(self(), message_queue_len), + get_messages(self()), get_process_info(self(), links), get_cleaned_dictionary(self()), get_process_info(self(), trap_exit), @@ -539,12 +540,56 @@ get_ancestors(Pid) -> {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 +%% control characters P and W takes precedence over the depth set by +%% application variable error_logger_format_depth). However, it is +%% assumed that all report handlers call proc_lib:format(). +get_messages(Pid) -> + Messages = get_process_messages(Pid), + {messages, error_logger:limit_term(Messages)}. + +get_process_messages(Pid) -> + case get_depth() of + unlimited -> + {messages, Messages} = get_process_info(Pid, messages), + Messages; + Depth -> + %% If there are more messages than Depth, garbage + %% collection can sometimes be avoided by collecting just + %% enough messages for the output. It is assumed the + %% process is about to die anyway. + receive_messages(Depth) + end. + +get_depth() -> + case application:get_env(kernel, error_logger_format_depth) of + {ok, Depth} when is_integer(Depth) -> + max(10, Depth); + undefined -> + unlimited + end. + +receive_messages(0) -> []; +receive_messages(N) -> + receive + M -> + [M|receive_messages(N - 1)] + after 0 -> + [] + end. + get_cleaned_dictionary(Pid) -> case get_process_info(Pid,dictionary) of - {dictionary,Dict} -> {dictionary,clean_dict(Dict)}; + {dictionary,Dict} -> {dictionary,cleaned_dict(Dict)}; _ -> {dictionary,[]} end. +cleaned_dict(Dict) -> + CleanDict = clean_dict(Dict), + error_logger:limit_term(CleanDict). + clean_dict([{'$ancestors',_}|Dict]) -> clean_dict(Dict); clean_dict([{'$initial_call',_}|Dict]) -> @@ -582,15 +627,18 @@ make_neighbour_reports1([P|Ps]) -> 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, messages), + get_process_info(Pid, message_queue_len), + %% get_messages(Pid), get_process_info(Pid, links), - get_cleaned_dictionary(Pid), + %% get_cleaned_dictionary(Pid), get_process_info(Pid, trap_exit), get_process_info(Pid, status), get_process_info(Pid, heap_size), @@ -722,24 +770,37 @@ format(CrashReport, Encoding) -> format([OwnReport,LinkReport], Encoding, Depth) -> Extra = {Encoding,Depth}, - OwnFormat = format_report(OwnReport, Extra), - LinkFormat = format_report(LinkReport, Extra), + MyIndent = " ", + OwnFormat = format_report(OwnReport, MyIndent, Extra), + LinkFormat = format_link_report(LinkReport, MyIndent, Extra), Str = io_lib:format(" crasher:~n~ts neighbours:~n~ts", [OwnFormat, LinkFormat]), lists:flatten(Str). -format_report(Rep, Extra) when is_list(Rep) -> - format_rep(Rep, Extra); -format_report(Rep, {Enc,_}) -> - io_lib:format("~"++modifier(Enc)++"p~n", [Rep]). - -format_rep([{initial_call,InitialCall}|Rep], {_Enc,Depth}=Extra) -> - [format_mfa(InitialCall, Depth)|format_rep(Rep, Extra)]; -format_rep([{error_info,{Class,Reason,StackTrace}}|Rep], Extra) -> - [format_exception(Class, Reason, StackTrace, Extra)|format_rep(Rep, Extra)]; -format_rep([{Tag,Data}|Rep], Extra) -> - [format_tag(Tag, Data, Extra)|format_rep(Rep, Extra)]; -format_rep(_, _Extra) -> +format_link_report([Link|Reps], Indent, Extra) -> + Rep = case Link of + {neighbour,Rep0} -> Rep0; + _ -> Link + end, + LinkIndent = [" ",Indent], + [Indent,"neighbour:\n",format_report(Rep, LinkIndent, Extra)| + format_link_report(Reps, Indent, Extra)]; +format_link_report([], _, _) -> + []. + +format_report(Rep, Indent, Extra) when is_list(Rep) -> + format_rep(Rep, Indent, Extra); +format_report(Rep, Indent, {Enc,Depth}) -> + io_lib:format("~s~"++modifier(Enc)++"P~n", [Indent, Rep, Depth]). + +format_rep([{initial_call,InitialCall}|Rep], Indent, Extra) -> + [format_mfa(Indent, InitialCall, Extra)|format_rep(Rep, Indent, Extra)]; +format_rep([{error_info,{Class,Reason,StackTrace}}|Rep], Indent, Extra) -> + [format_exception(Class, Reason, StackTrace, Extra)| + format_rep(Rep, Indent, Extra)]; +format_rep([{Tag,Data}|Rep], Indent, Extra) -> + [format_tag(Indent, Tag, Data, Extra)|format_rep(Rep, Indent, Extra)]; +format_rep(_, _, _Extra) -> []. format_exception(Class, Reason, StackTrace, {Enc,_}=Extra) -> @@ -750,14 +811,14 @@ format_exception(Class, Reason, StackTrace, {Enc,_}=Extra) -> [EI, lib:format_exception(1+length(EI), Class, Reason, StackTrace, StackFun, PF, Enc), "\n"]. -format_mfa({M,F,Args}=StartF, Depth) -> +format_mfa(Indent, {M,F,Args}=StartF, Extra) -> try A = length(Args), - [" initial call: ",atom_to_list(M),$:,atom_to_list(F),$/, + [Indent,"initial call: ",atom_to_list(M),$:,atom_to_list(F),$/, integer_to_list(A),"\n"] catch error:_ -> - format_tag(initial_call, StartF, Depth) + format_tag(Indent, initial_call, StartF, Extra) end. pp_fun({Enc,Depth}) -> @@ -770,12 +831,12 @@ pp_fun({Enc,Depth}) -> io_lib:format("~." ++ integer_to_list(I) ++ P, [Term|Tl]) end. -format_tag(Tag, Data, {_Enc,Depth}) -> +format_tag(Indent, Tag, Data, {_Enc,Depth}) -> case Depth of unlimited -> - io_lib:format(" ~p: ~80.18p~n", [Tag, Data]); + io_lib:format("~s~p: ~80.18p~n", [Indent, Tag, Data]); _ -> - io_lib:format(" ~p: ~80.18P~n", [Tag, Data, Depth]) + io_lib:format("~s~p: ~80.18P~n", [Indent, Tag, Data, Depth]) end. modifier(latin1) -> ""; -- cgit v1.2.3 From a99b0a2a570e7429b05f3ce424880744ee3a8814 Mon Sep 17 00:00:00 2001 From: Hans Bolinder Date: Wed, 17 May 2017 16:16:58 +0200 Subject: kernel: Introcude error_logger:get_format_depth() --- lib/stdlib/src/error_logger_file_h.erl | 12 ++---------- lib/stdlib/src/error_logger_tty_h.erl | 14 +++----------- lib/stdlib/src/gen_server.erl | 2 +- lib/stdlib/src/proc_lib.erl | 20 +++++++------------- 4 files changed, 13 insertions(+), 35 deletions(-) (limited to 'lib/stdlib/src') diff --git a/lib/stdlib/src/error_logger_file_h.erl b/lib/stdlib/src/error_logger_file_h.erl index 0b262de3ab..76f89841b9 100644 --- a/lib/stdlib/src/error_logger_file_h.erl +++ b/lib/stdlib/src/error_logger_file_h.erl @@ -1,7 +1,7 @@ %% %% %CopyrightBegin% %% -%% Copyright Ericsson AB 1996-2016. All Rights Reserved. +%% Copyright Ericsson AB 1996-2017. All Rights Reserved. %% %% Licensed under the Apache License, Version 2.0 (the "License"); %% you may not use this file except in compliance with the License. @@ -57,7 +57,7 @@ init(File, PrevHandler) -> process_flag(trap_exit, true), case file:open(File, [write]) of {ok,Fd} -> - Depth = get_depth(), + Depth = error_logger:get_format_depth(), State = #st{fd=Fd,filename=File,prev_handler=PrevHandler, depth=Depth}, {ok, State}; @@ -65,14 +65,6 @@ init(File, PrevHandler) -> Error end. -get_depth() -> - case application:get_env(kernel, error_logger_format_depth) of - {ok, Depth} when is_integer(Depth) -> - max(10, Depth); - undefined -> - unlimited - end. - handle_event({_Type, GL, _Msg}, State) when node(GL) =/= node() -> {ok, State}; handle_event(Event, State) -> diff --git a/lib/stdlib/src/error_logger_tty_h.erl b/lib/stdlib/src/error_logger_tty_h.erl index 2f2fd65252..8f0d7b0362 100644 --- a/lib/stdlib/src/error_logger_tty_h.erl +++ b/lib/stdlib/src/error_logger_tty_h.erl @@ -1,7 +1,7 @@ %% %% %CopyrightBegin% %% -%% Copyright Ericsson AB 1996-2016. All Rights Reserved. +%% Copyright Ericsson AB 1996-2017. All Rights Reserved. %% %% Licensed under the Apache License, Version 2.0 (the "License"); %% you may not use this file except in compliance with the License. @@ -44,7 +44,7 @@ %% This one is used when we takeover from the simple error_logger. init({[], {error_logger, Buf}}) -> User = set_group_leader(), - Depth = get_depth(), + Depth = error_logger:get_format_depth(), State = #st{user=User,prev_handler=error_logger,depth=Depth}, write_events(State, Buf), {ok, State}; @@ -56,17 +56,9 @@ init({[], {error_logger_tty_h, PrevHandler}}) -> %% This one is used when we are started directly. init([]) -> User = set_group_leader(), - Depth = get_depth(), + Depth = error_logger:get_format_depth(), {ok, #st{user=User,prev_handler=[],depth=Depth}}. -get_depth() -> - case application:get_env(kernel, error_logger_format_depth) of - {ok, Depth} when is_integer(Depth) -> - max(10, Depth); - undefined -> - unlimited - end. - handle_event({_Type, GL, _Msg}, State) when node(GL) =/= node() -> {ok, State}; handle_event(Event, State) -> diff --git a/lib/stdlib/src/gen_server.erl b/lib/stdlib/src/gen_server.erl index 460ea0ed16..9f6568473d 100644 --- a/lib/stdlib/src/gen_server.erl +++ b/lib/stdlib/src/gen_server.erl @@ -859,7 +859,7 @@ error_info(Reason, Name, From, Msg, State, Debug) -> end end; _ -> - Reason + error_logger:limit_term(Reason) end, {ClientFmt, ClientArgs} = client_stacktrace(From), LimitedState = error_logger:limit_term(State), diff --git a/lib/stdlib/src/proc_lib.erl b/lib/stdlib/src/proc_lib.erl index b2856be805..3fa54cd0d5 100644 --- a/lib/stdlib/src/proc_lib.erl +++ b/lib/stdlib/src/proc_lib.erl @@ -551,26 +551,19 @@ get_messages(Pid) -> {messages, error_logger:limit_term(Messages)}. get_process_messages(Pid) -> - case get_depth() of - unlimited -> + Depth = error_logger:get_format_depth(), + case Pid =/= self() orelse Depth =:= unlimited of + true -> {messages, Messages} = get_process_info(Pid, messages), Messages; - Depth -> + false -> %% If there are more messages than Depth, garbage %% collection can sometimes be avoided by collecting just - %% enough messages for the output. It is assumed the + %% enough messages for the crash report. It is assumed the %% process is about to die anyway. receive_messages(Depth) end. -get_depth() -> - case application:get_env(kernel, error_logger_format_depth) of - {ok, Depth} when is_integer(Depth) -> - max(10, Depth); - undefined -> - unlimited - end. - receive_messages(0) -> []; receive_messages(N) -> receive @@ -643,7 +636,8 @@ make_neighbour_report(Pid) -> 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, reductions), + get_process_info(Pid, current_stacktrace) ]. get_initial_call(Pid) -> -- cgit v1.2.3 From 0b1fe37dbcfaad9b28ef529aa4f7b4be60ec5da8 Mon Sep 17 00:00:00 2001 From: Hans Bolinder Date: Thu, 18 May 2017 10:16:52 +0200 Subject: stdlib: Limit the size of gen_statem's error events The postponed events, the user state and data, and the error reason are all limited in error events (if the Kernel variable error_logger_format_depth is set). --- lib/stdlib/src/gen_statem.erl | 8 +++++--- 1 file changed, 5 insertions(+), 3 deletions(-) (limited to 'lib/stdlib/src') diff --git a/lib/stdlib/src/gen_statem.erl b/lib/stdlib/src/gen_statem.erl index 86109f04b4..b5e9da1e66 100644 --- a/lib/stdlib/src/gen_statem.erl +++ b/lib/stdlib/src/gen_statem.erl @@ -1722,6 +1722,8 @@ error_info( end; _ -> {Reason,Stacktrace} end, + [LimitedP, LimitedFmtData, LimitedFixedReason] = + [error_logger:limit_term(D) || D <- [P, FmtData, FixedReason]], CBMode = case StateEnter of true -> @@ -1755,8 +1757,8 @@ error_info( [] -> []; [Event|_] -> [Event] end] ++ - [FmtData, - Class,FixedReason, + [LimitedFmtData, + Class,LimitedFixedReason, CBMode] ++ case Q of [_|[_|_] = Events] -> [Events]; @@ -1764,7 +1766,7 @@ error_info( end ++ case P of [] -> []; - _ -> [P] + _ -> [LimitedP] end ++ case FixedStacktrace of [] -> []; -- cgit v1.2.3