File 1182-ssh-remove-adjust_window-call-from-ssh_connection.patch of Package erlang

From 08d43d659812857184878202955fad4f2de6c6ed Mon Sep 17 00:00:00 2001
From: Jakub Witczak <kuba@erlang.org>
Date: Thu, 16 Jan 2025 09:11:34 +0100
Subject: [PATCH] ssh: remove adjust_window call from ssh_connection

---
 lib/ssh/src/ssh_connection.erl        |   1 -
 lib/ssh/test/ssh_connection_SUITE.erl |  57 ++++++++-----
 lib/ssh/test/ssh_sftp_SUITE.erl       | 111 ++++++++++++++++++--------
 3 files changed, 115 insertions(+), 54 deletions(-)

diff --git a/lib/ssh/src/ssh_connection.erl b/lib/ssh/src/ssh_connection.erl
index f0de9db222..18a9a68c3d 100644
--- a/lib/ssh/src/ssh_connection.erl
+++ b/lib/ssh/src/ssh_connection.erl
@@ -1529,7 +1529,6 @@ channel_data_reply_msg(ChannelId, Connection, DataType, Data) ->
 	    WantedSize = Size - byte_size(Data),
 	    ssh_client_channel:cache_update(Connection#connection.channel_cache, 
                                      Channel#channel{recv_window_size = WantedSize}),
-            adjust_window(self(), ChannelId, byte_size(Data)),
             reply_msg(Channel, Connection, {data, ChannelId, DataType, Data});
 	undefined ->
 	    {[], Connection}
diff --git a/lib/ssh/test/ssh_connection_SUITE.erl b/lib/ssh/test/ssh_connection_SUITE.erl
index b2598a46b6..11f2d9dcf1 100644
--- a/lib/ssh/test/ssh_connection_SUITE.erl
+++ b/lib/ssh/test/ssh_connection_SUITE.erl
@@ -503,6 +503,9 @@ big_cat(Config) when is_list(Config) ->
     %% build 10MB binary
     Data = << <<X:32>> || X <- lists:seq(1,2500000)>>,
 
+    %% pre-adjust receive window so the other end doesn't block
+    ssh_connection:adjust_window(ConnectionRef, ChannelId0, size(Data)),
+
     ct:log("sending ~p byte binary~n",[size(Data)]),
     ok = ssh_connection:send(ConnectionRef, ChannelId0, Data, 10000),
     ok = ssh_connection:send_eof(ConnectionRef, ChannelId0),
@@ -640,6 +643,12 @@ ptty_alloc_pixel(Config) when is_list(Config) ->
     ssh:close(ConnectionRef).
 
 %%--------------------------------------------------------------------
+%%- small_interrupted_send is interrupted by ssh_echo_server which is
+%%  done with transferring data towards client and terminates the
+%%  channel (this results with {error, closed} return value from
+%%  ssh_connection:send on the client side)
+%%- interrupted_send is interrupted when ssh_echo_server ran
+%%  out of ssh data window and closed channel
 small_interrupted_send(Config) ->
     K = 1024,
     SendSize = 10 * K * K,
@@ -678,7 +687,7 @@ do_interrupted_send(Config, SendSize, EchoSize, SenderResult) ->
 		  fun() ->
 			  ct:log("~p:~p open channel",[?MODULE,?LINE]),
 			  {ok, ChannelId} = ssh_connection:session_channel(ConnectionRef, infinity),
-			  ct:log("~p:~p start subsystem", [?MODULE,?LINE]),
+			  ct:log("~p:~p start ssh subsystem", [?MODULE,?LINE]),
 			  case ssh_connection:subsystem(ConnectionRef, ChannelId, "echo_n", infinity) of
 			      success ->
 				  Parent ! {self(), channelId, ChannelId},
@@ -711,6 +720,7 @@ do_interrupted_send(Config, SendSize, EchoSize, SenderResult) ->
 	    SenderPid = spawn(fun() ->
 				      Parent ! {self(),  ssh_connection:send(ConnectionRef, ChannelId, Data, 30000)}
 			      end),
+            ct:log("SenderPid = ~p", [SenderPid]),
 	    receive
 	    	{ResultPid, result, {fail, Fail}} ->
 		    ct:log("~p:~p Listener failed: ~p", [?MODULE,?LINE,Fail]),
@@ -729,7 +739,7 @@ do_interrupted_send(Config, SendSize, EchoSize, SenderResult) ->
 			    ct:log("~p:~p Not expected send result: ~p",[?MODULE,?LINE,Msg]),
 			    {fail, "Not expected msg"}
 		    end;
-		{SenderPid, SenderResult} ->
+		{SenderPid, {error, closed}} ->
 		    ct:log("~p:~p ~p - That's what we expect, "
                            "but client channel handler has not reported yet",
                            [?MODULE,?LINE, SenderResult]),
@@ -1837,26 +1847,35 @@ do_simple_exec(ConnectionRef, N) ->
         _ ->
             receive_bytes(ConnectionRef, ChannelId0, N * byte_size(ExpectedBin), 0)
     end,
-
     %% receive close messages
+    CloseMessages =
+        [{ssh_cm, ConnectionRef, {eof, ChannelId0}},
+         {ssh_cm, ConnectionRef, {closed, ChannelId0}}],
+    Timeout = 10000,
+    [receive
+         M ->
+             ct:log("Received M = ~w", [M]),
+             ok
+     after
+         Timeout ->
+             ct:log("M = ~w not found !", [M]),
+             ct:log("Messages in queue =~n~p", [process_info(self(), messages)]),
+             ct:fail("timeout ~p:~p",[?MODULE,?LINE])
+     end || M <- CloseMessages],
     receive
-	{ssh_cm, ConnectionRef, {eof, ChannelId0}} ->
-	    ok
-    after
-	10000 -> ct:fail("timeout ~p:~p",[?MODULE,?LINE])
-    end,
-    receive
-	{ssh_cm, ConnectionRef, {exit_status, ChannelId0, 0}} ->
-	    ok
+        %% 141 is exit status of `yes testing | head -n 1` on tcsh
+        %% other shells return 0
+        ExitMsg = {ssh_cm, ConnectionRef, {exit_status, ChannelId0, ExitStatus}}
+          when ExitStatus == 0; ExitStatus == 141 ->
+            ct:log("Received M = ~w", [ExitMsg]),
+            ok
     after
-	10000 -> ct:fail("timeout ~p:~p",[?MODULE,?LINE])
+        Timeout ->
+            ct:log("Acceptable exit status not received"),
+            ct:log("Messages in queue =~n~p", [process_info(self(), messages)]),
+            ct:fail("timeout ~p:~p",[?MODULE,?LINE])
     end,
-    receive
-	{ssh_cm, ConnectionRef,{closed, ChannelId0}} ->
-	    ok
-    after
-	10000 -> ct:fail("timeout ~p:~p",[?MODULE,?LINE])
-    end.
+    ok.
 
 
 %%--------------------------------------------------------------------
@@ -1991,6 +2010,7 @@ collect_data(ConnectionRef, ChannelId, EchoSize, Acc, Sum) ->
 	{ssh_cm, ConnectionRef, {data, ChannelId, 0, Data}} when is_binary(Data) ->
 	    ct:log("~p:~p collect_data: received ~p bytes. total ~p bytes,  want ~p more",
 		   [?MODULE,?LINE,size(Data),Sum+size(Data),EchoSize-Sum]),
+            ssh_connection:adjust_window(ConnectionRef, ChannelId, size(Data)),
 	    collect_data(ConnectionRef, ChannelId, EchoSize, [Data | Acc], Sum+size(Data));
 	{ssh_cm, ConnectionRef, Msg={eof, ChannelId}} ->
 	    collect_data_report_end(Acc, Msg, EchoSize);
@@ -2054,6 +2074,7 @@ receive_bytes(ConnectionRef, ChannelId0, Budget, AccSize) when Budget > 0 ->
                 "~p bytes Received/Total = ~p/~p bytes",
             Args = [Budget, byte_size(D), AccSize + byte_size(D)],
             ct:log(Fmt, Args),
+            ssh_connection:adjust_window(ConnectionRef, ChannelId0, size(D)),
             receive_bytes(ConnectionRef, ChannelId0,
                           Budget - byte_size(D), AccSize + byte_size(D))
     after
diff --git a/lib/ssh/test/ssh_sftp_SUITE.erl b/lib/ssh/test/ssh_sftp_SUITE.erl
index 7fbcaf87e1..e1b25bc3c1 100644
--- a/lib/ssh/test/ssh_sftp_SUITE.erl
+++ b/lib/ssh/test/ssh_sftp_SUITE.erl
@@ -55,6 +55,7 @@
          pos_read/1,
          pos_write/1,
          position/1,
+         read_6GB/1,
          read_crypto_tar/1,
          read_dir/1,
          read_file/1,
@@ -82,6 +83,7 @@
 -include_lib("kernel/include/file.hrl").
 -include("ssh_test_lib.hrl").
 -include_lib("stdlib/include/assert.hrl").
+
 %% Default timetrap timeout
 -define(default_timeout, test_server:minutes(1)).
 
@@ -120,6 +122,7 @@ groups() ->
 
      {unicode, [], [{group,erlang_server},
 		    {group,openssh_server},
+                    read_6GB,
 		    sftp_nonexistent_subsystem
                    ]},
 
@@ -229,24 +232,7 @@ init_per_group(erlang_server, Config) ->
     [{peer, {fmt_host(HostX),PortX}}, {group, erlang_server}, {sftpd, Sftpd} | Config];
 
 init_per_group(openssh_server, Config) ->
-    ct:comment("Begin ~p",[grps(Config)]),
-    Host = ssh_test_lib:hostname(),
-    case (catch ssh_sftp:start_channel(Host,
-				       [{user_interaction, false},
-					{silently_accept_hosts, true},
-                                        {save_accepted_host, false}
-                                       ])) of
-	{ok, _ChannelPid, Connection} ->
-	    [{peer, {_HostName,{IPx,Portx}}}] = ssh:connection_info(Connection,[peer]),
-	    ssh:close(Connection),
-	    [{w2l, fun w2l/1},
-             {peer, {fmt_host(IPx),Portx}}, {group, openssh_server} | Config];
-	{error,"Key exchange failed"} ->
-	    {skip, "openssh server doesn't support the tested kex algorithm"};
-	Other ->
-            ct:log("No openssh server. Cause:~n~p~n",[Other]),
-	    {skip, "No openssh daemon (see log in testcase)"} 
-    end;
+    verify_openssh(Config);
 
 init_per_group(remote_tar, Config) ->
     ct:comment("Begin ~p",[grps(Config)]),
@@ -288,7 +274,18 @@ end_per_group(_, Config) ->
     Config.
 
 %%--------------------------------------------------------------------
-
+init_per_testcase(read_6GB, Config) ->
+    case verify_openssh(Config) of
+        Result = {skip, _} ->
+            Result;
+        _ ->
+            case os:type() of
+                {win32, _} ->
+                    {skip, "/dev/zero not available on Windws"};
+                _ ->
+                    init_per_testcase(read_6GB_prepare_openssh_server, Config)
+            end
+    end;
 init_per_testcase(sftp_nonexistent_subsystem, Config) ->
     PrivDir = proplists:get_value(priv_dir, Config),
     SysDir =  proplists:get_value(data_dir, Config),
@@ -301,7 +298,6 @@ init_per_testcase(sftp_nonexistent_subsystem, Config) ->
 				  [{User, Passwd}]}
 				]),
     [{sftpd, Sftpd} | Config];
