File 4531-stdlib-Remove-gen_statem-call-proxy-process.patch of Package erlang

From 3560e12ec72832d07c604046a6b06003aa07a1e9 Mon Sep 17 00:00:00 2001
From: Rickard Green <rickard@erlang.org>
Date: Thu, 30 Mar 2023 19:57:16 +0200
Subject: [PATCH] [stdlib] Remove gen_statem call proxy process

The proxy process was used to prevent late replies from reaching the client
at timeout or connection loss. This is no longer needed since process aliases
take care of this, are used and supported by all Erlang nodes that an OTP 26
Erlang node can communicate with.
---
 lib/stdlib/doc/src/gen_statem.xml | 44 ++++----------------
 lib/stdlib/src/gen_statem.erl     | 68 +++----------------------------
 2 files changed, 15 insertions(+), 97 deletions(-)

diff --git a/lib/stdlib/doc/src/gen_statem.xml b/lib/stdlib/doc/src/gen_statem.xml
index 1eae53d9e4..735852a13c 100644
--- a/lib/stdlib/doc/src/gen_statem.xml
+++ b/lib/stdlib/doc/src/gen_statem.xml
@@ -1774,43 +1774,17 @@ handle_event(_, _, State, Data) ->
 	  which is the default. If no reply is received within
 	  the specified time, the function call fails.
 	</p>
-	<note>
-	  <p>
-	    For <c><anno>Timeout</anno> &lt; infinity</c>,
-	    to avoid getting a late reply in the caller's
-	    inbox if the caller should catch exceptions,
-	    this function spawns a proxy process that
-	    does the call. A late reply gets delivered to the
-	    dead proxy process, hence gets discarded. This is
-	    less efficient than using
-	    <c><anno>Timeout</anno> == infinity</c>.
-	  </p>
-	</note>
 	<p>
-	  <c><anno>Timeout</anno></c> can also be a tuple
-	  <c>{clean_timeout,<anno>T</anno>}</c> or
-	  <c>{dirty_timeout,<anno>T</anno>}</c>, where
-	  <c><anno>T</anno></c> is the time-out time.
-	  <c>{clean_timeout,<anno>T</anno>}</c> works like
-	  just <c>T</c> described in the note above
-	  and uses a proxy process
-	  while <c>{dirty_timeout,<anno>T</anno>}</c>
-	  bypasses the proxy process which is more lightweight.
+          Previous issue with late replies that could occur when having
+          network issues or using <c>dirty_timeout</c> is now prevented
+          by use of
+          <seeguide marker="system/reference_manual:processes#process-aliases"><i>process
+          aliases</i></seeguide>. <c>{clean_timeout, <anno>T</anno>}</c>
+          and <c>{dirty_timeout, <anno>T</anno>}</c> therefore no longer
+          serves any purpose and will work the same as
+          <c><anno>Timeout</anno></c> while all of them also being
+          equally efficient.
 	</p>
-	<note>
-	  <p>
-	    If you combine catching exceptions from this function
-	    with <c>{dirty_timeout,<anno>T</anno>}</c>
-	    to avoid that the calling process dies when the call
-	    times out, you will have to be prepared to handle
-	    a late reply.  Note that there is an odd chance
-	    to get a late reply even with
-	    <c>{dirty_timeout,infinity}</c> or <c>infinity</c>
-	    for example in the event of network problems.
-	    So why not just let the calling process die
-	    by not catching the exception?
-	  </p>
-	</note>
 	<p>
 	  The call can also fail, for example, if the <c>gen_statem</c>
 	  dies before or during this function call.
diff --git a/lib/stdlib/src/gen_statem.erl b/lib/stdlib/src/gen_statem.erl
index b30337e7d8..849bf45561 100644
--- a/lib/stdlib/src/gen_statem.erl
+++ b/lib/stdlib/src/gen_statem.erl
@@ -645,15 +645,15 @@ call(ServerRef, Request) ->
 	  {'dirty_timeout',T :: timeout()}) ->
 		  Reply :: term().
 call(ServerRef, Request, infinity = T = Timeout) ->
