File 0329-fix-supervisor-fix-return-value-when-process-is-alre.patch of Package erlang

From 1e04e7add376119bab0299f895970ded8d90ad3f Mon Sep 17 00:00:00 2001
From: Thales Macedo Garitezi <thalesmg@gmail.com>
Date: Tue, 28 Mar 2023 14:36:53 -0300
Subject: [PATCH 1/2] fix(supervisor): fix return value when process is already
 registered

This fixes a bug where the return type for `supervisor:start_child/2`
was not being respected.

If a supervisor tries to start a child who tries to register the same
local name that a running process has already registered, the return
value was of the form `{error, {{already_started, pid()}, child_spec()}}`
rather than `{error, {already_started, pid()}}`.
---
 lib/stdlib/src/supervisor.erl        |  2 ++
 lib/stdlib/test/supervisor_SUITE.erl | 32 +++++++++++++++++++++++++---
 2 files changed, 31 insertions(+), 3 deletions(-)

diff --git a/lib/stdlib/src/supervisor.erl b/lib/stdlib/src/supervisor.erl
index de44ce55ee..6636fbc46d 100644
--- a/lib/stdlib/src/supervisor.erl
+++ b/lib/stdlib/src/supervisor.erl
@@ -716,6 +716,8 @@ handle_start_child(Child, State) ->
 		    {{ok, Pid}, save_child(Child#child{pid = Pid}, State)};
 		{ok, Pid, Extra} ->
 		    {{ok, Pid, Extra}, save_child(Child#child{pid = Pid}, State)};
+		{error, {already_started, _Pid} = What} ->
+		    {{error, What}, State};
 		{error, What} ->
 		    {{error, {What, Child}}, State}
 	    end;
diff --git a/lib/stdlib/test/supervisor_SUITE.erl b/lib/stdlib/test/supervisor_SUITE.erl
index a9cf48e997..9532aaf118 100644
--- a/lib/stdlib/test/supervisor_SUITE.erl
+++ b/lib/stdlib/test/supervisor_SUITE.erl
@@ -30,7 +30,7 @@
 
 %% Internal export
 -export([init/1, terminate_all_children/1,
-         middle9212/0, gen_server9212/0, handle_info/2]).
+         middle9212/0, gen_server9212/0, handle_info/2, start_registered_name/1]).
 
 %% API tests
 -export([ sup_start_normal/1, sup_start_ignore_init/1, 
@@ -90,7 +90,7 @@
 	 hanging_restart_loop_simple/1, code_change/1, code_change_map/1,
 	 code_change_simple/1, code_change_simple_map/1,
          order_of_children/1, scale_start_stop_many_children/1,
-         format_log_1/1, format_log_2/1]).
+         format_log_1/1, format_log_2/1, already_started_outside_supervisor/1]).
 
 %%-------------------------------------------------------------------------
 
@@ -119,7 +119,7 @@ all() ->
      hanging_restart_loop_rest_for_one, hanging_restart_loop_simple,
      code_change, code_change_map, code_change_simple, code_change_simple_map,
      order_of_children, scale_start_stop_many_children,
-     format_log_1, format_log_2].
+     format_log_1, format_log_2, already_started_outside_supervisor].
 
 groups() -> 
     [{sup_start, [],
@@ -3677,6 +3677,29 @@ significant_upgrade_child(_Config) ->
 
     ok.
 
+%% Test trying to start a child that uses an already registered name.
+already_started_outside_supervisor(_Config) ->
+    process_flag(trap_exit, true),
+    {ok, SupPid} = start_link({ok, {#{}, []}}),
+    RegName = registered_name,
+    Child = #{id => child,
+	      start => {?MODULE, start_registered_name, [RegName]},
+	      restart => transient,
+	      significant => false},
+    %% We start another process and register the name.
+    Pid = spawn_link(fun() ->
+                             true = register(RegName, self()),
+                             receive
+                                 die -> ok
+                             end
+                     end),
+    {error, {already_started, P}} = supervisor:start_child(SupPid, Child),
+    Pid = P,
+    terminate(SupPid, shutdown),
+    Pid ! die,
+    ok = check_exit([SupPid]),
+    ok.
+
 %%-------------------------------------------------------------------------
 terminate(Pid, Reason) when Reason =/= supervisor ->
     terminate(dummy, Pid, dummy, Reason).
@@ -3769,3 +3792,6 @@ check_no_exit(Timeout) ->
 	{'EXIT', Pid, Else} ->
 	    ct:fail({bad_exit_reason, Else})
     end.
+
+start_registered_name(Name) ->
+    supervisor:start_link({local, Name}, ?MODULE, []).
-- 
2.35.3

openSUSE Build Service is sponsored by