File 0189-Fix-race-condition-in-proc_lib-stop-3-with-small-tim.patch of Package erlang
From 311eb1258b697ac316f300ccee48b9a1b95c496b Mon Sep 17 00:00:00 2001
From: juhlig <juhlig@hnc-agency.org>
Date: Fri, 21 May 2021 17:37:29 +0200
Subject: [PATCH] Fix race condition in proc_lib:stop/3 with small timeouts
Ensures that the terminate message is always sent to the
target process.
Removes the obsolete proxy process.
---
lib/stdlib/src/proc_lib.erl | 51 +++++++++++++++---------------
lib/stdlib/test/proc_lib_SUITE.erl | 39 +++++++++++++++--------
2 files changed, 51 insertions(+), 39 deletions(-)
diff --git a/lib/stdlib/src/proc_lib.erl b/lib/stdlib/src/proc_lib.erl
index 58e6faf950..3bd68646fe 100644
--- a/lib/stdlib/src/proc_lib.erl
+++ b/lib/stdlib/src/proc_lib.erl
@@ -1062,33 +1062,32 @@ stop(Process) ->
Reason :: term(),
Timeout :: timeout().
stop(Process, Reason, Timeout) ->
- {Pid, Mref} = erlang:spawn_monitor(do_stop(Process, Reason)),
+ Mref = erlang:monitor(process, Process),
+ T0 = erlang:monotonic_time(millisecond),
+ RemainingTimeout = try
+ sys:terminate(Process, Reason, Timeout)
+ of
+ ok when Timeout =:= infinity ->
+ infinity;
+ ok ->
+ Timeout - (((erlang:monotonic_time(microsecond) + 999) div 1000) - T0)
+ catch
+ exit:{noproc, {sys, terminate, _}} ->
+ demonitor(Mref, [flush]),
+ exit(noproc);
+ exit:{timeout, {sys, terminate, _}} ->
+ demonitor(Mref, [flush]),
+ exit(timeout);
+ exit:Reason1 ->
+ demonitor(Mref, [flush]),
+ exit(Reason1)
+ end,
receive
{'DOWN', Mref, _, _, Reason} ->
ok;
- {'DOWN', Mref, _, _, {noproc,{sys,terminate,_}}} ->
- exit(noproc);
- {'DOWN', Mref, _, _, CrashReason} ->
- exit(CrashReason)
- after Timeout ->
- exit(Pid, kill),
- receive
- {'DOWN', Mref, _, _, _} ->
- exit(timeout)
- end
- end.
-
--spec do_stop(Process, Reason) -> Fun when
- Process :: pid() | RegName | {RegName,node()},
- RegName :: atom(),
- Reason :: term(),
- Fun :: fun(() -> no_return()).
-do_stop(Process, Reason) ->
- fun() ->
- Mref = erlang:monitor(process, Process),
- ok = sys:terminate(Process, Reason, infinity),
- receive
- {'DOWN', Mref, _, _, ExitReason} ->
- exit(ExitReason)
- end
+ {'DOWN', Mref, _, _, Reason2} ->
+ exit(Reason2)
+ after RemainingTimeout ->
+ demonitor(Mref, [flush]),
+ exit(timeout)
end.
diff --git a/lib/stdlib/test/proc_lib_SUITE.erl b/lib/stdlib/test/proc_lib_SUITE.erl
index b3673efb5a..33109e93ad 100644
--- a/lib/stdlib/test/proc_lib_SUITE.erl
+++ b/lib/stdlib/test/proc_lib_SUITE.erl
@@ -668,34 +668,47 @@ stop(_Config) ->
Pid3 = proc_lib:spawn(HangProc),
{'EXIT',timeout} = (catch proc_lib:stop(Pid3,normal,1000)),
+ %% Ensure that a termination message is always sent to the
+ %% target process and that it eventually terminates.
+ Pid4 = proc_lib:spawn(HangProc),
+ Ref4 = monitor(process, Pid4),
+ {'EXIT', timeout} = (catch proc_lib:stop(Pid4, normal, 0)),
+ ok = receive
+ {'DOWN', Ref4, process, _, _} ->
+ ok;
+ M -> M
+ after 6000 ->
+ timeout
+ end,
+
%% Success case with other reason than 'normal'
- Pid4 = proc_lib:spawn(SysMsgProc),
- ok = proc_lib:stop(Pid4,other_reason,infinity),
- false = erlang:is_process_alive(Pid4),
+ Pid5 = proc_lib:spawn(SysMsgProc),
+ ok = proc_lib:stop(Pid5,other_reason,infinity),
+ false = erlang:is_process_alive(Pid5),
%% System message is handled, but process dies with other reason
%% than the given (in system_terminate/4 below)
- Pid5 = proc_lib:spawn(SysMsgProc),
- {'EXIT',{{badmatch,2},_Stacktrace}} = (catch proc_lib:stop(Pid5,crash,infinity)),
- false = erlang:is_process_alive(Pid5),
+ Pid6 = proc_lib:spawn(SysMsgProc),
+ {'EXIT',{{badmatch,2},_Stacktrace}} = (catch proc_lib:stop(Pid6,crash,infinity)),
+ false = erlang:is_process_alive(Pid6),
%% Local registered name
- Pid6 = proc_lib:spawn(SysMsgProc),
- register(to_stop,Pid6),
+ Pid7 = proc_lib:spawn(SysMsgProc),
+ register(to_stop,Pid7),
ok = proc_lib:stop(to_stop),
undefined = whereis(to_stop),
- false = erlang:is_process_alive(Pid6),
+ false = erlang:is_process_alive(Pid7),
%% Remote registered name
{ok,Node} = test_server:start_node(proc_lib_SUITE_stop,slave,[]),
Dir = filename:dirname(code:which(?MODULE)),
rpc:call(Node,code,add_path,[Dir]),
- Pid7 = spawn(Node,SysMsgProc),
- true = rpc:call(Node,erlang,register,[to_stop,Pid7]),
- Pid7 = rpc:call(Node,erlang,whereis,[to_stop]),
+ Pid8 = spawn(Node,SysMsgProc),
+ true = rpc:call(Node,erlang,register,[to_stop,Pid8]),
+ Pid8 = rpc:call(Node,erlang,whereis,[to_stop]),
ok = proc_lib:stop({to_stop,Node}),
undefined = rpc:call(Node,erlang,whereis,[to_stop]),
- false = rpc:call(Node,erlang,is_process_alive,[Pid7]),
+ false = rpc:call(Node,erlang,is_process_alive,[Pid8]),
%% Local and remote registered name, but non-existing
{'EXIT',noproc} = (catch proc_lib:stop(to_stop)),
--
2.26.2