File 8131-Add-supervisor-which_child-2.patch of Package erlang

From a720ea9c86637166c2824d8cde2c340dca05e7d2 Mon Sep 17 00:00:00 2001
From: Maria Scott <maria-12648430@hnc-agency.org>
Date: Mon, 4 Nov 2024 11:38:57 +0100
Subject: [PATCH] Add supervisor:which_child/2

---
 lib/stdlib/src/supervisor.erl        | 56 ++++++++++++++++++++--
 lib/stdlib/test/supervisor_SUITE.erl | 72 +++++++++++++++++++++++++++-
 2 files changed, 123 insertions(+), 5 deletions(-)

diff --git a/lib/stdlib/src/supervisor.erl b/lib/stdlib/src/supervisor.erl
index 55454ef89b..64517e0454 100644
--- a/lib/stdlib/src/supervisor.erl
+++ b/lib/stdlib/src/supervisor.erl
@@ -283,9 +283,9 @@ but the map is preferred.
 -export([start_link/2, start_link/3,
 	 start_child/2, restart_child/2,
 	 delete_child/2, terminate_child/2,
-	 which_children/1, count_children/1,
-	 check_childspecs/1, check_childspecs/2,
-	 get_childspec/2]).
+	 which_children/1, which_child/2,
+	 count_children/1, check_childspecs/1,
+	 check_childspecs/2, get_childspec/2]).
 
 %% Internal exports
 -export([init/1, handle_call/3, handle_cast/2, handle_info/2,
@@ -763,6 +763,17 @@ The following information is given for each child specification/process:
 which_children(Supervisor) ->
     call(Supervisor, which_children).
 
+-spec which_child(SupRef, Id) -> Result when
+      SupRef :: sup_ref(),
+      Id :: pid() | child_id(),
+      Result :: {'ok', {Id, Child, Type, Modules}} | {'error', Error},
+      Child :: child() | 'restarting',
+      Type :: worker(),
+      Modules :: modules(),
+      Error :: 'not_found'.
+which_child(Supervisor, Id) ->
+    call(Supervisor, {which_child, Id}).
+
 -spec count_children(SupRef) -> PropListOfCounts when
       SupRef :: sup_ref(),
       PropListOfCounts :: [Count],
@@ -1091,6 +1110,37 @@ handle_call(which_children, _From, State) ->
           State#state.children),
     {reply, Resp, State};
 
+%% which_child for simple_one_for_one can only be done with pid
+handle_call({which_child, Id}, _From, State) when not is_pid(Id),
+                                                  ?is_simple(State) ->
+    {reply, {error, simple_one_for_one}, State};
+
+handle_call({which_child, Pid}, _From, State) when ?is_simple(State) ->
+    Result = case find_dynamic_child(Pid, State) of
+		 {ok, #child{pid = ?restarting(_),
+			     child_type = CT, modules = Mods}} ->
+		     {ok, {undefined, restarting, CT, Mods}};
+		 {ok, #child{pid = Pid,
+			     child_type = CT, modules = Mods}} ->
+		     {ok, {undefined, Pid, CT, Mods}};
+		 error ->
+		     {error, not_found}
+	     end,
+    {reply, Result, State};
+
+handle_call({which_child, Id}, _From, State) ->
+    Result = case find_child(Id, State) of
+		 {ok, #child{pid = ?restarting(_),
+			     child_type = CT, modules = Mods}} ->
+		     {ok, {Id, restarting, CT, Mods}};
+		 {ok, #child{pid = Pid,
+			     child_type = CT, modules = Mods}} ->
+		     {ok, {Id, Pid, CT, Mods}};
+		 error ->
+		     {error, not_found}
+	     end,
+    {reply, Result, State};
+
 handle_call(count_children, _From,  #state{dynamic_restarts = Restarts} = State)
   when ?is_simple(State) ->
     #child{child_type = CT} = get_dynamic_child(State),
diff --git a/lib/stdlib/test/supervisor_SUITE.erl b/lib/stdlib/test/supervisor_SUITE.erl
index 566c36912d..79ca0418b4 100644
--- a/lib/stdlib/test/supervisor_SUITE.erl
+++ b/lib/stdlib/test/supervisor_SUITE.erl
@@ -90,7 +90,8 @@
 	 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, already_started_outside_supervisor/1]).
+         format_log_1/1, format_log_2/1, already_started_outside_supervisor/1,
+	 which_children/1, which_children_simple_one_for_one/1]).
 
 %%-------------------------------------------------------------------------
 
