File 2463-Implement-timeout-Name-timeouts.patch of Package erlang

From 30cae2492d8d8e927d57c0dc656ee2dfbec0a70c Mon Sep 17 00:00:00 2001
From: Raimo Niskanen <raimo@erlang.org>
Date: Mon, 13 Feb 2017 08:20:16 +0100
Subject: [PATCH 3/4] Implement {timeout,Name} timeouts

---
 lib/stdlib/doc/src/gen_statem.xml       | 100 ++++++++++++++++++++-------
 lib/stdlib/src/gen_statem.erl           |  79 +++++++++++++---------
 lib/stdlib/test/gen_statem_SUITE.erl    |  70 ++++++++++++++++++-
 system/doc/design_principles/statem.xml | 115 ++++++++++++++++++++++++++------
 4 files changed, 285 insertions(+), 79 deletions(-)

diff --git a/lib/stdlib/doc/src/gen_statem.xml b/lib/stdlib/doc/src/gen_statem.xml
index 44ac1ad8a..1b99b65e0 100644
--- a/lib/stdlib/doc/src/gen_statem.xml
+++ b/lib/stdlib/doc/src/gen_statem.xml
@@ -67,13 +67,16 @@
       It has the same features and adds some really useful:
     </p>
     <list type="bulleted">
-      <item>State code is gathered.</item>
-      <item>The state can be any term.</item>
-      <item>Events can be postponed.</item>
-      <item>Events can be self-generated.</item>
-      <item>Automatic state enter code can be called.</item>
-      <item>A reply can be sent from a later state.</item>
-      <item>There can be multiple <c>sys</c> traceable replies.</item>
+      <item>Gathered state code.</item>
+      <item>Arbitrary term state.</item>
+      <item>Event postponing.</item>
+      <item>Self-generated events.</item>
+      <item>State time-out.</item>
+      <item>Multiple generic named time-outs.</item>
+      <item>Absolute time-out time.</item>
+      <item>Automatic state enter calls.</item>
+      <item>Reply from other state than the request.</item>
+      <item>Multiple <c>sys</c> traceable replies.</item>
     </list>
     <p>
       The callback model(s) for <c>gen_statem</c> differs from
@@ -531,10 +534,12 @@ handle_event(_, _, State, Data) ->
 	  originate from the corresponding API functions.
 	  For calls, the event contains whom to reply to.
 	  Type <c>info</c> originates from regular process messages sent
-	  to the <c>gen_statem</c>. Also, the state machine
-	  implementation can generate events of types
-	  <c>timeout</c>, <c>state_timeout</c>,
-	  and <c>internal</c> to itself.
+	  to the <c>gen_statem</c>. The state machine
+	  implementation can, in addition to the above,
+	  generate
+	  <seealso marker="#type-event_type"><c>events of types</c></seealso>
+	  <c>timeout</c>, <c>{timeout,<anno>Name</anno>}</c>,
+	  <c>state_timeout</c>, and <c>internal</c> to itself.
 	</p>
       </desc>
     </datatype>
@@ -701,13 +706,14 @@ handle_event(_, _, State, Data) ->
 	  </item>
 	  <item>
 	    <p>
-	      Timeout timers 
-              <seealso marker="#type-state_timeout"><c>state_timeout()</c></seealso>
+	      Time-out timers 
+              <seealso marker="#type-event_timeout"><c>event_timeout()</c></seealso>,
+              <seealso marker="#type-generic_timeout"><c>generic_timeout()</c></seealso>
 	      and 
-              <seealso marker="#type-event_timeout"><c>event_timeout()</c></seealso>
+              <seealso marker="#type-state_timeout"><c>state_timeout()</c></seealso>
 	      are handled.  Time-outs with zero time are guaranteed to be
 	      delivered to the state machine before any external
-	      not yet received event so if there is such a timeout requested,
+	      not yet received event so if there is such a time-out requested,
 	      the corresponding time-out zero event is enqueued as
 	      the newest event.
 	    </p>
@@ -795,8 +801,8 @@ handle_event(_, _, State, Data) ->
 	  <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.
