Skip to content

Commit 981a866

Browse files
committed
ssh: fix ssh_sftpd:new_handle
1 parent 412bff5 commit 981a866

File tree

2 files changed

+45
-30
lines changed

2 files changed

+45
-30
lines changed

lib/ssh/src/ssh_sftpd.erl

Lines changed: 18 additions & 12 deletions
Original file line numberDiff line numberDiff line change
@@ -426,23 +426,29 @@ handle_op(?SSH_FXP_SYMLINK, ReqId,
426426
State1 = State0#state{file_state = FS1},
427427
send_status(Status, ReqId, State1).
428428

429-
new_handle([], H) ->
430-
H;
431-
new_handle([{N, _,_} | Rest], H) when N =< H ->
432-
new_handle(Rest, N+1);
433-
new_handle([_ | Rest], H) ->
434-
new_handle(Rest, H).
429+
new_handle_id([]) -> 0;
430+
new_handle_id([{_, _, _} | _] = Handles) ->
431+
{HandleIds, _, _} = lists:unzip3(Handles),
432+
new_handle_id(lists:sort(HandleIds));
433+
new_handle_id(HandleIds) ->
434+
find_gap(HandleIds).
435+
436+
find_gap([Id]) -> % no gap found
437+
Id + 1;
438+
find_gap([Id1, Id2 | _]) when Id2 - Id1 > 1 -> % gap found
439+
Id1 + 1;
440+
find_gap([_, Id | Rest]) ->
441+
find_gap([Id | Rest]).
435442

436443
add_handle(State, XF, ReqId, Type, DirFileTuple) ->
437444
Handles = State#state.handles,
438-
Handle = new_handle(Handles, 0),
439-
ssh_xfer:xf_send_handle(XF, ReqId, integer_to_list(Handle)),
440-
%% OBS: If you change handles-tuple also change new_handle!
441-
%% Is this this the best way to implement new handle?
442-
State#state{handles = [{Handle, Type, DirFileTuple} | Handles]}.
445+
HandleId = new_handle_id(Handles),
446+
ssh_xfer:xf_send_handle(XF, ReqId, integer_to_list(HandleId)),
447+
%% OBS: If you change handles-tuple also change new_handle_id!
448+
State#state{handles = [{HandleId, Type, DirFileTuple} | Handles]}.
443449

444450
get_handle(Handles, BinHandle) ->
445-
case (catch list_to_integer(binary_to_list(BinHandle))) of
451+
case (catch binary_to_integer(BinHandle)) of
446452
I when is_integer(I) ->
447453
case lists:keysearch(I, 1, Handles) of
448454
{value, T} -> T;

lib/ssh/test/ssh_sftpd_SUITE.erl

Lines changed: 27 additions & 18 deletions
Original file line numberDiff line numberDiff line change
@@ -60,6 +60,7 @@
6060

6161
-include_lib("common_test/include/ct.hrl").
6262
-include_lib("kernel/include/file.hrl").
63+
-include_lib("stdlib/include/assert.hrl").
6364
-include("ssh_xfer.hrl").
6465
-include("ssh.hrl").
6566
-include("ssh_test_lib.hrl").
@@ -728,25 +729,33 @@ root_with_cwd(Config) when is_list(Config) ->
728729
FileName = "root_with_cwd.txt",
729730
FilePath = filename:join(CWD, FileName),
730731
ok = filelib:ensure_dir(FilePath),
731-
ok = file:write_file(FilePath ++ "0", <<>>),
732-
ok = file:write_file(FilePath ++ "1", <<>>),
733-
ok = file:write_file(FilePath ++ "2", <<>>),
734732
{Cm, Channel} = proplists:get_value(sftp, Config),
735-
ReqId0 = 0,
736-
{ok, <<?SSH_FXP_HANDLE, ?UINT32(ReqId0), _Handle0/binary>>, _} =
737-
open_file(FileName ++ "0", Cm, Channel, ReqId0,
738-
?ACE4_READ_DATA bor ?ACE4_READ_ATTRIBUTES,
739-
?SSH_FXF_OPEN_EXISTING),
740-
ReqId1 = 1,
741-
{ok, <<?SSH_FXP_HANDLE, ?UINT32(ReqId1), _Handle1/binary>>, _} =
742-
open_file("./" ++ FileName ++ "1", Cm, Channel, ReqId1,
743-
?ACE4_READ_DATA bor ?ACE4_READ_ATTRIBUTES,
744-
?SSH_FXF_OPEN_EXISTING),
745-
ReqId2 = 2,
746-
{ok, <<?SSH_FXP_HANDLE, ?UINT32(ReqId2), _Handle2/binary>>, _} =
747-
open_file("/home/" ++ FileName ++ "2", Cm, Channel, ReqId2,
748-
?ACE4_READ_DATA bor ?ACE4_READ_ATTRIBUTES,
749-
?SSH_FXF_OPEN_EXISTING).
733+
734+
%% repeat procedure to make sure uniq file handles are generated
735+
FileHandles =
736+
[begin
737+
ReqIdStr = integer_to_list(ReqId),
738+
ok = file:write_file(FilePath ++ ReqIdStr, <<>>),
739+
{ok, <<?SSH_FXP_HANDLE, ?UINT32(ReqId), Handle/binary>>, _} =
740+
open_file(FileName ++ ReqIdStr, Cm, Channel, ReqId,
741+
?ACE4_READ_DATA bor ?ACE4_READ_ATTRIBUTES,
742+
?SSH_FXF_OPEN_EXISTING),
743+
Handle
744+
end ||
745+
ReqId <- lists:seq(0,2)],
746+
?assertEqual(length(FileHandles),
747+
length(lists:uniq(FileHandles))),
748+
%% create a gap in file handles
749+
[_, MiddleHandle, _] = FileHandles,
750+
close(MiddleHandle, 3, Cm, Channel),
751+
752+
%% check that gap in file handles is is re-used
753+
GapReqId = 4,
754+
{ok, <<?SSH_FXP_HANDLE, ?UINT32(GapReqId), MiddleHandle/binary>>, _} =
755+
open_file(FileName ++ integer_to_list(1), Cm, Channel, GapReqId,
756+
?ACE4_READ_DATA bor ?ACE4_READ_ATTRIBUTES,
757+
?SSH_FXF_OPEN_EXISTING),
758+
ok.
750759

751760
%%--------------------------------------------------------------------
752761
relative_path(Config) when is_list(Config) ->

0 commit comments

Comments
 (0)