diff options
Diffstat (limited to 'lib/stdlib/src')
-rw-r--r-- | lib/stdlib/src/calendar.erl | 11 | ||||
-rw-r--r-- | lib/stdlib/src/erl_lint.erl | 9 | ||||
-rw-r--r-- | lib/stdlib/src/erl_parse.yrl | 9 | ||||
-rw-r--r-- | lib/stdlib/src/gen_fsm.erl | 154 | ||||
-rw-r--r-- | lib/stdlib/src/gen_server.erl | 53 | ||||
-rw-r--r-- | lib/stdlib/src/gen_statem.erl | 2302 | ||||
-rw-r--r-- | lib/stdlib/src/ms_transform.erl | 4 | ||||
-rw-r--r-- | lib/stdlib/src/otp_internal.erl | 8 | ||||
-rw-r--r-- | lib/stdlib/src/stdlib.appup.src | 43 | ||||
-rw-r--r-- | lib/stdlib/src/sys.erl | 150 |
10 files changed, 1639 insertions, 1104 deletions
diff --git a/lib/stdlib/src/calendar.erl b/lib/stdlib/src/calendar.erl index 9a600c1972..bb5d450cd6 100644 --- a/lib/stdlib/src/calendar.erl +++ b/lib/stdlib/src/calendar.erl @@ -693,14 +693,11 @@ local_offset(SystemTime, Unit) -> UniversalSecs = datetime_to_gregorian_seconds(UniversalTime), LocalSecs - UniversalSecs. +fraction_str(1, _Time) -> + ""; fraction_str(Factor, Time) -> - case Time rem Factor of - 0 -> - ""; - Fraction -> - FS = io_lib:fwrite(".~*..0B", [log10(Factor), abs(Fraction)]), - string:trim(FS, trailing, "0") - end. + Fraction = Time rem Factor, + io_lib:fwrite(".~*..0B", [log10(Factor), abs(Fraction)]). fraction(second, _) -> 0; diff --git a/lib/stdlib/src/erl_lint.erl b/lib/stdlib/src/erl_lint.erl index e9ac2fcdff..3ec78a2667 100644 --- a/lib/stdlib/src/erl_lint.erl +++ b/lib/stdlib/src/erl_lint.erl @@ -831,13 +831,15 @@ bif_clashes(Forms, #lint{nowarn_bif_clash=Nowarn} = St) -> %% not_deprecated(Forms, State0) -> State -not_deprecated(Forms, St0) -> +not_deprecated(Forms, #lint{compile=Opts}=St0) -> %% There are no line numbers in St0#lint.compile. MFAsL = [{MFA,L} || {attribute, L, compile, Args} <- Forms, {nowarn_deprecated_function, MFAs0} <- lists:flatten([Args]), MFA <- lists:flatten([MFAs0])], - Nowarn = [MFA || {MFA,_L} <- MFAsL], + Nowarn = [MFA || + {nowarn_deprecated_function, MFAs0} <- Opts, + MFA <- lists:flatten([MFAs0])], ML = [{M,L} || {{M,_F,_A},L} <- MFAsL, is_atom(M)], St1 = foldl(fun ({M,L}, St2) -> check_module_name(M, L, St2) @@ -2262,8 +2264,7 @@ expr({'fun',Line,Body}, Vt, St) -> {[],St}; {function,M,F,A} -> %% New in R15. - {Bvt, St1} = expr_list([M,F,A], Vt, St), - {vtupdate(Bvt, Vt),St1} + expr_list([M,F,A], Vt, St) end; expr({named_fun,_,'_',Cs}, Vt, St) -> fun_clauses(Cs, Vt, St); diff --git a/lib/stdlib/src/erl_parse.yrl b/lib/stdlib/src/erl_parse.yrl index 9602f0bcd9..4ad94f2507 100644 --- a/lib/stdlib/src/erl_parse.yrl +++ b/lib/stdlib/src/erl_parse.yrl @@ -841,7 +841,7 @@ Erlang code. -type af_record_field(T) :: {'record_field', anno(), af_field_name(), T}. -type af_map_pattern() :: - {'map', anno(), [af_assoc_exact(abstract_expr)]}. + {'map', anno(), [af_assoc_exact(abstract_expr())]}. -type abstract_type() :: af_annotated_type() | af_atom() @@ -872,7 +872,7 @@ Erlang code. -type af_fun_type() :: {'type', anno(), 'fun', []} | {'type', anno(), 'fun', [{'type', anno(), 'any'} | abstract_type()]} - | {'type', anno(), 'fun', af_function_type()}. + | af_function_type(). -type af_integer_range_type() :: {'type', anno(), 'range', [af_singleton_integer_type()]}. @@ -924,10 +924,11 @@ Erlang code. -type af_function_constraint() :: [af_constraint()]. -type af_constraint() :: {'type', anno(), 'constraint', - af_lit_atom('is_subtype'), - [af_type_variable() | abstract_type()]}. % [V, T] + [af_lit_atom('is_subtype') | + [af_type_variable() | abstract_type()]]}. % [IsSubtype, [V, T]] -type af_singleton_integer_type() :: af_integer() + | af_character() | af_unary_op(af_singleton_integer_type()) | af_binary_op(af_singleton_integer_type()). diff --git a/lib/stdlib/src/gen_fsm.erl b/lib/stdlib/src/gen_fsm.erl index caaaf8fa2e..1e18710738 100644 --- a/lib/stdlib/src/gen_fsm.erl +++ b/lib/stdlib/src/gen_fsm.erl @@ -411,12 +411,13 @@ decode_msg(Msg,Parent, Name, StateName, StateData, Mod, Time, HibernateAfterTime sys:handle_system_msg(Req, From, Parent, ?MODULE, Debug, [Name, StateName, StateData, Mod, Time, HibernateAfterTimeout], Hib); {'EXIT', Parent, Reason} -> - terminate(Reason, Name, Msg, Mod, StateName, StateData, Debug); + terminate( + Reason, Name, undefined, Msg, Mod, StateName, StateData, Debug); _Msg when Debug =:= [] -> handle_msg(Msg, Parent, Name, StateName, StateData, Mod, Time, HibernateAfterTimeout); _Msg -> Debug1 = sys:handle_debug(Debug, fun print_event/3, - {Name, StateName}, {in, Msg}), + Name, {in, Msg, StateName}), handle_msg(Msg, Parent, Name, StateName, StateData, Mod, Time, HibernateAfterTimeout, Debug1) end. @@ -431,7 +432,7 @@ system_continue(Parent, Debug, [Name, StateName, StateData, Mod, Time, Hibernate system_terminate(Reason, _Parent, Debug, [Name, StateName, StateData, Mod, _Time, _HibernateAfterTimeout]) -> - terminate(Reason, Name, [], Mod, StateName, StateData, Debug). + terminate(Reason, Name, undefined, [], Mod, StateName, StateData, Debug). system_code_change([Name, StateName, StateData, Mod, Time, HibernateAfterTimeout], _Module, OldVsn, Extra) -> @@ -452,7 +453,7 @@ system_replace_state(StateFun, [Name, StateName, StateData, Mod, Time, Hibernate %% Format debug messages. Print them as the call-back module sees %% them, not as the real erlang messages. Use trace for that. %%----------------------------------------------------------------- -print_event(Dev, {in, Msg}, {Name, StateName}) -> +print_event(Dev, {in, Msg, StateName}, Name) -> case Msg of {'$gen_event', Event} -> io:format(Dev, "*DBG* ~tp got event ~tp in state ~tw~n", @@ -461,6 +462,16 @@ print_event(Dev, {in, Msg}, {Name, StateName}) -> io:format(Dev, "*DBG* ~tp got all_state_event ~tp in state ~tw~n", [Name, Event, StateName]); + {'$gen_sync_event', {From,_Tag}, Event} -> + io:format(Dev, + "*DBG* ~tp got sync_event ~tp " + "from ~tw in state ~tw~n", + [Name, Event, From, StateName]); + {'$gen_sync_all_state_event', {From,_Tag}, Event} -> + io:format(Dev, + "*DBG* ~tp got sync_all_state_event ~tp " + "from ~tw in state ~tw~n", + [Name, Event, From, StateName]); {timeout, Ref, {'$gen_timer', Message}} -> io:format(Dev, "*DBG* ~tp got timer ~tp in state ~tw~n", @@ -473,11 +484,11 @@ print_event(Dev, {in, Msg}, {Name, StateName}) -> io:format(Dev, "*DBG* ~tp got ~tp in state ~tw~n", [Name, Msg, StateName]) end; -print_event(Dev, {out, Msg, To, StateName}, Name) -> +print_event(Dev, {out, Msg, {To,_Tag}, StateName}, Name) -> io:format(Dev, "*DBG* ~tp sent ~tp to ~tw~n" " and switched to state ~tw~n", [Name, Msg, To, StateName]); -print_event(Dev, return, {Name, StateName}) -> +print_event(Dev, {noreply, StateName}, Name) -> io:format(Dev, "*DBG* ~tp switched to state ~tw~n", [Name, StateName]). @@ -495,9 +506,9 @@ handle_msg(Msg, Parent, Name, StateName, StateData, Mod, _Time, HibernateAfterTi reply(From, Reply), loop(Parent, Name, NStateName, NStateData, Mod, Time1, HibernateAfterTimeout, []); {stop, Reason, NStateData} -> - terminate(Reason, Name, Msg, Mod, StateName, NStateData, []); + terminate(Reason, Name, From, Msg, Mod, StateName, NStateData, []); {stop, Reason, Reply, NStateData} when From =/= undefined -> - {'EXIT', R} = (catch terminate(Reason, Name, Msg, Mod, + {'EXIT', R} = (catch terminate(Reason, Name, From, Msg, Mod, StateName, NStateData, [])), reply(From, Reply), exit(R); @@ -510,10 +521,10 @@ handle_msg(Msg, Parent, Name, StateName, StateData, Mod, _Time, HibernateAfterTi error_logger=>#{tag=>warning_msg}}), loop(Parent, Name, StateName, StateData, Mod, infinity, HibernateAfterTimeout, []); {'EXIT', What} -> - terminate(What, Name, Msg, Mod, StateName, StateData, []); + terminate(What, Name, From, Msg, Mod, StateName, StateData, []); Reply -> terminate({bad_return_value, Reply}, - Name, Msg, Mod, StateName, StateData, []) + Name, From, Msg, Mod, StateName, StateData, []) end. handle_msg(Msg, Parent, Name, StateName, StateData, Mod, _Time, HibernateAfterTimeout, Debug) -> @@ -521,11 +532,11 @@ handle_msg(Msg, Parent, Name, StateName, StateData, Mod, _Time, HibernateAfterTi case catch dispatch(Msg, Mod, StateName, StateData) of {next_state, NStateName, NStateData} -> Debug1 = sys:handle_debug(Debug, fun print_event/3, - {Name, NStateName}, return), + Name, {noreply, NStateName}), loop(Parent, Name, NStateName, NStateData, Mod, infinity, HibernateAfterTimeout, Debug1); {next_state, NStateName, NStateData, Time1} -> Debug1 = sys:handle_debug(Debug, fun print_event/3, - {Name, NStateName}, return), + Name, {noreply, NStateName}), loop(Parent, Name, NStateName, NStateData, Mod, Time1, HibernateAfterTimeout, Debug1); {reply, Reply, NStateName, NStateData} when From =/= undefined -> Debug1 = reply(Name, From, Reply, Debug, NStateName), @@ -534,17 +545,18 @@ handle_msg(Msg, Parent, Name, StateName, StateData, Mod, _Time, HibernateAfterTi Debug1 = reply(Name, From, Reply, Debug, NStateName), loop(Parent, Name, NStateName, NStateData, Mod, Time1, HibernateAfterTimeout, Debug1); {stop, Reason, NStateData} -> - terminate(Reason, Name, Msg, Mod, StateName, NStateData, Debug); + terminate( + Reason, Name, From, Msg, Mod, StateName, NStateData, Debug); {stop, Reason, Reply, NStateData} when From =/= undefined -> - {'EXIT', R} = (catch terminate(Reason, Name, Msg, Mod, + {'EXIT', R} = (catch terminate(Reason, Name, From, Msg, Mod, StateName, NStateData, Debug)), _ = reply(Name, From, Reply, Debug, StateName), exit(R); {'EXIT', What} -> - terminate(What, Name, Msg, Mod, StateName, StateData, Debug); + terminate(What, Name, From, Msg, Mod, StateName, StateData, Debug); Reply -> terminate({bad_return_value, Reply}, - Name, Msg, Mod, StateName, StateData, Debug) + Name, From, Msg, Mod, StateName, StateData, Debug) end. dispatch({'$gen_event', Event}, Mod, StateName, StateData) -> @@ -571,24 +583,25 @@ from(_) -> undefined. reply({To, Tag}, Reply) -> catch To ! {Tag, Reply}. -reply(Name, {To, Tag}, Reply, Debug, StateName) -> - reply({To, Tag}, Reply), +reply(Name, From, Reply, Debug, StateName) -> + reply(From, Reply), sys:handle_debug(Debug, fun print_event/3, Name, - {out, Reply, To, StateName}). + {out, Reply, From, StateName}). %%% --------------------------------------------------- %%% Terminate the server. %%% --------------------------------------------------- --spec terminate(term(), _, _, atom(), _, _, _) -> no_return(). +-spec terminate(term(), _, _, _, atom(), _, _, _) -> no_return(). -terminate(Reason, Name, Msg, Mod, StateName, StateData, Debug) -> +terminate(Reason, Name, From, Msg, Mod, StateName, StateData, Debug) -> case erlang:function_exported(Mod, terminate, 3) of true -> case catch Mod:terminate(Reason, StateName, StateData) of {'EXIT', R} -> FmtStateData = format_status(terminate, Mod, get(), StateData), - error_info(R, Name, Msg, StateName, FmtStateData, Debug), + error_info( + R, Name, From, Msg, StateName, FmtStateData, Debug), exit(R); _ -> ok @@ -605,29 +618,51 @@ terminate(Reason, Name, Msg, Mod, StateName, StateData, Debug) -> exit(Shutdown); _ -> FmtStateData1 = format_status(terminate, Mod, get(), StateData), - error_info(Reason,Name,Msg,StateName,FmtStateData1,Debug), + error_info( + Reason, Name, From, Msg, StateName, FmtStateData1, Debug), exit(Reason) end. -error_info(Reason, Name, Msg, StateName, StateData, Debug) -> +error_info(Reason, Name, From, Msg, StateName, StateData, Debug) -> + Log = sys:get_log(Debug), ?LOG_ERROR(#{label=>{gen_fsm,terminate}, name=>Name, last_message=>Msg, state_name=>StateName, state_data=>StateData, - reason=>Reason}, + log=>Log, + reason=>Reason, + client_info=>client_stacktrace(From)}, #{domain=>[otp], report_cb=>fun gen_fsm:format_log/1, error_logger=>#{tag=>error}}), - sys:print_log(Debug), ok. +client_stacktrace(undefined) -> + undefined; +client_stacktrace({Pid,_Tag}) -> + client_stacktrace(Pid); +client_stacktrace(Pid) when is_pid(Pid), 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; +client_stacktrace(Pid) when is_pid(Pid) -> + {Pid,remote}. + + format_log(#{label:={gen_fsm,terminate}, name:=Name, last_message:=Msg, state_name:=StateName, state_data:=StateData, - reason:=Reason}) -> + log:=Log, + reason:=Reason, + client_info:=ClientInfo}) -> Reason1 = case Reason of {undef,[{M,F,A,L}|MFAs]} -> @@ -645,27 +680,39 @@ format_log(#{label:={gen_fsm,terminate}, _ -> Reason end, + {ClientFmt,ClientArgs} = format_client_log(ClientInfo), {"** 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]}; + "** Reason for termination ==~n** ~tp~n" ++ + case Log of + [] -> []; + _ -> "** Log ==~n** ~tp~n" + end ++ ClientFmt, + [Name|error_logger:limit_term(get_msg(Msg))] ++ + [StateName, + error_logger:limit_term(StateData), + error_logger:limit_term(Reason1) | + case Log of + [] -> []; + _ -> [[error_logger:limit_term(D) || D <- Log]] + end] ++ ClientArgs}; format_log(#{label:={gen_fsm,no_handle_info}, module:=Mod, message:=Msg}) -> {"** Undefined handle_info in ~p~n" "** Unhandled message: ~tp~n", - [Mod, Msg]}. + [Mod, error_logger:limit_term(Msg)]}. get_msg_str({'$gen_event', _Event}) -> "** Last event in was ~tp~n"; -get_msg_str({'$gen_sync_event', _Event}) -> - "** Last sync event in was ~tp~n"; +get_msg_str({'$gen_sync_event', _From, _Event}) -> + "** Last sync event in was ~tp from ~tw~n"; get_msg_str({'$gen_all_state_event', _Event}) -> "** Last event in was ~tp (for all states)~n"; -get_msg_str({'$gen_sync_all_state_event', _Event}) -> - "** Last sync event in was ~tp (for all states)~n"; +get_msg_str({'$gen_sync_all_state_event', _From, _Event}) -> + "** Last sync event in was ~tp (for all states) from ~tw~n"; get_msg_str({timeout, _Ref, {'$gen_timer', _Msg}}) -> "** Last timer event in was ~tp~n"; get_msg_str({timeout, _Ref, {'$gen_event', _Msg}}) -> @@ -673,13 +720,24 @@ get_msg_str({timeout, _Ref, {'$gen_event', _Msg}}) -> get_msg_str(_Msg) -> "** Last message in was ~tp~n". -get_msg({'$gen_event', Event}) -> Event; -get_msg({'$gen_sync_event', Event}) -> Event; -get_msg({'$gen_all_state_event', Event}) -> Event; -get_msg({'$gen_sync_all_state_event', Event}) -> Event; -get_msg({timeout, Ref, {'$gen_timer', Msg}}) -> {timeout, Ref, Msg}; -get_msg({timeout, _Ref, {'$gen_event', Event}}) -> Event; -get_msg(Msg) -> Msg. +get_msg({'$gen_event', Event}) -> [Event]; +get_msg({'$gen_sync_event', {From,_Tag}, Event}) -> [Event,From]; +get_msg({'$gen_all_state_event', Event}) -> [Event]; +get_msg({'$gen_sync_all_state_event', {From,_Tag}, Event}) -> [Event,From]; +get_msg({timeout, Ref, {'$gen_timer', Msg}}) -> [{timeout, Ref, Msg}]; +get_msg({timeout, _Ref, {'$gen_event', Event}}) -> [Event]; +get_msg(Msg) -> [Msg]. + +format_client_log(undefined) -> + {"", []}; +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, error_logger:limit_term(Stacktrace)]}. %%----------------------------------------------------------------- %% Status information @@ -689,18 +747,18 @@ format_status(Opt, StatusData) -> StatusData, Header = gen:format_status_header("Status for state machine", Name), - Log = sys:get_debug(log, Debug, []), - Specfic = format_status(Opt, Mod, PDict, StateData), - Specfic = case format_status(Opt, Mod, PDict, StateData) of - S when is_list(S) -> S; - S -> [S] - end, + Log = sys:get_log(Debug), + Specific = + case format_status(Opt, Mod, PDict, StateData) of + S when is_list(S) -> S; + S -> [S] + end, [{header, Header}, {data, [{"Status", SysState}, {"Parent", Parent}, {"Logged events", Log}, {"StateName", StateName}]} | - Specfic]. + Specific]. format_status(Opt, Mod, PDict, State) -> DefStatus = case Opt of diff --git a/lib/stdlib/src/gen_server.erl b/lib/stdlib/src/gen_server.erl index 44e9231ebe..c7b6406f54 100644 --- a/lib/stdlib/src/gen_server.erl +++ b/lib/stdlib/src/gen_server.erl @@ -773,10 +773,10 @@ handle_common_reply(Reply, Parent, Name, From, Msg, Mod, HibernateAfterTimeout, terminate({bad_return_value, BadReply}, ?STACKTRACE(), Name, From, Msg, Mod, State, Debug) end. -reply(Name, {To, Tag}, Reply, State, Debug) -> - reply({To, Tag}, Reply), +reply(Name, From, Reply, State, Debug) -> + reply(From, Reply), sys:handle_debug(Debug, fun print_event/3, Name, - {out, Reply, To, State} ). + {out, Reply, From, State} ). %%----------------------------------------------------------------- @@ -810,7 +810,7 @@ system_replace_state(StateFun, [Name, State, Mod, Time, HibernateAfterTimeout]) print_event(Dev, {in, Msg}, Name) -> case Msg of {'$gen_call', {From, _Tag}, Call} -> - io:format(Dev, "*DBG* ~tp got call ~tp from ~w~n", + io:format(Dev, "*DBG* ~tp got call ~tp from ~tw~n", [Name, Call, From]); {'$gen_cast', Cast} -> io:format(Dev, "*DBG* ~tp got cast ~tp~n", @@ -818,8 +818,8 @@ print_event(Dev, {in, Msg}, Name) -> _ -> io:format(Dev, "*DBG* ~tp got ~tp~n", [Name, Msg]) end; -print_event(Dev, {out, Msg, To, State}, Name) -> - io:format(Dev, "*DBG* ~tp sent ~tp to ~w, new state ~tp~n", +print_event(Dev, {out, Msg, {To,_Tag}, State}, Name) -> + io:format(Dev, "*DBG* ~tp sent ~tp to ~tw, new state ~tp~n", [Name, Msg, To, State]); print_event(Dev, {noreply, State}, Name) -> io:format(Dev, "*DBG* ~tp new state ~tp~n", [Name, State]); @@ -885,16 +885,17 @@ error_info(_Reason, application_controller, _From, _Msg, _Mod, _State, _Debug) - %% of it instead ok; error_info(Reason, Name, From, Msg, Mod, State, Debug) -> + Log = sys:get_log(Debug), ?LOG_ERROR(#{label=>{gen_server,terminate}, name=>Name, last_message=>Msg, state=>format_status(terminate, Mod, get(), State), + log=>format_log_state(Mod, Log), reason=>Reason, client_info=>client_stacktrace(From)}, #{domain=>[otp], report_cb=>fun gen_server:format_log/1, error_logger=>#{tag=>error}}), - sys:print_log(Debug), ok. client_stacktrace(undefined) -> @@ -917,6 +918,7 @@ format_log(#{label:={gen_server,terminate}, name:=Name, last_message:=Msg, state:=State, + log:=Log, reason:=Reason, client_info:=Client}) -> Reason1 = @@ -934,20 +936,30 @@ format_log(#{label:={gen_server,terminate}, end end; _ -> - error_logger:limit_term(Reason) + Reason end, {ClientFmt,ClientArgs} = format_client_log(Client), + [LimitedMsg,LimitedState,LimitedReason|LimitedLog] = + [error_logger:limit_term(D) || D <- [Msg,State,Reason1|Log]], {"** 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, error_logger:limit_term(State), Reason1] ++ ClientArgs}; + "** Reason for termination ==~n** ~tp~n" ++ + case LimitedLog of + [] -> []; + _ -> "** Log ==~n** ~tp~n" + end ++ ClientFmt, + [Name, LimitedMsg, LimitedState, LimitedReason] ++ + case LimitedLog of + [] -> []; + _ -> [LimitedLog] + end ++ 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]}. + [Mod, error_logger:limit_term(Msg)]}. format_client_log(undefined) -> {"", []}; @@ -958,7 +970,7 @@ format_client_log({From,remote}) -> format_client_log({_From,{Name,Stacktrace}}) -> {"** Client ~tp stacktrace~n" "** ~tp~n", - [Name, Stacktrace]}. + [Name, error_logger:limit_term(Stacktrace)]}. %%----------------------------------------------------------------- %% Status information @@ -966,16 +978,25 @@ format_client_log({_From,{Name,Stacktrace}}) -> format_status(Opt, StatusData) -> [PDict, SysState, Parent, Debug, [Name, State, Mod, _Time, _HibernateAfterTimeout]] = StatusData, Header = gen:format_status_header("Status for generic server", Name), - Log = sys:get_debug(log, Debug, []), - Specfic = case format_status(Opt, Mod, PDict, State) of + Log = sys:get_log(Debug), + Specific = case format_status(Opt, Mod, PDict, State) of S when is_list(S) -> S; S -> [S] end, [{header, Header}, {data, [{"Status", SysState}, {"Parent", Parent}, - {"Logged events", Log}]} | - Specfic]. + {"Logged events", format_log_state(Mod, Log)}]} | + Specific]. + +format_log_state(Mod, Log) -> + [case Event of + {out,Msg,From,State} -> + {out,Msg,From,format_status(terminate, Mod, get(), State)}; + {noreply,State} -> + {noreply,format_status(terminate, Mod, get(), State)}; + _ -> Event + end || Event <- Log]. format_status(Opt, Mod, PDict, State) -> DefStatus = case Opt of diff --git a/lib/stdlib/src/gen_statem.erl b/lib/stdlib/src/gen_statem.erl index 24b268cd38..513118a874 100644 --- a/lib/stdlib/src/gen_statem.erl +++ b/lib/stdlib/src/gen_statem.erl @@ -1,7 +1,7 @@ %% %% %CopyrightBegin% %% -%% Copyright Ericsson AB 2016-2018. All Rights Reserved. +%% Copyright Ericsson AB 2016-2019. 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. @@ -374,50 +374,51 @@ timeout_event_type(Type) -> -define( + relative_timeout(T), + ((is_integer(T) andalso 0 =< (T)) orelse (T) =:= infinity)). + +-define( + absolute_timeout(T), + (is_integer(T) orelse (T) =:= infinity)). + +-define( STACKTRACE(), element(2, erlang:process_info(self(), current_stacktrace))). -define(not_sys_debug, []). %% %% This is a macro to only evaluate arguments if Debug =/= []. -%% Debug is evaluated multiple times. +%% Debug is evaluated 2 times. -define( - sys_debug(Debug, NameState, Entry), + sys_debug(Debug, Extra, SystemEvent), case begin Debug end of ?not_sys_debug -> begin Debug end; _ -> - sys_debug(begin Debug end, begin NameState end, begin Entry end) + sys_debug( + begin Debug end, begin Extra end, begin SystemEvent end) end). --record(state, +-record(params, {callback_mode = undefined :: callback_mode() | undefined, state_enter = false :: boolean(), + parent :: pid(), module :: atom(), - name :: atom(), - state :: term(), - data :: term(), + name :: atom() | pid(), + hibernate_after = infinity :: timeout() + }). + +-record(state, + {state_data = {undefined,undefined} :: + {State :: term(),Data :: term()}, postponed = [] :: [{event_type(),term()}], - %% - timer_refs = #{} :: % timer ref => the timer's event type - #{reference() => timeout_event_type()}, - timer_types = #{} :: % timer's event type => timer ref - #{timeout_event_type() => reference()}, - cancel_timers = 0 :: non_neg_integer(), - %% We add a timer to both timer_refs and timer_types - %% when we start it. When we request an asynchronous - %% timer cancel we remove it from timer_types. When - %% the timer cancel message arrives we remove it from - %% timer_refs. - %% - hibernate = false :: boolean(), - hibernate_after = infinity :: timeout()}). - --record(trans_opts, - {hibernate = false, - postpone = false, - timeouts_r = [], - next_events_r = []}). + timers = {#{},#{}} :: + {%% TimerRef => TimeoutType + TimerRefs :: #{reference() => timeout_event_type()}, + %% TimeoutType => TimerRef + TimeoutTypes :: #{timeout_event_type() => reference()}}, + hibernate = false :: boolean() + }). %%%========================================================================== %%% API @@ -586,7 +587,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 @@ -658,36 +664,29 @@ 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}, + Q = [{internal,init_state}], %% We enforce {postpone,false} to ensure that %% our fake Event gets discarded, thought it might get logged - NewActions = listify(Actions) ++ [{postpone,false}], - S = - #state{ + Actions_1 = listify(Actions) ++ [{postpone,false}], + P = + #params{ + parent = Parent, module = Module, name = Name, - state = State, - data = Data, hibernate_after = HibernateAfterTimeout}, - CallEnter = true, - NewDebug = ?sys_debug(Debug, {Name,State}, {enter,Event,State}), - case call_callback_mode(S) of - #state{} = NewS -> - loop_event_actions_list( - Parent, NewDebug, NewS, - Events, Event, State, Data, false, - NewActions, CallEnter); - [Class,Reason,Stacktrace] -> - terminate( - Class, Reason, Stacktrace, NewDebug, - S, [Event|Events]) - end. + S = #state{state_data = {State,Data}}, + Debug_1 = ?sys_debug(Debug, Name, {enter,State}), + loop_callback_mode( + P, Debug_1, S, Q, {State,Data}, + %% Tunneling Actions through CallbackEvent here... + %% Special path to go to action handling, after first + %% finding out the callback mode. CallbackEvent is + %% a 2-tuple and Actions a list, which achieves this distinction. + Actions_1). %%%========================================================================== %%% gen callbacks @@ -695,34 +694,46 @@ 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, - #state{name = Name}, - []), + Class, Reason, Stacktrace, Debug, + #params{parent = Parent, name = Name, module = Module}, + #state{}, []), erlang:raise(Class, Reason, Stacktrace) end. %%--------------------------------------------------------------------------- %% 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}), @@ -732,31 +743,34 @@ 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(), - #state{name = Name}, - []), + error, Error, ?STACKTRACE(), Debug, + #params{parent = Parent, name = Name, module = Module}, + #state{}, []), exit(Error) end. %%%========================================================================== %%% sys callbacks +%%% +%%% We use {P,S} as state (Misc) for the sys module, +%%% wrap/unwrap it for the server loop* and update +%%% P#params{parent = Parent}. -system_continue(Parent, Debug, S) -> - loop(Parent, Debug, S). +system_continue(Parent, Debug, {P,S}) -> + loop(update_parent(P, Parent), Debug, S). -system_terminate(Reason, _Parent, Debug, S) -> - terminate(exit, Reason, ?STACKTRACE(), Debug, S, []). +system_terminate(Reason, Parent, Debug, {P,S}) -> + terminate( + exit, Reason, ?STACKTRACE(), + update_parent(P, Parent), Debug, S, []). system_code_change( - #state{ - module = Module, - state = State, - data = Data} = S, + {#params{module = Module} = P, + #state{state_data = {State,Data}} = S}, _Mod, OldVsn, Extra) -> case try Module:code_change(OldVsn, State, Data, Extra) @@ -766,44 +780,54 @@ system_code_change( of {ok,NewState,NewData} -> {ok, - S#state{ - callback_mode = undefined, - state = NewState, - data = NewData}}; + {P#params{callback_mode = undefined}, + S#state{state_data = {NewState,NewData}}}}; {ok,_} = Error -> error({case_clause,Error}); Error -> Error end. -system_get_state(#state{state = State, data = Data}) -> - {ok,{State,Data}}. +system_get_state({_P,#state{state_data = State_Data}}) -> + {ok,State_Data}. system_replace_state( - StateFun, - #state{ - state = State, - data = Data} = S) -> - {NewState,NewData} = Result = StateFun({State,Data}), - {ok,Result,S#state{state = NewState, data = NewData}}. + StateFun, {P,#state{state_data = State_Data} = S}) -> + %% + NewState_NewData = StateFun(State_Data), + {ok,NewState_NewData,{P,S#state{state_data = NewState_NewData}}}. format_status( Opt, [PDict,SysState,Parent,Debug, - #state{name = Name, postponed = P} = S]) -> + {#params{name = Name} = P, + #state{postponed = Postponed} = 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}, {"Parent",Parent}, {"Logged Events",Log}, - {"Postponed",P}]} | - case format_status(Opt, PDict, S) of + {"Postponed",Postponed}]} | + case format_status(Opt, PDict, update_parent(P, Parent), S) of L when is_list(L) -> L; T -> [T] end]. +%% Update #params.parent only if it differs. This should not +%% be possible today (OTP-22.0), but could happen for example +%% if someone implements changing a server's parent +%% in a new sys call. +-compile({inline, update_parent/2}). +update_parent(P, Parent) -> + case P of + #params{parent = Parent} -> + P; + #params{} -> + P#params{parent = Parent} + end. + %%--------------------------------------------------------------------------- %% Format debug messages. Print them as the call-back module sees %% them, not as the real erlang messages. Use trace for that. @@ -812,34 +836,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. @@ -847,964 +883,1169 @@ event_string(Event) -> %%%========================================================================== %%% Internal callbacks -wakeup_from_hibernate(Parent, Debug, S) -> +wakeup_from_hibernate(P, Debug, S) -> %% It is a new message that woke us up so we have to receive it now - loop_receive(Parent, Debug, S). + loop_receive(P, Debug, S). %%%========================================================================== -%%% State Machine engine implementation of proc_lib/gen server +%%% State Machine engine implementation on proc_lib/gen %% Server loop, consists of all loop* functions %% and detours through sys:handle_system_message/7 and proc_lib:hibernate/3 +%% +%% The loop tries to keep all temporary values in arguments +%% and takes shortcuts for ?not_sys_debug, empty lists, etc. +%% The engine state #state{} is picked apart during the loop, +%% new values are kept in arguments, and a new #state{} is +%% composed at the end of the loop. #params{} collect engine +%% state fields that rarely changes. +%% +%% The loop is optimized a bit for staying in the loop, assuming that +%% system events are rare. So a detour to sys requires re-packing +%% of the engine state. %% Entry point for system_continue/3 -loop(Parent, Debug, #state{hibernate = true, cancel_timers = 0} = S) -> - loop_hibernate(Parent, Debug, S); -loop(Parent, Debug, S) -> - loop_receive(Parent, Debug, S). +%% +loop(P, Debug, #state{hibernate = true} = S) -> + loop_hibernate(P, Debug, S); +loop(P, Debug, S) -> + loop_receive(P, Debug, S). -loop_hibernate(Parent, Debug, S) -> +%% Go to hibernation +%% +loop_hibernate(P, Debug, S) -> %% %% Does not return but restarts process at %% wakeup_from_hibernate/3 that jumps to loop_receive/3 %% - proc_lib:hibernate( - ?MODULE, wakeup_from_hibernate, [Parent,Debug,S]), + proc_lib:hibernate(?MODULE, wakeup_from_hibernate, [P, Debug, S]), error( {should_not_have_arrived_here_but_instead_in, - {wakeup_from_hibernate,3}}). + {?MODULE,wakeup_from_hibernate,3}}). + %% Entry point for wakeup_from_hibernate/3 +%% +%% Receive a new process message +%% loop_receive( - Parent, Debug, #state{hibernate_after = HibernateAfterTimeout} = S) -> + #params{hibernate_after = HibernateAfterTimeout} = P, Debug, S) -> %% receive Msg -> case Msg of + {'$gen_call',From,Request} -> + loop_receive_result(P, Debug, S, {{call,From},Request}); + {'$gen_cast',Cast} -> + loop_receive_result(P, Debug, S, {cast,Cast}); + %% + {timeout,TimerRef,TimeoutMsg} -> + {TimerRefs,TimeoutTypes} = S#state.timers, + case TimerRefs of + #{TimerRef := TimeoutType} -> + %% Our timer + Timers = + {maps:remove(TimerRef, TimerRefs), + maps:remove(TimeoutType, TimeoutTypes)}, + S_1 = S#state{timers = Timers}, + loop_receive_result( + P, Debug, S_1, {TimeoutType,TimeoutMsg}); + #{} -> + loop_receive_result(P, Debug, S, {info,Msg}) + end; + %% {system,Pid,Req} -> %% Does not return but tail recursively calls %% system_continue/3 that jumps to loop/3 sys:handle_system_msg( - Req, Pid, Parent, ?MODULE, Debug, S, + Req, Pid, P#params.parent, ?MODULE, Debug, + {P,S}, S#state.hibernate); - {'EXIT',Parent,Reason} = EXIT -> - %% EXIT is not a 2-tuple therefore - %% not an event but this will stand out - %% in the crash report... - Q = [EXIT], - terminate(exit, Reason, ?STACKTRACE(), Debug, S, Q); - {timeout,TimerRef,TimerMsg} -> - #state{ - timer_refs = TimerRefs, - timer_types = TimerTypes} = S, - case TimerRefs of - #{TimerRef := TimerType} -> - %% We know of this timer; is it a running - %% timer or a timer being cancelled that - %% managed to send a late timeout message? - case TimerTypes of - #{TimerType := TimerRef} -> - %% The timer type maps back to this - %% timer ref, so it was a running timer - %% Unregister the triggered timeout - NewTimerRefs = - maps:remove(TimerRef, TimerRefs), - NewTimerTypes = - maps:remove(TimerType, TimerTypes), - loop_receive_result( - Parent, Debug, - S#state{ - timer_refs = NewTimerRefs, - timer_types = NewTimerTypes}, - TimerType, TimerMsg); - _ -> - %% This was a late timeout message - %% from timer being cancelled, so - %% ignore it and expect a cancel_timer - %% msg shortly - loop_receive(Parent, Debug, S) - end; - _ -> - %% Not our timer; present it as an event - loop_receive_result(Parent, Debug, S, info, Msg) - end; - {cancel_timer,TimerRef,_} -> - #state{ - timer_refs = TimerRefs, - cancel_timers = CancelTimers, - hibernate = Hibernate} = S, - case TimerRefs of - #{TimerRef := _} -> - %% We must have requested a cancel - %% of this timer so it is already - %% removed from TimerTypes - NewTimerRefs = - maps:remove(TimerRef, TimerRefs), - NewCancelTimers = CancelTimers - 1, - NewS = - S#state{ - timer_refs = NewTimerRefs, - cancel_timers = NewCancelTimers}, - if - Hibernate =:= true, NewCancelTimers =:= 0 -> - %% No more cancel_timer msgs to expect; - %% we can hibernate - loop_hibernate(Parent, Debug, NewS); - NewCancelTimers >= 0 -> % Assert - loop_receive(Parent, Debug, NewS) - end; - _ -> - %% Not our cancel_timer msg; - %% present it as an event - loop_receive_result(Parent, Debug, S, info, Msg) - end; - _ -> - %% External msg - case Msg of - {'$gen_call',From,Request} -> - loop_receive_result( - Parent, Debug, S, {call,From}, Request); - {'$gen_cast',Cast} -> - loop_receive_result(Parent, Debug, S, cast, Cast); + {'EXIT',Pid,Reason} -> + case P#params.parent of + Pid -> + terminate( + exit, Reason, ?STACKTRACE(), P, Debug, S, []); _ -> - loop_receive_result(Parent, Debug, S, info, Msg) - end + loop_receive_result(P, Debug, S, {info,Msg}) + end; + %% + _ -> + loop_receive_result(P, Debug, S, {info,Msg}) end after - HibernateAfterTimeout -> - loop_hibernate(Parent, Debug, S) + HibernateAfterTimeout -> + loop_hibernate(P, Debug, S) end. -loop_receive_result(Parent, ?not_sys_debug, S, Type, Content) -> +%% We have received an event +%% +loop_receive_result(P, ?not_sys_debug = Debug, S, Event) -> %% Here is the queue of not yet handled events created Events = [], - loop_event(Parent, ?not_sys_debug, S, Events, Type, Content); + loop_event(P, Debug, S, Event, Events); loop_receive_result( - Parent, Debug, #state{name = Name, state = State} = S, Type, Content) -> - NewDebug = sys_debug(Debug, {Name,State}, {in,{Type,Content}}), + #params{name = Name, callback_mode = CallbackMode} = P, Debug, + #state{state_data = {State,_Data}} = S, Event) -> + Debug_1 = + case CallbackMode 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). + loop_event(P, Debug_1, S, Event, Events). -%% Entry point for handling an event, received or enqueued +%% Handle one event; received or enqueued +%% loop_event( - Parent, Debug, #state{hibernate = Hibernate} = S, - Events, Type, Content) -> + P, Debug, #state{hibernate = true} = S, Event, Events) -> %% - case Hibernate of - true -> - %% - %% If (this old) Hibernate is true here it can only be - %% because it was set from an event action - %% and we did not go into hibernation since there were - %% events in queue, so we do what the user - %% might rely on i.e collect garbage which - %% would have happened if we actually hibernated - %% and immediately was awakened. - %% - _ = garbage_collect(), - loop_event_state_function( - Parent, Debug, S, Events, Type, Content); - false -> - loop_event_state_function( - Parent, Debug, S, Events, Type, Content) - end. + %% If (this old) Hibernate is true here it can only be + %% because it was set from an event action + %% and we did not go into hibernation since there were + %% events in queue, so we do what the user + %% might rely on i.e collect garbage which + %% would have happened if we actually hibernated + %% and immediately was awakened. + %% + _ = garbage_collect(), + loop_event_handler(P, Debug, S, Event, Events); +loop_event(P, Debug, S, Event, Events) -> + loop_event_handler(P, Debug, S, Event, Events). -%% Call the state function -loop_event_state_function( - Parent, Debug, - #state{state = State, data = Data} = S, - Events, Type, Content) -> +%% Call the state function, eventually +%% +-compile({inline, [loop_event_handler/5]}). +loop_event_handler( + P, Debug, #state{state_data = State_Data} = S, Event, Events) -> %% %% The field 'hibernate' in S is now invalid and will be - %% restored when looping back to loop/3 or loop_event/6. + %% restored when looping back to loop/3 or loop_event/5. %% - Event = {Type,Content}, - TransOpts = false, - case call_state_function(S, Type, Content, State, Data) of - {Result, NewS} -> - loop_event_result( - Parent, Debug, NewS, - Events, Event, State, Data, TransOpts, Result); - [Class,Reason,Stacktrace] -> - terminate( - Class, Reason, Stacktrace, Debug, S, [Event|Events]) - end. + Q = [Event|Events], + loop_callback_mode(P, Debug, S, Q, State_Data, Event). -%% Make a state enter call to the state function -loop_event_state_enter( - Parent, Debug, #state{state = PrevState} = S, - Events, Event, NextState, NewData, TransOpts) -> +%% Figure out the callback mode +%% +loop_callback_mode( + #params{callback_mode = undefined} = P, Debug, S, + Q, State_Data, CallbackEvent) -> %% - case call_state_function(S, enter, PrevState, NextState, NewData) of - {Result, NewS} -> - loop_event_result( - Parent, Debug, NewS, - Events, Event, NextState, NewData, TransOpts, Result); - [Class,Reason,Stacktrace] -> + Module = P#params.module, + try Module:callback_mode() of + CallbackMode -> + loop_callback_mode_result( + P, Debug, S, + Q, State_Data, CallbackEvent, + CallbackMode, listify(CallbackMode), undefined, false) + catch + CallbackMode -> + loop_callback_mode_result( + P, Debug, S, + Q, State_Data, CallbackEvent, + CallbackMode, listify(CallbackMode), undefined, false); + Class:Reason:Stacktrace -> terminate( - Class, Reason, Stacktrace, Debug, S, [Event|Events]) + Class, Reason, Stacktrace, P, Debug, S, Q) + end; +loop_callback_mode(P, Debug, S, Q, State_Data, CallbackEvent) -> + loop_state_callback(P, Debug, S, Q, State_Data, CallbackEvent). + +%% Check the result of Module:callback_mode() +%% +loop_callback_mode_result( + P, Debug, S, Q, State_Data, CallbackEvent, + CallbackMode, [H|T], NewCallbackMode, NewStateEnter) -> + %% + case callback_mode(H) of + true -> + loop_callback_mode_result( + P, Debug, S, Q, State_Data, CallbackEvent, + CallbackMode, T, H, NewStateEnter); + false -> + case state_enter(H) of + true -> + loop_callback_mode_result( + P, Debug, S, Q, State_Data, CallbackEvent, + CallbackMode, T, NewCallbackMode, true); + false -> + terminate( + error, + {bad_return_from_callback_mode,CallbackMode}, + ?STACKTRACE(), + P, Debug, S, Q) + end + end; +loop_callback_mode_result( + P, Debug, S, Q, State_Data, CallbackEvent, + CallbackMode, [], NewCallbackMode, NewStateEnter) -> + %% + case NewCallbackMode of + undefined -> + terminate( + error, + {bad_return_from_callback_mode,CallbackMode}, + ?STACKTRACE(), + P, Debug, S, Q); + _ -> + P_1 = + P#params{ + callback_mode = NewCallbackMode, + state_enter = NewStateEnter}, + loop_state_callback( + P_1, Debug, S, Q, State_Data, CallbackEvent) end. -%% Process the result from the state function. -%% When TransOpts =:= false it was a state function call, -%% otherwise it is an option tuple and it was a state enter call. + +%% Make a state enter call to the state function, we loop back here +%% from further down if state enter calls are enabled +%% +loop_state_enter( + P, Debug, #state{state_data = {PrevState,_PrevData}} = S, + Q, NextState_NewData, + NextEventsR, Hibernate, TimeoutsR, Postpone) -> + %% + StateCall = false, + CallbackEvent = {enter,PrevState}, + loop_state_callback( + P, Debug, S, Q, NextState_NewData, + NextEventsR, Hibernate, TimeoutsR, Postpone, + StateCall, CallbackEvent). + +%% Make a state call (not state enter call) to the state function +%% +loop_state_callback(P, Debug, S, Q, State_Data, CallbackEvent) -> + NextEventsR = [], + Hibernate = false, + TimeoutsR = [], + Postpone = false, + StateCall = true, + loop_state_callback( + P, Debug, S, Q, State_Data, + NextEventsR, Hibernate, TimeoutsR, Postpone, + StateCall, CallbackEvent). +%% +loop_state_callback( + #params{callback_mode = CallbackMode, module = Module} = P, + Debug, S, Q, {State,Data} = State_Data, + NextEventsR, Hibernate, TimeoutsR, Postpone, + StateCall, {Type,Content}) -> + try + case CallbackMode of + state_functions -> + Module:State(Type, Content, Data); + handle_event_function -> + Module:handle_event(Type, Content, State, Data) + end + of + Result -> + loop_state_callback_result( + P, Debug, S, Q, State_Data, + NextEventsR, Hibernate, TimeoutsR, Postpone, + StateCall, Result) + catch + Result -> + loop_state_callback_result( + P, Debug, S, Q, State_Data, + NextEventsR, Hibernate, TimeoutsR, Postpone, + StateCall, Result); + Class:Reason:Stacktrace -> + terminate(Class, Reason, Stacktrace, P, Debug, S, Q) + end; +loop_state_callback( + P, Debug, S, Q, State_Data, + NextEventsR, Hibernate, TimeoutsR, Postpone, + StateCall, Actions) when is_list(Actions) -> + %% Tunneled actions from enter/8 + CallEnter = true, + loop_actions_list( + P, Debug, S, Q, State_Data, + NextEventsR, Hibernate, TimeoutsR, Postpone, + CallEnter, StateCall, Actions). + +%% Process the result from the state function %% -loop_event_result( - Parent, Debug, S, - Events, Event, State, Data, TransOpts, Result) -> +loop_state_callback_result( + P, Debug, S, Q, {State,_Data} = State_Data, + NextEventsR, Hibernate, TimeoutsR, Postpone, + StateCall, Result) -> %% case Result of {next_state,State,NewData} -> - loop_event_actions( - Parent, Debug, S, - Events, Event, State, NewData, TransOpts, - [], false); + loop_actions( + P, Debug, S, Q, {State,NewData}, + NextEventsR, Hibernate, TimeoutsR, Postpone, + false); {next_state,NextState,NewData} - when TransOpts =:= false -> - loop_event_actions( - Parent, Debug, S, - Events, Event, NextState, NewData, TransOpts, - [], true); + when StateCall -> + loop_actions( + P, Debug, S, Q, {NextState,NewData}, + NextEventsR, Hibernate, TimeoutsR, Postpone, + true); {next_state,_NextState,_NewData} -> terminate( error, {bad_state_enter_return_from_state_function,Result}, - ?STACKTRACE(), Debug, + ?STACKTRACE(), P, Debug, S#state{ - state = State, data = Data, - hibernate = hibernate_in_trans_opts(TransOpts)}, - [Event|Events]); + state_data = State_Data, + hibernate = Hibernate}, + Q); {next_state,State,NewData,Actions} -> - loop_event_actions( - Parent, Debug, S, - Events, Event, State, NewData, TransOpts, - Actions, false); + loop_actions( + P, Debug, S, Q, {State,NewData}, + NextEventsR, Hibernate, TimeoutsR, Postpone, + false, StateCall, Actions); {next_state,NextState,NewData,Actions} - when TransOpts =:= false -> - loop_event_actions( - Parent, Debug, S, - Events, Event, NextState, NewData, TransOpts, - Actions, true); + when StateCall -> + loop_actions( + P, Debug, S, Q, {NextState,NewData}, + NextEventsR, Hibernate, TimeoutsR, Postpone, + true, StateCall, Actions); {next_state,_NextState,_NewData,_Actions} -> terminate( error, {bad_state_enter_return_from_state_function,Result}, - ?STACKTRACE(), Debug, + ?STACKTRACE(), P, Debug, S#state{ - state = State, data = Data, - hibernate = hibernate_in_trans_opts(TransOpts)}, - [Event|Events]); + state_data = State_Data, + hibernate = Hibernate}, + Q); %% {keep_state,NewData} -> - loop_event_actions( - Parent, Debug, S, - Events, Event, State, NewData, TransOpts, - [], false); + loop_actions( + P, Debug, S, Q, {State,NewData}, + NextEventsR, Hibernate, TimeoutsR, Postpone, + false); {keep_state,NewData,Actions} -> - loop_event_actions( - Parent, Debug, S, - Events, Event, State, NewData, TransOpts, - Actions, false); + loop_actions( + P, Debug, S, Q, {State,NewData}, + NextEventsR, Hibernate, TimeoutsR, Postpone, + false, StateCall, Actions); %% keep_state_and_data -> - loop_event_actions( - Parent, Debug, S, - Events, Event, State, Data, TransOpts, - [], false); + loop_actions( + P, Debug, S, Q, State_Data, + NextEventsR, Hibernate, TimeoutsR, Postpone, + false); {keep_state_and_data,Actions} -> - loop_event_actions( - Parent, Debug, S, - Events, Event, State, Data, TransOpts, - Actions, false); + loop_actions( + P, Debug, S, Q, State_Data, + NextEventsR, Hibernate, TimeoutsR, Postpone, + false, StateCall, Actions); %% {repeat_state,NewData} -> - loop_event_actions( - Parent, Debug, S, - Events, Event, State, NewData, TransOpts, - [], true); + loop_actions( + P, Debug, S, Q, {State,NewData}, + NextEventsR, Hibernate, TimeoutsR, Postpone, + true); {repeat_state,NewData,Actions} -> - loop_event_actions( - Parent, Debug, S, - Events, Event, State, NewData, TransOpts, - Actions, true); + loop_actions( + P, Debug, S, Q, {State,NewData}, + NextEventsR, Hibernate, TimeoutsR, Postpone, + true, StateCall, Actions); %% repeat_state_and_data -> - loop_event_actions( - Parent, Debug, S, - Events, Event, State, Data, TransOpts, - [], true); + loop_actions( + P, Debug, S, Q, State_Data, + NextEventsR, Hibernate, TimeoutsR, Postpone, + true); {repeat_state_and_data,Actions} -> - loop_event_actions( - Parent, Debug, S, - Events, Event, State, Data, TransOpts, - Actions, true); + loop_actions( + P, Debug, S, Q, State_Data, + NextEventsR, Hibernate, TimeoutsR, Postpone, + true, StateCall, Actions); %% stop -> terminate( - exit, normal, ?STACKTRACE(), Debug, + exit, normal, ?STACKTRACE(), P, Debug, S#state{ - state = State, data = Data, - hibernate = hibernate_in_trans_opts(TransOpts)}, - [Event|Events]); + state_data = State_Data, + hibernate = Hibernate}, + Q); {stop,Reason} -> terminate( - exit, Reason, ?STACKTRACE(), Debug, + exit, Reason, ?STACKTRACE(), P, Debug, S#state{ - state = State, data = Data, - hibernate = hibernate_in_trans_opts(TransOpts)}, - [Event|Events]); + state_data = State_Data, + hibernate = Hibernate}, + Q); {stop,Reason,NewData} -> terminate( - exit, Reason, ?STACKTRACE(), Debug, + exit, Reason, ?STACKTRACE(), P, Debug, S#state{ - state = State, data = NewData, - hibernate = hibernate_in_trans_opts(TransOpts)}, - [Event|Events]); + state_data = {State,NewData}, + hibernate = Hibernate}, + Q); %% {stop_and_reply,Reason,Replies} -> reply_then_terminate( - exit, Reason, ?STACKTRACE(), Debug, + exit, Reason, ?STACKTRACE(), P, Debug, S#state{ - state = State, data = Data, - hibernate = hibernate_in_trans_opts(TransOpts)}, - [Event|Events], Replies); + state_data = State_Data, + hibernate = Hibernate}, + Q, Replies); {stop_and_reply,Reason,Replies,NewData} -> reply_then_terminate( - exit, Reason, ?STACKTRACE(), Debug, + exit, Reason, ?STACKTRACE(), P, Debug, S#state{ - state = State, data = NewData, - hibernate = hibernate_in_trans_opts(TransOpts)}, - [Event|Events], Replies); + state_data = {State,NewData}, + hibernate = Hibernate}, + Q, Replies); %% _ -> terminate( error, {bad_return_from_state_function,Result}, - ?STACKTRACE(), Debug, + ?STACKTRACE(), P, Debug, S#state{ - state = State, data = Data, - hibernate = hibernate_in_trans_opts(TransOpts)}, - [Event|Events]) + state_data = State_Data, + hibernate = Hibernate}, + Q) end. %% Ensure that Actions are a list -loop_event_actions( - Parent, Debug, S, - Events, Event, NextState, NewerData, TransOpts, - Actions, CallEnter) -> - loop_event_actions_list( - Parent, Debug, S, - Events, Event, NextState, NewerData, TransOpts, - listify(Actions), CallEnter). - -%% Process actions from the state function -loop_event_actions_list( - Parent, Debug, #state{state_enter = StateEnter} = S, - Events, Event, NextState, NewerData, TransOpts, - Actions, CallEnter) -> +%% +loop_actions( + P, Debug, S, Q, NextState_NewData, + NextEventsR, Hibernate, TimeoutsR, Postpone, + CallEnter, _StateCall, []) -> + loop_actions( + P, Debug, S, Q, NextState_NewData, + NextEventsR, Hibernate, TimeoutsR, Postpone, + CallEnter); +loop_actions( + P, Debug, S, Q, NextState_NewData, + NextEventsR, Hibernate, TimeoutsR, Postpone, + CallEnter, StateCall, Actions) -> %% - case parse_actions(TransOpts, Debug, S, Actions) of - {NewDebug,NewTransOpts} - when StateEnter, CallEnter -> - loop_event_state_enter( - Parent, NewDebug, S, - Events, Event, NextState, NewerData, NewTransOpts); - {NewDebug,NewTransOpts} -> - loop_event_done( - Parent, NewDebug, S, - Events, Event, NextState, NewerData, NewTransOpts); - [Class,Reason,Stacktrace,NewDebug] -> - terminate( - Class, Reason, Stacktrace, NewDebug, - S#state{ - state = NextState, - data = NewerData, - hibernate = hibernate_in_trans_opts(TransOpts)}, - [Event|Events]) + loop_actions_list( + P, Debug, S, Q, NextState_NewData, + NextEventsR, Hibernate, TimeoutsR, Postpone, + CallEnter, StateCall, listify(Actions)). +%% +%% Shortcut for no actions +-compile({inline, [loop_actions/10]}). +loop_actions( + P, Debug, S, Q, NextState_NewData, + NextEventsR, Hibernate, TimeoutsR, Postpone, + CallEnter) -> + %% + %% Shortcut for no actions + case CallEnter andalso P#params.state_enter of + true -> + loop_state_enter( + P, Debug, S, Q, NextState_NewData, + NextEventsR, Hibernate, TimeoutsR, Postpone); + false -> + loop_state_transition( + P, Debug, S, Q, NextState_NewData, + NextEventsR, Hibernate, TimeoutsR, Postpone) end. --compile({inline, [hibernate_in_trans_opts/1]}). -hibernate_in_trans_opts(false) -> - (#trans_opts{})#trans_opts.hibernate; -hibernate_in_trans_opts(#trans_opts{hibernate = Hibernate}) -> - Hibernate. - -parse_actions(false, Debug, S, Actions) -> - parse_actions(true, Debug, S, Actions, #trans_opts{}); -parse_actions(TransOpts, Debug, S, Actions) -> - parse_actions(false, Debug, S, Actions, TransOpts). +%% Process the returned actions %% -parse_actions(_StateCall, Debug, _S, [], TransOpts) -> - {Debug,TransOpts}; -parse_actions(StateCall, Debug, S, [Action|Actions], TransOpts) -> +loop_actions_list( + P, Debug, S, Q, NextState_NewData, + NextEventsR, Hibernate, TimeoutsR, Postpone, + CallEnter, _StateCall, []) -> + %% + case P#params.state_enter of + true when CallEnter -> + loop_state_enter( + P, Debug, S, Q, NextState_NewData, + NextEventsR, Hibernate, TimeoutsR, Postpone); + _ -> + loop_state_transition( + P, Debug, S, Q, NextState_NewData, + NextEventsR, Hibernate, TimeoutsR, Postpone) + end; +loop_actions_list( + P, Debug, S, Q, NextState_NewData, + NextEventsR, Hibernate, TimeoutsR, Postpone, + CallEnter, StateCall, [Action|Actions]) -> + %% case Action of %% Actual actions {reply,From,Reply} -> - parse_actions_reply( - StateCall, Debug, S, Actions, TransOpts, From, Reply); + loop_actions_reply( + P, Debug, S, Q, NextState_NewData, + NextEventsR, Hibernate, TimeoutsR, Postpone, + CallEnter, StateCall, Actions, + From, Reply); %% %% Actions that set options - {hibernate,NewHibernate} when is_boolean(NewHibernate) -> - parse_actions( - StateCall, Debug, S, Actions, - TransOpts#trans_opts{hibernate = NewHibernate}); + {hibernate,Hibernate_1} when is_boolean(Hibernate_1) -> + loop_actions_list( + P, Debug, S, Q, NextState_NewData, + NextEventsR, Hibernate_1, TimeoutsR, Postpone, + CallEnter, StateCall, Actions); hibernate -> - parse_actions( - StateCall, Debug, S, Actions, - TransOpts#trans_opts{hibernate = true}); + loop_actions_list( + P, Debug, S, Q, NextState_NewData, + NextEventsR, true, TimeoutsR, Postpone, + CallEnter, StateCall, Actions); %% - {postpone,NewPostpone} when not NewPostpone orelse StateCall -> - parse_actions( - StateCall, Debug, S, Actions, - TransOpts#trans_opts{postpone = NewPostpone}); + {postpone,Postpone_1} when not Postpone_1 orelse StateCall -> + loop_actions_list( + P, Debug, S, Q, NextState_NewData, + NextEventsR, Hibernate, TimeoutsR, Postpone_1, + CallEnter, StateCall, Actions); postpone when StateCall -> - parse_actions( - StateCall, Debug, S, Actions, - TransOpts#trans_opts{postpone = true}); + loop_actions_list( + P, Debug, S, Q, NextState_NewData, + NextEventsR, Hibernate, TimeoutsR, true, + CallEnter, StateCall, Actions); postpone -> - [error, - {bad_state_enter_action_from_state_function,Action}, - ?STACKTRACE(), - Debug]; + terminate( + error, + {bad_state_enter_action_from_state_function,Action}, + ?STACKTRACE(), P, Debug, + S#state{ + state_data = NextState_NewData, + hibernate = Hibernate}, + Q); %% {next_event,Type,Content} -> - parse_actions_next_event( - StateCall, Debug, S, Actions, TransOpts, Type, Content); + loop_actions_next_event( + P, Debug, S, Q, NextState_NewData, + NextEventsR, Hibernate, TimeoutsR, Postpone, + CallEnter, StateCall, Actions, Type, Content); %% - _ -> - parse_actions_timeout( - StateCall, Debug, S, Actions, TransOpts, Action) + Timeout -> + loop_actions_timeout( + P, Debug, S, Q, NextState_NewData, + NextEventsR, Hibernate, TimeoutsR, Postpone, + CallEnter, StateCall, Actions, Timeout) end. -parse_actions_reply( - StateCall, ?not_sys_debug = Debug, S, Actions, TransOpts, +%% Process a reply action +%% +loop_actions_reply( + P, Debug, S, Q, NextState_NewData, + NextEventsR, Hibernate, TimeoutsR, Postpone, + CallEnter, StateCall, Actions, From, Reply) -> %% case from(From) of true -> + %% No need for a separate ?not_sys_debug clause here + %% since the external call to erlang:'!'/2 in reply/2 + %% will cause swap out of all live registers anyway reply(From, Reply), - parse_actions(StateCall, ?not_sys_debug, S, Actions, TransOpts); - false -> - [error, - {bad_action_from_state_function,{reply,From,Reply}}, - ?STACKTRACE(), Debug] - end; -parse_actions_reply( - StateCall, Debug, #state{name = Name, state = State} = S, - Actions, TransOpts, From, Reply) -> - %% - case from(From) of - true -> - reply(From, Reply), - NewDebug = sys_debug(Debug, {Name,State}, {out,Reply,From}), - parse_actions(StateCall, NewDebug, S, Actions, TransOpts); + Debug_1 = ?sys_debug(Debug, P#params.name, {out,Reply,From}), + loop_actions_list( + P, Debug_1, S, Q, NextState_NewData, + NextEventsR, Hibernate, TimeoutsR, Postpone, + CallEnter, StateCall, Actions); false -> - [error, - {bad_action_from_state_function,{reply,From,Reply}}, - ?STACKTRACE(), Debug] + terminate( + error, + {bad_action_from_state_function,{reply,From,Reply}}, + ?STACKTRACE(), P, Debug, + S#state{ + state_data = NextState_NewData, + hibernate = Hibernate}, + Q) end. -parse_actions_next_event( - StateCall, ?not_sys_debug = Debug, S, - Actions, TransOpts, Type, Content) -> - case event_type(Type) of - true when StateCall -> - NextEventsR = TransOpts#trans_opts.next_events_r, - parse_actions( - StateCall, ?not_sys_debug, S, Actions, - TransOpts#trans_opts{ - next_events_r = [{Type,Content}|NextEventsR]}); - _ -> - [error, - {bad_state_enter_action_from_state_function, - {next_event,Type,Content}}, - ?STACKTRACE(), Debug] - end; -parse_actions_next_event( - StateCall, Debug, #state{name = Name, state = State} = S, - Actions, TransOpts, Type, Content) -> +%% Process a next_event action +%% +loop_actions_next_event( + P, Debug, S, Q, NextState_NewData, + NextEventsR, Hibernate, TimeoutsR, Postpone, + CallEnter, StateCall, Actions, Type, Content) -> case event_type(Type) of true when StateCall -> - NewDebug = sys_debug(Debug, {Name,State}, {in,{Type,Content}}), - NextEventsR = TransOpts#trans_opts.next_events_r, - parse_actions( - StateCall, NewDebug, S, Actions, - TransOpts#trans_opts{ - next_events_r = [{Type,Content}|NextEventsR]}); + NextEvent = {Type,Content}, + case Debug of + ?not_sys_debug -> + loop_actions_list( + P, Debug, S, Q, NextState_NewData, + [NextEvent|NextEventsR], + Hibernate, TimeoutsR, Postpone, + CallEnter, StateCall, Actions); + _ -> + Name = P#params.name, + {State,_Data} = S#state.state_data, + Debug_1 = + sys_debug(Debug, Name, {in,{Type,Content},State}), + loop_actions_list( + P, Debug_1, S, Q, NextState_NewData, + [NextEvent|NextEventsR], + Hibernate, TimeoutsR, Postpone, + CallEnter, StateCall, Actions) + end; _ -> - [error, - {bad_state_enter_action_from_state_function, - {next_event,Type,Content}}, - ?STACKTRACE(), - Debug] + terminate( + error, + {if + StateCall -> + bad_action_from_state_function; + true -> + bad_state_enter_action_from_state_function + end, + {next_event,Type,Content}}, + ?STACKTRACE(), P, Debug, + S#state{ + state_data = NextState_NewData, + hibernate = Hibernate}, + Q) end. -parse_actions_timeout( - StateCall, Debug, S, Actions, TransOpts, - {TimeoutType,Time,TimerMsg,TimerOpts} = AbsoluteTimeout) -> +%% Process a timeout action, or also any unrecognized action +%% +loop_actions_timeout( + P, Debug, S, Q, NextState_NewData, + NextEventsR, Hibernate, TimeoutsR, Postpone, + CallEnter, StateCall, Actions, + {TimeoutType,Time,TimeoutMsg,TimeoutOpts} = Timeout) -> %% - case classify_timeout(TimeoutType, Time, listify(TimerOpts)) of - absolute -> - parse_actions_timeout_add( - StateCall, Debug, S, Actions, - TransOpts, AbsoluteTimeout); - relative -> - RelativeTimeout = {TimeoutType,Time,TimerMsg}, - parse_actions_timeout_add( - StateCall, Debug, S, Actions, - TransOpts, RelativeTimeout); - badarg -> - [error, - {bad_action_from_state_function,AbsoluteTimeout}, - ?STACKTRACE(), - Debug] + case timeout_event_type(TimeoutType) of + true -> + case listify(TimeoutOpts) of + %% Optimization cases + [] when ?relative_timeout(Time) -> + RelativeTimeout = {TimeoutType,Time,TimeoutMsg}, + loop_actions_list( + P, Debug, S, Q, NextState_NewData, + NextEventsR, Hibernate, + [RelativeTimeout|TimeoutsR], Postpone, + CallEnter, StateCall, Actions); + [{abs,true}] when ?absolute_timeout(Time) -> + loop_actions_list( + P, Debug, S, Q, NextState_NewData, + NextEventsR, Hibernate, + [Timeout|TimeoutsR], Postpone, + CallEnter, StateCall, Actions); + [{abs,false}] when ?relative_timeout(Time) -> + RelativeTimeout = {TimeoutType,Time,TimeoutMsg}, + loop_actions_list( + P, Debug, S, Q, NextState_NewData, + NextEventsR, Hibernate, + [RelativeTimeout|TimeoutsR], Postpone, + CallEnter, StateCall, Actions); + %% Generic case + TimeoutOptsList -> + case parse_timeout_opts_abs(TimeoutOptsList) of + true when ?absolute_timeout(Time) -> + loop_actions_list( + P, Debug, S, Q, NextState_NewData, + NextEventsR, Hibernate, + [Timeout|TimeoutsR], Postpone, + CallEnter, StateCall, Actions); + false when ?relative_timeout(Time) -> + RelativeTimeout = + {TimeoutType,Time,TimeoutMsg}, + loop_actions_list( + P, Debug, S, Q, NextState_NewData, + NextEventsR, Hibernate, + [RelativeTimeout|TimeoutsR], Postpone, + CallEnter, StateCall, Actions); + badarg -> + terminate( + error, + {bad_action_from_state_function,Timeout}, + ?STACKTRACE(), P, Debug, + S#state{ + state_data = NextState_NewData, + hibernate = Hibernate}, + Q) + end + end; + false -> + terminate( + error, + {bad_action_from_state_function,Timeout}, + ?STACKTRACE(), P, Debug, + S#state{ + state_data = NextState_NewData, + hibernate = Hibernate}, + Q) end; -parse_actions_timeout( - StateCall, Debug, S, Actions, TransOpts, - {TimeoutType,Time,_} = RelativeTimeout) -> - case classify_timeout(TimeoutType, Time, []) of - relative -> - parse_actions_timeout_add( - StateCall, Debug, S, Actions, - TransOpts, RelativeTimeout); - badarg -> - [error, - {bad_action_from_state_function,RelativeTimeout}, - ?STACKTRACE(), - Debug] +loop_actions_timeout( + P, Debug, S, Q, NextState_NewData, + NextEventsR, Hibernate, TimeoutsR, Postpone, + CallEnter, StateCall, Actions, + {TimeoutType,Time,_} = Timeout) -> + %% + case timeout_event_type(TimeoutType) of + true when ?relative_timeout(Time) -> + loop_actions_list( + P, Debug, S, Q, NextState_NewData, + NextEventsR, Hibernate, + [Timeout|TimeoutsR], Postpone, + CallEnter, StateCall, Actions); + _ -> + terminate( + error, + {bad_action_from_state_function,Timeout}, + ?STACKTRACE(), P, Debug, + S#state{ + state_data = NextState_NewData, + hibernate = Hibernate}, + Q) end; -parse_actions_timeout( - StateCall, Debug, S, Actions, TransOpts, - Time) -> - case classify_timeout(timeout, Time, []) of - relative -> +loop_actions_timeout( + P, Debug, S, Q, NextState_NewData, + NextEventsR, Hibernate, TimeoutsR, Postpone, + CallEnter, StateCall, Actions, Time) -> + %% + if + ?relative_timeout(Time) -> RelativeTimeout = {timeout,Time,Time}, - parse_actions_timeout_add( - StateCall, Debug, S, Actions, - TransOpts, RelativeTimeout); - badarg -> - [error, - {bad_action_from_state_function,Time}, - ?STACKTRACE(), - Debug] + loop_actions_list( + P, Debug, S, Q, NextState_NewData, + NextEventsR, Hibernate, + [RelativeTimeout|TimeoutsR], Postpone, + CallEnter, StateCall, Actions); + true -> + terminate( + error, + {bad_action_from_state_function,Time}, + ?STACKTRACE(), P, Debug, + S#state{ + state_data = NextState_NewData, + hibernate = Hibernate}, + Q) end. -parse_actions_timeout_add( - StateCall, Debug, S, Actions, - #trans_opts{timeouts_r = TimeoutsR} = TransOpts, Timeout) -> - parse_actions( - StateCall, Debug, S, Actions, - TransOpts#trans_opts{timeouts_r = [Timeout|TimeoutsR]}). - %% Do the state transition -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 = NextEventsR}) -> - %% - %% Optimize the simple cases i.e no debug and no timer changes, - %% by duplicate stripped down code - %% - %% Fast path - %% - case Postpone of - true -> - loop_event_done_fast( - Parent, Hibernate, S, - Events, [Event|P], NextState, NewData, NextEventsR); - false -> - loop_event_done_fast( - Parent, Hibernate, S, - Events, P, NextState, NewData, NextEventsR) - end; -loop_event_done( - Parent, Debug_0, - #state{ - state = State, postponed = P_0, - timer_refs = TimerRefs_0, timer_types = TimerTypes_0, - cancel_timers = CancelTimers_0} = S, - Events_0, Event_0, NextState, NewData, - #trans_opts{ - hibernate = Hibernate, timeouts_r = TimeoutsR, - postpone = Postpone, next_events_r = NextEventsR}) -> +%% +loop_state_transition( + P, Debug, #state{state_data = {State,_Data}, postponed = Postponed} = S, + [Event|Events], {NextState,_NewData} = NextState_NewData, + NextEventsR, Hibernate, TimeoutsR, Postpone) -> %% %% All options have been collected and next_events are buffered. %% Do the actual state transition. %% - %% Full feature path - %% - [Debug_1|P_1] = % Move current event to postponed if Postpone + Postponed_1 = % Move current event to postponed if Postpone case Postpone of true -> - [?sys_debug( - Debug_0, - {S#state.name,State}, - {postpone,Event_0,NextState}), - Event_0|P_0]; + [Event|Postponed]; false -> - [?sys_debug( - Debug_0, - {S#state.name,State}, - {consume,Event_0,NextState})|P_0] + Postponed end, - {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 -> - %% 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}))} - 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), - loop_event_done( - Parent, Debug_1, - S#state{ - state = NextState, - data = NewData, - postponed = P_2, - timer_refs = TimerRefs_3, - timer_types = TimerTypes_3, - cancel_timers = CancelTimers_3, - 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) + case Debug of + ?not_sys_debug -> + %% Optimization for no sys_debug + %% - avoid calling sys_debug/3 + if + NextState =:= State -> + loop_keep_state( + P, Debug, S, + Events, NextState_NewData, + NextEventsR, Hibernate, TimeoutsR, Postponed_1); + true -> + loop_state_change( + P, Debug, S, + Events, NextState_NewData, + NextEventsR, Hibernate, TimeoutsR, Postponed_1) + end; + _ -> + %% With sys_debug + Name = P#params.name, + Debug_1 = + case Postpone of + true -> + sys_debug( + Debug, Name, + {postpone,Event,State,NextState}); + false -> + sys_debug( + Debug, Name, + {consume,Event,State,NextState}) + end, + if + NextState =:= State -> + loop_keep_state( + P, Debug_1, S, + Events, NextState_NewData, + NextEventsR, Hibernate, TimeoutsR, Postponed_1); + true -> + loop_state_change( + P, Debug_1, S, + Events, NextState_NewData, + NextEventsR, Hibernate, TimeoutsR, Postponed_1) + end end. +%% State transition to the same state +%% +loop_keep_state( + P, Debug, #state{timers = {TimerRefs,TimeoutTypes} = Timers} = S, + Events, NextState_NewData, + NextEventsR, Hibernate, TimeoutsR, Postponed) -> + %% + %% Cancel event timeout + %% + case TimeoutTypes of + %% Optimization + %% - only cancel timer when there is a timer to cancel + #{timeout := TimerRef} -> + %% Event timeout active + loop_next_events( + P, Debug, S, + Events, NextState_NewData, + NextEventsR, Hibernate, TimeoutsR, Postponed, + cancel_timer_by_ref_and_type( + TimerRef, timeout, TimerRefs, TimeoutTypes)); + _ -> + %% No event timeout active + loop_next_events( + P, Debug, S, + Events, NextState_NewData, + NextEventsR, Hibernate, TimeoutsR, Postponed, + Timers) + end. -%% Fast path -%% -%% Cancel event timer and state timer only if running -loop_event_done_fast( - Parent, Hibernate, - #state{ - state = NextState, - timer_types = TimerTypes, - cancel_timers = CancelTimers} = S, - Events, P, NextState, NewData, NextEventsR) -> - %% Same state - 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 = TimerTypes, - cancel_timers = CancelTimers} = S, - 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})); +%% State transition to a different state +%% +loop_state_change( + P, Debug, S, Events, NextState_NewData, + NextEventsR, Hibernate, TimeoutsR, Postponed) -> + %% + %% Retry postponed events + %% + case Postponed of + [] -> + loop_state_change( + P, Debug, S, + Events, NextState_NewData, + NextEventsR, Hibernate, TimeoutsR); + [E1] -> + loop_state_change( + P, Debug, S, + [E1|Events], NextState_NewData, + NextEventsR, Hibernate, TimeoutsR); + [E2,E1] -> + loop_state_change( + P, Debug, S, + [E1,E2|Events], NextState_NewData, + NextEventsR, Hibernate, TimeoutsR); _ -> - %% No event nor state_timeout active - loop_event_done_fast( - Parent, Hibernate, S, - Events, P, NextState, NewData, NextEventsR, - {TimerTypes,CancelTimers}) + loop_state_change( + P, Debug, S, + lists:reverse(Postponed, Events), NextState_NewData, + NextEventsR, Hibernate, TimeoutsR) end. %% -%% Retry postponed events -loop_event_done_fast( - 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); +loop_state_change( + P, Debug, #state{timers = {TimerRefs,TimeoutTypes} = Timers} = S, + Events, NextState_NewData, + NextEventsR, Hibernate, TimeoutsR) -> + %% + %% Cancel state and event timeout + %% + case TimeoutTypes of + %% Optimization + %% - only cancel timeout when there is an active timeout + %% + #{state_timeout := TimerRef} -> + %% State timeout active + %% - cancel event timeout too since it is faster than inspecting + loop_next_events( + P, Debug, S, Events, NextState_NewData, + NextEventsR, Hibernate, TimeoutsR, [], + cancel_timer_by_type( + timeout, + cancel_timer_by_ref_and_type( + TimerRef, state_timeout, TimerRefs, TimeoutTypes))); + #{timeout := TimerRef} -> + %% Event timeout active but not state timeout + %% - cancel event timeout only + loop_next_events( + P, Debug, S, Events, NextState_NewData, + NextEventsR, Hibernate, TimeoutsR, [], + cancel_timer_by_ref_and_type( + TimerRef, timeout, TimerRefs, TimeoutTypes)); _ -> - %% A bit slower path - loop_event_done_fast_2( - Parent, Hibernate, S, - lists:reverse(P, Events), [], NextState, NewData, NextEventsR, - TimerTypes_CancelTimers) + %% No state nor event timeout active. + loop_next_events( + P, Debug, S, Events, NextState_NewData, + NextEventsR, Hibernate, TimeoutsR, [], + Timers) end. + +%% Continue state transition with processing of +%% inserted events and timeout events %% -%% Fast path +loop_next_events( + P, Debug, S, + Events, NextState_NewData, + NextEventsR, Hibernate, [], Postponed, + Timers) -> + %% + %% Optimization when there are no timeout actions + %% hence no timeout zero events to append to Events + %% - avoid loop_timeouts + loop_done( + P, Debug, + S#state{ + state_data = NextState_NewData, + postponed = Postponed, + timers = Timers, + hibernate = Hibernate}, + NextEventsR, Events); +loop_next_events( + P, Debug, S, + Events, NextState_NewData, + NextEventsR, Hibernate, TimeoutsR, Postponed, + Timers) -> + %% + Seen = #{}, + TimeoutEvents = [], + loop_timeouts( + P, Debug, S, + Events, NextState_NewData, + NextEventsR, Hibernate, TimeoutsR, Postponed, + Timers, Seen, TimeoutEvents). + +%% Continue state transition with processing of timeout events %% -loop_event_done_fast_2( - Parent, Hibernate, S, - Events, P, NextState, NewData, NextEventsR, - {TimerTypes,CancelTimers}) -> +loop_timeouts( + P, Debug, S, + Events, NextState_NewData, + NextEventsR, Hibernate, [], Postponed, + Timers, _Seen, TimeoutEvents) -> %% - NewS = + S_1 = S#state{ - state = NextState, - data = NewData, - postponed = P, - timer_types = TimerTypes, - cancel_timers = CancelTimers, + state_data = NextState_NewData, + postponed = Postponed, + timers = Timers, hibernate = Hibernate}, - case NextEventsR of - %% Handle 0..2 next events without list reversal since - %% that will move out all live registers and back again + case TimeoutEvents of [] -> - 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]); + loop_done(P, Debug, S_1, NextEventsR, Events); _ -> - %% A bit slower path - loop_event_done( - Parent, ?not_sys_debug, NewS, lists:reverse(NextEventsR, Events)) + case Events of + [] -> + loop_prepend_timeout_events( + P, Debug, S_1, TimeoutEvents, + NextEventsR); + [E1] -> + loop_prepend_timeout_events( + P, Debug, S_1, TimeoutEvents, + [E1|NextEventsR]); + [E2,E1] -> + loop_prepend_timeout_events( + P, Debug, S_1, TimeoutEvents, + [E1,E2|NextEventsR]); + _ -> + loop_prepend_timeout_events( + P, Debug, S_1, TimeoutEvents, + lists:reverse(Events, NextEventsR)) + end + end; +loop_timeouts( + P, Debug, S, + Events, NextState_NewData, + NextEventsR, Hibernate, [Timeout|TimeoutsR], Postponed, + Timers, Seen, TimeoutEvents) -> + %% + case Timeout of + {TimeoutType,Time,TimeoutMsg} -> + %% Relative timeout + case Seen of + #{TimeoutType := _} -> + %% Type seen before - ignore + loop_timeouts( + P, Debug, S, + Events, NextState_NewData, + NextEventsR, Hibernate, TimeoutsR, Postponed, + Timers, Seen, TimeoutEvents); + #{} -> + loop_timeouts( + P, Debug, S, + Events, NextState_NewData, + NextEventsR, Hibernate, TimeoutsR, Postponed, + Timers, Seen, TimeoutEvents, + TimeoutType, Time, TimeoutMsg, []) + end; + {TimeoutType,Time,TimeoutMsg,TimeoutOpts} -> + %% Absolute timeout + case Seen of + #{TimeoutType := _} -> + %% Type seen before - ignore + loop_timeouts( + P, Debug, S, + Events, NextState_NewData, + NextEventsR, Hibernate, TimeoutsR, Postponed, + Timers, Seen, TimeoutEvents); + #{} -> + loop_timeouts( + P, Debug, S, + Events, NextState_NewData, + NextEventsR, Hibernate, TimeoutsR, Postponed, + Timers, Seen, TimeoutEvents, + TimeoutType, Time, TimeoutMsg, listify(TimeoutOpts)) + end end. - -%%--------------------------------------------------------------------------- -%% Server loop helpers - -call_callback_mode(#state{module = Module} = S) -> - try Module:callback_mode() of - CallbackMode -> - callback_mode_result(S, CallbackMode) - catch - CallbackMode -> - callback_mode_result(S, CallbackMode); - Class:Reason:Stacktrace -> - [Class,Reason,Stacktrace] +%% +loop_timeouts( + P, Debug, S, + Events, NextState_NewData, + NextEventsR, Hibernate, TimeoutsR, Postponed, + Timers, Seen, TimeoutEvents, + TimeoutType, Time, TimeoutMsg, TimeoutOpts) -> + %% + case Time of + infinity -> + %% Cancel any running timer + loop_timeouts_cancel( + P, Debug, S, + Events, NextState_NewData, + NextEventsR, Hibernate, TimeoutsR, Postponed, + Timers, Seen, TimeoutEvents, + TimeoutType); + 0 when TimeoutOpts =:= [] -> + %% Relative timeout zero + %% - cancel any running timer + %% handle timeout zero events later + %% + loop_timeouts_cancel( + P, Debug, S, + Events, NextState_NewData, + NextEventsR, Hibernate, TimeoutsR, Postponed, + Timers, Seen, [{TimeoutType,TimeoutMsg}|TimeoutEvents], + TimeoutType); + _ -> + %% (Re)start the timer + TimerRef = + erlang:start_timer(Time, self(), TimeoutMsg, TimeoutOpts), + {TimerRefs,TimeoutTypes} = Timers, + case TimeoutTypes of + #{TimeoutType := OldTimerRef} -> + %% Cancel the running timer, + %% update the timeout type, + %% insert the new timer ref, + %% and remove the old timer ref + Timers_1 = + {maps:remove( + OldTimerRef, + TimerRefs#{TimerRef => TimeoutType}), + TimeoutTypes#{TimeoutType := TimerRef}}, + cancel_timer(OldTimerRef), + loop_timeouts( + P, Debug, S, + Events, NextState_NewData, + NextEventsR, Hibernate, TimeoutsR, Postponed, + Timers_1, Seen#{TimeoutType => true}, TimeoutEvents); + #{} -> + %% Insert the new timer type and ref + Timers_1 = + {TimerRefs#{TimerRef => TimeoutType}, + TimeoutTypes#{TimeoutType => TimerRef}}, + loop_timeouts( + P, Debug, S, + Events, NextState_NewData, + NextEventsR, Hibernate, TimeoutsR, Postponed, + Timers_1, Seen#{TimeoutType => true}, TimeoutEvents) + end end. -callback_mode_result(S, CallbackMode) -> - callback_mode_result( - S, CallbackMode, listify(CallbackMode), undefined, false). -%% -callback_mode_result(_S, CallbackMode, [], undefined, _StateEnter) -> - [error, - {bad_return_from_callback_mode,CallbackMode}, - ?STACKTRACE()]; -callback_mode_result(S, _CallbackMode, [], CBMode, StateEnter) -> - S#state{callback_mode = CBMode, state_enter = StateEnter}; -callback_mode_result(S, CallbackMode, [H|T], CBMode, StateEnter) -> - case callback_mode(H) of - true -> - callback_mode_result(S, CallbackMode, T, H, StateEnter); - false -> - case state_enter(H) of - true -> - callback_mode_result(S, CallbackMode, T, CBMode, true); - false -> - [error, - {bad_return_from_callback_mode,CallbackMode}, - ?STACKTRACE()] - end +%% Loop helper to cancel a timeout +%% +loop_timeouts_cancel( + P, Debug, S, + Events, NextState_NewData, + NextEventsR, Hibernate, TimeoutsR, Postponed, + {TimerRefs,TimeoutTypes} = Timers, Seen, TimeoutEvents, + TimeoutType) -> + %% This function body should have been: + %% Timers_1 = cancel_timer_by_type(TimeoutType, Timers), + %% loop_timeouts( + %% P, Debug, S, + %% Events, NextState_NewData, + %% NextEventsR, Hibernate, TimeoutsR, Postponed, + %% Timers_1, Seen#{TimeoutType => true}, TimeoutEvents). + %% + %% Explicitly separate cases to get separate code paths for when + %% the map key exists vs. not, since otherwise the external call + %% to erlang:cancel_timer/1 and to map:remove/2 within + %% cancel_timer_by_type/2 would cause all live registers + %% to be saved to and restored from the stack also for + %% the case when the map key TimeoutType does not exist + case TimeoutTypes of + #{TimeoutType := TimerRef} -> + Timers_1 = + cancel_timer_by_ref_and_type( + TimerRef, TimeoutType, TimerRefs, TimeoutTypes), + loop_timeouts( + P, Debug, S, + Events, NextState_NewData, + NextEventsR, Hibernate, TimeoutsR, Postponed, + Timers_1, Seen#{TimeoutType => true}, TimeoutEvents); + #{} -> + loop_timeouts( + P, Debug, S, + Events, NextState_NewData, + NextEventsR, Hibernate, TimeoutsR, Postponed, + Timers, Seen#{TimeoutType => true}, TimeoutEvents) end. +%% Continue state transition with prepending timeout zero events +%% before event queue reversal i.e appending timeout zero events +%% +loop_prepend_timeout_events(P, Debug, S, TimeoutEvents, EventsR) -> + {Debug_1,Events_1R} = + prepend_timeout_events(P, Debug, S, TimeoutEvents, EventsR), + loop_done(P, Debug_1, S, Events_1R, []). -call_state_function( - #state{callback_mode = undefined} = S, Type, Content, State, Data) -> - case call_callback_mode(S) of - #state{} = NewS -> - call_state_function(NewS, Type, Content, State, Data); - Error -> - Error - end; -call_state_function( - #state{callback_mode = CallbackMode, module = Module} = S, - Type, Content, State, Data) -> - try - case CallbackMode of - state_functions -> - Module:State(Type, Content, Data); - handle_event_function -> - Module:handle_event(Type, Content, State, Data) - end - of - Result -> - {Result,S} - catch - Result -> - {Result,S}; - Class:Reason:Stacktrace -> - [Class,Reason,Stacktrace] +%% Place inserted events first in the event queue +%% +loop_done(P, Debug, S, NextEventsR, Events) -> + case NextEventsR of + [] -> + loop_done(P, Debug, S, Events); + [E1] -> + loop_done(P, Debug, S, [E1|Events]); + [E2,E1] -> + loop_done(P, Debug, S, [E1,E2|Events]); + _ -> + loop_done(P, Debug, S, lists:reverse(NextEventsR, Events)) end. - - -%% -> absolute | relative | badarg -classify_timeout(TimeoutType, Time, Opts) -> - case timeout_event_type(TimeoutType) of - true -> - classify_time(false, Time, Opts); - false -> - badarg +%% +%% State transition is done, keep looping if there are +%% enqueued events, otherwise get a new event +%% +loop_done(P, Debug, S, Q) -> +%%% io:format( +%%% "loop_done: state_data = ~p,~n" +%%% " postponed = ~p, Q = ~p,~n", +%%% " timers = ~p.~n" +%%% [S#state.state_data,,S#state.postponed,Q,S#state.timers]), + case Q of + [] -> + %% Get a new event + loop(P, Debug, S); + [Event|Events] -> + %% Loop until out of enqueued events + loop_event(P, Debug, S, Event, Events) end. -classify_time(Abs, Time, []) -> - case Abs of - true when - is_integer(Time); - Time =:= infinity -> - absolute; - false when - is_integer(Time), 0 =< Time; - Time =:= infinity -> - relative; - _ -> - badarg - end; -classify_time(_, Time, [{abs,Abs}|Opts]) when is_boolean(Abs) -> - classify_time(Abs, Time, Opts); -classify_time(_, _, Opts) when is_list(Opts) -> - badarg. +%%--------------------------------------------------------------------------- +%% Server loop helpers -%% Stop and start timers as well as create timeout zero events -%% and pending event timer +%% Parse an option list for erlang:start_timer/4 to figure out +%% if the timeout will be absolute or relative %% -%% Stop and start timers non-event timers -parse_timers(TimerRefs, Timers, TimeoutsR) -> - parse_timers(TimerRefs, Timers, TimeoutsR, #{}, []). +parse_timeout_opts_abs(Opts) -> + parse_timeout_opts_abs(Opts, false). %% -parse_timers( - TimerRefs, Timers, [], _Seen, TimeoutEvents) -> - %% - {TimerRefs,Timers,TimeoutEvents}; -parse_timers( - TimerRefs, Timers, [Timeout|TimeoutsR], Seen, TimeoutEvents) -> - %% - case Timeout of - {TimerType,Time,TimerMsg,TimerOpts} -> - %% Absolute timer - parse_timers( - TimerRefs, Timers, TimeoutsR, Seen, TimeoutEvents, - TimerType, Time, TimerMsg, listify(TimerOpts)); - %% Relative timers below - {TimerType,0,TimerMsg} -> - parse_timers( - TimerRefs, Timers, TimeoutsR, Seen, TimeoutEvents, - TimerType, zero, TimerMsg, []); - {TimerType,Time,TimerMsg} -> - parse_timers( - TimerRefs, Timers, TimeoutsR, Seen, TimeoutEvents, - TimerType, Time, TimerMsg, []) - end. - -parse_timers( - TimerRefs, Timers, TimeoutsR, Seen, TimeoutEvents, - TimerType, Time, TimerMsg, TimerOpts) -> - case Seen of - #{TimerType := _} -> - %% Type seen before - ignore - parse_timers( - TimerRefs, Timers, TimeoutsR, Seen, TimeoutEvents); - #{} -> - %% Unseen type - handle - NewSeen = Seen#{TimerType => true}, - case Time of - infinity -> - %% Cancel any running timer - parse_timers( - TimerRefs, cancel_timer_by_type(TimerType, Timers), - TimeoutsR, NewSeen, TimeoutEvents); - zero -> - %% Cancel any running timer - %% Handle zero time timeouts later - parse_timers( - TimerRefs, cancel_timer_by_type(TimerType, Timers), - TimeoutsR, NewSeen, - [{TimerType,TimerMsg}|TimeoutEvents]); - _ -> - %% (Re)start the timer - TimerRef = - erlang:start_timer( - Time, self(), TimerMsg, TimerOpts), - case Timers of - {#{TimerType := OldTimerRef} = TimerTypes, - CancelTimers} -> - %% Cancel the running timer - cancel_timer(OldTimerRef), - NewCancelTimers = CancelTimers + 1, - %% Insert the new timer into - %% both TimerRefs and TimerTypes - parse_timers( - TimerRefs#{TimerRef => TimerType}, - {TimerTypes#{TimerType => TimerRef}, - NewCancelTimers}, - TimeoutsR, NewSeen, TimeoutEvents); - {#{} = TimerTypes,CancelTimers} -> - %% Insert the new timer into - %% both TimerRefs and TimerTypes - parse_timers( - TimerRefs#{TimerRef => TimerType}, - {TimerTypes#{TimerType => TimerRef}, - CancelTimers}, - TimeoutsR, NewSeen, TimeoutEvents) - end - end +parse_timeout_opts_abs(Opts, Abs) -> + case Opts of + [] -> + Abs; + [{abs,Abs_1}|Opts] when is_boolean(Abs_1) -> + parse_timeout_opts_abs(Opts, Abs_1); + _ -> + badarg end. %% Enqueue immediate timeout events (timeout 0 events) @@ -1814,62 +2055,94 @@ 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(_P, Debug, _S, [], EventsR) -> + {Debug,EventsR}; +prepend_timeout_events( + P, Debug, S, [{timeout,_} = TimeoutEvent|TimeoutEvents], []) -> + %% Prepend this since there are no other events in queue + case Debug of + ?not_sys_debug -> + prepend_timeout_events( + P, Debug, S, TimeoutEvents, [TimeoutEvent]); + _ -> + {State,_Data} = S#state.state_data, + Debug_1 = + sys_debug( + Debug, P#params.name, {in,TimeoutEvent,State}), + prepend_timeout_events( + P, Debug_1, S, TimeoutEvents, [TimeoutEvent]) + end; +prepend_timeout_events( + P, 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(P, Debug, S, TimeoutEvents, EventsR); +prepend_timeout_events( + P, Debug, S, [TimeoutEvent|TimeoutEvents], EventsR) -> %% Just prepend all others - prepend_timeout_events(TimeoutEvents, [TimeoutEvent|EventsR]). + case Debug of + ?not_sys_debug -> + prepend_timeout_events( + P, Debug, S, TimeoutEvents, [TimeoutEvent|EventsR]); + _ -> + {State,_Data} = S#state.state_data, + Debug_1 = + sys_debug( + Debug, P#params.name, {in,TimeoutEvent,State}), + prepend_timeout_events( + P, Debug_1, S, TimeoutEvents, [TimeoutEvent|EventsR]) + end. %%--------------------------------------------------------------------------- %% Server helpers -reply_then_terminate(Class, Reason, Stacktrace, Debug, S, Q, Replies) -> +reply_then_terminate(Class, Reason, Stacktrace, P, Debug, S, Q, Replies) -> do_reply_then_terminate( - Class, Reason, Stacktrace, Debug, S, Q, listify(Replies)). + Class, Reason, Stacktrace, P, Debug, S, Q, listify(Replies)). %% do_reply_then_terminate( - Class, Reason, Stacktrace, Debug, S, Q, []) -> - terminate(Class, Reason, Stacktrace, Debug, S, Q); + Class, Reason, Stacktrace, P, Debug, S, Q, []) -> + terminate(Class, Reason, Stacktrace, P, Debug, S, Q); do_reply_then_terminate( - Class, Reason, Stacktrace, Debug, S, Q, [R|Rs]) -> + Class, Reason, Stacktrace, P, 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), + Debug_1 = + ?sys_debug( + Debug, + P#params.name, + {out,Reply,From}), + do_reply_then_terminate( + Class, Reason, Stacktrace, P, Debug_1, S, Q, Rs); + false -> + terminate( + error, + {bad_reply_action_from_state_function,R}, + ?STACKTRACE(), + P, Debug, S, Q) + end; _ -> terminate( error, {bad_reply_action_from_state_function,R}, ?STACKTRACE(), - Debug, S, Q) + P, Debug, S, Q) end. terminate( - Class, Reason, Stacktrace, Debug, - #state{module = Module, state = State, data = Data} = S, - Q) -> + Class, Reason, Stacktrace, + #params{module = Module} = P, Debug, + #state{state_data = {State,Data}} = S, Q) -> case erlang:function_exported(Module, terminate, 3) of true -> try Module:terminate(Reason, State, Data) of @@ -1877,8 +2150,7 @@ terminate( catch _ -> ok; C:R:ST -> - error_info(C, R, ST, S, Q), - sys:print_log(Debug), + error_info(C, R, ST, Debug, P, S, Q), erlang:raise(C, R, ST) end; false -> @@ -1887,14 +2159,13 @@ terminate( _ = case Reason of normal -> - terminate_sys_debug(Debug, S, State, Reason); + terminate_sys_debug(Debug, P, State, Reason); shutdown -> - terminate_sys_debug(Debug, S, State, Reason); + terminate_sys_debug(Debug, P, State, Reason); {shutdown,_} -> - terminate_sys_debug(Debug, S, State, Reason); + terminate_sys_debug(Debug, P, State, Reason); _ -> - error_info(Class, Reason, Stacktrace, S, Q), - sys:print_log(Debug) + error_info(Class, Reason, Stacktrace, Debug, P, S, Q) end, case Stacktrace of [] -> @@ -1903,38 +2174,67 @@ terminate( erlang:raise(Class, Reason, Stacktrace) end. -terminate_sys_debug(Debug, S, State, Reason) -> - ?sys_debug(Debug, {S#state.name,State}, {terminate,Reason}). +terminate_sys_debug(Debug, P, State, Reason) -> + ?sys_debug(Debug, P#params.name, {terminate,Reason,State}). error_info( - Class, Reason, Stacktrace, - #state{ + Class, Reason, Stacktrace, Debug, + #params{ name = Name, callback_mode = CallbackMode, - state_enter = StateEnter, - postponed = P} = S, + state_enter = StateEnter} = P, + #state{postponed = Postponed} = S, Q) -> + Log = sys:get_log(Debug), ?LOG_ERROR(#{label=>{gen_statem,terminate}, name=>Name, queue=>Q, - postponed=>P, + postponed=>Postponed, callback_mode=>CallbackMode, state_enter=>StateEnter, - state=>format_status(terminate, get(), S), - reason=>{Class,Reason,Stacktrace}}, + state=>format_status(terminate, get(), P, S), + 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, - postponed:=P, + postponed:=Postponed, 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] @@ -1954,14 +2254,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 -> @@ -1981,39 +2279,60 @@ format_log(#{label:={gen_statem,terminate}, [_,_|_] -> "** Queued = ~tp~n"; _ -> "" end ++ - case P of + case Postponed of [] -> ""; _ -> "** Postponed = ~tp~n" end ++ 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 + case Postponed of [] -> []; - _ -> [LimitedP] + _ -> [error_logger:limit_term(Postponed)] 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( Opt, PDict, - #state{module = Module, state = State, data = Data}) -> + #params{module = Module}, + #state{state_data = {State,Data} = State_Data}) -> case erlang:function_exported(Module, format_status, 2) of true -> try Module:format_status(Opt, [PDict,State,Data]) @@ -2021,21 +2340,21 @@ format_status( Result -> Result; _:_ -> format_status_default( - Opt, State, - atom_to_list(Module) ++ ":format_status/2 crashed") + Opt, + {State, + atom_to_list(Module) ++ ":format_status/2 crashed"}) end; false -> - format_status_default(Opt, State, Data) + format_status_default(Opt, State_Data) end. -%% The default Module:format_status/2 -format_status_default(Opt, State, Data) -> - StateData = {State,Data}, +%% The default Module:format_status/3 +format_status_default(Opt, State_Data) -> case Opt of terminate -> - StateData; + State_Data; _ -> - [{data,[{"State",StateData}]}] + [{data,[{"State",State_Data}]}] end. -compile({inline, [listify/1]}). @@ -2044,24 +2363,41 @@ listify(Item) when is_list(Item) -> listify(Item) -> [Item]. + +-define(cancel_timer(TimerRef), + case erlang:cancel_timer(TimerRef) of + false -> + %% No timer found and we have not seen the timeout message + receive + {timeout,(TimerRef),_} -> + ok + end; + _ -> + %% Timer was running + ok + end). + +-compile({inline, [cancel_timer/1]}). +cancel_timer(TimerRef) -> + ?cancel_timer(TimerRef). + %% Cancel timer if running, otherwise no op %% -%% This is an asynchronous cancel so the timer is not really cancelled -%% until we get a cancel_timer msg i.e {cancel_timer,TimerRef,_}. -%% In the mean time we might get a timeout message. -%% -%% Remove the timer from TimerTypes. -%% When we get the cancel_timer msg we remove it from TimerRefs. +%% Remove the timer from Timers -compile({inline, [cancel_timer_by_type/2]}). -cancel_timer_by_type(TimerType, {TimerTypes,CancelTimers} = TT_CT) -> - case TimerTypes of - #{TimerType := TimerRef} -> - ok = erlang:cancel_timer(TimerRef, [{async,true}]), - {maps:remove(TimerType, TimerTypes),CancelTimers + 1}; - #{} -> - TT_CT +cancel_timer_by_type(TimeoutType, {TimerRefs,TimeoutTypes} = Timers) -> + case TimeoutTypes of + #{TimeoutType := TimerRef} -> + ?cancel_timer(TimerRef), + {maps:remove(TimerRef, TimerRefs), + maps:remove(TimeoutType, TimeoutTypes)}; + #{} -> + Timers end. --compile({inline, [cancel_timer/1]}). -cancel_timer(TimerRef) -> - ok = erlang:cancel_timer(TimerRef, [{async,true}]). +-compile({inline, [cancel_timer_by_ref_and_type/4]}). +cancel_timer_by_ref_and_type( + TimerRef, TimeoutType, TimerRefs, TimeoutTypes) -> + ?cancel_timer(TimerRef), + {maps:remove(TimerRef, TimerRefs), + maps:remove(TimeoutType, TimeoutTypes)}. diff --git a/lib/stdlib/src/ms_transform.erl b/lib/stdlib/src/ms_transform.erl index 6d243e1bec..97ec785c62 100644 --- a/lib/stdlib/src/ms_transform.erl +++ b/lib/stdlib/src/ms_transform.erl @@ -556,8 +556,8 @@ tg({call, Line, {remote,_,{atom,_,erlang},{atom, Line2, FunName}},ParaList}, FunName,length(ParaList)}}) end; tg({call, Line, {remote,_,{atom,_,ModuleName}, - {atom, _, FunName}},_ParaList},B) -> - throw({error,Line,{?ERR_GENREMOTECALL+B#tgd.eb,ModuleName,FunName}}); + {atom, _, FunName}},ParaList},B) -> + throw({error,Line,{?ERR_GENREMOTECALL+B#tgd.eb,ModuleName,FunName,length(ParaList)}}); tg({cons,Line, H, T},B) -> {cons, Line, tg(H,B), tg(T,B)}; tg({nil, Line},_B) -> diff --git a/lib/stdlib/src/otp_internal.erl b/lib/stdlib/src/otp_internal.erl index 2cfc702b53..f2b50c354a 100644 --- a/lib/stdlib/src/otp_internal.erl +++ b/lib/stdlib/src/otp_internal.erl @@ -55,6 +55,14 @@ obsolete_1(erlang, now, 0) -> obsolete_1(calendar, local_time_to_universal_time, 1) -> {deprecated, {calendar, local_time_to_universal_time_dst, 1}}; +%% *** STDLIB added in OTP 22 *** + +obsolete_1(sys, get_debug, 3) -> + {deprecated, + "Deprecated function. " + "Incorrectly documented and in fact only for internal use. " + "Can often be replaced with sys:get_log/1."}; + %% *** STDLIB added in OTP 20 *** obsolete_1(gen_fsm, start, 3) -> diff --git a/lib/stdlib/src/stdlib.appup.src b/lib/stdlib/src/stdlib.appup.src index 8c0b186288..2a324aef82 100644 --- a/lib/stdlib/src/stdlib.appup.src +++ b/lib/stdlib/src/stdlib.appup.src @@ -16,13 +16,38 @@ %% limitations under the License. %% %% %CopyrightEnd% +%% +%% We allow upgrade from, and downgrade to all previous +%% versions from the following OTP releases: +%% - OTP 20 +%% - OTP 21 +%% +%% We also allow upgrade from, and downgrade to all +%% versions that have branched off from the above +%% stated previous versions. +%% {"%VSN%", - %% Up from - max one major revision back - [{<<"3\\.4(\\.[0-9]+)*">>,[restart_new_emulator]}, % OTP-20.* - {<<"3\\.5(\\.[0-9]+)*">>,[restart_new_emulator]}, % OTP-21.0 - {<<"3\\.6(\\.[0-9]+)*">>,[restart_new_emulator]}],% OTP-21.1 - %% Down to - max one major revision back - [{<<"3\\.4(\\.[0-9]+)*">>,[restart_new_emulator]}, % OTP-20.* - {<<"3\\.5(\\.[0-9]+)*">>,[restart_new_emulator]}, % OTP-21.0 - {<<"3\\.6(\\.[0-9]+)*">>,[restart_new_emulator]}] % OTP-21.1 -}. + [{<<"^3\\.4$">>,[restart_new_emulator]}, + {<<"^3\\.4\\.0(?:\\.[0-9]+)+$">>,[restart_new_emulator]}, + {<<"^3\\.4\\.1(?:\\.[0-9]+)*$">>,[restart_new_emulator]}, + {<<"^3\\.4\\.2(?:\\.[0-9]+)*$">>,[restart_new_emulator]}, + {<<"^3\\.4\\.3(?:\\.[0-9]+)*$">>,[restart_new_emulator]}, + {<<"^3\\.4\\.4(?:\\.[0-9]+)*$">>,[restart_new_emulator]}, + {<<"^3\\.4\\.5(?:\\.[0-9]+)*$">>,[restart_new_emulator]}, + {<<"^3\\.5$">>,[restart_new_emulator]}, + {<<"^3\\.5\\.0(?:\\.[0-9]+)+$">>,[restart_new_emulator]}, + {<<"^3\\.5\\.1(?:\\.[0-9]+)*$">>,[restart_new_emulator]}, + {<<"^3\\.6$">>,[restart_new_emulator]}, + {<<"^3\\.6\\.0(?:\\.[0-9]+)+$">>,[restart_new_emulator]}], + [{<<"^3\\.4$">>,[restart_new_emulator]}, + {<<"^3\\.4\\.0(?:\\.[0-9]+)+$">>,[restart_new_emulator]}, + {<<"^3\\.4\\.1(?:\\.[0-9]+)*$">>,[restart_new_emulator]}, + {<<"^3\\.4\\.2(?:\\.[0-9]+)*$">>,[restart_new_emulator]}, + {<<"^3\\.4\\.3(?:\\.[0-9]+)*$">>,[restart_new_emulator]}, + {<<"^3\\.4\\.4(?:\\.[0-9]+)*$">>,[restart_new_emulator]}, + {<<"^3\\.4\\.5(?:\\.[0-9]+)*$">>,[restart_new_emulator]}, + {<<"^3\\.5$">>,[restart_new_emulator]}, + {<<"^3\\.5\\.0(?:\\.[0-9]+)+$">>,[restart_new_emulator]}, + {<<"^3\\.5\\.1(?:\\.[0-9]+)*$">>,[restart_new_emulator]}, + {<<"^3\\.6$">>,[restart_new_emulator]}, + {<<"^3\\.6\\.0(?:\\.[0-9]+)+$">>,[restart_new_emulator]}]}. diff --git a/lib/stdlib/src/sys.erl b/lib/stdlib/src/sys.erl index 0064414d6f..a04195c9ed 100644 --- a/lib/stdlib/src/sys.erl +++ b/lib/stdlib/src/sys.erl @@ -30,7 +30,8 @@ log_to_file/2, log_to_file/3, no_debug/1, no_debug/2, install/2, install/3, remove/2, remove/3]). -export([handle_system_msg/6, handle_system_msg/7, handle_debug/4, - print_log/1, get_debug/3, debug_options/1, suspend_loop_hib/6]). + print_log/1, get_log/1, get_debug/3, debug_options/1, suspend_loop_hib/6]). +-deprecated([{get_debug,3,eventually}]). %%----------------------------------------------------------------- %% Types @@ -42,10 +43,17 @@ | {'global', term()} | {'via', module(), term()}. -type system_event() :: {'in', Msg :: _} - | {'in', Msg :: _, From :: _} + | {'in', Msg :: _, State :: _} | {'out', Msg :: _, To :: _} | {'out', Msg :: _, To :: _, State :: _} - | term(). + | {'noreply', State :: _} + | {'continue', Continuation :: _} + | {'code_change', Event :: _, State :: _} + | {'postpone', Event :: _, State :: _, NextState :: _} + | {'consume', Event :: _, State :: _, NextState :: _} + | {'enter', State :: _} + | {'terminate', Reason :: _, State :: _} + | term(). -opaque dbg_opt() :: {'trace', 'true'} | {'log', {N :: non_neg_integer(), @@ -385,31 +393,41 @@ handle_system_msg(SysState, Msg, From, Parent, Mod, Debug, Misc, Hib) -> FormFunc :: format_fun(), Extra :: term(), Event :: system_event(). -handle_debug([{trace, true} | T], FormFunc, State, Event) -> +handle_debug([{trace, true} = DbgOpt | T], FormFunc, State, Event) -> print_event({Event, State, FormFunc}), - [{trace, true} | handle_debug(T, FormFunc, State, Event)]; -handle_debug([{log, {N, LogData}} | T], FormFunc, State, Event) -> - NLogData = [{Event, State, FormFunc} | trim(N, LogData)], - [{log, {N, NLogData}} | handle_debug(T, FormFunc, State, Event)]; -handle_debug([{log_to_file, Fd} | T], FormFunc, State, Event) -> + [DbgOpt | handle_debug(T, FormFunc, State, Event)]; +handle_debug([{log, NLog} | T], FormFunc, State, Event) -> + Item = {Event, State, FormFunc}, + [{log, nlog_put(Item, NLog)} | handle_debug(T, FormFunc, State, Event)]; +handle_debug([{log_to_file, Fd} = DbgOpt | T], FormFunc, State, Event) -> print_event(Fd, {Event, State, FormFunc}), - [{log_to_file, Fd} | handle_debug(T, FormFunc, State, Event)]; + [DbgOpt | handle_debug(T, FormFunc, State, Event)]; handle_debug([{statistics, StatData} | T], FormFunc, State, Event) -> NStatData = stat(Event, StatData), [{statistics, NStatData} | handle_debug(T, FormFunc, State, Event)]; handle_debug([{FuncId, {Func, FuncState}} | T], FormFunc, State, Event) -> - case catch Func(FuncState, Event, State) of + try Func(FuncState, Event, State) of done -> handle_debug(T, FormFunc, State, Event); - {'EXIT', _} -> handle_debug(T, FormFunc, State, Event); NFuncState -> - [{FuncId, {Func, NFuncState}} | handle_debug(T, FormFunc, State, Event)] + [{FuncId, {Func, NFuncState}} | + handle_debug(T, FormFunc, State, Event)] + catch + done -> handle_debug(T, FormFunc, State, Event); + NFuncState -> + [{FuncId, {Func, NFuncState}} | + handle_debug(T, FormFunc, State, Event)]; + _:_ -> handle_debug(T, FormFunc, State, Event) end; handle_debug([{Func, FuncState} | T], FormFunc, State, Event) -> - case catch Func(FuncState, Event, State) of + try Func(FuncState, Event, State) of done -> handle_debug(T, FormFunc, State, Event); - {'EXIT', _} -> handle_debug(T, FormFunc, State, Event); - NFuncState -> + NFuncState -> [{Func, NFuncState} | handle_debug(T, FormFunc, State, Event)] + catch + done -> handle_debug(T, FormFunc, State, Event); + NFuncState -> + [{Func, NFuncState} | handle_debug(T, FormFunc, State, Event)]; + _:_ -> handle_debug(T, FormFunc, State, Event) end; handle_debug([], _FormFunc, _State, _Event) -> []. @@ -526,19 +544,19 @@ debug_cmd({trace, true}, Debug) -> debug_cmd({trace, false}, Debug) -> {ok, remove_debug(trace, Debug)}; debug_cmd({log, true}, Debug) -> - {_N, Logs} = get_debug(log, Debug, {0, []}), - {ok, install_debug(log, {10, trim(10, Logs)}, Debug)}; -debug_cmd({log, {true, N}}, Debug) when is_integer(N), N > 0 -> - {_N, Logs} = get_debug(log, Debug, {0, []}), - {ok, install_debug(log, {N, trim(N, Logs)}, Debug)}; + NLog = get_debug(log, Debug, nlog_new()), + {ok, install_debug(log, nlog_new(NLog), Debug)}; +debug_cmd({log, {true, N}}, Debug) when is_integer(N), 1 =< N -> + NLog = get_debug(log, Debug, nlog_new(N)), + {ok, install_debug(log, nlog_new(N, NLog), Debug)}; debug_cmd({log, false}, Debug) -> {ok, remove_debug(log, Debug)}; debug_cmd({log, print}, Debug) -> print_log(Debug), {ok, Debug}; debug_cmd({log, get}, Debug) -> - {_N, Logs} = get_debug(log, Debug, {0, []}), - {{ok, lists:reverse(Logs)}, Debug}; + NLog = get_debug(log, Debug, nlog_new()), + {{ok, [Event || {Event, _State, _FormFunc} <- nlog_get(NLog)]}, Debug}; debug_cmd({log_to_file, false}, Debug) -> NDebug = close_log_file(Debug), {ok, NDebug}; @@ -595,9 +613,6 @@ stat({out, _Msg, _To}, {Time, Reds, In, Out}) -> {Time, Reds, In, Out+1}; stat({out, _Msg, _To, _State}, {Time, Reds, In, Out}) -> {Time, Reds, In, Out+1}; stat(_, StatData) -> StatData. -trim(N, LogData) -> - lists:sublist(LogData, 1, N-1). - %%----------------------------------------------------------------- %% Debug structure manipulating functions %%----------------------------------------------------------------- @@ -625,9 +640,14 @@ get_debug2(Item, Debug, Default) -> -spec print_log(Debug) -> 'ok' when Debug :: [dbg_opt()]. print_log(Debug) -> - {_N, Logs} = get_debug(log, Debug, {0, []}), - lists:foreach(fun print_event/1, - lists:reverse(Logs)). + NLog = get_debug(log, Debug, nlog_new()), + lists:foreach(fun print_event/1, nlog_get(NLog)). + +-spec get_log(Debug) -> [system_event()] when + Debug :: [dbg_opt()]. +get_log(Debug) -> + NLog = get_debug(log, Debug, nlog_new()), + [Event || {Event, _State, _FormFunc} <- nlog_get(NLog)]. close_log_file(Debug) -> case get_debug2(log_to_file, Debug, []) of @@ -639,6 +659,74 @@ close_log_file(Debug) -> end. %%----------------------------------------------------------------- +%% Keep the last N Log functions +%%----------------------------------------------------------------- +%% +%% Streamlined Okasaki queue as base for "keep the last N" log. +%% +%% To the reverse list head we cons new items. +%% The forward list contains elements in insertion order, +%% so the head is the oldest and the one to drop off +%% when the log is full. +%% +%% Here is how we can get away with only using one cons cell +%% to wrap the forward and reverse list, and the log size: +%% +%% A full log does not need a counter; we just cons one +%% and drop one: +%% +%% [ReverseList|ForwardList] +%% +%% A non-full log is filling up to N elements; +%% use a down counter instead of a list as first element: +%% +%% [RemainingToFullCount|ReverseList] + +nlog_new() -> + nlog_new(10). +%% +nlog_new([_|_] = NLog) -> + nlog_new(10, NLog); +nlog_new(N) -> + [N]. % Empty log size N >= 1 +%% +nlog_new(N, NLog) -> + lists:foldl( + fun (Item, NL) -> nlog_put(Item, NL) end, + nlog_new(N), + nlog_get(NLog)). + +%% +nlog_put(Item, NLog) -> + case NLog of + [R|FF] when is_list(R) -> + %% Full log + case FF of + [_|F] -> + %% Cons to reverse list, drop from forward list + [[Item|R]|F]; + [] -> + %% Create new forward list from reverse list, + %% create new empty reverse list + [_|F] = lists:reverse(R, [Item]), + [[]|F] + end; + [1|R] -> + %% Log now gets full + [[Item|R]]; + [J|R] -> + %% Filling up to N elements + [J - 1,Item|R] + end. + +nlog_get([[]|F]) -> + F; +nlog_get([[_|_] = R|F]) -> + F ++ lists:reverse(R); +nlog_get([_J|R]) -> + lists:reverse(R). + +%%----------------------------------------------------------------- %% Func: debug_options/1 %% Purpose: Initiate a debug structure. Called by a process that %% wishes to initiate the debug structure without the @@ -665,9 +753,9 @@ debug_options(Options) -> debug_options([trace | T], Debug) -> debug_options(T, install_debug(trace, true, Debug)); debug_options([log | T], Debug) -> - debug_options(T, install_debug(log, {10, []}, Debug)); + debug_options(T, install_debug(log, nlog_new(), Debug)); debug_options([{log, N} | T], Debug) when is_integer(N), N > 0 -> - debug_options(T, install_debug(log, {N, []}, Debug)); + debug_options(T, install_debug(log, nlog_new(N), Debug)); debug_options([statistics | T], Debug) -> debug_options(T, install_debug(statistics, init_stat(), Debug)); debug_options([{log_to_file, FileName} | T], Debug) -> |