-
 init_per_testcase(version_option, Config0) ->
     Config = prepare(Config0),
     TmpConfig0 = lists:keydelete(watchdog, 1, Config),
@@ -321,7 +317,6 @@ init_per_testcase(version_option, Config0) ->
                                ]),
     Sftp = {ChannelPid, Connection},
     [{sftp,Sftp}, {watchdog, Dog} | TmpConfig];
-
 init_per_testcase(Case, Config00) ->
     Config0 = prepare(Config00),
     Config1 = lists:keydelete(watchdog, 1, Config0),
@@ -333,11 +328,24 @@ init_per_testcase(Case, Config00) ->
 		   undefined -> [];
 		   Sz -> [{packet_size,Sz}]
 	       end,
+    PrepareOpenSSHServer =
+        fun() ->
+                Host = ssh_test_lib:hostname(),
+        	{ok, ChannelPid, Connection} =
+        	    ssh_sftp:start_channel(Host,
+        				   [{user_interaction, false},
+        				    {silently_accept_hosts, true},
+                                            {save_accepted_host, false}
+                                           | PktSzOpt
+        				   ]),
+        	Sftp = {ChannelPid, Connection},
+        	[{sftp, Sftp}, {watchdog, Dog} | Config2]
+        end,
     Config =
 	case proplists:get_value(group,Config2) of
 	    erlang_server ->
