File 2475-ssh-fix-formatting.patch of Package erlang

From c24ff479c448f8398ade2c7fd96305857a121877 Mon Sep 17 00:00:00 2001
From: Jakub Witczak <kuba@erlang.org>
Date: Tue, 22 Apr 2025 13:02:43 +0200
Subject: [PATCH 5/5] ssh: fix formatting

---
 lib/ssh/src/ssh_connection_handler.erl | 38 ++++++-------
 lib/ssh/test/ssh_connection_SUITE.erl  | 77 +++++++++++++-------------
 lib/ssh/test/ssh_echo_server.erl       |  2 +-
 lib/ssh/test/ssh_protocol_SUITE.erl    | 21 +------
 4 files changed, 62 insertions(+), 76 deletions(-)

diff --git a/lib/ssh/src/ssh_connection_handler.erl b/lib/ssh/src/ssh_connection_handler.erl
index f790559b97..8271e594f6 100644
--- a/lib/ssh/src/ssh_connection_handler.erl
+++ b/lib/ssh/src/ssh_connection_handler.erl
@@ -1264,29 +1264,29 @@ handle_event(info, {'DOWN', _Ref, process, ChannelPid, _Reason}, _, D) ->
     %% Here we first collect the list of channel id's  handled by the process
     %% Do NOT remove them from the cache - they are not closed yet!
     Channels = ssh_client_channel:cache_foldl(
-      fun(#channel{user=U} = Channel, Acc) when U == ChannelPid ->
-              [Channel | Acc];
-         (_,Acc) ->
-              Acc
-      end, [], Cache),
+                 fun(#channel{user=U} = Channel, Acc) when U == ChannelPid ->
+                         [Channel | Acc];
+                    (_,Acc) ->
+                         Acc
+                 end, [], Cache),
     %% Then for each channel where 'channel-close' has not been sent yet
     %% we send 'channel-close' and(!) update the cache so that we remember
     %% what we've done.
     %% Also set user as 'undefined' as there is no such process anyway
     {D2, NewTimers} = lists:foldl(
-      fun(#channel{remote_id = Id, sent_close = false} = Channel,
-          {D0, Timers}) when Id /= undefined ->
-          D1 = send_msg(ssh_connection:channel_close_msg(Id), D0),
-          ssh_client_channel:cache_update(cache(D1),
-                                          Channel#channel{sent_close = true,
-                                                          user = undefined}),
-          ChannelTimer = channel_close_timer(D1, Id),
-          {D1, [ChannelTimer | Timers]};
-         (Channel, {D0, _} = Acc) ->
-          ssh_client_channel:cache_update(cache(D0),
-                                          Channel#channel{user = undefined}),
-          Acc
-      end, {D, []}, Channels),
+                        fun(#channel{remote_id = Id, sent_close = false} = Channel,
+                            {D0, Timers}) when Id /= undefined ->
+                                D1 = send_msg(ssh_connection:channel_close_msg(Id), D0),
+                                ssh_client_channel:cache_update(cache(D1),
+                                                                Channel#channel{sent_close = true,
+                                                                                user = undefined}),
+                                ChannelTimer = channel_close_timer(D1, Id),
+                                {D1, [ChannelTimer | Timers]};
+                           (Channel, {D0, _} = Acc) ->
+                                ssh_client_channel:cache_update(cache(D0),
+                                                                Channel#channel{user = undefined}),
+                                Acc
+                        end, {D, []}, Channels),
     {keep_state, D2, [cond_set_idle_timer(D2) | NewTimers]};
 
 handle_event({timeout,idle_time}, _Data,  _StateName, D) ->
