Skip to content

Commit

Permalink
zip: List dir now returns directories
Browse files Browse the repository at this point in the history
  • Loading branch information
garazdawi committed Jun 3, 2024
1 parent 30988f6 commit 8d537f5
Show file tree
Hide file tree
Showing 2 changed files with 47 additions and 26 deletions.
46 changes: 26 additions & 20 deletions lib/stdlib/src/zip.erl
Original file line number Diff line number Diff line change
Expand Up @@ -1700,7 +1700,8 @@ get_z_files([{#zip_file{offset = Offset},_} = ZFile | Rest], Z, In0,
{In2, Acc1} =
case get_z_file(In1, Z, Input, Output, OpO, FB,
CWD, ZFile, Filter) of
{file, GZD, Inx} -> {Inx, [GZD | Acc0]};
{Type, GZD, Inx} when Type =:= file; Type =:= dir ->
{Inx, [GZD | Acc0]};
{_, Inx} -> {Inx, Acc0}
end,
get_z_files(Rest, Z, In2, Opts, Acc1);
Expand Down Expand Up @@ -1742,9 +1743,8 @@ get_z_file(In0, Z, Input, Output, OpO, FB,
true ->
case lists:last(FileName) of
$/ ->
%% perhaps this should always be done?
Output({ensure_dir,FileName1},[]),
{dir, In3};
Out1 = Output({ensure_path,FileName1},[]),
{dir, Out1, In3};
_ ->
%% FileInfo = local_file_header_to_file_info(LH)
%%{Out, In4, CRC, UncompSize} =
Expand All @@ -1768,18 +1768,24 @@ get_z_file(In0, Z, Input, Output, OpO, FB,

%% make sure FileName doesn't have relative path that points over CWD
check_valid_location(CWD, FileName) ->
TrailingSlash = case lists:last(FileName) of
$/ -> "/";
_ -> ""
end,
%% check for directory traversal exploit
case check_dir_level(filename:split(FileName), 0) of
{FileOrDir,Level} when Level < 0 ->
CWD1 = if CWD == "" -> "./";
true -> CWD
end,
error_logger:format("Illegal path: ~ts, extracting in ~ts~n",
[add_cwd(CWD,FileName),CWD1]),
{false,add_cwd(CWD, FileOrDir)};
_ ->
{true,add_cwd(CWD, FileName)}
end.
{IsValid, Cwd, Name} =
case check_dir_level(filename:split(FileName), 0) of
{FileOrDir,Level} when Level < 0 ->
CWD1 = if CWD == "" -> "./";
true -> CWD
end,
error_logger:format("Illegal path: ~ts, extracting in ~ts~n",
[add_cwd(CWD,FileName),CWD1]),
{false, CWD, FileOrDir};
_ ->
{true, CWD, FileName}
end,
{IsValid, string:trim(add_cwd(Cwd, Name), trailing, "/") ++ TrailingSlash}.

check_dir_level([FileOrDir], Level) ->
{FileOrDir,Level};
Expand Down Expand Up @@ -2088,8 +2094,8 @@ binary_io({list_dir, _F}, _B) ->
[];
binary_io({set_file_info, _F, _FI}, B) ->
B;
binary_io({ensure_dir, _Dir}, B) ->
B.
binary_io({ensure_path, Dir}, _B) ->
{Dir, <<>>}.

file_io({file_info, F}, _) ->
case file:read_file_info(F) of
Expand Down Expand Up @@ -2149,6 +2155,6 @@ file_io({set_file_info, F, FI}, H) ->
ok -> H;
{error, Error} -> throw(Error)
end;
file_io({ensure_dir, Dir}, H) ->
ok = filelib:ensure_dir(Dir),
H.
file_io({ensure_path, Dir}, _H) ->
ok = filelib:ensure_path(Dir),
Dir.
27 changes: 21 additions & 6 deletions lib/stdlib/test/zip_SUITE.erl
Original file line number Diff line number Diff line change
Expand Up @@ -380,18 +380,22 @@ unzip_jar(Config) when is_list(Config) ->
%% create a temp directory
Subdir = filename:join(PrivDir, "jartest"),
ok = file:make_dir(Subdir),
ok = file:set_cwd(Subdir),

FList = ["META-INF/MANIFEST.MF","test.txt"],

{ok, RetList} = zip:unzip(JarFile),
{ok, RetList} = zip:unzip(JarFile, [{cwd, Subdir}]),

%% Verify.
lists:foreach(fun(F)-> {ok,B} = file:read_file(filename:join(DataDir, F)),
{ok,B} = file:read_file(filename:join(Subdir, F)) end,
FList),
lists:foreach(fun(F)-> ok = file:delete(F) end,
RetList),
lists:foreach(fun(F)->
case lists:last(F) =:= $/ of
true -> ok = file:del_dir(F);
false -> ok = file:delete(F)
end
end,
lists:reverse(RetList)),

%% Clean up and verify no more files.
0 = delete_files([Subdir]),
Expand Down Expand Up @@ -528,6 +532,7 @@ unzip_to_binary(Config) when is_list(Config) ->
PrivDir = proplists:get_value(priv_dir, Config),
WorkDir = filename:join(PrivDir, "unzip_to_binary"),
_ = file:make_dir(WorkDir),
_ = file:make_dir(filename:join(DataDir, "empty")),

ok = file:set_cwd(WorkDir),
Long = filename:join(DataDir, "abc.zip"),
Expand All @@ -536,7 +541,16 @@ unzip_to_binary(Config) when is_list(Config) ->
{ok, FBList} = zip:unzip(Long, [memory]),

%% Verify.
lists:foreach(fun({F,B}) -> {ok,B}=file:read_file(filename:join(DataDir, F))
lists:foreach(fun({F,B}) ->
Filename = filename:join(DataDir, F),
case lists:last(F) =:= $/ of
true ->
<<>> = B,
{ok, #file_info{ type = directory}} =
file:read_file_info(Filename);
false ->
{ok,B}=file:read_file(filename:join(DataDir, F))
end
end, FBList),

%% Make sure no files created in cwd
Expand Down Expand Up @@ -609,11 +623,12 @@ unzip_from_binary(Config) when is_list(Config) ->
Quote = "quotes/rain.txt",
Wikipedia = "wikipedia.txt",
EmptyFile = "emptyFile",
EmptyDir = "empty/",
file:set_cwd(ExtractDir),

%% Read a zip file into a binary and extract from the binary.
{ok, Bin} = file:read_file(Archive),
{ok, [FileName,Quote,Wikipedia,EmptyFile]} = zip:unzip(Bin),
{ok, [FileName,Quote,EmptyDir,Wikipedia,EmptyFile]} = zip:unzip(Bin),

%% Verify.
DestFilename = filename:join(ExtractDir, "abc.txt"),
Expand Down

0 comments on commit 8d537f5

Please sign in to comment.