File 2185-Fix-timeout-parsing-and-doc-feedback.patch of Package erlang

From 3ed7d729cab697b9f668dadb563d629de10f593d Mon Sep 17 00:00:00 2001
From: Raimo Niskanen <raimo@erlang.org>
Date: Tue, 10 Apr 2018 10:50:41 +0200
Subject: [PATCH 5/9] Fix timeout parsing and doc feedback

---
 lib/stdlib/doc/src/gen_statem.xml       | 134 ++++++++----
 lib/stdlib/src/gen_statem.erl           |  91 ++++----
 lib/stdlib/test/gen_statem_SUITE.erl    |  46 +++-
 system/doc/design_principles/statem.xml | 372 +++++++++++++++-----------------
 4 files changed, 354 insertions(+), 289 deletions(-)

diff --git a/lib/stdlib/doc/src/gen_statem.xml b/lib/stdlib/doc/src/gen_statem.xml
index 252a8370ad..fe391b329a 100644
--- a/lib/stdlib/doc/src/gen_statem.xml
+++ b/lib/stdlib/doc/src/gen_statem.xml
@@ -71,16 +71,18 @@
       had and adds some really useful:
     </p>
     <list type="bulleted">
-      <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>
+      <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, <c>sys</c> traceable
+      </item>
+      <item>Multiple <c>sys</c> traceable replies</item>
     </list>
 
 
@@ -232,8 +234,10 @@ erlang:'!'            -----> Module:StateName/3
       whenever a new state is entered; see 
       <seealso marker="#type-state_enter"><c>state_enter()</c></seealso>.
       This is for writing code common to all state entries.
-      Another way to do it is to insert events at state transitions,
-      but you have to do so everywhere it is needed.
+      Another way to do it is to insert an event at the state transition,
+      and/or to use a dedicated state transition function,
+      but that is something you will have to remember
+      at every state transition to the state(s) that need it.
     </p>
     <note>
       <p>If you in <c>gen_statem</c>, for example, postpone
@@ -703,9 +707,9 @@ handle_event(_, _, State, Data) ->
 	<p>
 	  If 
 	  <seealso marker="#Module:code_change/4"><c>Module:code_change/4</c></seealso>
-	  should transform the state to a state with a different
-	  name it is still regarded as the same state so this
-	  does not cause a state enter call.
+	  should transform the state,
+	  it is regarded as a state rename and not a state change,
+	  which will not cause a state enter call.
 	</p>
 	<p>
 	  Note that a state enter call <em>will</em> be done
@@ -723,12 +727,19 @@ handle_event(_, _, State, Data) ->
 	<p>
 	  Transition options can be set by
 	  <seealso marker="#type-action">actions</seealso>
-	  and they modify how the state transition is done:
+	  and modify the state transition.
+	  Here are the sequence of steps for a state transition:
 	</p>
 	<list type="ordered">
 	  <item>
             <p>
-	      If the state changes, is the initial state,
+	      If
+	      <seealso marker="#type-state_enter">
+		<em>state enter calls</em>
+	      </seealso>
+	      are used, and either:
+	      the state changes, it is the initial state,
+	      or one of the callback results
 	      <seealso marker="#type-state_callback_result">
 		<c>repeat_state</c>
 	      </seealso>
@@ -736,16 +747,21 @@ handle_event(_, _, State, Data) ->
 	      <seealso marker="#type-state_callback_result">
 		<c>repeat_state_and_data</c>
 	      </seealso>
-	      is used, and also
-	      <seealso marker="#type-state_enter"><em>state enter calls</em></seealso>
-	      are used, the <c>gen_statem</c> calls
+	      is used; the <c>gen_statem</c> calls
 	      the new state callback with arguments
 	      <seealso marker="#type-state_enter">(enter, OldState, Data)</seealso>.
+	    </p>
+	    <p>
 	      Any 
 	      <seealso marker="#type-enter_action"><c>actions</c></seealso>
 	      returned from this call are handled as if they were
-	      appended to the actions 
-	      returned by the state callback that changed states.
+	      appended to the actions
+	      returned by the state callback that caused the state entry.
+	    </p>
+	    <p>
+	      Should this state enter call return any of
+	      the mentioned <c>repeat_*</c> callback results
+	      it is repeated again, with the updated <c>Data</c>.
             </p>
 	  </item>
 	  <item>
@@ -774,7 +790,7 @@ handle_event(_, _, State, Data) ->
 	      All events stored with
 	      <seealso marker="#type-action"><c>action()</c></seealso>
 	      <c>next_event</c>
-	      are inserted to be processed before the other queued events.
+	      are inserted to be processed before previously queued events.
             </p>
 	  </item>
 	  <item>
@@ -788,7 +804,9 @@ handle_event(_, _, State, Data) ->
 	      delivered to the state machine before any external
 	      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.
+	      the newest received event;
+	      that is after already queued events
+	      such as inserted and postponed events.
 	    </p>
 	    <p>
 	      Any event cancels an
@@ -826,7 +844,7 @@ handle_event(_, _, State, Data) ->
 	      When a new message arrives the 
 	      <seealso marker="#state callback">state callback</seealso>
 	      is called with the corresponding event,
-	      and we start again from the top of this list.
+	      and we start again from the top of this sequence.
 	    </p>
 	  </item>
 	</list>
@@ -851,13 +869,19 @@ handle_event(_, _, State, Data) ->
 	  <seealso marker="proc_lib#hibernate/3"><c>proc_lib:hibernate/3</c></seealso>
 	  before going into <c>receive</c>
 	  to wait for a new external event.
-	  If there are enqueued events,
-	  to prevent receiving any new event, an
-	  <seealso marker="erts:erlang#garbage_collect/0"><c>erlang:garbage_collect/0</c></seealso>
-	  is done instead to simulate
-	  that the <c>gen_statem</c> entered hibernation
-	  and immediately got awakened by the oldest enqueued event.
 	</p>
