File 2462-Implement-erlang-start_timer-opts.patch of Package erlang

From bca4b5c87fd1aae2fdcb78b605181393a0caf9d9 Mon Sep 17 00:00:00 2001
From: Raimo Niskanen <raimo@erlang.org>
Date: Tue, 7 Feb 2017 22:38:36 +0100
Subject: [PATCH 2/4] Implement erlang:start_timer opts

---
 lib/stdlib/doc/src/gen_statem.xml    |  75 ++++++++++++++-----
 lib/stdlib/src/gen_statem.erl        | 139 ++++++++++++++++++++++++++---------
 lib/stdlib/test/gen_statem_SUITE.erl |   3 +-
 3 files changed, 162 insertions(+), 55 deletions(-)

diff --git a/lib/stdlib/doc/src/gen_statem.xml b/lib/stdlib/doc/src/gen_statem.xml
index f7baaad5d..44ac1ad8a 100644
--- a/lib/stdlib/doc/src/gen_statem.xml
+++ b/lib/stdlib/doc/src/gen_statem.xml
@@ -785,28 +785,38 @@ handle_event(_, _, State, Data) ->
       <name name="event_timeout"/>
       <desc>
 	<p>
-	  Generates an event of
+	  Starts a timer set by
+	  <seealso marker="#type-enter_action"><c>enter_action()</c></seealso>
+	  <c>timeout</c>.
+	  When the timer expires an event of
 	  <seealso marker="#type-event_type"><c>event_type()</c></seealso>
-	  <c>timeout</c>
-	  after this time (in milliseconds) unless another
-	  event arrives or has arrived
-	  in which case this time-out is cancelled.
+	  <c>timeout</c> will be generated.
+	  See
+	  <seealso marker="erts:erlang#start_timer/4"><c>erlang:start_timer/4</c></seealso>
+	  for how <c>Time</c> and
+	  <seealso marker="#type-timeout_option"><c>Options</c></seealso>
+	  are interpreted.  All <c>Options</c> of <c>erlang:start_timer/4</c>
+	  will not necessarily be supported in the future.
+	</p>
+	<p>
+	  Any event that arrives cancels this time-out.
 	  Note that a retried or inserted event counts as arrived.
 	  So does a state time-out zero event, if it was generated
-	  before this timer is requested.
+	  before this time-out is requested.
 	</p>
 	<p>
-	  If the value is <c>infinity</c>, no timer is started, as
-	  it never would trigger anyway.
+	  If <c>Time</c> is <c>infinity</c>,
+	  no timer is started, as it never would expire anyway.
 	</p>
 	<p>
-	  If the value is <c>0</c> no timer is actually started,
+	  If <c>Time</c> is relative and <c>0</c>
+	  no timer is actually started,
 	  instead the the time-out event is enqueued to ensure
 	  that it gets processed before any not yet
 	  received external event.
 	</p>
 	<p>
-	  Note that it is not possible or needed to cancel this time-out,
+	  Note that it is not possible nor needed to cancel this time-out,
 	  as it is cancelled automatically by any other event.
 	</p>
       </desc>
@@ -815,19 +825,26 @@ handle_event(_, _, State, Data) ->
       <name name="state_timeout"/>
       <desc>
 	<p>
-	  Generates an event of
+	  Starts a timer set by
+	  <seealso marker="#type-enter_action"><c>enter_action()</c></seealso>
+	  <c>state_timeout</c>.
+	  When the timer expires an event of
 	  <seealso marker="#type-event_type"><c>event_type()</c></seealso>
-	  <c>state_timeout</c>
-	  after this time (in milliseconds) unless the <c>gen_statem</c>
-	  changes states (<c>NewState =/= OldState</c>)
-	  which case this time-out is cancelled.
+	  <c>state_timeout</c> will be generated.
+	  See
+	  <seealso marker="erts:erlang#start_timer/4"><c>erlang:start_timer/4</c></seealso>
+	  for how <c>Time</c> and
+	  <seealso marker="#type-timeout_option"><c>Options</c></seealso>
+	  are interpreted.  All <c>Options</c> of <c>erlang:start_timer/4</c>
+	  will not necessarily be supported in the future.
 	</p>
 	<p>
