aboutsummaryrefslogtreecommitdiffstats
path: root/lib/stdlib/test
diff options
context:
space:
mode:
Diffstat (limited to 'lib/stdlib/test')
-rw-r--r--lib/stdlib/test/edlin_expand_SUITE.erl165
-rw-r--r--lib/stdlib/test/epp_SUITE.erl32
-rw-r--r--lib/stdlib/test/erl_eval_SUITE.erl37
-rw-r--r--lib/stdlib/test/erl_expand_records_SUITE.erl21
-rw-r--r--lib/stdlib/test/erl_lint_SUITE.erl49
-rw-r--r--lib/stdlib/test/erl_lint_SUITE_data/predef.erl67
-rw-r--r--lib/stdlib/test/erl_lint_SUITE_data/predef2.erl56
-rw-r--r--lib/stdlib/test/erl_pp_SUITE.erl23
-rw-r--r--lib/stdlib/test/ets_SUITE.erl18
-rw-r--r--lib/stdlib/test/expand_test.erl6
-rw-r--r--lib/stdlib/test/expand_test1.erl4
-rw-r--r--lib/stdlib/test/lists_SUITE.erl12
-rw-r--r--lib/stdlib/test/stdlib_SUITE.erl73
13 files changed, 422 insertions, 141 deletions
diff --git a/lib/stdlib/test/edlin_expand_SUITE.erl b/lib/stdlib/test/edlin_expand_SUITE.erl
index 0cd2688e2e..43c980e994 100644
--- a/lib/stdlib/test/edlin_expand_SUITE.erl
+++ b/lib/stdlib/test/edlin_expand_SUITE.erl
@@ -26,11 +26,11 @@
-include_lib("test_server/include/test_server.hrl").
-% Default timetrap timeout (set in init_per_testcase).
+%% Default timetrap timeout (set in init_per_testcase).
-define(default_timeout, ?t:minutes(1)).
init_per_testcase(_Case, Config) ->
- ?line Dog = ?t:timetrap(?default_timeout),
+ Dog = ?t:timetrap(?default_timeout),
[{watchdog, Dog} | Config].
end_per_testcase(_Case, Config) ->
Dog = ?config(watchdog, Config),
@@ -67,20 +67,21 @@ normal(doc) ->
normal(suite) ->
[];
normal(Config) when is_list(Config) ->
- ?line {module,expand_test} = c:l(expand_test),
- % These tests might fail if another module with the prefix "expand_" happens
- % to also be loaded.
- ?line {yes, "test:", []} = edlin_expand:expand(lists:reverse("expand_")),
- ?line {no, [], []} = edlin_expand:expand(lists:reverse("expandXX_")),
- ?line {no,[],
- [{"a_fun_name",1},
- {"a_less_fun_name",1},
- {"b_comes_after_a",1},
- {"module_info",0},
- {"module_info",1}]} = edlin_expand:expand(lists:reverse("expand_test:")),
- ?line {yes,[],[{"a_fun_name",1},
- {"a_less_fun_name",1}]} = edlin_expand:expand(
- lists:reverse("expand_test:a_")),
+ {module,expand_test} = c:l(expand_test),
+ %% These tests might fail if another module with the prefix
+ %% "expand_" happens to also be loaded.
+ {yes, "test:", []} = do_expand("expand_"),
+ {no, [], []} = do_expand("expandXX_"),
+ {no,[],
+ [{"a_fun_name",1},
+ {"a_less_fun_name",1},
+ {"b_comes_after_a",1},
+ {"expand0arity_entirely",0},
+ {"module_info",0},
+ {"module_info",1}]} = do_expand("expand_test:"),
+ {yes,[],[{"a_fun_name",1},
+ {"a_less_fun_name",1}]} = do_expand("expand_test:a_"),
+ {yes,"arity_entirely()",[]} = do_expand("expand_test:expand0"),
ok.
quoted_fun(doc) ->
@@ -88,38 +89,35 @@ quoted_fun(doc) ->
quoted_fun(suite) ->
[];
quoted_fun(Config) when is_list(Config) ->
- ?line {module,expand_test} = c:l(expand_test),
- ?line {module,expand_test1} = c:l(expand_test1),
+ {module,expand_test} = c:l(expand_test),
+ {module,expand_test1} = c:l(expand_test1),
%% should be no colon after test this time
- ?line {yes, "test", []} = edlin_expand:expand(lists:reverse("expand_")),
- ?line {no, [], []} = edlin_expand:expand(lists:reverse("expandXX_")),
- ?line {no,[],[{"'#weird-fun-name'",0},
- {"'Quoted_fun_name'",0},
- {"'Quoted_fun_too'",0},
- {"a_fun_name",1},
- {"a_less_fun_name",1},
- {"b_comes_after_a",1},
- {"module_info",0},
- {"module_info",1}]} = edlin_expand:expand(
- lists:reverse("expand_test1:")),
- ?line {yes,"_",[]} = edlin_expand:expand(
- lists:reverse("expand_test1:a")),
- ?line {yes,[],[{"a_fun_name",1},
- {"a_less_fun_name",1}]} = edlin_expand:expand(
- lists:reverse("expand_test1:a_")),
- ?line {yes,[],
- [{"'#weird-fun-name'",0},
+ {yes, "test", []} = do_expand("expand_"),
+ {no, [], []} = do_expand("expandXX_"),
+ {no,[],[{"'#weird-fun-name'",1},
{"'Quoted_fun_name'",0},
- {"'Quoted_fun_too'",0}]} = edlin_expand:expand(
- lists:reverse("expand_test1:'")),
- ?line {yes,"uoted_fun_",[]} = edlin_expand:expand(
- lists:reverse("expand_test1:'Q")),
- ?line {yes,[],
- [{"'Quoted_fun_name'",0},
- {"'Quoted_fun_too'",0}]} = edlin_expand:expand(
- lists:reverse("expand_test1:'Quoted_fun_")),
- ?line {yes,"weird-fun-name'(",[]} = edlin_expand:expand(
- lists:reverse("expand_test1:'#")),
+ {"'Quoted_fun_too'",0},
+ {"a_fun_name",1},
+ {"a_less_fun_name",1},
+ {"b_comes_after_a",1},
+ {"module_info",0},
+ {"module_info",1}]} = do_expand("expand_test1:"),
+ {yes,"_",[]} = do_expand("expand_test1:a"),
+ {yes,[],[{"a_fun_name",1},
+ {"a_less_fun_name",1}]} = do_expand("expand_test1:a_"),
+ {yes,[],
+ [{"'#weird-fun-name'",1},
+ {"'Quoted_fun_name'",0},
+ {"'Quoted_fun_too'",0}]} = do_expand("expand_test1:'"),
+ {yes,"uoted_fun_",[]} = do_expand("expand_test1:'Q"),
+ {yes,[],
+ [{"'Quoted_fun_name'",0},
+ {"'Quoted_fun_too'",0}]} = do_expand("expand_test1:'Quoted_fun_"),
+ {yes,"weird-fun-name'(",[]} = do_expand("expand_test1:'#"),
+
+ %% Since there is a module_info/1 as well as a module_info/0
+ %% there should not be a closing parenthesis added.
+ {yes,"(",[]} = do_expand("expand_test:module_info"),
ok.
quoted_module(doc) ->
@@ -127,51 +125,46 @@ quoted_module(doc) ->
quoted_module(suite) ->
[];
quoted_module(Config) when is_list(Config) ->
- ?line {module,'ExpandTestCaps'} = c:l('ExpandTestCaps'),
- ?line {yes, "Caps':", []} = edlin_expand:expand(lists:reverse("'ExpandTest")),
- ?line {no,[],
- [{"a_fun_name",1},
- {"a_less_fun_name",1},
- {"b_comes_after_a",1},
- {"module_info",0},
- {"module_info",1}]} = edlin_expand:expand(lists:reverse("'ExpandTestCaps':")),
- ?line {yes,[],[{"a_fun_name",1},
- {"a_less_fun_name",1}]} = edlin_expand:expand(
- lists:reverse("'ExpandTestCaps':a_")),
+ {module,'ExpandTestCaps'} = c:l('ExpandTestCaps'),
+ {yes, "Caps':", []} = do_expand("'ExpandTest"),
+ {no,[],
+ [{"a_fun_name",1},
+ {"a_less_fun_name",1},
+ {"b_comes_after_a",1},
+ {"module_info",0},
+ {"module_info",1}]} = do_expand("'ExpandTestCaps':"),
+ {yes,[],[{"a_fun_name",1},
+ {"a_less_fun_name",1}]} = do_expand("'ExpandTestCaps':a_"),
ok.
quoted_both(suite) ->
[];
quoted_both(Config) when is_list(Config) ->
- ?line {module,'ExpandTestCaps'} = c:l('ExpandTestCaps'),
- ?line {module,'ExpandTestCaps1'} = c:l('ExpandTestCaps1'),
+ {module,'ExpandTestCaps'} = c:l('ExpandTestCaps'),
+ {module,'ExpandTestCaps1'} = c:l('ExpandTestCaps1'),
%% should be no colon (or quote) after test this time
- ?line {yes, "Caps", []} = edlin_expand:expand(lists:reverse("'ExpandTest")),
- ?line {no,[],[{"'#weird-fun-name'",0},
- {"'Quoted_fun_name'",0},
- {"'Quoted_fun_too'",0},
- {"a_fun_name",1},
- {"a_less_fun_name",1},
- {"b_comes_after_a",1},
- {"module_info",0},
- {"module_info",1}]} = edlin_expand:expand(
- lists:reverse("'ExpandTestCaps1':")),
- ?line {yes,"_",[]} = edlin_expand:expand(
- lists:reverse("'ExpandTestCaps1':a")),
- ?line {yes,[],[{"a_fun_name",1},
- {"a_less_fun_name",1}]} = edlin_expand:expand(
- lists:reverse("'ExpandTestCaps1':a_")),
- ?line {yes,[],
- [{"'#weird-fun-name'",0},
+ {yes, "Caps", []} = do_expand("'ExpandTest"),
+ {no,[],[{"'#weird-fun-name'",0},
{"'Quoted_fun_name'",0},
- {"'Quoted_fun_too'",0}]} = edlin_expand:expand(
- lists:reverse("'ExpandTestCaps1':'")),
- ?line {yes,"uoted_fun_",[]} = edlin_expand:expand(
- lists:reverse("'ExpandTestCaps1':'Q")),
- ?line {yes,[],
- [{"'Quoted_fun_name'",0},
- {"'Quoted_fun_too'",0}]} = edlin_expand:expand(
- lists:reverse("'ExpandTestCaps1':'Quoted_fun_")),
- ?line {yes,"weird-fun-name'(",[]} = edlin_expand:expand(
- lists:reverse("'ExpandTestCaps1':'#")),
+ {"'Quoted_fun_too'",0},
+ {"a_fun_name",1},
+ {"a_less_fun_name",1},
+ {"b_comes_after_a",1},
+ {"module_info",0},
+ {"module_info",1}]} = do_expand("'ExpandTestCaps1':"),
+ {yes,"_",[]} = do_expand("'ExpandTestCaps1':a"),
+ {yes,[],[{"a_fun_name",1},
+ {"a_less_fun_name",1}]} = do_expand("'ExpandTestCaps1':a_"),
+ {yes,[],
+ [{"'#weird-fun-name'",0},
+ {"'Quoted_fun_name'",0},
+ {"'Quoted_fun_too'",0}]} = do_expand("'ExpandTestCaps1':'"),
+ {yes,"uoted_fun_",[]} = do_expand("'ExpandTestCaps1':'Q"),
+ {yes,[],
+ [{"'Quoted_fun_name'",0},
+ {"'Quoted_fun_too'",0}]} = do_expand("'ExpandTestCaps1':'Quoted_fun_"),
+ {yes,"weird-fun-name'()",[]} = do_expand("'ExpandTestCaps1':'#"),
ok.
+
+do_expand(String) ->
+ edlin_expand:expand(lists:reverse(String)).
diff --git a/lib/stdlib/test/epp_SUITE.erl b/lib/stdlib/test/epp_SUITE.erl
index 0cbdf76270..0b4726c07a 100644
--- a/lib/stdlib/test/epp_SUITE.erl
+++ b/lib/stdlib/test/epp_SUITE.erl
@@ -1,7 +1,7 @@
%%
%% %CopyrightBegin%
%%
-%% Copyright Ericsson AB 1998-2013. All Rights Reserved.
+%% Copyright Ericsson AB 1998-2014. All Rights Reserved.
%%
%% The contents of this file are subject to the Erlang Public License,
%% Version 1.1, (the "License"); you may not use this file except in
@@ -25,7 +25,8 @@
variable_1/1, otp_4870/1, otp_4871/1, otp_5362/1,
pmod/1, not_circular/1, skip_header/1, otp_6277/1, otp_7702/1,
otp_8130/1, overload_mac/1, otp_8388/1, otp_8470/1, otp_8503/1,
- otp_8562/1, otp_8665/1, otp_8911/1, otp_10302/1, otp_10820/1]).
+ otp_8562/1, otp_8665/1, otp_8911/1, otp_10302/1, otp_10820/1,
+ otp_11728/1]).
-export([epp_parse_erl_form/2]).
@@ -67,7 +68,7 @@ all() ->
{group, variable}, otp_4870, otp_4871, otp_5362, pmod,
not_circular, skip_header, otp_6277, otp_7702, otp_8130,
overload_mac, otp_8388, otp_8470, otp_8503, otp_8562,
- otp_8665, otp_8911, otp_10302, otp_10820].
+ otp_8665, otp_8911, otp_10302, otp_10820, otp_11728].
groups() ->
[{upcase_mac, [], [upcase_mac_1, upcase_mac_2]},
@@ -1387,6 +1388,31 @@ do_otp_10820(File, C, PC) ->
true = test_server:stop_node(Node),
ok.
+otp_11728(doc) ->
+ ["OTP-11728. Bugfix circular macro."];
+otp_11728(suite) ->
+ [];
+otp_11728(Config) when is_list(Config) ->
+ Dir = ?config(priv_dir, Config),
+ H = <<"-define(MACRO,[[]++?MACRO]).">>,
+ HrlFile = filename:join(Dir, "otp_11728.hrl"),
+ ok = file:write_file(HrlFile, H),
+ C = <<"-module(otp_11728).
+ -compile(export_all).
+
+ -include(\"otp_11728.hrl\").
+
+ function_name()->
+ A=?MACRO, % line 7
+ ok">>,
+ ErlFile = filename:join(Dir, "otp_11728.erl"),
+ ok = file:write_file(ErlFile, C),
+ {ok, L} = epp:parse_file(ErlFile, [Dir], []),
+ true = lists:member({error,{7,epp,{circular,'MACRO',none}}}, L),
+ _ = file:delete(HrlFile),
+ _ = file:delete(ErlFile),
+ ok.
+
check(Config, Tests) ->
eval_tests(Config, fun check_test/2, Tests).
diff --git a/lib/stdlib/test/erl_eval_SUITE.erl b/lib/stdlib/test/erl_eval_SUITE.erl
index c4b6b35e72..e6512b7d71 100644
--- a/lib/stdlib/test/erl_eval_SUITE.erl
+++ b/lib/stdlib/test/erl_eval_SUITE.erl
@@ -25,7 +25,7 @@
match_bin/1,
string_plusplus/1,
pattern_expr/1,
- guard_3/1, guard_4/1,
+ guard_3/1, guard_4/1, guard_5/1,
lc/1,
simple_cases/1,
unary_plus/1,
@@ -42,7 +42,8 @@
try_catch/1,
eval_expr_5/1,
zero_width/1,
- eep37/1]).
+ eep37/1,
+ eep43/1]).
%%
%% Define to run outside of test server
@@ -78,11 +79,11 @@ suite() -> [{ct_hooks,[ts_install_cth]}].
all() ->
[guard_1, guard_2, match_pattern, string_plusplus,
- pattern_expr, match_bin, guard_3, guard_4, lc,
+ pattern_expr, match_bin, guard_3, guard_4, guard_5, lc,
simple_cases, unary_plus, apply_atom, otp_5269,
otp_6539, otp_6543, otp_6787, otp_6977, otp_7550,
otp_8133, otp_10622, funs, try_catch, eval_expr_5, zero_width,
- eep37].
+ eep37, eep43].
groups() ->
[].
@@ -247,6 +248,20 @@ guard_4(Config) when is_list(Config) ->
false),
ok.
+guard_5(doc) ->
+ ["Guards with erlang:'=='/2"];
+guard_5(suite) ->
+ [];
+guard_5(Config) when is_list(Config) ->
+ {ok,Tokens ,_} =
+ erl_scan:string("case 1 of A when erlang:'=='(A, 1) -> true end."),
+ {ok, [Expr]} = erl_parse:parse_exprs(Tokens),
+ true = guard_5_compiled(),
+ {value, true, [{'A',1}]} = erl_eval:expr(Expr, []),
+ ok.
+
+guard_5_compiled() ->
+ case 1 of A when erlang:'=='(A, 1) -> true end.
lc(doc) ->
["OTP-4518."];
@@ -1424,6 +1439,20 @@ eep37(Config) when is_list(Config) ->
720),
ok.
+eep43(Config) when is_list(Config) ->
+ check(fun () -> #{} end, " #{}.", #{}),
+ check(fun () -> #{a => b} end, "#{a => b}.", #{a => b}),
+ check(fun () ->
+ Map = #{a => b},
+ {Map#{a := b},Map#{a => c},Map#{d => e}}
+ end,
+ "begin "
+ " Map = #{a => B=b}, "
+ " {Map#{a := B},Map#{a => c},Map#{d => e}} "
+ "end.",
+ {#{a => b},#{a => c},#{a => b,d => e}}),
+ ok.
+
%% Check the string in different contexts: as is; in fun; from compiled code.
check(F, String, Result) ->
check1(F, String, Result),
diff --git a/lib/stdlib/test/erl_expand_records_SUITE.erl b/lib/stdlib/test/erl_expand_records_SUITE.erl
index 94b4397a9c..43e679f7ed 100644
--- a/lib/stdlib/test/erl_expand_records_SUITE.erl
+++ b/lib/stdlib/test/erl_expand_records_SUITE.erl
@@ -38,7 +38,7 @@
-export([attributes/1, expr/1, guard/1,
init/1, pattern/1, strict/1, update/1,
otp_5915/1, otp_7931/1, otp_5990/1,
- otp_7078/1, otp_7101/1]).
+ otp_7078/1, otp_7101/1, maps/1]).
% Default timetrap timeout (set in init_per_testcase).
-define(default_timeout, ?t:minutes(1)).
@@ -56,7 +56,7 @@ suite() -> [{ct_hooks,[ts_install_cth]}].
all() ->
[attributes, expr, guard, init,
- pattern, strict, update, {group, tickets}].
+ pattern, strict, update, maps, {group, tickets}].
groups() ->
[{tickets, [],
@@ -402,7 +402,22 @@ update(Config) when is_list(Config) ->
],
?line run(Config, Ts),
ok.
-
+
+maps(Config) when is_list(Config) ->
+ Ts = [<<"-record(rr, {a,b,c}).
+ t() ->
+ R0 = id(#rr{a=1,b=2,c=3}),
+ R1 = id(#rr{a=4,b=5,c=6}),
+ [{R0,R1}] =
+ maps:to_list(#{#rr{a=1,b=2,c=3} => #rr{a=4,b=5,c=6}}),
+ #{#rr{a=1,b=2,c=3} := #rr{a=1,b=2,c=3}} =
+ #{#rr{a=1,b=2,c=3} => R1}#{#rr{a=1,b=2,c=3} := R0},
+ ok.
+
+ id(X) -> X.
+ ">>],
+ run(Config, Ts, [strict_record_tests]),
+ ok.
otp_5915(doc) ->
"Strict record tests in guards.";
diff --git a/lib/stdlib/test/erl_lint_SUITE.erl b/lib/stdlib/test/erl_lint_SUITE.erl
index 6e9a9dd7bf..1614a2722f 100644
--- a/lib/stdlib/test/erl_lint_SUITE.erl
+++ b/lib/stdlib/test/erl_lint_SUITE.erl
@@ -1,7 +1,7 @@
%%
%% %CopyrightBegin%
%%
-%% Copyright Ericsson AB 1999-2013. All Rights Reserved.
+%% Copyright Ericsson AB 1999-2014. All Rights Reserved.
%%
%% The contents of this file are subject to the Erlang Public License,
%% Version 1.1, (the "License"); you may not use this file except in
@@ -60,7 +60,8 @@
format_warn/1,
on_load_successful/1, on_load_failing/1,
too_many_arguments/1,
- basic_errors/1,bin_syntax_errors/1
+ basic_errors/1,bin_syntax_errors/1,
+ predef/1
]).
% Default timetrap timeout (set in init_per_testcase).
@@ -87,7 +88,7 @@ all() ->
otp_5878, otp_5917, otp_6585, otp_6885, otp_10436, otp_11254,export_all,
bif_clash, behaviour_basic, behaviour_multiple,
otp_7550, otp_8051, format_warn, {group, on_load},
- too_many_arguments, basic_errors, bin_syntax_errors].
+ too_many_arguments, basic_errors, bin_syntax_errors, predef].
groups() ->
[{unused_vars_warn, [],
@@ -2827,7 +2828,24 @@ bif_clash(Config) when is_list(Config) ->
{6,erl_lint,{illegal_guard_local_call,{is_tuple,1}}},
{7,erl_lint,{illegal_guard_local_call,{is_list,1}}},
{8,erl_lint,{illegal_guard_local_call,{is_record,3}}},
- {9,erl_lint,{illegal_guard_local_call,{is_record,3}}}],[]}}
+ {9,erl_lint,{illegal_guard_local_call,{is_record,3}}}],[]}},
+ %% We can also suppress all auto imports at once
+ {clash22,
+ <<"-export([size/1, binary_part/2]).
+ -compile(no_auto_import).
+ size([]) ->
+ 0;
+ size({N,_}) ->
+ N;
+ size([_|T]) ->
+ 1+size(T).
+ binary_part({B,_},{X,Y}) ->
+ binary_part(B,{X,Y});
+ binary_part(B,{X,Y}) ->
+ binary:part(B,X,Y).
+ ">>,
+ [],
+ []}
],
?line [] = run(Config, Ts),
@@ -3224,6 +3242,23 @@ bin_syntax_errors(Config) ->
[] = run(Config, Ts),
ok.
+predef(doc) ->
+ "Predefined types: array(), digraph(), and so on";
+predef(suite) -> [];
+predef(Config) when is_list(Config) ->
+ W = get_compilation_warnings(Config, "predef", []),
+ [] = W,
+ W2 = get_compilation_warnings(Config, "predef2", []),
+ [{7,erl_lint,{deprecated_type,{array,0},{array,array},"OTP 18.0"}},
+ {12,erl_lint,{deprecated_type,{dict,0},{dict,dict},"OTP 18.0"}},
+ {17,erl_lint,{deprecated_type,{digraph,0},{digraph,graph},"OTP 18.0"}},
+ {27,erl_lint,{deprecated_type,{gb_set,0},{gb_sets,set},"OTP 18.0"}},
+ {32,erl_lint,{deprecated_type,{gb_tree,0},{gb_trees,tree},"OTP 18.0"}},
+ {37,erl_lint,{deprecated_type,{queue,0},{queue,queue},"OTP 18.0"}},
+ {42,erl_lint,{deprecated_type,{set,0},{sets,set},"OTP 18.0"}},
+ {47,erl_lint,{deprecated_type,{tid,0},{ets,tid},"OTP 18.0"}}] = W2,
+ ok.
+
run(Config, Tests) ->
F = fun({N,P,Ws,E}, BadL) ->
case catch run_test(Config, P, Ws) of
@@ -3246,8 +3281,10 @@ get_compilation_warnings(Conf, Filename, Warnings) ->
FileS = binary_to_list(Bin),
{match,[{Start,Length}|_]} = re:run(FileS, "-module.*\\n"),
Test = lists:nthtail(Start+Length, FileS),
- {warnings, Ws} = run_test(Conf, Test, Warnings),
- Ws.
+ case run_test(Conf, Test, Warnings) of
+ {warnings, Ws} -> Ws;
+ [] -> []
+ end.
%% Compiles a test module and returns the list of errors and warnings.
diff --git a/lib/stdlib/test/erl_lint_SUITE_data/predef.erl b/lib/stdlib/test/erl_lint_SUITE_data/predef.erl
new file mode 100644
index 0000000000..c2364fd1c2
--- /dev/null
+++ b/lib/stdlib/test/erl_lint_SUITE_data/predef.erl
@@ -0,0 +1,67 @@
+-module(predef).
+
+-export([array/1, dict/1, digraph/1, digraph2/1, gb_set/1, gb_tree/1,
+ queue/1, set/1, tid/0, tid2/0]).
+
+-export_type([array/0, digraph/0, gb_set/0]).
+
+%% Before R17B local re-definitions of pre-defined opaque types were
+%% ignored but did not generate any warning.
+-opaque array() :: atom().
+-opaque digraph() :: atom().
+-opaque gb_set() :: atom().
+-type dict() :: atom().
+-type gb_tree() :: atom().
+-type queue() :: atom().
+-type set() :: atom().
+-type tid() :: atom().
+
+-spec array(array()) -> array:array().
+
+array(A) ->
+ array:relax(A).
+
+-spec dict(dict()) -> dict:dict().
+
+dict(D) ->
+ dict:store(1, a, D).
+
+-spec digraph(digraph()) -> [digraph:edge()].
+
+digraph(G) ->
+ digraph:edges(G).
+
+-spec digraph2(digraph:graph()) -> [digraph:edge()].
+
+digraph2(G) ->
+ digraph:edges(G).
+
+-spec gb_set(gb_set()) -> gb_sets:set().
+
+gb_set(S) ->
+ gb_sets:balance(S).
+
+-spec gb_tree(gb_tree()) -> gb_trees:tree().
+
+gb_tree(S) ->
+ gb_trees:balance(S).
+
+-spec queue(queue()) -> queue:queue().
+
+queue(Q) ->
+ queue:reverse(Q).
+
+-spec set(set()) -> sets:set().
+
+set(S) ->
+ sets:union([S]).
+
+-spec tid() -> tid().
+
+tid() ->
+ ets:new(tid, []).
+
+-spec tid2() -> ets:tid().
+
+tid2() ->
+ ets:new(tid, []).
diff --git a/lib/stdlib/test/erl_lint_SUITE_data/predef2.erl b/lib/stdlib/test/erl_lint_SUITE_data/predef2.erl
new file mode 100644
index 0000000000..b1d941a49a
--- /dev/null
+++ b/lib/stdlib/test/erl_lint_SUITE_data/predef2.erl
@@ -0,0 +1,56 @@
+-module(predef2).
+
+-export([array/1, dict/1, digraph/1, digraph2/1, gb_set/1, gb_tree/1,
+ queue/1, set/1, tid/0, tid2/0]).
+
+-export_type([array/0, digraph/0, gb_set/0]).
+
+-spec array(array()) -> array:array().
+
+array(A) ->
+ array:relax(A).
+
+-spec dict(dict()) -> dict:dict().
+
+dict(D) ->
+ dict:store(1, a, D).
+
+-spec digraph(digraph()) -> [digraph:edge()].
+
+digraph(G) ->
+ digraph:edges(G).
+
+-spec digraph2(digraph:graph()) -> [digraph:edge()].
+
+digraph2(G) ->
+ digraph:edges(G).
+
+-spec gb_set(gb_set()) -> gb_sets:set().
+
+gb_set(S) ->
+ gb_sets:balance(S).
+
+-spec gb_tree(gb_tree()) -> gb_trees:tree().
+
+gb_tree(S) ->
+ gb_trees:balance(S).
+
+-spec queue(queue()) -> queue:queue().
+
+queue(Q) ->
+ queue:reverse(Q).
+
+-spec set(set()) -> sets:set().
+
+set(S) ->
+ sets:union([S]).
+
+-spec tid() -> tid().
+
+tid() ->
+ ets:new(tid, []).
+
+-spec tid2() -> ets:tid().
+
+tid2() ->
+ ets:new(tid, []).
diff --git a/lib/stdlib/test/erl_pp_SUITE.erl b/lib/stdlib/test/erl_pp_SUITE.erl
index cc744ee76b..390322a5fa 100644
--- a/lib/stdlib/test/erl_pp_SUITE.erl
+++ b/lib/stdlib/test/erl_pp_SUITE.erl
@@ -46,6 +46,7 @@
import_export/1, misc_attrs/1, dialyzer_attrs/1,
hook/1,
neg_indent/1,
+ maps_syntax/1,
otp_6321/1, otp_6911/1, otp_6914/1, otp_8150/1, otp_8238/1,
otp_8473/1, otp_8522/1, otp_8567/1, otp_8664/1, otp_9147/1,
@@ -76,7 +77,8 @@ groups() ->
[{expr, [],
[func, call, recs, try_catch, if_then, receive_after,
bits, head_tail, cond1, block, case1, ops,
- messages, old_mnemosyne_syntax]},
+ messages, old_mnemosyne_syntax, maps_syntax
+ ]},
{attributes, [], [misc_attrs, import_export, dialyzer_attrs]},
{tickets, [],
[otp_6321, otp_6911, otp_6914, otp_8150, otp_8238,
@@ -975,6 +977,25 @@ count_atom(L, A) when is_list(L) ->
count_atom(_, _) ->
0.
+maps_syntax(doc) -> "Maps syntax";
+maps_syntax(suite) -> [];
+maps_syntax(Config) when is_list(Config) ->
+ Ts = [{map_fun_1,
+ <<"t() ->\n"
+ " M0 = #{ 1 => hi, hi => 42, 1.0 => {hi,world}},\n"
+ " M1 = M0#{ 1 := hello, new_val => 1337 },\n"
+ " map_fun_2:val(M1).\n">>},
+ {map_fun_2,
+ <<"val(#{ 1 := V1, hi := V2, new_val := V3}) -> {V1,V2,V3}.\n">>}],
+ compile(Config, Ts),
+
+ ok = pp_expr(<<"#{}">>),
+ ok = pp_expr(<<"#{ a => 1, <<\"hi\">> => \"world\", 33 => 1.0 }">>),
+ ok = pp_expr(<<"#{ a := V1, <<\"hi\">> := V2 } = M">>),
+ ok = pp_expr(<<"M#{ a => V1, <<\"hi\">> := V2 }">>),
+ ok.
+
+
otp_8567(doc) ->
"OTP_8567. Avoid duplicated 'undefined' in record field types.";
otp_8567(suite) -> [];
diff --git a/lib/stdlib/test/ets_SUITE.erl b/lib/stdlib/test/ets_SUITE.erl
index 82c3e7ecaf..8dc8b2c291 100644
--- a/lib/stdlib/test/ets_SUITE.erl
+++ b/lib/stdlib/test/ets_SUITE.erl
@@ -1,7 +1,7 @@
%%
%% %CopyrightBegin%
%%
-%% Copyright Ericsson AB 1996-2013. All Rights Reserved.
+%% Copyright Ericsson AB 1996-2014. All Rights Reserved.
%%
%% The contents of this file are subject to the Erlang Public License,
%% Version 1.1, (the "License"); you may not use this file except in
@@ -75,6 +75,7 @@
-export([otp_9932/1]).
-export([otp_9423/1]).
-export([otp_10182/1]).
+-export([ets_all/1]).
-export([memory_check_summary/1]).
-export([init_per_testcase/2, end_per_testcase/2]).
@@ -151,6 +152,7 @@ all() ->
otp_10182,
otp_9932,
otp_9423,
+ ets_all,
memory_check_summary]. % MUST BE LAST
@@ -5565,7 +5567,19 @@ otp_10182(Config) when is_list(Config) ->
ets:delete(Db),
In = Out.
-
+%% Test that ets:all include/exclude tables that we know are created/deleted
+ets_all(Config) when is_list(Config) ->
+ Pids = [spawn_link(fun() -> ets_all_run() end) || _ <- [1,2]],
+ receive after 3*1000 -> ok end,
+ [begin unlink(P), exit(P,kill) end || P <- Pids],
+ ok.
+
+ets_all_run() ->
+ Table = ets:new(undefined, []),
+ true = lists:member(Table, ets:all()),
+ ets:delete(Table),
+ false = lists:member(Table, ets:all()),
+ ets_all_run().
%
diff --git a/lib/stdlib/test/expand_test.erl b/lib/stdlib/test/expand_test.erl
index 63e4bc3aa0..b9db32c352 100644
--- a/lib/stdlib/test/expand_test.erl
+++ b/lib/stdlib/test/expand_test.erl
@@ -20,7 +20,8 @@
-export([a_fun_name/1,
a_less_fun_name/1,
- b_comes_after_a/1]).
+ b_comes_after_a/1,
+ expand0arity_entirely/0]).
a_fun_name(X) ->
X.
@@ -30,3 +31,6 @@ a_less_fun_name(X) ->
b_comes_after_a(X) ->
X.
+
+expand0arity_entirely () ->
+ ok.
diff --git a/lib/stdlib/test/expand_test1.erl b/lib/stdlib/test/expand_test1.erl
index 11b6fec0f3..1d375e5677 100644
--- a/lib/stdlib/test/expand_test1.erl
+++ b/lib/stdlib/test/expand_test1.erl
@@ -23,7 +23,7 @@
b_comes_after_a/1,
'Quoted_fun_name'/0,
'Quoted_fun_too'/0,
- '#weird-fun-name'/0]).
+ '#weird-fun-name'/1]).
a_fun_name(X) ->
X.
@@ -40,5 +40,5 @@ b_comes_after_a(X) ->
'Quoted_fun_too'() ->
too.
-'#weird-fun-name'() ->
+'#weird-fun-name'(_) ->
weird.
diff --git a/lib/stdlib/test/lists_SUITE.erl b/lib/stdlib/test/lists_SUITE.erl
index 92253ef5b9..f4589a8e24 100644
--- a/lib/stdlib/test/lists_SUITE.erl
+++ b/lib/stdlib/test/lists_SUITE.erl
@@ -61,7 +61,7 @@
zip_unzip/1, zip_unzip3/1, zipwith/1, zipwith3/1,
filter_partition/1,
otp_5939/1, otp_6023/1, otp_6606/1, otp_7230/1,
- suffix/1, subtract/1]).
+ suffix/1, subtract/1, droplast/1]).
%% Sort randomized lists until stopped.
%%
@@ -2641,4 +2641,12 @@ sub_non_matching(A, B) ->
sub(A, B) ->
Res = A -- B,
Res = lists:subtract(A, B).
-
+
+%% Test lists:droplast/1
+droplast(Config) when is_list(Config) ->
+ ?line [] = lists:droplast([x]),
+ ?line [x] = lists:droplast([x, y]),
+ ?line {'EXIT', {function_clause, _}} = (catch lists:droplast([])),
+ ?line {'EXIT', {function_clause, _}} = (catch lists:droplast(x)),
+
+ ok.
diff --git a/lib/stdlib/test/stdlib_SUITE.erl b/lib/stdlib/test/stdlib_SUITE.erl
index 8fff5e2e05..53a34511d9 100644
--- a/lib/stdlib/test/stdlib_SUITE.erl
+++ b/lib/stdlib/test/stdlib_SUITE.erl
@@ -23,10 +23,6 @@
-include_lib("test_server/include/test_server.hrl").
-% Default timetrap timeout (set in init_per_testcase).
--define(default_timeout, ?t:minutes(1)).
--define(application, stdlib).
-
% 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]).
@@ -60,11 +56,8 @@ end_per_group(_GroupName, Config) ->
init_per_testcase(_Case, Config) ->
- ?line Dog=test_server:timetrap(?default_timeout),
- [{watchdog, Dog}|Config].
-end_per_testcase(_Case, Config) ->
- Dog=?config(watchdog, Config),
- test_server:timetrap_cancel(Dog),
+ Config.
+end_per_testcase(_Case, _Config) ->
ok.
%
@@ -78,17 +71,18 @@ app_test(Config) when is_list(Config) ->
?t:app_test(stdlib),
ok.
-%% Test that appup allows upgrade from/downgrade to a maximum of two
-%% major releases back.
+%% Test that appup allows upgrade from/downgrade to a maximum of one
+%% major release back.
appup_test(_Config) ->
- do_appup_tests(create_test_vsns()).
+ appup_tests(stdlib,create_test_vsns(stdlib)).
-do_appup_tests({[],[]}) ->
+appup_tests(_App,{[],[]}) ->
{skip,"no previous releases available"};
-do_appup_tests({OkVsns,NokVsns}) ->
- application:load(stdlib),
- {_,_,Vsn} = lists:keyfind(stdlib,1,application:loaded_applications()),
- AppupFile = filename:join([code:lib_dir(stdlib),ebin,"stdlib.appup"]),
+appup_tests(App,{OkVsns,NokVsns}) ->
+ application:load(App),
+ {_,_,Vsn} = lists:keyfind(App,1,application:loaded_applications()),
+ AppupFileName = atom_to_list(App) ++ ".appup",
+ AppupFile = filename:join([code:lib_dir(App),ebin,AppupFileName]),
{ok,[{Vsn,UpFrom,DownTo}=AppupScript]} = file:consult(AppupFile),
ct:log("~p~n",[AppupScript]),
ct:log("Testing ok versions: ~p~n",[OkVsns]),
@@ -99,13 +93,12 @@ do_appup_tests({OkVsns,NokVsns}) ->
check_appup(NokVsns,DownTo,error),
ok.
-create_test_vsns() ->
+create_test_vsns(App) ->
This = erlang:system_info(otp_release),
FirstMajor = previous_major(This),
SecondMajor = previous_major(FirstMajor),
- ThirdMajor = previous_major(SecondMajor),
- Ok = stdlib_vsn([FirstMajor,SecondMajor]),
- Nok0 = stdlib_vsn([ThirdMajor]),
+ Ok = app_vsn(App,[FirstMajor]),
+ Nok0 = app_vsn(App,[SecondMajor]),
Nok = case Ok of
[Ok1|_] ->
[Ok1 ++ ",1" | Nok0]; % illegal
@@ -121,18 +114,36 @@ previous_major("r"++Rel) ->
previous_major(Rel) ->
integer_to_list(list_to_integer(Rel)-1).
-stdlib_vsn([R|Rs]) ->
- case test_server:is_release_available(R) of
- true ->
- {ok,N} = test_server:start_node(prevrel,peer,[{erl,[{release,R}]}]),
- As = rpc:call(N,application,which_applications,[]),
- {_,_,KV} = lists:keyfind(stdlib,1,As),
- test_server:stop_node(N),
- [KV|stdlib_vsn(Rs)];
+app_vsn(App,[R|Rs]) ->
+ OldRel =
+ case test_server:is_release_available(R) of
+ true ->
+ {release,R};
+ false ->
+ case ct:get_config({otp_releases,list_to_atom(R)}) of
+ undefined ->
+ false;
+ Prog0 ->
+ case os:find_executable(Prog0) of
+ false ->
+ false;
+ Prog ->
+ {prog,Prog}
+ end
+ end
+ end,
+ case OldRel of
false ->
- stdlib_vsn(Rs)
+ app_vsn(App,Rs);
+ _ ->
+ {ok,N} = test_server:start_node(prevrel,peer,[{erl,[OldRel]}]),
+ _ = rpc:call(N,application,load,[App]),
+ As = rpc:call(N,application,loaded_applications,[]),
+ {_,_,V} = lists:keyfind(App,1,As),
+ test_server:stop_node(N),
+ [V|app_vsn(App,Rs)]
end;
-stdlib_vsn([]) ->
+app_vsn(_App,[]) ->
[].
check_appup([Vsn|Vsns],Instrs,Expected) ->