+	<note>
+	  <p>
+	    If there are enqueued events to process
+	    when hibrnation is requested,
+	    this is optimized by not hibernating but instead calling
+	    <seealso marker="erts:erlang#garbage_collect/0">
+	      <c>erlang:garbage_collect/0</c>
+	    </seealso>
+	    to simulate that the <c>gen_statem</c> entered hibernation
+	    and immediately got awakened by an enqueued event.
+	  </p>
+	</note>
       </desc>
     </datatype>
     <datatype>
@@ -892,7 +916,7 @@ handle_event(_, _, State, Data) ->
 	  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.
+	  received external event, but after already queued events.
 	</p>
 	<p>
 	  Note that it is not possible nor needed to cancel this time-out,
@@ -978,7 +1002,9 @@ handle_event(_, _, State, Data) ->
 	  If <c>Abs</c> is <c>true</c> an absolute timer is started,
 	  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>
+	  <seealso marker="erts:erlang#start_timer/4">
+	    <c>erlang:start_timer/4</c>
+	  </seealso>
 	  for details.
 	</p>
 	<p>
@@ -1004,7 +1030,9 @@ handle_event(_, _, State, Data) ->
 	</p>
 	<p>
 	  Actions that set
-	  <seealso marker="#type-transition_option">transition options</seealso>
+	  <seealso marker="#type-transition_option">
+	    transition options
+	  </seealso>
 	  override any previous of the same type,
 	  so the last in the containing list wins.
 	  For example, the last
@@ -1016,7 +1044,9 @@ handle_event(_, _, State, Data) ->
 	  <item>
 	    <p>
 	      Sets the
-	      <seealso marker="#type-transition_option"><c>transition_option()</c></seealso>
+	      <seealso marker="#type-transition_option">
+		<c>transition_option()</c>
+	      </seealso>
 	      <seealso marker="#type-postpone"><c>postpone()</c></seealso>
 	      for this state transition.
 	      This action is ignored when returned from
@@ -1029,7 +1059,11 @@ handle_event(_, _, State, Data) ->
 	  <tag><c>next_event</c></tag>
 	  <item>
 	    <p>
-	      Stores the specified <c><anno>EventType</anno></c>
+	      This action does not set any
+	      <seealso marker="#type-transition_option">
+		<c>transition_option()</c>
+	      </seealso>
+	      but instead stores the specified <c><anno>EventType</anno></c>
 	      and <c><anno>EventContent</anno></c> for insertion after all
 	      actions have been executed.
 	    </p>
@@ -1101,15 +1135,15 @@ handle_event(_, _, State, Data) ->
 	  <seealso marker="#type-transition_option">transition options</seealso>.
 	</p>
 	<taglist>
-	  <tag><c>Timeout</c></tag>
+	  <tag><c>Time</c></tag>
 	  <item>
 	    <p>
-	      Short for <c>{timeout,Timeout,Timeout}</c>, that is,
+	      Short for <c>{timeout,Time,Time}</c>, that is,
 	      the time-out message is the time-out time.
 	      This form exists to make the
 	      <seealso marker="#state callback">state callback</seealso>
-	      return value <c>{next_state,NextState,NewData,Timeout}</c>
-	      allowed like for <c>gen_fsm</c>'s
+	      return value <c>{next_state,NextState,NewData,Time}</c>
+	      allowed like for <c>gen_fsm</c>.
 	    </p>
 	  </item>
 	  <tag><c>timeout</c></tag>
@@ -1161,7 +1195,11 @@ handle_event(_, _, State, Data) ->
 	  <seealso marker="#enter_loop/5"><c>enter_loop/5,6</c></seealso>.
 	</p>
 	<p>
-	  It replies to a caller waiting for a reply in
+	  It does not set any
+	  <seealso marker="#type-transition_option">
+	    <c>transition_option()</c>
+	  </seealso>
+	  but instead replies to a caller waiting for a reply in
 	  <seealso marker="#call/2"><c>call/2</c></seealso>.
 	  <c><anno>From</anno></c> must be the term from argument
 	  <seealso marker="#type-event_type"><c>{call,<anno>From</anno>}</c></seealso>
@@ -2144,16 +2182,20 @@ init(Args) -> erlang:error(not_implemented, [Args]).</pre>
 	  You may also not change states from this call.
 	  Should you return <c>{next_state,NextState, ...}</c>
 	  with <c>NextState =/= State</c> the <c>gen_statem</c> crashes.
-	  It is possible to use <c>{repeat_state, ...}</c>,
-	  <c>{repeat_state_and_data,_}</c> or
-	  <c>repeat_state_and_data</c> but all of them makes little
+	  Note that it is actually allowed to use
+	  <c>{repeat_state, NewData, ...}</c> although it makes little
 	  sense since you immediately will be called again with a new
 	  <em>state enter call</em> making this just a weird way
 	  of looping, and there are better ways to loop in Erlang.
+	  If you do not update <c>NewData</c> and have some
+	  loop termination condition, or if you use
+	  <c>{repeat_state_and_data, _}</c> or
+	  <c>repeat_state_and_data</c> you have an infinite loop!
 	  You are advised to use <c>{keep_state,...}</c>,
 	  <c>{keep_state_and_data,_}</c> or
-	  <c>keep_state_and_data</c> since you can not change states
-	  from a <em>state enter call</em> anyway.
+	  <c>keep_state_and_data</c>
+	  since changing states from a <em>state enter call</em>
+	  is not possible anyway.
 	</p>
 	<p>
 	  Note the fact that you can use
diff --git a/lib/stdlib/src/gen_statem.erl b/lib/stdlib/src/gen_statem.erl
index 34507bfd1c..f7dc0050b3 100644
--- a/lib/stdlib/src/gen_statem.erl
+++ b/lib/stdlib/src/gen_statem.erl
@@ -143,7 +143,7 @@
         timeout_action() |
 	reply_action().
 -type timeout_action() ::
-	(Timeout :: event_timeout()) | % {timeout,Timeout}
+	(Time :: event_timeout()) | % {timeout,Time,Time}
 	{'timeout', % Set the event_timeout option
 	 Time :: event_timeout(), EventContent :: term()} |
 	{'timeout', % Set the event_timeout option
@@ -327,7 +327,8 @@
 %% Type validation functions
 -compile(
    {inline,
-    [callback_mode/1, state_enter/1, from/1, event_type/1]}).
+    [callback_mode/1, state_enter/1,
+     event_type/1, from/1, timeout_event_type/1]}).
 %%
 callback_mode(CallbackMode) ->
     case CallbackMode of
