File 4941-ssh-log-not-pal-in-ssh-tests.patch of Package erlang

From 632c53b1c6f36b005da743802918d7559b58ae28 Mon Sep 17 00:00:00 2001
From: Jakub Witczak <kuba@erlang.org>
Date: Wed, 27 Sep 2023 09:33:34 +0200
Subject: [PATCH] ssh: log not pal in ssh tests

---
 lib/common_test/src/ct_property_test.erl |  2 +-
 lib/ssh/test/ssh_options_SUITE.erl       |  2 +-
 lib/ssh/test/ssh_protocol_SUITE.erl      | 18 +++++++++---------
 lib/ssh/test/ssh_sup_SUITE.erl           | 10 +++++-----
 4 files changed, 16 insertions(+), 16 deletions(-)

diff --git a/lib/common_test/src/ct_property_test.erl b/lib/common_test/src/ct_property_test.erl
index dce4edfd9d..4d9c2a0dba 100644
--- a/lib/common_test/src/ct_property_test.erl
+++ b/lib/common_test/src/ct_property_test.erl
@@ -86,7 +86,7 @@ init_tool(Config) ->
 init_tool_extensions(proper) ->
     ProperExtDir = code:lib_dir(common_test, proper_ext),
     true = code:add_patha(ProperExtDir),
-    ct:pal("Added ~ts to code path~n", [ProperExtDir]),
+    ct:log("Added ~ts to code path~n", [ProperExtDir]),
     ok;
 init_tool_extensions(_) ->
     ok.
diff --git a/lib/ssh/test/ssh_options_SUITE.erl b/lib/ssh/test/ssh_options_SUITE.erl
index c02b20d6a2..3def2597b7 100644
--- a/lib/ssh/test/ssh_options_SUITE.erl
+++ b/lib/ssh/test/ssh_options_SUITE.erl
@@ -1514,7 +1514,7 @@ max_sessions(Config, ParallelLogin, Connect0) when is_function(Connect0,2) ->
 	    [_|_] = Connections,
 
 	    %% N w try one more than allowed:
-	    ct:pal("Info Report expected here (if not disabled) ...",[]),
+	    ct:log("Info Report expected here (if not disabled) ...",[]),
 	    try Connect(Host,Port)
 	    of
 		_ConnectionRef1 ->
diff --git a/lib/ssh/test/ssh_protocol_SUITE.erl b/lib/ssh/test/ssh_protocol_SUITE.erl
index 666ac76f63..b0a40b80e7 100644
--- a/lib/ssh/test/ssh_protocol_SUITE.erl
+++ b/lib/ssh/test/ssh_protocol_SUITE.erl
@@ -929,11 +929,11 @@ client_close_after_hello(Config0) ->
             {send, hello}
            ]) || _ <- lists:seq(1,MaxSessions+100)],
 
-    ct:pal("=== Tried to start ~p sessions.", [length(Cs)]),
+    ct:log("=== Tried to start ~p sessions.", [length(Cs)]),
 
-    ssh_info:print(fun ct:pal/2),
+    ssh_info:print(fun ct:log/2),
     {Parents, Conns, Handshakers} = find_handshake_parent(server_port(Config)),
