Skip to content

Commit 5f9af63

Browse files
committed
ssh: max_handles option added to ssh_sftpd
- add max_handles option and update tests (1000 by default) - remove sshd_read_file redundant testcase
1 parent c388a2d commit 5f9af63

File tree

2 files changed

+79
-58
lines changed

2 files changed

+79
-58
lines changed

lib/ssh/src/ssh_sftpd.erl

Lines changed: 33 additions & 8 deletions
Original file line numberDiff line numberDiff line change
@@ -57,6 +57,7 @@ Specifies a channel process to handle an SFTP subsystem.
5757
file_handler, % atom() - callback module
5858
file_state, % state for the file callback module
5959
max_files, % integer >= 0 max no files sent during READDIR
60+
max_handles, % integer > 0 - max number of file handles
6061
options, % from the subsystem declaration
6162
handles % list of open handles
6263
%% handle is either {<int>, directory, {Path, unread|eof}} or
@@ -86,6 +87,13 @@ Options:
8687
limit. If supplied, the number of filenames returned to the SFTP client per
8788
`READDIR` request is limited to at most the given value.
8889

90+
- **`max_handles`** - The default value is `1000`. Positive integer
91+
value represents the maximum number of file handles allowed for a
92+
connection.
93+
94+
(Note: separate limitation might be also enforced by underlying
95+
operating system)
96+
8997
- **`root`** - Sets the SFTP root directory. Then the user cannot see any files
9098
above this root. If, for example, the root directory is set to `/tmp`, then
9199
the user sees this directory as `/`. If the user then writes `cd /etc`, the
@@ -98,6 +106,7 @@ Options:
98106
Options :: [ {cwd, string()} |
99107
{file_handler, CbMod | {CbMod, FileState}} |
100108
{max_files, integer()} |
109+
{max_handles, integer()} |
101110
{root, string()} |
102111
{sftpd_vsn, integer()}
103112
],
@@ -149,8 +158,12 @@ init(Options) ->
149158
{Root0, State0}
150159
end,
151160
MaxLength = proplists:get_value(max_files, Options, 0),
161+
MaxHandles = proplists:get_value(max_handles, Options, 1000),
152162
Vsn = proplists:get_value(sftpd_vsn, Options, 5),
153-
{ok, State#state{cwd = CWD, root = Root, max_files = MaxLength,
163+
{ok, State#state{cwd = CWD,
164+
root = Root,
165+
max_files = MaxLength,
166+
max_handles = MaxHandles,
154167
options = Options,
155168
handles = [], pending = <<>>,
156169
xf = #ssh_xfer{vsn = Vsn, ext = []}}}.
@@ -282,14 +295,16 @@ handle_op(?SSH_FXP_REALPATH, ReqId,
282295
end;
283296
handle_op(?SSH_FXP_OPENDIR, ReqId,
284297
<<?UINT32(RLen), RPath:RLen/binary>>,
285-
State0 = #state{xf = #ssh_xfer{vsn = Vsn},
286-
file_handler = FileMod, file_state = FS0}) ->
298+
State0 = #state{xf = #ssh_xfer{vsn = Vsn},
299+
file_handler = FileMod, file_state = FS0,
300+
max_handles = MaxHandles}) ->
287301
RelPath = unicode:characters_to_list(RPath),
288302
AbsPath = relate_file_name(RelPath, State0),
289303