@@ -344,23 +345,26 @@ state_enter(StateEnter) ->
             false
     end.
 %%
-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;
-	{timeout,_} -> true;
-	_ -> false
+        _ -> timeout_event_type(Type)
+    end.
+%%
+from({Pid,_}) when is_pid(Pid) -> true;
+from(_) -> false.
+%%
+timeout_event_type(Type) ->
+    case Type of
+        timeout -> true;
+        state_timeout -> true;
+        {timeout,_Name} -> true;
+        _ -> false
     end.
-
 
 
 -define(
@@ -1178,12 +1182,6 @@ loop_event_result(
               [Event|Events])
     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.
-
 %% Ensure that Actions are a list
 loop_event_actions(
   Parent, Debug, S,
@@ -1216,10 +1214,16 @@ loop_event_actions_list(
               S#state{
                 state = NextState,
                 data = NewerData,
-                hibernate = TransOpts#trans_opts.hibernate},
+                hibernate = hibernate_in_trans_opts(TransOpts)},
               [Event|Events])
     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) ->
@@ -1335,15 +1339,15 @@ parse_actions_next_event(
 
 parse_actions_timeout(
   StateCall, Debug, S, Actions, TransOpts,
-  {TimerType,Time,TimerMsg,TimerOpts} = AbsoluteTimeout) ->
+  {TimeoutType,Time,TimerMsg,TimerOpts} = AbsoluteTimeout) ->
     %%
-    case classify_timer(Time, listify(TimerOpts)) of
+    case classify_timeout(TimeoutType, Time, listify(TimerOpts)) of
         absolute ->
             parse_actions_timeout_add(
               StateCall, Debug, S, Actions,
               TransOpts, AbsoluteTimeout);
         relative ->
-            RelativeTimeout = {TimerType,Time,TimerMsg},
+            RelativeTimeout = {TimeoutType,Time,TimerMsg},
             parse_actions_timeout_add(
               StateCall, Debug, S, Actions,
               TransOpts, RelativeTimeout);
@@ -1355,8 +1359,8 @@ parse_actions_timeout(
     end;
 parse_actions_timeout(
   StateCall, Debug, S, Actions, TransOpts,
-  {_,Time,_} = RelativeTimeout) ->
-    case classify_timer(Time, []) of
+  {TimeoutType,Time,_} = RelativeTimeout) ->
+    case classify_timeout(TimeoutType, Time, []) of
         relative ->
             parse_actions_timeout_add(
               StateCall, Debug, S, Actions,
@@ -1369,14 +1373,16 @@ parse_actions_timeout(
     end;
 parse_actions_timeout(
   StateCall, Debug, S, Actions, TransOpts,
-  Timeout) ->
-    case classify_timer(Timeout, []) of
+  Time) ->
+    case classify_timeout(timeout, Time, []) of
         relative ->
+            RelativeTimeout = {timeout,Time,Time},
             parse_actions_timeout_add(
-              StateCall, Debug, S, Actions, TransOpts, Timeout);
+              StateCall, Debug, S, Actions,
+              TransOpts, RelativeTimeout);
         badarg ->
             [error,
-             {bad_action_from_state_function,Timeout},
+             {bad_action_from_state_function,Time},
              ?STACKTRACE(),
              Debug]
     end.
