aboutsummaryrefslogtreecommitdiffstats
path: root/lib/stdlib/src/proc_lib.erl
diff options
context:
space:
mode:
Diffstat (limited to 'lib/stdlib/src/proc_lib.erl')
-rw-r--r--lib/stdlib/src/proc_lib.erl175
1 files changed, 108 insertions, 67 deletions
diff --git a/lib/stdlib/src/proc_lib.erl b/lib/stdlib/src/proc_lib.erl
index 89a840be2d..cfbaf8b242 100644
--- a/lib/stdlib/src/proc_lib.erl
+++ b/lib/stdlib/src/proc_lib.erl
@@ -30,7 +30,7 @@
start/3, start/4, start/5, start_link/3, start_link/4, start_link/5,
hibernate/3,
init_ack/1, init_ack/2,
- init_p/3,init_p/5,format/1,format/2,format/3,report_cb/1,
+ init_p/3,init_p/5,format/1,format/2,format/3,report_cb/2,
initial_call/1,
translate_initial_call/1,
stop/1, stop/3]).
@@ -509,7 +509,7 @@ crash_report(Class, Reason, StartF, Stacktrace) ->
report=>[my_info(Class, Reason, StartF, Stacktrace),
linked_info(self())]},
#{domain=>[otp,sasl],
- report_cb=>fun proc_lib:report_cb/1,
+ report_cb=>fun proc_lib:report_cb/2,
logger_formatter=>#{title=>"CRASH REPORT"},
error_logger=>#{tag=>error_report,type=>crash_report}}).
@@ -750,14 +750,16 @@ check(Res) -> Res.
%%% Format a generated crash info structure.
%%% -----------------------------------------------------------
--spec report_cb(CrashReport) -> {Format,Args} when
- CrashReport :: #{label=>{proc_lib,crash},report=>[term()]},
- Format :: io:format(),
- Args :: [term()].
-report_cb(#{label:={proc_lib,crash},
- report:=CrashReport}) ->
- Depth = error_logger:get_format_depth(),
- get_format_and_args(CrashReport, utf8, Depth).
+-spec report_cb(CrashReport,FormatOpts) -> unicode:chardata() when
+ CrashReport :: #{label => {proc_lib,crash},
+ report => [term()]},
+ FormatOpts :: logger:report_cb_config().
+report_cb(#{label:={proc_lib,crash}, report:=CrashReport}, Extra) ->
+ Default = #{chars_limit => unlimited,
+ depth => unlimited,
+ single_line => false,
+ encoding => utf8},
+ do_format(CrashReport, maps:merge(Default,Extra)).
-spec format(CrashReport) -> string() when
CrashReport :: [term()].
@@ -777,84 +779,121 @@ format(CrashReport, Encoding) ->
Depth :: unlimited | pos_integer().
format(CrashReport, Encoding, Depth) ->
- {F,A} = get_format_and_args(CrashReport, Encoding, Depth),
- lists:flatten(io_lib:format(F,A)).
-
-get_format_and_args([OwnReport,LinkReport], Encoding, Depth) ->
- Extra = {Encoding,Depth},
- MyIndent = " ",
- {OwnFormat,OwnArgs} = format_report(OwnReport, MyIndent, Extra, [], []),
- {LinkFormat,LinkArgs} = format_link_report(LinkReport, MyIndent, Extra, [], []),
- {" crasher:~n"++OwnFormat++" neighbours:~n"++LinkFormat,OwnArgs++LinkArgs}.
-
-format_link_report([], _Indent, _Extra, Format, Args) ->
- {lists:flatten(lists:reverse(Format)),lists:append(lists:reverse(Args))};
-format_link_report([Link|Reps], Indent, Extra, Format, Args) ->
+ do_format(CrashReport, #{chars_limit => unlimited,
+ depth => Depth,
+ encoding => Encoding,
+ single_line => false}).
+
+do_format([OwnReport,LinkReport], #{single_line:=Single}=Extra) ->
+ Indent = if Single -> "";
+ true -> " "
+ end,
+ MyIndent = Indent ++ Indent,
+ Sep = nl(Single,"; "),
+ OwnFormat = format_report(OwnReport, MyIndent, Extra),
+ LinkFormat = lists:join(Sep,format_link_report(LinkReport, MyIndent, Extra)),
+ Nl = nl(Single," "),
+ Str = io_lib:format("~scrasher:"++Nl++"~ts"++Sep++"~sneighbours:"++Nl++"~ts",
+ [Indent,OwnFormat,Indent,LinkFormat]),
+ lists:flatten(Str).
+
+format_link_report([Link|Reps], Indent0, #{single_line:=Single}=Extra) ->
Rep = case Link of
{neighbour,Rep0} -> Rep0;
_ -> Link
end,
+ Indent = if Single -> "";
+ true -> Indent0
+ end,
LinkIndent = [" ",Indent],
- {LinkFormat,LinkArgs} = format_report(Rep, LinkIndent, Extra, [], []),
- F = "~sneighbour:\n"++LinkFormat,
- A = [Indent|LinkArgs],
- format_link_report(Reps, Indent, Extra, [F|Format], [A|Args]);
-format_link_report(Rep, Indent, Extra, Format, Args) ->
- {F,A} = format_report(Rep, Indent, Extra, [], []),
- format_link_report([], Indent, Extra, [F|Format],[A|Args]).
-
-format_report([], _Indent, _Extra, Format, Args) ->
- {lists:flatten(lists:reverse(Format)),lists:append(lists:reverse(Args))};
-format_report([Rep|Reps], Indent, Extra, Format, Args) ->
- {F,A} = format_rep(Rep, Indent, Extra),
- format_report(Reps, Indent, Extra, [F|Format], [A|Args]);
-format_report(Rep, Indent, {Enc,unlimited}=Extra, Format, Args) ->
- {F,A} = {"~s~"++modifier(Enc)++"p~n", [Indent, Rep]},
- format_report([], Indent, Extra, [F|Format], [A|Args]);
-format_report(Rep, Indent, {Enc,Depth}=Extra, Format, Args) ->
- {F,A} = {"~s~"++modifier(Enc)++"P~n", [Indent, Rep, Depth]},
- format_report([], Indent, Extra, [F|Format], [A|Args]).
-
-format_rep({initial_call,InitialCall}, Indent, Extra) ->
- format_mfa(Indent, InitialCall, Extra);
-format_rep({error_info,{Class,Reason,StackTrace}}, _Indent, Extra) ->
- {lists:flatten(format_exception(Class, Reason, StackTrace, Extra)),[]};
-format_rep({Tag,Data}, Indent, Extra) ->
- format_tag(Indent, Tag, Data, Extra).
-
-format_mfa(Indent, {M,F,Args}=StartF, {Enc,_}=Extra) ->
+ [[Indent,"neighbour:",nl(Single," "),format_report(Rep, LinkIndent, Extra)]|
+ format_link_report(Reps, Indent, Extra)];
+format_link_report(Rep, Indent, Extra) ->
+ format_report(Rep, Indent, Extra).
+
+format_report(Rep, Indent, #{single_line:=Single}=Extra) when is_list(Rep) ->
+ lists:join(nl(Single,", "),format_rep(Rep, Indent, Extra));
+format_report(Rep, Indent0, #{encoding:=Enc,depth:=Depth,
+ chars_limit:=Limit,single_line:=Single}) ->
+ {P,Tl} = p(Enc,Depth),
+ {Indent,Width} = if Single -> {"","0"};
+ true -> {Indent0,""}
+ end,
+ Opts = if is_integer(Limit) -> [{chars_limit,Limit}];
+ true -> []
+ end,
+ io_lib:format("~s~"++Width++P, [Indent, Rep | Tl], Opts).
+
+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,
+ #{encoding:=Enc,depth:=Depth,chars_limit:=Limit,
+ single_line:=Single}=Extra) ->
+ PF = pp_fun(Extra),
+ StackFun = fun(M, _F, _A) -> (M =:= erl_eval) or (M =:= ?MODULE) end,
+ if Single ->
+ {P,Tl} = p(Enc,Depth),
+ Opts = if is_integer(Limit) -> [{chars_limit,Limit}];
+ true -> []
+ end,
+ [atom_to_list(Class), ": ",
+ io_lib:format("~0"++P,[{Reason,StackTrace}|Tl],Opts)];
+ true ->
+ EI = " ",
+ [EI, erl_error:format_exception(1+length(EI), Class, Reason,
+ StackTrace, StackFun, PF, Enc)]
+ end.
+
+format_mfa(Indent0, {M,F,Args}=StartF, #{encoding:=Enc,single_line:=Single}=Extra) ->
+ Indent = if Single -> "";
+ true -> Indent0
+ end,
try
A = length(Args),
- {lists:flatten([Indent,"initial call: ",atom_to_list(M),
- $:,to_string(F, Enc),$/,integer_to_list(A),"\n"]),[]}
+ [Indent,"initial call: ",atom_to_list(M),$:,to_string(F, Enc),$/,
+ integer_to_list(A)]
catch
error:_ ->
format_tag(Indent, initial_call, StartF, Extra)
end.
-format_tag(Indent, Tag, Data, {Enc,Depth}) ->
- {P,Tl} = p(Enc, Depth),
- {"~s~p: ~80.18" ++ P ++ "\n", [Indent, Tag, Data|Tl]}.
-
-format_exception(Class, Reason, StackTrace, {Enc,_}=Extra) ->
- PF = pp_fun(Extra),
- StackFun = fun(M, _F, _A) -> (M =:= erl_eval) or (M =:= ?MODULE) end,
- %% EI = " exception: ",
- EI = " ",
- [EI, erl_error:format_exception(1+length(EI), Class, Reason,
- StackTrace, StackFun, PF, Enc), "\n"].
-
to_string(A, latin1) ->
io_lib:write_atom_as_latin1(A);
to_string(A, _) ->
io_lib:write_atom(A).
-pp_fun({Enc,Depth}) ->
+pp_fun(#{encoding:=Enc,depth:=Depth,chars_limit:=Limit,single_line:=Single}) ->
{P,Tl} = p(Enc, Depth),
+ Width = if Single -> "0";
+ true -> ""
+ end,
+ Opts = if is_integer(Limit) -> [{chars_limit,Limit}];
+ true -> []
+ end,
fun(Term, I) ->
- io_lib:format("~." ++ integer_to_list(I) ++ P, [Term|Tl])
+ io_lib:format("~" ++ Width ++ "." ++ integer_to_list(I) ++ P,
+ [Term|Tl], Opts)
end.
+format_tag(Indent0, Tag, Data, #{encoding:=Enc,depth:=Depth,chars_limit:=Limit,single_line:=Single}) ->
+ {P,Tl} = p(Enc, Depth),
+ {Indent,Width} = if Single -> {"","0"};
+ true -> {Indent0,""}
+ end,
+ Opts = if is_integer(Limit) -> [{chars_limit,Limit}];
+ true -> []
+ end,
+ io_lib:format("~s~" ++ Width ++ "p: ~" ++ Width ++ ".18" ++ P,
+ [Indent, Tag, Data|Tl], Opts).
+
p(Encoding, Depth) ->
{Letter, Tl} = case Depth of
unlimited -> {"p", []};
@@ -866,6 +905,8 @@ p(Encoding, Depth) ->
modifier(latin1) -> "";
modifier(_) -> "t".
+nl(true,Else) -> Else;
+nl(false,_) -> "\n".
%%% -----------------------------------------------------------
%%% Stop a process and wait for it to terminate