Skip to content

Commit 43b9064

Browse files
author
Erlang/OTP
committed
Merge branch 'kuba/ssh/dfx_sftp_opendir_fix/OTP-19701' into maint-27
* kuba/ssh/dfx_sftp_opendir_fix/OTP-19701: ssh: max_handles option added to ssh_sftpd
2 parents 6b1e065 + 5f9af63 commit 43b9064

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>>,
@@ -757,7 +776,9 @@ open(Vsn, ReqId, Data, State) when Vsn >= 4 ->
757776
do_open(ReqId, State, Path, Flags).
758777

759778
do_open(ReqId, State0, Path, Flags) ->
760-
#state{file_handler = FileMod, file_state = FS0, xf = #ssh_xfer{vsn = Vsn}} = State0,
779+
#state{file_handler = FileMod, file_state = FS0, xf = #ssh_xfer{vsn = Vsn},
780+
max_handles = MaxHandles} = State0,
781+
HandlesCnt = length(State0#state.handles),
761782
AbsPath = relate_file_name(Path, State0),
762783
{IsDir, _FS1} = FileMod:is_dir(AbsPath, FS0),
763784
case IsDir of
@@ -769,7 +790,7 @@ do_open(ReqId, State0, Path, Flags) ->
769790
ssh_xfer:xf_send_status(State0#state.xf, ReqId,
770791
?SSH_FX_FAILURE, "File is a directory"),
771792
State0;
772-
false ->
793+
false when HandlesCnt < MaxHandles ->
773794
OpenFlags = [binary | Flags],
774795
{Res, FS1} = FileMod:open(AbsPath, OpenFlags, FS0),
775796
State1 = State0#state{file_state = FS1},
@@ -780,7 +801,11 @@ do_open(ReqId, State0, Path, Flags) ->
780801
ssh_xfer:xf_send_status(State1#state.xf, ReqId,
781802
ssh_xfer:encode_erlang_status(Error)),
782803
State1
783-
end
804+
end;
805+
false ->
806+
ssh_xfer:xf_send_status(State0#state.xf, ReqId,
807+
?SSH_FX_FAILURE, "max_handles limit reached"),
808+
State0
784809
end.
785810

786811
%% 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,
@@ -72,9 +71,8 @@
7271
-define(SSH_TIMEOUT, 5000).
7372
-define(REG_ATTERS, <<0,0,0,0,1>>).
7473
-define(UNIX_EPOCH, 62167219200).
75-
76-
-define(is_set(F, Bits),
77-
((F) band (Bits)) == (F)).
74+
-define(MAX_HANDLES, 10).
75+
-define(is_set(F, Bits), ((F) band (Bits)) == (F)).
7876

7977
%%--------------------------------------------------------------------
8078
%% Common Test interface functions -----------------------------------
@@ -98,8 +96,7 @@ all() ->
9896
links,
9997
ver3_rename,
10098
ver3_open_flags,
101-
relpath,
102-
sshd_read_file,
99+
relpath,
103100
ver6_basic,
104101
access_outside_root,
105102
root_with_cwd,
@@ -181,7 +178,7 @@ init_per_testcase(TestCase, Config) ->
181178
{sftpd_vsn, 6}])],
182179
ssh:daemon(0, [{subsystems, SubSystems}|Options]);
183180
_ ->
184-
SubSystems = [ssh_sftpd:subsystem_spec([])],
181+
SubSystems = [ssh_sftpd:subsystem_spec([{max_handles, ?MAX_HANDLES}])],
185182
ssh:daemon(0, [{subsystems, SubSystems}|Options])
186183
end,
187184

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

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

346-
%%--------------------------------------------------------------------
347355
write_file(Config) when is_list(Config) ->
348356
PrivDir = proplists:get_value(priv_dir, Config),
349357
FileName = filename:join(PrivDir, "test.txt"),
@@ -645,27 +653,6 @@ relpath(Config) when is_list(Config) ->
645653
Root = Path
646654
end.
647655

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

10881075
not_default_permissions() ->
10891076
8#600. %% User read-write-only
1077+
1078+
req_id() ->
1079+
ReqId =
1080+
case get(req_id) of
1081+
undefined -> 0;
1082+
I -> I
1083+
end,
1084+
put(req_id, ReqId + 1),
1085+
ReqId.

0 commit comments

Comments
 (0)