Skip to content
Merged
Show file tree
Hide file tree
Changes from all commits
Commits
File filter

Filter by extension

Filter by extension

Conversations
Failed to load comments.
Loading
Jump to
Jump to file
Failed to load files.
Loading
Diff view
Diff view
37 changes: 36 additions & 1 deletion lib/ssh/src/ssh_sftpd.erl
Original file line number Diff line number Diff line change
Expand Up @@ -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_path, % integer > 0 - max length of path
options, % from the subsystem declaration
handles % list of open handles
%% handle is either {<int>, directory, {Path, unread|eof}} or
Expand Down Expand Up @@ -86,6 +87,11 @@ Options:
limit. If supplied, the number of filenames returned to the SFTP client per
`READDIR` request is limited to at most the given value.

- **`max_path`** - The default value is `4096`. Positive integer value
represents the maximum path length which cannot be exceeded in
data provided by the SFTP client. (Note: limitations might be also
enforced by underlying operating system)

- **`root`** - Sets the SFTP root directory. Then the user cannot see any files
above this root. If, for example, the root directory is set to `/tmp`, then
the user sees this directory as `/`. If the user then writes `cd /etc`, the
Expand All @@ -98,6 +104,7 @@ Options:
Options :: [ {cwd, string()} |
{file_handler, CbMod | {CbMod, FileState}} |
{max_files, integer()} |
{max_path, integer()} |
{root, string()} |
{sftpd_vsn, integer()}
],
Expand Down Expand Up @@ -149,8 +156,12 @@ init(Options) ->
{Root0, State0}
end,
MaxLength = proplists:get_value(max_files, Options, 0),
MaxPath = proplists:get_value(max_path, Options, 4096),
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_path = MaxPath,
options = Options,
handles = [], pending = <<>>,
xf = #ssh_xfer{vsn = Vsn, ext = []}}}.
Expand Down Expand Up @@ -259,6 +270,30 @@ handle_data(Type, ChannelId, Data0, State = #state{pending = Pending}) ->
handle_data(Type, ChannelId, Data, State#state{pending = <<>>})
end.

handle_op(Request, ReqId, <<?UINT32(PLen), _/binary>>,
State = #state{max_path = MaxPath, xf = XF})
when (Request == ?SSH_FXP_LSTAT orelse
Request == ?SSH_FXP_MKDIR orelse
Request == ?SSH_FXP_OPEN orelse
Request == ?SSH_FXP_OPENDIR orelse
Request == ?SSH_FXP_READLINK orelse
Request == ?SSH_FXP_REALPATH orelse
Request == ?SSH_FXP_REMOVE orelse
Request == ?SSH_FXP_RMDIR orelse
Request == ?SSH_FXP_SETSTAT orelse
Request == ?SSH_FXP_STAT),
PLen > MaxPath ->
ssh_xfer:xf_send_status(XF, ReqId, ?SSH_FX_NO_SUCH_PATH,
"No such path"),
State;
handle_op(Request, ReqId, <<?UINT32(PLen), _:PLen/binary, ?UINT32(PLen2), _/binary>>,
State = #state{max_path = MaxPath, xf = XF})
when (Request == ?SSH_FXP_RENAME orelse
Request == ?SSH_FXP_SYMLINK),
(PLen > MaxPath orelse PLen2 > MaxPath) ->
ssh_xfer:xf_send_status(XF, ReqId, ?SSH_FX_NO_SUCH_PATH,
"No such path"),
State;
handle_op(?SSH_FXP_INIT, Version, B, State) when is_binary(B) ->
XF = State#state.xf,
Vsn = lists:min([XF#ssh_xfer.vsn, Version]),
Expand Down
90 changes: 58 additions & 32 deletions lib/ssh/test/ssh_sftpd_SUITE.erl
Original file line number Diff line number Diff line change
Expand Up @@ -43,6 +43,7 @@
open_file_dir_v6/1,
read_dir/1,
read_file/1,
max_path/1,
real_path/1,
relative_path/1,
relpath/1,
Expand Down Expand Up @@ -71,9 +72,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_PATH, 200).
-define(is_set(F, Bits), ((F) band (Bits)) == (F)).

%%--------------------------------------------------------------------
%% Common Test interface functions -----------------------------------
Expand All @@ -86,6 +86,7 @@ all() ->
[open_close_file,
open_close_dir,
read_file,
max_path,
read_dir,
write_file,
rename_file,
Expand Down Expand Up @@ -180,7 +181,8 @@ 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_path, ?MAX_PATH}])],
ssh:daemon(0, [{subsystems, SubSystems}|Options])
end,

Expand Down Expand Up @@ -333,6 +335,23 @@ read_file(Config) when is_list(Config) ->

{ok, Data} = file:read_file(FileName).

%%--------------------------------------------------------------------
max_path(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),
%% verify max_path limit
LongFileName =
filename:join(PrivDir,
"t" ++ lists:flatten(lists:duplicate(?MAX_PATH, "e")) ++ "st.txt"),
{ok, _} = file:copy(FileName, LongFileName),
ReqId1 = req_id(),
{ok, <<?SSH_FXP_STATUS, ?UINT32(ReqId1), ?UINT32(?SSH_FX_NO_SUCH_PATH),
_/binary>>, _} =
open_file(LongFileName, Cm, Channel, ReqId1,
?ACE4_READ_DATA bor ?ACE4_READ_ATTRIBUTES,
?SSH_FXF_OPEN_EXISTING).

%%--------------------------------------------------------------------
read_dir(Config) when is_list(Config) ->
PrivDir = proplists:get_value(priv_dir, Config),
Expand Down Expand Up @@ -388,35 +407,33 @@ rename_file(Config) when is_list(Config) ->
PrivDir = proplists:get_value(priv_dir, Config),
FileName = filename:join(PrivDir, "test.txt"),
NewFileName = filename:join(PrivDir, "test1.txt"),
ReqId = 0,
LongFileName =
filename:join(PrivDir,
"t" ++ lists:flatten(lists:duplicate(?MAX_PATH, "e")) ++ "st.txt"),
{Cm, Channel} = proplists:get_value(sftp, Config),

{ok, <<?SSH_FXP_STATUS, ?UINT32(ReqId),
?UINT32(?SSH_FX_OK), _/binary>>, _} =
rename(FileName, NewFileName, Cm, Channel, ReqId, 6, 0),

NewReqId = ReqId + 1,

{ok, <<?SSH_FXP_STATUS, ?UINT32(NewReqId),
?UINT32(?SSH_FX_OK), _/binary>>, _} =
rename(NewFileName, FileName, Cm, Channel, NewReqId, 6,
?SSH_FXP_RENAME_OVERWRITE),

NewReqId1 = NewReqId + 1,
file:copy(FileName, NewFileName),

%% No overwrite
{ok, <<?SSH_FXP_STATUS, ?UINT32(NewReqId1),
?UINT32(?SSH_FX_FILE_ALREADY_EXISTS), _/binary>>, _} =
rename(FileName, NewFileName, Cm, Channel, NewReqId1, 6,
?SSH_FXP_RENAME_NATIVE),

NewReqId2 = NewReqId1 + 1,

{ok, <<?SSH_FXP_STATUS, ?UINT32(NewReqId2),
?UINT32(?SSH_FX_OP_UNSUPPORTED), _/binary>>, _} =
rename(FileName, NewFileName, Cm, Channel, NewReqId2, 6,
?SSH_FXP_RENAME_ATOMIC).
Version = 6,
[begin
case Action of
{Code, AFile, BFile, Flags} ->
ReqId = req_id(),
ct:log("ReqId = ~p,~nCode = ~p,~nAFile = ~p,~nBFile = ~p,~nFlags = ~p",
[ReqId, Code, AFile, BFile, Flags]),
{ok, <<?SSH_FXP_STATUS, ?UINT32(ReqId), ?UINT32(Code), _/binary>>, _} =
rename(AFile, BFile, Cm, Channel, ReqId, Version, Flags);
{file_copy, AFile, BFile} ->
{ok, _} = file:copy(AFile, BFile)
end
end ||
Action <-
[{?SSH_FX_OK, FileName, NewFileName, 0},
{?SSH_FX_OK, NewFileName, FileName, ?SSH_FXP_RENAME_OVERWRITE},
{file_copy, FileName, NewFileName},
%% no overwrite
{?SSH_FX_FILE_ALREADY_EXISTS, FileName, NewFileName, ?SSH_FXP_RENAME_NATIVE},
{?SSH_FX_OP_UNSUPPORTED, FileName, NewFileName, ?SSH_FXP_RENAME_ATOMIC},
%% max_path
{?SSH_FX_NO_SUCH_PATH, FileName, LongFileName, 0}]],
ok.

%%--------------------------------------------------------------------
mk_rm_dir(Config) when is_list(Config) ->
Expand Down Expand Up @@ -1078,3 +1095,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.