290304
XF = State0#state.xf,
291305
{IsDir, FS1} = FileMod:is_dir(AbsPath, FS0),
292306
State1 = State0#state{file_state = FS1},
307+
HandlesCnt = length(State0#state.handles),
293308
case IsDir of
294309
false when Vsn > 5 ->
295310
ssh_xfer:xf_send_status(XF, ReqId, ?SSH_FX_NOT_A_DIRECTORY,
@@ -299,8 +314,12 @@ handle_op(?SSH_FXP_OPENDIR, ReqId,
299314
ssh_xfer:xf_send_status(XF, ReqId, ?SSH_FX_FAILURE,
300315
"Not a directory"),
301316
State1;
302-
true ->
303-
add_handle(State1, XF, ReqId, directory, {RelPath,unread})
317+
true when HandlesCnt < MaxHandles ->
318+
add_handle(State1, XF, ReqId, directory, {RelPath,unread});
319+
true ->
320+
ssh_xfer:xf_send_status(XF, ReqId, ?SSH_FX_FAILURE,
321+
"max_handles limit reached"),
322+
State1
304323
end;
305324
handle_op(?SSH_FXP_READDIR, ReqId,
306325
<<?UINT32(HLen), BinHandle:HLen/binary>>,
@@ -751,7 +770,9 @@ open(Vsn, ReqId, Data, State) when Vsn >= 4 ->
751770
do_open(ReqId, State, Path, Flags).
752771

753772
do_open(ReqId, State0, Path, Flags) ->
754-
#state{file_handler = FileMod, file_state = FS0, xf = #ssh_xfer{vsn = Vsn}} = State0,
773+
#state{file_handler = FileMod, file_state = FS0, xf = #ssh_xfer{vsn = Vsn},
774+
max_handles = MaxHandles} = State0,
775+
HandlesCnt = length(State0#state.handles),
755776
AbsPath = relate_file_name(Path, State0),
756777
{IsDir, _FS1} = FileMod:is_dir(AbsPath, FS0),
757778
case IsDir of
@@ -763,7 +784,7 @@ do_open(ReqId, State0, Path, Flags) ->
763784
ssh_xfer:xf_send_status(State0#state.xf, ReqId,
764785
?SSH_FX_FAILURE, "File is a directory"),
765786
State0;
766-
false ->
787+
false when HandlesCnt < MaxHandles ->
767788
OpenFlags = [binary | Flags],
768789
{Res, FS1} = FileMod:open(AbsPath, OpenFlags, FS0),
769790
State1 = State0#state{file_state = FS1},
@@ -774,7 +795,11 @@ do_open(ReqId, State0, Path, Flags) ->
774795
ssh_xfer:xf_send_status(State1#state.xf, ReqId,
775796
ssh_xfer:encode_erlang_status(Error)),
776797
State1
777-
end
798+
end;
799+
false ->
800+
ssh_xfer:xf_send_status(State0#state.xf, ReqId,
801+
?SSH_FX_FAILURE, "max_handles limit reached"),
802+
State0
778803
end.
779804

780805
%% resolve all symlinks in a path

lib/ssh/test/ssh_sftpd_SUITE.erl

Lines changed: 46 additions & 50 deletions
Original file line numberDiff line numberDiff line change
@@ -51,7 +51,6 @@
5151
retrieve_attributes/1,
5252
root_with_cwd/1,
5353
set_attributes/1,
54-
sshd_read_file/1,
5554
ver3_open_flags/1,
5655
ver3_rename/1,
5756
ver6_basic/1,
@@ -71,9 +70,8 @@
7170
-define(SSH_TIMEOUT, 5000).
7271
-define(REG_ATTERS, <<0,0,0,0,1>>).
7372
-define(UNIX_EPOCH, 62167219200).
74-
75-
-define(is_set(F, Bits),
76-
((F) band (Bits)) == (F)).
73+
-define(MAX_HANDLES, 10).
74+
-define(is_set(F, Bits), ((F) band (Bits)) == (F)).
7775

7876
%%--------------------------------------------------------------------
7977
%% Common Test interface functions -----------------------------------
@@ -97,8 +95,7 @@ all() ->
9795
links,
9896
ver3_rename,
9997
ver3_open_flags,
100-
relpath,
101-
sshd_read_file,
98+
relpath,
10299
ver6_basic,
103100
access_outside_root,
104101
root_with_cwd,
@@ -180,7 +177,7 @@ init_per_testcase(TestCase, Config) ->
180177
{sftpd_vsn, 6}])],
181178
ssh:daemon(0, [{subsystems, SubSystems}|Options]);
182179
_ ->
183-
SubSystems = [ssh_sftpd:subsystem_spec([])],
180+
SubSystems = [ssh_sftpd:subsystem_spec([{max_handles, ?MAX_HANDLES}])],
184181
ssh:daemon(0, [{subsystems, SubSystems}|Options])
185182
end,
186183

@@ -316,33 +313,44 @@ open_close_dir(Config) when is_list(Config) ->
316313
read_file(Config) when is_list(Config) ->
317314
PrivDir = proplists:get_value(priv_dir, Config),
318315
FileName = filename:join(PrivDir, "test.txt"),
316+
{Cm, Channel} = proplists:get_value(sftp, Config),
317+
[begin
318+
R1 = req_id(),
319+
{ok, <<?SSH_FXP_HANDLE, ?UINT32(R1), Handle/binary>>, _} =
320+
open_file(FileName, Cm, Channel, R1, ?ACE4_READ_DATA bor ?ACE4_READ_ATTRIBUTES,
321+
?SSH_FXF_OPEN_EXISTING),
322+
R2 = req_id(),
323+
{ok, <<?SSH_FXP_DATA, ?UINT32(R2), ?UINT32(_Length), Data/binary>>, _} =
324+
read_file(Handle, 100, 0, Cm, Channel, R2),
325+
{ok, Data} = file:read_file(FileName)
326+
end || _I <- lists:seq(0, ?MAX_HANDLES-1)],
327+
ReqId = req_id(),
328+
{ok, <<?SSH_FXP_STATUS, ?UINT32(ReqId), ?UINT32(?SSH_FX_FAILURE),
329+
?UINT32(MsgLen), Msg:MsgLen/binary,
330+
?UINT32(LangTagLen), _LangTag:LangTagLen/binary>>, _} =
331+
open_file(FileName, Cm, Channel, ReqId, ?ACE4_READ_DATA bor ?ACE4_READ_ATTRIBUTES,
332+
?SSH_FXF_OPEN_EXISTING),
333+
ct:log("Message: ~s", [Msg]),
334+
ok.
319335

320-
ReqId = 0,
321-
{Cm, Channel} = proplists:get_value(sftp, Config),
322-
323-
{ok, <<?SSH_FXP_HANDLE, ?UINT32(ReqId), Handle/binary>>, _} =
324-
open_file(FileName, Cm, Channel, ReqId,
325-
?ACE4_READ_DATA bor ?ACE4_READ_ATTRIBUTES,
326-
?SSH_FXF_OPEN_EXISTING),
327-
328-
NewReqId = 1,
329-
330-
{ok, <<?SSH_FXP_DATA, ?UINT32(NewReqId), ?UINT32(_Length),
331-
Data/binary>>, _} =
332-
read_file(Handle, 100, 0, Cm, Channel, NewReqId),
333-
334-
{ok, Data} = file:read_file(FileName).
335-
336-
%%--------------------------------------------------------------------
337336
read_dir(Config) when is_list(Config) ->
338337
PrivDir = proplists:get_value(priv_dir, Config),
339338
{Cm, Channel} = proplists:get_value(sftp, Config),
340-
ReqId = 0,
341-
{ok, <<?SSH_FXP_HANDLE, ?UINT32(ReqId), Handle/binary>>, _} =
342-
open_dir(PrivDir, Cm, Channel, ReqId),
343-
ok = read_dir(Handle, Cm, Channel, ReqId).
339+
[begin
340+
R1 = req_id(),
341+
{ok, <<?SSH_FXP_HANDLE, ?UINT32(R1), Handle/binary>>, _} =
342+
open_dir(PrivDir, Cm, Channel, R1),
343+
R2 = req_id(),
344+
ok = read_dir(Handle, Cm, Channel, R2)
345+
end || _I <- lists:seq(0, ?MAX_HANDLES-1)],
346+
ReqId = req_id(),
347+
{ok, <<?SSH_FXP_STATUS, ?UINT32(ReqId), ?UINT32(?SSH_FX_FAILURE),
348+
?UINT32(MsgLen), Msg:MsgLen/binary,
349+
?UINT32(LangTagLen), _LangTag:LangTagLen/binary>>, _} =
350+
open_dir(PrivDir, Cm, Channel, ReqId),
351+
ct:log("Message: ~s", [Msg]),
352+
ok.
344353

345-
%%--------------------------------------------------------------------
346354
write_file(Config) when is_list(Config) ->
347355
PrivDir = proplists:get_value(priv_dir, Config),
348356
FileName = filename:join(PrivDir, "test.txt"),
@@ -644,27 +652,6 @@ relpath(Config) when is_list(Config) ->
644652
Root = Path
645653
end.
646654

647-
%%--------------------------------------------------------------------
648-
sshd_read_file(Config) when is_list(Config) ->
649-
PrivDir = proplists:get_value(priv_dir, Config),
650-
FileName = filename:join(PrivDir, "test.txt"),
651-
652-
ReqId = 0,
653-
{Cm, Channel} = proplists:get_value(sftp, Config),
654-
655-
{ok, <<?SSH_FXP_HANDLE, ?UINT32(ReqId), Handle/binary>>, _} =
656-
open_file(FileName, Cm, Channel, ReqId,
657-
?ACE4_READ_DATA bor ?ACE4_READ_ATTRIBUTES,
658-
?SSH_FXF_OPEN_EXISTING),
659-
660-
NewReqId = 1,
661-
662-
{ok, <<?SSH_FXP_DATA, ?UINT32(NewReqId), ?UINT32(_Length),
663-
Data/binary>>, _} =
664-
read_file(Handle, 100, 0, Cm, Channel, NewReqId),
665-
666-
{ok, Data} = file:read_file(FileName).
667-
%%--------------------------------------------------------------------
668655
ver6_basic(Config) when is_list(Config) ->
669656
PrivDir = proplists:get_value(priv_dir, Config),
670657
%FileName = filename:join(PrivDir, "test.txt"),
@@ -1078,3 +1065,12 @@ encode_file_type(Type) ->
10781065

10791066
not_default_permissions() ->
10801067
8#600. %% User read-write-only
1068+
1069+
req_id() ->
1070+
ReqId =
1071+
case get(req_id) of
1072+
undefined -> 0;
1073+
I -> I
1074+
end,
1075+
put(req_id, ReqId + 1),
1076+
ReqId.

0 commit comments

Comments
 (0)