File 1735-ssh-fix-ssh_sftpd-new_handle.patch of Package erlang

From 981a866ece347e8355da2a561280f7d3f07eab52 Mon Sep 17 00:00:00 2001
From: Jakub Witczak <kuba@erlang.org>
Date: Mon, 7 Jul 2025 16:35:48 +0200
Subject: [PATCH] ssh: fix ssh_sftpd:new_handle

---
 lib/ssh/src/ssh_sftpd.erl        | 30 ++++++++++++---------
 lib/ssh/test/ssh_sftpd_SUITE.erl | 45 +++++++++++++++++++-------------
 2 files changed, 45 insertions(+), 30 deletions(-)

diff --git a/lib/ssh/src/ssh_sftpd.erl b/lib/ssh/src/ssh_sftpd.erl
index c86ed2cb81..f2767678c0 100644
--- a/lib/ssh/src/ssh_sftpd.erl
+++ b/lib/ssh/src/ssh_sftpd.erl
@@ -426,23 +426,29 @@ handle_op(?SSH_FXP_SYMLINK, ReqId,
     State1 = State0#state{file_state = FS1},
     send_status(Status, ReqId, State1).
 
-new_handle([], H) ->
-    H;
-new_handle([{N, _,_} | Rest], H) when N =< H ->
-    new_handle(Rest, N+1);
-new_handle([_ | Rest], H) ->
-    new_handle(Rest, H).
+new_handle_id([]) -> 0;
+new_handle_id([{_, _, _} | _] = Handles) ->
+    {HandleIds, _, _} = lists:unzip3(Handles),
+    new_handle_id(lists:sort(HandleIds));
+new_handle_id(HandleIds) ->
+    find_gap(HandleIds).
+
+find_gap([Id]) -> % no gap found
+    Id + 1;
+find_gap([Id1, Id2 | _]) when Id2 - Id1 > 1 -> % gap found
+    Id1 + 1;
+find_gap([_, Id | Rest]) ->
+    find_gap([Id | Rest]).
 
 add_handle(State, XF, ReqId, Type, DirFileTuple) ->
     Handles = State#state.handles,
-    Handle = new_handle(Handles, 0),
-    ssh_xfer:xf_send_handle(XF, ReqId, integer_to_list(Handle)),
-    %% OBS: If you change handles-tuple also change new_handle!
-    %% Is this this the best way to implement new handle?
-    State#state{handles = [{Handle, Type, DirFileTuple} | Handles]}.
+    HandleId = new_handle_id(Handles),
+    ssh_xfer:xf_send_handle(XF, ReqId, integer_to_list(HandleId)),
+    %% OBS: If you change handles-tuple also change new_handle_id!
+    State#state{handles = [{HandleId, Type, DirFileTuple} | Handles]}.
     
 get_handle(Handles, BinHandle) ->
-    case (catch list_to_integer(binary_to_list(BinHandle))) of
+    case (catch binary_to_integer(BinHandle)) of
 	I when is_integer(I) ->
 	    case lists:keysearch(I, 1, Handles) of
 		{value, T} -> T;
diff --git a/lib/ssh/test/ssh_sftpd_SUITE.erl b/lib/ssh/test/ssh_sftpd_SUITE.erl
index 42677b7613..e37d2b08f7 100644
--- a/lib/ssh/test/ssh_sftpd_SUITE.erl
+++ b/lib/ssh/test/ssh_sftpd_SUITE.erl
@@ -60,6 +60,7 @@
 
 -include_lib("common_test/include/ct.hrl").
 -include_lib("kernel/include/file.hrl").
+-include_lib("stdlib/include/assert.hrl").
 -include("ssh_xfer.hrl").
 -include("ssh.hrl").
 -include("ssh_test_lib.hrl").
@@ -728,25 +729,33 @@ root_with_cwd(Config) when is_list(Config) ->
     FileName = "root_with_cwd.txt",
     FilePath = filename:join(CWD, FileName),
     ok = filelib:ensure_dir(FilePath),
-    ok = file:write_file(FilePath ++ "0", <<>>),
-    ok = file:write_file(FilePath ++ "1", <<>>),
-    ok = file:write_file(FilePath ++ "2", <<>>),
     {Cm, Channel} = proplists:get_value(sftp, Config),
-    ReqId0 = 0,
-    {ok, <<?SSH_FXP_HANDLE, ?UINT32(ReqId0), _Handle0/binary>>, _} =
-	open_file(FileName ++ "0", Cm, Channel, ReqId0,
-		  ?ACE4_READ_DATA  bor ?ACE4_READ_ATTRIBUTES,
-		  ?SSH_FXF_OPEN_EXISTING),
-    ReqId1 = 1,
-    {ok, <<?SSH_FXP_HANDLE, ?UINT32(ReqId1), _Handle1/binary>>, _} =
-	open_file("./" ++ FileName ++ "1", Cm, Channel, ReqId1,
-		  ?ACE4_READ_DATA  bor ?ACE4_READ_ATTRIBUTES,
-		  ?SSH_FXF_OPEN_EXISTING),
-    ReqId2 = 2,
-    {ok, <<?SSH_FXP_HANDLE, ?UINT32(ReqId2), _Handle2/binary>>, _} =
-	open_file("/home/" ++ FileName ++ "2", Cm, Channel, ReqId2,
-		  ?ACE4_READ_DATA  bor ?ACE4_READ_ATTRIBUTES,
-		  ?SSH_FXF_OPEN_EXISTING).
+
+    %% repeat procedure to make sure uniq file handles are generated
+    FileHandles =
+        [begin
+             ReqIdStr = integer_to_list(ReqId),
+             ok = file:write_file(FilePath ++ ReqIdStr, <<>>),
+             {ok, <<?SSH_FXP_HANDLE, ?UINT32(ReqId), Handle/binary>>, _} =
+                 open_file(FileName ++ ReqIdStr, Cm, Channel, ReqId,
+                           ?ACE4_READ_DATA  bor ?ACE4_READ_ATTRIBUTES,
+                           ?SSH_FXF_OPEN_EXISTING),
+             Handle
+         end ||
+            ReqId <- lists:seq(0,2)],
+    ?assertEqual(length(FileHandles),
+                 length(lists:uniq(FileHandles))),
+    %% create a gap in file handles
+    [_, MiddleHandle, _] = FileHandles,
+    close(MiddleHandle, 3, Cm, Channel),
+
+    %% check that gap in file handles is is re-used
+    GapReqId = 4,
+    {ok, <<?SSH_FXP_HANDLE, ?UINT32(GapReqId), MiddleHandle/binary>>, _} =
+        open_file(FileName ++ integer_to_list(1), Cm, Channel, GapReqId,
+                  ?ACE4_READ_DATA  bor ?ACE4_READ_ATTRIBUTES,
+                  ?SSH_FXF_OPEN_EXISTING),
+    ok.
 
 %%--------------------------------------------------------------------
 relative_path(Config) when is_list(Config) ->
-- 
2.43.0

openSUSE Build Service is sponsored by