+	  are interpreted.  Future <c>erlang:start_timer/4</c> <c>Options</c>
+	  will not necessarily be supported.
 	</p>
 	<p>
 	  Any event that arrives cancels this time-out.
@@ -822,6 +828,42 @@ handle_event(_, _, State, Data) ->
       </desc>
     </datatype>
     <datatype>
+      <name name="generic_timeout"/>
+      <desc>
+	<p>
+	  Starts a timer set by
+	  <seealso marker="#type-enter_action"><c>enter_action()</c></seealso>
+	  <c>{timeout,Name}</c>.
+	  When the timer expires an event of
+	  <seealso marker="#type-event_type"><c>event_type()</c></seealso>
+	  <c>{timeout,Name}</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.  Future <c>erlang:start_timer/4</c> <c>Options</c>
+	  will not necessarily be supported.
+	</p>
+	<p>
+	  If <c>Time</c> is <c>infinity</c>,
+	  no timer is started, as it never would expire anyway.
+	</p>
+	<p>
+	  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>
+	  Setting a timer with the same <c>Name</c> while it is running
+	  will restart it with the new time-out value.
+	  Therefore it is possible to cancel
+	  a specific time-out by setting it to <c>infinity</c>.
+	</p>
+      </desc>
+    </datatype>
+    <datatype>
       <name name="state_timeout"/>
       <desc>
 	<p>
@@ -835,8 +877,8 @@ handle_event(_, _, State, Data) ->
 	  <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.
+	  are interpreted.  Future <c>erlang:start_timer/4</c> <c>Options</c>
+	  will not necessarily be supported.
 	</p>
 	<p>
 	  If <c>Time</c> is <c>infinity</c>,
@@ -861,7 +903,7 @@ handle_event(_, _, State, Data) ->
       <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.
+	  and if it is <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.
@@ -986,7 +1028,19 @@ handle_event(_, _, State, Data) ->
 	      <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>
-	      and options
+	      and time-out options
+	      <seealso marker="#type-timeout_option"><c><anno>Options</anno></c></seealso>.
+	    </p>
+	  </item>
+	  <tag><c>{timeout,<anno>Name</anno>}</c></tag>
+	  <item>
+	    <p>
+	      Sets the
+	      <seealso marker="#type-transition_option"><c>transition_option()</c></seealso>
+	      <seealso marker="#type-generic_timeout"><c>generic_timeout()</c></seealso>
+	      to <c><anno>Time</anno></c> for <c><anno>Name</anno></c>
+	      with <c><anno>EventContent</anno></c>
+	      and time-out options
 	      <seealso marker="#type-timeout_option"><c><anno>Options</anno></c></seealso>.
 	    </p>
 	  </item>
@@ -997,7 +1051,7 @@ handle_event(_, _, State, Data) ->
 	      <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>
-	      and options
+	      and time-out options
 	      <seealso marker="#type-timeout_option"><c><anno>Options</anno></c></seealso>.
 	    </p>
 	  </item>
@@ -1270,7 +1324,7 @@ handle_event(_, _, State, Data) ->
 	    to avoid that the calling process dies when the call
 	    times out, you will have to be prepared to handle
 	    a late reply.
-	    So why not just allow the calling process to die?
+	    So why not just let the calling process die?
 	  </p>
 	</note>
 	<p>
diff --git a/lib/stdlib/src/gen_statem.erl b/lib/stdlib/src/gen_statem.erl
index fe80bb5de..6f566b8be 100644
--- a/lib/stdlib/src/gen_statem.erl
+++ b/lib/stdlib/src/gen_statem.erl
@@ -78,8 +78,9 @@
 -type data() :: term().
 
 -type event_type() ::
-	{'call',From :: from()} | 'cast' |
-	'info' | 'timeout' | 'state_timeout' | 'internal'.
+	{'call',From :: from()} | 'cast' | 'info' |
+	'timeout' | {'timeout', Name :: term()} | 'state_timeout' |
+	'internal'.
 
 -type callback_mode_result() ::
 	callback_mode() | [callback_mode() | state_enter()].