@@ -2084,7 +2084,7 @@ cond_set_idle_timer(D) ->
 
 channel_close_timer(D, ChannelId) ->
     {{timeout, {channel_close, ChannelId}},
-               ?GET_OPT(channel_close_timeout, (D#data.ssh_params)#ssh.opts), none}.
+     ?GET_OPT(channel_close_timeout, (D#data.ssh_params)#ssh.opts), none}.
 
 %%%----------------------------------------------------------------
 start_channel_request_timer(_,_, infinity) ->
diff --git a/lib/ssh/test/ssh_connection_SUITE.erl b/lib/ssh/test/ssh_connection_SUITE.erl
index 9c9c71e7d1..2da2084e22 100644
--- a/lib/ssh/test/ssh_connection_SUITE.erl
+++ b/lib/ssh/test/ssh_connection_SUITE.erl
@@ -1176,7 +1176,7 @@ simple_eval(Inp) -> {simple_eval,Inp}.
 
 do_start_shell_exec_fun(Fun, Command, Expect, ExpectType, Config) ->
     DefaultReceiveFun =
-        fun(ConnectionRef, ChannelId, Expect, ExpectType) ->
+        fun(ConnectionRef, ChannelId, _Expect, _ExpectType) ->
                 receive
                     {ssh_cm, ConnectionRef, {data, ChannelId, ExpectType, Expect}} ->
                         ok
@@ -1852,44 +1852,45 @@ handler_down_before_open(Config) ->
 						      {user_dir, UserDir}]),
     ct:log("~p:~p connected", [?MODULE,?LINE]),
 
-    ExecChannelPid = spawn(
-        fun() ->
-            {ok, ChannelId0} = ssh_connection:session_channel(ConnectionRef, infinity),
-
-            %% This is to get peer's connection handler PID ({conn_peer ...} below) and suspend it
-            {ok, ChannelId1} = ssh_connection:session_channel(ConnectionRef, infinity),
-            ssh_connection:subsystem(ConnectionRef, ChannelId1, "echo_n", infinity),
-            ssh_connection:close(ConnectionRef, ChannelId1),
-            receive
-                {ssh_cm, ConnectionRef, {closed, 1}} -> ok
-            end,
-
-            Parent ! {self(), channelId, ChannelId0},
-            Result = receive
-                cmd ->
-                    ct:log("~p:~p Channel ~p executing", [?MODULE, ?LINE, ChannelId0]),
-                    success = ssh_connection:exec(ConnectionRef, ChannelId0, "testing", infinity),
-                    Expect = <<"echo testing\n">>,
-                    ExpSz = size(Expect),
-                    receive
-                        {ssh_cm, ConnectionRef, {data, ChannelId0, 0,
-                                                 <<Expect:ExpSz/binary, _/binary>>}} = R ->
-                            ct:log("~p:~p Got expected ~p",[?MODULE,?LINE, R]),
-                            ok;
-                        Other ->
-                            ct:log("~p:~p Got unexpected ~p~nExpect: ~p~n",
-                                   [?MODULE,?LINE, Other, {ssh_cm, ConnectionRef,
-                                                          {data, ChannelId0, 0, Expect}}]),
-                            {fail, "Unexpected data"}
-                    after 5000 ->
-                            {fail, "Exec Timeout"}
-                    end;
-                stop -> {fail, "Stopped"}
-            end,
-            Parent ! {self(), Result}
-      end),
+    ExecChannelPid =
+        spawn(
+          fun() ->
+                  {ok, ChannelId0} = ssh_connection:session_channel(ConnectionRef, infinity),
+
+                  %% This is to get peer's connection handler PID ({conn_peer ...} below) and suspend it
+                  {ok, ChannelId1} = ssh_connection:session_channel(ConnectionRef, infinity),
+                  ssh_connection:subsystem(ConnectionRef, ChannelId1, "echo_n", infinity),
+                  ssh_connection:close(ConnectionRef, ChannelId1),
+                  receive
+                      {ssh_cm, ConnectionRef, {closed, 1}} -> ok
+                  end,
+
+                  Parent ! {self(), channelId, ChannelId0},
+                  Result = receive
+                               cmd ->
+                                   ct:log("~p:~p Channel ~p executing", [?MODULE, ?LINE, ChannelId0]),
+                                   success = ssh_connection:exec(ConnectionRef, ChannelId0, "testing", infinity),
+                                   Expect = <<"echo testing\n">>,
+                                   ExpSz = size(Expect),
+                                   receive
+                                       {ssh_cm, ConnectionRef, {data, ChannelId0, 0,
+                                                                <<Expect:ExpSz/binary, _/binary>>}} = R ->
+                                           ct:log("~p:~p Got expected ~p",[?MODULE,?LINE, R]),
+                                           ok;
+                                       Other ->
+                                           ct:log("~p:~p Got unexpected ~p~nExpect: ~p~n",
+                                                  [?MODULE,?LINE, Other, {ssh_cm, ConnectionRef,
+                                                                          {data, ChannelId0, 0, Expect}}]),
+                                           {fail, "Unexpected data"}
+                                   after 5000 ->
+                                           {fail, "Exec Timeout"}
+                                   end;
+                               stop -> {fail, "Stopped"}
+                           end,
+                  Parent ! {self(), Result}
+          end),
     try
-        TestResult = receive
+        receive
             {ExecChannelPid, channelId, ExId} ->
                 ct:log("~p:~p Channel that should stay: ~p pid ~p",
                        [?MODULE, ?LINE, ExId, ExecChannelPid]),
diff --git a/lib/ssh/test/ssh_echo_server.erl b/lib/ssh/test/ssh_echo_server.erl
index bbfd64c16a..c0e69c5c32 100644
--- a/lib/ssh/test/ssh_echo_server.erl
+++ b/lib/ssh/test/ssh_echo_server.erl
@@ -54,7 +54,7 @@ handle_msg({ssh_channel_up, ChannelId, ConnectionManager}, State) ->
     Pid = State#state.parent,
     if Pid /= undefined ->
             Pid ! {conn_peer, ConnectionManager};
-        true -> ok
+       true -> ok
     end,
     {ok, State#state{id = ChannelId,
 		     cm = ConnectionManager}}.
diff --git a/lib/ssh/test/ssh_protocol_SUITE.erl b/lib/ssh/test/ssh_protocol_SUITE.erl
index b08527d9b2..489384ca36 100644
--- a/lib/ssh/test/ssh_protocol_SUITE.erl
+++ b/lib/ssh/test/ssh_protocol_SUITE.erl
@@ -174,8 +174,7 @@ groups() ->
                                  modify_rm,
                                  modify_combo
                                 ]},
