File 1273-Fix-multiple-ct_gen_conn-do_within_time-2-issues.patch of Package erlang
From 0baef2c39cf68f6f413ea057dc36e447047a8cd8 Mon Sep 17 00:00:00 2001
From: Anders Svensson <anders@erlang.org>
Date: Wed, 7 Apr 2021 12:15:52 +0200
Subject: [PATCH 3/4] Fix multiple ct_gen_conn:do_within_time/2 issues
The function assumed the caller is trapping exits and is linked to the
connection process, but had several problems:
- It left an EXIT message from the temporary process evaluating the
function whose value is to be returned in the caller's message queue
in the successful case before timeout.
- It could leave both a result message and an EXIT message in the
caller's message queue after connection process exit since both
can be sent before the temporary process is unlinked and killed.
- It didn't return at all if the fun being evaluated failed before
timeout since receiving the EXIT message matched on the reason
being 'killed'.
- It potentially reordered the caller's message queue by resending
an EXIT message to self().
Do away with the second assumption and all the problems by using the
exit reason to communicate the result from the temporary process and
monitoring on the connection process.
There's one more problem however: the connection process pid retrieved
from the process dictionary is only put there after the user's init/3
callback returns it, but ct_telnet calls do_within_time/2 from this
callback (and others). The link to the connection process is also added
after init/3 makes it known. This should be fixed by not passing
function arguments through the process dictionary, but fixing this in
the tortured mechanics of ct_telnet (the only caller of do_within_time/2
in practice) isn't worth the effort in this commit. Simply work around
it by using self() as the connection pid in this case, which renders the
monitoring as ineffectual as an unset link. The consequence is just that
failure of a connection process won't be detected in this case, so
do_within_time/2 times out instead in the error case.
---
lib/common_test/src/ct_gen_conn.erl | 75 +++++++++++++++++------------
1 file changed, 43 insertions(+), 32 deletions(-)
diff --git a/lib/common_test/src/ct_gen_conn.erl b/lib/common_test/src/ct_gen_conn.erl
index 3059cb2b46..47aa5966bb 100644
--- a/lib/common_test/src/ct_gen_conn.erl
+++ b/lib/common_test/src/ct_gen_conn.erl
@@ -220,41 +220,52 @@ end_log() ->
Result :: term().
%% Return the result of evaluating Fun, or interrupt after Tmo
-%% milliseconds or if the connection is closed.
-
-do_within_time(Fun,Timeout) ->
- Self = self(),
- Silent = get(silent),
- TmpPid = spawn_link(fun() ->
- ct_util:mark_process(),
- put(silent,Silent),
- R = Fun(),
- Self ! {self(),R}
- end),
- ConnPid = get(conn_pid),
+%% milliseconds or if the connection is closed. Assumes the caller
+%% is trapping exits.
+
+do_within_time(Fun, Tmo) ->
+ do_within_time(Fun, Tmo, get(silent), get(conn_pid)).
+
+%% Work around the fact that ct_telnet calls do_within_time/2 in its
+%% init callback, before it returns the connection pid for init/1 to
+%% write to the process dictionary. Monitoring on self() is pointless,
+%% but harmless. Should really be fixed by not using the process
+%% dictionary to pass arguments.
+do_within_time(Fun, Tmo, Silent, undefined) ->
+ do_within_time(Fun, Tmo, Silent, self());
+
+do_within_time(Fun, Tmo, Silent, ConnPid) ->
+ MRef = monitor(process, ConnPid),
+ Pid = spawn_link(fun() ->
+ ct_util:mark_process(),
+ put(silent, Silent),
+ exit({MRef, Fun()})
+ end),
+ down(Pid, MRef, Tmo, failure).
+
+down(Pid, MRef, Tmo, Reason) ->
receive
- {TmpPid,Result} ->
- Result;
- {'EXIT',ConnPid,_Reason}=M ->
- unlink(TmpPid),
- exit(TmpPid,kill),
- self() ! M,
- {error,connection_closed}
- after
- Timeout ->
- exit(TmpPid,kill),
- receive
- {TmpPid,Result} ->
- %% TmpPid just managed to send the result at the same time
- %% as the timeout expired.
- receive {'EXIT',TmpPid,_reason} -> ok end,
- Result;
- {'EXIT',TmpPid,killed} ->
- %% TmpPid did not send the result before the timeout expired.
- {error,timeout}
- end
+ {'EXIT', Pid, T} ->
+ infinity == Tmo orelse demonitor(MRef, [flush]),
+ rc(MRef, T, Reason);
+ {'DOWN', MRef, process, _, _} ->
+ down(Pid, MRef, connection_closed)
+ after Tmo ->
+ demonitor(MRef, [flush]),
+ down(Pid, MRef, timeout)
end.
+down(Pid, MRef, Reason) ->
+ exit(Pid, kill),
+ down(Pid, MRef, infinity, Reason).
+
+rc(Ref, {Ref, RC}, _Reason) ->
+ RC;
+rc(_, Reason, failure) -> %% failure before timeout or lost connection
+ {error, Reason};
+rc(_, _, Reason) ->
+ {error, Reason}.
+
%% ===========================================================================
do_start(Address, InitData, CallbackMod, OptsList) ->
--
2.26.2