diff options
Diffstat (limited to 'lib/stdlib/src')
| -rw-r--r-- | lib/stdlib/src/gen.erl | 10 | ||||
| -rw-r--r-- | lib/stdlib/src/gen_event.erl | 71 | ||||
| -rw-r--r-- | lib/stdlib/src/gen_fsm.erl | 81 | ||||
| -rw-r--r-- | lib/stdlib/src/gen_server.erl | 106 | ||||
| -rw-r--r-- | lib/stdlib/src/gen_statem.erl | 18 | 
5 files changed, 163 insertions, 123 deletions
| diff --git a/lib/stdlib/src/gen.erl b/lib/stdlib/src/gen.erl index 597830cf9a..257c829801 100644 --- a/lib/stdlib/src/gen.erl +++ b/lib/stdlib/src/gen.erl @@ -26,7 +26,7 @@  %%%  %%% The standard behaviour should export init_it/6.  %%%----------------------------------------------------------------- --export([start/5, start/6, debug_options/2, +-export([start/5, start/6, debug_options/2, hibernate_after/1,  	 name/1, unregister_name/1, get_proc_name/1, get_parent/0,  	 call/3, call/4, reply/2, stop/1, stop/3]). @@ -408,6 +408,14 @@ spawn_opts(Options) ->  	    []      end. +hibernate_after(Options) -> +	case lists:keyfind(hibernate_after, 1, Options) of +		{_,HibernateAfterTimeout} -> +			HibernateAfterTimeout; +		false -> +			infinity +	end. +  debug_options(Name, Opts) ->      case lists:keyfind(debug, 1, Opts) of  	{_,Options} -> diff --git a/lib/stdlib/src/gen_event.erl b/lib/stdlib/src/gen_event.erl index 4c80464680..da2b0da3ca 100644 --- a/lib/stdlib/src/gen_event.erl +++ b/lib/stdlib/src/gen_event.erl @@ -37,7 +37,7 @@           stop/1, stop/3,  	 notify/2, sync_notify/2,  	 add_handler/3, add_sup_handler/3, delete_handler/3, swap_handler/3, -	 swap_sup_handler/3, which_handlers/1, call/3, call/4, wake_hib/4]). +	 swap_sup_handler/3, which_handlers/1, call/3, call/4, wake_hib/5]).  -export([init_it/6,  	 system_continue/3, @@ -186,8 +186,9 @@ init_it(Starter, Parent, Name0, _, _, Options) ->      process_flag(trap_exit, true),      Name = gen:name(Name0),      Debug = gen:debug_options(Name, Options), +	HibernateAfterTimeout = gen:hibernate_after(Options),      proc_lib:init_ack(Starter, {ok, self()}), -    loop(Parent, Name, [], Debug, false). +    loop(Parent, Name, [], HibernateAfterTimeout, Debug, false).  -spec add_handler(emgr_ref(), handler(), term()) -> term().  add_handler(M, Handler, Args) -> rpc(M, {add_handler, Handler, Args}). @@ -264,81 +265,83 @@ send(M, Cmd) ->      M ! Cmd,      ok. -loop(Parent, ServerName, MSL, Debug, true) -> -     proc_lib:hibernate(?MODULE, wake_hib, [Parent, ServerName, MSL, Debug]); -loop(Parent, ServerName, MSL, Debug, _) -> -    fetch_msg(Parent, ServerName, MSL, Debug, false). +loop(Parent, ServerName, MSL, HibernateAfterTimeout, Debug, true) -> +     proc_lib:hibernate(?MODULE, wake_hib, [Parent, ServerName, MSL, HibernateAfterTimeout, Debug]); +loop(Parent, ServerName, MSL, HibernateAfterTimeout, Debug, _) -> +    fetch_msg(Parent, ServerName, MSL, HibernateAfterTimeout, Debug, false). -wake_hib(Parent, ServerName, MSL, Debug) -> -    fetch_msg(Parent, ServerName, MSL, Debug, true). +wake_hib(Parent, ServerName, MSL, HibernateAfterTimeout, Debug) -> +    fetch_msg(Parent, ServerName, MSL, HibernateAfterTimeout, Debug, true). -fetch_msg(Parent, ServerName, MSL, Debug, Hib) -> +fetch_msg(Parent, ServerName, MSL, HibernateAfterTimeout, Debug, Hib) ->      receive  	{system, From, Req} ->  	    sys:handle_system_msg(Req, From, Parent, ?MODULE, Debug, -				  [ServerName, MSL, Hib],Hib); +				  [ServerName, MSL, HibernateAfterTimeout, Hib],Hib);  	{'EXIT', Parent, Reason} ->  	    terminate_server(Reason, Parent, MSL, ServerName);  	Msg when Debug =:= [] -> -	    handle_msg(Msg, Parent, ServerName, MSL, []); +	    handle_msg(Msg, Parent, ServerName, MSL, HibernateAfterTimeout, []);  	Msg ->  	    Debug1 = sys:handle_debug(Debug, fun print_event/3,  				      ServerName, {in, Msg}), -	    handle_msg(Msg, Parent, ServerName, MSL, Debug1) +	    handle_msg(Msg, Parent, ServerName, MSL, HibernateAfterTimeout, Debug1) +    after HibernateAfterTimeout -> +	    loop(Parent, ServerName, MSL, HibernateAfterTimeout, Debug, true)      end. -handle_msg(Msg, Parent, ServerName, MSL, Debug) -> +handle_msg(Msg, Parent, ServerName, MSL, HibernateAfterTimeout, Debug) ->      case Msg of  	{notify, Event} ->  	    {Hib,MSL1} = server_notify(Event, handle_event, MSL, ServerName), -	    loop(Parent, ServerName, MSL1, Debug, Hib); +	    loop(Parent, ServerName, MSL1, HibernateAfterTimeout, Debug, Hib);  	{_From, Tag, {sync_notify, Event}} ->  	    {Hib, MSL1} = server_notify(Event, handle_event, MSL, ServerName),  	    reply(Tag, ok), -	    loop(Parent, ServerName, MSL1, Debug, Hib); +	    loop(Parent, ServerName, MSL1, HibernateAfterTimeout, Debug, Hib);  	{'EXIT', From, Reason} ->  	    MSL1 = handle_exit(From, Reason, MSL, ServerName), -	    loop(Parent, ServerName, MSL1, Debug, false); +	    loop(Parent, ServerName, MSL1, HibernateAfterTimeout, Debug, false);  	{_From, Tag, {call, Handler, Query}} ->  	    {Hib, Reply, MSL1} = server_call(Handler, Query, MSL, ServerName),  	    reply(Tag, Reply), -	    loop(Parent, ServerName, MSL1, Debug, Hib); +	    loop(Parent, ServerName, MSL1, HibernateAfterTimeout, Debug, Hib);  	{_From, Tag, {add_handler, Handler, Args}} ->  	    {Hib, Reply, MSL1} = server_add_handler(Handler, Args, MSL),  	    reply(Tag, Reply), -	    loop(Parent, ServerName, MSL1, Debug, Hib); +	    loop(Parent, ServerName, MSL1, HibernateAfterTimeout, Debug, Hib);  	{_From, Tag, {add_sup_handler, Handler, Args, SupP}} ->  	    {Hib, Reply, MSL1} = server_add_sup_handler(Handler, Args, MSL, SupP),  	    reply(Tag, Reply), -	    loop(Parent, ServerName, MSL1, Debug, Hib); +	    loop(Parent, ServerName, MSL1, HibernateAfterTimeout, Debug, Hib);  	{_From, Tag, {delete_handler, Handler, Args}} ->  	    {Reply, MSL1} = server_delete_handler(Handler, Args, MSL,  						  ServerName),  	    reply(Tag, Reply), -	    loop(Parent, ServerName, MSL1, Debug, false); +	    loop(Parent, ServerName, MSL1, HibernateAfterTimeout, Debug, false);  	{_From, Tag, {swap_handler, Handler1, Args1, Handler2, Args2}} ->  	    {Hib, Reply, MSL1} = server_swap_handler(Handler1, Args1, Handler2,  						     Args2, MSL, ServerName),  	    reply(Tag, Reply), -	    loop(Parent, ServerName, MSL1, Debug, Hib); +	    loop(Parent, ServerName, MSL1, HibernateAfterTimeout, Debug, Hib);  	{_From, Tag, {swap_sup_handler, Handler1, Args1, Handler2, Args2,  		     Sup}} ->  	    {Hib, Reply, MSL1} = server_swap_handler(Handler1, Args1, Handler2,  						Args2, MSL, Sup, ServerName),  	    reply(Tag, Reply), -	    loop(Parent, ServerName, MSL1, Debug, Hib); +	    loop(Parent, ServerName, MSL1, HibernateAfterTimeout, Debug, Hib);  	{_From, Tag, stop} ->  	    catch terminate_server(normal, Parent, MSL, ServerName),  	    reply(Tag, ok);  	{_From, Tag, which_handlers} ->  	    reply(Tag, the_handlers(MSL)), -	    loop(Parent, ServerName, MSL, Debug, false); +	    loop(Parent, ServerName, MSL, HibernateAfterTimeout, Debug, false);  	{_From, Tag, get_modules} ->  	    reply(Tag, get_modules(MSL)), -	    loop(Parent, ServerName, MSL, Debug, false); +	    loop(Parent, ServerName, MSL, HibernateAfterTimeout, Debug, false);  	Other  ->  	    {Hib, MSL1} = server_notify(Other, handle_info, MSL, ServerName), -	    loop(Parent, ServerName, MSL1, Debug, Hib) +	    loop(Parent, ServerName, MSL1, HibernateAfterTimeout, Debug, Hib)      end.  terminate_server(Reason, Parent, MSL, ServerName) -> @@ -392,18 +395,18 @@ terminate_supervised(Pid, Reason, MSL, SName) ->  %%-----------------------------------------------------------------  %% Callback functions for system messages handling.  %%----------------------------------------------------------------- -system_continue(Parent, Debug, [ServerName, MSL, Hib]) -> -    loop(Parent, ServerName, MSL, Debug, Hib). +system_continue(Parent, Debug, [ServerName, MSL, HibernateAfterTimeout, Hib]) -> +    loop(Parent, ServerName, MSL, HibernateAfterTimeout, Debug, Hib).  -spec system_terminate(_, _, _, [_]) -> no_return(). -system_terminate(Reason, Parent, _Debug, [ServerName, MSL, _Hib]) -> +system_terminate(Reason, Parent, _Debug, [ServerName, MSL, _HibernateAfterTimeout, _Hib]) ->      terminate_server(Reason, Parent, MSL, ServerName).  %%-----------------------------------------------------------------  %% Module here is sent in the system msg change_code.  It specifies  %% which module should be changed.  %%----------------------------------------------------------------- -system_code_change([ServerName, MSL, Hib], Module, OldVsn, Extra) -> +system_code_change([ServerName, MSL, HibernateAfterTimeout, Hib], Module, OldVsn, Extra) ->      MSL1 = lists:zf(fun(H) when H#handler.module =:= Module ->  			    {ok, NewState} =  				Module:code_change(OldVsn, @@ -412,12 +415,12 @@ system_code_change([ServerName, MSL, Hib], Module, OldVsn, Extra) ->  		       (_) -> true  		    end,  		    MSL), -    {ok, [ServerName, MSL1, Hib]}. +    {ok, [ServerName, MSL1, HibernateAfterTimeout, Hib]}. -system_get_state([_ServerName, MSL, _Hib]) -> +system_get_state([_ServerName, MSL, _HibernateAfterTimeout, _Hib]) ->      {ok, [{Mod,Id,State} || #handler{module=Mod, id=Id, state=State} <- MSL]}. -system_replace_state(StateFun, [ServerName, MSL, Hib]) -> +system_replace_state(StateFun, [ServerName, MSL, HibernateAfterTimeout, Hib]) ->      {NMSL, NStates} =  		lists:unzip([begin  				 Cur = {Mod,Id,State}, @@ -429,7 +432,7 @@ system_replace_state(StateFun, [ServerName, MSL, Hib]) ->  					 {HS, Cur}  				 end  			     end || #handler{module=Mod, id=Id, state=State}=HS <- MSL]), -    {ok, NStates, [ServerName, NMSL, Hib]}. +    {ok, NStates, [ServerName, NMSL, HibernateAfterTimeout, Hib]}.  %%-----------------------------------------------------------------  %% Format debug messages.  Print them as the call-back module sees @@ -798,7 +801,7 @@ get_modules(MSL) ->  %% Status information  %%-----------------------------------------------------------------  format_status(Opt, StatusData) -> -    [PDict, SysState, Parent, _Debug, [ServerName, MSL, _Hib]] = StatusData, +    [PDict, SysState, Parent, _Debug, [ServerName, MSL, _HibernateAfterTimeout, _Hib]] = StatusData,      Header = gen:format_status_header("Status for event handler",                                        ServerName),      FmtMSL = [case erlang:function_exported(Mod, format_status, 2) of diff --git a/lib/stdlib/src/gen_fsm.erl b/lib/stdlib/src/gen_fsm.erl index f9d4286a7c..9ef0ca818c 100644 --- a/lib/stdlib/src/gen_fsm.erl +++ b/lib/stdlib/src/gen_fsm.erl @@ -113,7 +113,7 @@  	 sync_send_all_state_event/2, sync_send_all_state_event/3,  	 reply/2,  	 start_timer/2,send_event_after/2,cancel_timer/1, -	 enter_loop/4, enter_loop/5, enter_loop/6, wake_hib/6]). +	 enter_loop/4, enter_loop/5, enter_loop/6, wake_hib/7]).  %% Internal exports  -export([init_it/6, @@ -329,7 +329,8 @@ enter_loop(Mod, Options, StateName, StateData, ServerName, Timeout) ->      Name = gen:get_proc_name(ServerName),      Parent = gen:get_parent(),      Debug = gen:debug_options(Name, Options), -    loop(Parent, Name, StateName, StateData, Mod, Timeout, Debug). +	HibernateAfterTimeout = gen:hibernate_after(Options), +    loop(Parent, Name, StateName, StateData, Mod, Timeout, HibernateAfterTimeout, Debug).  %%% ---------------------------------------------------  %%% Initiate the new process. @@ -343,13 +344,14 @@ init_it(Starter, self, Name, Mod, Args, Options) ->  init_it(Starter, Parent, Name0, Mod, Args, Options) ->      Name = gen:name(Name0),      Debug = gen:debug_options(Name, Options), -    case catch Mod:init(Args) of +	HibernateAfterTimeout = gen:hibernate_after(Options), +	case catch Mod:init(Args) of  	{ok, StateName, StateData} ->  	    proc_lib:init_ack(Starter, {ok, self()}), 	     -	    loop(Parent, Name, StateName, StateData, Mod, infinity, Debug); +	    loop(Parent, Name, StateName, StateData, Mod, infinity, HibernateAfterTimeout, Debug);  	{ok, StateName, StateData, Timeout} ->  	    proc_lib:init_ack(Starter, {ok, self()}), 	     -	    loop(Parent, Name, StateName, StateData, Mod, Timeout, Debug); +	    loop(Parent, Name, StateName, StateData, Mod, Timeout, HibernateAfterTimeout, Debug);  	{stop, Reason} ->  	    gen:unregister_name(Name0),  	    proc_lib:init_ack(Starter, {error, Reason}), @@ -371,68 +373,77 @@ init_it(Starter, Parent, Name0, Mod, Args, Options) ->  %%-----------------------------------------------------------------  %% The MAIN loop  %%----------------------------------------------------------------- -loop(Parent, Name, StateName, StateData, Mod, hibernate, Debug) -> +loop(Parent, Name, StateName, StateData, Mod, hibernate, HibernateAfterTimeout, Debug) ->      proc_lib:hibernate(?MODULE,wake_hib, -		       [Parent, Name, StateName, StateData, Mod,  +		       [Parent, Name, StateName, StateData, Mod, HibernateAfterTimeout,  			Debug]); -loop(Parent, Name, StateName, StateData, Mod, Time, Debug) -> + +loop(Parent, Name, StateName, StateData, Mod, infinity, HibernateAfterTimeout, Debug) -> +	receive +		Msg -> +			decode_msg(Msg,Parent, Name, StateName, StateData, Mod, infinity, HibernateAfterTimeout, Debug, false) +	after HibernateAfterTimeout -> +		loop(Parent, Name, StateName, StateData, Mod, hibernate, HibernateAfterTimeout, Debug) +	end; + +loop(Parent, Name, StateName, StateData, Mod, Time, HibernateAfterTimeout, Debug) ->      Msg = receive  	      Input ->  		    Input  	  after Time ->  		  {'$gen_event', timeout}  	  end, -    decode_msg(Msg,Parent, Name, StateName, StateData, Mod, Time, Debug, false). +    decode_msg(Msg,Parent, Name, StateName, StateData, Mod, Time, HibernateAfterTimeout, Debug, false). -wake_hib(Parent, Name, StateName, StateData, Mod, Debug) -> +wake_hib(Parent, Name, StateName, StateData, Mod, HibernateAfterTimeout, Debug) ->      Msg = receive  	      Input ->  		  Input  	  end, -    decode_msg(Msg, Parent, Name, StateName, StateData, Mod, hibernate, Debug, true). +    decode_msg(Msg, Parent, Name, StateName, StateData, Mod, hibernate, HibernateAfterTimeout, Debug, true). -decode_msg(Msg,Parent, Name, StateName, StateData, Mod, Time, Debug, Hib) -> +decode_msg(Msg,Parent, Name, StateName, StateData, Mod, Time, HibernateAfterTimeout, Debug, Hib) ->      case Msg of          {system, From, Req} ->  	    sys:handle_system_msg(Req, From, Parent, ?MODULE, Debug, -				  [Name, StateName, StateData, Mod, Time], Hib); +				  [Name, StateName, StateData, Mod, Time, HibernateAfterTimeout], Hib);  	{'EXIT', Parent, Reason} ->  	    terminate(Reason, Name, Msg, Mod, StateName, StateData, Debug);  	_Msg when Debug =:= [] -> -	    handle_msg(Msg, Parent, Name, StateName, StateData, Mod, Time); +	    handle_msg(Msg, Parent, Name, StateName, StateData, Mod, Time, HibernateAfterTimeout);  	_Msg ->  	    Debug1 = sys:handle_debug(Debug, fun print_event/3,  				      {Name, StateName}, {in, Msg}),  	    handle_msg(Msg, Parent, Name, StateName, StateData, -		       Mod, Time, Debug1) +		       Mod, Time, HibernateAfterTimeout, Debug1)      end.  %%-----------------------------------------------------------------  %% Callback functions for system messages handling.  %%----------------------------------------------------------------- -system_continue(Parent, Debug, [Name, StateName, StateData, Mod, Time]) -> -    loop(Parent, Name, StateName, StateData, Mod, Time, Debug). +system_continue(Parent, Debug, [Name, StateName, StateData, Mod, Time, HibernateAfterTimeout]) -> +    loop(Parent, Name, StateName, StateData, Mod, Time, HibernateAfterTimeout, Debug).  -spec system_terminate(term(), _, _, [term(),...]) -> no_return().  system_terminate(Reason, _Parent, Debug, -		 [Name, StateName, StateData, Mod, _Time]) -> +		 [Name, StateName, StateData, Mod, _Time, _HibernateAfterTimeout]) ->      terminate(Reason, Name, [], Mod, StateName, StateData, Debug). -system_code_change([Name, StateName, StateData, Mod, Time], +system_code_change([Name, StateName, StateData, Mod, Time, HibernateAfterTimeout],  		   _Module, OldVsn, Extra) ->      case catch Mod:code_change(OldVsn, StateName, StateData, Extra) of  	{ok, NewStateName, NewStateData} -> -	    {ok, [Name, NewStateName, NewStateData, Mod, Time]}; +	    {ok, [Name, NewStateName, NewStateData, Mod, Time, HibernateAfterTimeout]};  	Else -> Else      end. -system_get_state([_Name, StateName, StateData, _Mod, _Time]) -> +system_get_state([_Name, StateName, StateData, _Mod, _Time, _HibernateAfterTimeout]) ->      {ok, {StateName, StateData}}. -system_replace_state(StateFun, [Name, StateName, StateData, Mod, Time]) -> +system_replace_state(StateFun, [Name, StateName, StateData, Mod, Time, HibernateAfterTimeout]) ->      Result = {NStateName, NStateData} = StateFun({StateName, StateData}), -    {ok, Result, [Name, NStateName, NStateData, Mod, Time]}. +    {ok, Result, [Name, NStateName, NStateData, Mod, Time, HibernateAfterTimeout]}.  %%-----------------------------------------------------------------  %% Format debug messages.  Print them as the call-back module sees @@ -467,19 +478,19 @@ print_event(Dev, return, {Name, StateName}) ->      io:format(Dev, "*DBG* ~p switched to state ~w~n",  	      [Name, StateName]). -handle_msg(Msg, Parent, Name, StateName, StateData, Mod, _Time) -> %No debug here +handle_msg(Msg, Parent, Name, StateName, StateData, Mod, _Time, HibernateAfterTimeout) -> %No debug here      From = from(Msg),      case catch dispatch(Msg, Mod, StateName, StateData) of  	{next_state, NStateName, NStateData} ->	     -	    loop(Parent, Name, NStateName, NStateData, Mod, infinity, []); +	    loop(Parent, Name, NStateName, NStateData, Mod, infinity, HibernateAfterTimeout, []);  	{next_state, NStateName, NStateData, Time1} -> -	    loop(Parent, Name, NStateName, NStateData, Mod, Time1, []); +	    loop(Parent, Name, NStateName, NStateData, Mod, Time1, HibernateAfterTimeout, []);          {reply, Reply, NStateName, NStateData} when From =/= undefined ->  	    reply(From, Reply), -	    loop(Parent, Name, NStateName, NStateData, Mod, infinity, []); +	    loop(Parent, Name, NStateName, NStateData, Mod, infinity, HibernateAfterTimeout, []);          {reply, Reply, NStateName, NStateData, Time1} when From =/= undefined ->  	    reply(From, Reply), -	    loop(Parent, Name, NStateName, NStateData, Mod, Time1, []); +	    loop(Parent, Name, NStateName, NStateData, Mod, Time1, HibernateAfterTimeout, []);  	{stop, Reason, NStateData} ->  	    terminate(Reason, Name, Msg, Mod, StateName, NStateData, []);  	{stop, Reason, Reply, NStateData} when From =/= undefined -> @@ -490,7 +501,7 @@ handle_msg(Msg, Parent, Name, StateName, StateData, Mod, _Time) -> %No debug her          {'EXIT', {undef, [{Mod, handle_info, [_,_,_], _}|_]}} ->              error_logger:warning_msg("** Undefined handle_info in ~p~n"                                       "** Unhandled message: ~p~n", [Mod, Msg]), -            loop(Parent, Name, StateName, StateData, Mod, infinity, []); +            loop(Parent, Name, StateName, StateData, Mod, infinity, HibernateAfterTimeout, []);  	{'EXIT', What} ->  	    terminate(What, Name, Msg, Mod, StateName, StateData, []);  	Reply -> @@ -498,23 +509,23 @@ handle_msg(Msg, Parent, Name, StateName, StateData, Mod, _Time) -> %No debug her  		      Name, Msg, Mod, StateName, StateData, [])      end. -handle_msg(Msg, Parent, Name, StateName, StateData, Mod, _Time, Debug) -> +handle_msg(Msg, Parent, Name, StateName, StateData, Mod, _Time, HibernateAfterTimeout, Debug) ->      From = from(Msg),      case catch dispatch(Msg, Mod, StateName, StateData) of  	{next_state, NStateName, NStateData} ->  	    Debug1 = sys:handle_debug(Debug, fun print_event/3,  				      {Name, NStateName}, return), -	    loop(Parent, Name, NStateName, NStateData, Mod, infinity, Debug1); +	    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), -	    loop(Parent, Name, NStateName, NStateData, Mod, Time1, Debug1); +	    loop(Parent, Name, NStateName, NStateData, Mod, Time1, HibernateAfterTimeout, Debug1);          {reply, Reply, NStateName, NStateData} when From =/= undefined ->  	    Debug1 = reply(Name, From, Reply, Debug, NStateName), -	    loop(Parent, Name, NStateName, NStateData, Mod, infinity, Debug1); +	    loop(Parent, Name, NStateName, NStateData, Mod, infinity, HibernateAfterTimeout, Debug1);          {reply, Reply, NStateName, NStateData, Time1} when From =/= undefined ->  	    Debug1 = reply(Name, From, Reply, Debug, NStateName), -	    loop(Parent, Name, NStateName, NStateData, Mod, Time1, Debug1); +	    loop(Parent, Name, NStateName, NStateData, Mod, Time1, HibernateAfterTimeout, Debug1);  	{stop, Reason, NStateData} ->  	    terminate(Reason, Name, Msg, Mod, StateName, NStateData, Debug);  	{stop, Reason, Reply, NStateData} when From =/= undefined -> @@ -645,7 +656,7 @@ get_msg(Msg) -> Msg.  %% Status information  %%-----------------------------------------------------------------  format_status(Opt, StatusData) -> -    [PDict, SysState, Parent, Debug, [Name, StateName, StateData, Mod, _Time]] = +    [PDict, SysState, Parent, Debug, [Name, StateName, StateData, Mod, _Time, _HibernateAfterTimeout]] =  	StatusData,      Header = gen:format_status_header("Status for state machine",                                        Name), diff --git a/lib/stdlib/src/gen_server.erl b/lib/stdlib/src/gen_server.erl index e628fec00f..ba0a7ae8e5 100644 --- a/lib/stdlib/src/gen_server.erl +++ b/lib/stdlib/src/gen_server.erl @@ -94,7 +94,7 @@  	 cast/2, reply/2,  	 abcast/2, abcast/3,  	 multi_call/2, multi_call/3, multi_call/4, -	 enter_loop/3, enter_loop/4, enter_loop/5, wake_hib/5]). +	 enter_loop/3, enter_loop/4, enter_loop/5, wake_hib/6]).  %% System exports  -export([system_continue/3, @@ -307,7 +307,8 @@ enter_loop(Mod, Options, State, ServerName, Timeout) ->      Name = gen:get_proc_name(ServerName),      Parent = gen:get_parent(),      Debug = gen:debug_options(Name, Options), -    loop(Parent, Name, State, Mod, Timeout, Debug). +	HibernateAfterTimeout = gen:hibernate_after(Options), +    loop(Parent, Name, State, Mod, Timeout, HibernateAfterTimeout, Debug).  %%%========================================================================  %%% Gen-callback functions @@ -325,13 +326,14 @@ init_it(Starter, self, Name, Mod, Args, Options) ->  init_it(Starter, Parent, Name0, Mod, Args, Options) ->      Name = gen:name(Name0),      Debug = gen:debug_options(Name, Options), +	HibernateAfterTimeout = gen:hibernate_after(Options),      case catch Mod:init(Args) of  	{ok, State} ->  	    proc_lib:init_ack(Starter, {ok, self()}), 	     -	    loop(Parent, Name, State, Mod, infinity, Debug); +	    loop(Parent, Name, State, Mod, infinity, HibernateAfterTimeout, Debug);  	{ok, State, Timeout} ->  	    proc_lib:init_ack(Starter, {ok, self()}), 	     -	    loop(Parent, Name, State, Mod, Timeout, Debug); +	    loop(Parent, Name, State, Mod, Timeout, HibernateAfterTimeout, Debug);  	{stop, Reason} ->  	    %% For consistency, we must make sure that the  	    %% registered name (if any) is unregistered before @@ -362,37 +364,46 @@ init_it(Starter, Parent, Name0, Mod, Args, Options) ->  %%% ---------------------------------------------------  %%% The MAIN loop.  %%% --------------------------------------------------- -loop(Parent, Name, State, Mod, hibernate, Debug) -> -    proc_lib:hibernate(?MODULE,wake_hib,[Parent, Name, State, Mod, Debug]); -loop(Parent, Name, State, Mod, Time, Debug) -> +loop(Parent, Name, State, Mod, hibernate, HibernateAfterTimeout, Debug) -> +    proc_lib:hibernate(?MODULE,wake_hib,[Parent, Name, State, Mod, HibernateAfterTimeout, Debug]); + +loop(Parent, Name, State, Mod, infinity, HibernateAfterTimeout, Debug) -> +	receive +		Msg -> +			decode_msg(Msg, Parent, Name, State, Mod, infinity, HibernateAfterTimeout, Debug, false) +	after HibernateAfterTimeout -> +		loop(Parent, Name, State, Mod, hibernate, HibernateAfterTimeout, Debug) +	end; + +loop(Parent, Name, State, Mod, Time, HibernateAfterTimeout, Debug) ->      Msg = receive  	      Input ->  		    Input  	  after Time ->  		  timeout  	  end, -    decode_msg(Msg, Parent, Name, State, Mod, Time, Debug, false). +    decode_msg(Msg, Parent, Name, State, Mod, Time, HibernateAfterTimeout, Debug, false). -wake_hib(Parent, Name, State, Mod, Debug) -> +wake_hib(Parent, Name, State, Mod, HibernateAfterTimeout, Debug) ->      Msg = receive  	      Input ->  		  Input  	  end, -    decode_msg(Msg, Parent, Name, State, Mod, hibernate, Debug, true). +    decode_msg(Msg, Parent, Name, State, Mod, hibernate, HibernateAfterTimeout, Debug, true). -decode_msg(Msg, Parent, Name, State, Mod, Time, Debug, Hib) -> +decode_msg(Msg, Parent, Name, State, Mod, Time, HibernateAfterTimeout, Debug, Hib) ->      case Msg of  	{system, From, Req} ->  	    sys:handle_system_msg(Req, From, Parent, ?MODULE, Debug, -				  [Name, State, Mod, Time], Hib); +				  [Name, State, Mod, Time, HibernateAfterTimeout], Hib);  	{'EXIT', Parent, Reason} ->  	    terminate(Reason, Name, undefined, Msg, Mod, State, Debug);  	_Msg when Debug =:= [] -> -	    handle_msg(Msg, Parent, Name, State, Mod); +	    handle_msg(Msg, Parent, Name, State, Mod, HibernateAfterTimeout);  	_Msg ->  	    Debug1 = sys:handle_debug(Debug, fun print_event/3,  				      Name, {in, Msg}), -	    handle_msg(Msg, Parent, Name, State, Mod, Debug1) +	    handle_msg(Msg, Parent, Name, State, Mod, HibernateAfterTimeout, Debug1)      end.  %%% --------------------------------------------------- @@ -659,65 +670,65 @@ try_terminate(Mod, Reason, State) ->  %%% Message handling functions  %%% --------------------------------------------------- -handle_msg({'$gen_call', From, Msg}, Parent, Name, State, Mod) -> +handle_msg({'$gen_call', From, Msg}, Parent, Name, State, Mod, HibernateAfterTimeout) ->      Result = try_handle_call(Mod, Msg, From, State),      case Result of  	{ok, {reply, Reply, NState}} ->  	    reply(From, Reply), -	    loop(Parent, Name, NState, Mod, infinity, []); +	    loop(Parent, Name, NState, Mod, infinity, HibernateAfterTimeout, []);  	{ok, {reply, Reply, NState, Time1}} ->  	    reply(From, Reply), -	    loop(Parent, Name, NState, Mod, Time1, []); +	    loop(Parent, Name, NState, Mod, Time1, HibernateAfterTimeout, []);  	{ok, {noreply, NState}} -> -	    loop(Parent, Name, NState, Mod, infinity, []); +	    loop(Parent, Name, NState, Mod, infinity, HibernateAfterTimeout, []);  	{ok, {noreply, NState, Time1}} -> -	    loop(Parent, Name, NState, Mod, Time1, []); +	    loop(Parent, Name, NState, Mod, Time1, HibernateAfterTimeout, []);  	{ok, {stop, Reason, Reply, NState}} ->  	    {'EXIT', R} =   		(catch terminate(Reason, Name, From, Msg, Mod, NState, [])),  	    reply(From, Reply),  	    exit(R); -	Other -> handle_common_reply(Other, Parent, Name, From, Msg, Mod, State) +	Other -> handle_common_reply(Other, Parent, Name, From, Msg, Mod, HibernateAfterTimeout, State)      end; -handle_msg(Msg, Parent, Name, State, Mod) -> +handle_msg(Msg, Parent, Name, State, Mod, HibernateAfterTimeout) ->      Reply = try_dispatch(Msg, Mod, State), -    handle_common_reply(Reply, Parent, Name, undefined, Msg, Mod, State). +    handle_common_reply(Reply, Parent, Name, undefined, Msg, Mod, HibernateAfterTimeout, State). -handle_msg({'$gen_call', From, Msg}, Parent, Name, State, Mod, Debug) -> +handle_msg({'$gen_call', From, Msg}, Parent, Name, State, Mod, HibernateAfterTimeout, Debug) ->      Result = try_handle_call(Mod, Msg, From, State),      case Result of  	{ok, {reply, Reply, NState}} ->  	    Debug1 = reply(Name, From, Reply, NState, Debug), -	    loop(Parent, Name, NState, Mod, infinity, Debug1); +	    loop(Parent, Name, NState, Mod, infinity, HibernateAfterTimeout, Debug1);  	{ok, {reply, Reply, NState, Time1}} ->  	    Debug1 = reply(Name, From, Reply, NState, Debug), -	    loop(Parent, Name, NState, Mod, Time1, Debug1); +	    loop(Parent, Name, NState, Mod, Time1, HibernateAfterTimeout, Debug1);  	{ok, {noreply, NState}} ->  	    Debug1 = sys:handle_debug(Debug, fun print_event/3, Name,  				      {noreply, NState}), -	    loop(Parent, Name, NState, Mod, infinity, Debug1); +	    loop(Parent, Name, NState, Mod, infinity, HibernateAfterTimeout, Debug1);  	{ok, {noreply, NState, Time1}} ->  	    Debug1 = sys:handle_debug(Debug, fun print_event/3, Name,  				      {noreply, NState}), -	    loop(Parent, Name, NState, Mod, Time1, Debug1); +	    loop(Parent, Name, NState, Mod, Time1, HibernateAfterTimeout, Debug1);  	{ok, {stop, Reason, Reply, NState}} ->  	    {'EXIT', R} =   		(catch terminate(Reason, Name, From, Msg, Mod, NState, Debug)),  	    _ = reply(Name, From, Reply, NState, Debug),  	    exit(R);  	Other -> -	    handle_common_reply(Other, Parent, Name, From, Msg, Mod, State, Debug) +	    handle_common_reply(Other, Parent, Name, From, Msg, Mod, HibernateAfterTimeout, State, Debug)      end; -handle_msg(Msg, Parent, Name, State, Mod, Debug) -> +handle_msg(Msg, Parent, Name, State, Mod, HibernateAfterTimeout, Debug) ->      Reply = try_dispatch(Msg, Mod, State), -    handle_common_reply(Reply, Parent, Name, undefined, Msg, Mod, State, Debug). +    handle_common_reply(Reply, Parent, Name, undefined, Msg, Mod, HibernateAfterTimeout, State, Debug). -handle_common_reply(Reply, Parent, Name, From, Msg, Mod, State) -> +handle_common_reply(Reply, Parent, Name, From, Msg, Mod, HibernateAfterTimeout, State) ->      case Reply of  	{ok, {noreply, NState}} -> -	    loop(Parent, Name, NState, Mod, infinity, []); +	    loop(Parent, Name, NState, Mod, infinity, HibernateAfterTimeout, []);  	{ok, {noreply, NState, Time1}} -> -	    loop(Parent, Name, NState, Mod, Time1, []); +	    loop(Parent, Name, NState, Mod, Time1, HibernateAfterTimeout, []);  	{ok, {stop, Reason, NState}} ->  	    terminate(Reason, Name, From, Msg, Mod, NState, []);  	{'EXIT', ExitReason, ReportReason} -> @@ -726,16 +737,16 @@ handle_common_reply(Reply, Parent, Name, From, Msg, Mod, State) ->  	    terminate({bad_return_value, BadReply}, Name, From, Msg, Mod, State, [])      end. -handle_common_reply(Reply, Parent, Name, From, Msg, Mod, State, Debug) -> +handle_common_reply(Reply, Parent, Name, From, Msg, Mod, HibernateAfterTimeout, State, Debug) ->      case Reply of  	{ok, {noreply, NState}} ->  	    Debug1 = sys:handle_debug(Debug, fun print_event/3, Name,  				      {noreply, NState}), -	    loop(Parent, Name, NState, Mod, infinity, Debug1); +	    loop(Parent, Name, NState, Mod, infinity, HibernateAfterTimeout, Debug1);  	{ok, {noreply, NState, Time1}} ->  	    Debug1 = sys:handle_debug(Debug, fun print_event/3, Name,  				      {noreply, NState}), -	    loop(Parent, Name, NState, Mod, Time1, Debug1); +	    loop(Parent, Name, NState, Mod, Time1, HibernateAfterTimeout, Debug1);  	{ok, {stop, Reason, NState}} ->  	    terminate(Reason, Name, From, Msg, Mod, NState, Debug);  	{'EXIT', ExitReason, ReportReason} -> @@ -753,26 +764,26 @@ reply(Name, {To, Tag}, Reply, State, Debug) ->  %%-----------------------------------------------------------------  %% Callback functions for system messages handling.  %%----------------------------------------------------------------- -system_continue(Parent, Debug, [Name, State, Mod, Time]) -> -    loop(Parent, Name, State, Mod, Time, Debug). +system_continue(Parent, Debug, [Name, State, Mod, Time, HibernateAfterTimeout]) -> +    loop(Parent, Name, State, Mod, Time, HibernateAfterTimeout, Debug).  -spec system_terminate(_, _, _, [_]) -> no_return(). -system_terminate(Reason, _Parent, Debug, [Name, State, Mod, _Time]) -> +system_terminate(Reason, _Parent, Debug, [Name, State, Mod, _Time, _HibernateAfterTimeout]) ->      terminate(Reason, Name, undefined, [], Mod, State, Debug). -system_code_change([Name, State, Mod, Time], _Module, OldVsn, Extra) -> +system_code_change([Name, State, Mod, Time, HibernateAfterTimeout], _Module, OldVsn, Extra) ->      case catch Mod:code_change(OldVsn, State, Extra) of -	{ok, NewState} -> {ok, [Name, NewState, Mod, Time]}; +	{ok, NewState} -> {ok, [Name, NewState, Mod, Time, HibernateAfterTimeout]};  	Else -> Else      end. -system_get_state([_Name, State, _Mod, _Time]) -> +system_get_state([_Name, State, _Mod, _Time, _HibernateAfterTimeout]) ->      {ok, State}. -system_replace_state(StateFun, [Name, State, Mod, Time]) -> +system_replace_state(StateFun, [Name, State, Mod, Time, HibernateAfterTimeout]) ->      NState = StateFun(State), -    {ok, NState, [Name, NState, Mod, Time]}. +    {ok, NState, [Name, NState, Mod, Time, HibernateAfterTimeout]}.  %%-----------------------------------------------------------------  %% Format debug messages.  Print them as the call-back module sees @@ -802,10 +813,10 @@ print_event(Dev, Event, Name) ->  %%% Terminate the server.  %%% --------------------------------------------------- +  -spec terminate(_, _, _, _, _, _, _) -> no_return().  terminate(Reason, Name, From, Msg, Mod, State, Debug) ->      terminate(Reason, Reason, Name, From, Msg, Mod, State, Debug). -  -spec terminate(_, _, _, _, _, _, _, _) -> no_return().  terminate(ExitReason, ReportReason, Name, From, Msg, Mod, State, Debug) ->      Reply = try_terminate(Mod, ExitReason, State), @@ -851,7 +862,7 @@ error_info(Reason, Name, From, Msg, State, Debug) ->  		end;  	    _ ->  		Reason -	end, +	end,          {ClientFmt, ClientArgs} = client_stacktrace(From),      format("** Generic server ~p terminating \n"             "** Last message in was ~p~n" @@ -860,7 +871,6 @@ error_info(Reason, Name, From, Msg, State, Debug) ->  	   [Name, Msg, State, Reason1] ++ ClientArgs),      sys:print_log(Debug),      ok. -  client_stacktrace(undefined) ->      {"", []};  client_stacktrace({From, _Tag}) -> @@ -885,7 +895,7 @@ client_stacktrace(From) when is_pid(From) ->  %% Status information  %%-----------------------------------------------------------------  format_status(Opt, StatusData) -> -    [PDict, SysState, Parent, Debug, [Name, State, Mod, _Time]] = 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 diff --git a/lib/stdlib/src/gen_statem.erl b/lib/stdlib/src/gen_statem.erl index 6f566b8beb..86109f04b4 100644 --- a/lib/stdlib/src/gen_statem.erl +++ b/lib/stdlib/src/gen_statem.erl @@ -369,9 +369,12 @@ event_type(Type) ->  	 Dbgs ::  	   ['trace' | 'log' | 'statistics' | 'debug'  	    | {'logfile', string()}]}. +-type hibernate_after_opt() :: +	{'hibernate_after', HibernateAfterTimeout :: timeout()}.  -type start_opt() ::  	debug_opt()        | {'timeout', Time :: timeout()} +	  | hibernate_after_opt()        | {'spawn_opt', [proc_lib:spawn_option()]}.  -type start_ret() ::  {'ok', pid()} | 'ignore' | {'error', term()}. @@ -544,14 +547,14 @@ reply({To,Tag}, Reply) when is_pid(To) ->  %% started by proc_lib into a state machine using  %% the same arguments as you would have returned from init/1  -spec enter_loop( -	Module :: module(), Opts :: [debug_opt()], +	Module :: module(), Opts :: [debug_opt() | hibernate_after_opt()],  	State :: state(), Data :: data()) ->  			no_return().  enter_loop(Module, Opts, State, Data) ->      enter_loop(Module, Opts, State, Data, self()).  %%  -spec enter_loop( -	Module :: module(), Opts :: [debug_opt()], +	Module :: module(), Opts :: [debug_opt() | hibernate_after_opt()],  	State :: state(), Data :: data(),  	Server_or_Actions ::  	  server_name() | pid() | [action()]) -> @@ -565,7 +568,7 @@ enter_loop(Module, Opts, State, Data, Server_or_Actions) ->      end.  %%  -spec enter_loop( -	Module :: module(), Opts :: [debug_opt()], +	Module :: module(), Opts :: [debug_opt() | hibernate_after_opt()],  	State :: state(), Data :: data(),  	Server :: server_name() | pid(),  	Actions :: [action()] | action()) -> @@ -605,7 +608,8 @@ enter(Module, Opts, State, Data, Server, Actions, Parent) ->      %% The values should already have been type checked      Name = gen:get_proc_name(Server),      Debug = gen:debug_options(Name, Opts), -    Events = [], +	HibernateAfterTimeout = gen:hibernate_after(Opts), +	Events = [],      P = [],      Event = {internal,init_state},      %% We enforce {postpone,false} to ensure that @@ -648,6 +652,7 @@ enter(Module, Opts, State, Data, Server, Actions, Parent) ->        timer_refs => TimerRefs,        timer_types => TimerTypes,        hibernate => Hibernate, +	  hibernate_after => HibernateAfterTimeout,        cancel_timers => CancelTimers       },      NewDebug = sys_debug(Debug, S, State, {enter,Event,State}), @@ -854,7 +859,7 @@ loop_hibernate(Parent, Debug, S) ->         {wakeup_from_hibernate,3}}).  %% Entry point for wakeup_from_hibernate/3 -loop_receive(Parent, Debug, S) -> +loop_receive(Parent, Debug, #{hibernate_after := HibernateAfterTimeout} = S) ->      receive  	Msg ->  	    case Msg of @@ -956,6 +961,9 @@ loop_receive(Parent, Debug, S) ->  		    loop_receive_result(  		      Parent, Debug, S, Hibernate, Event)  	    end +    after +	    HibernateAfterTimeout -> +		    loop_hibernate(Parent, Debug, S)      end.  loop_receive_result( | 