-	  If the value is <c>infinity</c>, no timer is started, as
-	  it never would trigger anyway.
+	  If <c>Time</c> is <c>infinity</c>,
+	  no timer is started, as it never would expire anyway.
 	</p>
 	<p>
-	  If the value is <c>0</c> no timer is actually started,
+	  If <c>Time</c> is relative and <c>0</c>
+	  no timer is actually started,
 	  instead the the time-out event is enqueued to ensure
 	  that it gets processed before any not yet
 	  received external event.
@@ -840,6 +857,20 @@ handle_event(_, _, State, Data) ->
       </desc>
     </datatype>
     <datatype>
+      <name name="timeout_option"/>
+      <desc>
+	<p>
+	  If <c>Abs</c> is <c>true</c> an absolute timer is started,
+	  and if it <c>false</c> a relative, which is the default.
+	  See
+	  <seealso marker="erts:erlang#start_timer/4"><c>erlang:start_timer/4</c></seealso>
+	  for details.
+	</p>
+	<p>
+	</p>
+      </desc>
+    </datatype>
+    <datatype>
       <name name="action"/>
       <desc>
 	<p>
@@ -954,7 +985,9 @@ handle_event(_, _, State, Data) ->
 	      Sets the
 	      <seealso marker="#type-transition_option"><c>transition_option()</c></seealso>
 	      <seealso marker="#type-event_timeout"><c>event_timeout()</c></seealso>
-	      to <c><anno>Time</anno></c> with <c><anno>EventContent</anno></c>.
+	      to <c><anno>Time</anno></c> with <c><anno>EventContent</anno></c>
+	      and options
+	      <seealso marker="#type-timeout_option"><c><anno>Options</anno></c></seealso>.
 	    </p>
 	  </item>
 	  <tag><c>state_timeout</c></tag>
@@ -963,7 +996,9 @@ handle_event(_, _, State, Data) ->
 	      Sets the
 	      <seealso marker="#type-transition_option"><c>transition_option()</c></seealso>
 	      <seealso marker="#type-state_timeout"><c>state_timeout()</c></seealso>
-	      to <c><anno>Time</anno></c> with <c><anno>EventContent</anno></c>.
+	      to <c><anno>Time</anno></c> with <c><anno>EventContent</anno></c>
+	      and options
+	      <seealso marker="#type-timeout_option"><c><anno>Options</anno></c></seealso>.
 	    </p>
 	  </item>
 	</taglist>
diff --git a/lib/stdlib/src/gen_statem.erl b/lib/stdlib/src/gen_statem.erl
index 242ff87be..fe80bb5de 100644
--- a/lib/stdlib/src/gen_statem.erl
+++ b/lib/stdlib/src/gen_statem.erl
@@ -97,13 +97,14 @@
 	%% If 'true' hibernate the server instead of going into receive
 	boolean().
 -type event_timeout() ::
-	%% Generate a ('timeout', EventContent, ...) event after Time
+	%% Generate a ('timeout', EventContent, ...) event
 	%% unless some other event is delivered
-	Time :: timeout().
+	Time :: timeout() | integer().
 -type state_timeout() ::
-	%% Generate a ('state_timeout', EventContent, ...) event after Time
+	%% Generate a ('state_timeout', EventContent, ...) event
 	%% unless the state is changed
-	Time :: timeout().
+	Time :: timeout() | integer().
+-type timeout_option() :: {abs,Abs :: boolean()}.
 
 -type action() ::
 	%% During a state change:
@@ -137,8 +138,16 @@
 	(Timeout :: event_timeout()) | % {timeout,Timeout}
 	{'timeout', % Set the event_timeout option
 	 Time :: event_timeout(), EventContent :: term()} |
+	{'timeout', % Set the event_timeout option
+	 Time :: event_timeout(),
+	 EventContent :: term(),
+	 Options :: (timeout_option() | [timeout_option()])} |
 	{'state_timeout', % Set the state_timeout option
 	 Time :: state_timeout(), EventContent :: term()} |
+	{'state_timeout', % Set the state_timeout option
+	 Time :: state_timeout(),
+	 EventContent :: term(),
+	 Options :: (timeout_option() | [timeout_option()])} |
 	%%
 	reply_action().
 -type reply_action() ::
