Skip to content

Commit 37b5b05

Browse files
committed
Merge branch 'kuba/ssh/fix_new_handle/OTP-19691' into maint
* kuba/ssh/fix_new_handle/OTP-19691: ssh: fix ssh_sftpd:new_handle
2 parents 45a34da + 981a866 commit 37b5b05

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
@@ -482,23 +482,29 @@ handle_op(?SSH_FXP_SYMLINK, ReqId,
482482
State1 = State0#state{file_state = FS1},
483483
send_status(Status, ReqId, State1).
484484

485-
new_handle([], H) ->
486-
H;
487-
new_handle([{N, _,_} | Rest], H) when N =< H ->
488-
new_handle(Rest, N+1);
489-
new_handle([_ | Rest], H) ->
490-
new_handle(Rest, H).
485+
new_handle_id([]) -> 0;
486+
new_handle_id([{_, _, _} | _] = Handles) ->
487+
{HandleIds, _, _} = lists:unzip3(Handles),
488+
new_handle_id(lists:sort(HandleIds));
489+
new_handle_id(HandleIds) ->
490+
find_gap(HandleIds).
491+
492+
find_gap([Id]) -> % no gap found
493+
Id + 1;
494+
find_gap([Id1, Id2 | _]) when Id2 - Id1 > 1 -> % gap found
495+
Id1 + 1;
496+
find_gap([_, Id | Rest]) ->
497+
find_gap([Id | Rest]).
491498

492499
add_handle(State, XF, ReqId, Type, DirFileTuple) ->
493500
Handles = State#state.handles,
494-
Handle = new_handle(Handles, 0),
495-
ssh_xfer:xf_send_handle(XF, ReqId, integer_to_list(Handle)),
496-
%% OBS: If you change handles-tuple also change new_handle!
497-
%% Is this this the best way to implement new handle?
498-
State#state{handles = [{Handle, Type, DirFileTuple} | Handles]}.
501+
HandleId = new_handle_id(Handles),
502+
ssh_xfer:xf_send_handle(XF, ReqId, integer_to_list(HandleId)),
503+
%% OBS: If you change handles-tuple also change new_handle_id!
504+
State#state{handles = [{HandleId, Type, DirFileTuple} | Handles]}.
499505

500506
get_handle(Handles, BinHandle) ->
501-
case (catch list_to_integer(binary_to_list(BinHandle))) of
507+
case (catch binary_to_integer(BinHandle)) of
502508
I when is_integer(I) ->
503509
case lists:keysearch(I, 1, Handles) of
504510
{value, T} -> T;

lib/ssh/test/ssh_sftpd_SUITE.erl

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

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

753762
%%--------------------------------------------------------------------
754763
relative_path(Config) when is_list(Config) ->

0 commit comments

Comments
 (0)