File 3511-Allow-0-for-child-shutdown-in-supervisor.patch of Package erlang

From 8287d0aeee101ba89de54431f62a90714b09c251 Mon Sep 17 00:00:00 2001
From: Maria-12648430 <maria-12648430@hnc-agency.org>
Date: Mon, 19 Apr 2021 14:20:04 +0200
Subject: [PATCH] Allow 0 for child shutdown in supervisor

---
 lib/stdlib/src/supervisor.erl        |  2 +-
 lib/stdlib/test/supervisor_SUITE.erl | 32 +++++++++++++++-------------
 2 files changed, 18 insertions(+), 16 deletions(-)

diff --git a/lib/stdlib/src/supervisor.erl b/lib/stdlib/src/supervisor.erl
index 1ee7f1bd35..4c82830884 100644
--- a/lib/stdlib/src/supervisor.erl
+++ b/lib/stdlib/src/supervisor.erl
@@ -1455,7 +1455,7 @@ validSignificant(Significant, _RestartType, _AutoShutdown) ->
 validRestartType(RestartType) -> throw({invalid_restart_type, RestartType}).
 
 validShutdown(Shutdown)
-  when is_integer(Shutdown), Shutdown > 0 -> true;
+  when is_integer(Shutdown), Shutdown >= 0 -> true;
 validShutdown(infinity)             -> true;
 validShutdown(brutal_kill)          -> true;
 validShutdown(Shutdown)             -> throw({invalid_shutdown, Shutdown}).
diff --git a/lib/stdlib/test/supervisor_SUITE.erl b/lib/stdlib/test/supervisor_SUITE.erl
index 65f5c054e1..3830e25507 100644
--- a/lib/stdlib/test/supervisor_SUITE.erl
+++ b/lib/stdlib/test/supervisor_SUITE.erl
@@ -702,15 +702,6 @@ child_specs(Config) when is_list(Config) ->
     B5 = {child, {m,f,[a]}, permanent, 1000, worker, dy},
     B6 = {child, {m,f,[a]}, permanent, 1000, worker, [1,2,3]},
 
-    %% Correct child specs!
-    %% <Modules> (last parameter in a child spec) can be [] as we do 
-    %% not test code upgrade here.  
-    C1 = {child, {m,f,[a]}, permanent, infinity, supervisor, []},
-    C2 = {child, {m,f,[a]}, permanent, 1000, supervisor, []},
-    C3 = {child, {m,f,[a]}, temporary, 1000, worker, dynamic},
-    C4 = {child, {m,f,[a]}, transient, 1000, worker, [m]},
-    C5 = {child, {m,f,[a]}, permanent, infinity, worker, [m]},
-
     {error, {invalid_mfa,mfa}} = supervisor:start_child(sup_test, B1),
     {error, {invalid_restart_type, prmanent}} =
 	supervisor:start_child(sup_test, B2),
@@ -732,11 +723,22 @@ child_specs(Config) when is_list(Config) ->
     {error, {invalid_module, 1}} =
 	supervisor:check_childspecs([B6]),
 
-    ok = supervisor:check_childspecs([C1]),
-    ok = supervisor:check_childspecs([C2]),
-    ok = supervisor:check_childspecs([C3]),
-    ok = supervisor:check_childspecs([C4]),
-    ok = supervisor:check_childspecs([C5]),
+    lists:foreach(
+	fun (ChildSpec) ->
+	    ok = supervisor:check_childspecs([ChildSpec])
+	end,
+	[
+	    {child, {m, f, [a]}, Restart, Shutdown, Type, Modules}
+	    ||
+		Restart <- [permanent, transient, temporary],
+		Shutdown <- [0, 1000, infinity, brutal_kill],
+		Type <- [supervisor, worker],
+		Modules <- [dynamic, [], [m], [m1, m2]]
+	]
+    ),
+
+    C1 = {child, {m,f,[a]}, permanent, infinity, supervisor, []},
+    C2 = {child, {m,f,[a]}, permanent, 1000, supervisor, []},
 
     {error,{duplicate_child_name,child}} = supervisor:check_childspecs([C1,C2]),
 
-- 
2.26.2

openSUSE Build Service is sponsored by