File 1301-stdlib-Properly-sanatize-filenames-when-un-zipping.patch of Package erlang
From 10608879c81332af2d3c00db61ee173c93c1ea4e Mon Sep 17 00:00:00 2001
From: =?UTF-8?q?Lukas=20Backstr=C3=B6m?= <lukas@erlang.org>
Date: Tue, 27 May 2025 21:50:01 +0200
Subject: [PATCH] stdlib: Properly sanatize filenames when (un)zipping
According to the Zip APPNOTE filenames "MUST NOT contain a drive or
device letter, or a leading slash.". So we strip those when zipping
and unzipping.
---
lib/stdlib/src/zip.erl | 21 ++++++++++++++----
lib/stdlib/test/zip_SUITE.erl | 40 ++++++++++++++++++++++++++++-------
2 files changed, 49 insertions(+), 12 deletions(-)
diff --git a/lib/stdlib/src/zip.erl b/lib/stdlib/src/zip.erl
index 0809dbb492..b75055024c 100644
--- a/lib/stdlib/src/zip.erl
+++ b/lib/stdlib/src/zip.erl
@@ -833,12 +833,12 @@ get_filename({Name, _}, Type) ->
get_filename({Name, _, _}, Type) ->
get_filename(Name, Type);
get_filename(Name, regular) ->
- Name;
+ sanitize_filename(Name);
get_filename(Name, directory) ->
%% Ensure trailing slash
case lists:reverse(Name) of
- [$/ | _Rev] -> Name;
- Rev -> lists:reverse([$/ | Rev])
+ [$/ | _Rev] -> sanitize_filename(Name);
+ Rev -> sanitize_filename(lists:reverse([$/ | Rev]))
end.
add_cwd(_CWD, {_Name, _} = F) -> F;
@@ -1550,12 +1550,25 @@ check_dir_level([_Dir | Parts], Level) ->
get_file_name_extra(FileNameLen, ExtraLen, B, GPFlag) ->
try
<<BFileName:FileNameLen/binary, BExtra:ExtraLen/binary>> = B,
- {binary_to_chars(BFileName, GPFlag), BExtra}
+ {sanitize_filename(binary_to_chars(BFileName, GPFlag)), BExtra}
catch
_:_ ->
throw(bad_file_header)
end.
+sanitize_filename(Filename) ->
+ case filename:pathtype(Filename) of
+ relative -> Filename;
+ _ ->
+ %% With absolute or volumerelative, we drop the prefix and rejoin
+ %% the path to create a relative path
+ Relative = filename:join(tl(filename:split(Filename))),
+ error_logger:format("Illegal absolute path: ~ts, converting to ~ts~n",
+ [Filename, Relative]),
+ relative = filename:pathtype(Relative),
+ Relative
+ end.
+
%% get compressed or stored data
get_z_data(?DEFLATED, In0, FileName, CompSize, Input, Output, OpO, Z) ->
ok = zlib:inflateInit(Z, -?MAX_WBITS),
diff --git a/lib/stdlib/test/zip_SUITE.erl b/lib/stdlib/test/zip_SUITE.erl
index 97e5c660dd..1edf6c1067 100644
--- a/lib/stdlib/test/zip_SUITE.erl
+++ b/lib/stdlib/test/zip_SUITE.erl
@@ -22,7 +22,7 @@
-export([all/0, suite/0,groups/0,init_per_suite/1, end_per_suite/1,
init_per_group/2,end_per_group/2, borderline/1, atomic/1,
bad_zip/1, unzip_from_binary/1, unzip_to_binary/1,
- zip_to_binary/1,
+ zip_to_binary/1, sanitize_filenames/1,
unzip_options/1, zip_options/1, list_dir_options/1, aliases/1,
openzip_api/1, zip_api/1, open_leak/1, unzip_jar/1,
unzip_traversal_exploit/1,
@@ -42,7 +42,7 @@ all() ->
zip_options, list_dir_options, aliases, openzip_api,
zip_api, open_leak, unzip_jar, compress_control, foldl,
unzip_traversal_exploit,fd_leak,unicode,test_zip_dir,
- explicit_file_info].
+ sanitize_filenames,explicit_file_info].
groups() ->
[].
@@ -92,22 +92,27 @@ borderline_test(Size, TempDir) ->
{ok, Archive} = zip:zip(Archive, [Name]),
ok = file:delete(Name),
+ RelName = filename:join(tl(filename:split(Name))),
+
%% Verify listing and extracting.
{ok, [#zip_comment{comment = []},
- #zip_file{name = Name,
+ #zip_file{name = RelName,
info = Info,
offset = 0,
comp_size = _}]} = zip:list_dir(Archive),
Size = Info#file_info.size,
- {ok, [Name]} = zip:extract(Archive, [verbose]),
+ TempRelName = filename:join(TempDir, RelName),
+ {ok, [TempRelName]} = zip:extract(Archive, [verbose, {cwd, TempDir}]),
- %% Verify contents of extracted file.
- {ok, Bin} = file:read_file(Name),
- true = match_byte_list(X0, binary_to_list(Bin)),
+ %% Verify that absolute file was not created
+ {error, enoent} = file:read_file(Name),
+ %% Verify that relative contents of extracted file.
+ {ok, Bin} = file:read_file(TempRelName),
+ true = match_byte_list(X0, binary_to_list(Bin)),
%% Verify that Unix zip can read it. (if we have a unix zip that is!)
- zipinfo_match(Archive, Name),
+ zipinfo_match(Archive, RelName),
ok.
@@ -1054,6 +1059,25 @@ run_command(Command, Args) ->
end
end)().
+sanitize_filenames(Config) ->
+ RootDir = proplists:get_value(priv_dir, Config),
+ TempDir = filename:join(RootDir, "borderline"),
+ ok = file:make_dir(TempDir),
+
+ %% Create a zip archive /tmp/absolute in it
+ %% This file was created using the command below on Erlang/OTP 28.0
+ %% 1> rr(file), {ok, {_, Bin}} = zip:zip("absolute.zip", [{"/tmp/absolute",<<>>,#file_info{ type=regular, mtime={{1970,1,1},{0,0,0}}, size=0 }}], [memory]), rp(base64:encode(Bin)).
+ AbsZip = base64:decode(<<"UEsDBBQAAAAAAAAAIewAAAAAAAAAAAAAAAANAAAAL3RtcC9hYnNvbHV0ZVBLAQIUAxQAAAAAAAAAIewAAAAAAAAAAAAAAAANAAAAAAAAAAAAAACkAQAAAAAvdG1wL2Fic29sdXRlUEsFBgAAAAABAAEAOwAAACsAAAAAAA==">>),
+ Archive = filename:join(TempDir, "absolute.zip"),
+ ok = file:write_file(Archive, AbsZip),
+
+ TmpAbs = filename:join([TempDir, "tmp", "absolute"]),
+ {ok, [TmpAbs]} = zip:unzip(Archive, [verbose, {cwd, TempDir}]),
+ {error, enoent} = file:read_file("/tmp/absolute"),
+ {ok, <<>>} = file:read_file(TmpAbs),
+
+ ok.
+
explicit_file_info(_Config) ->
Epoch = {{1980,1,1},{0,0,0}},
FileInfo = #file_info{type=regular, size=0, mtime=Epoch},
--
2.43.0