diff options
Diffstat (limited to 'lib/stdlib/src')
| -rw-r--r-- | lib/stdlib/src/error_logger_file_h.erl | 218 | ||||
| -rw-r--r-- | lib/stdlib/src/error_logger_tty_h.erl | 237 | ||||
| -rw-r--r-- | lib/stdlib/src/proc_lib.erl | 65 | 
3 files changed, 284 insertions, 236 deletions
| diff --git a/lib/stdlib/src/error_logger_file_h.erl b/lib/stdlib/src/error_logger_file_h.erl index a7f3615972..48c471924e 100644 --- a/lib/stdlib/src/error_logger_file_h.erl +++ b/lib/stdlib/src/error_logger_file_h.erl @@ -24,24 +24,28 @@  %%%  %%% A handler that can be connected to the error_logger -%%% event handler. -%%% Writes all events formatted to file. -%%%   Handles events tagged error, emulator and info. +%%% event handler. Writes all events formatted to file.  %%%  %%% It can only be started from error_logger:swap_handler({logfile, File}) -%%% or error_logger:logfile(File) +%%% or error_logger:logfile(File).  %%%  -export([init/1,  	 handle_event/2, handle_call/2, handle_info/2,  	 terminate/2, code_change/3]). +-record(st, +	{fd, +	 filename, +	 prev_handler, +	 depth=unlimited :: 'unlimited' | non_neg_integer()}). +  %% This one is used when we takeover from the simple error_logger.  init({File, {error_logger, Buf}}) ->      case init(File, error_logger) of -	{ok, {Fd, File, PrevHandler}} -> -	    write_events(Fd, Buf), -	    {ok, {Fd, File, PrevHandler}}; +	{ok, State} -> +	    write_events(State, Buf), +	    {ok, State};  	Error ->  	    Error      end; @@ -53,38 +57,40 @@ init(File, PrevHandler) ->      process_flag(trap_exit, true),      case file:open(File, [write]) of  	{ok,Fd} -> -	    {ok, {Fd, File, PrevHandler}}; +	    Depth = get_depth(), +	    State = #st{fd=Fd,filename=File,prev_handler=PrevHandler, +			depth=Depth}, +	    {ok, State};  	Error ->  	    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, {Fd, File, PrevHandler}) -> -    write_event(Fd, tag_event(Event)), -    {ok, {Fd, File, PrevHandler}}; -handle_event(_, State) -> +handle_event(Event, State) -> +    write_event(State, Event),      {ok, State}. -handle_info({'EXIT', Fd, _Reason}, {Fd, _File, PrevHandler}) -> +handle_info({'EXIT', Fd, _Reason}, #st{fd=Fd,prev_handler=PrevHandler}) ->      case PrevHandler of  	[] ->  	    remove_handler;  	_ ->   	    {swap_handler, install_prev, [], PrevHandler, go_back}      end; -handle_info({emulator, GL, Chars}, {Fd, File, PrevHandler}) -  when node(GL) == node() -> -    write_event(Fd, tag_event({emulator, GL, Chars})), -    {ok, {Fd, File, PrevHandler}}; -handle_info({emulator, noproc, Chars}, {Fd, File, PrevHandler}) -> -    write_event(Fd, tag_event({emulator, noproc, Chars})), -    {ok, {Fd, File, PrevHandler}};  handle_info(_, State) ->      {ok, State}. -handle_call(filename, {Fd, File, Prev}) -> -    {ok, File, {Fd, File, Prev}}; +handle_call(filename, #st{filename=File}=State) -> +    {ok, File, State};  handle_call(_Query, State) ->      {ok, {error, bad_query}, State}. @@ -104,69 +110,73 @@ code_change(_OldVsn, State, _Extra) ->  %%% Misc. functions.  %%% ------------------------------------------------------ -tag_event(Event) ->     -    {erlang:universaltime(), Event}. +write_events(State, [Ev|Es]) -> +    %% Write the events in reversed order. +    write_events(State, Es), +    write_event(State, Ev); +write_events(_State, []) -> +    ok. -write_events(Fd, Events) -> write_events1(Fd, lists:reverse(Events)). +write_event(#st{fd=Fd}=State, Event) -> +    case parse_event(Event) of +	ignore -> +	    ok; +	{Head,Pid,FormatList} -> +	    Time = maybe_utc(erlang:universaltime()), +	    Header = write_time(Time, Head), +	    Body = format_body(State, FormatList), +	    AtNode = if +			 node(Pid) =/= node() -> +			     ["** at node ",atom_to_list(node(Pid))," **\n"]; +			 true -> +			     [] +		     end, +	    io:put_chars(Fd, [Header,Body,AtNode]) +    end. -write_events1(Fd, [Event|Es]) -> -    write_event(Fd, Event), -    write_events1(Fd, Es); -write_events1(_, []) -> -    ok. +format_body(State, [{Format,Args}|T]) -> +    S = try format(State, Format, Args) of +	    S0 -> +		S0 +	catch +	    _:_ -> +		format(State, "ERROR: ~p - ~p\n", [Format,Args]) +	end, +    [S|format_body(State, T)]; +format_body(_State, []) -> +    []. -write_event(Fd, {Time, {error, _GL, {Pid, Format, Args}}}) -> -    T = write_time(maybe_utc(Time)), -    case catch io_lib:format(add_node(Format,Pid), Args) of -	S when is_list(S) -> -	    io:format(Fd, T ++ S, []); -	_ -> -	    F = add_node("ERROR: ~p - ~p~n", Pid), -	    io:format(Fd, T ++ F, [Format,Args]) -    end; -write_event(Fd, {Time, {emulator, _GL, Chars}}) -> -    T = write_time(maybe_utc(Time)), -    case catch io_lib:format(Chars, []) of -	S when is_list(S) -> -	    io:format(Fd, T ++ S, []); -	_ -> -	    io:format(Fd, T ++ "ERROR: ~p ~n", [Chars]) -    end; -write_event(Fd, {Time, {info, _GL, {Pid, Info, _}}}) -> -    T = write_time(maybe_utc(Time)), -    io:format(Fd, T ++ add_node("~p~n",Pid),[Info]); -write_event(Fd, {Time, {error_report, _GL, {Pid, std_error, Rep}}}) -> -    T = write_time(maybe_utc(Time)), -    S = format_report(Rep), -    io:format(Fd, T ++ S ++ add_node("", Pid), []); -write_event(Fd, {Time, {info_report, _GL, {Pid, std_info, Rep}}}) -> -    T = write_time(maybe_utc(Time), "INFO REPORT"), -    S = format_report(Rep), -    io:format(Fd, T ++ S ++ add_node("", Pid), []); -write_event(Fd, {Time, {info_msg, _GL, {Pid, Format, Args}}}) -> -    T = write_time(maybe_utc(Time), "INFO REPORT"), -    case catch io_lib:format(add_node(Format,Pid), Args) of -	S when is_list(S) -> -	    io:format(Fd, T ++ S, []); -	_ -> -	    F = add_node("ERROR: ~p - ~p~n", Pid), -	    io:format(Fd, T ++ F, [Format,Args]) -    end; -write_event(Fd, {Time, {warning_report, _GL, {Pid, std_warning, Rep}}}) -> -    T = write_time(maybe_utc(Time), "WARNING REPORT"), -    S = format_report(Rep), -    io:format(Fd, T ++ S ++ add_node("", Pid), []); -write_event(Fd, {Time, {warning_msg, _GL, {Pid, Format, Args}}}) -> -    T = write_time(maybe_utc(Time), "WARNING REPORT"), -    case catch io_lib:format(add_node(Format,Pid), Args) of -	S when is_list(S) -> -	    io:format(Fd, T ++ S, []); -	_ -> -	    F = add_node("ERROR: ~p - ~p~n", Pid), -	    io:format(Fd, T ++ F, [Format,Args]) -    end; -write_event(_, _) -> -    ok. +format(#st{depth=unlimited}, Format, Args) -> +    io_lib:format(Format, Args); +format(#st{depth=Depth}, Format0, Args) -> +    Format1 = io_lib:scan_format(Format0, Args), +    Format = limit_format(Format1, Depth), +    io_lib:build_text(Format). + +limit_format([#{control_char:=C0}=M0|T], Depth) when C0 =:= $p; +						     C0 =:= $w -> +    C = C0 - ($a - $A),				%To uppercase. +    #{args:=Args} = M0, +    M = M0#{control_char:=C,args:=Args++[Depth]}, +    [M|limit_format(T, Depth)]; +limit_format([H|T], Depth) -> +    [H|limit_format(T, Depth)]; +limit_format([], _) -> +    []. + +parse_event({error, _GL, {Pid, Format, Args}}) -> +    {"ERROR REPORT",Pid,[{Format,Args}]}; +parse_event({info_msg, _GL, {Pid, Format, Args}}) -> +    {"INFO REPORT",Pid,[{Format, Args}]}; +parse_event({warning_msg, _GL, {Pid, Format, Args}}) -> +    {"WARNING REPORT",Pid,[{Format,Args}]}; +parse_event({error_report, _GL, {Pid, std_error, Args}}) -> +    {"ERROR REPORT",Pid,format_term(Args)}; +parse_event({info_report, _GL, {Pid, std_info, Args}}) -> +    {"INFO REPORT",Pid,format_term(Args)}; +parse_event({warning_report, _GL, {Pid, std_warning, Args}}) -> +    {"WARNING REPORT",Pid,format_term(Args)}; +parse_event(_) -> ignore.  maybe_utc(Time) ->      UTC = case application:get_env(sasl, utc_log) of @@ -183,30 +193,27 @@ maybe_utc(Time) ->  maybe_utc(Time, true) -> {utc, Time};  maybe_utc(Time, _) -> {local, calendar:universal_time_to_local_time(Time)}. -format_report(Rep) when is_list(Rep) -> -    case string_p(Rep) of +format_term(Term) when is_list(Term) -> +    case string_p(Term) of  	true -> -	    io_lib:format("~s~n",[Rep]); -	_ -> -	    format_rep(Rep) +	    [{"~s\n",[Term]}]; +	false -> +	    format_term_list(Term)      end; -format_report(Rep) -> -    io_lib:format("~p~n",[Rep]). +format_term(Term) -> +    [{"~p\n",[Term]}]. -format_rep([{Tag,Data}|Rep]) -> -    io_lib:format("    ~p: ~p~n",[Tag,Data]) ++ format_rep(Rep); -format_rep([Other|Rep]) -> -    io_lib:format("    ~p~n",[Other]) ++ format_rep(Rep); -format_rep(_) -> +format_term_list([{Tag,Data}|T]) -> +    [{"    ~p: ~p\n",[Tag,Data]}|format_term_list(T)]; +format_term_list([Data|T]) -> +    [{"    ~p\n",[Data]}|format_term_list(T)]; +format_term_list([]) -> +    []; +format_term_list(_) -> +    %% Continue to allow non-proper lists for now. +    %% FIXME: Remove this clause in OTP 19.      []. -add_node(X, Pid) when is_atom(X) -> -    add_node(atom_to_list(X), Pid); -add_node(X, Pid) when node(Pid) =/= node() -> -    lists:concat([X,"** at node ",node(Pid)," **~n"]); -add_node(X, _) -> -    X. -  string_p([]) ->      false;  string_p(Term) -> @@ -222,15 +229,10 @@ string_p1([$\b|T]) -> string_p1(T);  string_p1([$\f|T]) -> string_p1(T);  string_p1([$\e|T]) -> string_p1(T);  string_p1([H|T]) when is_list(H) -> -    case string_p1(H) of -	true -> string_p1(T); -	_    -> false -    end; +    string_p1(H) andalso string_p1(T);  string_p1([]) -> true;  string_p1(_) ->  false. -write_time(Time) -> write_time(Time, "ERROR REPORT"). -  write_time({utc,{{Y,Mo,D},{H,Mi,S}}}, Type) ->      io_lib:format("~n=~s==== ~p-~s-~p::~s:~s:~s UTC ===~n",  		  [Type,D,month(Mo),Y,t(H),t(Mi),t(S)]); diff --git a/lib/stdlib/src/error_logger_tty_h.erl b/lib/stdlib/src/error_logger_tty_h.erl index 65ea645bd9..d2df6681e3 100644 --- a/lib/stdlib/src/error_logger_tty_h.erl +++ b/lib/stdlib/src/error_logger_tty_h.erl @@ -23,145 +23,180 @@  %%%  %%% A handler that can be connected to the error_logger -%%% event handler. -%%% Writes all events formatted to stdout. -%%%   Handles events tagged error, emulator and info. +%%% event handler. Writes all events formatted to stdout.  %%%  %%% It can only be started from error_logger:swap_handler(tty) -%%% or error_logger:tty(true) +%%% or error_logger:tty(true).  %%%  -export([init/1,  	 handle_event/2, handle_call/2, handle_info/2,  	 terminate/2, code_change/3]). --export([write_event/2]). +-export([write_event/2,write_event/3]). + +-record(st, +	{user, +	 prev_handler, +	 io_mod=io, +	 depth=unlimited}).  %% This one is used when we takeover from the simple error_logger.  init({[], {error_logger, Buf}}) ->      User = set_group_leader(), -    write_events(Buf,io), -    {ok, {User, error_logger}}; +    Depth = get_depth(), +    State = #st{user=User,prev_handler=error_logger,depth=Depth}, +    write_events(State, Buf), +    {ok, State};  %% This one is used if someone took over from us, and now wants to  %% go back.  init({[], {error_logger_tty_h, PrevHandler}}) ->      User = set_group_leader(), -    {ok, {User, PrevHandler}}; +    {ok, #st{user=User,prev_handler=PrevHandler}};  %% This one is used when we are started directly.  init([]) ->      User = set_group_leader(), -    {ok, {User, []}}. +    Depth = get_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) -> -    ok = write_event(tag_event(Event),io), +    ok = do_write_event(State, tag_event(Event)),      {ok, State}. -handle_info({'EXIT', User, _Reason}, {User, PrevHandler}) -> +handle_info({'EXIT', User, _Reason}, +	    #st{user=User,prev_handler=PrevHandler}=State) ->      case PrevHandler of  	[] ->  	    remove_handler;  	_ ->  -	    {swap_handler, install_prev, {User, PrevHandler},  +	    {swap_handler, install_prev, State,  	     PrevHandler, go_back}      end; -handle_info({emulator, GL, Chars}, State) when node(GL) == node() -> -    ok = write_event(tag_event({emulator, GL, Chars}),io), -    {ok, State}; -handle_info({emulator, noproc, Chars}, State) -> -    ok = write_event(tag_event({emulator, noproc, Chars}),io), -    {ok, State};  handle_info(_, State) ->      {ok, State}.  handle_call(_Query, State) -> {ok, {error, bad_query}, State}. -% unfortunately, we can't unlink from User - links are not counted! -%    if pid(User) -> unlink(User); true -> ok end,  terminate(install_prev, _State) ->      []; -terminate(_Reason, {_User, PrevHandler}) -> +terminate(_Reason, #st{prev_handler=PrevHandler}) ->      {error_logger_tty_h, PrevHandler}.  code_change(_OldVsn, State, _Extra) ->      {ok, State}. +%% Exported (but unoffical) API. +write_event(Event, IoMod) -> +    do_write_event(#st{io_mod=IoMod}, Event). + +write_event(Event, IoMod, Depth) -> +    do_write_event(#st{io_mod=IoMod,depth=Depth}, Event). + +  %%% ------------------------------------------------------  %%% Misc. functions.  %%% ------------------------------------------------------  set_group_leader() ->      case whereis(user) of -	User when is_pid(User) -> link(User), group_leader(User,self()), User; -	_                      -> false +	User when is_pid(User) -> +	    link(User), +	    group_leader(User,self()), +	    User; +	_ -> +	    false      end.  tag_event(Event) ->          {erlang:universaltime(), Event}. -%% IOMOd is always 'io' -write_events(Events,IOMod) -> write_events1(lists:reverse(Events),IOMod). - -write_events1([Event|Es],IOMod) -> -    ok = write_event(Event,IOMod), -    write_events1(Es,IOMod); -write_events1([],_IOMod) -> +write_events(State, [Ev|Es]) -> +    %% Write the events in reverse order. +    _ = write_events(State, Es), +    _ = do_write_event(State, Ev), +    ok; +write_events(_State, []) ->      ok. -write_event({Time, {error, _GL, {Pid, Format, Args}}},IOMod) -> -    T = write_time(maybe_utc(Time)), -    case catch io_lib:format(add_node(Format,Pid), Args) of -	S when is_list(S) -> -	    format(IOMod, T ++ S); -	_ -> -	    F = add_node("ERROR: ~p - ~p~n", Pid), -	    format(IOMod, T ++ F, [Format,Args]) +do_write_event(State, {Time0, Event}) -> +    case parse_event(Event) of +	ignore -> +	    ok; +	{Head,Pid,FormatList} -> +	    Time = maybe_utc(Time0), +	    Header = write_time(Time, Head), +	    Body = format_body(State, FormatList), +	    AtNode = if +			 node(Pid) =/= node() -> +			     ["** at node ",atom_to_list(node(Pid))," **\n"]; +			 true -> +			     [] +		     end, +	    Str = [Header,Body,AtNode], +	    case State#st.io_mod of +		io_lib -> +		    Str; +		io -> +		    io:put_chars(user, Str) +	    end      end; -write_event({Time, {emulator, _GL, Chars}},IOMod) -> -    T = write_time(maybe_utc(Time)), -    case catch io_lib:format(Chars, []) of -	S when is_list(S) -> -	    format(IOMod, T ++ S); -	_ -> -	    format(IOMod, T ++ "ERROR: ~p ~n", [Chars]) -    end; -write_event({Time, {info, _GL, {Pid, Info, _}}},IOMod) -> -    T = write_time(maybe_utc(Time)), -    format(IOMod, T ++ add_node("~p~n",Pid),[Info]); -write_event({Time, {error_report, _GL, {Pid, std_error, Rep}}},IOMod) -> -    T = write_time(maybe_utc(Time)), -    S = format_report(Rep), -    format(IOMod, T ++ S ++ add_node("", Pid)); -write_event({Time, {info_report, _GL, {Pid, std_info, Rep}}},IOMod) -> -    T = write_time(maybe_utc(Time), "INFO REPORT"), -    S = format_report(Rep), -    format(IOMod, T ++ S ++ add_node("", Pid)); -write_event({Time, {info_msg, _GL, {Pid, Format, Args}}},IOMod) -> -    T = write_time(maybe_utc(Time), "INFO REPORT"), -    case catch io_lib:format(add_node(Format,Pid), Args) of -	S when is_list(S) -> -	    format(IOMod, T ++ S); -	_ -> -	    F = add_node("ERROR: ~p - ~p~n", Pid), -	    format(IOMod, T ++ F, [Format,Args]) -    end; -write_event({Time, {warning_report, _GL, {Pid, std_warning, Rep}}},IOMod) -> -    T = write_time(maybe_utc(Time), "WARNING REPORT"), -    S = format_report(Rep), -    format(IOMod, T ++ S ++ add_node("", Pid)); -write_event({Time, {warning_msg, _GL, {Pid, Format, Args}}},IOMod) -> -    T = write_time(maybe_utc(Time), "WARNING REPORT"), -    case catch io_lib:format(add_node(Format,Pid), Args) of -	S when is_list(S) -> -	    format(IOMod, T ++ S); -	_ -> -	    F = add_node("ERROR: ~p - ~p~n", Pid), -	    format(IOMod, T ++ F, [Format,Args]) -    end; -write_event({_Time, _Error},_IOMod) -> +do_write_event(_, _) ->      ok. +format_body(State, [{Format,Args}|T]) -> +    S = try format(State, Format, Args) of +	    S0 -> +		S0 +	catch +	    _:_ -> +		format(State, "ERROR: ~p - ~p\n", [Format,Args]) +	end, +    [S|format_body(State, T)]; +format_body(_State, []) -> +    []. + +format(#st{depth=unlimited}, Format, Args) -> +    io_lib:format(Format, Args); +format(#st{depth=Depth}, Format0, Args) -> +    Format1 = io_lib:scan_format(Format0, Args), +    Format = limit_format(Format1, Depth), +    io_lib:build_text(Format). + +limit_format([#{control_char:=C0}=M0|T], Depth) when C0 =:= $p; +						     C0 =:= $w -> +    C = C0 - ($a - $A),				%To uppercase. +    #{args:=Args} = M0, +    M = M0#{control_char:=C,args:=Args++[Depth]}, +    [M|limit_format(T, Depth)]; +limit_format([H|T], Depth) -> +    [H|limit_format(T, Depth)]; +limit_format([], _) -> +    []. + +parse_event({error, _GL, {Pid, Format, Args}}) -> +    {"ERROR REPORT",Pid,[{Format,Args}]}; +parse_event({info_msg, _GL, {Pid, Format, Args}}) -> +    {"INFO REPORT",Pid,[{Format, Args}]}; +parse_event({warning_msg, _GL, {Pid, Format, Args}}) -> +    {"WARNING REPORT",Pid,[{Format,Args}]}; +parse_event({error_report, _GL, {Pid, std_error, Args}}) -> +    {"ERROR REPORT",Pid,format_term(Args)}; +parse_event({info_report, _GL, {Pid, std_info, Args}}) -> +    {"INFO REPORT",Pid,format_term(Args)}; +parse_event({warning_report, _GL, {Pid, std_warning, Args}}) -> +    {"WARNING REPORT",Pid,format_term(Args)}; +parse_event(_) -> ignore. +  maybe_utc(Time) ->      UTC = case application:get_env(sasl, utc_log) of                {ok, Val} -> Val; @@ -177,33 +212,26 @@ maybe_utc(Time) ->  maybe_utc(Time, true) -> {utc, Time};  maybe_utc(Time, _) -> {local, calendar:universal_time_to_local_time(Time)}. -format(IOMod, String)       -> format(IOMod, String, []). -format(io_lib, String, Args) -> io_lib:format(String, Args); -format(io, String, Args) -> io:format(user, String, Args). - -format_report(Rep) when is_list(Rep) -> -    case string_p(Rep) of +format_term(Term) when is_list(Term) -> +    case string_p(Term) of  	true -> -	    io_lib:format("~s~n",[Rep]); -	_ -> -	    format_rep(Rep) +	    [{"~s\n",[Term]}]; +	false -> +	    format_term_list(Term)      end; -format_report(Rep) -> -    io_lib:format("~p~n",[Rep]). - -format_rep([{Tag,Data}|Rep]) -> -    io_lib:format("    ~p: ~p~n",[Tag,Data]) ++ format_rep(Rep); -format_rep([Other|Rep]) -> -    io_lib:format("    ~p~n",[Other]) ++ format_rep(Rep); -format_rep(_) -> -    []. +format_term(Term) -> +    [{"~p\n",[Term]}]. -add_node(X, Pid) when is_atom(X) -> -    add_node(atom_to_list(X), Pid); -add_node(X, Pid) when node(Pid) =/= node() -> -    lists:concat([X,"** at node ",node(Pid)," **~n"]); -add_node(X, _) -> -    X. +format_term_list([{Tag,Data}|T]) -> +    [{"    ~p: ~p\n",[Tag,Data]}|format_term_list(T)]; +format_term_list([Data|T]) -> +    [{"    ~p\n",[Data]}|format_term_list(T)]; +format_term_list([]) -> +    []; +format_term_list(_) -> +    %% Continue to allow non-proper lists for now. +    %% FIXME: Remove this clause in OTP 19. +    [].  string_p([]) ->      false; @@ -227,7 +255,6 @@ string_p1([H|T]) when is_list(H) ->  string_p1([]) -> true;  string_p1(_) ->  false. -write_time(Time) -> write_time(Time, "ERROR REPORT").  write_time({utc,{{Y,Mo,D},{H,Mi,S}}},Type) ->      io_lib:format("~n=~s==== ~p-~s-~p::~s:~s:~s UTC ===~n",  		  [Type,D,month(Mo),Y,t(H),t(Mi),t(S)]); diff --git a/lib/stdlib/src/proc_lib.erl b/lib/stdlib/src/proc_lib.erl index bbf4f573f5..10c476a6f5 100644 --- a/lib/stdlib/src/proc_lib.erl +++ b/lib/stdlib/src/proc_lib.erl @@ -30,7 +30,8 @@  	 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,initial_call/1, +	 init_p/3,init_p/5,format/1,format/2,format/3, +	 initial_call/1,           translate_initial_call/1,  	 stop/1, stop/3]). @@ -700,53 +701,71 @@ format(CrashReport) ->        CrashReport :: [term()],        Encoding :: latin1 | unicode | utf8. -format([OwnReport,LinkReport], Encoding) -> -    OwnFormat = format_report(OwnReport, Encoding), -    LinkFormat = format_report(LinkReport, Encoding), +format(CrashReport, Encoding) -> +    format(CrashReport, Encoding, unlimited). + +-spec format(CrashReport, Encoding, Depth) -> string() when +      CrashReport :: [term()], +      Encoding :: latin1 | unicode | utf8, +      Depth :: unlimited | pos_integer(). + +format([OwnReport,LinkReport], Encoding, Depth) -> +    Extra = {Encoding,Depth}, +    OwnFormat = format_report(OwnReport, Extra), +    LinkFormat = format_report(LinkReport, Extra),      Str = io_lib:format("  crasher:~n~ts  neighbours:~n~ts",                          [OwnFormat, LinkFormat]),      lists:flatten(Str). -format_report(Rep, Enc) when is_list(Rep) -> -    format_rep(Rep,Enc); -format_report(Rep, Enc) -> +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) -> -    [format_mfa(InitialCall)|format_rep(Rep, Enc)]; -format_rep([{error_info,{Class,Reason,StackTrace}}|Rep], Enc) -> -    [format_exception(Class, Reason, StackTrace, Enc)|format_rep(Rep, Enc)]; -format_rep([{Tag,Data}|Rep], Enc) -> -    [format_tag(Tag, Data)|format_rep(Rep, Enc)]; -format_rep(_, _Enc) -> +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_exception(Class, Reason, StackTrace, Enc) -> -    PF = pp_fun(Enc), +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, lib:format_exception(1+length(EI), Class, Reason,                                 StackTrace, StackFun, PF, Enc), "\n"]. -format_mfa({M,F,Args}=StartF) -> +format_mfa({M,F,Args}=StartF, Depth) ->      try  	A = length(Args),  	["    initial call: ",atom_to_list(M),$:,atom_to_list(F),$/,  	 integer_to_list(A),"\n"]      catch  	error:_ -> -	    format_tag(initial_call, StartF) +	    format_tag(initial_call, StartF, Depth)      end. -pp_fun(Enc) -> -    P = modifier(Enc) ++ "p", +pp_fun({Enc,Depth}) -> +    {Letter,Tl} = case Depth of +		      unlimited -> {"p",[]}; +		      _ -> {"P",[Depth]} +		  end, +    P = modifier(Enc) ++ Letter,      fun(Term, I) ->  -            io_lib:format("~." ++ integer_to_list(I) ++ P, [Term]) +            io_lib:format("~." ++ integer_to_list(I) ++ P, [Term|Tl])      end. -format_tag(Tag, Data) -> -    io_lib:format("    ~p: ~80.18p~n", [Tag, Data]). +format_tag(Tag, Data, {_Enc,Depth}) -> +    case Depth of +	unlimited -> +	    io_lib:format("    ~p: ~80.18p~n", [Tag, Data]); +	_ -> +	    io_lib:format("    ~p: ~80.18P~n", [Tag, Data, Depth]) +    end.  modifier(latin1) -> "";  modifier(_) -> "t". | 