@@ -1312,7 +1321,7 @@ parse_enter_actions(Debug, S, State, Actions, Hibernate, TimeoutsR) ->
 
 parse_actions(Debug, S, State, Actions) ->
     Hibernate = false,
-    TimeoutsR = [{timeout,infinity,infinity}], %% Will cancel event timer
+    TimeoutsR = [infinity], %% Will cancel event timer
     Postpone = false,
     NextEventsR = [],
     parse_actions(
@@ -1378,11 +1387,15 @@ parse_actions(
 		     ?STACKTRACE()}
 	    end;
 	%%
-	{state_timeout,_,_} = Timeout ->
+	{TimerType,_,_} = Timeout
+	  when TimerType =:= timeout;
+	       TimerType =:= state_timeout ->
 	    parse_actions_timeout(
 	      Debug, S, State, Actions,
 	      Hibernate, TimeoutsR, Postpone, NextEventsR, Timeout);
-	{timeout,_,_} = Timeout ->
+	{TimerType,_,_,_} = Timeout
+	  when TimerType =:= timeout;
+	       TimerType =:= state_timeout ->
 	    parse_actions_timeout(
 	      Debug, S, State, Actions,
 	      Hibernate, TimeoutsR, Postpone, NextEventsR, Timeout);
@@ -1395,26 +1408,64 @@ parse_actions(
 parse_actions_timeout(
   Debug, S, State, Actions,
   Hibernate, TimeoutsR, Postpone, NextEventsR, Timeout) ->
-    Time =
-	case Timeout of
-	    {_,T,_} -> T;
-	    T -> T
-	end,
-    case validate_time(Time) of
-	true ->
-	    parse_actions(
-	      Debug, S, State, Actions,
-	      Hibernate, [Timeout|TimeoutsR],
-	      Postpone, NextEventsR);
-	false ->
-	    {error,
-	     {bad_action_from_state_function,Timeout},
-	     ?STACKTRACE()}
+    case Timeout of
+	{TimerType,Time,TimerMsg,TimerOpts} ->
+	    case validate_timer_args(Time, listify(TimerOpts)) of
+		true ->
+		    parse_actions(
+		      Debug, S, State, Actions,
+		      Hibernate, [Timeout|TimeoutsR],
+		      Postpone, NextEventsR);
+		false ->
+		    NewTimeout = {TimerType,Time,TimerMsg},
+		    parse_actions(
+		      Debug, S, State, Actions,
+		      Hibernate, [NewTimeout|TimeoutsR],
+		      Postpone, NextEventsR);
+		error ->
+		    {error,
+		     {bad_action_from_state_function,Timeout},
+		     ?STACKTRACE()}
+	    end;
+	{_,Time,_} ->
+	    case validate_timer_args(Time, []) of
+		false ->
+		    parse_actions(
+		      Debug, S, State, Actions,
+		      Hibernate, [Timeout|TimeoutsR],
+		      Postpone, NextEventsR);
+		error ->
+		    {error,
+		     {bad_action_from_state_function,Timeout},
+		     ?STACKTRACE()}
+	    end;
+	Time ->
+	    case validate_timer_args(Time, []) of
+		false ->
+		    parse_actions(
+		      Debug, S, State, Actions,
+		      Hibernate, [Timeout|TimeoutsR],
+		      Postpone, NextEventsR);
+		error ->
+		    {error,
+		     {bad_action_from_state_function,Timeout},
+		     ?STACKTRACE()}
+	    end
     end.
 
-validate_time(Time) when is_integer(Time), Time >= 0 -> true;
-validate_time(infinity) -> true;
-validate_time(_) -> false.
+validate_timer_args(Time, Opts) ->
+    validate_timer_args(Time, Opts, false).
+%%
+validate_timer_args(Time, [], true) when is_integer(Time) ->
+    true;
+validate_timer_args(Time, [], false) when is_integer(Time), Time >= 0 ->
+    false;
+validate_timer_args(infinity, [], Abs) ->
+    Abs;
+validate_timer_args(Time, [{abs,Abs}|Opts], _) when is_boolean(Abs) ->
+    validate_timer_args(Time, Opts, Abs);
+validate_timer_args(_, [_|_], _) ->
+    error.
 
 %% Stop and start timers as well as create timeout zero events
 %% and pending event timer
@@ -1430,22 +1481,39 @@ parse_timers(
   TimerRefs, TimerTypes, CancelTimers, [Timeout|TimeoutsR],
   Seen, TimeoutEvents) ->
     case Timeout of
+	{TimerType,Time,TimerMsg,TimerOpts} ->
+	    %% Absolute timer
+	    parse_timers(
+	      TimerRefs, TimerTypes, CancelTimers, TimeoutsR,
+	      Seen, TimeoutEvents,
+	      TimerType, Time, TimerMsg, listify(TimerOpts));
+	%% Relative timers below
+	{TimerType,0,TimerMsg} ->
+	    parse_timers(
+	      TimerRefs, TimerTypes, CancelTimers, TimeoutsR,
+	      Seen, TimeoutEvents,
+	      TimerType, zero, TimerMsg, []);
 	{TimerType,Time,TimerMsg} ->
 	    parse_timers(
-              TimerRefs, TimerTypes, CancelTimers, TimeoutsR,
-              Seen, TimeoutEvents,
-              TimerType, Time, TimerMsg);
+	      TimerRefs, TimerTypes, CancelTimers, TimeoutsR,
+	      Seen, TimeoutEvents,
+	      TimerType, Time, TimerMsg, []);
+	0 ->
+	    parse_timers(
+	      TimerRefs, TimerTypes, CancelTimers, TimeoutsR,
+	      Seen, TimeoutEvents,
+	      timeout, zero, 0, []);
 	Time ->
 	    parse_timers(
-              TimerRefs, TimerTypes, CancelTimers, TimeoutsR,
-              Seen, TimeoutEvents,
-              timeout, Time, Time)
+	      TimerRefs, TimerTypes, CancelTimers, TimeoutsR,
+	      Seen, TimeoutEvents,
+	      timeout, Time, Time, [])
     end.
 
 parse_timers(
   TimerRefs, TimerTypes, CancelTimers, TimeoutsR,
   Seen, TimeoutEvents,
-  TimerType, Time, TimerMsg) ->
+  TimerType, Time, TimerMsg, TimerOpts) ->
     case Seen of
 	#{TimerType := _} ->
 	    %% Type seen before - ignore
