File 1125-Add-longname-field-in-sftp-version-3.patch of Package erlang

From 2787cdb4a29dd2c827f639580210de26c9e048cf Mon Sep 17 00:00:00 2001
From: Jonatas Cardador <jonatas.cardador@gmail.com>
Date: Tue, 9 Feb 2021 10:32:37 +0100
Subject: [PATCH 2/2] Add longname field in sftp version 3

Include longname field in SSH_FXP_NAME response in sftp version 3.
The longname field is an expanded format for the file name.
Although its format is unspecified by sftp protocol, some clients retrieve this field to
display file information.
According to documentation (https://tools.ietf.org/html/draft-ietf-secsh-filexfer-02)
the recommended format for the longname field is as follows:
-rwxr-xr-x   1 mjos     staff      348911 Mar 25 14:29 t-filexfer
(similar to what is returned by "ls -l" on Unix systems).
---
 lib/ssh/src/ssh_sftpd.erl | 78 +++++++++++++++++++++++++++++++++------
 1 file changed, 66 insertions(+), 12 deletions(-)

diff --git a/lib/ssh/src/ssh_sftpd.erl b/lib/ssh/src/ssh_sftpd.erl
index 158ef3d5ae..1c53690ed0 100644
--- a/lib/ssh/src/ssh_sftpd.erl
+++ b/lib/ssh/src/ssh_sftpd.erl
@@ -453,19 +454,19 @@ get_handle(Handles, BinHandle) ->
 
 %%% read_dir/5: read directory, send names, and return new state
 read_dir(State0 = #state{file_handler = FileMod, max_files = MaxLength, file_state = FS0},
-	 XF, ReqId, Handle, RelPath, {cache, Files}) ->
+	 XF = #ssh_xfer{cm = _CM, channel = _Channel, vsn = Vsn}, ReqId, Handle, RelPath, {cache, Files}) ->
     AbsPath = relate_file_name(RelPath, State0),
     if
 	length(Files) > MaxLength ->
 	    {ToSend, NewCache} = lists:split(MaxLength, Files),
-	    {NamesAndAttrs, FS1} = get_attrs(AbsPath, ToSend, FileMod, FS0),
+	    {NamesAndAttrs, FS1} = get_attrs(AbsPath, ToSend, FileMod, FS0, Vsn),
 	    ssh_xfer:xf_send_names(XF, ReqId, NamesAndAttrs),
 	    Handles = lists:keyreplace(Handle, 1,
 				       State0#state.handles,
 				       {Handle, directory, {RelPath,{cache, NewCache}}}),
 	    State0#state{handles = Handles, file_state = FS1};
 	true ->
-	    {NamesAndAttrs, FS1} = get_attrs(AbsPath, Files, FileMod, FS0),
+	    {NamesAndAttrs, FS1} = get_attrs(AbsPath, Files, FileMod, FS0, Vsn),
 	    ssh_xfer:xf_send_names(XF, ReqId, NamesAndAttrs),
 	    Handles = lists:keyreplace(Handle, 1,
 				       State0#state.handles,
@@ -473,12 +474,12 @@ read_dir(State0 = #state{file_handler = FileMod, max_files = MaxLength, file_sta
 	    State0#state{handles = Handles, file_state = FS1}
     end;
 read_dir(State0 = #state{file_handler = FileMod, max_files = MaxLength, file_state = FS0},
-	 XF, ReqId, Handle, RelPath, _Status) ->
+	 XF = #ssh_xfer{cm = _CM, channel = _Channel, vsn = Vsn}, ReqId, Handle, RelPath, _Status) ->
     AbsPath = relate_file_name(RelPath, State0),
     {Res, FS1} = FileMod:list_dir(AbsPath, FS0),
     case Res of
 	{ok, Files} when MaxLength == 0 orelse MaxLength > length(Files) ->
-	    {NamesAndAttrs, FS2} = get_attrs(AbsPath, Files, FileMod, FS1),
+	    {NamesAndAttrs, FS2} = get_attrs(AbsPath, Files, FileMod, FS1, Vsn),
 	    ssh_xfer:xf_send_names(XF, ReqId, NamesAndAttrs),
 	    Handles = lists:keyreplace(Handle, 1,
 				       State0#state.handles,
@@ -486,7 +487,7 @@ read_dir(State0 = #state{file_handler = FileMod, max_files = MaxLength, file_sta
 	    State0#state{handles = Handles, file_state = FS2};
 	{ok, Files} ->
 	    {ToSend, Cache} = lists:split(MaxLength, Files),
-	    {NamesAndAttrs, FS2} = get_attrs(AbsPath, ToSend, FileMod, FS1),
+	    {NamesAndAttrs, FS2} = get_attrs(AbsPath, ToSend, FileMod, FS1, Vsn),
 	    ssh_xfer:xf_send_names(XF, ReqId, NamesAndAttrs),
 	    Handles = lists:keyreplace(Handle, 1,
 				       State0#state.handles,
@@ -497,21 +498,74 @@ read_dir(State0 = #state{file_handler = FileMod, max_files = MaxLength, file_sta
 	    send_status({error, Error}, ReqId, State1)
     end.
 
+type_to_string(regular)   -> "-";
+type_to_string(directory) -> "d";
+type_to_string(symlink)   -> "s";
+type_to_string(device)   -> "?";
+type_to_string(undefined)   -> "?";
+type_to_string(other)   -> "?".
+
+%% Converts a numeric mode to its human-readable representation
+mode_to_string(Mode) ->
+    mode_to_string(Mode, "xwrxwrxwr", []).
+mode_to_string(Mode, [C|T], Acc) when Mode band 1 =:= 1 ->
+    mode_to_string(Mode bsr 1, T, [C|Acc]);
+mode_to_string(Mode, [_|T], Acc) ->
+    mode_to_string(Mode bsr 1, T, [$-|Acc]);
+mode_to_string(_, [], Acc) ->
+    Acc.
+
+%% Converts a POSIX time to a readable string
+time_to_string({{Y, Mon, Day}, {H, Min, _}}) ->
+    io_lib:format("~s ~2w ~s:~s ~w", [month(Mon), Day, two_d(H), two_d(Min), Y]).
+
+two_d(N) ->
+    tl(integer_to_list(N + 100)).
+
+month(1) -> "Jan";
+month(2) -> "Feb";
+month(3) -> "Mar";
+month(4) -> "Apr";
+month(5) -> "May";
+month(6) -> "Jun";
+month(7) -> "Jul";
+month(8) -> "Aug";
+month(9) -> "Sep";
+month(10) -> "Oct";
+month(11) -> "Nov";
+month(12) -> "Dec".
+
+longame({Name, Type, Size, Mtime, Mode, Uid, Gid}) ->
+	io_lib:format("~s~s ~4w/~-4w ~7w ~s ~s\n", 
+           [type_to_string(Type), mode_to_string(Mode),
+           Uid, Gid, Size, time_to_string(Mtime), Name]).
+
+%%% get_long_name: get file longname (version 3)
+%%% format output : -rwxr-xr-x   1 uid/gid    348911 Mar 25 14:29 t-filexfer
+get_long_name(FileName, I) when is_record(I, file_info) ->
+    longame({FileName, I#file_info.type, I#file_info.size, I#file_info.mtime, 
+        I#file_info.mode, I#file_info.uid, I#file_info.gid}).
 
 %%% get_attrs: get stat of each file and return
-get_attrs(RelPath, Files, FileMod, FS) ->
-    get_attrs(RelPath, Files, FileMod, FS, []).
+get_attrs(RelPath, Files, FileMod, FS, Vsn) ->
+    get_attrs(RelPath, Files, FileMod, FS, Vsn, []).
 
-get_attrs(_RelPath, [], _FileMod, FS, Acc) ->
+get_attrs(_RelPath, [], _FileMod, FS, _Vsn, Acc) ->
     {lists:reverse(Acc), FS};
-get_attrs(RelPath, [F | Rest], FileMod, FS0, Acc) ->
+get_attrs(RelPath, [F | Rest], FileMod, FS0, Vsn, Acc) ->
     Path = filename:absname(F, RelPath),
     case FileMod:read_link_info(Path, FS0) of
 	{{ok, Info}, FS1} ->
+		Name = if Vsn =< 3 ->
+			 LongName = get_long_name(F, Info),
+		     {F, LongName};
+		 true ->
+			 F
+	     end,
 	    Attrs = ssh_sftp:info_to_attr(Info),
-	    get_attrs(RelPath, Rest, FileMod, FS1, [{F, Attrs} | Acc]);
+	    get_attrs(RelPath, Rest, FileMod, FS1, Vsn, [{Name, Attrs} | Acc]);
 	{{error, enoent}, FS1} ->
-	    get_attrs(RelPath, Rest, FileMod, FS1, Acc);
+	    get_attrs(RelPath, Rest, FileMod, FS1, Vsn, Acc);
 	{Error, FS1} ->
 	    {Error, FS1}
     end.
-- 
2.26.2

openSUSE Build Service is sponsored by