File 0718-stdlib-Mark-zip-files-as-Unix-compatible.patch of Package erlang
From 0992d6174e0e2eb594fb48012fed9f142397fc30 Mon Sep 17 00:00:00 2001
From: =?UTF-8?q?John=20H=C3=B6gberg?= <john@erlang.org>
Date: Mon, 17 Feb 2020 14:57:35 +0100
Subject: [PATCH] stdlib: Mark zip files as Unix-compatible
Tools like 'zip' and 'unzip' mangle unicode paths for zip files
marked as compatible with DOS/OS2 (specifically), even when all
the appropriate flags are set.
Windows does the right thing regardless, so we'll mark all archives
as Unix-compatible.
---
lib/stdlib/src/zip.erl | 7 +++--
lib/stdlib/test/zip_SUITE.erl | 73 ++++++++++++++++++-------------------------
2 files changed, 36 insertions(+), 44 deletions(-)
diff --git a/lib/stdlib/src/zip.erl b/lib/stdlib/src/zip.erl
index 688467d992..8f703d9d1a 100644
--- a/lib/stdlib/src/zip.erl
+++ b/lib/stdlib/src/zip.erl
@@ -142,6 +142,8 @@
-define(PKWARE_RESERVED, 11).
-define(BZIP2_COMPRESSED, 12).
+%% Version 2.0, attribute compatibility type 3 (Unix)
+-define(VERSION_MADE_BY, 20 bor (3 bsl 8)).
-define(GP_BIT_11, 16#800). % Filename and file comment UTF-8 encoded.
%% zip-file records
@@ -166,6 +168,7 @@
-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_FILE_MAGIC, 16#02014b50).
-record(cd_file_header, {version_made_by,
@@ -1027,7 +1030,7 @@ cd_file_header_from_lh_and_pos(LH, Pos) ->
uncomp_size = UncompSize,
file_name_length = FileNameLength,
extra_field_length = ExtraFieldLength} = LH,
- #cd_file_header{version_made_by = 20,
+ #cd_file_header{version_made_by = ?VERSION_MADE_BY,
version_needed = VersionNeeded,
gp_flag = GPFlag,
comp_method = CompMethod,
@@ -1041,7 +1044,7 @@ 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 = 0, % ExternalAttr,
+ external_attr = ?CENTRAL_FILE_EXT_ATTRIBUTES, % ExternalAttr,
local_header_offset = Pos}.
cd_file_header_to_bin(
diff --git a/lib/stdlib/test/zip_SUITE.erl b/lib/stdlib/test/zip_SUITE.erl
index 6272798c17..095967177b 100644
--- a/lib/stdlib/test/zip_SUITE.erl
+++ b/lib/stdlib/test/zip_SUITE.erl
@@ -105,49 +105,32 @@ borderline_test(Size, TempDir) ->
%% Verify that Unix zip can read it. (if we have a unix zip that is!)
- unzip_list(Archive, Name),
+ zipinfo_match(Archive, Name),
ok.
-unzip_list(Archive, Name) ->
- case unix_unzip_exists() of
- true ->
- unzip_list1(Archive, Name);
+zipinfo_match(Archive, Name) ->
+ case check_zipinfo_exists() of
+ true ->
+ Encoding = file:native_name_encoding(),
+ Expect = unicode:characters_to_binary(Name ++ "\n",
+ Encoding, Encoding),
+ cmd_expect("zipinfo -1 " ++ Archive, Expect);
_ ->
ok
end.
-%% Used to do os:find_executable() to check if unzip exists, but on
-%% some hosts that would give an unzip program which did not take the
-%% "-Z" option.
-%% Here we check that "unzip -Z" (which should display usage) and
-%% check that it exists with status 0.
-unix_unzip_exists() ->
- case os:type() of
- {unix,_} ->
- Port = open_port({spawn,"unzip -Z > /dev/null"}, [exit_status]),
- receive
- {Port,{exit_status,0}} ->
- true;
- {Port,{exit_status,_Fail}} ->
- false
- end;
- _ ->
- false
- end.
-
-unzip_list1(Archive, Name) ->
- Expect = Name ++ "\n",
- cmd_expect("unzip -Z -1 " ++ Archive, Expect).
+check_zipinfo_exists() ->
+ is_list(os:find_executable("zipinfo")).
cmd_expect(Cmd, Expect) ->
- Port = open_port({spawn, make_cmd(Cmd)}, [stream, in, eof]),
- get_data(Port, Expect).
+ Port = open_port({spawn, make_cmd(Cmd)}, [stream, in, binary, eof]),
+ get_data(Port, Expect, <<>>).
-get_data(Port, Expect) ->
+get_data(Port, Expect, Acc) ->
receive
{Port, {data, Bytes}} ->
- get_data(Port, match_output(Bytes, Expect, Port));
+ get_data(Port, Expect, <<Acc/binary, Bytes/binary>>);
{Port, eof} ->
Port ! {self(), close},
receive
@@ -160,21 +143,17 @@ get_data(Port, Expect) ->
after 1 -> % force context switch
ok
end,
- match_output(eof, Expect, Port)
+ match_output(Acc, Expect, Port)
end.
-match_output([C|Output], [C|Expect], Port) ->
+match_output(<<C, Output/bits>>, <<C,Expect/bits>>, Port) ->
match_output(Output, Expect, Port);
-match_output([_|_], [_|_], Port) ->
+match_output(<<_, _/bits>>, <<_, _/bits>>, Port) ->
kill_port_and_fail(Port, badmatch);
-match_output([X|Output], [], Port) ->
- kill_port_and_fail(Port, {too_much_data, [X|Output]});
-match_output([], Expect, _Port) ->
- Expect;
-match_output(eof, [], _Port) ->
- [];
-match_output(eof, Expect, Port) ->
- kill_port_and_fail(Port, {unexpected_end_of_input, Expect}).
+match_output(<<_, _/bits>>=Rest, <<>>, Port) ->
+ kill_port_and_fail(Port, {too_much_data, Rest});
+match_output(<<>>, <<>>, _Port) ->
+ ok.
kill_port_and_fail(Port, Reason) ->
unlink(Port),
@@ -925,6 +904,7 @@ unicode(Config) ->
test_archive_comment(DataDir),
test_bad_comment(DataDir),
test_latin1_archive(DataDir),
+ test_filename_compatibility(),
case has_zip() of
false ->
{comment, "No zip program found; skipping some tests"};
@@ -938,6 +918,15 @@ unicode(Config) ->
end
end.
+test_filename_compatibility() ->
+ FancyName = "üñíĉòdë한",
+ Archive = "test.zip",
+
+ {ok, Archive} = zip:zip(Archive, [{FancyName, <<"test">>}]),
+ zipinfo_match(Archive, FancyName),
+
+ ok.
+
test_file_comment(DataDir) ->
Archive = filename:join(DataDir, "zip_file_comment.zip"),
Comments = ["a", [246], [1024]],
--
2.16.4