@@ -1662,10 +1668,15 @@ call_state_function(
 
 
 %% -> absolute | relative | badarg
-classify_timer(Time, Opts) ->
-    classify_timer(Time, Opts, false).
-%%
-classify_timer(Time, [], Abs) ->
+classify_timeout(TimeoutType, Time, Opts) ->
+    case timeout_event_type(TimeoutType) of
+        true ->
+            classify_time(false, Time, Opts);
+        false ->
+            badarg
+    end.
+
+classify_time(Abs, Time, []) ->
     case Abs of
         true when
               is_integer(Time);
@@ -1678,9 +1689,9 @@ classify_timer(Time, [], Abs) ->
         _ ->
             badarg
     end;
-classify_timer(Time, [{abs,Abs}|Opts], _) when is_boolean(Abs) ->
-    classify_timer(Time, Opts, Abs);
-classify_timer(_, Opts, _) when is_list(Opts) ->
+classify_time(_, Time, [{abs,Abs}|Opts]) when is_boolean(Abs) ->
+    classify_time(Abs, Time, Opts);
+classify_time(_, _, Opts) when is_list(Opts) ->
     badarg.
 
 %% Stop and start timers as well as create timeout zero events
@@ -1711,15 +1722,7 @@ parse_timers(
 	{TimerType,Time,TimerMsg} ->
 	    parse_timers(
 	      TimerRefs, Timers, TimeoutsR, Seen, TimeoutEvents,
-	      TimerType, Time, TimerMsg, []);
-	0 ->
-	    parse_timers(
-	      TimerRefs, Timers, TimeoutsR, Seen, TimeoutEvents,
-	      timeout, zero, 0, []);
-	Time ->
-	    parse_timers(
-	      TimerRefs, Timers, TimeoutsR, Seen, TimeoutEvents,
-	      timeout, Time, Time, [])
+	      TimerType, Time, TimerMsg, [])
     end.
 
 parse_timers(
diff --git a/lib/stdlib/test/gen_statem_SUITE.erl b/lib/stdlib/test/gen_statem_SUITE.erl
index 3f48fe1590..053233df9b 100644
--- a/lib/stdlib/test/gen_statem_SUITE.erl
+++ b/lib/stdlib/test/gen_statem_SUITE.erl
@@ -60,7 +60,8 @@ tcs(start) ->
 tcs(stop) ->
     [stop1, stop2, stop3, stop4, stop5, stop6, stop7, stop8, stop9, stop10];
 tcs(abnormal) ->
-    [abnormal1, abnormal1clean, abnormal1dirty, abnormal2];
+    [abnormal1, abnormal1clean, abnormal1dirty,
+     abnormal2, abnormal3, abnormal4];
 tcs(sys) ->
     [sys1, call_format_status,
      error_format_status, terminate_crash_format,
@@ -524,6 +525,43 @@ abnormal2(Config) ->
     process_flag(trap_exit, OldFl),
     ok = verify_empty_msgq().
 
+%% Check that bad return actions makes the stm crash. Note that we must
+%% trap exit since we must link to get the real bad_return_ error
+abnormal3(Config) ->
+    OldFl = process_flag(trap_exit, true),
+    {ok,Pid} = gen_statem:start_link(?MODULE, start_arg(Config, []), []),
+
+    %% bad return value in the gen_statem loop
+    {{{bad_action_from_state_function,badaction},_},_} =
+	?EXPECT_FAILURE(gen_statem:call(Pid, badaction), Reason),
+    receive
+	{'EXIT',Pid,{{bad_action_from_state_function,badaction},_}} -> ok
+    after 5000 ->
+	    ct:fail(gen_statem_did_not_die)
+    end,
+
+    process_flag(trap_exit, OldFl),
+    ok = verify_empty_msgq().
+
+%% Check that bad timeout actions makes the stm crash. Note that we must
+%% trap exit since we must link to get the real bad_return_ error
+abnormal4(Config) ->
+    OldFl = process_flag(trap_exit, true),
+    {ok,Pid} = gen_statem:start_link(?MODULE, start_arg(Config, []), []),
+
+    %% bad return value in the gen_statem loop
+    BadTimeout = {badtimeout,4711,ouch},
+    {{{bad_action_from_state_function,BadTimeout},_},_} =
+	?EXPECT_FAILURE(gen_statem:call(Pid, BadTimeout), Reason),
+    receive
+	{'EXIT',Pid,{{bad_action_from_state_function,BadTimeout},_}} -> ok
+    after 5000 ->
+	    ct:fail(gen_statem_did_not_die)
+    end,
+
+    process_flag(trap_exit, OldFl),
+    ok = verify_empty_msgq().
+
 shutdown(Config) ->
     process_flag(trap_exit, true),
 
@@ -1806,10 +1844,12 @@ idle(cast, {connect,Pid}, Data) ->
 idle({call,From}, connect, Data) ->
     gen_statem:reply(From, accept),
     {next_state,wfor_conf,Data,infinity}; % NoOp timeout just to test API
-idle(cast, badreturn, _Data) ->
-    badreturn;
 idle({call,_From}, badreturn, _Data) ->
     badreturn;
+idle({call,_From}, badaction, Data) ->
+    {keep_state, Data, [badaction]};
+idle({call,_From}, {badtimeout,_,_} = BadTimeout, Data) ->
+    {keep_state, Data, BadTimeout};
 idle({call,From}, {delayed_answer,T}, Data) ->
     receive
     after T ->
diff --git a/system/doc/design_principles/statem.xml b/system/doc/design_principles/statem.xml
index 5269d23487..b44e169a9a 100644
--- a/system/doc/design_principles/statem.xml
+++ b/system/doc/design_principles/statem.xml
@@ -67,8 +67,8 @@ State(S) x Event(E) -> Actions(A), State(S')</pre>
     <p>
       As <c>A</c> and <c>S'</c> depend only on
       <c>S</c> and <c>E</c>, the kind of state machine described
-      here is a Mealy Machine
-      (see, for example, the corresponding Wikipedia article).
+      here is a Mealy machine
+      (see, for example, the Wikipedia article "Mealy machine").
     </p>
     <p>
       Like most <c>gen_</c> behaviors, <c>gen_statem</c> keeps
@@ -78,7 +78,7 @@ State(S) x Event(E) -> Actions(A), State(S')</pre>
       or on the number of distinct input events,
       a state machine implemented with this behavior
       is in fact Turing complete.
-      But it feels mostly like an Event-Driven Mealy Machine.
+      But it feels mostly like an Event-Driven Mealy machine.
     </p>
   </section>
 
@@ -300,7 +300,10 @@ State(S) x Event(E) -> Actions(A), State(S')</pre>
 	</p>
 	<p>
 	  See section
-	  <seealso marker="#Actions">Actions</seealso> for a list of possible
+	  <seealso marker="#State Transition Actions">
+	    State Transition Actions
+	  </seealso>
+	  for a list of possible
 	  state transition actions.
 	</p>
 	<p>
@@ -401,8 +404,8 @@ State(S) x Event(E) -> Actions(A), State(S')</pre>
 <!-- =================================================================== -->
 
   <section>
-    <marker id="Actions" />
-    <title>Actions</title>
+    <marker id="State Transition Actions" />
+    <title>State Transition Actions</title>
     <p>
       In the first
       <seealso marker="#Event-Driven State Machines">section</seealso>
@@ -415,9 +418,9 @@ State(S) x Event(E) -> Actions(A), State(S')</pre>
     </p>
     <p>
       There are more specific state-transition actions
-      that a callback function can order the <c>gen_statem</c>
+      that a callback function can command the <c>gen_statem</c>
       engine to do after the callback function return.
-      These are ordered by returning a list of
+      These are commanded by returning a list of
       <seealso marker="stdlib:gen_statem#type-action">actions</seealso>
       in the
       <seealso marker="stdlib:gen_statem#type-state_callback_result">
@@ -641,7 +644,7 @@ StateName(EventType, EventContent, Data) ->
     <p>
       Since the state enter call is not an event there are restrictions
       on the allowed return value and
-      <seealso marker="#Actions">state transition actions</seealso>.
+      <seealso marker="#State Transition Actions">state transition actions</seealso>.
       You may not change the state,
       <seealso marker="#Postponing Events">postpone</seealso>
       this non-event, or
@@ -742,7 +745,8 @@ open(state_timeout, lock,  Data) ->
     {next_state, locked, Data};
 open(cast, {button,_}, Data) ->
     {next_state, open, Data}.
-
+    ]]></code>
+    <code type="erl"><![CDATA[
 do_lock() ->
     io:format("Lock~n", []).
 do_unlock() ->
@@ -925,7 +929,7 @@ locked(
     <p>
       In state <c>locked</c>, when a button is pressed,
       it is collected with the last pressed buttons
-      up to the length of the correct dode,
+      up to the length of the correct code,
       and compared with the correct code.
       Depending on the result, the door is either unlocked
       and the <c>gen_statem</c> goes to state <c>open</c>,
@@ -960,7 +964,7 @@ open(cast, {button,_}, Data) ->
     <code type="erl"><![CDATA[
 {next_state, open, Data#{buttons := []},
  [{state_timeout,10000,lock}]};
-    ]]></code>
+ ]]></code>
     <p>
       10,000 is a time-out value in milliseconds.
       After this time (10 seconds), a time-out occurs.
@@ -1024,7 +1028,7 @@ handle_common({call,From}, code_length, #{code := Code} = Data) ->
 
     <p>
       Another way to do it is through a convenience macro
-      <c>?HANDLE_COMMON/3</c>:
+      <c>?HANDLE_COMMON/0</c>:
     </p>
     <code type="erl"><![CDATA[
 ...
@@ -1034,8 +1038,8 @@ handle_common({call,From}, code_length, #{code := Code} = Data) ->
 code_length() ->
     gen_statem:call(?NAME, code_length).
 
--define(HANDLE_COMMON(T, C, D),
-    ?FUNCTION_NAME(T, C, D) -> handle_common((T), (C), (D))).
+-define(HANDLE_COMMON,
+    ?FUNCTION_NAME(T, C, D) -> handle_common(T, C, D)).
 %%
 handle_common({call,From}, code_length, #{code := Code} = Data) ->
     {keep_state, Data, [{reply,From,length(Code)}]}.
@@ -1047,7 +1051,7 @@ locked(...) -> ... ;
 ...
 open(...) -> ... ;
 ?HANDLE_COMMON.
-    ]]></code>
+]]></code>
 
     <p>
       This example uses
@@ -1059,6 +1063,14 @@ open(...) -> ... ;
       when you want to stay in the current state but do not know or
       care about what it is.
     </p>
+    <p>
+      If the common event handler needs to know the current state
+      a function <c>handle_common/4</c> can be used instead:
+    </p>
+    <code type="erl"><![CDATA[
+-define(HANDLE_COMMON,
+    ?FUNCTION_NAME(T, C, D) -> handle_common(T, C, ?FUNCTION_NAME, D)).
+    ]]></code>
   </section>
 
 <!-- =================================================================== -->
@@ -1109,7 +1121,7 @@ handle_event(state_timeout, lock, open, Data) ->
     {next_state, locked, Data}.
 
 ...
-    ]]></code>
+]]></code>
   </section>
 
 <!-- =================================================================== -->
@@ -1141,7 +1153,7 @@ init(Args) ->
     process_flag(trap_exit, true),
     do_lock(),
     ...
-      ]]></code>
+    ]]></code>
       <p>
 	When ordered to shut down, the <c>gen_statem</c> then calls
 	callback function <c>terminate(shutdown, State, Data)</c>.
