File 5041-ssh-max_handles-option-added-to-ssh_sftpd.patch of Package erlang
From 5f9af63eec4657a37663828d206517828cb9f288 Mon Sep 17 00:00:00 2001
From: Jakub Witczak <kuba@erlang.org>
Date: Wed, 20 Aug 2025 10:31:50 +0200
Subject: [PATCH] ssh: max_handles option added to ssh_sftpd
- add max_handles option and update tests (1000 by default)
- remove sshd_read_file redundant testcase
---
lib/ssh/src/ssh_sftpd.erl | 41 +++++++++++---
lib/ssh/test/ssh_sftpd_SUITE.erl | 96 +++++++++++++++-----------------
2 files changed, 79 insertions(+), 58 deletions(-)
diff --git a/lib/ssh/src/ssh_sftpd.erl b/lib/ssh/src/ssh_sftpd.erl
index e7c51cc948..03ddff71dc 100644
--- a/lib/ssh/src/ssh_sftpd.erl
+++ b/lib/ssh/src/ssh_sftpd.erl
@@ -57,6 +57,7 @@ Specifies a channel process to handle an SFTP subsystem.
file_handler, % atom() - callback module
file_state, % state for the file callback module
max_files, % integer >= 0 max no files sent during READDIR
+ max_handles, % integer > 0 - max number of file handles
options, % from the subsystem declaration
handles % list of open handles
%% handle is either {<int>, directory, {Path, unread|eof}} or
@@ -98,6 +106,7 @@ Options:
Options :: [ {cwd, string()} |
{file_handler, CbMod | {CbMod, FileState}} |
{max_files, integer()} |
+ {max_handles, integer()} |
{root, string()} |
{sftpd_vsn, integer()}
],
@@ -149,8 +158,12 @@ init(Options) ->
{Root0, State0}
end,
MaxLength = proplists:get_value(max_files, Options, 0),
+ MaxHandles = proplists:get_value(max_handles, Options, 1000),
Vsn = proplists:get_value(sftpd_vsn, Options, 5),
- {ok, State#state{cwd = CWD, root = Root, max_files = MaxLength,
+ {ok, State#state{cwd = CWD,
+ root = Root,
+ max_files = MaxLength,
+ max_handles = MaxHandles,
options = Options,
handles = [], pending = <<>>,
xf = #ssh_xfer{vsn = Vsn, ext = []}}}.
@@ -282,14 +295,16 @@ handle_op(?SSH_FXP_REALPATH, ReqId,
end;
handle_op(?SSH_FXP_OPENDIR, ReqId,
<<?UINT32(RLen), RPath:RLen/binary>>,
- State0 = #state{xf = #ssh_xfer{vsn = Vsn},
- file_handler = FileMod, file_state = FS0}) ->
+ State0 = #state{xf = #ssh_xfer{vsn = Vsn},
+ file_handler = FileMod, file_state = FS0,
+ max_handles = MaxHandles}) ->
RelPath = unicode:characters_to_list(RPath),
AbsPath = relate_file_name(RelPath, State0),
XF = State0#state.xf,
{IsDir, FS1} = FileMod:is_dir(AbsPath, FS0),
State1 = State0#state{file_state = FS1},
+ HandlesCnt = length(State0#state.handles),
case IsDir of
false when Vsn > 5 ->
ssh_xfer:xf_send_status(XF, ReqId, ?SSH_FX_NOT_A_DIRECTORY,
@@ -299,8 +314,12 @@ handle_op(?SSH_FXP_OPENDIR, ReqId,
ssh_xfer:xf_send_status(XF, ReqId, ?SSH_FX_FAILURE,
"Not a directory"),
State1;
- true ->
- add_handle(State1, XF, ReqId, directory, {RelPath,unread})
+ true when HandlesCnt < MaxHandles ->
+ add_handle(State1, XF, ReqId, directory, {RelPath,unread});
+ true ->
+ ssh_xfer:xf_send_status(XF, ReqId, ?SSH_FX_FAILURE,
+ "max_handles limit reached"),
+ State1
end;
handle_op(?SSH_FXP_READDIR, ReqId,
<<?UINT32(HLen), BinHandle:HLen/binary>>,
@@ -751,7 +770,9 @@ open(Vsn, ReqId, Data, State) when Vsn >= 4 ->
do_open(ReqId, State, Path, Flags).
do_open(ReqId, State0, Path, Flags) ->
- #state{file_handler = FileMod, file_state = FS0, xf = #ssh_xfer{vsn = Vsn}} = State0,
+ #state{file_handler = FileMod, file_state = FS0, xf = #ssh_xfer{vsn = Vsn},
+ max_handles = MaxHandles} = State0,
+ HandlesCnt = length(State0#state.handles),
AbsPath = relate_file_name(Path, State0),
{IsDir, _FS1} = FileMod:is_dir(AbsPath, FS0),
case IsDir of
@@ -763,7 +784,7 @@ do_open(ReqId, State0, Path, Flags) ->
ssh_xfer:xf_send_status(State0#state.xf, ReqId,
?SSH_FX_FAILURE, "File is a directory"),
State0;
- false ->
+ false when HandlesCnt < MaxHandles ->
OpenFlags = [binary | Flags],
{Res, FS1} = FileMod:open(AbsPath, OpenFlags, FS0),
State1 = State0#state{file_state = FS1},
@@ -774,7 +795,11 @@ do_open(ReqId, State0, Path, Flags) ->
ssh_xfer:xf_send_status(State1#state.xf, ReqId,
ssh_xfer:encode_erlang_status(Error)),
State1
- end
+ end;
+ false ->
+ ssh_xfer:xf_send_status(State0#state.xf, ReqId,
+ ?SSH_FX_FAILURE, "max_handles limit reached"),
+ State0
end.
%% resolve all symlinks in a path
diff --git a/lib/ssh/test/ssh_sftpd_SUITE.erl b/lib/ssh/test/ssh_sftpd_SUITE.erl
index 085748d78f..85aefd1f25 100644
--- a/lib/ssh/test/ssh_sftpd_SUITE.erl
+++ b/lib/ssh/test/ssh_sftpd_SUITE.erl
@@ -51,7 +51,6 @@
retrieve_attributes/1,
root_with_cwd/1,
set_attributes/1,
- sshd_read_file/1,
ver3_open_flags/1,
ver3_rename/1,
ver6_basic/1,
@@ -71,9 +70,8 @@
-define(SSH_TIMEOUT, 5000).
-define(REG_ATTERS, <<0,0,0,0,1>>).
-define(UNIX_EPOCH, 62167219200).
-
--define(is_set(F, Bits),
- ((F) band (Bits)) == (F)).
+-define(MAX_HANDLES, 10).
+-define(is_set(F, Bits), ((F) band (Bits)) == (F)).
%%--------------------------------------------------------------------
%% Common Test interface functions -----------------------------------
@@ -97,8 +95,7 @@ all() ->
links,
ver3_rename,
ver3_open_flags,
- relpath,
- sshd_read_file,
+ relpath,
ver6_basic,
access_outside_root,
root_with_cwd,
@@ -180,7 +177,7 @@ init_per_testcase(TestCase, Config) ->
{sftpd_vsn, 6}])],
ssh:daemon(0, [{subsystems, SubSystems}|Options]);
_ ->
- SubSystems = [ssh_sftpd:subsystem_spec([])],
+ SubSystems = [ssh_sftpd:subsystem_spec([{max_handles, ?MAX_HANDLES}])],
ssh:daemon(0, [{subsystems, SubSystems}|Options])
end,
@@ -316,33 +313,44 @@ open_close_dir(Config) when is_list(Config) ->
read_file(Config) when is_list(Config) ->
PrivDir = proplists:get_value(priv_dir, Config),
FileName = filename:join(PrivDir, "test.txt"),
+ {Cm, Channel} = proplists:get_value(sftp, Config),
+ [begin
+ R1 = req_id(),
+ {ok, <<?SSH_FXP_HANDLE, ?UINT32(R1), Handle/binary>>, _} =
+ open_file(FileName, Cm, Channel, R1, ?ACE4_READ_DATA bor ?ACE4_READ_ATTRIBUTES,
+ ?SSH_FXF_OPEN_EXISTING),
+ R2 = req_id(),
+ {ok, <<?SSH_FXP_DATA, ?UINT32(R2), ?UINT32(_Length), Data/binary>>, _} =
+ read_file(Handle, 100, 0, Cm, Channel, R2),
+ {ok, Data} = file:read_file(FileName)
+ end || _I <- lists:seq(0, ?MAX_HANDLES-1)],
+ ReqId = req_id(),
+ {ok, <<?SSH_FXP_STATUS, ?UINT32(ReqId), ?UINT32(?SSH_FX_FAILURE),
+ ?UINT32(MsgLen), Msg:MsgLen/binary,
+ ?UINT32(LangTagLen), _LangTag:LangTagLen/binary>>, _} =
+ open_file(FileName, Cm, Channel, ReqId, ?ACE4_READ_DATA bor ?ACE4_READ_ATTRIBUTES,
+ ?SSH_FXF_OPEN_EXISTING),
+ ct:log("Message: ~s", [Msg]),
+ ok.
- ReqId = 0,
- {Cm, Channel} = proplists:get_value(sftp, Config),
-
- {ok, <<?SSH_FXP_HANDLE, ?UINT32(ReqId), Handle/binary>>, _} =
- open_file(FileName, Cm, Channel, ReqId,
- ?ACE4_READ_DATA bor ?ACE4_READ_ATTRIBUTES,
- ?SSH_FXF_OPEN_EXISTING),
-
- NewReqId = 1,
-
- {ok, <<?SSH_FXP_DATA, ?UINT32(NewReqId), ?UINT32(_Length),
- Data/binary>>, _} =
- read_file(Handle, 100, 0, Cm, Channel, NewReqId),
-
- {ok, Data} = file:read_file(FileName).
-
-%%--------------------------------------------------------------------
read_dir(Config) when is_list(Config) ->
PrivDir = proplists:get_value(priv_dir, Config),
{Cm, Channel} = proplists:get_value(sftp, Config),
- ReqId = 0,
- {ok, <<?SSH_FXP_HANDLE, ?UINT32(ReqId), Handle/binary>>, _} =
- open_dir(PrivDir, Cm, Channel, ReqId),
- ok = read_dir(Handle, Cm, Channel, ReqId).
+ [begin
+ R1 = req_id(),
+ {ok, <<?SSH_FXP_HANDLE, ?UINT32(R1), Handle/binary>>, _} =
+ open_dir(PrivDir, Cm, Channel, R1),
+ R2 = req_id(),
+ ok = read_dir(Handle, Cm, Channel, R2)
+ end || _I <- lists:seq(0, ?MAX_HANDLES-1)],
+ ReqId = req_id(),
+ {ok, <<?SSH_FXP_STATUS, ?UINT32(ReqId), ?UINT32(?SSH_FX_FAILURE),
+ ?UINT32(MsgLen), Msg:MsgLen/binary,
+ ?UINT32(LangTagLen), _LangTag:LangTagLen/binary>>, _} =
+ open_dir(PrivDir, Cm, Channel, ReqId),
+ ct:log("Message: ~s", [Msg]),
+ ok.
-%%--------------------------------------------------------------------
write_file(Config) when is_list(Config) ->
PrivDir = proplists:get_value(priv_dir, Config),
FileName = filename:join(PrivDir, "test.txt"),
@@ -644,27 +652,6 @@ relpath(Config) when is_list(Config) ->
Root = Path
end.
-%%--------------------------------------------------------------------
-sshd_read_file(Config) when is_list(Config) ->
- PrivDir = proplists:get_value(priv_dir, Config),
- FileName = filename:join(PrivDir, "test.txt"),
-
- ReqId = 0,
- {Cm, Channel} = proplists:get_value(sftp, Config),
-
- {ok, <<?SSH_FXP_HANDLE, ?UINT32(ReqId), Handle/binary>>, _} =
- open_file(FileName, Cm, Channel, ReqId,
- ?ACE4_READ_DATA bor ?ACE4_READ_ATTRIBUTES,
- ?SSH_FXF_OPEN_EXISTING),
-
- NewReqId = 1,
-
- {ok, <<?SSH_FXP_DATA, ?UINT32(NewReqId), ?UINT32(_Length),
- Data/binary>>, _} =
- read_file(Handle, 100, 0, Cm, Channel, NewReqId),
-
- {ok, Data} = file:read_file(FileName).
-%%--------------------------------------------------------------------
ver6_basic(Config) when is_list(Config) ->
PrivDir = proplists:get_value(priv_dir, Config),
%FileName = filename:join(PrivDir, "test.txt"),
@@ -1078,3 +1065,12 @@ encode_file_type(Type) ->
not_default_permissions() ->
8#600. %% User read-write-only
+
+req_id() ->
+ ReqId =
+ case get(req_id) of
+ undefined -> 0;
+ I -> I
+ end,
+ put(req_id, ReqId + 1),
+ ReqId.
--
2.51.0