File 1338-zip-Add-execute-permission-to-zipped-directories-fix.patch of Package erlang
From 4faaa6727eeda17d8550779c10b67943dbf27077 Mon Sep 17 00:00:00 2001
From: Kjell Winblad <kjellwinblad@gmail.com>
Date: Thu, 1 Apr 2021 10:23:14 +0200
Subject: [PATCH] [zip] Add execute permission to zipped directories (fix
GH-4687)
Before this commit all files and directories in a ZIP-archive created
by `zip:create` or `zip:zip` got the same permission 644. This made
the files inside dictionaries inaccessible (even for the owner). After
this commit all zipped dictionaries get permission 744 (adds
executable permission for the owner), which makes the dictionary
content accessible for the owner.
---
lib/stdlib/src/zip.erl | 21 ++++++++-----
lib/stdlib/test/zip_SUITE.erl | 30 +++++++++++++++++--
.../zip_SUITE_data/test-zip-output/.keepdir | 0
.../zip_SUITE_data/test-zip/dir-1/file.txt | 1 +
4 files changed, 43 insertions(+), 9 deletions(-)
create mode 100644 lib/stdlib/test/zip_SUITE_data/test-zip-output/.keepdir
create mode 100644 lib/stdlib/test/zip_SUITE_data/test-zip/dir-1/file.txt
diff --git a/lib/stdlib/src/zip.erl b/lib/stdlib/src/zip.erl
index 8f703d9d1a..629e0e2a72 100644
--- a/lib/stdlib/src/zip.erl
+++ b/lib/stdlib/src/zip.erl
@@ -159,7 +159,8 @@
comp_size,
uncomp_size,
file_name_length,
- extra_field_length}).
+ extra_field_length,
+ type}).
-define(CENTRAL_FILE_HEADER_SZ,(4+2+2+2+2+2+2+4+4+4+2+2+2+2+2+4+4)).
@@ -167,8 +168,8 @@
-define(CENTRAL_DIR_SZ, (4+2+2+2+2+4+4+2)).
-define(CENTRAL_DIR_DIGITAL_SIG_MAGIC, 16#05054b50).
-define(CENTRAL_DIR_DIGITAL_SIG_SZ, (4+2)).
-
--define(CENTRAL_FILE_EXT_ATTRIBUTES, 8#644 bsl 16).
+-define(CENTRAL_REGULAR_FILE_EXT_ATTRIBUTES, 8#644 bsl 16).
+-define(CENTRAL_DIRECTORY_FILE_EXT_ATTRIBUTES, 8#744 bsl 16).
-define(CENTRAL_FILE_MAGIC, 16#02014b50).
-record(cd_file_header, {version_made_by,
@@ -1029,7 +1030,8 @@ cd_file_header_from_lh_and_pos(LH, Pos) ->
comp_size = CompSize,
uncomp_size = UncompSize,
file_name_length = FileNameLength,
- extra_field_length = ExtraFieldLength} = LH,
+ extra_field_length = ExtraFieldLength,
+ type = Type} = LH,
#cd_file_header{version_made_by = ?VERSION_MADE_BY,
version_needed = VersionNeeded,
gp_flag = GPFlag,
@@ -1044,7 +1046,11 @@ cd_file_header_from_lh_and_pos(LH, Pos) ->
file_comment_length = 0, % FileCommentLength,
disk_num_start = 0, % DiskNumStart,
internal_attr = 0, % InternalAttr,
- external_attr = ?CENTRAL_FILE_EXT_ATTRIBUTES, % ExternalAttr,
+ external_attr = % ExternalAttr
+ case Type of
+ regular -> ?CENTRAL_REGULAR_FILE_EXT_ATTRIBUTES;
+ directory -> ?CENTRAL_DIRECTORY_FILE_EXT_ATTRIBUTES
+ end,
local_header_offset = Pos}.
cd_file_header_to_bin(
@@ -1119,7 +1125,7 @@ eocd_to_bin(#eocd{disk_num = DiskNum,
ZipCommentLength:16/little>>.
%% put together a local file header
-local_file_header_from_info_method_name(#file_info{mtime = MTime},
+local_file_header_from_info_method_name(#file_info{mtime = MTime, type = Type},
UncompSize,
CompMethod, Name, GPFlag) ->
{ModDate, ModTime} = dos_date_time_from_datetime(MTime),
@@ -1132,7 +1138,8 @@ local_file_header_from_info_method_name(#file_info{mtime = MTime},
comp_size = -1,
uncomp_size = UncompSize,
file_name_length = length(Name),
- extra_field_length = 0}.
+ extra_field_length = 0,
+ type = Type}.
server_init(Parent) ->
%% we want to know if our parent dies
diff --git a/lib/stdlib/test/zip_SUITE.erl b/lib/stdlib/test/zip_SUITE.erl
index c1be2786da..1c55b32713 100644
--- a/lib/stdlib/test/zip_SUITE.erl
+++ b/lib/stdlib/test/zip_SUITE.erl
@@ -27,7 +27,7 @@
openzip_api/1, zip_api/1, open_leak/1, unzip_jar/1,
unzip_traversal_exploit/1,
compress_control/1,
- foldl/1,fd_leak/1,unicode/1]).
+ foldl/1,fd_leak/1,unicode/1,test_zip_dir/1]).
-include_lib("common_test/include/ct.hrl").
-include_lib("kernel/include/file.hrl").
@@ -40,7 +40,7 @@ all() ->
unzip_to_binary, zip_to_binary, unzip_options,
zip_options, list_dir_options, aliases, openzip_api,
zip_api, open_leak, unzip_jar, compress_control, foldl,
- unzip_traversal_exploit,fd_leak,unicode].
+ unzip_traversal_exploit,fd_leak,unicode,test_zip_dir].
groups() ->
[].
@@ -1026,3 +1026,29 @@ test_latin1_archive(DataDir) ->
FileName = [246] ++ ".txt",
ArchiveComment = [246],
zip_check(Archive, ArchiveComment, FileName, "").
+
+test_zip_dir(Config) when is_list(Config) ->
+ case {os:find_executable("unzip"), os:type()} of
+ {UnzipPath, {unix,_}} when is_list(UnzipPath)->
+ DataDir = proplists:get_value(data_dir, Config),
+ Dir = filename:join([DataDir, "test-zip", "dir-1"]),
+ TestZipOutputDir = filename:join(DataDir, "test-zip-output"),
+ TestZipOutput = filename:join(TestZipOutputDir, "test.zip"),
+ zip:create(TestZipOutput, [Dir]),
+ run_command(UnzipPath, ["-o", TestZipOutput, "-d", TestZipOutputDir]),
+ {ok, FileContent} = file:read_file(filename:join([TestZipOutputDir, Dir, "file.txt"])),
+ <<"OKOK\n">> = FileContent,
+ ok;
+ _ -> {skip, "Not Unix or unzip program not found"}
+ end.
+
+run_command(Command, Args) ->
+ Port = erlang:open_port({spawn_executable, Command}, [{args, Args}, exit_status]),
+ (fun Reciver() ->
+ receive
+ {Port,{exit_status,_}} -> ok;
+ {Port, S} -> io:format("UNZIP: ~p~n", [S]),
+ Reciver()
+ end
+ end)().
+
diff --git a/lib/stdlib/test/zip_SUITE_data/test-zip-output/.keepdir b/lib/stdlib/test/zip_SUITE_data/test-zip-output/.keepdir
new file mode 100644
index 0000000000..e69de29bb2
diff --git a/lib/stdlib/test/zip_SUITE_data/test-zip/dir-1/file.txt b/lib/stdlib/test/zip_SUITE_data/test-zip/dir-1/file.txt
new file mode 100644
index 0000000000..d65874ef66
--- /dev/null
+++ b/lib/stdlib/test/zip_SUITE_data/test-zip/dir-1/file.txt
@@ -0,0 +1 @@
+OKOK
--
2.26.2