From c4504cbe3a474b0bb5dab00ae66d680d3d0e9ff1 Mon Sep 17 00:00:00 2001 From: Siri Hansen Date: Tue, 24 Apr 2018 15:15:57 +0200 Subject: Start using logger internally in kernel and stdlib --- lib/stdlib/src/Makefile | 7 ++ lib/stdlib/src/gen_event.erl | 87 +++++++++++++++--------- lib/stdlib/src/gen_fsm.erl | 53 +++++++++++---- lib/stdlib/src/gen_server.erl | 110 +++++++++++++++++++----------- lib/stdlib/src/gen_statem.erl | 125 ++++++++++++++++++++--------------- lib/stdlib/src/proc_lib.erl | 125 +++++++++++++++++++++-------------- lib/stdlib/src/supervisor.erl | 55 +++++++++------ lib/stdlib/src/supervisor_bridge.erl | 27 +++++--- 8 files changed, 374 insertions(+), 215 deletions(-) (limited to 'lib/stdlib/src') diff --git a/lib/stdlib/src/Makefile b/lib/stdlib/src/Makefile index 8b156929d7..dc3735055a 100644 --- a/lib/stdlib/src/Makefile +++ b/lib/stdlib/src/Makefile @@ -238,6 +238,13 @@ $(EBIN)/erl_tar.beam: ../../kernel/include/file.hrl erl_tar.hrl $(EBIN)/file_sorter.beam: ../../kernel/include/file.hrl $(EBIN)/filelib.beam: ../../kernel/include/file.hrl $(EBIN)/filename.beam: ../../kernel/include/file.hrl +$(EBIN)/gen_event.beam: ../../kernel/include/logger.hrl +$(EBIN)/gen_fsm.beam: ../../kernel/include/logger.hrl +$(EBIN)/gen_server.beam: ../../kernel/include/logger.hrl +$(EBIN)/gen_statem.beam: ../../kernel/include/logger.hrl +$(EBIN)/proc_lib.beam: ../../kernel/include/logger.hrl $(EBIN)/qlc_pt.beam: ../include/ms_transform.hrl $(EBIN)/shell.beam: ../../kernel/include/file.hrl +$(EBIN)/supervisor.beam: ../../kernel/include/logger.hrl +$(EBIN)/supervisor_bridge.beam: ../../kernel/include/logger.hrl $(EBIN)/zip.beam: ../include/zip.hrl ../../kernel/include/file.hrl diff --git a/lib/stdlib/src/gen_event.erl b/lib/stdlib/src/gen_event.erl index 73e4457bd0..53042251cc 100644 --- a/lib/stdlib/src/gen_event.erl +++ b/lib/stdlib/src/gen_event.erl @@ -47,16 +47,19 @@ system_replace_state/2, format_status/2]). +%% logger callback +-export([format_log/1]). + -export_type([handler/0, handler_args/0, add_handler_ret/0, del_handler_ret/0]). --import(error_logger, [error_msg/2]). - -record(handler, {module :: atom(), id = false, state, supervised = false :: 'false' | pid()}). +-include("logger.hrl"). + %%%========================================================================= %%% API %%%========================================================================= @@ -583,9 +586,13 @@ server_update(Handler1, Func, Event, SName) -> remove, SName, normal), no; {'EXIT', {undef, [{Mod1, handle_info, [_,_], _}|_]}} -> - error_logger:warning_msg("** Undefined handle_info in ~tp~n" - "** Unhandled message: ~tp~n", [Mod1, Event]), - {ok, Handler1}; + ?LOG_WARNING(#{label=>{gen_event,no_handle_info}, + module=>Mod1, + message=>Event}, + #{domain=>[beam,erlang,otp], + report_cb=>fun gen_event:format_log/1, + error_logger=>#{tag=>warning_msg}}), % warningmap?? + {ok, Handler1}; Other -> do_terminate(Mod1, Handler1, {error, Other}, State, Event, SName, crash), @@ -737,6 +744,23 @@ report_error(_Handler, normal, _, _, _) -> ok; report_error(_Handler, shutdown, _, _, _) -> ok; report_error(_Handler, {swapped,_,_}, _, _, _) -> ok; report_error(Handler, Reason, State, LastIn, SName) -> + ?LOG_ERROR(#{label=>{gen_event,terminate}, + handler=>handler(Handler), + name=>SName, + last_message=>LastIn, + state=>format_status(terminate,Handler#handler.module, + get(),State), + reason=>Reason}, + #{domain=>[beam,erlang,otp], + report_cb=>fun gen_event:format_log/1, + error_logger=>#{tag=>error}}). + +format_log(#{label:={gen_event,terminate}, + handler:=Handler, + name:=SName, + last_message:=LastIn, + state:=State, + reason:=Reason}) -> Reason1 = case Reason of {'EXIT',{undef,[{M,F,A,L}|MFAs]}} -> @@ -756,23 +780,18 @@ report_error(Handler, Reason, State, LastIn, SName) -> _ -> Reason end, - Mod = Handler#handler.module, - FmtState = case erlang:function_exported(Mod, format_status, 2) of - true -> - Args = [get(), State], - case catch Mod:format_status(terminate, Args) of - {'EXIT', _} -> State; - Else -> Else - end; - _ -> - State - end, - error_msg("** gen_event handler ~p crashed.~n" - "** Was installed in ~tp~n" - "** Last event was: ~tp~n" - "** When handler state == ~tp~n" - "** Reason == ~tp~n", - [handler(Handler),SName,LastIn,FmtState,Reason1]). + {"** gen_event handler ~p crashed.~n" + "** Was installed in ~tp~n" + "** Last event was: ~tp~n" + "** When handler state == ~tp~n" + "** Reason == ~tp~n", + [Handler,SName,LastIn,State,Reason1]}; +format_log(#{label:={gen_event,no_handle_info}, + module:=Mod, + message:=Msg}) -> + {"** Undefined handle_info in ~tp~n" + "** Unhandled message: ~tp~n", + [Mod, Msg]}. handler(Handler) when not Handler#handler.id -> Handler#handler.module; @@ -805,17 +824,21 @@ format_status(Opt, StatusData) -> [PDict, SysState, Parent, _Debug, [ServerName, MSL, _HibernateAfterTimeout, _Hib]] = StatusData, Header = gen:format_status_header("Status for event handler", ServerName), - FmtMSL = [case erlang:function_exported(Mod, format_status, 2) of - true -> - Args = [PDict, State], - case catch Mod:format_status(Opt, Args) of - {'EXIT', _} -> MSL; - Else -> MS#handler{state = Else} - end; - _ -> - MS - end || #handler{module = Mod, state = State} = MS <- MSL], + FmtMSL = [MS#handler{state=format_status(Opt, Mod, PDict, State)} + || #handler{module = Mod, state = State} = MS <- MSL], [{header, Header}, {data, [{"Status", SysState}, {"Parent", Parent}]}, {items, {"Installed handlers", FmtMSL}}]. + +format_status(Opt, Mod, PDict, State) -> + case erlang:function_exported(Mod, format_status, 2) of + true -> + Args = [PDict, State], + case catch Mod:format_status(Opt, Args) of + {'EXIT', _} -> State; + Else -> Else + end; + false -> + State + end. diff --git a/lib/stdlib/src/gen_fsm.erl b/lib/stdlib/src/gen_fsm.erl index 8c7db65563..77826c3dc6 100644 --- a/lib/stdlib/src/gen_fsm.erl +++ b/lib/stdlib/src/gen_fsm.erl @@ -105,6 +105,8 @@ %%% %%% --------------------------------------------------- +-include("logger.hrl"). + -export([start/3, start/4, start_link/3, start_link/4, stop/1, stop/3, @@ -124,6 +126,9 @@ system_replace_state/2, format_status/2]). +%% logger callback +-export([format_log/1]). + -deprecated({start, 3, next_major_release}). -deprecated({start, 4, next_major_release}). -deprecated({start_link, 3, next_major_release}). @@ -144,8 +149,6 @@ -deprecated({enter_loop, 5, next_major_release}). -deprecated({enter_loop, 6, next_major_release}). --import(error_logger, [format/2]). - %%% --------------------------------------------------- %%% Interface functions. %%% --------------------------------------------------- @@ -499,8 +502,12 @@ handle_msg(Msg, Parent, Name, StateName, StateData, Mod, _Time, HibernateAfterTi reply(From, Reply), exit(R); {'EXIT', {undef, [{Mod, handle_info, [_,_,_], _}|_]}} -> - error_logger:warning_msg("** Undefined handle_info in ~p~n" - "** Unhandled message: ~tp~n", [Mod, Msg]), + ?LOG_WARNING(#{label=>{gen_fsm,no_handle_info}, + module=>Mod, + message=>Msg}, + #{domain=>[beam,erlang,otp], + report_cb=>fun gen_fsm:format_log/1, + error_logger=>#{tag=>warning_msg}}), loop(Parent, Name, StateName, StateData, Mod, infinity, HibernateAfterTimeout, []); {'EXIT', What} -> terminate(What, Name, Msg, Mod, StateName, StateData, []); @@ -603,6 +610,24 @@ terminate(Reason, Name, Msg, Mod, StateName, StateData, Debug) -> end. error_info(Reason, Name, Msg, StateName, StateData, Debug) -> + ?LOG_ERROR(#{label=>{gen_fsm,terminate}, + name=>Name, + last_message=>Msg, + state_name=>StateName, + state_data=>StateData, + reason=>Reason}, + #{domain=>[beam,erlang,otp], + report_cb=>fun gen_fsm:format_log/1, + error_logger=>#{tag=>error}}), + sys:print_log(Debug), + ok. + +format_log(#{label:={gen_fsm,terminate}, + name:=Name, + last_message:=Msg, + state_name:=StateName, + state_data:=StateData, + reason:=Reason}) -> Reason1 = case Reason of {undef,[{M,F,A,L}|MFAs]} -> @@ -620,14 +645,18 @@ error_info(Reason, Name, Msg, StateName, StateData, Debug) -> _ -> Reason end, - Str = "** State machine ~tp terminating \n" ++ - get_msg_str(Msg) ++ - "** When State == ~tp~n" - "** Data == ~tp~n" - "** Reason for termination = ~n** ~tp~n", - format(Str, [Name, get_msg(Msg), StateName, StateData, Reason1]), - sys:print_log(Debug), - ok. + {"** State machine ~tp terminating \n" ++ + get_msg_str(Msg) ++ + "** When State == ~tp~n" + "** Data == ~tp~n" + "** Reason for termination = ~n** ~tp~n", + [Name, get_msg(Msg), StateName, StateData, Reason1]}; +format_log(#{label:={gen_fsm,no_handle_info}, + module:=Mod, + message:=Msg}) -> + {"** Undefined handle_info in ~p~n" + "** Unhandled message: ~tp~n", + [Mod, Msg]}. get_msg_str({'$gen_event', _Event}) -> "** Last event in was ~tp~n"; diff --git a/lib/stdlib/src/gen_server.erl b/lib/stdlib/src/gen_server.erl index f29314d0a2..f65ef78636 100644 --- a/lib/stdlib/src/gen_server.erl +++ b/lib/stdlib/src/gen_server.erl @@ -104,9 +104,14 @@ system_replace_state/2, format_status/2]). +%% logger callback +-export([format_log/1]). + %% Internal exports -export([init_it/6]). +-include("logger.hrl"). + -define( STACKTRACE(), element(2, erlang:process_info(self(), current_stacktrace))). @@ -636,9 +641,13 @@ try_dispatch(Mod, Func, Msg, State) -> error:undef = R:Stacktrace when Func == handle_info -> case erlang:function_exported(Mod, handle_info, 2) of false -> - error_logger:warning_msg("** Undefined handle_info in ~p~n" - "** Unhandled message: ~tp~n", - [Mod, Msg]), + ?LOG_WARNING( + #{label=>{gen_server,no_handle_info}, + module=>Mod, + message=>Msg}, + #{domain=>[beam,erlang,otp], + report_cb=>fun gen_server:format_log/1, + error_logger=>#{tag=>warning_msg}}), {ok, {noreply, State}}; true -> {'EXIT', error, R, Stacktrace} @@ -849,8 +858,7 @@ terminate(Class, Reason, Stacktrace, ReportReason, Name, From, Msg, Mod, State, Reply = try_terminate(Mod, terminate_reason(Class, Reason, Stacktrace), State), case Reply of {'EXIT', C, R, S} -> - FmtState = format_status(terminate, Mod, get(), State), - error_info({R, S}, Name, From, Msg, FmtState, Debug), + error_info({R, S}, Name, From, Msg, Mod, State, Debug), erlang:raise(C, R, S); _ -> case {Class, Reason} of @@ -858,8 +866,7 @@ terminate(Class, Reason, Stacktrace, ReportReason, Name, From, Msg, Mod, State, {exit, shutdown} -> ok; {exit, {shutdown,_}} -> ok; _ -> - FmtState = format_status(terminate, Mod, get(), State), - error_info(ReportReason, Name, From, Msg, FmtState, Debug) + error_info(ReportReason, Name, From, Msg, Mod, State, Debug) end end, case Stacktrace of @@ -872,12 +879,46 @@ terminate(Class, Reason, Stacktrace, ReportReason, Name, From, Msg, Mod, State, terminate_reason(error, Reason, Stacktrace) -> {Reason, Stacktrace}; terminate_reason(exit, Reason, _Stacktrace) -> Reason. -error_info(_Reason, application_controller, _From, _Msg, _State, _Debug) -> +error_info(_Reason, application_controller, _From, _Msg, _Mod, _State, _Debug) -> %% OTP-5811 Don't send an error report if it's the system process %% application_controller which is terminating - let init take care %% of it instead ok; -error_info(Reason, Name, From, Msg, State, Debug) -> +error_info(Reason, Name, From, Msg, Mod, State, Debug) -> + ?LOG_ERROR(#{label=>{gen_server,terminate}, + name=>Name, + last_message=>Msg, + state=>format_status(terminate, Mod, get(), State), + reason=>Reason, + client_info=>client_stacktrace(From)}, + #{domain=>[beam,erlang,otp], + report_cb=>fun gen_server:format_log/1, + error_logger=>#{tag=>error}}), + sys:print_log(Debug), + ok. + +client_stacktrace(undefined) -> + undefined; +client_stacktrace({From,_Tag}) -> + client_stacktrace(From); +client_stacktrace(From) when is_pid(From), node(From) =:= node() -> + case process_info(From, [current_stacktrace, registered_name]) of + undefined -> + {From,dead}; + [{current_stacktrace, Stacktrace}, {registered_name, []}] -> + {From,{From,Stacktrace}}; + [{current_stacktrace, Stacktrace}, {registered_name, Name}] -> + {From,{Name,Stacktrace}} + end; +client_stacktrace(From) when is_pid(From) -> + {From,remote}. + +format_log(#{label:={gen_server,terminate}, + name:=Name, + last_message:=Msg, + state:=State, + reason:=Reason, + client_info:=Client}) -> Reason1 = case Reason of {undef,[{M,F,A,L}|MFAs]} -> @@ -893,36 +934,31 @@ error_info(Reason, Name, From, Msg, State, Debug) -> end end; _ -> - error_logger:limit_term(Reason) + logger:limit_term(Reason) end, - {ClientFmt, ClientArgs} = client_stacktrace(From), - LimitedState = error_logger:limit_term(State), - error_logger:format("** Generic server ~tp terminating \n" - "** Last message in was ~tp~n" - "** When Server state == ~tp~n" - "** Reason for termination == ~n** ~tp~n" ++ ClientFmt, - [Name, Msg, LimitedState, Reason1] ++ ClientArgs), - sys:print_log(Debug), - ok. -client_stacktrace(undefined) -> + {ClientFmt,ClientArgs} = format_client_log(Client), + {"** Generic server ~tp terminating \n" + "** Last message in was ~tp~n" + "** When Server state == ~tp~n" + "** Reason for termination == ~n** ~tp~n" ++ ClientFmt, + [Name, Msg, logger:limit_term(State), Reason1] ++ ClientArgs}; +format_log(#{label:={gen_server,no_handle_info}, + module:=Mod, + message:=Msg}) -> + {"** Undefined handle_info in ~p~n" + "** Unhandled message: ~tp~n", + [Mod, Msg]}. + +format_client_log(undefined) -> {"", []}; -client_stacktrace({From, _Tag}) -> - client_stacktrace(From); -client_stacktrace(From) when is_pid(From), node(From) =:= node() -> - case process_info(From, [current_stacktrace, registered_name]) of - undefined -> - {"** Client ~p is dead~n", [From]}; - [{current_stacktrace, Stacktrace}, {registered_name, []}] -> - {"** Client ~p stacktrace~n" - "** ~tp~n", - [From, Stacktrace]}; - [{current_stacktrace, Stacktrace}, {registered_name, Name}] -> - {"** Client ~tp stacktrace~n" - "** ~tp~n", - [Name, Stacktrace]} - end; -client_stacktrace(From) when is_pid(From) -> - {"** Client ~p is remote on node ~p~n", [From, node(From)]}. +format_client_log({From,dead}) -> + {"** Client ~p is dead~n", [From]}; +format_client_log({From,remote}) -> + {"** Client ~p is remote on node ~p~n", [From, node(From)]}; +format_client_log({_From,{Name,Stacktrace}}) -> + {"** Client ~tp stacktrace~n" + "** ~tp~n", + [Name, Stacktrace]}. %%----------------------------------------------------------------- %% Status information diff --git a/lib/stdlib/src/gen_statem.erl b/lib/stdlib/src/gen_statem.erl index f7dc0050b3..f558f0d33e 100644 --- a/lib/stdlib/src/gen_statem.erl +++ b/lib/stdlib/src/gen_statem.erl @@ -19,6 +19,8 @@ %% -module(gen_statem). +-include("logger.hrl"). + %% API -export( [start/3,start/4,start_link/3,start_link/4, @@ -44,6 +46,9 @@ -export( [wakeup_from_hibernate/3]). +%% logger callback +-export([format_log/1]). + %% Type exports for templates and callback modules -export_type( [event_type/0, @@ -702,7 +707,7 @@ init_it(Starter, Parent, ServerRef, Module, Args, Opts) -> error_info( Class, Reason, Stacktrace, #state{name = Name}, - [], undefined), + []), erlang:raise(Class, Reason, Stacktrace) end. @@ -733,7 +738,7 @@ init_result(Starter, Parent, ServerRef, Module, Result, Opts) -> error_info( error, Error, ?STACKTRACE(), #state{name = Name}, - [], undefined), + []), exit(Error) end. @@ -1849,9 +1854,7 @@ terminate( catch _ -> ok; C:R:ST -> - error_info( - C, R, ST, S, Q, - format_status(terminate, get(), S)), + error_info(C, R, ST, S, Q), sys:print_log(Debug), erlang:raise(C, R, ST) end; @@ -1867,9 +1870,7 @@ terminate( {shutdown,_} -> terminate_sys_debug(Debug, S, State, Reason); _ -> - error_info( - Class, Reason, Stacktrace, S, Q, - format_status(terminate, get(), S)), + error_info(Class, Reason, Stacktrace, S, Q), sys:print_log(Debug) end, case Stacktrace of @@ -1889,8 +1890,28 @@ error_info( name = Name, callback_mode = CallbackMode, state_enter = StateEnter, - postponed = P}, - Q, FmtData) -> + postponed = P} = S, + Q) -> + ?LOG_ERROR(#{label=>{gen_statem,terminate}, + name=>Name, + queue=>Q, + postponed=>P, + callback_mode=>CallbackMode, + state_enter=>StateEnter, + state=>format_status(terminate, get(), S), + reason=>{Class,Reason,Stacktrace}}, + #{domain=>[beam,erlang,otp], + report_cb=>fun gen_statem:format_log/1, + error_logger=>#{tag=>error}}). + +format_log(#{label:={gen_statem,terminate}, + name:=Name, + queue:=Q, + postponed:=P, + callback_mode:=CallbackMode, + state_enter:=StateEnter, + state:=FmtData, + reason:={Class,Reason,Stacktrace}}) -> {FixedReason,FixedStacktrace} = case Stacktrace of [{M,F,Args,_}|ST] @@ -1917,7 +1938,7 @@ error_info( _ -> {Reason,Stacktrace} end, [LimitedP, LimitedFmtData, LimitedFixedReason] = - [error_logger:limit_term(D) || D <- [P, FmtData, FixedReason]], + [logger:limit_term(D) || D <- [P, FmtData, FixedReason]], CBMode = case StateEnter of true -> @@ -1925,48 +1946,46 @@ error_info( false -> CallbackMode end, - error_logger:format( - "** State machine ~tp terminating~n" ++ - case Q of - [] -> ""; - _ -> "** Last event = ~tp~n" - end ++ - "** When server state = ~tp~n" ++ - "** Reason for termination = ~w:~tp~n" ++ - "** Callback mode = ~p~n" ++ - case Q of - [_,_|_] -> "** Queued = ~tp~n"; - _ -> "" - end ++ - case P of - [] -> ""; - _ -> "** Postponed = ~tp~n" - end ++ - case FixedStacktrace of - [] -> ""; - _ -> "** Stacktrace =~n** ~tp~n" - end, - [Name | - case Q of - [] -> []; - [Event|_] -> [Event] - end] ++ - [LimitedFmtData, - Class,LimitedFixedReason, - CBMode] ++ - case Q of - [_|[_|_] = Events] -> [Events]; - _ -> [] - end ++ - case P of - [] -> []; - _ -> [LimitedP] - end ++ - case FixedStacktrace of - [] -> []; - _ -> [FixedStacktrace] - end). - + {"** State machine ~tp terminating~n" ++ + case Q of + [] -> ""; + _ -> "** Last event = ~tp~n" + end ++ + "** When server state = ~tp~n" ++ + "** Reason for termination = ~w:~tp~n" ++ + "** Callback mode = ~p~n" ++ + case Q of + [_,_|_] -> "** Queued = ~tp~n"; + _ -> "" + end ++ + case P of + [] -> ""; + _ -> "** Postponed = ~tp~n" + end ++ + case FixedStacktrace of + [] -> ""; + _ -> "** Stacktrace =~n** ~tp~n" + end, + [Name | + case Q of + [] -> []; + [Event|_] -> [Event] + end] ++ + [LimitedFmtData, + Class,LimitedFixedReason, + CBMode] ++ + case Q of + [_|[_|_] = Events] -> [Events]; + _ -> [] + end ++ + case P of + [] -> []; + _ -> [LimitedP] + end ++ + case FixedStacktrace of + [] -> []; + _ -> [FixedStacktrace] + end}. %% Call Module:format_status/2 or return a default value format_status( diff --git a/lib/stdlib/src/proc_lib.erl b/lib/stdlib/src/proc_lib.erl index 1991585c13..8d01840313 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, + init_p/3,init_p/5,format/1,format/2,format/3,report_cb/1, initial_call/1, translate_initial_call/1, stop/1, stop/3]). @@ -40,6 +40,8 @@ -export_type([spawn_option/0]). +-include("logger.hrl"). + %%----------------------------------------------------------------------------- -type priority_level() :: 'high' | 'low' | 'max' | 'normal'. @@ -503,10 +505,13 @@ 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). + ?LOG_ERROR(#{label=>{proc_lib,crash}, + report=>[my_info(Class, Reason, StartF, Stacktrace), + linked_info(self())]}, + #{domain=>[beam,erlang,otp,sasl], + report_cb=>fun proc_lib:report_cb/1, + logger_formatter=>#{title=>"CRASH REPORT"}, + error_logger=>#{tag=>error_report,type=>crash_report}}). my_info(Class, Reason, [], Stacktrace) -> my_info_1(Class, Reason, Stacktrace); @@ -548,10 +553,10 @@ get_ancestors(Pid) -> %% assumed that all report handlers call proc_lib:format(). get_messages(Pid) -> Messages = get_process_messages(Pid), - {messages, error_logger:limit_term(Messages)}. + {messages, logger:limit_term(Messages)}. get_process_messages(Pid) -> - Depth = error_logger:get_format_depth(), + Depth = logger:get_format_depth(), case Pid =/= self() orelse Depth =:= unlimited of true -> {messages, Messages} = get_process_info(Pid, messages), @@ -581,7 +586,7 @@ get_cleaned_dictionary(Pid) -> cleaned_dict(Dict) -> CleanDict = clean_dict(Dict), - error_logger:limit_term(CleanDict). + logger:limit_term(CleanDict). clean_dict([{'$ancestors',_}|Dict]) -> clean_dict(Dict); @@ -742,9 +747,18 @@ check({badrpc,Error}) -> Error; check(Res) -> Res. %%% ----------------------------------------------------------- -%%% Format (and write) a generated crash info structure. +%%% 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 = logger:get_format_depth(), + get_format_and_args(CrashReport, utf8, Depth). + -spec format(CrashReport) -> string() when CrashReport :: [term()]. format(CrashReport) -> @@ -762,61 +776,74 @@ format(CrashReport, Encoding) -> Encoding :: latin1 | unicode | utf8, Depth :: unlimited | pos_integer(). -format([OwnReport,LinkReport], Encoding, Depth) -> +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 = 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). + {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([Link|Reps], Indent, Extra) -> +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) -> 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(Rep, Indent, Extra) -> - format_report(Rep, Indent, Extra). - -format_report(Rep, Indent, Extra) when is_list(Rep) -> - format_rep(Rep, Indent, Extra); -format_report(Rep, Indent, {Enc,unlimited}) -> - io_lib:format("~s~"++modifier(Enc)++"p~n", [Indent, Rep]); -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) -> - 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"]. + {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) -> try A = length(Args), - [Indent,"initial call: ",atom_to_list(M),$:,to_string(F, Enc),$/, - integer_to_list(A),"\n"] + {lists:flatten([Indent,"initial call: ",atom_to_list(M), + $:,to_string(F, Enc),$/,integer_to_list(A),"\n"]),[]} 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, lib: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, _) -> @@ -828,10 +855,6 @@ pp_fun({Enc,Depth}) -> io_lib:format("~." ++ integer_to_list(I) ++ P, [Term|Tl]) end. -format_tag(Indent, Tag, Data, {Enc,Depth}) -> - {P,Tl} = p(Enc, Depth), - io_lib:format("~s~p: ~80.18" ++ P ++ "\n", [Indent, Tag, Data|Tl]). - p(Encoding, Depth) -> {Letter, Tl} = case Depth of unlimited -> {"p", []}; diff --git a/lib/stdlib/src/supervisor.erl b/lib/stdlib/src/supervisor.erl index e56415650f..eb46ac611a 100644 --- a/lib/stdlib/src/supervisor.erl +++ b/lib/stdlib/src/supervisor.erl @@ -35,6 +35,20 @@ %% For release_handler only -export([get_callback_module/1]). +-include("logger.hrl"). + +-define(report_error(Error, Reason, Child, SupName), + ?LOG_ERROR(#{label=>{supervisor,Error}, + report=>[{supervisor,SupName}, + {errorContext,Error}, + {reason,Reason}, + {offender,extract_child(Child)}]}, + #{domain=>[beam,erlang,otp,sasl], + report_cb=>fun logger:format_otp_report/1, + logger_formatter=>#{title=>"SUPERVISOR REPORT"}, + error_logger=>#{tag=>error_report, + type=>supervisor_report}})). + %%-------------------------------------------------------------------------- -export_type([sup_flags/0, child_spec/0, startchild_ret/0, strategy/0]). @@ -340,7 +354,7 @@ start_children(Children, SupName) -> {ok, Pid, _Extra} -> {update,Child#child{pid = Pid}}; {error, Reason} -> - report_error(start_error, Reason, Child, SupName), + ?report_error(start_error, Reason, Child, SupName), {abort,{failed_to_start_child,Id,Reason}} end end, @@ -565,8 +579,9 @@ handle_info({'EXIT', Pid, Reason}, State) -> end; handle_info(Msg, State) -> - error_logger:error_msg("Supervisor received unexpected message: ~tp~n", - [Msg]), + ?LOG_ERROR("Supervisor received unexpected message: ~tp~n",[Msg], + #{domain=>[beam,erlang,otp], + error_logger=>#{tag=>error}}), {noreply, State}. %% @@ -683,7 +698,7 @@ restart_child(Pid, Reason, State) -> end. do_restart(Reason, Child, State) when ?is_permanent(Child) -> - report_error(child_terminated, Reason, Child, State#state.name), + ?report_error(child_terminated, Reason, Child, State#state.name), restart(Child, State); do_restart(normal, Child, State) -> NState = del_child(Child, State), @@ -695,10 +710,10 @@ do_restart({shutdown, _Term}, Child, State) -> NState = del_child(Child, State), {ok, NState}; do_restart(Reason, Child, State) when ?is_transient(Child) -> - report_error(child_terminated, Reason, Child, State#state.name), + ?report_error(child_terminated, Reason, Child, State#state.name), restart(Child, State); do_restart(Reason, Child, State) when ?is_temporary(Child) -> - report_error(child_terminated, Reason, Child, State#state.name), + ?report_error(child_terminated, Reason, Child, State#state.name), NState = del_child(Child, State), {ok, NState}. @@ -718,7 +733,7 @@ restart(Child, State) -> Other end; {terminate, NState} -> - report_error(shutdown, reached_max_restart_intensity, + ?report_error(shutdown, reached_max_restart_intensity, Child, State#state.name), {shutdown, del_child(Child, NState)} end. @@ -745,7 +760,7 @@ restart(simple_one_for_one, Child, State0) -> NRestarts = State2#state.dynamic_restarts + 1, State3 = State2#state{dynamic_restarts = NRestarts}, NState = dyn_store(ROldPid, A, State3), - report_error(start_error, Error, Child, NState#state.name), + ?report_error(start_error, Error, Child, NState#state.name), {{try_again, ROldPid}, NState} end; restart(one_for_one, #child{id=Id} = Child, State) -> @@ -759,7 +774,7 @@ restart(one_for_one, #child{id=Id} = Child, State) -> {ok, NState}; {error, Reason} -> NState = set_pid(restarting(OldPid), Id, State), - report_error(start_error, Reason, Child, State#state.name), + ?report_error(start_error, Reason, Child, State#state.name), {{try_again,Id}, NState} end; restart(rest_for_one, #child{id=Id} = Child, #state{name=SupName} = State) -> @@ -820,7 +835,7 @@ do_terminate(Child, SupName) when is_pid(Child#child.pid) -> {error, normal} when not (?is_permanent(Child)) -> ok; {error, OtherReason} -> - report_error(shutdown_error, OtherReason, Child, SupName) + ?report_error(shutdown_error, OtherReason, Child, SupName) end, ok; do_terminate(_Child, _SupName) -> @@ -924,7 +939,7 @@ terminate_dynamic_children(State) -> end, %% Unroll stacked errors and report them dict:fold(fun(Reason, Ls, _) -> - report_error(shutdown_error, Reason, + ?report_error(shutdown_error, Reason, Child#child{pid=Ls}, State#state.name) end, ok, EStack). @@ -1385,14 +1400,6 @@ inPeriod(Then, Now, Period) -> %%% ------------------------------------------------------ %%% Error and progress reporting. %%% ------------------------------------------------------ - -report_error(Error, Reason, Child, SupName) -> - ErrorMsg = [{supervisor, SupName}, - {errorContext, Error}, - {reason, Reason}, - {offender, extract_child(Child)}], - error_logger:error_report(supervisor_report, ErrorMsg). - extract_child(Child) when is_list(Child#child.pid) -> [{nb_children, length(Child#child.pid)}, {id, Child#child.id}, @@ -1409,9 +1416,13 @@ extract_child(Child) -> {child_type, Child#child.child_type}]. report_progress(Child, SupName) -> - Progress = [{supervisor, SupName}, - {started, extract_child(Child)}], - error_logger:info_report(progress, Progress). + ?LOG_INFO(#{label=>{supervisor,progress}, + report=>[{supervisor,SupName}, + {started,extract_child(Child)}]}, + #{domain=>[beam,erlang,otp,sasl], + report_cb=>fun logger:format_otp_report/1, + logger_formatter=>#{title=>"PROGRESS REPORT"}, + error_logger=>#{tag=>info_report,type=>progress}}). format_status(terminate, [_PDict, State]) -> State; diff --git a/lib/stdlib/src/supervisor_bridge.erl b/lib/stdlib/src/supervisor_bridge.erl index af1e046d30..39372935fa 100644 --- a/lib/stdlib/src/supervisor_bridge.erl +++ b/lib/stdlib/src/supervisor_bridge.erl @@ -21,6 +21,8 @@ -behaviour(gen_server). +-include("logger.hrl"). + %% External exports -export([start_link/2, start_link/3]). %% Internal exports @@ -129,13 +131,22 @@ terminate_pid(Reason, #state{mod = Mod, child_state = ChildState}) -> Mod:terminate(Reason, ChildState). report_progress(Pid, Mod, StartArgs, SupName) -> - Progress = [{supervisor, SupName}, - {started, [{pid, Pid}, {mfa, {Mod, init, [StartArgs]}}]}], - error_logger:info_report(progress, Progress). + ?LOG_INFO(#{label=>{supervisor,progress}, + report=>[{supervisor, SupName}, + {started, [{pid, Pid}, + {mfa, {Mod, init, [StartArgs]}}]}]}, + #{domain=>[beam,erlang,otp,sasl], + report_cb=>fun logger:format_otp_report/1, + logger_formatter=>#{title=>"PROGRESS REPORT"}, + error_logger=>#{tag=>info_report,type=>progress}}). report_error(Error, Reason, #state{name = Name, pid = Pid, mod = Mod}) -> - ErrorMsg = [{supervisor, Name}, - {errorContext, Error}, - {reason, Reason}, - {offender, [{pid, Pid}, {mod, Mod}]}], - error_logger:error_report(supervisor_report, ErrorMsg). + ?LOG_ERROR(#{label=>{supervisor,error}, + report=>[{supervisor, Name}, + {errorContext, Error}, + {reason, Reason}, + {offender, [{pid, Pid}, {mod, Mod}]}]}, + #{domain=>[beam,erlang,otp,sasl], + report_cb=>fun logger:format_otp_report/1, + logger_formatter=>#{title=>"SUPERVISOR REPORT"}, + error_logger=>#{tag=>error_report,type=>supervisor_report}}). -- cgit v1.2.3