@@ -1155,7 +1167,7 @@ init(Args) ->
 terminate(_Reason, State, _Data) ->
     State =/= locked andalso do_lock(),
     ok.
-      ]]></code>
+    ]]></code>
     </section>
 
     <section>
@@ -1174,7 +1186,7 @@ terminate(_Reason, State, _Data) ->
 ...
 stop() ->
     gen_statem:stop(?NAME).
-      ]]></code>
+    ]]></code>
       <p>
 	This makes the <c>gen_statem</c> call callback function
 	<c>terminate/3</c> just like for a supervised server
@@ -1197,12 +1209,12 @@ stop() ->
     </p>
     <p>
       It is ordered by the state transition action
-      <c>{timeout,Time,EventContent}</c>, or just <c>Time</c>,
-      or even just <c>Time</c> instead of an action list
+      <c>{timeout,Time,EventContent}</c>, or just an integer <c>Time</c>,
+      even without the enclosing actions list
       (the latter is a form inherited from <c>gen_fsm</c>.
     </p>
     <p>
-      This type of time-out is useful to for example act on inactivity.
+      This type of time-out is useful for example to act on inactivity.
       Let us restart the code sequence
       if no button is pressed for say 30 seconds:
     </p>
@@ -1219,7 +1231,7 @@ locked(
             {next_state, locked, Data#{buttons := NewButtons},
              30000}
 ...
-     ]]></code>
+]]></code>
     <p>
       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>
@@ -1266,7 +1278,7 @@ locked(
     <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>:
+      named for example <c>open</c>:
     </p>
     <code type="erl"><![CDATA[
 ...
@@ -1278,26 +1290,31 @@ locked(
         NewButtons =:= Code -> % Correct
 	    do_unlock(),
             {next_state, open, Data#{buttons := []},
-             [{{timeout,open_tm},10000,lock}]};
+             [{{timeout,open},10000,lock}]};
 ...
 
-open({timeout,open_tm}, lock, Data) ->
+open({timeout,open}, lock, Data) ->
     do_lock(),
     {next_state,locked,Data};
 open(cast, {button,_}, Data) ->
     {keep_state,Data};
 ...
-    ]]></code>
+]]></code>
     <p>
-      Just as
-      <seealso marker="#State Time-Outs">state time-outs</seealso>
-      you can restart or cancel a specific generic time-out
+      An specific generic time-out can just as a
+      <seealso marker="#State Time-Outs">state time-out</seealso>
+      be restarted or cancelled
       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.
+      In this particular case we do not need to cancel the timeout
+      since the timeout event is the only possible reason to
+      change the state from <c>open</c> to <c>locked</c>.
+    </p>
+    <p>
+      Instead of bothering with when to cancel a time-out,
+      a late time-out event can be handled by ignoring it
+      if it arrives in a state where it is known to be late.
     </p>
   </section>
 
@@ -1309,7 +1326,7 @@ open(cast, {button,_}, Data) ->
     <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>.
+      <seealso marker="erts:erlang#start_timer/4"><c>erlang:start_timer/3,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
@@ -1339,7 +1356,7 @@ open(info, {timeout,Tref,lock}, #{timer := Tref} = Data) ->
 open(cast, {button,_}, Data) ->
     {keep_state,Data};
 ...
-    ]]></code>
+]]></code>
     <p>
       Removing the <c>timer</c> key from the map when we
       change to state <c>locked</c> is not strictly
