diff options
Diffstat (limited to 'lib/stdlib/src/gen_statem.erl')
-rw-r--r-- | lib/stdlib/src/gen_statem.erl | 541 |
1 files changed, 330 insertions, 211 deletions
diff --git a/lib/stdlib/src/gen_statem.erl b/lib/stdlib/src/gen_statem.erl index faa43fbc1e..6f1f6a0228 100644 --- a/lib/stdlib/src/gen_statem.erl +++ b/lib/stdlib/src/gen_statem.erl @@ -330,6 +330,7 @@ %% Type validation functions +%% - return true if the value is of the type, false otherwise -compile( {inline, [callback_mode/1, state_enter/1, @@ -585,7 +586,12 @@ enter_loop(Module, Opts, State, Data, Server_or_Actions) -> enter_loop(Module, Opts, State, Data, Server, Actions) -> is_atom(Module) orelse error({atom,Module}), Parent = gen:get_parent(), - enter(Module, Opts, State, Data, Server, Actions, Parent). + Name = gen:get_proc_name(Server), + Debug = gen:debug_options(Name, Opts), + HibernateAfterTimeout = gen:hibernate_after(Opts), + enter( + Parent, Debug, Module, Name, HibernateAfterTimeout, + State, Data, Actions). %%--------------------------------------------------------------------------- %% API helpers @@ -657,11 +663,10 @@ send(Proc, Msg) -> ok. %% Here the init_it/6 and enter_loop/5,6,7 functions converge -enter(Module, Opts, State, Data, Server, Actions, Parent) -> +enter( + Parent, Debug, Module, Name, HibernateAfterTimeout, + State, Data, Actions) -> %% The values should already have been type checked - Name = gen:get_proc_name(Server), - Debug = gen:debug_options(Name, Opts), - HibernateAfterTimeout = gen:hibernate_after(Opts), Events = [], Event = {internal,init_state}, %% We enforce {postpone,false} to ensure that @@ -675,7 +680,7 @@ enter(Module, Opts, State, Data, Server, Actions, Parent) -> data = Data, hibernate_after = HibernateAfterTimeout}, CallEnter = true, - NewDebug = ?sys_debug(Debug, {Name,State}, {enter,Event,State}), + NewDebug = ?sys_debug(Debug, Name, {enter,State}), case call_callback_mode(S) of #state{} = NewS -> loop_event_actions_list( @@ -694,18 +699,24 @@ enter(Module, Opts, State, Data, Server, Actions, Parent) -> init_it(Starter, self, ServerRef, Module, Args, Opts) -> init_it(Starter, self(), ServerRef, Module, Args, Opts); init_it(Starter, Parent, ServerRef, Module, Args, Opts) -> + Name = gen:get_proc_name(ServerRef), + Debug = gen:debug_options(Name, Opts), + HibernateAfterTimeout = gen:hibernate_after(Opts), try Module:init(Args) of Result -> - init_result(Starter, Parent, ServerRef, Module, Result, Opts) + init_result( + Starter, Parent, ServerRef, Module, Result, + Name, Debug, HibernateAfterTimeout) catch Result -> - init_result(Starter, Parent, ServerRef, Module, Result, Opts); + init_result( + Starter, Parent, ServerRef, Module, Result, + Name, Debug, HibernateAfterTimeout); Class:Reason:Stacktrace -> - Name = gen:get_proc_name(ServerRef), gen:unregister_name(ServerRef), proc_lib:init_ack(Starter, {error,Reason}), error_info( - Class, Reason, Stacktrace, + Class, Reason, Stacktrace, Debug, #state{name = Name}, []), erlang:raise(Class, Reason, Stacktrace) @@ -714,14 +725,20 @@ init_it(Starter, Parent, ServerRef, Module, Args, Opts) -> %%--------------------------------------------------------------------------- %% gen callbacks helpers -init_result(Starter, Parent, ServerRef, Module, Result, Opts) -> +init_result( + Starter, Parent, ServerRef, Module, Result, + Name, Debug, HibernateAfterTimeout) -> case Result of {ok,State,Data} -> proc_lib:init_ack(Starter, {ok,self()}), - enter(Module, Opts, State, Data, ServerRef, [], Parent); + enter( + Parent, Debug, Module, Name, HibernateAfterTimeout, + State, Data, []); {ok,State,Data,Actions} -> proc_lib:init_ack(Starter, {ok,self()}), - enter(Module, Opts, State, Data, ServerRef, Actions, Parent); + enter( + Parent, Debug, Module, Name, HibernateAfterTimeout, + State, Data, Actions); {stop,Reason} -> gen:unregister_name(ServerRef), proc_lib:init_ack(Starter, {error,Reason}), @@ -731,12 +748,11 @@ init_result(Starter, Parent, ServerRef, Module, Result, Opts) -> proc_lib:init_ack(Starter, ignore), exit(normal); _ -> - Name = gen:get_proc_name(ServerRef), gen:unregister_name(ServerRef), Error = {bad_return_from_init,Result}, proc_lib:init_ack(Starter, {error,Error}), error_info( - error, Error, ?STACKTRACE(), + error, Error, ?STACKTRACE(), Debug, #state{name = Name}, []), exit(Error) @@ -791,7 +807,7 @@ format_status( [PDict,SysState,Parent,Debug, #state{name = Name, postponed = P} = S]) -> Header = gen:format_status_header("Status for state machine", Name), - Log = sys:get_debug(log, Debug, []), + Log = sys:get_log(Debug), [{header,Header}, {data, [{"Status",SysState}, @@ -811,34 +827,46 @@ format_status( sys_debug(Debug, NameState, Entry) -> sys:handle_debug(Debug, fun print_event/3, NameState, Entry). -print_event(Dev, {in,Event}, {Name,State}) -> - io:format( - Dev, "*DBG* ~tp receive ~ts in state ~tp~n", - [Name,event_string(Event),State]); -print_event(Dev, {out,Reply,{To,_Tag}}, {Name,State}) -> - io:format( - Dev, "*DBG* ~tp send ~tp to ~p from state ~tp~n", - [Name,Reply,To,State]); -print_event(Dev, {terminate,Reason}, {Name,State}) -> - io:format( - Dev, "*DBG* ~tp terminate ~tp in state ~tp~n", - [Name,Reason,State]); -print_event(Dev, {Tag,Event,NextState}, {Name,State}) -> - StateString = - case NextState of - State -> - io_lib:format("~tp", [State]); - _ -> - io_lib:format("~tp => ~tp", [State,NextState]) - end, - io:format( - Dev, "*DBG* ~tp ~tw ~ts in state ~ts~n", - [Name,Tag,event_string(Event),StateString]). +print_event(Dev, SystemEvent, Name) -> + case SystemEvent of + {in,Event,State} -> + io:format( + Dev, "*DBG* ~tp receive ~ts in state ~tp~n", + [Name,event_string(Event),State]); + {code_change,Event,State} -> + io:format( + Dev, "*DBG* ~tp receive ~ts after code change in state ~tp~n", + [Name,event_string(Event),State]); + {out,Reply,{To,_Tag}} -> + io:format( + Dev, "*DBG* ~tp send ~tp to ~tw~n", + [Name,Reply,To]); + {enter,State} -> + io:format( + Dev, "*DBG* ~tp enter in state ~tp~n", + [Name,State]); + {terminate,Reason,State} -> + io:format( + Dev, "*DBG* ~tp terminate ~tp in state ~tp~n", + [Name,Reason,State]); + {Tag,Event,State,NextState} + when Tag =:= postpone; Tag =:= consume -> + StateString = + case NextState of + State -> + io_lib:format("~tp", [State]); + _ -> + io_lib:format("~tp => ~tp", [State,NextState]) + end, + io:format( + Dev, "*DBG* ~tp ~tw ~ts in state ~ts~n", + [Name,Tag,event_string(Event),StateString]) + end. event_string(Event) -> case Event of {{call,{Pid,_Tag}},Request} -> - io_lib:format("call ~tp from ~w", [Request,Pid]); + io_lib:format("call ~tp from ~tw", [Request,Pid]); {EventType,EventContent} -> io_lib:format("~tw ~tp", [EventType,EventContent]) end. @@ -980,7 +1008,14 @@ loop_receive_result(Parent, ?not_sys_debug, S, Type, Content) -> loop_event(Parent, ?not_sys_debug, S, Events, Type, Content); loop_receive_result( Parent, Debug, #state{name = Name, state = State} = S, Type, Content) -> - NewDebug = sys_debug(Debug, {Name,State}, {in,{Type,Content}}), + Event = {Type,Content}, + NewDebug = + case S#state.callback_mode of + undefined -> + sys_debug(Debug, Name, {code_change,Event,State}); + _ -> + sys_debug(Debug, Name, {in,Event,State}) + end, %% Here is the queue of not yet handled events created Events = [], loop_event(Parent, NewDebug, S, Events, Type, Content). @@ -1277,7 +1312,7 @@ parse_actions(StateCall, Debug, S, [Action|Actions], TransOpts) -> end. parse_actions_reply( - StateCall, ?not_sys_debug, S, Actions, TransOpts, + StateCall, ?not_sys_debug = Debug, S, Actions, TransOpts, From, Reply) -> %% case from(From) of @@ -1287,27 +1322,25 @@ parse_actions_reply( false -> [error, {bad_action_from_state_function,{reply,From,Reply}}, - ?STACKTRACE(), - ?not_sys_debug] + ?STACKTRACE(), Debug] end; parse_actions_reply( - StateCall, Debug, #state{name = Name, state = State} = S, + StateCall, Debug, #state{name = Name} = S, Actions, TransOpts, From, Reply) -> %% case from(From) of true -> reply(From, Reply), - NewDebug = sys_debug(Debug, {Name,State}, {out,Reply,From}), + NewDebug = sys_debug(Debug, Name, {out,Reply,From}), parse_actions(StateCall, NewDebug, S, Actions, TransOpts); false -> [error, {bad_action_from_state_function,{reply,From,Reply}}, - ?STACKTRACE(), - Debug] + ?STACKTRACE(), Debug] end. parse_actions_next_event( - StateCall, ?not_sys_debug, S, + StateCall, ?not_sys_debug = Debug, S, Actions, TransOpts, Type, Content) -> case event_type(Type) of true when StateCall -> @@ -1320,15 +1353,14 @@ parse_actions_next_event( [error, {bad_state_enter_action_from_state_function, {next_event,Type,Content}}, - ?STACKTRACE(), - ?not_sys_debug] + ?STACKTRACE(), Debug] end; parse_actions_next_event( StateCall, Debug, #state{name = Name, state = State} = S, Actions, TransOpts, Type, Content) -> case event_type(Type) of true when StateCall -> - NewDebug = sys_debug(Debug, {Name,State}, {in,{Type,Content}}), + NewDebug = sys_debug(Debug, Name, {in,{Type,Content},State}), NextEventsR = TransOpts#trans_opts.next_events_r, parse_actions( StateCall, NewDebug, S, Actions, @@ -1403,13 +1435,13 @@ parse_actions_timeout_add( loop_event_done( Parent, ?not_sys_debug, #state{postponed = P} = S, +%% #state{postponed = will_not_happen = P} = S, Events, Event, NextState, NewData, #trans_opts{ postpone = Postpone, hibernate = Hibernate, - timeouts_r = [], next_events_r = []}) -> + timeouts_r = [], next_events_r = NextEventsR}) -> %% - %% Optimize the simple cases - %% i.e no timer changes, no inserted events and no debug, + %% Optimize the simple cases i.e no debug and no timer changes, %% by duplicate stripped down code %% %% Fast path @@ -1417,14 +1449,12 @@ loop_event_done( case Postpone of true -> loop_event_done_fast( - Parent, Hibernate, - S, - Events, [Event|P], NextState, NewData); + Parent, Hibernate, S, + Events, [Event|P], NextState, NewData, NextEventsR); false -> loop_event_done_fast( - Parent, Hibernate, - S, - Events, P, NextState, NewData) + Parent, Hibernate, S, + Events, P, NextState, NewData, NextEventsR) end; loop_event_done( Parent, Debug_0, @@ -1447,44 +1477,43 @@ loop_event_done( true -> [?sys_debug( Debug_0, - {S#state.name,State}, - {postpone,Event_0,NextState}), + S#state.name, + {postpone,Event_0,State,NextState}), Event_0|P_0]; false -> [?sys_debug( Debug_0, - {S#state.name,State}, - {consume,Event_0,NextState})|P_0] + S#state.name, + {consume,Event_0,State,NextState})|P_0] end, - {Events_2,P_2,Timers_2} = - %% Move all postponed events to queue, - %% cancel the event timer, - %% and cancel the state timeout if the state changes - if - NextState =:= State -> - {Events_0,P_1, + {Events_2,P_2, + Timers_2} = + %% Cancel the event timeout + if + NextState =:= State -> + {Events_0,P_1, cancel_timer_by_type( timeout, {TimerTypes_0,CancelTimers_0})}; - true -> - {lists:reverse(P_1, Events_0), - [], - cancel_timer_by_type( - state_timeout, + true -> + %% Move all postponed events to queue + %% and cancel the state timeout + {lists:reverse(P_1, Events_0),[], + cancel_timer_by_type( + state_timeout, cancel_timer_by_type( timeout, {TimerTypes_0,CancelTimers_0}))} - %% The state timer is removed from TimerTypes - %% but remains in TimerRefs until we get - %% the cancel_timer msg - end, + end, {TimerRefs_3,{TimerTypes_3,CancelTimers_3},TimeoutEvents} = %% Stop and start timers parse_timers(TimerRefs_0, Timers_2, TimeoutsR), %% Place next events last in reversed queue Events_3R = lists:reverse(Events_2, NextEventsR), %% Enqueue immediate timeout events - Events_4R = prepend_timeout_events(TimeoutEvents, Events_3R), + [Debug_2|Events_4R] = + prepend_timeout_events( + NextState, Debug_1, S, TimeoutEvents, Events_3R), loop_event_done( - Parent, Debug_1, + Parent, Debug_2, S#state{ state = NextState, data = NewData, @@ -1495,114 +1524,144 @@ loop_event_done( hibernate = Hibernate}, lists:reverse(Events_4R)). +loop_event_done(Parent, Debug, S, Q) -> +%% io:format( +%% "loop_event_done:~n" +%% " state = ~p, data = ~p, postponed = ~p~n " +%% " timer_refs = ~p, timer_types = ~p, cancel_timers = ~p.~n" +%% " Q = ~p.~n", +%% [S#state.state,S#state.data,S#state.postponed, +%% S#state.timer_refs,S#state.timer_types,S#state.cancel_timers, +%% Q]), + case Q of + [] -> + %% Get a new event + loop(Parent, Debug, S); + [{Type,Content}|Events] -> + %% Loop until out of enqueued events + loop_event(Parent, Debug, S, Events, Type, Content) + end. + + %% Fast path %% +%% Cancel event timer and state timer only if running loop_event_done_fast( Parent, Hibernate, #state{ state = NextState, - timer_types = #{timeout := _} = TimerTypes, + timer_types = TimerTypes, cancel_timers = CancelTimers} = S, - Events, P, NextState, NewData) -> - %% - %% Same state, event timeout active - %% - loop_event_done_fast( - Parent, Hibernate, S, - Events, P, NextState, NewData, - cancel_timer_by_type( - timeout, {TimerTypes,CancelTimers})); -loop_event_done_fast( - Parent, Hibernate, - #state{state = NextState} = S, - Events, P, NextState, NewData) -> - %% + Events, P, NextState, NewData, NextEventsR) -> %% Same state - %% - loop_event_done( - Parent, ?not_sys_debug, - S#state{ - data = NewData, - postponed = P, - hibernate = Hibernate}, - Events); -loop_event_done_fast( - Parent, Hibernate, - #state{ - timer_types = #{timeout := _} = TimerTypes, - cancel_timers = CancelTimers} = S, - Events, P, NextState, NewData) -> - %% - %% State change, event timeout active - %% - loop_event_done_fast( - Parent, Hibernate, S, - lists:reverse(P, Events), [], NextState, NewData, - cancel_timer_by_type( - state_timeout, - cancel_timer_by_type( - timeout, {TimerTypes,CancelTimers}))); + case TimerTypes of + #{timeout := _} -> + %% Event timeout active + loop_event_done_fast_2( + Parent, Hibernate, S, + Events, P, NextState, NewData, NextEventsR, + cancel_timer_by_type( + timeout, {TimerTypes,CancelTimers})); + _ -> + %% No event timeout active + loop_event_done_fast_2( + Parent, Hibernate, S, + Events, P, NextState, NewData, NextEventsR, + {TimerTypes,CancelTimers}) + end; loop_event_done_fast( Parent, Hibernate, #state{ - timer_types = #{state_timeout := _} = TimerTypes, + timer_types = TimerTypes, cancel_timers = CancelTimers} = S, - Events, P, NextState, NewData) -> - %% - %% State change, state timeout active - %% - loop_event_done_fast( - Parent, Hibernate, S, - lists:reverse(P, Events), [], NextState, NewData, - cancel_timer_by_type( - state_timeout, - cancel_timer_by_type( - timeout, {TimerTypes,CancelTimers}))); + Events, P, NextState, NewData, NextEventsR) -> + %% State change + case TimerTypes of + #{timeout := _} -> + %% Event timeout active + %% - cancel state_timeout too since it is faster than inspecting + loop_event_done_fast( + Parent, Hibernate, S, + Events, P, NextState, NewData, NextEventsR, + cancel_timer_by_type( + state_timeout, + cancel_timer_by_type( + timeout, {TimerTypes,CancelTimers}))); + #{state_timeout := _} -> + %% State_timeout active but not event timeout + loop_event_done_fast( + Parent, Hibernate, S, + Events, P, NextState, NewData, NextEventsR, + cancel_timer_by_type( + state_timeout, {TimerTypes,CancelTimers})); + _ -> + %% No event nor state_timeout active + loop_event_done_fast( + Parent, Hibernate, S, + Events, P, NextState, NewData, NextEventsR, + {TimerTypes,CancelTimers}) + end. +%% +%% Retry postponed events loop_event_done_fast( - Parent, Hibernate, - #state{} = S, - Events, P, NextState, NewData) -> - %% - %% State change, no timeout to automatically cancel - %% - loop_event_done( - Parent, ?not_sys_debug, - S#state{ - state = NextState, - data = NewData, - postponed = [], - hibernate = Hibernate}, - lists:reverse(P, Events)). + Parent, Hibernate, S, + Events, P, NextState, NewData, NextEventsR, TimerTypes_CancelTimers) -> + case P of + %% Handle 0..2 postponed events without list reversal since + %% that will move out all live registers and back again + [] -> + loop_event_done_fast_2( + Parent, Hibernate, S, + Events, [], NextState, NewData, NextEventsR, + TimerTypes_CancelTimers); + [E] -> + loop_event_done_fast_2( + Parent, Hibernate, S, + [E|Events], [], NextState, NewData, NextEventsR, + TimerTypes_CancelTimers); + [E1,E2] -> + loop_event_done_fast_2( + Parent, Hibernate, S, + [E2,E1|Events], [], NextState, NewData, NextEventsR, + TimerTypes_CancelTimers); + _ -> + %% A bit slower path + loop_event_done_fast_2( + Parent, Hibernate, S, + lists:reverse(P, Events), [], NextState, NewData, NextEventsR, + TimerTypes_CancelTimers) + end. %% %% Fast path %% -loop_event_done_fast( +loop_event_done_fast_2( Parent, Hibernate, S, - Events, P, NextState, NewData, + Events, P, NextState, NewData, NextEventsR, {TimerTypes,CancelTimers}) -> %% - loop_event_done( - Parent, ?not_sys_debug, - S#state{ - state = NextState, - data = NewData, - postponed = P, - timer_types = TimerTypes, - cancel_timers = CancelTimers, - hibernate = Hibernate}, - Events). - -loop_event_done(Parent, Debug, S, Q) -> - case Q of + NewS = + S#state{ + state = NextState, + data = NewData, + postponed = P, + timer_types = TimerTypes, + cancel_timers = CancelTimers, + hibernate = Hibernate}, + case NextEventsR of + %% Handle 0..2 next events without list reversal since + %% that will move out all live registers and back again [] -> - %% Get a new event - loop(Parent, Debug, S); - [{Type,Content}|Events] -> - %% Loop until out of enqueued events - loop_event(Parent, Debug, S, Events, Type, Content) + loop_event_done(Parent, ?not_sys_debug, NewS, Events); + [E] -> + loop_event_done(Parent, ?not_sys_debug, NewS, [E|Events]); + [E2,E1] -> + loop_event_done(Parent, ?not_sys_debug, NewS, [E1,E2|Events]); + _ -> + %% A bit slower path + loop_event_done( + Parent, ?not_sys_debug, NewS, lists:reverse(NextEventsR, Events)) end. - %%--------------------------------------------------------------------------- %% Server loop helpers @@ -1791,22 +1850,31 @@ parse_timers( %% so if there are enqueued events before the event timer %% timeout 0 event - the event timer is cancelled hence no event. %% -%% Other (state_timeout) timeout 0 events that are after -%% the event timer timeout 0 events are considered to +%% Other (state_timeout and {timeout,Name}) timeout 0 events +%% that are after an event timer timeout 0 event are considered to %% belong to timers that were started after the event timer %% timeout 0 event fired, so they do not cancel the event timer. %% -prepend_timeout_events([], EventsR) -> - EventsR; -prepend_timeout_events([{timeout,_} = TimeoutEvent|TimeoutEvents], []) -> - prepend_timeout_events(TimeoutEvents, [TimeoutEvent]); -prepend_timeout_events([{timeout,_}|TimeoutEvents], EventsR) -> +prepend_timeout_events(_NextState, Debug, _S, [], EventsR) -> + [Debug|EventsR]; +prepend_timeout_events( + NextState, Debug, S, [{timeout,_} = TimeoutEvent|TimeoutEvents], []) -> + prepend_timeout_events( + NextState, + sys_debug(Debug, S#state.name, {in,TimeoutEvent,NextState}), + S, TimeoutEvents, [TimeoutEvent]); +prepend_timeout_events( + NextState, Debug, S, [{timeout,_}|TimeoutEvents], EventsR) -> %% Ignore since there are other events in queue %% so they have cancelled the event timeout 0. - prepend_timeout_events(TimeoutEvents, EventsR); -prepend_timeout_events([TimeoutEvent|TimeoutEvents], EventsR) -> + prepend_timeout_events(NextState, Debug, S, TimeoutEvents, EventsR); +prepend_timeout_events( + NextState, Debug, S, [TimeoutEvent|TimeoutEvents], EventsR) -> %% Just prepend all others - prepend_timeout_events(TimeoutEvents, [TimeoutEvent|EventsR]). + prepend_timeout_events( + NextState, + sys_debug(Debug, S#state.name, {in,TimeoutEvent,NextState}), + S, TimeoutEvents, [TimeoutEvent|EventsR]). @@ -1823,18 +1891,24 @@ do_reply_then_terminate( do_reply_then_terminate( Class, Reason, Stacktrace, Debug, S, Q, [R|Rs]) -> case R of - {reply,{_To,_Tag}=From,Reply} -> - reply(From, Reply), - NewDebug = - ?sys_debug( - Debug, - begin - #state{name = Name, state = State} = S, - {Name,State} - end, - {out,Reply,From}), - do_reply_then_terminate( - Class, Reason, Stacktrace, NewDebug, S, Q, Rs); + {reply,From,Reply} -> + case from(From) of + true -> + reply(From, Reply), + NewDebug = + ?sys_debug( + Debug, + S#state.name, + {out,Reply,From}), + do_reply_then_terminate( + Class, Reason, Stacktrace, NewDebug, S, Q, Rs); + false -> + terminate( + error, + {bad_reply_action_from_state_function,R}, + ?STACKTRACE(), + Debug, S, Q) + end; _ -> terminate( error, @@ -1854,8 +1928,7 @@ terminate( catch _ -> ok; C:R:ST -> - error_info(C, R, ST, S, Q), - sys:print_log(Debug), + error_info(C, R, ST, Debug, S, Q), erlang:raise(C, R, ST) end; false -> @@ -1870,8 +1943,7 @@ terminate( {shutdown,_} -> terminate_sys_debug(Debug, S, State, Reason); _ -> - error_info(Class, Reason, Stacktrace, S, Q), - sys:print_log(Debug) + error_info(Class, Reason, Stacktrace, Debug, S, Q) end, case Stacktrace of [] -> @@ -1881,17 +1953,18 @@ terminate( end. terminate_sys_debug(Debug, S, State, Reason) -> - ?sys_debug(Debug, {S#state.name,State}, {terminate,Reason}). + ?sys_debug(Debug, S#state.name, {terminate,Reason,State}). error_info( - Class, Reason, Stacktrace, + Class, Reason, Stacktrace, Debug, #state{ name = Name, callback_mode = CallbackMode, state_enter = StateEnter, postponed = P} = S, Q) -> + Log = sys:get_log(Debug), ?LOG_ERROR(#{label=>{gen_statem,terminate}, name=>Name, queue=>Q, @@ -1899,11 +1972,37 @@ error_info( callback_mode=>CallbackMode, state_enter=>StateEnter, state=>format_status(terminate, get(), S), - reason=>{Class,Reason,Stacktrace}}, + log=>Log, + reason=>{Class,Reason,Stacktrace}, + client_info=>client_stacktrace(Q)}, #{domain=>[otp], report_cb=>fun gen_statem:format_log/1, error_logger=>#{tag=>error}}). +client_stacktrace([]) -> + undefined; +client_stacktrace([{{call,{Pid,_Tag}},_Req}|_]) when is_pid(Pid) -> + if + node(Pid) =:= node() -> + case + process_info(Pid, [current_stacktrace, registered_name]) + of + undefined -> + {Pid,dead}; + [{current_stacktrace, Stacktrace}, + {registered_name, []}] -> + {Pid,{Pid,Stacktrace}}; + [{current_stacktrace, Stacktrace}, + {registered_name, Name}] -> + {Pid,{Name,Stacktrace}} + end; + true -> + {Pid,remote} + end; +client_stacktrace([_|_]) -> + undefined. + + format_log(#{label:={gen_statem,terminate}, name:=Name, queue:=Q, @@ -1911,7 +2010,9 @@ format_log(#{label:={gen_statem,terminate}, callback_mode:=CallbackMode, state_enter:=StateEnter, state:=FmtData, - reason:={Class,Reason,Stacktrace}}) -> + log:=Log, + reason:={Class,Reason,Stacktrace}, + client_info:=ClientInfo}) -> {FixedReason,FixedStacktrace} = case Stacktrace of [{M,F,Args,_}|ST] @@ -1931,14 +2032,12 @@ format_log(#{label:={gen_statem,terminate}, true -> {Reason,Stacktrace}; false -> - {{'function not exported',{M,F,Arity}}, - ST} + {{'function not exported',{M,F,Arity}},ST} end end; _ -> {Reason,Stacktrace} end, - [LimitedP, LimitedFmtData, LimitedFixedReason] = - [error_logger:limit_term(D) || D <- [P, FmtData, FixedReason]], + {ClientFmt,ClientArgs} = format_client_log(ClientInfo), CBMode = case StateEnter of true -> @@ -1965,27 +2064,47 @@ format_log(#{label:={gen_statem,terminate}, case FixedStacktrace of [] -> ""; _ -> "** Stacktrace =~n** ~tp~n" - end, + end ++ + case Log of + [] -> ""; + _ -> "** Log =~n** ~tp~n" + end ++ ClientFmt, [Name | case Q of [] -> []; - [Event|_] -> [Event] + [Event|_] -> [error_logger:limit_term(Event)] end] ++ - [LimitedFmtData, - Class,LimitedFixedReason, + [error_logger:limit_term(FmtData), + Class,error_logger:limit_term(FixedReason), CBMode] ++ case Q of - [_|[_|_] = Events] -> [Events]; + [_|[_|_] = Events] -> [error_logger:limit_term(Events)]; _ -> [] end ++ case P of [] -> []; - _ -> [LimitedP] + _ -> [error_logger:limit_term(P)] end ++ case FixedStacktrace of [] -> []; - _ -> [FixedStacktrace] - end}. + _ -> [error_logger:limit_term(FixedStacktrace)] + end ++ + case Log of + [] -> []; + _ -> [[error_logger:limit_term(T) || T <- Log]] + end ++ ClientArgs}. + +format_client_log(undefined) -> + {"", []}; +format_client_log({Pid,dead}) -> + {"** Client ~p is dead~n", [Pid]}; +format_client_log({Pid,remote}) -> + {"** Client ~p is remote on node ~p~n", [Pid, node(Pid)]}; +format_client_log({_Pid,{Name,Stacktrace}}) -> + {"** Client ~tp stacktrace~n" + "** ~tp~n", + [Name, error_logger:limit_term(Stacktrace)]}. + %% Call Module:format_status/2 or return a default value format_status( |