-		{_,Host, Port} =  proplists:get_value(sftpd, Config2),
-		{ok, ChannelPid, Connection}  = 
+		{_,Host, Port} = proplists:get_value(sftpd, Config2),
+		{ok, ChannelPid, Connection} =
 		    ssh_sftp:start_channel(Host, Port,
 					   [{user, User},
 					    {password, Passwd},
@@ -352,18 +360,10 @@ init_per_testcase(Case, Config00) ->
 	    openssh_server when Case == links ->
 		{skip, "known bug in openssh"};
 	    openssh_server ->
-		Host = ssh_test_lib:hostname(),
-		{ok, ChannelPid, Connection} = 
-		    ssh_sftp:start_channel(Host, 
-					   [{user_interaction, false},
-					    {silently_accept_hosts, true},
-                                            {save_accepted_host, false}
-					    | PktSzOpt
-					   ]),
-		Sftp = {ChannelPid, Connection},
-		[{sftp, Sftp}, {watchdog, Dog} | Config2]
+                PrepareOpenSSHServer();
+            _ when Case == read_6GB_prepare_openssh_server ->
+                PrepareOpenSSHServer()
 	end,
-
     case catch proplists:get_value(remote_tar,Config) of
 	%% The 'catch' is for the case of Config={skip,...}
 	true ->
@@ -713,6 +713,29 @@ position(Config) when is_list(Config) ->
     {ok, 1} = ssh_sftp:position(Sftp, Handle, cur),
     {ok, "2"} = ssh_sftp:read(Sftp, Handle, 1).
 
+read_6GB(Config) when is_list(Config) ->
+    ct:timetrap(16*?default_timeout),
+    FileName = "/dev/zero",
+    SftpFileName = w2l(Config, FileName),
+    {SftpChannel, _ConnectionRef} = proplists:get_value(sftp, Config),
+    ChunkSize = 65535,
+    N = 100000,
+    {ok, Handle} = ssh_sftp:open(SftpChannel, SftpFileName, [read]),
+    ExpectedList = lists:duplicate(ChunkSize, 0),
+    [begin
+         MBTransferred = io_lib:format("~.2f", [I * ChunkSize / 1048576.0]),
+         case ssh_sftp:read(SftpChannel, Handle, ChunkSize, timer:minutes(1)) of
+             {ok, ExpectedList} ->
+                 [ct:log("~n~s MB read~n", [MBTransferred]) || I rem 10000 == 0];
+             Result ->
+                 ct:log("## After reading ~s MB~n## Unexpected result received = ~p",
+                        [MBTransferred, Result]),
+                 ct:fail(unexpected_reason)
+         end
+     end ||
+        I <- lists:seq(0, N)],
+    ok.
+
 %%--------------------------------------------------------------------
 pos_read(Config) when is_list(Config) ->
     FileName = proplists:get_value(testfile, Config),
@@ -1271,4 +1294,22 @@ w2l(Config, P) ->
     W2L = proplists:get_value(w2l, Config, fun(X) -> X end),
     W2L(P).
 
-    
+verify_openssh(Config) ->
+    ct:comment("Begin ~p",[grps(Config)]),
+    Host = ssh_test_lib:hostname(),
+    case (catch ssh_sftp:start_channel(Host,
+				       [{user_interaction, false},
+					{silently_accept_hosts, true},
+                                        {save_accepted_host, false}
+                                       ])) of
+	{ok, _ChannelPid, Connection} ->
+	    [{peer, {_HostName,{IPx,Portx}}}] = ssh:connection_info(Connection,[peer]),
+	    ssh:close(Connection),
+	    [{w2l, fun w2l/1},
+             {peer, {fmt_host(IPx),Portx}}, {group, openssh_server} | Config];
+	{error,"Key exchange failed"} ->
+	    {skip, "openssh server doesn't support the tested kex algorithm"};
+	Other ->
+            ct:log("No openssh server. Cause:~n~p~n",[Other]),
+	    {skip, "No openssh daemon (see log in testcase)"}
+    end.
-- 
2.43.0

openSUSE Build Service is sponsored by