aboutsummaryrefslogtreecommitdiffstats
path: root/lib/stdlib/src/zip.erl
diff options
context:
space:
mode:
Diffstat (limited to 'lib/stdlib/src/zip.erl')
-rw-r--r--lib/stdlib/src/zip.erl146
1 files changed, 82 insertions, 64 deletions
diff --git a/lib/stdlib/src/zip.erl b/lib/stdlib/src/zip.erl
index f8ba6f18e9..81f927f399 100644
--- a/lib/stdlib/src/zip.erl
+++ b/lib/stdlib/src/zip.erl
@@ -1,7 +1,7 @@
%%
%% %CopyrightBegin%
%%
-%% Copyright Ericsson AB 2006-2016. All Rights Reserved.
+%% Copyright Ericsson AB 2006-2017. All Rights Reserved.
%%
%% Licensed under the Apache License, Version 2.0 (the "License");
%% you may not use this file except in compliance with the License.
@@ -179,19 +179,6 @@
external_attr,
local_header_offset}).
-%% Unix extra fields (not yet supported)
--define(UNIX_EXTRA_FIELD_TAG, 16#000d).
--record(unix_extra_field, {atime,
- mtime,
- uid,
- gid}).
-
-%% extended timestamps (not yet supported)
--define(EXTENDED_TIMESTAMP_TAG, 16#5455).
-%% -record(extended_timestamp, {mtime,
-%% atime,
-%% ctime}).
-
-define(END_OF_CENTRAL_DIR_MAGIC, 16#06054b50).
-define(END_OF_CENTRAL_DIR_SZ, (4+2+2+2+2+4+4+2)).
@@ -279,7 +266,8 @@ do_openzip_get(F, #openzip{files = Files, in = In0, input = Input,
case file_name_search(F, Files) of
{#zip_file{offset = Offset},_}=ZFile ->
In1 = Input({seek, bof, Offset}, In0),
- case get_z_file(In1, Z, Input, Output, [], fun silent/1, CWD, ZFile) of
+ case get_z_file(In1, Z, Input, Output, [], fun silent/1,
+ CWD, ZFile, fun all/1) of
{file, R, _In2} -> {ok, R};
_ -> throw(file_not_found)
end;
@@ -380,9 +368,12 @@ do_unzip(F, Options) ->
{Info, In1} = get_central_dir(In0, RawIterator, Input),
%% get rid of zip-comment
Z = zlib:open(),
- Files = get_z_files(Info, Z, In1, Opts, []),
- zlib:close(Z),
- Input(close, In1),
+ Files = try
+ get_z_files(Info, Z, In1, Opts, [])
+ after
+ zlib:close(Z),
+ Input(close, In1)
+ end,
{ok, Files}.
%% Iterate over all files in a zip archive
@@ -459,11 +450,20 @@ do_zip(F, Files, Options) ->
#zip_opts{output = Output, open_opts = OpO} = Opts,
Out0 = Output({open, F, OpO}, []),
Z = zlib:open(),
- {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),
- {ok, Out3}.
+ try
+ {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),
+ {ok, Out3}
+ catch
+ C:R ->
+ Stk = erlang:get_stacktrace(),
+ zlib:close(Z),
+ Output({close, F}, Out0),
+ erlang:raise(C, R, Stk)
+ end.
+
%% List zip directory contents
%%
@@ -1378,12 +1378,7 @@ cd_file_header_to_file_info(FileName,
gid = 0},
add_extra_info(FI, ExtraField).
-%% add extra info to file (some day when we implement it)
-add_extra_info(FI, <<?EXTENDED_TIMESTAMP_TAG:16/little, _Rest/binary>>) ->
- FI; % not yet supported, some other day...
-add_extra_info(FI, <<?UNIX_EXTRA_FIELD_TAG:16/little, Rest/binary>>) ->
- _UnixExtra = unix_extra_field_and_var_from_bin(Rest),
- FI; % not yet supported, and not widely used
+%% Currently, we ignore all the extra fields.
add_extra_info(FI, _) ->
FI.
@@ -1403,9 +1398,10 @@ get_z_files([{#zip_file{offset = Offset},_} = ZFile | Rest], Z, In0,
true ->
In1 = Input({seek, bof, Offset}, In0),
{In2, Acc1} =
- case get_z_file(In1, Z, Input, Output, OpO, FB, CWD, ZFile) of
+ case get_z_file(In1, Z, Input, Output, OpO, FB,
+ CWD, ZFile, Filter) of
{file, GZD, Inx} -> {Inx, [GZD | Acc0]};
- {dir, Inx} -> {Inx, Acc0}
+ {_, Inx} -> {Inx, Acc0}
end,
get_z_files(Rest, Z, In2, Opts, Acc1);
_ ->
@@ -1413,7 +1409,8 @@ get_z_files([{#zip_file{offset = Offset},_} = ZFile | Rest], Z, In0,
end.
%% get a file from the archive, reading chunks
-get_z_file(In0, Z, Input, Output, OpO, FB, CWD, {ZipFile,Extra}) ->
+get_z_file(In0, Z, Input, Output, OpO, FB,
+ CWD, {ZipFile,Extra}, Filter) ->
case Input({read, ?LOCAL_FILE_HEADER_SZ}, In0) of
{eof, In1} ->
{eof, In1};
@@ -1433,29 +1430,64 @@ get_z_file(In0, Z, Input, Output, OpO, FB, CWD, {ZipFile,Extra}) ->
end,
{BFileN, In3} = Input({read, FileNameLen + ExtraLen}, In1),
{FileName, _} = get_file_name_extra(FileNameLen, ExtraLen, BFileN),
- FileName1 = add_cwd(CWD, FileName),
- case lists:last(FileName) of
- $/ ->
- %% perhaps this should always be done?
- Output({ensure_dir,FileName1},[]),
- {dir, In3};
- _ ->
- %% FileInfo = local_file_header_to_file_info(LH)
- %%{Out, In4, CRC, UncompSize} =
- {Out, In4, CRC, _UncompSize} =
- get_z_data(CompMethod, In3, FileName1,
- CompSize, Input, Output, OpO, Z),
- In5 = skip_z_data_descriptor(GPFlag, Input, In4),
- %% TODO This should be fixed some day:
- %% In5 = Input({set_file_info, FileName, FileInfo#file_info{size=UncompSize}}, In4),
- FB(FileName),
- CRC =:= CRC32 orelse throw({bad_crc, FileName}),
- {file, Out, In5}
+ ReadAndWrite =
+ case check_valid_location(CWD, FileName) of
+ {true,FileName1} ->
+ true;
+ {false,FileName1} ->
+ Filter({ZipFile#zip_file{name = FileName1},Extra})
+ end,
+ case ReadAndWrite of
+ true ->
+ case lists:last(FileName) of
+ $/ ->
+ %% perhaps this should always be done?
+ Output({ensure_dir,FileName1},[]),
+ {dir, In3};
+ _ ->
+ %% FileInfo = local_file_header_to_file_info(LH)
+ %%{Out, In4, CRC, UncompSize} =
+ {Out, In4, CRC, _UncompSize} =
+ get_z_data(CompMethod, In3, FileName1,
+ CompSize, Input, Output, OpO, Z),
+ In5 = skip_z_data_descriptor(GPFlag, Input, In4),
+ %% TODO This should be fixed some day:
+ %% In5 = Input({set_file_info, FileName,
+ %% FileInfo#file_info{size=UncompSize}}, In4),
+ FB(FileName),
+ CRC =:= CRC32 orelse throw({bad_crc, FileName}),
+ {file, Out, In5}
+ end;
+ false ->
+ {ignore, In3}
end;
_ ->
throw(bad_local_file_header)
end.
+%% make sure FileName doesn't have relative path that points over CWD
+check_valid_location(CWD, FileName) ->
+ %% 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.
+
+check_dir_level([FileOrDir], Level) ->
+ {FileOrDir,Level};
+check_dir_level(["." | Parts], Level) ->
+ check_dir_level(Parts, Level);
+check_dir_level([".." | Parts], Level) ->
+ check_dir_level(Parts, Level-1);
+check_dir_level([_Dir | Parts], Level) ->
+ check_dir_level(Parts, Level+1).
get_file_name_extra(FileNameLen, ExtraLen, B) ->
case B of
@@ -1534,20 +1566,6 @@ dos_date_time_from_datetime({{Year, Month, Day}, {Hour, Min, Sec}}) ->
<<DosDate:16>> = <<YearFrom1980:7, Month:4, Day:5>>,
{DosDate, DosTime}.
-unix_extra_field_and_var_from_bin(<<TSize:16/little,
- ATime:32/little,
- MTime:32/little,
- UID:16/little,
- GID:16/little,
- Var:TSize/binary>>) ->
- {#unix_extra_field{atime = ATime,
- mtime = MTime,
- uid = UID,
- gid = GID},
- Var};
-unix_extra_field_and_var_from_bin(_) ->
- throw(bad_unix_extra_field).
-
%% A pwrite-like function for iolists (used by memory-option)
pwrite_binary(B, Pos, Bin) when byte_size(B) =:= Pos ->