-    ct:pal("Found (Port=~p):~n"
+    ct:log("Found (Port=~p):~n"
            "  Connections  (length ~p): ~p~n"
            "  Handshakers  (length ~p): ~p~n"
            "  with parents (length ~p): ~p",
@@ -944,12 +944,12 @@ client_close_after_hello(Config0) ->
     if
         length(Handshakers)>0 ->
             lists:foreach(fun(P) -> exit(P,some_reason) end, Parents),
-            ct:pal("After sending exits; now going to sleep", []),
+            ct:log("After sending exits; now going to sleep", []),
             timer:sleep((SleepSec+15)*1000),
-            ct:pal("After sleeping", []),
-            ssh_info:print(fun ct:pal/2),
+            ct:log("After sleeping", []),
+            ssh_info:print(fun ct:log/2),
             {Parents2, Conns2, Handshakers2} = find_handshake_parent(server_port(Config)),
-            ct:pal("Found (Port=~p):~n"
+            ct:log("Found (Port=~p):~n"
                    "  Connections  (length ~p): ~p~n"
                    "  Handshakers  (length ~p): ~p~n"
                    "  with parents (length ~p): ~p",
@@ -961,10 +961,10 @@ client_close_after_hello(Config0) ->
                 Handshakers2==[] andalso Conns2==Conns0 ->
                     ok;
                 Handshakers2=/=[] ->
-                    ct:pal("Handshakers still alive: ~p", [Handshakers2]),
+                    ct:log("Handshakers still alive: ~p", [Handshakers2]),
                     {fail, handshakers_alive};
                 true ->
-                    ct:pal("Connections before: ~p~n"
+                    ct:log("Connections before: ~p~n"
                            "Connections after: ~p", [Conns0,Conns2]),
                     {fail, connections_bad}
             end;
diff --git a/lib/ssh/test/ssh_sup_SUITE.erl b/lib/ssh/test/ssh_sup_SUITE.erl
index 245e07ccd7..6dc592b942 100644
--- a/lib/ssh/test/ssh_sup_SUITE.erl
+++ b/lib/ssh/test/ssh_sup_SUITE.erl
@@ -229,7 +229,7 @@ killed_acceptor_restarts(Config) ->
     ct:log("~s",[lists:flatten(ssh_info:string())]),
 
     %% Make acceptor restart:
-    ct:pal("Expect a SUPERVISOR REPORT with offender {pid,~p}....~n", [AccPid]),
+    ct:log("Expect a SUPERVISOR REPORT with offender {pid,~p}....~n", [AccPid]),
     exit(AccPid, kill),
     ?wait_match(undefined, process_info(AccPid)),
 
@@ -239,7 +239,7 @@ killed_acceptor_restarts(Config) ->
                 AccPid1,
                 500, 30),
 
-    ct:pal("... now there should not be any SUPERVISOR REPORT.~n", []),
+    ct:log("... now there should not be any SUPERVISOR REPORT.~n", []),
 
     true = (AccPid1 =/= AccPid2),
 
@@ -454,7 +454,7 @@ check_sshc_system_tree(SysSup, Connection, _LocalIP, _LocalPort, _Config) ->
                 supervisor:which_children(ChSup),
                 [ChPid1,ChPid2]),
 
-    ct:pal("Expect a SUPERVISOR REPORT with offender {pid,~p}....~n", [ChPid1]),
+    ct:log("Expect a SUPERVISOR REPORT with offender {pid,~p}....~n", [ChPid1]),
     exit(ChPid1, kill),
     ?wait_match([{_,FwdAccSup, supervisor,[ssh_tcpip_forward_acceptor_sup]},
                  {_,ChSup,supervisor, [ssh_channel_sup]},
@@ -468,7 +468,7 @@ check_sshc_system_tree(SysSup, Connection, _LocalIP, _LocalPort, _Config) ->
                 supervisor:which_children(ChSup),
                 [ChPid2]),
 
-    ct:pal("Expect a SUPERVISOR REPORT with offender {pid,~p}....~n", [ChPid2]),
+    ct:log("Expect a SUPERVISOR REPORT with offender {pid,~p}....~n", [ChPid2]),
     exit(ChPid2, kill),
     ?wait_match([{_,FwdAccSup, supervisor,[ssh_tcpip_forward_acceptor_sup]},
                  {_,ChSup,supervisor, [ssh_channel_sup]},
@@ -479,7 +479,7 @@ check_sshc_system_tree(SysSup, Connection, _LocalIP, _LocalPort, _Config) ->
 
     ?wait_match([], supervisor:which_children(ChSup)),
 
-    ct:pal("... now there should not be any SUPERVISOR REPORT.~n", []).
+    ct:log("... now there should not be any SUPERVISOR REPORT.~n", []).
 
 
 
-- 
2.35.3

openSUSE Build Service is sponsored by