Skip to content

Commit

Permalink
stdlib: Fix zip:unzip on read-only directory with content
Browse files Browse the repository at this point in the history
The permissions were set on extrected directories before the files within
were extracted, making it impossible to create the files within. This
commit delays all directory permissions to after all files/directories
have been created so that they can all be set.

Closed #9332
  • Loading branch information
garazdawi committed Jan 23, 2025
1 parent a47de22 commit 8a73aad
Show file tree
Hide file tree
Showing 2 changed files with 51 additions and 16 deletions.
50 changes: 37 additions & 13 deletions lib/stdlib/src/zip.erl
Original file line number Diff line number Diff line change
Expand Up @@ -651,12 +651,12 @@ do_zip(F, Files, Options) ->
{Out1, LHS, Pos} = put_z_files(Files, Z, Out0, 0, Opts, []),
zlib:close(Z),
Out2 = put_central_dir(LHS, Pos, Out1, Opts),
Out3 = Output({close, F}, Out2),
Out3 = Output(flush, Output({close, F}, Out2)),
{ok, Out3}
catch
C:R:Stk ->
?CATCH(zlib:close(Z)),
Output({close, F}, Out0),
Output(flush, Output({close, F}, Out0)),
erlang:raise(C, R, Stk)
end.

Expand Down Expand Up @@ -2216,8 +2216,8 @@ cd_file_header_to_file_info(FileName,

%% get all files using file list
%% (the offset list is already filtered on which file to get... isn't it?)
get_z_files([], _Z, _In, _Opts, Acc) ->
lists:reverse(Acc);
get_z_files([], _Z, _In, #unzip_opts{ output = Output }, Acc) ->
flush_and_reverse(Output, Acc, []);
get_z_files([#zip_comment{comment = _} | Rest], Z, In, Opts, Acc) ->
get_z_files(Rest, Z, In, Opts, Acc);
get_z_files([{#zip_file{offset = Offset} = ZipFile, ZipExtra} | Rest], Z, In0,
Expand All @@ -2239,6 +2239,11 @@ get_z_files([{#zip_file{offset = Offset} = ZipFile, ZipExtra} | Rest], Z, In0,
get_z_files(Rest, Z, In0, Opts, Acc0)
end.

flush_and_reverse(Output, [H|T], Acc) ->
flush_and_reverse(Output, T, [Output(flush, H) | Acc]);
flush_and_reverse(_Output, [], Acc) ->
Acc.

%% get a file from the archive, reading chunks
get_z_file(In0, Z, Input, Output, OpO, FB,
CWD, {ZipFile,ZipExtra}, Filter, SkipDirs, ExtraOpts) ->
Expand Down Expand Up @@ -2278,8 +2283,8 @@ get_z_file(In0, Z, Input, Output, OpO, FB,

IsDir = lists:last(FileName) =:= $/,

case ReadAndWrite andalso not (IsDir andalso SkipDirs) of
true ->
case ReadAndWrite andalso not (IsDir andalso SkipDirs) of
true ->
{Type, Out, In} =
case lists:last(FileName) of
$/ ->
Expand All @@ -2300,11 +2305,20 @@ get_z_file(In0, Z, Input, Output, OpO, FB,
Output({file_info, FileNameWithCwd}, Out),
LHExtra, ZipFile),

Out2 = Output({set_file_info, FileNameWithCwd, FileInfo, [{time, local}]}, Out),
SetFileInfo =
fun(O) -> Output({set_file_info, FileNameWithCwd, FileInfo, [{time, local}]}, O) end,

Out2 =
if Type =:= dir ->
Output({delay, SetFileInfo}, Out);
Type =:= file ->
SetFileInfo(Out)
end,

{Type, Out2, In};
false ->
{ignore, In3}
end;
false ->
{ignore, In3}
end;
Else ->
throw({bad_local_file_header, Else})
end.
Expand Down Expand Up @@ -2678,7 +2692,12 @@ binary_io({set_file_info, _F, _FI}, B) ->
binary_io({set_file_info, _F, _FI, _O}, B) ->
B;
binary_io({ensure_path, Dir}, _B) ->
{Dir, <<>>}.
{Dir, <<>>};
binary_io({delay, Fun}, B) ->
%% We don't delay things in binary_io
Fun(B);
binary_io(flush, FN) ->
FN.

file_io({file_info, F}, _) ->
case file:read_file_info(F) of
Expand Down Expand Up @@ -2733,7 +2752,7 @@ file_io({pwrite, Pos, Data}, H) ->
end;
file_io({close, FN}, H) ->
case file:close(H) of
ok -> FN;
ok -> #{ name => FN, flush => []};
{error, Error} -> throw(Error)
end;
file_io(close, H) ->
Expand All @@ -2755,4 +2774,9 @@ file_io({set_file_info, F, FI, O}, H) ->
end;
file_io({ensure_path, Dir}, _H) ->
ok = filelib:ensure_path(Dir),
Dir.
#{ name => Dir, flush => []};
file_io({delay, Fun}, #{flush := Flush} = H) ->
H#{flush := [Fun | Flush] };
file_io(flush, #{ name := Name, flush := Flush }) ->
[F(Name) || F <- Flush],
Name.
17 changes: 14 additions & 3 deletions lib/stdlib/test/zip_SUITE.erl
Original file line number Diff line number Diff line change
Expand Up @@ -1276,7 +1276,12 @@ mode(Config) ->

Directory = filename:join(PrivDir,"dir"),
ok = file:make_dir(Directory),
{ok, DirFI } = file:read_file_info(Executable),
{ok, DirFI } = file:read_file_info(Directory),

NestedFile = filename:join(Directory, "nested"),
file:write_file(NestedFile, "bbb"),
{ok, NestedFI } = file:read_file_info(NestedFile),

ok = file:write_file_info(Directory, DirFI#file_info{ mode = 8#111 bor 8#400 }),
{ok, #file_info{ mode = OrigDirMode }} = file:read_file_info(Directory),

Expand All @@ -1286,16 +1291,18 @@ mode(Config) ->

OrigExecMode777 = OrigExecMode band 8#777,
OrigDirMode777 = OrigDirMode band 8#777,
OrigNestedFileMode777 = NestedFI#file_info.mode band 8#777,

?assertMatch(
{ok, [#zip_comment{},
#zip_file{ name = "dir/", info = #file_info{ mode = OrigDirMode777 }},
#zip_file{ name = "dir/nested", info = #file_info{ mode = OrigNestedFileMode777 }},
#zip_file{ name = "exec", info = #file_info{ mode = OrigExecMode777 }} ]},
zip:list_dir(Archive)),

ok = file:make_dir(ExtractDir),
?assertMatch(
{ok, ["dir/","exec"]}, unzip(Config, Archive, [{cwd,ExtractDir}])),
{ok, ["dir/","dir/nested","exec"]}, unzip(Config, Archive, [{cwd,ExtractDir}])),

case un_z64(get_value(unzip, Config)) =/= unemzip of
true ->
Expand All @@ -1305,7 +1312,11 @@ mode(Config) ->

{ok,#file_info{ mode = DirMode }} =
file:read_file_info(filename:join(ExtractDir,"dir")),
?assertEqual(DirMode band 8#777, OrigDirMode777);
?assertEqual(DirMode band 8#777, OrigDirMode777),

{ok,#file_info{ mode = NestedMode }} =
file:read_file_info(filename:join(ExtractDir,"dir/nested")),
?assertEqual(NestedMode band 8#777, OrigNestedFileMode777);
false ->
%% emzip does not support mode
ok
Expand Down

0 comments on commit 8a73aad

Please sign in to comment.