File 6543-Make-shutdown-connections-synchronous.patch of Package erlang

From b3eccb35a4faac5cdd3f008403a3d629d682b83b Mon Sep 17 00:00:00 2001
From: Raimo Niskanen <raimo@erlang.org>
Date: Fri, 21 Jul 2023 15:54:17 +0200
Subject: [PATCH 3/3] Make shutdown connections synchronous

Use monitors to wait for workers to stop.

Use `supervisor:terminate_child/2` to terminate workers
so the supervisor does not complain on them being killed.

Change restart strategy to `brutal_kill` so the workers
are terminated as they were with `exit(Worker, kill)`.

Fix a bug in `mod_esi` that it reacts to `'EXIT'` messages
not only from the spawned ESI worker process.
---
 .../src/http_server/httpd_connection_sup.erl  |  4 +--
 lib/inets/src/http_server/httpd_manager.erl   | 33 +++++++++----------
 lib/inets/src/http_server/mod_esi.erl         | 12 +++----
 3 files changed, 24 insertions(+), 25 deletions(-)

diff --git a/lib/inets/src/http_server/httpd_connection_sup.erl b/lib/inets/src/http_server/httpd_connection_sup.erl
index f7b3bef245..9f76613e44 100644
--- a/lib/inets/src/http_server/httpd_connection_sup.erl
+++ b/lib/inets/src/http_server/httpd_connection_sup.erl
@@ -1,7 +1,7 @@
 %%
 %% %CopyrightBegin%
 %% 
-%% Copyright Ericsson AB 2008-2016. All Rights Reserved.
+%% Copyright Ericsson AB 2008-2023. All Rights Reserved.
 %% 
 %% Licensed under the Apache License, Version 2.0 (the "License");
 %% you may not use this file except in compliance with the License.
@@ -58,7 +58,7 @@ init([[Addr, Port]]) ->
     Name = undefined, % As simple_one_for_one is used.
     StartFunc = {httpd_request_handler, start_link, []},
     Restart = temporary, % E.g. should not be restarted
-    Shutdown = 4000,
+    Shutdown = brutal_kill,
     Modules = [httpd_request_handler],
     Type = worker,
 
diff --git a/lib/inets/src/http_server/httpd_manager.erl b/lib/inets/src/http_server/httpd_manager.erl
index d198bc8fbf..17332ebc5d 100644
--- a/lib/inets/src/http_server/httpd_manager.erl
+++ b/lib/inets/src/http_server/httpd_manager.erl
@@ -462,20 +462,19 @@ count_children(Sup) ->
     Children = supervisor:count_children(whereis(Sup)),
     proplists:get_value(workers, Children).
 
-shutdown_connections(Sup) ->
-    Children = [Child || {_,Child,_,_} <- supervisor:which_children(Sup)],
-    lists:foreach(fun(Pid) -> exit(Pid, kill) end,
-		  Children).
-
-wait_for_shutdown(CSup, Manager) ->	      
-    case count_children(CSup) of
-	0 ->
-	    Manager ! connections_terminated;
-	_ ->
-	    receive 
-	    after 500 ->
-		    ok
-	    end,
-	    wait_for_shutdown(CSup, Manager)
-    end.	
-
+shutdown_connections(CSup) ->
+    Children = [Child || {_,Child,_,_} <- supervisor:which_children(CSup)],
+    lists:foreach(
+      fun(Child) ->
+              _ = supervisor:terminate_child(CSup, Child)
+      end, Children).
+
+wait_for_shutdown(CSup, Manager) ->
+    Children = [Child || {_,Child,_,_} <- supervisor:which_children(CSup)],
+    Monitors = [erlang:monitor(process, Child) || Child <- Children],
+    lists:foreach(
+      fun(Mref) ->
+              receive {'DOWN', Mref, _, _, _} -> ok end
+      end, Monitors),
+    Manager ! connections_terminated,
+    ok.
diff --git a/lib/inets/src/http_server/mod_esi.erl b/lib/inets/src/http_server/mod_esi.erl
index 64af60e508..755860227d 100644
--- a/lib/inets/src/http_server/mod_esi.erl
+++ b/lib/inets/src/http_server/mod_esi.erl
@@ -1,7 +1,7 @@
 %%
 %% %CopyrightBegin%
 %%
-%% Copyright Ericsson AB 1997-2022. All Rights Reserved.
+%% Copyright Ericsson AB 1997-2023. All Rights Reserved.
 %%
 %% Licensed under the Apache License, Version 2.0 (the "License");
 %% you may not use this file except in compliance with the License.
@@ -292,7 +292,7 @@ deliver_webpage_chunk(#mod{config_db = Db} = ModData, Pid) ->
     deliver_webpage_chunk(ModData, Pid, Timeout).
 
 deliver_webpage_chunk(#mod{config_db = Db} = ModData, Pid, Timeout) ->
-    case receive_headers(Timeout) of
+    case receive_headers(Pid, Timeout) of
 	{error, Reason} ->
 	    %% Happens when webpage generator callback/3 is undefined
 	    {error, Reason}; 
@@ -329,17 +329,17 @@ deliver_webpage_chunk(#mod{config_db = Db} = ModData, Pid, Timeout) ->
 	    {proceed,[{response, {already_sent, 504, 0}} | ModData#mod.data]}
     end.
 
-receive_headers(Timeout) ->
+receive_headers(Pid, Timeout) ->
     receive
 	{esi_data, Chunk} ->
 	    httpd_esi:parse_headers(lists:flatten(Chunk));		
 	{ok, Chunk} ->
 	    httpd_esi:parse_headers(lists:flatten(Chunk));		
-	{'EXIT', Pid, erl_scheme_webpage_chunk_undefined} when is_pid(Pid) ->
+	{'EXIT', Pid, erl_scheme_webpage_chunk_undefined} ->
 	    {error, erl_scheme_webpage_chunk_undefined};
-	{'EXIT', Pid, {continue, _} = Continue} when is_pid(Pid) ->
+	{'EXIT', Pid, {continue, _} = Continue} ->
             Continue;
-        {'EXIT', Pid, Reason} when is_pid(Pid) ->
+        {'EXIT', Pid, Reason} ->
 	    exit({mod_esi_linked_process_died, Pid, Reason})
     after Timeout ->
 	    timeout
-- 
2.35.3

openSUSE Build Service is sponsored by