@@ -1379,7 +1396,9 @@ open(cast, {button,_}, Data) ->
     </p>
     <p>
       Postponing is ordered by the state transition
-      <seealso marker="stdlib:gen_statem#type-action">action</seealso>
+      <seealso marker="#State Transition Actions">
+	state transition action
+      </seealso>
       <c>postpone</c>.
     </p>
     <p>
@@ -1392,14 +1411,17 @@ open(cast, {button,_}, Data) ->
 open(cast, {button,_}, Data) ->
     {keep_state,Data,[postpone]};
 ...
-    ]]></code>
+]]></code>
     <p>
       Since a postponed event is only retried after a state change,
       you have to think about where to keep a state data item.
       You can keep it in the server <c>Data</c>
       or in the <c>State</c> itself,
       for example by having two more or less identical states
-      to keep a boolean value, or by using a complex state with
+      to keep a boolean value, or by using a complex state
+      (see section
+      <seealso marker="#Complex State">Complex State</seealso>)
+      with
       <seealso marker="#Callback Modes">callback mode</seealso>
       <seealso marker="stdlib:gen_statem#type-callback_mode"><c>handle_event_function</c></seealso>.
       If a change in the value changes the set of events that is handled,
@@ -1504,8 +1526,10 @@ do_unlock() ->
       passing non-system messages to the callback module.
     </p>
     <p>
-      The state transition
-      <seealso marker="stdlib:gen_statem#type-action">action</seealso>
+      The
+      <seealso marker="#State Transition Action">
+	state transition action
+      </seealso>
       <c>postpone</c> is designed to model
       selective receives. A selective receive implicitly postpones
       any not received events, but the <c>postpone</c>
@@ -1569,7 +1593,7 @@ open(enter, _OldState, _Data) ->
 open(state_timeout, lock, Data) ->
     {next_state, locked, Data};
 ...
-    ]]></code>
+]]></code>
     <p>
       You can repeat the state enter code by returning one of
       <c>{repeat_state, ...}</c>, <c>{repeat_state_and_data,_}</c>
@@ -1591,8 +1615,10 @@ open(state_timeout, lock, Data) ->
     <p>
       It can sometimes be beneficial to be able to generate events
       to your own state machine.
-      This can be done with the state transition
-      <seealso marker="stdlib:gen_statem#type-action">action</seealso>
+      This can be done with the
+      <seealso marker="#State Transition Action">
+	state transition action
+      </seealso>
       <c>{next_event,EventType,EventContent}</c>.
     </p>
     <p>
@@ -1643,10 +1669,10 @@ locked(
   internal, {button,Digit},
   #{code := Code, length := Length, buttons := Buttons} = Data) ->
 ...
-    ]]></code>
+]]></code>
     <code type="erl"><![CDATA[
 handle_common(cast, {down,Button}, Data) ->
-    {keep_state, Data#{button := Button};
+    {keep_state, Data#{button := Button}};
 handle_common(cast, {up,Button}, Data) ->
     case Data of
         #{button := Button} ->
@@ -1660,7 +1686,7 @@ handle_common(cast, {up,Button}, Data) ->
 open(internal, {button,_}, Data) ->
     {keep_state,Data,[postpone]};
 ...
-    ]]></code>
+]]></code>
     <p>
       If you start this program with <c>code_lock:start([17])</c>
       you can unlock with <c>code_lock:down(17), code_lock:up(17).</c>
@@ -1685,8 +1711,8 @@ open(internal, {button,_}, Data) ->
     <p>
       Notice that this state diagram does not specify how to handle
       a button event in the state <c>open</c>. So, you need to
-      read here that unspecified events
-      must be ignored as in not consumed but handled in some other state.
+      read in some side notes, that is, here: that unspecified events
+      shall be postponed (handled in some later state).
       Also, the state diagram does not show that the <c>code_length/0</c>
       call must be handled in every state.
     </p>
@@ -1719,17 +1745,17 @@ up(Digit) ->
 code_length() ->
     gen_statem:call(?NAME, code_length).
     ]]></code>
-    <code type="erl"><![CDATA[
+      <code type="erl"><![CDATA[
 init(Code) ->
     process_flag(trap_exit, true),
-    Data = #{code => Code, length => Length, buttons => []},
+    Data = #{code => Code, length => length(Code), buttons => []},
     {ok, locked, Data}.
 
 callback_mode() ->
     [state_functions,state_enter].
 
 -define(HANDLE_COMMON,
-    ?FUNCTION_NAME(T, C, D) -> handle_common((T), (C), (D))).
+    ?FUNCTION_NAME(T, C, D) -> handle_common(T, C, D)).
 %%
 handle_common(cast, {down,Button}, Data) ->
     {keep_state, Data#{button => Button}};
@@ -1763,14 +1789,13 @@ locked(
     if
         NewButtons =:= Code -> % Correct
 	    do_unlock(),
-            {next_state, open, Data,
-             [{state_timeout,10000,lock}]};
+            {next_state, open, Data};
 	true -> % Incomplete | Incorrect
             {keep_state, Data#{buttons := NewButtons},
              [{state_timeout,30000,button}]}
     end;
 ?HANDLE_COMMON.
-    ]]></code>
+]]></code>
     <code type="erl"><![CDATA[
 open(enter, _OldState, _Data) ->
     do_unlock(),
@@ -1789,7 +1814,7 @@ do_unlock() ->
 terminate(_Reason, State, _Data) ->
     State =/= locked andalso do_lock(),
     ok.
-      ]]></code>
+    ]]></code>
     </section>
 
     <section>