@@ -119,7 +120,8 @@ 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, already_started_outside_supervisor].
+     format_log_1, format_log_2, already_started_outside_supervisor,
+     which_children, which_children_simple_one_for_one].
 
 groups() -> 
     [{sup_start, [],
@@ -3727,6 +3729,72 @@ already_started_outside_supervisor(_Config) ->
     ok = check_exit([SupPid]),
     ok.
 
+%% Test which_children/1 and which_child/2.
+which_children(Config) when is_list(Config) ->
+    {ok, SupPid} = start_link({ok, {#{}, []}}),
+
+    [] = supervisor:which_children(SupPid),
+    {error, not_found} = supervisor:which_child(SupPid, childx),
+
+    {ok, Child1} = supervisor:start_child(SupPid, #{id => child1,
+						    start => {supervisor_1, start_child, []}}),
+    [{child1, Child1, worker, [supervisor_1]}] = supervisor:which_children(SupPid),
+    {ok, {child1, Child1, worker, [supervisor_1]}} = supervisor:which_child(SupPid, child1),
+    {error, not_found} = supervisor:which_child(SupPid, childx),
+
+    {ok, Child2} = supervisor:start_child(SupPid, #{id => child2,
+						    start => {supervisor_1, start_child, []}}),
+    [{child2, Child2, worker, [supervisor_1]},
+     {child1, Child1, worker, [supervisor_1]}] = supervisor:which_children(SupPid),
+    {ok, {child1, Child1, worker, [supervisor_1]}} = supervisor:which_child(SupPid, child1),
+    {ok, {child2, Child2, worker, [supervisor_1]}} = supervisor:which_child(SupPid, child2),
+    {error, not_found} = supervisor:which_child(SupPid, childx),
+
+    ok = supervisor:terminate_child(SupPid, child1),
+    [{child2, Child2, worker, [supervisor_1]},
+     {child1, undefined, worker, [supervisor_1]}] = supervisor:which_children(SupPid),
+    {ok, {child1, undefined, worker, [supervisor_1]}} = supervisor:which_child(SupPid, child1),
+    {ok, {child2, Child2, worker, [supervisor_1]}} = supervisor:which_child(SupPid, child2),
+    {error, not_found} = supervisor:which_child(SupPid, childx),
+
+    ok = supervisor:delete_child(SupPid, child1),
+    [{child2, Child2, worker, [supervisor_1]}] = supervisor:which_children(SupPid),
+    {error, not_found} = supervisor:which_child(SupPid, child1),
+    {ok, {child2, Child2, worker, [supervisor_1]}} = supervisor:which_child(SupPid, child2),
+    {error, not_found} = supervisor:which_child(SupPid, childx),
+
+    ok.
+
+which_children_simple_one_for_one(Config) when is_list(Config) ->
+    {ok, SupPid} = start_link({ok, {#{strategy => simple_one_for_one}, [#{id => child,
+									  start => {supervisor_1, start_child, []},
+									  restart => temporary}]}}),
+
+    [] = supervisor:which_children(SupPid),
+    {error, not_found} = supervisor:which_child(SupPid, self()),
+
+    {ok, Child1} = supervisor:start_child(SupPid, []),
+    [{undefined, Child1, worker, [supervisor_1]}] = supervisor:which_children(SupPid),
+    {ok, {undefined, Child1, worker, [supervisor_1]}} = supervisor:which_child(SupPid, Child1),
+    {error, not_found} = supervisor:which_child(SupPid, self()),
+
+    {ok, Child2} = supervisor:start_child(SupPid, []),
+    [{undefined, Child1, worker, [supervisor_1]},
+     {undefined, Child2, worker, [supervisor_1]}] = supervisor:which_children(SupPid),
+    {ok, {undefined, Child1, worker, [supervisor_1]}} = supervisor:which_child(SupPid, Child1),
+    {ok, {undefined, Child2, worker, [supervisor_1]}} = supervisor:which_child(SupPid, Child2),
+    {error, not_found} = supervisor:which_child(SupPid, self()),
+
+    ok = supervisor:terminate_child(SupPid, Child1),
+    [{undefined, Child2, worker, [supervisor_1]}] = supervisor:which_children(SupPid),
+    {error, not_found} = supervisor:which_child(SupPid, Child1),
+    {ok, {undefined, Child2, worker, [supervisor_1]}} = supervisor:which_child(SupPid, Child2),
+    {error, not_found} = supervisor:which_child(SupPid, self()),
+
+    {error, simple_one_for_one} = supervisor:which_child(SupPid, not_a_pid),
+
+    ok.
+
 %%-------------------------------------------------------------------------
 terminate(Pid, Reason) when Reason =/= supervisor ->
     terminate(dummy, Pid, dummy, Reason).
-- 
2.43.0

openSUSE Build Service is sponsored by