Skip to content

Commit

Permalink
ssh: remove adjust_window call from ssh_connection
Browse files Browse the repository at this point in the history
  • Loading branch information
u3s committed Jan 17, 2025
1 parent 6bf99d6 commit df20679
Show file tree
Hide file tree
Showing 3 changed files with 68 additions and 25 deletions.
1 change: 0 additions & 1 deletion lib/ssh/src/ssh_connection.erl
Original file line number Diff line number Diff line change
Expand Up @@ -1835,7 +1835,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}
Expand Down
57 changes: 34 additions & 23 deletions lib/ssh/test/ssh_connection_SUITE.erl
Original file line number Diff line number Diff line change
Expand Up @@ -623,6 +623,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),
Expand Down Expand Up @@ -764,11 +767,8 @@ ptty_alloc_pixel(Config) when is_list(Config) ->
%% 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 used to be interrupted when ssh_echo_server ran
%% out of data window and closed channel
%%- but with automatic window adjustment, above condition is not taking
%% place, so ssh_echo_server continues sending data until it is done
%%- so ssh_connection:send returns 'ok'
%%- 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,
Expand Down Expand Up @@ -807,7 +807,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},
Expand Down Expand Up @@ -840,6 +840,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]),
Expand All @@ -858,7 +859,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]),
Expand Down Expand Up @@ -1966,26 +1967,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.


%%--------------------------------------------------------------------
Expand Down Expand Up @@ -2122,6 +2132,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);
Expand Down
35 changes: 34 additions & 1 deletion lib/ssh/test/ssh_sftp_SUITE.erl
Original file line number Diff line number Diff line change
Expand Up @@ -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,
Expand Down Expand Up @@ -82,6 +83,8 @@
-include_lib("kernel/include/file.hrl").
-include("ssh_test_lib.hrl").
-include_lib("stdlib/include/assert.hrl").

-include_lib("/home/ejakwit/src/tools/src/tools.hrl").
%% Default timetrap timeout
-define(default_timeout, test_server:minutes(0.5)).

Expand Down Expand Up @@ -131,7 +134,8 @@ groups() ->
{group,remote_tar}]},

{openssh_server, [], [{group,write_read_tests},
{group,remote_tar}]},
{group,remote_tar},
read_6GB]},

{remote_tar, [], [create_empty_tar,
ascii_filename_ascii_contents_to_tar,
Expand Down Expand Up @@ -713,6 +717,35 @@ 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(8*?default_timeout),
case os:type() of
{win32, _} ->
{skip, "/dev/zero not available on Windws"};
_ ->
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],
[ct:log(".", []) || I rem 100 == 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
end.

%%--------------------------------------------------------------------
pos_read(Config) when is_list(Config) ->
FileName = proplists:get_value(testfile, Config),
Expand Down

0 comments on commit df20679

Please sign in to comment.