@@ -88,7 +89,7 @@
 
 -type transition_option() ::
 	postpone() | hibernate() |
-	event_timeout() | state_timeout().
+	event_timeout() | generic_timeout() | state_timeout().
 -type postpone() ::
 	%% If 'true' postpone the current event
 	%% and retry it when the state changes (=/=)
@@ -100,6 +101,9 @@
 	%% Generate a ('timeout', EventContent, ...) event
 	%% unless some other event is delivered
 	Time :: timeout() | integer().
+-type generic_timeout() ::
+	%% Generate a ({'timeout',Name}, EventContent, ...) event
+	Time :: timeout() | integer().
 -type state_timeout() ::
 	%% Generate a ('state_timeout', EventContent, ...) event
 	%% unless the state is changed
@@ -142,6 +146,14 @@
 	 Time :: event_timeout(),
 	 EventContent :: term(),
 	 Options :: (timeout_option() | [timeout_option()])} |
+	%%
+	{{'timeout', Name :: term()}, % Set the generic_timeout option
+	 Time :: generic_timeout(), EventContent :: term()} |
+	{{'timeout', Name :: term()}, % Set the generic_timeout option
+	 Time :: generic_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
@@ -311,37 +323,26 @@
 %% Type validation functions
 callback_mode(CallbackMode) ->
     case CallbackMode of
-	state_functions ->
-	    true;
-	handle_event_function ->
-	    true;
-	_ ->
-	    false
+	state_functions -> true;
+	handle_event_function -> true;
+	_ -> false
     end.
 %%
-from({Pid,_}) when is_pid(Pid) ->
-    true;
-from(_) ->
-    false.
+from({Pid,_}) when is_pid(Pid) -> true;
+from(_) -> false.
 %%
 event_type({call,From}) ->
     from(From);
 event_type(Type) ->
     case Type of
-	{call,From} ->
-	    from(From);
-	cast ->
-	    true;
-	info ->
-	    true;
-	timeout ->
-	    true;
-	state_timeout ->
-	    true;
-	internal ->
-	    true;
-	_ ->
-	    false
+	{call,From} -> from(From);
+	cast -> true;
+	info -> true;
+	timeout -> true;
+	state_timeout -> true;
+	internal -> true;
+	{timeout,_} -> true;
+	_ -> false
     end.
 
 
@@ -1387,15 +1388,27 @@ parse_actions(
 		     ?STACKTRACE()}
 	    end;
 	%%
-	{TimerType,_,_} = Timeout
-	  when TimerType =:= timeout;
-	       TimerType =:= state_timeout ->
+	{{timeout,_},_,_} = Timeout ->
+	    parse_actions_timeout(
+	      Debug, S, State, Actions,
+	      Hibernate, TimeoutsR, Postpone, NextEventsR, Timeout);
+	{{timeout,_},_,_,_} = Timeout ->
+	    parse_actions_timeout(
+	      Debug, S, State, Actions,
+	      Hibernate, TimeoutsR, Postpone, NextEventsR, Timeout);
+	{timeout,_,_} = Timeout ->
+	    parse_actions_timeout(
+	      Debug, S, State, Actions,
+	      Hibernate, TimeoutsR, Postpone, NextEventsR, Timeout);
+	{timeout,_,_,_} = Timeout ->
+	    parse_actions_timeout(
+	      Debug, S, State, Actions,
+	      Hibernate, TimeoutsR, Postpone, NextEventsR, Timeout);
+	{state_timeout,_,_} = Timeout ->
 	    parse_actions_timeout(
 	      Debug, S, State, Actions,
 	      Hibernate, TimeoutsR, Postpone, NextEventsR, Timeout);
-	{TimerType,_,_,_} = Timeout
-	  when TimerType =:= timeout;
-	       TimerType =:= state_timeout ->
+	{state_timeout,_,_,_} = Timeout ->
 	    parse_actions_timeout(
 	      Debug, S, State, Actions,
 	      Hibernate, TimeoutsR, Postpone, NextEventsR, Timeout);
diff --git a/lib/stdlib/test/gen_statem_SUITE.erl b/lib/stdlib/test/gen_statem_SUITE.erl
index ee6109915..36b1f761a 100644
--- a/lib/stdlib/test/gen_statem_SUITE.erl
+++ b/lib/stdlib/test/gen_statem_SUITE.erl
@@ -38,7 +38,7 @@ all() ->
      {group, abnormal},
      {group, abnormal_handle_event},
      shutdown, stop_and_reply, state_enter, event_order,
-     state_timeout, event_types, code_change,
+     state_timeout, event_types, generic_timers, code_change,
      {group, sys},
      hibernate, enter_loop].
 
