aboutsummaryrefslogtreecommitdiffstats
path: root/lib/stdlib/test
diff options
context:
space:
mode:
Diffstat (limited to 'lib/stdlib/test')
-rw-r--r--lib/stdlib/test/Makefile1
-rw-r--r--lib/stdlib/test/erl_lint_SUITE.erl10
-rw-r--r--lib/stdlib/test/erl_pp_SUITE.erl20
-rw-r--r--lib/stdlib/test/gen_statem_SUITE.erl121
-rw-r--r--lib/stdlib/test/math_SUITE.erl92
-rw-r--r--lib/stdlib/test/qlc_SUITE.erl21
-rw-r--r--lib/stdlib/test/shell_SUITE.erl7
-rw-r--r--lib/stdlib/test/zip_SUITE.erl50
-rw-r--r--lib/stdlib/test/zip_SUITE_data/exploit.zipbin0 -> 797 bytes
9 files changed, 244 insertions, 78 deletions
diff --git a/lib/stdlib/test/Makefile b/lib/stdlib/test/Makefile
index 28c35aed55..deac04aa66 100644
--- a/lib/stdlib/test/Makefile
+++ b/lib/stdlib/test/Makefile
@@ -52,6 +52,7 @@ MODULES= \
io_proto_SUITE \
lists_SUITE \
log_mf_h_SUITE \
+ math_SUITE \
ms_transform_SUITE \
proc_lib_SUITE \
qlc_SUITE \
diff --git a/lib/stdlib/test/erl_lint_SUITE.erl b/lib/stdlib/test/erl_lint_SUITE.erl
index d916eb3eef..4ee3950882 100644
--- a/lib/stdlib/test/erl_lint_SUITE.erl
+++ b/lib/stdlib/test/erl_lint_SUITE.erl
@@ -1554,7 +1554,15 @@ guard(Config) when is_list(Config) ->
[],
{errors,[{1,erl_lint,illegal_guard_expr},
{2,erl_lint,illegal_guard_expr}],
- []}}
+ []}},
+ {guard10,
+ <<"is_port(_) -> false.
+ t(P) when port(P) -> ok.
+ ">>,
+ [],
+ {error,
+ [{2,erl_lint,{obsolete_guard_overridden,port}}],
+ [{2,erl_lint,{obsolete_guard,{port,1}}}]}}
],
[] = run(Config, Ts1),
ok.
diff --git a/lib/stdlib/test/erl_pp_SUITE.erl b/lib/stdlib/test/erl_pp_SUITE.erl
index a103f6dc53..13c5662741 100644
--- a/lib/stdlib/test/erl_pp_SUITE.erl
+++ b/lib/stdlib/test/erl_pp_SUITE.erl
@@ -1166,19 +1166,21 @@ compile(Config, Tests) ->
lists:foldl(F, [], Tests).
compile_file(Config, Test0) ->
- case compile_file(Config, Test0, ['E']) of
+ Test = ["-module(erl_pp_test).\n",
+ "-compile(export_all).\n",
+ Test0],
+ case compile_file(Config, Test, ['E']) of
{ok, RootFile} ->
File = RootFile ++ ".E",
{ok, Bin0} = file:read_file(File),
- Bin = strip_module_info(Bin0),
%% A very simple check: just try to compile the output.
- case compile_file(Config, Bin, []) of
+ case compile_file(Config, Bin0, []) of
{ok, RootFile2} ->
File2 = RootFile2 ++ ".E",
{ok, Bin1} = file:read_file(File2),
case Bin0 =:= Bin1 of
true ->
- test_max_line(binary_to_list(Bin));
+ test_max_line(binary_to_list(Bin0));
false ->
{error, file_contents_modified, {Bin0, Bin1}}
end;
@@ -1189,11 +1191,8 @@ compile_file(Config, Test0) ->
Error
end.
-compile_file(Config, Test0, Opts0) ->
+compile_file(Config, Test, Opts0) ->
FileName = filename('erl_pp_test.erl', Config),
- Test = list_to_binary(["-module(erl_pp_test). "
- "-compile(export_all). ",
- Test0]),
Opts = [export_all,return,nowarn_unused_record,{outdir,?privdir} | Opts0],
ok = file:write_file(FileName, Test),
case compile:file(FileName, Opts) of
@@ -1202,11 +1201,6 @@ compile_file(Config, Test0, Opts0) ->
Error -> Error
end.
-strip_module_info(Bin) ->
- {match, [{Start,_Len}|_]} = re:run(Bin, "module_info"),
- <<R:Start/binary,_/binary>> = Bin,
- R.
-
flat_expr1(Expr0) ->
Expr = erl_parse:new_anno(Expr0),
lists:flatten(erl_pp:expr(Expr)).
diff --git a/lib/stdlib/test/gen_statem_SUITE.erl b/lib/stdlib/test/gen_statem_SUITE.erl
index 364314f91b..1d1417c2e6 100644
--- a/lib/stdlib/test/gen_statem_SUITE.erl
+++ b/lib/stdlib/test/gen_statem_SUITE.erl
@@ -37,33 +37,32 @@ all() ->
{group, stop_handle_event},
{group, abnormal},
{group, abnormal_handle_event},
- shutdown, stop_and_reply, event_order,
+ shutdown, stop_and_reply, event_order, code_change,
{group, sys},
hibernate, enter_loop].
groups() ->
- [{start, [],
- [start1, start2, start3, start4, start5, start6, start7,
- start8, start9, start10, start11, start12, next_events]},
- {start_handle_event, [],
- [start1, start2, start3, start4, start5, start6, start7,
- start8, start9, start10, start11, start12, next_events]},
- {stop, [],
- [stop1, stop2, stop3, stop4, stop5, stop6, stop7, stop8, stop9, stop10]},
- {stop_handle_event, [],
- [stop1, stop2, stop3, stop4, stop5, stop6, stop7, stop8, stop9, stop10]},
- {abnormal, [], [abnormal1, abnormal2]},
- {abnormal_handle_event, [], [abnormal1, abnormal2]},
- {sys, [],
- [sys1, code_change,
- call_format_status,
- error_format_status, terminate_crash_format,
- get_state, replace_state]},
- {sys_handle_event, [],
- [sys1,
- call_format_status,
- error_format_status, terminate_crash_format,
- get_state, replace_state]}].
+ [{start, [], tcs(start)},
+ {start_handle_event, [], tcs(start)},
+ {stop, [], tcs(stop)},
+ {stop_handle_event, [], tcs(stop)},
+ {abnormal, [], tcs(abnormal)},
+ {abnormal_handle_event, [], tcs(abnormal)},
+ {sys, [], tcs(sys)},
+ {sys_handle_event, [], tcs(sys)}].
+
+tcs(start) ->
+ [start1, start2, start3, start4, start5, start6, start7,
+ start8, start9, start10, start11, start12, next_events];
+tcs(stop) ->
+ [stop1, stop2, stop3, stop4, stop5, stop6, stop7, stop8, stop9, stop10];
+tcs(abnormal) ->
+ [abnormal1, abnormal2];
+tcs(sys) ->
+ [sys1, call_format_status,
+ error_format_status, terminate_crash_format,
+ get_state, replace_state].
+
init_per_suite(Config) ->
Config.
@@ -461,10 +460,10 @@ abnormal2(Config) ->
{ok,Pid} = gen_statem:start_link(?MODULE, start_arg(Config, []), []),
%% bad return value in the gen_statem loop
- {{bad_return_value,badreturn},_} =
+ {{bad_return_from_state_function,badreturn},_} =
?EXPECT_FAILURE(gen_statem:call(Pid, badreturn), Reason),
receive
- {'EXIT',Pid,{bad_return_value,badreturn}} -> ok
+ {'EXIT',Pid,{bad_return_from_state_function,badreturn}} -> ok
after 5000 ->
ct:fail(gen_statem_did_not_die)
end,
@@ -633,11 +632,13 @@ sys1(Config) ->
sys:resume(Pid),
stop_it(Pid).
-code_change(Config) ->
- Mode = handle_event_function,
- {ok,Pid} = gen_statem:start(?MODULE, start_arg(Config, []), []),
+code_change(_Config) ->
+ {ok,Pid} =
+ gen_statem:start(
+ ?MODULE, {callback_mode,state_functions,[]}, []),
{idle,data} = sys:get_state(Pid),
sys:suspend(Pid),
+ Mode = handle_event_function,
sys:change_code(Pid, ?MODULE, old_vsn, Mode),
sys:resume(Pid),
{idle,{old_vsn,data,Mode}} = sys:get_state(Pid),
@@ -708,7 +709,7 @@ error_format_status(Config) ->
gen_statem:start(
?MODULE, start_arg(Config, {data,Data}), []),
%% bad return value in the gen_statem loop
- {{bad_return_value,badreturn},_} =
+ {{bad_return_from_state_function,badreturn},_} =
?EXPECT_FAILURE(gen_statem:call(Pid, badreturn), Reason),
receive
{error,_,
@@ -716,7 +717,7 @@ error_format_status(Config) ->
"** State machine"++_,
[Pid,{{call,_},badreturn},
{formatted,idle,Data},
- error,{bad_return_value,badreturn}|_]}} ->
+ error,{bad_return_from_state_function,badreturn}|_]}} ->
ok;
Other when is_tuple(Other), element(1, Other) =:= error ->
error_logger_forwarder:unregister(),
@@ -1029,11 +1030,7 @@ enter_loop(_Config) ->
end,
%% Process not started using proc_lib
- CallbackMode = state_functions,
- Pid4 =
- spawn_link(
- gen_statem, enter_loop,
- [?MODULE,[],CallbackMode,state0,[]]),
+ Pid4 = spawn_link(gen_statem, enter_loop, [?MODULE,[],state0,[]]),
receive
{'EXIT',Pid4,process_was_not_started_by_proc_lib} ->
ok
@@ -1107,21 +1104,18 @@ enter_loop(Reg1, Reg2) ->
anon -> ignore
end,
proc_lib:init_ack({ok, self()}),
- CallbackMode = state_functions,
case Reg2 of
local ->
gen_statem:enter_loop(
- ?MODULE, [], CallbackMode, state0, [], {local,armitage});
+ ?MODULE, [], state0, [], {local,armitage});
global ->
gen_statem:enter_loop(
- ?MODULE, [], CallbackMode, state0, [], {global,armitage});
+ ?MODULE, [], state0, [], {global,armitage});
via ->
gen_statem:enter_loop(
- ?MODULE, [], CallbackMode, state0, [],
- {via, dummy_via, armitage});
+ ?MODULE, [], state0, [], {via, dummy_via, armitage});
anon ->
- gen_statem:enter_loop(
- ?MODULE, [], CallbackMode, state0, [])
+ gen_statem:enter_loop(?MODULE, [], state0, [])
end.
@@ -1266,33 +1260,39 @@ init(stop_shutdown) ->
{stop,shutdown};
init(sleep) ->
?t:sleep(1000),
- {state_functions,idle,data};
+ {ok,idle,data};
init(hiber) ->
- {state_functions,hiber_idle,[]};
+ {ok,hiber_idle,[]};
init(hiber_now) ->
- {state_functions,hiber_idle,[],[hibernate]};
+ {ok,hiber_idle,[],[hibernate]};
init({data, Data}) ->
- {state_functions,idle,Data};
+ {ok,idle,Data};
init({callback_mode,CallbackMode,Arg}) ->
- case init(Arg) of
- {_,State,Data,Ops} ->
- {CallbackMode,State,Data,Ops};
- {_,State,Data} ->
- {CallbackMode,State,Data};
- Other ->
- Other
- end;
+ ets:new(?MODULE, [named_table,private]),
+ ets:insert(?MODULE, {callback_mode,CallbackMode}),
+ init(Arg);
init({map_statem,#{init := Init}=Machine}) ->
+ ets:new(?MODULE, [named_table,private]),
+ ets:insert(?MODULE, {callback_mode,handle_event_function}),
case Init() of
{ok,State,Data,Ops} ->
- {handle_event_function,State,[Data|Machine],Ops};
+ {ok,State,[Data|Machine],Ops};
{ok,State,Data} ->
- {handle_event_function,State,[Data|Machine]};
+ {ok,State,[Data|Machine]};
Other ->
Other
end;
init([]) ->
- {state_functions,idle,data}.
+ {ok,idle,data}.
+
+callback_mode() ->
+ try ets:lookup(?MODULE, callback_mode) of
+ [{callback_mode,CallbackMode}] ->
+ CallbackMode
+ catch
+ error:badarg ->
+ state_functions
+ end.
terminate(_, _State, crash_terminate) ->
exit({crash,terminate});
@@ -1568,7 +1568,12 @@ wrap_result(Result) ->
code_change(OldVsn, State, Data, CallbackMode) ->
- {CallbackMode,State,{OldVsn,Data,CallbackMode}}.
+ io:format(
+ "code_change(~p, ~p, ~p, ~p)~n", [OldVsn,State,Data,CallbackMode]),
+ ets:insert(?MODULE, {callback_mode,CallbackMode}),
+ io:format(
+ "code_change(~p, ~p, ~p, ~p)~n", [OldVsn,State,Data,CallbackMode]),
+ {ok,State,{OldVsn,Data,CallbackMode}}.
format_status(terminate, [_Pdict,State,Data]) ->
{formatted,State,Data};
diff --git a/lib/stdlib/test/math_SUITE.erl b/lib/stdlib/test/math_SUITE.erl
new file mode 100644
index 0000000000..2b29e44228
--- /dev/null
+++ b/lib/stdlib/test/math_SUITE.erl
@@ -0,0 +1,92 @@
+%%
+%% %CopyrightBegin%
+%%
+%% Copyright Ericsson AB 2007-2016. 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.
+%% You may obtain a copy of the License at
+%%
+%% http://www.apache.org/licenses/LICENSE-2.0
+%%
+%% Unless required by applicable law or agreed to in writing, software
+%% distributed under the License is distributed on an "AS IS" BASIS,
+%% WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied.
+%% See the License for the specific language governing permissions and
+%% limitations under the License.
+%%
+%% %CopyrightEnd%
+%%
+
+-module(math_SUITE).
+
+-include_lib("common_test/include/ct.hrl").
+
+%% Test server specific exports
+-export([all/0, suite/0,groups/0,init_per_suite/1, end_per_suite/1,
+ init_per_group/2,end_per_group/2,
+ init_per_testcase/2, end_per_testcase/2]).
+
+%% Test cases
+-export([floor_ceil/1]).
+
+
+suite() ->
+ [{ct_hooks,[ts_install_cth]},
+ {timetrap,{minutes,1}}].
+
+all() ->
+ [floor_ceil].
+
+groups() ->
+ [].
+
+init_per_suite(Config) ->
+ Config.
+
+end_per_suite(_Config) ->
+ ok.
+
+init_per_group(_GroupName, Config) ->
+ Config.
+
+end_per_group(_GroupName, Config) ->
+ Config.
+
+
+init_per_testcase(_Case, Config) ->
+ Config.
+
+end_per_testcase(_Case, _Config) ->
+ ok.
+
+floor_ceil(_Config) ->
+ MinusZero = 0.0/(-1.0),
+ -43.0 = do_floor_ceil(-42.1),
+ -43.0 = do_floor_ceil(-42.7),
+ 0.0 = do_floor_ceil(MinusZero),
+ 10.0 = do_floor_ceil(10.1),
+ 10.0 = do_floor_ceil(10.9),
+
+ -533.0 = do_floor_ceil(-533.0),
+ 453555.0 = do_floor_ceil(453555.0),
+
+ -58.0 = do_floor_ceil(-58),
+ 777.0 = do_floor_ceil(777),
+
+ ok.
+
+do_floor_ceil(Val) ->
+ Floor = math:floor(Val),
+ Ceil = math:ceil(Val),
+
+ true = is_float(Floor),
+ true = is_float(Ceil),
+
+ if
+ Floor =:= Ceil ->
+ Floor;
+ true ->
+ 1.0 = Ceil - Floor,
+ Floor
+ end.
diff --git a/lib/stdlib/test/qlc_SUITE.erl b/lib/stdlib/test/qlc_SUITE.erl
index 2bd940020c..8c7d5a5fcf 100644
--- a/lib/stdlib/test/qlc_SUITE.erl
+++ b/lib/stdlib/test/qlc_SUITE.erl
@@ -58,7 +58,7 @@
-export([
badarg/1, nested_qlc/1, unused_var/1, lc/1, fun_clauses/1,
filter_var/1, single/1, exported_var/1, generator_vars/1,
- nomatch/1, errors/1, pattern/1,
+ nomatch/1, errors/1, pattern/1, overridden_bif/1,
eval/1, cursor/1, fold/1, eval_unique/1, eval_cache/1, append/1,
evaluator/1, string_to_handle/1, table/1, process_dies/1,
@@ -126,7 +126,7 @@ groups() ->
[{parse_transform, [],
[badarg, nested_qlc, unused_var, lc, fun_clauses,
filter_var, single, exported_var, generator_vars,
- nomatch, errors, pattern]},
+ nomatch, errors, pattern, overridden_bif]},
{evaluation, [],
[eval, cursor, fold, eval_unique, eval_cache, append,
evaluator, string_to_handle, table, process_dies, sort,
@@ -468,6 +468,23 @@ pattern(Config) when is_list(Config) ->
-record(k, {t,v}).\n">>, Ts),
ok.
+%% Override a guard BIF with an imported or local function.
+overridden_bif(Config) ->
+ Ts = [
+ <<"[2] = qlc:e(qlc:q([P || P <- [1,2,3], port(P)])),
+ [10] = qlc:e(qlc:q([P || P <- [0,9,10,11,12],
+ (is_reference(P) andalso P > 5)])),
+ Empty = gb_sets:empty(), Single = gb_sets:singleton(42),
+ GbSets = [Empty,Single],
+ [Single] = qlc:e(qlc:q([S || S <- GbSets, size(S) =/= 0]))
+ ">>
+ ],
+ run(Config, "-import(gb_sets, [size/1]).
+ -compile({no_auto_import, [size/1, is_reference/1]}).
+ port(N) -> N rem 2 =:= 0.
+ is_reference(N) -> N rem 10 =:= 0.\n", Ts),
+ ok.
+
%% eval/2
eval(Config) when is_list(Config) ->
diff --git a/lib/stdlib/test/shell_SUITE.erl b/lib/stdlib/test/shell_SUITE.erl
index c409a6949b..07eb6772db 100644
--- a/lib/stdlib/test/shell_SUITE.erl
+++ b/lib/stdlib/test/shell_SUITE.erl
@@ -573,7 +573,7 @@ otp_5327(Config) when is_list(Config) ->
(catch evaluate(<<"<<32/unit:8>>.">>, [])),
ok.
-%% OTP-5435. sys_pre_expand not in the path.
+%% OTP-5435. compiler application not in the path.
otp_5435(Config) when is_list(Config) ->
true = <<103133:64/float>> =:=
evaluate(<<"<<103133:64/float>> = <<103133:64/float>>.">>, []),
@@ -591,8 +591,9 @@ start_node(Name) ->
otp_5435_2() ->
true = code:del_path(compiler),
- %% sys_pre_expand can no longer be found
- %% OTP-5876. But erl_expand_records can!
+ %% Make sure record evaluation is not dependent on the compiler
+ %% application being in the path.
+ %% OTP-5876.
[{attribute,_,record,{bar,_}},ok] =
scan(<<"rd(foo,{bar}),
rd(bar,{foo = (#foo{})#foo.bar}),
diff --git a/lib/stdlib/test/zip_SUITE.erl b/lib/stdlib/test/zip_SUITE.erl
index 2add5a39a2..7d90795c9e 100644
--- a/lib/stdlib/test/zip_SUITE.erl
+++ b/lib/stdlib/test/zip_SUITE.erl
@@ -25,6 +25,7 @@
zip_to_binary/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,
compress_control/1,
foldl/1]).
@@ -38,7 +39,8 @@ all() ->
[borderline, atomic, bad_zip, unzip_from_binary,
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].
+ zip_api, open_leak, unzip_jar, compress_control, foldl,
+ unzip_traversal_exploit].
groups() ->
[].
@@ -377,6 +379,52 @@ unzip_options(Config) when is_list(Config) ->
0 = delete_files([Subdir]),
ok.
+%% Test that unzip handles directory traversal exploit (OTP-13633)
+unzip_traversal_exploit(Config) ->
+ DataDir = proplists:get_value(data_dir, Config),
+ PrivDir = proplists:get_value(priv_dir, Config),
+ ZipName = filename:join(DataDir, "exploit.zip"),
+
+ %% $ zipinfo -1 test/zip_SUITE_data/exploit.zip
+ %% clash.txt
+ %% ../clash.txt
+ %% ../above.txt
+ %% subdir/../in_root_dir.txt
+
+ %% create a temp directory
+ SubDir = filename:join(PrivDir, "exploit_test"),
+ ok = file:make_dir(SubDir),
+
+ ClashFile = filename:join(SubDir,"clash.txt"),
+ AboveFile = filename:join(SubDir,"above.txt"),
+ RelativePathFile = filename:join(SubDir,"subdir/../in_root_dir.txt"),
+
+ %% unzip in SubDir
+ {ok, [ClashFile, ClashFile, AboveFile, RelativePathFile]} =
+ zip:unzip(ZipName, [{cwd,SubDir}]),
+
+ {ok,<<"This file will overwrite other file.\n">>} =
+ file:read_file(ClashFile),
+ {ok,_} = file:read_file(AboveFile),
+ {ok,_} = file:read_file(RelativePathFile),
+
+ %% clean up
+ delete_files([SubDir]),
+
+ %% create the temp directory again
+ ok = file:make_dir(SubDir),
+
+ %% unzip in SubDir
+ {ok, [ClashFile, AboveFile, RelativePathFile]} =
+ zip:unzip(ZipName, [{cwd,SubDir},keep_old_files]),
+
+ {ok,<<"This is the original file.\n">>} =
+ file:read_file(ClashFile),
+
+ %% clean up
+ delete_files([SubDir]),
+ ok.
+
%% Test unzip a jar file (OTP-7382).
unzip_jar(Config) when is_list(Config) ->
DataDir = proplists:get_value(data_dir, Config),
diff --git a/lib/stdlib/test/zip_SUITE_data/exploit.zip b/lib/stdlib/test/zip_SUITE_data/exploit.zip
new file mode 100644
index 0000000000..afb8dbd192
--- /dev/null
+++ b/lib/stdlib/test/zip_SUITE_data/exploit.zip
Binary files differ