@@ -1803,13 +1828,14 @@ terminate(_Reason, State, _Data) ->
         so this example first branches depending on state:
       </p>
       <code type="erl"><![CDATA[
-...
 -export([handle_event/4]).
-
-...
+]]></code>
+      <code type="erl"><![CDATA[
 callback_mode() ->
     [handle_event_function,state_enter].
-
+    ]]></code>
+      <code type="erl"><![CDATA[
+%%
 %% State: locked
 handle_event(enter, _OldState, locked, Data) ->
     do_lock(),
@@ -1829,14 +1855,13 @@ handle_event(
     if
         NewButtons =:= Code -> % Correct
 	    do_unlock(),
-            {next_state, open, Data,
-             [{state_timeout,10000,lock}]};
+            {next_state, open, Data};
 	true -> % Incomplete | Incorrect
             {keep_state, Data#{buttons := NewButtons},
              [{state_timeout,30000,button}]}
     end;
     ]]></code>
-    <code type="erl"><![CDATA[
+      <code type="erl"><![CDATA[
 %%
 %% State: open
 handle_event(enter, _OldState, open, _Data) ->
@@ -1844,12 +1869,11 @@ handle_event(enter, _OldState, open, _Data) ->
     {keep_state_and_data, [{state_timeout,10000,lock}]};
 handle_event(state_timeout, lock, open, Data) ->
     {next_state, locked, Data};
-handle_event(cast, {button,_}, open, _) ->
+handle_event(internal, {button,_}, open, _) ->
     {keep_state_and_data,[postpone]};
     ]]></code>
-    <code type="erl"><![CDATA[
-%%
-%% Any state
+      <code type="erl"><![CDATA[
+%% Common events
 handle_event(cast, {down,Button}, _State, Data) ->
     {keep_state, Data#{button => Button}};
 handle_event(cast, {up,Button}, _State, Data) ->
@@ -1862,13 +1886,11 @@ handle_event(cast, {up,Button}, _State, Data) ->
     end;
 handle_event({call,From}, code_length, _State, #{length := Length}) ->
     {keep_state_and_data, [{reply,From,Length}]}.
-
-...
-      ]]></code>
+    ]]></code>
     </section>
     <p>
-      Notice that postponing buttons from the <c>locked</c> state
-      to the <c>open</c> state feels like a strange thing to do
+      Notice that postponing buttons from the <c>open</c> state
+      to the <c>locked</c> state feels like a strange thing to do
       for a code lock, but it at least illustrates event postponing.
     </p>
   </section>
@@ -1951,7 +1973,7 @@ format_status(Opt, [_PDict,State,Data]) ->
       <seealso marker="#State Time-Outs">state time-out</seealso>,
       or one that affects the event handling
       in combination with postponing events.
-      We will complicate the previous example
+      We will go for the latter and complicate the previous example
       by introducing a configurable lock button
       (this is the state item in question),
       which in the <c>open</c> state immediately locks the door,
@@ -1960,33 +1982,33 @@ format_status(Opt, [_PDict,State,Data]) ->
     <p>
       Suppose now that we call <c>set_lock_button</c>
       while the door is open,
-      and have already postponed a button event
-      that until now was not the lock button.
-      The sensible thing can be to say that
-      the button was pressed too early so it is
-      not to be recognized as the lock button.
-      However, then it can be surprising that a button event
-      that now is the lock button event arrives (as retried postponed)
-      immediately after the state transits to <c>locked</c>.
-    </p>
-    <p>
-      So we make the <c>button/1</c> function synchronous
-      by using
-      <seealso marker="stdlib:gen_statem#call/2"><c>gen_statem:call</c></seealso>
-      and still postpone its events in the <c>open</c> state.
-      Then a call to <c>button/1</c> during the <c>open</c>
-      state does not return until the state transits to <c>locked</c>,
-      as it is there the event is handled and the reply is sent.
-    </p>
-    <p>
-      If a process now calls <c>set_lock_button/1</c>
-      to change the lock button while another process
-      hangs in <c>button/1</c> with the new lock button,
-      it can be expected that the hanging lock button call
-      immediately takes effect and locks the lock.
-      Therefore, we make the current lock button a part of the state,
-      so that when we change the lock button, the state changes
-      and all postponed events are retried.
+      and we have already postponed a button event
+      that was the new lock button:
+    </p>
+    <code type="erl"><![CDATA[
+1> code_lock:start_link([a,b,c], x).
+{ok,<0.666.0>}
+2> code_lock:button(a).
+ok
+3> code_lock:button(b).
+ok
+4> code_lock:button(c).
+ok
+Open
+5> code_lock:button(y).
+ok
+6> code_lock:set_lock_button(y).
+x
+% What should happen here?  Immediate lock or nothing?
+]]></code>
+    <p>
+      We could say that the button was pressed too early
+      so it is not to be recognized as the lock button.
+      Or we can make the lock button part of the state so
+      when we then change the lock button in the locked state,
+      the change becomes a state change
+      and all postponed events are retried,
+      therefore the lock is immediately locked!
     </p>
     <p>
       We define the state as <c>{StateName,LockButton}</c>,
@@ -1999,8 +2021,8 @@ format_status(Opt, [_PDict,State,Data]) ->
 -define(NAME, code_lock_3).
 
 -export([start_link/2,stop/0]).
--export([button/1,code_length/0,set_lock_button/1]).
--export([init/1,callback_mode/0,terminate/3,format_status/2]).
+-export([button/1,set_lock_button/1]).
+-export([init/1,callback_mode/0,terminate/3]).
 -export([handle_event/4]).
 
 start_link(Code, LockButton) ->
@@ -2009,10 +2031,8 @@ start_link(Code, LockButton) ->
 stop() ->
     gen_statem:stop(?NAME).
 
-button(Digit) ->
-    gen_statem:call(?NAME, {button,Digit}).
-code_length() ->
-    gen_statem:call(?NAME, code_length).
+button(Button) ->
+    gen_statem:cast(?NAME, {button,Button}).
 set_lock_button(LockButton) ->
     gen_statem:call(?NAME, {set_lock_button,LockButton}).
     ]]></code>
@@ -2025,70 +2045,53 @@ init({Code,LockButton}) ->
 callback_mode() ->
     [handle_event_function,state_enter].
 
+%% State: locked
+handle_event(enter, _OldState, {locked,_}, Data) ->
+    do_lock(),
+    {keep_state, Data#{buttons := []}};
+handle_event(state_timeout, button, {locked,_}, Data) ->
+    {keep_state, Data#{buttons := []}};
 handle_event(
-  {call,From}, {set_lock_button,NewLockButton},
-  {StateName,OldLockButton}, Data) ->
-    {next_state, {StateName,NewLockButton}, Data,
-     [{reply,From,OldLockButton}]};
-handle_event(
-  {call,From}, code_length,
-  {_StateName,_LockButton}, #{length := Length}) ->
-    {keep_state_and_data,
-     [{reply,From,Length}]};
+  cast, {button,Digit}, {locked,LockButton},
+  #{code := Code, length := Length, buttons := Buttons} = Data) ->
+    NewButtons =
+        if
+            length(Buttons) < Length ->
+                Buttons;
+            true ->
+                tl(Buttons)
+        end ++ [Button],
+    if
+        NewButtons =:= Code -> % Correct
+	    do_unlock(),
+            {next_state, {open,LockButton}, Data};
+	true -> % Incomplete | Incorrect
+            {keep_state, Data#{buttons := NewButtons},
+             [{state_timeout,30000,button}]}
+    end;
     ]]></code>
     <code type="erl"><![CDATA[
 %%
-%% State: locked
-handle_event(EventType, EventContent, {locked,LockButton}, Data) ->
-    case {EventType, EventContent} of
-	{enter, _OldState} ->
-	    do_lock(),
-	    {keep_state, Data#{buttons := []}};
-        {state_timeout, button} ->
-            {keep_state, Data#{buttons := []}};
-	{{call,From}, {button,Digit}} ->
-            #{length := Length, buttons := Buttons} = Data,
-            NewButtons =
-                if
-                    length(Buttons) < Length ->
-                        Buttons;
-                    true ->
-                        tl(Buttons)
-                end ++ [Button],
-            case Data of
-                #{code := NewButtons} ->
-		    {next_state, {open,LockButton}, Data,
-		     [{reply,From,ok}]};
-                #{} ->
-		    {keep_state, Data#{buttons := NewButtons},
-		     [{reply,From,ok},
-                      {state_timeout,30000,button}]}
-            end
-    end;
+%% State: open
+handle_event(enter, _OldState, {open,_}, _Data) ->
+    do_unlock(),
+    {keep_state_and_data,
+     [{state_timeout,10000,lock}]};
+handle_event(state_timeout, lock, {open,_}, Data) ->
+    {next_state, locked, Data};
+handle_event(cast, {button,LockButton}, {open,LockButton}, Data) ->
+    {next_state, {locked,LockButton}, Data};
+handle_event(cast, {button,_}, {open,_}, Data) ->
+    {keep_state_and_data,[postpone]};
     ]]></code>
     <code type="erl"><![CDATA[
 %%
-%% State: open
+%% Common events
 handle_event(
-  EventType, EventContent,
-  {open,LockButton}, Data) ->
-    case {EventType, EventContent} of
-	{enter, _OldState} ->
-	    do_unlock(),
-	    {keep_state_and_data,
-             [{state_timeout,10000,lock}]};
-	{state_timeout, lock} ->
-	    {next_state, {locked,LockButton}, Data};
-	{{call,From}, {button,Digit}} ->
-	    if
-		Digit =:= LockButton ->
-		    {next_state, {locked,LockButton}, Data,
-		     [{reply,From,locked}]};
-		true ->
-		    {keep_state_and_data,
-		     [postpone]}
-	    end
-    end.
+  {call,From}, {set_lock_button,NewLockButton},
+  {StateName,OldLockButton}, Data) ->
+    {next_state, {StateName,NewLockButton}, Data,
+     [{reply,From,OldLockButton}]}.
     ]]></code>
     <code type="erl"><![CDATA[
 do_lock() ->
@@ -2099,27 +2102,7 @@ do_unlock() ->
 terminate(_Reason, State, _Data) ->
     State =/= locked andalso do_lock(),
     ok.
-format_status(Opt, [_PDict,State,Data]) ->
-    StateData =
-	{State,
-	 maps:filter(
-	   fun (code, _) -> false;
-	       (remaining, _) -> false;
-	       (_, _) -> true
-	   end,
-	   Data)},
-    case Opt of
-	terminate ->
-	    StateData;
-	normal ->
-	    [{data,[{"State",StateData}]}]
-    end.
     ]]></code>
-    <p>
-      It can be an ill-fitting model for a physical code lock
-      that the <c>button/1</c> call can hang until the lock
-      is locked. But for an API in general it is not that strange.
-    </p>
   </section>
 
 <!-- =================================================================== -->
@@ -2151,18 +2134,15 @@ format_status(Opt, [_PDict,State,Data]) ->
     </p>
     <code type="erl"><![CDATA[
 ...
+%%
 %% State: open
-handle_event(
-  EventType, EventContent,
-  {open,LockButton}, Data) ->
-    case {EventType, EventContent} of
-        {enter, _OldState} ->
-            do_unlock(),
-            {keep_state_and_data,
-             [{state_timeout,10000,lock},
-              hibernate]};
+handle_event(enter, _OldState, {open,_}, _Data) ->
+    do_unlock(),
+    {keep_state_and_data,
+     [{state_timeout,10000,lock},
+      hibernate]};
 ...
-    ]]></code>
+]]></code>
     <p>
       The atom
       <seealso marker="stdlib:gen_statem#type-hibernate"><c>hibernate</c></seealso>
@@ -2175,9 +2155,8 @@ handle_event(
     <p>
       To change that we would need to insert
       action <c>hibernate</c> in more places.
-      For example, for the state-independent <c>set_lock_button</c>
-      and <c>code_length</c> operations that then would have to
-      be aware of using <c>hibernate</c> while in the
+      For example, the state-independent <c>set_lock_button</c>
+      operation would have to use <c>hibernate</c> but only in the
       <c>{open,_}</c> state, which would clutter the code.
     </p>
     <p>
@@ -2201,7 +2180,8 @@ handle_event(
       This particular server probably does not use
       heap memory worth hibernating for.
       To gain anything from hibernation, your server would
-      have to produce some garbage during callback execution,
+      have to produce non-insignificant garbage
+      during callback execution,
       for which this example server can serve as a bad example.
     </p>
   </section>
-- 
2.16.3

openSUSE Build Service is sponsored by