@@ -834,6 +834,7 @@ event_types(_Config) ->
 			{next_event,timeout,3},
 			{next_event,info,4},
 			{next_event,cast,5},
+			{next_event,{timeout,6}, 6},
 			{next_event,Call,Req}]}
 	      end,
 	  state1 =>
@@ -857,6 +858,10 @@ event_types(_Config) ->
 		      {next_state, state6, undefined}
 	      end,
 	  state6 =>
+	      fun ({timeout,6}, 6, undefined) ->
+		      {next_state, state7, undefined}
+	      end,
+	  state7 =>
 	      fun ({call,From}, stop, undefined) ->
 		      {stop_and_reply, shutdown,
 		       [{reply,From,stopped}]}
@@ -884,6 +889,69 @@ event_types(_Config) ->
 
 
 
+generic_timers(_Config) ->
+    process_flag(trap_exit, true),
+
+    Machine =
+	%% Abusing the internal format of From...
+	#{init =>
+	      fun () ->
+		      {ok, start, undefined}
+	      end,
+	  start =>
+	      fun ({call,_} = Call, Req, undefined) ->
+		      {next_state, state1, undefined,
+		       [{{timeout,a},1500,1},
+			{state_timeout,1500,1},
+			{{timeout,b},1000,1},
+			{next_event,Call,Req}]}
+	      end,
+	  state1 =>
+	      fun ({call,_} = Call, Req, undefined) ->
+		      T = erlang:monotonic_time(millisecond) + 500,
+		      {next_state, state2, undefined,
+		       [{{timeout,c},T,2,{abs,true}},
+			{{timeout,d},0,2,[{abs,false}]},
+			{timeout,0,2},
+			{{timeout,b},infinity,2},
+			{{timeout,a},1000,{Call,Req}}]}
+	      end,
+	  state2 =>
+	      fun ({timeout,d}, 2, undefined) ->
+		      {next_state, state3, undefined}
+	      end,
+	  state3 =>
+	      fun ({timeout,c}, 2, undefined) ->
+		      {next_state, state4, undefined}
+	      end,
+	  state4 =>
+	      fun ({timeout,a}, {{call,From},stop}, undefined) ->
+		      {stop_and_reply, shutdown,
+		       [{reply,From,stopped}]}
+	      end},
+    {ok,STM} =
+	gen_statem:start_link(
+	  ?MODULE, {map_statem,Machine,[]}, [{debug,[trace]}]),
+
+    stopped = gen_statem:call(STM, stop),
+    receive
+	{'EXIT',STM,shutdown} ->
+	    ok
+    after 500 ->
+	    ct:fail(did_not_stop)
+    end,
+
+    {noproc,_} =
+	?EXPECT_FAILURE(gen_statem:call(STM, hej), Reason),
+    case flush() of
+	[] ->
+	    ok;
+	Other2 ->
+	    ct:fail({unexpected,Other2})
+    end.
+
+
+
 sys1(Config) ->
     {ok,Pid} = gen_statem:start(?MODULE, start_arg(Config, []), []),
     {status, Pid, {module,gen_statem}, _} = sys:get_status(Pid),
diff --git a/system/doc/design_principles/statem.xml b/system/doc/design_principles/statem.xml
index f4d84ab16..f01615fdc 100644
--- a/system/doc/design_principles/statem.xml
+++ b/system/doc/design_principles/statem.xml
@@ -4,7 +4,7 @@
 <chapter>
   <header>
     <copyright>