-    call_dirty(ServerRef, Request, Timeout, T);
+    call(ServerRef, Request, Timeout, T);
 call(ServerRef, Request, {dirty_timeout, T} = Timeout) ->
-    call_dirty(ServerRef, Request, Timeout, T);
+    call(ServerRef, Request, Timeout, T);
 call(ServerRef, Request, {clean_timeout, T} = Timeout) ->
-    call_clean(ServerRef, Request, Timeout, T);
+    call(ServerRef, Request, Timeout, T);
 call(ServerRef, Request, {_, _} = Timeout) ->
     erlang:error(badarg, [ServerRef,Request,Timeout]);
 call(ServerRef, Request, Timeout) ->
-    call_clean(ServerRef, Request, Timeout, Timeout).
+    call(ServerRef, Request, Timeout, Timeout).
 
 -spec send_request(ServerRef::server_ref(), Request::term()) ->
         ReqId::request_id().
@@ -900,7 +900,8 @@ enter_loop(Module, Opts, State, Data, Server, Actions) ->
 wrap_cast(Event) ->
     {'$gen_cast',Event}.
 
-call_dirty(ServerRef, Request, Timeout, T) ->
+-compile({inline, [call/4]}).
+call(ServerRef, Request, Timeout, T) ->
     try gen:call(ServerRef, '$gen_call', Request, T) of
         {ok,Reply} ->
             Reply
@@ -914,63 +915,6 @@ call_dirty(ServerRef, Request, Timeout, T) ->
               Stacktrace)
     end.
 
-call_clean(ServerRef, Request, Timeout, T)
-  when (is_pid(ServerRef)
-        andalso (node(ServerRef) == node()))
-       orelse (element(2, ServerRef) == node()
-               andalso is_atom(element(1, ServerRef))
-               andalso (tuple_size(ServerRef) =:= 2)) ->
-    %% No need to use a proxy locally since we know alias will be
-    %% used as of OTP 24 which will prevent garbage responses...
-    call_dirty(ServerRef, Request, Timeout, T);
-call_clean(ServerRef, Request, Timeout, T) ->
-    %% Call server through proxy process to dodge any late reply
-    %%
-    %% We still need a proxy in the distributed case since we may
-    %% communicate with a node that does not understand aliases.
-    %% This can be removed when alias support is mandatory.
-    %% Probably in OTP 26.
-    Ref = make_ref(),
-    Self = self(),
-    Pid = spawn(
-            fun () ->
-                    Self !
-                        try gen:call(
-                              ServerRef, '$gen_call', Request, T) of
-                            Result ->
-                                {Ref,Result}
-                        catch Class:Reason:Stacktrace ->
-                                {Ref,Class,Reason,Stacktrace}
-                        end
-            end),
-    Mref = monitor(process, Pid),
-    receive
-        {Ref,Result} ->
-            demonitor(Mref, [flush]),
-            case Result of
-                {ok,Reply} ->
-                    Reply
-            end;
-        {Ref,Class,Reason,Stacktrace} when Class =:= exit ->
-            %% 'gen' raises 'exit' for problems
-            demonitor(Mref, [flush]),
-            %% Pretend it happened in this process
-            erlang:raise(
-              Class,
-              %% Wrap the reason according to tradition
-              {Reason,{?MODULE,call,[ServerRef,Request,Timeout]}},
-              Stacktrace);
-        {Ref,Class,Reason,Stacktrace} ->
-            demonitor(Mref, [flush]),
-            %% Pretend it happened in this process
-            erlang:raise(Class, Reason, Stacktrace);
-        {'DOWN',Mref,_,_,Reason} ->
-            %% There is a theoretical possibility that the
-            %% proxy process gets killed between try--of and !
-            %% so this clause is in case of that
-            exit(Reason)
-    end.
-
 replies([{reply,From,Reply}|Replies]) ->
     reply(From, Reply),
     replies(Replies);
-- 
2.35.3

openSUSE Build Service is sponsored by