File: zip-sanitize-paths.patch

package info (click to toggle)
erlang 1%3A25.2.3%2Bdfsg-1%2Bdeb12u3
  • links: PTS, VCS
  • area: main
  • in suites: bookworm
  • size: 219,972 kB
  • sloc: erlang: 1,440,803; xml: 473,412; ansic: 392,382; cpp: 164,287; makefile: 17,392; sh: 13,842; lisp: 9,675; java: 8,578; asm: 6,426; perl: 5,527; python: 5,469; javascript: 610; pascal: 126; sed: 72; php: 3
file content (133 lines) | stat: -rw-r--r-- 5,320 bytes parent folder | download
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
From: Lukas Backstrom <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.
Origin: https://github.com/erlang/otp/commit/ee67d46285394db95133709cef74b0c462d665aa
Bug-Debian: https://bugs.debian.org/1107939
Bug-Debian-Security: https://security-tracker.debian.org/tracker/CVE-2025-4748

--- a/lib/stdlib/src/zip.erl
+++ b/lib/stdlib/src/zip.erl
@@ -826,12 +826,12 @@
 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;
@@ -1531,12 +1531,25 @@
 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),
--- 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,
@@ -40,7 +40,8 @@
      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,test_zip_dir].
+     unzip_traversal_exploit,fd_leak,unicode,test_zip_dir,
+     sanitize_filenames].
 
 groups() -> 
     [].
@@ -90,22 +91,27 @@
     {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.
 
@@ -1052,3 +1058,21 @@
              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.
\ No newline at end of file