-      <year>2016</year><year>2017</year>
+      <year>2016-2017</year>
       <holder>Ericsson AB. All Rights Reserved.</holder>
     </copyright>
     <legalnotice>
@@ -293,6 +293,13 @@ StateName(EventType, EventContent, Data) ->
 	<seealso marker="#State Time-Outs">State Time-Outs</seealso>
       </item>
       <item>
+	Start a
+	<seealso marker="stdlib:gen_statem#type-generic_timeout">
+	  generic time-out</seealso>,
+	  read more in section
+	<seealso marker="#Generic Time-Outs">Generic Time-Outs</seealso>
+      </item>
+      <item>
 	Start an
 	<seealso marker="stdlib:gen_statem#type-event_timeout">event time-out</seealso>,
 	see more in section
@@ -320,8 +327,9 @@ StateName(EventType, EventContent, Data) ->
 	<c>gen_statem(3)</c>
       </seealso>
       manual page.
-      You can, for example, reply to many callers
-      and generate multiple next events to handle.
+      You can, for example, reply to many callers,
+      generate multiple next events,
+      and set time-outs to relative or absolute times.
     </p>
   </section>
 
@@ -369,6 +377,14 @@ StateName(EventType, EventContent, Data) ->
 	</seealso>
 	state timer timing out.
       </item>
+      <tag><c>{timeout,Name}</c></tag>
+      <item>
+	Generated by state transition action
+	<seealso marker="stdlib:gen_statem#type-generic_timeout">
+	  <c>{{timeout,Name},Time,EventContent}</c>
+	</seealso>
+	generic timer timing out.
+      </item>
       <tag><c>timeout</c></tag>
       <item>
 	Generated by state transition action