@@ -1464,7 +1532,7 @@ parse_timers(
 		    parse_timers(
 		      TimerRefs, NewTimerTypes, NewCancelTimers, TimeoutsR,
 		      NewSeen, TimeoutEvents);
-		0 ->
+		zero ->
 		    %% Cancel any running timer
 		    {NewTimerTypes,NewCancelTimers} =
 			cancel_timer_by_type(
@@ -1477,7 +1545,8 @@ parse_timers(
 		_ ->
 		    %% (Re)start the timer
 		    TimerRef =
-			erlang:start_timer(Time, self(), TimerMsg),
+			erlang:start_timer(
+			  Time, self(), TimerMsg, TimerOpts),
 		    case TimerTypes of
 			#{TimerType := OldTimerRef} ->
 			    %% Cancel the running timer
@@ -1491,6 +1560,8 @@ parse_timers(
 			      NewCancelTimers, TimeoutsR,
 			      NewSeen, TimeoutEvents);
 			#{} ->
+			    %% Insert the new timer into
+			    %% both TimerRefs and TimerTypes
 			    parse_timers(
 			      TimerRefs#{TimerRef => TimerType},
 			      TimerTypes#{TimerType => TimerRef},
diff --git a/lib/stdlib/test/gen_statem_SUITE.erl b/lib/stdlib/test/gen_statem_SUITE.erl
index ac27c9fc7..ee6109915 100644
--- a/lib/stdlib/test/gen_statem_SUITE.erl
+++ b/lib/stdlib/test/gen_statem_SUITE.erl
@@ -1597,8 +1597,9 @@ idle({call,From}, {delayed_answer,T}, Data) ->
 	    throw({keep_state,Data})
     end;
 idle({call,From}, {timeout,Time}, _Data) ->
+    AbsTime = erlang:monotonic_time(millisecond) + Time,
     {next_state,timeout,{From,Time},
-     {timeout,Time,idle}};
+     {timeout,AbsTime,idle,[{abs,true}]}};
 idle(cast, next_event, _Data) ->
     {next_state,next_events,[a,b,c],
      [{next_event,internal,a},
-- 
2.12.2

openSUSE Build Service is sponsored by