Skip to content

Commit 3095b6f

Browse files
author
Erlang/OTP
committed
Merge branch 'kuba/ssh/max_path_option/OTP-19742' into maint-27
* kuba/ssh/max_path_option/OTP-19742: ssh: ssh_sftpd verify path size for client data # Conflicts: # lib/ssh/src/ssh_sftpd.erl # lib/ssh/test/ssh_sftpd_SUITE.erl
2 parents aa51795 + c242e64 commit 3095b6f

File tree

2 files changed

+83
-29
lines changed

2 files changed

+83
-29
lines changed

lib/ssh/src/ssh_sftpd.erl

Lines changed: 33 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -58,6 +58,7 @@ Specifies a channel process to handle an SFTP subsystem.
5858
file_state, % state for the file callback module
5959
max_files, % integer >= 0 max no files sent during READDIR
6060
max_handles, % integer > 0 - max number of file handles
61+
max_path, % integer > 0 - max length of path
6162
options, % from the subsystem declaration
6263
handles % list of open handles
6364
%% handle is either {<int>, directory, {Path, unread|eof}} or
@@ -94,6 +95,11 @@ Options:
9495
(Note: separate limitation might be also enforced by underlying
9596
operating system)
9697

98+
- **`max_path`** - The default value is `4096`. Positive integer value
99+
represents the maximum path length which cannot be exceeded in
100+
data provided by the SFTP client. (Note: limitations might be also
101+
enforced by underlying operating system)
102+
97103
- **`root`** - Sets the SFTP root directory. Then the user cannot see any files
98104
above this root. If, for example, the root directory is set to `/tmp`, then
99105
the user sees this directory as `/`. If the user then writes `cd /etc`, the
@@ -107,6 +113,7 @@ Options:
107113
{file_handler, CbMod | {CbMod, FileState}} |
108114
{max_files, integer()} |
109115
{max_handles, integer()} |
116+
{max_path, integer()} |
110117
{root, string()} |
111118
{sftpd_vsn, integer()}
112119
],
@@ -159,11 +166,13 @@ init(Options) ->
159166
end,
160167
MaxLength = proplists:get_value(max_files, Options, 0),
161168
MaxHandles = proplists:get_value(max_handles, Options, 1000),
169+
MaxPath = proplists:get_value(max_path, Options, 4096),
162170
Vsn = proplists:get_value(sftpd_vsn, Options, 5),
163171
{ok, State#state{cwd = CWD,
164172
root = Root,
165173
max_files = MaxLength,
166174
max_handles = MaxHandles,
175+
max_path = MaxPath,
167176
options = Options,
168177
handles = [], pending = <<>>,
169178
xf = #ssh_xfer{vsn = Vsn, ext = []}}}.
@@ -283,6 +292,30 @@ handle_op(Request, ReqId, <<?UINT32(HLen), _/binary>>, State = #state{xf = XF})
283292
HLen > 256 ->
284293
ssh_xfer:xf_send_status(XF, ReqId, ?SSH_FX_INVALID_HANDLE, "Invalid handle"),
285294
State;
295+
handle_op(Request, ReqId, <<?UINT32(PLen), _/binary>>,
296+
State = #state{max_path = MaxPath, xf = XF})
297+
when (Request == ?SSH_FXP_LSTAT orelse
298+
Request == ?SSH_FXP_MKDIR orelse
299+
Request == ?SSH_FXP_OPEN orelse
300+
Request == ?SSH_FXP_OPENDIR orelse
301+
Request == ?SSH_FXP_READLINK orelse
302+
Request == ?SSH_FXP_REALPATH orelse
303+
Request == ?SSH_FXP_REMOVE orelse
304+
Request == ?SSH_FXP_RMDIR orelse
305+
Request == ?SSH_FXP_SETSTAT orelse
306+
Request == ?SSH_FXP_STAT),
307+
PLen > MaxPath ->
308+
ssh_xfer:xf_send_status(XF, ReqId, ?SSH_FX_NO_SUCH_PATH,
309+
"No such path"),
310+
State;
311+
handle_op(Request, ReqId, <<?UINT32(PLen), _:PLen/binary, ?UINT32(PLen2), _/binary>>,
312+
State = #state{max_path = MaxPath, xf = XF})
313+
when (Request == ?SSH_FXP_RENAME orelse
314+
Request == ?SSH_FXP_SYMLINK),
315+
(PLen > MaxPath orelse PLen2 > MaxPath) ->
316+
ssh_xfer:xf_send_status(XF, ReqId, ?SSH_FX_NO_SUCH_PATH,
317+
"No such path"),
318+
State;
286319
handle_op(?SSH_FXP_INIT, Version, B, State) when is_binary(B) ->
287320
XF = State#state.xf,
288321
Vsn = lists:min([XF#ssh_xfer.vsn, Version]),

lib/ssh/test/ssh_sftpd_SUITE.erl

Lines changed: 50 additions & 29 deletions
Original file line numberDiff line numberDiff line change
@@ -43,6 +43,7 @@
4343
open_file_dir_v6/1,
4444
read_dir/1,
4545
read_file/1,
46+
max_path/1,
4647
real_path/1,
4748
relative_path/1,
4849
relpath/1,
@@ -72,6 +73,7 @@
7273
-define(REG_ATTERS, <<0,0,0,0,1>>).
7374
-define(UNIX_EPOCH, 62167219200).
7475
-define(MAX_HANDLES, 10).
76+
-define(MAX_PATH, 200).
7577
-define(is_set(F, Bits), ((F) band (Bits)) == (F)).
7678

7779
%%--------------------------------------------------------------------
@@ -85,6 +87,7 @@ all() ->
8587
[open_close_file,
8688
open_close_dir,
8789
read_file,
90+
max_path,
8891
read_dir,
8992
write_file,
9093
rename_file,
@@ -178,7 +181,9 @@ init_per_testcase(TestCase, Config) ->
178181
{sftpd_vsn, 6}])],
179182
ssh:daemon(0, [{subsystems, SubSystems}|Options]);
180183
_ ->
181-
SubSystems = [ssh_sftpd:subsystem_spec([{max_handles, ?MAX_HANDLES}])],
184+
SubSystems = [ssh_sftpd:subsystem_spec(
185+
[{max_handles, ?MAX_HANDLES},
186+
{max_path, ?MAX_PATH}])],
182187
ssh:daemon(0, [{subsystems, SubSystems}|Options])
183188
end,
184189

@@ -334,6 +339,24 @@ read_file(Config) when is_list(Config) ->
334339
ct:log("Message: ~s", [Msg]),
335340
ok.
336341

342+
%%--------------------------------------------------------------------
343+
max_path(Config) when is_list(Config) ->
344+
PrivDir = proplists:get_value(priv_dir, Config),
345+
FileName = filename:join(PrivDir, "test.txt"),
346+
{Cm, Channel} = proplists:get_value(sftp, Config),
347+
%% verify max_path limit
348+
LongFileName =
349+
filename:join(PrivDir,
350+
"t" ++ lists:flatten(lists:duplicate(?MAX_PATH, "e")) ++ "st.txt"),
351+
{ok, _} = file:copy(FileName, LongFileName),
352+
ReqId1 = req_id(),
353+
{ok, <<?SSH_FXP_STATUS, ?UINT32(ReqId1), ?UINT32(?SSH_FX_NO_SUCH_PATH),
354+
_/binary>>, _} =
355+
open_file(LongFileName, Cm, Channel, ReqId1,
356+
?ACE4_READ_DATA bor ?ACE4_READ_ATTRIBUTES,
357+
?SSH_FXF_OPEN_EXISTING).
358+
359+
%%--------------------------------------------------------------------
337360
read_dir(Config) when is_list(Config) ->
338361
PrivDir = proplists:get_value(priv_dir, Config),
339362
{Cm, Channel} = proplists:get_value(sftp, Config),
@@ -397,35 +420,33 @@ rename_file(Config) when is_list(Config) ->
397420
PrivDir = proplists:get_value(priv_dir, Config),
398421
FileName = filename:join(PrivDir, "test.txt"),
399422
NewFileName = filename:join(PrivDir, "test1.txt"),
400-
ReqId = 0,
423+
LongFileName =
424+
filename:join(PrivDir,
425+
"t" ++ lists:flatten(lists:duplicate(?MAX_PATH, "e")) ++ "st.txt"),
401426
{Cm, Channel} = proplists:get_value(sftp, Config),
402-
403-
{ok, <<?SSH_FXP_STATUS, ?UINT32(ReqId),
404-
?UINT32(?SSH_FX_OK), _/binary>>, _} =
405-
rename(FileName, NewFileName, Cm, Channel, ReqId, 6, 0),
406-
407-
NewReqId = ReqId + 1,
408-
409-
{ok, <<?SSH_FXP_STATUS, ?UINT32(NewReqId),
410-
?UINT32(?SSH_FX_OK), _/binary>>, _} =
411-
rename(NewFileName, FileName, Cm, Channel, NewReqId, 6,
412-
?SSH_FXP_RENAME_OVERWRITE),
413-
414-
NewReqId1 = NewReqId + 1,
415-
file:copy(FileName, NewFileName),
416-
417-
%% No overwrite
418-
{ok, <<?SSH_FXP_STATUS, ?UINT32(NewReqId1),
419-
?UINT32(?SSH_FX_FILE_ALREADY_EXISTS), _/binary>>, _} =
420-
rename(FileName, NewFileName, Cm, Channel, NewReqId1, 6,
421-
?SSH_FXP_RENAME_NATIVE),
422-
423-
NewReqId2 = NewReqId1 + 1,
424-
425-
{ok, <<?SSH_FXP_STATUS, ?UINT32(NewReqId2),
426-
?UINT32(?SSH_FX_OP_UNSUPPORTED), _/binary>>, _} =
427-
rename(FileName, NewFileName, Cm, Channel, NewReqId2, 6,
428-
?SSH_FXP_RENAME_ATOMIC).
427+
Version = 6,
428+
[begin
429+
case Action of
430+
{Code, AFile, BFile, Flags} ->
431+
ReqId = req_id(),
432+
ct:log("ReqId = ~p,~nCode = ~p,~nAFile = ~p,~nBFile = ~p,~nFlags = ~p",
433+
[ReqId, Code, AFile, BFile, Flags]),
434+
{ok, <<?SSH_FXP_STATUS, ?UINT32(ReqId), ?UINT32(Code), _/binary>>, _} =
435+
rename(AFile, BFile, Cm, Channel, ReqId, Version, Flags);
436+
{file_copy, AFile, BFile} ->
437+
{ok, _} = file:copy(AFile, BFile)
438+
end
439+
end ||
440+
Action <-
441+
[{?SSH_FX_OK, FileName, NewFileName, 0},
442+
{?SSH_FX_OK, NewFileName, FileName, ?SSH_FXP_RENAME_OVERWRITE},
443+
{file_copy, FileName, NewFileName},
444+
%% no overwrite
445+
{?SSH_FX_FILE_ALREADY_EXISTS, FileName, NewFileName, ?SSH_FXP_RENAME_NATIVE},
446+
{?SSH_FX_OP_UNSUPPORTED, FileName, NewFileName, ?SSH_FXP_RENAME_ATOMIC},
447+
%% max_path
448+
{?SSH_FX_NO_SUCH_PATH, FileName, LongFileName, 0}]],
449+
ok.
429450

430451
%%--------------------------------------------------------------------
431452
mk_rm_dir(Config) when is_list(Config) ->

0 commit comments

Comments
 (0)