@@ -450,7 +466,7 @@ locked(
         [Digit] ->
 	    do_unlock(),
             {next_state, open, Data#{remaining := Code},
-             [{state_timeout,10000,lock}];
+             [{state_timeout,10000,lock}]};
         [Digit|Rest] -> % Incomplete
             {next_state, locked, Data#{remaining := Rest}};
         _Wrong ->
@@ -779,7 +795,7 @@ handle_event(cast, {button,Digit}, State, #{code := Code} = Data) ->
 		[Digit] -> % Complete
 		    do_unlock(),
 		    {next_state, open, Data#{remaining := Code},
-                     [{state_timeout,10000,lock}};
+                     [{state_timeout,10000,lock}]};
 		[Digit|Rest] -> % Incomplete
 		    {keep_state, Data#{remaining := Rest}};
 		[_|_] -> % Wrong
@@ -873,7 +889,7 @@ stop() ->
     <marker id="Event Time-Outs" />
     <title>Event Time-Outs</title>
     <p>
-      A timeout feature inherited from <c>gen_statem</c>'s predecessor
+      A time-out feature inherited from <c>gen_statem</c>'s predecessor
       <seealso marker="stdlib:gen_fsm"><c>gen_fsm</c></seealso>,
       is an event time-out, that is,
       if an event arrives the timer is cancelled.
@@ -906,24 +922,24 @@ locked(
 ...
      ]]></code>
     <p>
-      Whenever we receive a button event we start an event timeout
+      Whenever we receive a button event we start an event time-out
       of 30 seconds, and if we get an event type <c>timeout</c>
       we reset the remaining code sequence.
     </p>
     <p>
-      An event timeout is cancelled by any other event so you either
-      get some other event or the timeout event.  It is therefore
-      not possible nor needed to cancel or restart an event timeout.
+      An event time-out is cancelled by any other event so you either
+      get some other event or the time-out event.  It is therefore
+      not possible nor needed to cancel or restart an event time-out.
       Whatever event you act on has already cancelled
-      the event timeout...
+      the event time-out...
     </p>
   </section>
 
 <!-- =================================================================== -->
 
   <section>
-    <marker id="Erlang Timers" />
-    <title>Erlang Timers</title>
+    <marker id="Generic Time-Outs" />
+    <title>Generic Time-Outs</title>
     <p>
       The previous example of state time-outs only work if
       the state machine stays in the same state during the
@@ -934,13 +950,68 @@ locked(
       You may want to start a timer in one state and respond
       to the time-out in another, maybe cancel the time-out
       without changing states, or perhaps run multiple
-      time-outs in parallel. All this can be accomplished
-      with Erlang Timers:
+      time-outs in parallel. All this can be accomplished with
+      <seealso marker="stdlib:gen_statem#type-generic_timeout">generic time-outs</seealso>.
+      They may look a little bit like
+      <seealso marker="stdlib:gen_statem#type-event_timeout">event time-outs</seealso>
+      but contain a name to allow for any number of them simultaneously
+      and they are not automatically cancelled.
+    </p>
+    <p>
+      Here is how to accomplish the state time-out
+      in the previous example by instead using a generic time-out
+      named <c>open_tm</c>:
+    </p>
+    <code type="erl"><![CDATA[
+...
+locked(
+  cast, {button,Digit},
+  #{code := Code, remaining := Remaining} = Data) ->
+    case Remaining of
+        [Digit] ->
+	    do_unlock(),
+            {next_state, open, Data#{remaining := Code},
+	     [{{timeout,open_tm},10000,lock}]};
+...
+
+open({timeout,open_tm}, lock, Data) ->
+    do_lock(),
+    {next_state,locked,Data};
+open(cast, {button,_}, Data) ->
+    {keep_state,Data};
+...
+    ]]></code>
+    <p>
+      Just as
+      <seealso marker="#State Time-Outs">state time-outs</seealso>
+      you can restart or cancel a specific generic time-out
+      by setting it to a new time or <c>infinity</c>.
+    </p>
+    <p>
+      Another way to handle a late time-out can be to not cancel it,
+      but to ignore it if it arrives in a state
+      where it is known to be late.
+    </p>
+  </section>
+
+<!-- =================================================================== -->
+
+  <section>
+    <marker id="Erlang Timers" />
+    <title>Erlang Timers</title>
+    <p>
+      The most versatile way to handle time-outs is to use
+      Erlang Timers; see
       <seealso marker="erts:erlang#start_timer/4"><c>erlang:start_timer3,4</c></seealso>.
+      Most time-out tasks can be performed with the
+      time-out features in <c>gen_statem</c>,
+      but an example of one that can not is if you should need
+      the return value from
+      <seealso marker="erts:erlang#cancel_timer/2"><c>erlang:cancel_timer(Tref)</c></seealso>, that is; the remaining time of the timer.
     </p>
     <p>
       Here is how to accomplish the state time-out
-      in the previous example by insted using an Erlang Timer:
+      in the previous example by instead using an Erlang Timer:
     </p>
     <code type="erl"><![CDATA[
 ...
@@ -1596,7 +1667,7 @@ handle_event(
   {call,From}, code_length,
   {_StateName,_LockButton}, #{code := Code}) ->
     {keep_state_and_data,
-    [{reply,From,length(Code)}]};
+     [{reply,From,length(Code)}]};
 %%
 %% State: locked
 handle_event(
@@ -1636,7 +1707,7 @@ handle_event(
 	    if
 		Digit =:= LockButton ->
 		    {next_state, {locked,LockButton}, Data,
-		     [{reply,From,locked}]);
+		     [{reply,From,locked}]};
 		true ->
 		    {keep_state_and_data,
 		     [postpone]}
@@ -1710,10 +1781,10 @@ handle_event(
   EventType, EventContent,
   {open,LockButton}, Data) ->
     case {EventType, EventContent} of
-	{enter, _OldState} ->
-	    do_unlock(),
-	    {keep_state_and_data,
-	    [{state_timeout,10000,lock},hibernate]};
+        {enter, _OldState} ->
+            do_unlock(),
+            {keep_state_and_data,
+             [{state_timeout,10000,lock},hibernate]};
 ...
     ]]></code>
     <p>
-- 
2.12.2

openSUSE Build Service is sponsored by