-     {client_close_early, [], [client_close_after_hello
-                               ]},
+     {client_close_early, [], [client_close_after_hello]},
      {channel_close, [], [channel_close_timeout]}
     ].
 
@@ -1514,11 +1513,9 @@ connect_and_kex(Config, InitialState) ->
 
 channel_close_timeout(Config) ->
     {User,_Pwd} = server_user_password(Config),
-
     %% Create a listening socket as server socket:
     {ok,InitialState} = ssh_trpt_test_lib:exec(listen),
     HostPort = ssh_trpt_test_lib:server_host_port(InitialState),
-
     %% Start a process handling one connection on the server side:
     spawn_link(
       fun() ->
@@ -1530,27 +1527,20 @@ channel_close_timeout(Config) ->
                                {idle_time, 50000}]},
 		     receive_hello,
 		     {send, hello},
-
 		     {send, ssh_msg_kexinit},
 		     {match, #ssh_msg_kexinit{_='_'}, receive_msg},
-
 		     {match, #ssh_msg_kexdh_init{_='_'}, receive_msg},
 		     {send, ssh_msg_kexdh_reply},
-
 		     {send, #ssh_msg_newkeys{}},
 		     {match,  #ssh_msg_newkeys{_='_'}, receive_msg},
-
 		     {match, #ssh_msg_service_request{name="ssh-userauth"}, receive_msg},
 		     {send, #ssh_msg_service_accept{name="ssh-userauth"}},
-
 		     {match, #ssh_msg_userauth_request{service="ssh-connection",
 						       method="none",
 						       user=User,
 						       _='_'}, receive_msg},
-
 		     {send, #ssh_msg_userauth_failure{authentications = "password",
 						      partial_success = false}},
-
 		     {match, #ssh_msg_userauth_request{service="ssh-connection",
 						       method="password",
 						       user=User,
@@ -1570,15 +1560,12 @@ channel_close_timeout(Config) ->
 		     {send, #ssh_msg_channel_open_confirmation{recipient_channel= 1,
                                                                sender_channel = 1,
                                                                initial_window_size = 64*1024,
-                                                               maximum_packet_size = 32*1024
-                                                               }},
+                                                               maximum_packet_size = 32*1024}},
                      {match, #ssh_msg_channel_close{recipient_channel = 0}, receive_msg},
                      {match, disconnect(), receive_msg},
-		     print_state
-		    ],
+		     print_state],
 		    InitialState)
       end),
-
     %% connect to it with a regular Erlang SSH client:
     ChannelCloseTimeout = 3000,
     {ok, ConnRef} = std_connect(HostPort, Config,
@@ -1602,8 +1589,6 @@ channel_close_timeout(Config) ->
         1 = length(Channels),
         ssh:close(ConnRef)
     end.
-
-
 %%%----------------------------------------------------------------
 
 %%% For matching peer disconnection
-- 
2.43.0

openSUSE Build Service is sponsored by