aboutsummaryrefslogtreecommitdiffstats
path: root/lib/stdlib/test
diff options
context:
space:
mode:
Diffstat (limited to 'lib/stdlib/test')
-rw-r--r--lib/stdlib/test/Makefile5
-rw-r--r--lib/stdlib/test/binary_module_SUITE.erl123
-rw-r--r--lib/stdlib/test/binref.erl37
-rw-r--r--lib/stdlib/test/dict_SUITE.erl50
-rw-r--r--lib/stdlib/test/dict_test_lib.erl5
-rw-r--r--lib/stdlib/test/epp_SUITE.erl52
-rw-r--r--lib/stdlib/test/erl_anno_SUITE.erl568
-rw-r--r--lib/stdlib/test/erl_eval_SUITE.erl29
-rw-r--r--lib/stdlib/test/erl_internal_SUITE.erl65
-rw-r--r--lib/stdlib/test/erl_lint_SUITE.erl511
-rw-r--r--lib/stdlib/test/erl_lint_SUITE_data/bad_behaviour1.erl6
-rw-r--r--lib/stdlib/test/erl_lint_SUITE_data/bad_behaviour2.erl6
-rw-r--r--lib/stdlib/test/erl_lint_SUITE_data/callback1.erl6
-rw-r--r--lib/stdlib/test/erl_lint_SUITE_data/callback2.erl6
-rw-r--r--lib/stdlib/test/erl_lint_SUITE_data/callback3.erl8
-rw-r--r--lib/stdlib/test/erl_lint_SUITE_data/predef.erl4
-rw-r--r--lib/stdlib/test/erl_pp_SUITE.erl160
-rw-r--r--lib/stdlib/test/erl_scan_SUITE.erl287
-rw-r--r--lib/stdlib/test/ets_SUITE.erl451
-rw-r--r--lib/stdlib/test/filelib_SUITE.erl3
-rw-r--r--lib/stdlib/test/filename_SUITE.erl118
-rw-r--r--lib/stdlib/test/gen_event_SUITE.erl177
-rw-r--r--lib/stdlib/test/gen_fsm_SUITE.erl324
-rw-r--r--lib/stdlib/test/gen_server_SUITE.erl246
-rw-r--r--lib/stdlib/test/io_SUITE.erl22
-rw-r--r--lib/stdlib/test/io_proto_SUITE.erl301
-rw-r--r--lib/stdlib/test/lists_SUITE.erl2
-rw-r--r--lib/stdlib/test/maps_SUITE.erl81
-rw-r--r--lib/stdlib/test/proc_lib_SUITE.erl93
-rw-r--r--lib/stdlib/test/qlc_SUITE.erl221
-rw-r--r--lib/stdlib/test/rand_SUITE.erl527
-rw-r--r--lib/stdlib/test/random_SUITE.erl2
-rw-r--r--lib/stdlib/test/select_SUITE.erl2
-rw-r--r--lib/stdlib/test/sets_SUITE.erl44
-rw-r--r--lib/stdlib/test/sets_test_lib.erl5
-rw-r--r--lib/stdlib/test/shell_SUITE.erl11
-rw-r--r--lib/stdlib/test/stdlib_SUITE.erl107
-rw-r--r--lib/stdlib/test/string_SUITE.erl44
-rw-r--r--lib/stdlib/test/supervisor_SUITE.erl390
-rw-r--r--lib/stdlib/test/sys_SUITE.erl16
-rw-r--r--lib/stdlib/test/sys_sp1.erl14
-rw-r--r--lib/stdlib/test/sys_sp2.erl33
-rw-r--r--lib/stdlib/test/tar_SUITE.erl2
-rw-r--r--lib/stdlib/test/timer_SUITE.erl43
-rw-r--r--lib/stdlib/test/timer_simple_SUITE.erl4
-rw-r--r--lib/stdlib/test/unicode_SUITE.erl175
-rw-r--r--lib/stdlib/test/zip_SUITE.erl46
47 files changed, 4221 insertions, 1211 deletions
diff --git a/lib/stdlib/test/Makefile b/lib/stdlib/test/Makefile
index a271229c59..d4ab674486 100644
--- a/lib/stdlib/test/Makefile
+++ b/lib/stdlib/test/Makefile
@@ -23,6 +23,7 @@ MODULES= \
dummy_via \
edlin_expand_SUITE \
epp_SUITE \
+ erl_anno_SUITE \
erl_eval_SUITE \
erl_expand_records_SUITE \
erl_internal_SUITE \
@@ -53,6 +54,7 @@ MODULES= \
proc_lib_SUITE \
qlc_SUITE \
queue_SUITE \
+ rand_SUITE \
random_SUITE \
re_SUITE \
run_pcre_tests \
@@ -105,7 +107,8 @@ RELSYSDIR = $(RELEASE_PATH)/stdlib_test
ERL_MAKE_FLAGS +=
ERL_COMPILE_FLAGS += -I$(ERL_TOP)/lib/test_server/include \
- -I$(ERL_TOP)/lib/kernel/include
+ -I$(ERL_TOP)/lib/kernel/include \
+ -I$(ERL_TOP)/lib/stdlib/include
EBIN = .
diff --git a/lib/stdlib/test/binary_module_SUITE.erl b/lib/stdlib/test/binary_module_SUITE.erl
index 32cec0db6f..8d26c77c9b 100644
--- a/lib/stdlib/test/binary_module_SUITE.erl
+++ b/lib/stdlib/test/binary_module_SUITE.erl
@@ -506,12 +506,35 @@ do_interesting(Module) ->
?line [<<1,2,3>>,<<6>>] = Module:split(<<1,2,3,4,5,6,7,8>>,
[<<4,5>>,<<7>>,<<8>>],
[global,trim]),
+ ?line [<<1,2,3>>,<<6>>] = Module:split(<<1,2,3,4,5,6,7,8>>,
+ [<<4,5>>,<<7>>,<<8>>],
+ [global,trim_all]),
?line [<<1,2,3,4,5,6,7,8>>] = Module:split(<<1,2,3,4,5,6,7,8>>,
[<<4,5>>,<<7>>,<<8>>],
[global,trim,{scope,{0,4}}]),
?line [<<1,2,3>>,<<6,7,8>>] = Module:split(<<1,2,3,4,5,6,7,8>>,
[<<4,5>>,<<7>>,<<8>>],
[global,trim,{scope,{0,5}}]),
+
+ ?line [<<>>,<<>>,<<3>>,<<6,7,8>>] = Module:split(<<1,2,3,4,5,6,7,8>>,
+ [<<1>>,<<2>>,<<4,5>>],
+ [global,trim]),
+ ?line [<<3>>,<<6,7,8>>] = Module:split(<<1,2,3,4,5,6,7,8>>,
+ [<<1>>,<<2>>,<<4,5>>],
+ [global,trim_all]),
+
+ ?line [<<1,2,3>>,<<>>,<<7,8>>] = Module:split(<<1,2,3,4,5,6,7,8>>,
+ [<<4,5>>,<<6>>],
+ [global,trim]),
+ ?line [<<1,2,3>>,<<7,8>>] = Module:split(<<1,2,3,4,5,6,7,8>>,
+ [<<4,5>>,<<6>>],
+ [global,trim_all]),
+ ?line [<<>>,<<>>,<<3>>,<<>>,<<6>>] = Module:split(<<1,2,3,4,5,6,7,8>>,
+ [<<1>>,<<2>>,<<4>>,<<5>>,<<7>>,<<8>>],
+ [global,trim]),
+ ?line [<<3>>,<<6>>] = Module:split(<<1,2,3,4,5,6,7,8>>,
+ [<<1>>,<<2>>,<<4>>,<<5>>,<<7>>,<<8>>],
+ [global,trim_all]),
?line badarg = ?MASK_ERROR(
Module:replace(<<1,2,3,4,5,6,7,8>>,
[<<4,5>>,<<7>>,<<8>>],<<99>>,
@@ -970,43 +993,51 @@ random_parts(X,N) ->
random_ref_comp(doc) ->
["Test pseudorandomly generated cases against reference imlementation"];
random_ref_comp(Config) when is_list(Config) ->
- ?line put(success_counter,0),
- ?line random:seed({1271,769940,559934}),
- ?line do_random_match_comp(5000,{1,40},{30,1000}),
+ put(success_counter,0),
+ random:seed({1271,769940,559934}),
+ Nr = {1,40},
+ Hr = {30,1000},
+ I1 = 1500,
+ I2 = 5,
+ do_random_match_comp(I1,Nr,Hr),
io:format("Number of successes: ~p~n",[get(success_counter)]),
- ?line do_random_match_comp2(5000,{1,40},{30,1000}),
+ do_random_match_comp2(I1,Nr,Hr),
io:format("Number of successes: ~p~n",[get(success_counter)]),
- ?line do_random_match_comp3(5000,{1,40},{30,1000}),
+ do_random_match_comp3(I1,Nr,Hr),
io:format("Number of successes: ~p~n",[get(success_counter)]),
- ?line do_random_match_comp4(5000,{1,40},{30,1000}),
+ do_random_match_comp4(I1,Nr,Hr),
io:format("Number of successes: ~p~n",[get(success_counter)]),
- ?line do_random_matches_comp(5000,{1,40},{30,1000}),
+ do_random_matches_comp(I1,Nr,Hr),
io:format("Number of successes: ~p~n",[get(success_counter)]),
- ?line do_random_matches_comp2(5000,{1,40},{30,1000}),
+ do_random_matches_comp2(I1,Nr,Hr),
io:format("Number of successes: ~p~n",[get(success_counter)]),
- ?line do_random_matches_comp3(5,{1,40},{30,1000}),
- ?line erts_debug:set_internal_state(available_internal_state,true),
- ?line io:format("oldlimit: ~p~n",[ erts_debug:set_internal_state(binary_loop_limit,100)]),
- ?line do_random_match_comp(5000,{1,40},{30,1000}),
- ?line do_random_matches_comp3(5,{1,40},{30,1000}),
- ?line io:format("limit was: ~p~n",[ erts_debug:set_internal_state(binary_loop_limit,default)]),
- ?line erts_debug:set_internal_state(available_internal_state,false),
+ do_random_matches_comp3(I2,Nr,Hr),
+ erts_debug:set_internal_state(available_internal_state,true),
+ io:format("oldlimit: ~p~n",[ erts_debug:set_internal_state(binary_loop_limit,100)]),
+ do_random_match_comp(I1,Nr,Hr),
+ do_random_matches_comp3(I2,Nr,Hr),
+ io:format("limit was: ~p~n",[ erts_debug:set_internal_state(binary_loop_limit,default)]),
+ erts_debug:set_internal_state(available_internal_state,false),
ok.
random_ref_sr_comp(doc) ->
["Test pseudorandomly generated cases against reference imlementation of split and replace"];
random_ref_sr_comp(Config) when is_list(Config) ->
- ?line put(success_counter,0),
- ?line random:seed({1271,769940,559934}),
- ?line do_random_split_comp(5000,{1,40},{30,1000}),
+ put(success_counter,0),
+ random:seed({1271,769940,559934}),
+ Nr = {1,40},
+ Hr = {30,1000},
+ I1 = 1500,
+ do_random_split_comp(I1,Nr,Hr),
io:format("Number of successes: ~p~n",[get(success_counter)]),
- ?line do_random_replace_comp(5000,{1,40},{30,1000}),
+ do_random_replace_comp(I1,Nr,Hr),
io:format("Number of successes: ~p~n",[get(success_counter)]),
- ?line do_random_split_comp2(5000,{1,40},{30,1000}),
+ do_random_split_comp2(I1,Nr,Hr),
io:format("Number of successes: ~p~n",[get(success_counter)]),
- ?line do_random_replace_comp2(5000,{1,40},{30,1000}),
+ do_random_replace_comp2(I1,Nr,Hr),
io:format("Number of successes: ~p~n",[get(success_counter)]),
ok.
+
random_ref_fla_comp(doc) ->
["Test pseudorandomly generated cases against reference imlementation of split and replace"];
random_ref_fla_comp(Config) when is_list(Config) ->
@@ -1107,7 +1138,9 @@ do_random_matches_comp3(N,NeedleRange,HaystackRange) ->
Needles = [random_substring(NeedleRange,Haystack) ||
_ <- lists:duplicate(NumNeedles,a)],
RefRes = binref:matches(Haystack,Needles),
- true = do_matches_comp_loop(10000,Needles,Haystack, RefRes),
+ RefRes = binary:matches(Haystack,Needles),
+ Compiled = binary:compile_pattern(Needles),
+ true = do_matches_comp_loop(10000,Compiled,Haystack, RefRes),
do_random_matches_comp3(N-1,NeedleRange,HaystackRange).
do_matches_comp_loop(0,_,_,_) ->
@@ -1137,9 +1170,8 @@ do_matches_comp2(N,H,A) ->
end.
do_matches_comp(N,H) ->
A = ?MASK_ERROR(binref:matches(H,N)),
- B = ?MASK_ERROR(binref:matches(H,binref:compile_pattern(N))),
- C = ?MASK_ERROR(binary:matches(H,N)),
- D = ?MASK_ERROR(binary:matches(make_unaligned(H),
+ B = ?MASK_ERROR(binary:matches(H,N)),
+ C = ?MASK_ERROR(binary:matches(make_unaligned(H),
binary:compile_pattern([make_unaligned2(X) || X <- N]))),
if
A =/= nomatch ->
@@ -1147,14 +1179,14 @@ do_matches_comp(N,H) ->
true ->
ok
end,
- case {(A =:= B), (B =:= C),(C =:= D)} of
- {true,true,true} ->
+ case {(A =:= B), (B =:= C)} of
+ {true,true} ->
true;
_ ->
io:format("Failed to match ~p (needle) against ~s (haystack)~n",
[N,H]),
- io:format("A:~p,~nB:~p,~n,C:~p,~n,D:~p.~n",
- [A,B,C,D]),
+ io:format("A:~p,~nB:~p,~n,C:~p,~n",
+ [A,B,C]),
exit(mismatch)
end.
@@ -1196,46 +1228,44 @@ do_random_match_comp4(N,NeedleRange,HaystackRange) ->
do_match_comp(N,H) ->
A = ?MASK_ERROR(binref:match(H,N)),
- B = ?MASK_ERROR(binref:match(H,binref:compile_pattern([N]))),
- C = ?MASK_ERROR(binary:match(make_unaligned(H),N)),
- D = ?MASK_ERROR(binary:match(H,binary:compile_pattern([N]))),
- E = ?MASK_ERROR(binary:match(H,binary:compile_pattern(make_unaligned(N)))),
+ B = ?MASK_ERROR(binary:match(make_unaligned(H),N)),
+ C = ?MASK_ERROR(binary:match(H,binary:compile_pattern([N]))),
+ D = ?MASK_ERROR(binary:match(H,binary:compile_pattern(make_unaligned(N)))),
if
A =/= nomatch ->
put(success_counter,get(success_counter)+1);
true ->
ok
end,
- case {(A =:= B), (B =:= C),(C =:= D),(D =:= E)} of
- {true,true,true,true} ->
+ case {(A =:= B), (B =:= C),(C =:= D)} of
+ {true,true,true} ->
true;
_ ->
io:format("Failed to match ~s (needle) against ~s (haystack)~n",
[N,H]),
- io:format("A:~p,~nB:~p,~n,C:~p,~n,D:~p,E:~p.~n",
- [A,B,C,D,E]),
+ io:format("A:~p,~nB:~p,~n,C:~p,~n,D:~p.~n",
+ [A,B,C,D]),
exit(mismatch)
end.
do_match_comp3(N,H) ->
A = ?MASK_ERROR(binref:match(H,N)),
- B = ?MASK_ERROR(binref:match(H,binref:compile_pattern(N))),
- C = ?MASK_ERROR(binary:match(H,N)),
- D = ?MASK_ERROR(binary:match(H,binary:compile_pattern(N))),
+ B = ?MASK_ERROR(binary:match(H,N)),
+ C = ?MASK_ERROR(binary:match(H,binary:compile_pattern(N))),
if
A =/= nomatch ->
put(success_counter,get(success_counter)+1);
true ->
ok
end,
- case {(A =:= B), (B =:= C),(C =:= D)} of
- {true,true,true} ->
+ case {(A =:= B),(B =:= C)} of
+ {true,true} ->
true;
_ ->
io:format("Failed to match ~s (needle) against ~s (haystack)~n",
[N,H]),
- io:format("A:~p,~nB:~p,~n,C:~p,~n,D:~p.~n",
- [A,B,C,D]),
+ io:format("A:~p,~nB:~p,~n,C:~p.~n",
+ [A,B,C]),
exit(mismatch)
end.
@@ -1247,6 +1277,8 @@ do_random_split_comp(N,NeedleRange,HaystackRange) ->
true = do_split_comp(Needle,Haystack,[]),
true = do_split_comp(Needle,Haystack,[global]),
true = do_split_comp(Needle,Haystack,[global,trim]),
+ true = do_split_comp(Needle,Haystack,[global,trim_all]),
+ true = do_split_comp(Needle,Haystack,[global,trim,trim_all]),
do_random_split_comp(N-1,NeedleRange,HaystackRange).
do_random_split_comp2(0,_,_) ->
ok;
@@ -1257,6 +1289,9 @@ do_random_split_comp2(N,NeedleRange,HaystackRange) ->
_ <- lists:duplicate(NumNeedles,a)],
true = do_split_comp(Needles,Haystack,[]),
true = do_split_comp(Needles,Haystack,[global]),
+ true = do_split_comp(Needles,Haystack,[global,trim]),
+ true = do_split_comp(Needles,Haystack,[global,trim_all]),
+ true = do_split_comp(Needles,Haystack,[global,trim,trim_all]),
do_random_split_comp2(N-1,NeedleRange,HaystackRange).
do_split_comp(N,H,Opts) ->
diff --git a/lib/stdlib/test/binref.erl b/lib/stdlib/test/binref.erl
index 6d96736ef3..a52ea98e5a 100644
--- a/lib/stdlib/test/binref.erl
+++ b/lib/stdlib/test/binref.erl
@@ -155,7 +155,8 @@ split(Haystack,Needles0,Options) ->
true ->
exit(badtype)
end,
- {Part,Global,Trim} = get_opts_split(Options,{nomatch,false,false}),
+ {Part,Global,Trim,TrimAll} =
+ get_opts_split(Options,{nomatch,false,false,false}),
{Start,End,NewStack} =
case Part of
nomatch ->
@@ -180,20 +181,24 @@ split(Haystack,Needles0,Options) ->
[X]
end
end,
- do_split(Haystack,MList,0,Trim)
+ do_split(Haystack,MList,0,Trim,TrimAll)
catch
_:_ ->
erlang:error(badarg)
end.
-do_split(H,[],N,true) when N >= byte_size(H) ->
+do_split(H,[],N,true,_) when N >= byte_size(H) ->
[];
-do_split(H,[],N,_) ->
+do_split(H,[],N,_,true) when N >= byte_size(H) ->
+ [];
+do_split(H,[],N,_,_) ->
[part(H,{N,byte_size(H)-N})];
-do_split(H,[{A,B}|T],N,Trim) ->
+do_split(H,[{A,B}|T],N,Trim,TrimAll) ->
case part(H,{N,A-N}) of
+ <<>> when TrimAll == true ->
+ do_split(H,T,A+B,Trim,TrimAll);
<<>> ->
- Rest = do_split(H,T,A+B,Trim),
+ Rest = do_split(H,T,A+B,Trim,TrimAll),
case {Trim, Rest} of
{true,[]} ->
[];
@@ -201,7 +206,7 @@ do_split(H,[{A,B}|T],N,Trim) ->
[<<>> | Rest]
end;
Oth ->
- [Oth | do_split(H,T,A+B,Trim)]
+ [Oth | do_split(H,T,A+B,Trim,TrimAll)]
end.
@@ -565,14 +570,16 @@ get_opts_match([{scope,{A,B}} | T],_Part) ->
get_opts_match(_,_) ->
throw(badopt).
-get_opts_split([],{Part,Global,Trim}) ->
- {Part,Global,Trim};
-get_opts_split([{scope,{A,B}} | T],{_Part,Global,Trim}) ->
- get_opts_split(T,{{A,B},Global,Trim});
-get_opts_split([global | T],{Part,_Global,Trim}) ->
- get_opts_split(T,{Part,true,Trim});
-get_opts_split([trim | T],{Part,Global,_Trim}) ->
- get_opts_split(T,{Part,Global,true});
+get_opts_split([],{Part,Global,Trim,TrimAll}) ->
+ {Part,Global,Trim,TrimAll};
+get_opts_split([{scope,{A,B}} | T],{_Part,Global,Trim,TrimAll}) ->
+ get_opts_split(T,{{A,B},Global,Trim,TrimAll});
+get_opts_split([global | T],{Part,_Global,Trim,TrimAll}) ->
+ get_opts_split(T,{Part,true,Trim,TrimAll});
+get_opts_split([trim | T],{Part,Global,_Trim,TrimAll}) ->
+ get_opts_split(T,{Part,Global,true,TrimAll});
+get_opts_split([trim_all | T],{Part,Global,Trim,_TrimAll}) ->
+ get_opts_split(T,{Part,Global,Trim,true});
get_opts_split(_,_) ->
throw(badopt).
diff --git a/lib/stdlib/test/dict_SUITE.erl b/lib/stdlib/test/dict_SUITE.erl
index 69814e12ce..ab624e8dd2 100644
--- a/lib/stdlib/test/dict_SUITE.erl
+++ b/lib/stdlib/test/dict_SUITE.erl
@@ -1,7 +1,7 @@
%%
%% %CopyrightBegin%
%%
-%% Copyright Ericsson AB 2008-2013. All Rights Reserved.
+%% Copyright Ericsson AB 2008-2015. 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,16 +25,16 @@
-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,
- create/1,store/1]).
+ create/1,store/1,iterate/1]).
-include_lib("test_server/include/test_server.hrl").
--import(lists, [foldl/3,reverse/1]).
+-import(lists, [foldl/3]).
suite() -> [{ct_hooks,[ts_install_cth]}].
all() ->
- [create, store].
+ [create, store, iterate].
groups() ->
[].
@@ -93,6 +93,48 @@ store_1(List, M) ->
D0.
%%%
+%%% Test specifics for gb_trees.
+%%%
+
+iterate(Config) when is_list(Config) ->
+ test_all(fun iterate_1/1).
+
+iterate_1(M) ->
+ case M(module, []) of
+ gb_trees -> iterate_2(M);
+ _ -> ok
+ end,
+ M(empty, []).
+
+iterate_2(M) ->
+ random:seed(1, 2, 42),
+ iter_tree(M, 1000).
+
+iter_tree(_M, 0) ->
+ ok;
+iter_tree(M, N) ->
+ L = [{I, I} || I <- lists:seq(1, N)],
+ T = M(from_list, L),
+ L = lists:reverse(iterate_tree(M, T)),
+ R = random:uniform(N),
+ KV = lists:reverse(iterate_tree_from(M, R, T)),
+ KV = [P || P={K,_} <- L, K >= R],
+ iter_tree(M, N-1).
+
+iterate_tree(M, Tree) ->
+ I = M(iterator, Tree),
+ iterate_tree_1(M, M(next, I), []).
+
+iterate_tree_from(M, Start, Tree) ->
+ I = M(iterator_from, {Start, Tree}),
+ iterate_tree_1(M, M(next, I), []).
+
+iterate_tree_1(_, none, R) ->
+ R;
+iterate_tree_1(M, {K, V, I}, R) ->
+ iterate_tree_1(M, M(next, I), [{K, V} | R]).
+
+%%%
%%% Helper functions.
%%%
diff --git a/lib/stdlib/test/dict_test_lib.erl b/lib/stdlib/test/dict_test_lib.erl
index 4fdb4fa0bd..81d26ce5f8 100644
--- a/lib/stdlib/test/dict_test_lib.erl
+++ b/lib/stdlib/test/dict_test_lib.erl
@@ -1,7 +1,7 @@
%%
%% %CopyrightBegin%
%%
-%% Copyright Ericsson AB 2008-2013. All Rights Reserved.
+%% Copyright Ericsson AB 2008-2015. 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
@@ -29,6 +29,9 @@ new(Mod, Eq) ->
(module, []) -> Mod;
(size, D) -> Mod:size(D);
(is_empty, D) -> Mod:is_empty(D);
+ (iterator, S) -> Mod:iterator(S);
+ (iterator_from, {Start, S}) -> Mod:iterator_from(Start, S);
+ (next, I) -> Mod:next(I);
(to_list, D) -> to_list(Mod, D)
end.
diff --git a/lib/stdlib/test/epp_SUITE.erl b/lib/stdlib/test/epp_SUITE.erl
index b17e8bd186..9ab170c826 100644
--- a/lib/stdlib/test/epp_SUITE.erl
+++ b/lib/stdlib/test/epp_SUITE.erl
@@ -1,7 +1,7 @@
%%
%% %CopyrightBegin%
%%
-%% Copyright Ericsson AB 1998-2014. All Rights Reserved.
+%% Copyright Ericsson AB 1998-2015. 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
@@ -211,7 +211,7 @@ predef_mac(Config) when is_list(Config) ->
?line File = filename:join(?config(data_dir, Config), "mac3.erl"),
?line {ok, List} = epp:parse_file(File, [], []),
?line [_,
- {attribute, LineCol1, l, Line1},
+ {attribute, Anno, l, Line1},
{attribute, _, f, File},
{attribute, _, machine1, _},
{attribute, _, module, mac3},
@@ -219,13 +219,9 @@ predef_mac(Config) when is_list(Config) ->
{attribute, _, ms, "mac3"},
{attribute, _, machine2, _}
| _] = List,
- ?line case LineCol1 of
- Line1 -> ok;
- {Line1,_} -> ok
- end,
+ Line1 = erl_anno:line(Anno),
ok.
-
variable_1(doc) ->
[];
variable_1(suite) ->
@@ -553,11 +549,7 @@ otp_7702(Config) when is_list(Config) ->
{ok, AC} = beam_lib:chunks(BeamFile, [abstract_code]),
{file_7702,[{abstract_code,{_,Forms}}]} = AC,
- Fun = fun(Attrs) ->
- {line, L} = erl_parse:get_attribute(Attrs, line),
- L
- end,
- Forms2 = [erl_lint:modify_line(Form, Fun) || Form <- Forms],
+ Forms2 = unopaque_forms(Forms),
?line
[{attribute,1,file,_},
_,
@@ -1395,9 +1387,10 @@ otp_10820(Config) when is_list(Config) ->
do_otp_10820(File, C, PC) ->
{ok,Node} = start_node(erl_pp_helper, "+fnu " ++ PC),
ok = rpc:call(Node, file, write_file, [File, C]),
- {ok,[{attribute,1,file,{File,1}},
- {attribute,2,module,any},
- {eof,2}]} = rpc:call(Node, epp, parse_file, [File, [],[]]),
+ {ok, Forms} = rpc:call(Node, epp, parse_file, [File, [],[]]),
+ [{attribute,1,file,{File,1}},
+ {attribute,2,module,any},
+ {eof,2}] = unopaque_forms(Forms),
true = test_server:stop_node(Node),
ok.
@@ -1440,15 +1433,15 @@ encoding(Config) when is_list(Config) ->
{attribute,1,module,encoding},
{error,_},
{error,{2,epp,cannot_parse}},
- {eof,2}]} = epp:parse_file(ErlFile, []),
+ {eof,2}]} = epp_parse_file(ErlFile, []),
{ok,[{attribute,1,file,_},
{attribute,1,module,encoding},
{eof,3}]} =
- epp:parse_file(ErlFile, [{default_encoding,latin1}]),
+ epp_parse_file(ErlFile, [{default_encoding,latin1}]),
{ok,[{attribute,1,file,_},
{attribute,1,module,encoding},
{eof,3}],[{encoding,none}]} =
- epp:parse_file(ErlFile, [{default_encoding,latin1},extra]),
+ epp_parse_file(ErlFile, [{default_encoding,latin1},extra]),
%% Try a latin-1 file with encoding given in a comment.
C2 = <<"-module(encoding).
@@ -1459,27 +1452,27 @@ encoding(Config) when is_list(Config) ->
{ok,[{attribute,1,file,_},
{attribute,1,module,encoding},
{eof,4}]} =
- epp:parse_file(ErlFile, []),
+ epp_parse_file(ErlFile, []),
{ok,[{attribute,1,file,_},
{attribute,1,module,encoding},
{eof,4}]} =
- epp:parse_file(ErlFile, [{default_encoding,latin1}]),
+ epp_parse_file(ErlFile, [{default_encoding,latin1}]),
{ok,[{attribute,1,file,_},
{attribute,1,module,encoding},
{eof,4}]} =
- epp:parse_file(ErlFile, [{default_encoding,utf8}]),
+ epp_parse_file(ErlFile, [{default_encoding,utf8}]),
{ok,[{attribute,1,file,_},
{attribute,1,module,encoding},
{eof,4}],[{encoding,latin1}]} =
- epp:parse_file(ErlFile, [extra]),
+ epp_parse_file(ErlFile, [extra]),
{ok,[{attribute,1,file,_},
{attribute,1,module,encoding},
{eof,4}],[{encoding,latin1}]} =
- epp:parse_file(ErlFile, [{default_encoding,latin1},extra]),
+ epp_parse_file(ErlFile, [{default_encoding,latin1},extra]),
{ok,[{attribute,1,file,_},
{attribute,1,module,encoding},
{eof,4}],[{encoding,latin1}]} =
- epp:parse_file(ErlFile, [{default_encoding,utf8},extra]),
+ epp_parse_file(ErlFile, [{default_encoding,utf8},extra]),
ok.
@@ -1552,6 +1545,17 @@ errs([_|L], File) ->
errs([], _File) ->
[].
+epp_parse_file(File, Opts) ->
+ case epp:parse_file(File, Opts) of
+ {ok, Forms} ->
+ {ok, unopaque_forms(Forms)};
+ {ok, Forms, Other} ->
+ {ok, unopaque_forms(Forms), Other}
+ end.
+
+unopaque_forms(Forms) ->
+ [erl_parse:anno_to_term(Form) || Form <- Forms].
+
run_test(Config, Test0) ->
Test = [<<"-module(epp_test). -compile(export_all). ">>, Test0],
Filename = "epp_test.erl",
diff --git a/lib/stdlib/test/erl_anno_SUITE.erl b/lib/stdlib/test/erl_anno_SUITE.erl
new file mode 100644
index 0000000000..d024f6907d
--- /dev/null
+++ b/lib/stdlib/test/erl_anno_SUITE.erl
@@ -0,0 +1,568 @@
+%%
+%% %CopyrightBegin%
+%%
+%% Copyright Ericsson AB 2001-2015. 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
+%% compliance with the License. You should have received a copy of the
+%% Erlang Public License along with this software. If not, it can be
+%% retrieved online at http://www.erlang.org/.
+%%
+%% Software distributed under the License is distributed on an "AS IS"
+%% basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See
+%% the License for the specific language governing rights and limitations
+%% under the License.
+%%
+%% %CopyrightEnd%
+%%
+-module(erl_anno_SUITE).
+
+%-define(debug, true).
+
+-ifdef(debug).
+-include_lib("test_server/include/test_server.hrl").
+-define(format(S, A), io:format(S, A)).
+-else.
+-include_lib("test_server/include/test_server.hrl").
+-define(format(S, A), ok).
+-endif.
+
+-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]).
+
+-export([new/1, is_anno/1, generated/1, end_location/1, file/1,
+ line/1, location/1, record/1, text/1, bad/1, neg_line/1]).
+
+-export([parse_abstract/1, mapfold_anno/1]).
+
+all() ->
+ [{group, anno}, {group, parse}].
+
+groups() ->
+ [{anno, [], [new, is_anno, generated, end_location, file,
+ line, location, record, text, bad, neg_line]},
+ {parse, [], [parse_abstract, mapfold_anno]}].
+
+suite() -> [{ct_hooks,[ts_install_cth]}].
+
+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) ->
+ Dog=?t:timetrap(?t:minutes(1)),
+ [{watchdog, Dog}|Config].
+
+end_per_testcase(_Case, _Config) ->
+ Dog=?config(watchdog, _Config),
+ test_server:timetrap_cancel(Dog),
+ ok.
+
+-define(INFO(T, V), {T, V}).
+
+-dialyzer({no_fail_call, new/1}).
+new(doc) ->
+ ["Test erl_anno:new/1"];
+new(_Config) ->
+ {'EXIT', {badarg, _}} =
+ (catch erl_anno:new([{location,1},{text, "text"}])), % badarg
+ ok.
+
+is_anno(doc) ->
+ ["Test erl_anno:is_anno/1"];
+is_anno(_Config) ->
+ false = erl_anno:is_anno(a),
+ false = erl_anno:is_anno({a}),
+ false = erl_anno:is_anno([]),
+ false = erl_anno:is_anno([{location, 1}|{generated, true}]),
+ false = erl_anno:is_anno([{generated,false}]),
+ false = erl_anno:is_anno([{generated,true}]),
+ false = erl_anno:is_anno([{location,1},{file,nofile}]),
+ false = erl_anno:is_anno([{location,1},{text,notext}]),
+
+ true = erl_anno:is_anno(erl_anno:new(1)),
+ A0 = erl_anno:new({1, 17}),
+ true = erl_anno:is_anno(A0),
+ A1 = erl_anno:set_generated(true, A0),
+ true = erl_anno:is_anno(A1),
+ A2 = erl_anno:set_file("", A1),
+ true = erl_anno:is_anno(A2),
+ A3 = erl_anno:set_record(true, A2),
+ true = erl_anno:is_anno(A3),
+ A4 = erl_anno:set_text("text", A3),
+ true = erl_anno:is_anno(A4),
+ A5 = erl_anno:set_file(<<"filename">>, A4),
+ true = erl_anno:is_anno(A5),
+ ok.
+
+generated(doc) ->
+ ["Test 'generated'"];
+generated(_Config) ->
+ test(1, [{generated, true}, {generated, false}]),
+ test(1, [{generated, false}, {generated, true}, {generated, false}]),
+ test({1, 17}, [{generated, false},
+ {generated, true},
+ {generated, false}]),
+ test({1, 17}, [{text, "text", [{end_location, {1, 21}}, {length, 4}]},
+ {generated, false},
+ {generated, true},
+ {generated, false}]),
+ test(1, [{generated, false},
+ {generated, true},
+ {generated, false}]),
+ test(1, [{text, "text", [{end_location, 1}, {length, 4}]},
+ {generated, false},
+ {generated, true},
+ {generated, false}]),
+ ok.
+
+end_location(doc) ->
+ ["Test 'end_location'"];
+end_location(_Config) ->
+ test({1, 17}, [{text, "TEXT", [{end_location, {1, 21}}, {length, 4}]},
+ {text, "TEXT\n", [{end_location, {2, 1}}, {length, 5}]},
+ {text, "TEXT\ntxt", [{end_location, {2, 4}}, {length, 8}]}]),
+ test(1, [{text, "TEXT", [{end_location, 1}, {length, 4}]},
+ {text, "TEXT\n", [{end_location, 2}, {length, 5}]},
+ {text, "TEXT\ntxt", [{end_location, 2}, {length, 8}]}]),
+ ok.
+
+file(doc) ->
+ ["Test 'file'"];
+file(_Config) ->
+ test(1, [{file, "name"}, {file, ""}]),
+ test({1, 17}, [{file, "name"}, {file, ""}]),
+ ok.
+
+line(doc) ->
+ ["Test 'line'"];
+line(_Config) ->
+ test(1, [{line, 17, [{location, 17}]},
+ {location, {9, 8}, [{line, 9}, {column, 8}]},
+ {line, 14, [{location, {14, 8}}]}]),
+ ok.
+
+location(doc) ->
+ ["Test 'location'"];
+location(_Config) ->
+ test(1, [{location, 2, [{line,2}]},
+ {location, {1, 17}, [{line, 1}, {column, 17}]},
+ {location, {9, 6}, [{line, 9}, {column, 6}]},
+ {location, 9, [{column, undefined}]}]),
+ test(1, [{generated, true},
+ {location, 2, [{line,2}]},
+ {location, {1, 17}, [{line, 1}, {column, 17}]},
+ {location, {9, 6}, [{line, 9}, {column, 6}]},
+ {location, 9, [{column, undefined}]}]),
+ test(1, [{record, true},
+ {location, 2, [{line,2}]},
+ {location, {1, 17}, [{line, 1}, {column, 17}]},
+ {location, {9, 6}, [{line, 9}, {column, 6}]},
+ {location, 9, [{column, undefined}]}]),
+ ok.
+
+record(doc) ->
+ ["Test 'record'"];
+record(_Config) ->
+ test({1, 17}, [{record, true}, {record, false}]),
+ test(1, [{record, true}, {record, false}]),
+ test({1, 17}, [{generated, false},
+ {generated, true},
+ {generated, false}]),
+ test({1, 17}, [{text, "text", [{end_location, {1, 21}}, {length, 4}]},
+ {generated, false},
+ {generated, true},
+ {generated, false}]),
+ test(1, [{generated, false},
+ {generated, true},
+ {generated, false}]),
+ test(1, [{text, "text", [{end_location, 1}, {length, 4}]},
+ {generated, false},
+ {generated, true},
+ {generated, false}]),
+ ok.
+
+text(doc) ->
+ ["Test 'text'"];
+text(_Config) ->
+ test(1, [{text, "text", [{end_location, 1}, {length, 4}]},
+ {text, "", [{end_location, 1}, {length, 0}]}]),
+ test({1, 17}, [{text, "text", [{end_location, {1,21}}, {length, 4}]},
+ {text, "", [{end_location, {1,17}}, {length, 0}]}]),
+ ok.
+
+-dialyzer({[no_opaque, no_fail_call], bad/1}).
+bad(doc) ->
+ ["Test bad annotations"];
+bad(_Config) ->
+ Line = erl_anno:new(1),
+ LineColumn = erl_anno:new({1, 17}),
+ {'EXIT', {badarg, _}} =
+ (catch erl_anno:set_generated(true, bad)), % 3rd arg not opaque
+ {'EXIT', {badarg, _}} =
+ (catch erl_anno:set_generated(false, bad)), % 3rd arg not opaque
+ {'EXIT', {badarg, _}} =
+ (catch erl_anno:set_generated(19, Line)),
+ {'EXIT', {badarg, _}} =
+ (catch erl_anno:set_generated(19, LineColumn)),
+
+ {'EXIT', {badarg, _}} =
+ (catch erl_anno:generated(bad)), % 1st arg not opaque
+ {'EXIT', {badarg, _}} =
+ (catch erl_anno:end_location(bad)), % 1st arg not opaque
+ {'EXIT', {badarg, _}} =
+ (catch erl_anno:file(bad)), % 1st arg not opaque
+ {'EXIT', {badarg, _}} =
+ (catch erl_anno:text(bad)), % 1st arg not opaque
+ {'EXIT', {badarg, _}} =
+ (catch erl_anno:record(bad)), % 1st arg not opaque
+ ok.
+
+neg_line(doc) ->
+ ["Test negative line numbers (OTP 18)"];
+neg_line(_Config) ->
+ neg_line1(false),
+ neg_line1(true),
+ ok.
+
+neg_line1(TextToo) ->
+ Minus8_0 = erl_anno:new(-8),
+ Plus8_0 = erl_anno:new(8),
+ Minus8C_0 = erl_anno:new({-8, 17}),
+ Plus8C_0 = erl_anno:new({8, 17}),
+
+ [Minus8, Plus8, Minus8C, Plus8C] =
+ [case TextToo of
+ true ->
+ erl_anno:set_text("foo", A);
+ false ->
+ A
+ end || A <- [Minus8_0, Plus8_0, Minus8C_0, Plus8C_0]],
+
+ tst(-3, erl_anno:set_location(3, Minus8)),
+ tst(-3, erl_anno:set_location(-3, Plus8)),
+ tst(-3, erl_anno:set_location(-3, Minus8)),
+ tst({-3,9}, erl_anno:set_location({3, 9}, Minus8)),
+ tst({-3,9}, erl_anno:set_location({-3, 9}, Plus8)),
+ tst({-3,9}, erl_anno:set_location({-3, 9}, Minus8)),
+ tst(-3, erl_anno:set_location(3, Minus8C)),
+ tst(-3, erl_anno:set_location(-3, Plus8C)),
+ tst(-3, erl_anno:set_location(-3, Minus8C)),
+ tst({-3,9}, erl_anno:set_location({3, 9}, Minus8C)),
+ tst({-3,9}, erl_anno:set_location({-3, 9}, Plus8C)),
+ tst({-3,9}, erl_anno:set_location({-3, 9}, Minus8C)),
+
+ tst(-8, erl_anno:set_generated(true, Plus8)),
+ tst(-8, erl_anno:set_generated(true, Minus8)),
+ tst({-8,17}, erl_anno:set_generated(true, Plus8C)),
+ tst({-8,17}, erl_anno:set_generated(true, Minus8C)),
+ tst(8, erl_anno:set_generated(false, Plus8)),
+ tst(8, erl_anno:set_generated(false, Minus8)),
+ tst({8,17}, erl_anno:set_generated(false, Plus8C)),
+ tst({8,17}, erl_anno:set_generated(false, Minus8C)),
+
+ tst(-3, erl_anno:set_line(3, Minus8)),
+ tst(-3, erl_anno:set_line(-3, Plus8)),
+ tst(-3, erl_anno:set_line(-3, Minus8)),
+ tst({-3,17}, erl_anno:set_line(3, Minus8C)),
+ tst({-3,17}, erl_anno:set_line(-3, Plus8C)),
+ tst({-3,17}, erl_anno:set_line(-3, Minus8C)),
+ ok.
+
+tst(Term, Anno) ->
+ ?format("Term: ~p\n", [Term]),
+ ?format("Anno: ~p\n", [Anno]),
+ case anno_to_term(Anno) of
+ Term ->
+ ok;
+ Else ->
+ case lists:keyfind(location, 1, Else) of
+ {location, Term} ->
+ ok;
+ _Else2 ->
+ ?format("Else2 ~p\n", [_Else2]),
+ io:format("expected ~p\n got ~p\n", [Term, Else]),
+ exit({Term, Else})
+ end
+ end.
+
+parse_abstract(doc) ->
+ ["Test erl_parse:new_anno/1, erl_parse:anno_to_term/1"
+ ", and erl_parse:anno_from_term/1"];
+parse_abstract(_Config) ->
+ T = sample_term(),
+ A = erl_parse:abstract(T, [{line,17}]),
+ T1 = erl_parse:anno_to_term(A),
+ Abstr = erl_parse:new_anno(T1),
+ T = erl_parse:normalise(Abstr),
+ Abstr2 = erl_parse:anno_from_term(T1),
+ T = erl_parse:normalise(Abstr2),
+ ok.
+
+mapfold_anno(doc) ->
+ ["Test erl_parse:{map_anno/2,fold_anno/3, and mapfold_anno/3}"];
+mapfold_anno(_Config) ->
+ T = sample_term(),
+ Abstr = erl_parse:abstract(T),
+ CF = fun(Anno, {L, D}) ->
+ {erl_anno:new(L), {L+1, dict:store(L, Anno, D)}}
+ end,
+ {U, {N, D}} = erl_parse:mapfold_anno(CF, {1, dict:new()}, Abstr),
+ SeqA = erl_parse:fold_anno(fun(Anno, Acc) -> [Anno|Acc] end, [], U),
+ Seq = [erl_anno:location(A) || A <- SeqA],
+ Seq = lists:seq(N-1, 1, -1),
+ NF = fun(Anno) ->
+ L = erl_anno:location(Anno),
+ dict:fetch(L, D)
+ end,
+ Abstr = erl_parse:map_anno(NF, U),
+ ok.
+
+sample_term() ->
+ %% This is just a sample.
+ {3,a,4.0,"foo",<<"bar">>,#{a => <<19:64/unsigned-little>>},
+ [1000,2000]}.
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+
+test(StartLocation, Updates) ->
+ S0 = init(StartLocation),
+ A0 = erl_anno:new(StartLocation),
+ chk(S0, A0, []),
+ eval(Updates, S0, A0).
+
+eval([], _S0, _A0) ->
+ ok;
+eval([{Item, Value}|Updates], S0, A0) ->
+ {S, A} = set(Item, Value, A0, S0, []),
+ eval(Updates, S, A);
+eval([{Item, Value, Secondary}|Updates], S0, A0) ->
+ {S, A} = set(Item, Value, A0, S0, Secondary),
+ eval(Updates, S, A).
+
+init({Line, Column}) ->
+ lists:sort([{location, {Line, Column}} | default()]);
+init(Line) when is_integer(Line) ->
+ lists:sort([{location, Line} | default()]).
+
+set(Item, Value, Anno0, State0, Secondary) ->
+ true = lists:member(Item, primary_items()),
+ ?format("Set '~w' to ~p\n", [Item, Value]),
+ State = set_value(Item, Value, State0),
+ Anno = anno_set(Item, Value, Anno0),
+ ?format("State0 ~p\n", [State0]),
+ ?format("State ~p\n", [State]),
+ ?format("Anno0 ~p\n", [anno_to_term(Anno0)]),
+ ?format("Anno ~p\n", [anno_to_term(Anno)]),
+ chk(State, Anno, Secondary),
+ ok = frame(Anno0, Anno, Secondary),
+ {State, Anno}.
+
+frame(OldAnno, NewAnno, Secondary) ->
+ SecItems = [I || {I, _} <- Secondary],
+ Frame = secondary_items() -- (SecItems ++ primary_items()),
+ ?format("Frame items ~p\n", [Frame]),
+ frame1(Frame, OldAnno, NewAnno).
+
+frame1([], _OldAnno, _NewAnno) ->
+ ok;
+frame1([Item|Items], OldAnno, NewAnno) ->
+ V1 = anno_info(OldAnno, Item),
+ V2 = anno_info(NewAnno, Item),
+ ok = check_value(Item, V1, V2),
+ frame1(Items, OldAnno, NewAnno).
+
+chk(State, Anno, Secondary) ->
+ ok = check_simple(Anno),
+ ok = chk_primary(State, Anno),
+ ok = check_secondary(Secondary, State, Anno).
+
+chk_primary(State, Anno) ->
+ chk_primary(primary_items(), State, Anno).
+
+chk_primary([], _State, _Anno) ->
+ ok;
+chk_primary([Item | Items], State, Anno) ->
+ V1 = primary_value(Item, State),
+ V2 = anno_info(Anno, Item),
+ ok = check_value(Item, V1, V2),
+ chk_primary(Items, State, Anno).
+
+check_secondary([], _State, _Anno) ->
+ ok;
+check_secondary([{Item, _}=V1 | Secondary], State, Anno) ->
+ V2 = anno_info(Anno, Item),
+ case {V1, V2} of
+ {{Item, undefined}, undefined} ->
+ ok;
+ _ ->
+ ok = check_value(Item, V1, V2)
+ end,
+ check_secondary(Secondary, State, Anno).
+
+check_value(Item, V1, V2) ->
+ ?format("~w: V1 ~p\n", [Item, V1]),
+ ?format("~w: V2 ~p\n", [Item, V2]),
+ case V1 =:= V2 of
+ true ->
+ ok;
+ false ->
+ io:format("~w: expected ~p\n got ~p\n", [Item, V1, V2]),
+ exit({V1, V2})
+ end.
+
+check_simple(Anno) ->
+ Term = anno_to_term(Anno),
+ case find_defaults(Term) of
+ [] ->
+ ok;
+ Ds ->
+ io:format("found default values ~w in ~p\n", [Ds, Anno]),
+ exit({defaults, Anno})
+ end,
+ case check_simple1(Term) of
+ true ->
+ ok;
+ false ->
+ io:format("not simple ~p\n", [Anno]),
+ exit({not_simple, Anno})
+ end.
+
+check_simple1(L) when is_integer(L) ->
+ true;
+check_simple1({L, C}) when is_integer(L), is_integer(C) ->
+ true;
+check_simple1(List) ->
+ case lists:sort(List) of
+ [{location, _}] ->
+ false;
+ _ ->
+ true
+ end.
+
+find_defaults(L) when is_list(L) ->
+ [I ||
+ I <- default_items(),
+ {I1, Value} <- L,
+ I =:= I1,
+ Value =:= default_value(I)];
+find_defaults(_) ->
+ [].
+
+anno_to_term(Anno) ->
+ T = erl_anno:to_term(Anno),
+ maybe_sort(T).
+
+maybe_sort(L) when is_list(L) ->
+ lists:sort(L);
+maybe_sort(T) ->
+ T.
+
+anno_set(file, Value, Anno) ->
+ erl_anno:set_file(Value, Anno);
+anno_set(generated, Value, Anno) ->
+ erl_anno:set_generated(Value, Anno);
+anno_set(line, Value, Anno) ->
+ erl_anno:set_line(Value, Anno);
+anno_set(location, Value, Anno) ->
+ erl_anno:set_location(Value, Anno);
+anno_set(record, Value, Anno) ->
+ erl_anno:set_record(Value, Anno);
+anno_set(text, Value, Anno) ->
+ erl_anno:set_text(Value, Anno).
+
+anno_info(Anno, Item) ->
+ Value =
+ case Item of
+ column ->
+ erl_anno:column(Anno);
+ generated ->
+ erl_anno:generated(Anno);
+ end_location ->
+ erl_anno:end_location(Anno);
+ file ->
+ erl_anno:file(Anno);
+ length ->
+ case erl_anno:text(Anno) of
+ undefined ->
+ undefined;
+ Text ->
+ length(Text)
+ end;
+ line ->
+ erl_anno:line(Anno);
+ location ->
+ erl_anno:location(Anno);
+ record ->
+ erl_anno:record(Anno);
+ text ->
+ erl_anno:text(Anno);
+ _ ->
+ erlang:error(badarg, [Anno, Item])
+ end,
+ if
+ Value =:= undefined ->
+ undefined;
+ true ->
+ {Item, Value}
+ end.
+
+%%% Originally 'location' was primary while 'line' and 'column' were
+%%% secondary (their values are determined by 'location'). But since
+%%% set_line() is used kind of frequently, 'line' is also primary,
+%%% and 'location' secondary (depends on 'line'). 'line' need to be
+%%% handled separately.
+
+set_value(line, Line, State) ->
+ {location, Location} = primary_value(location, State),
+ NewLocation = case Location of
+ {_, Column} ->
+ {Line, Column};
+ _ ->
+ Line
+ end,
+ set_value(location, NewLocation, State);
+set_value(Item, Value, State) ->
+ lists:ukeymerge(1, [{Item, Value}], State).
+
+primary_value(line, State) ->
+ {location, Location} = primary_value(location, State),
+ {line, case Location of
+ {Line, _} ->
+ Line;
+ Line ->
+ Line
+ end};
+primary_value(Item, State) ->
+ case lists:keyfind(Item, 1, State) of
+ false ->
+ undefined;
+ Tuple ->
+ Tuple
+ end.
+
+default() ->
+ [{Tag, default_value(Tag)} || Tag <- default_items()].
+
+primary_items() ->
+ [file, generated, line, location, record, text].
+
+secondary_items() ->
+ %% 'length' has not been implemented
+ [column, end_location, length, line, location].
+
+default_items() ->
+ [generated, record].
+
+default_value(generated) -> false;
+default_value(record) -> false.
diff --git a/lib/stdlib/test/erl_eval_SUITE.erl b/lib/stdlib/test/erl_eval_SUITE.erl
index b55324161b..a750c5cace 100644
--- a/lib/stdlib/test/erl_eval_SUITE.erl
+++ b/lib/stdlib/test/erl_eval_SUITE.erl
@@ -1458,8 +1458,35 @@ eep43(Config) when is_list(Config) ->
"lists:map(fun (X) -> X#{price := 0} end,
[#{hello => 0, price => nil}]).",
[#{hello => 0, price => 0}]),
- error_check("[camembert]#{}.", {badarg,[camembert]}),
+ check(fun () ->
+ Map = #{ <<33:333>> => "wat" },
+ #{ <<33:333>> := "wat" } = Map
+ end,
+ "begin "
+ " Map = #{ <<33:333>> => \"wat\" }, "
+ " #{ <<33:333>> := \"wat\" } = Map "
+ "end.",
+ #{ <<33:333>> => "wat" }),
+ check(fun () ->
+ K1 = 1,
+ K2 = <<42:301>>,
+ K3 = {3,K2},
+ Map = #{ K1 => 1, K2 => 2, K3 => 3, {2,2} => 4},
+ #{ K1 := 1, K2 := 2, K3 := 3, {2,2} := 4} = Map
+ end,
+ "begin "
+ " K1 = 1, "
+ " K2 = <<42:301>>, "
+ " K3 = {3,K2}, "
+ " Map = #{ K1 => 1, K2 => 2, K3 => 3, {2,2} => 4}, "
+ " #{ K1 := 1, K2 := 2, K3 := 3, {2,2} := 4} = Map "
+ "end.",
+ #{ 1 => 1, <<42:301>> => 2, {3,<<42:301>>} => 3, {2,2} => 4}),
+ error_check("[camembert]#{}.", {badmap,[camembert]}),
+ error_check("[camembert]#{nonexisting:=v}.", {badmap,[camembert]}),
error_check("#{} = 1.", {badmatch,1}),
+ error_check("[]#{a=>error(bad)}.", bad),
+ error_check("(#{})#{nonexisting:=value}.", {badkey,nonexisting}),
ok.
%% Check the string in different contexts: as is; in fun; from compiled code.
diff --git a/lib/stdlib/test/erl_internal_SUITE.erl b/lib/stdlib/test/erl_internal_SUITE.erl
index b6b3c004ea..197a7a33eb 100644
--- a/lib/stdlib/test/erl_internal_SUITE.erl
+++ b/lib/stdlib/test/erl_internal_SUITE.erl
@@ -1,7 +1,7 @@
%%
%% %CopyrightBegin%
%%
-%% Copyright Ericsson AB 1999-2011. 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
@@ -51,7 +51,7 @@ end_per_group(_GroupName, Config) ->
-define(default_timeout, ?t:minutes(2)).
init_per_testcase(_Case, Config) ->
- ?line Dog = test_server:timetrap(?default_timeout),
+ Dog = test_server:timetrap(?default_timeout),
[{watchdog, Dog}|Config].
end_per_testcase(_Case, Config) ->
@@ -63,27 +63,50 @@ behav(suite) -> [];
behav(doc) ->
["Check that the behaviour callbacks are correctly defined"];
behav(_) ->
- ?line check_behav_list([{start,2}, {stop,1}],
- application:behaviour_info(callbacks)),
- ?line check_behav_list([{init,1}, {handle_call,3}, {handle_cast,2},
- {handle_info,2}, {terminate,2}, {code_change,3}],
- gen_server:behaviour_info(callbacks)),
- ?line check_behav_list([{init,1}, {handle_event,3}, {handle_sync_event,4},
- {handle_info,3}, {terminate,3}, {code_change,4}],
- gen_fsm:behaviour_info(callbacks)),
- ?line check_behav_list([{init,1}, {handle_event,2}, {handle_call,2},
- {handle_info,2}, {terminate,2}, {code_change,3}],
- gen_event:behaviour_info(callbacks)),
- ?line check_behav_list( [{init,1}, {terminate,2}],
- supervisor_bridge:behaviour_info(callbacks)),
- ?line check_behav_list([{init,1}],
- supervisor:behaviour_info(callbacks)),
- ok.
+ Modules = [application, gen_server, gen_fsm, gen_event,
+ supervisor_bridge, supervisor],
+ lists:foreach(fun check_behav/1, Modules).
+
+check_behav(Module) ->
+ Callbacks = callbacks(Module),
+ Optional = optional_callbacks(Module),
+ check_behav_list(Callbacks, Module:behaviour_info(callbacks)),
+ check_behav_list(Optional, Module:behaviour_info(optional_callbacks)).
check_behav_list([], []) -> ok;
check_behav_list([L | L1], L2) ->
- ?line true = lists:member(L, L2),
- ?line L3 = lists:delete(L, L2),
+ true = lists:member(L, L2),
+ L3 = lists:delete(L, L2),
check_behav_list(L1, L3).
-
+callbacks(application) ->
+ [{start,2}, {stop,1}];
+callbacks(gen_server) ->
+ [{init,1}, {handle_call,3}, {handle_cast,2},
+ {handle_info,2}, {terminate,2}, {code_change,3},
+ {format_status,2}];
+callbacks(gen_fsm) ->
+ [{init,1}, {handle_event,3}, {handle_sync_event,4},
+ {handle_info,3}, {terminate,3}, {code_change,4},
+ {format_status,2}];
+callbacks(gen_event) ->
+ [{init,1}, {handle_event,2}, {handle_call,2},
+ {handle_info,2}, {terminate,2}, {code_change,3},
+ {format_status,2}];
+callbacks(supervisor_bridge) ->
+ [{init,1}, {terminate,2}];
+callbacks(supervisor) ->
+ [{init,1}].
+
+optional_callbacks(application) ->
+ [];
+optional_callbacks(gen_server) ->
+ [{format_status,2}];
+optional_callbacks(gen_fsm) ->
+ [{format_status,2}];
+optional_callbacks(gen_event) ->
+ [{format_status,2}];
+optional_callbacks(supervisor_bridge) ->
+ [];
+optional_callbacks(supervisor) ->
+ [].
diff --git a/lib/stdlib/test/erl_lint_SUITE.erl b/lib/stdlib/test/erl_lint_SUITE.erl
index ea61b2082b..c0d9b7c466 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-2014. All Rights Reserved.
+%% Copyright Ericsson AB 1999-2015. 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
@@ -42,6 +42,7 @@
unused_vars_warn_rec/1,
unused_vars_warn_fun/1,
unused_vars_OTP_4858/1,
+ unused_unsafe_vars_warn/1,
export_vars_warn/1,
shadow_vars/1,
unused_import/1,
@@ -55,7 +56,7 @@
otp_11772/1, otp_11771/1, otp_11872/1,
export_all/1,
bif_clash/1,
- behaviour_basic/1, behaviour_multiple/1,
+ behaviour_basic/1, behaviour_multiple/1, otp_11861/1,
otp_7550/1,
otp_8051/1,
format_warn/1,
@@ -63,7 +64,7 @@
too_many_arguments/1,
basic_errors/1,bin_syntax_errors/1,
predef/1,
- maps/1,maps_type/1
+ maps/1,maps_type/1,otp_11851/1,otp_12195/1
]).
% Default timetrap timeout (set in init_per_testcase).
@@ -89,16 +90,16 @@ all() ->
otp_5362, otp_5371, otp_7227, otp_5494, otp_5644,
otp_5878, otp_5917, otp_6585, otp_6885, otp_10436, otp_11254,
otp_11772, otp_11771, otp_11872, export_all,
- bif_clash, behaviour_basic, behaviour_multiple,
+ bif_clash, behaviour_basic, behaviour_multiple, otp_11861,
otp_7550, otp_8051, format_warn, {group, on_load},
too_many_arguments, basic_errors, bin_syntax_errors, predef,
- maps, maps_type].
+ maps, maps_type, otp_11851, otp_12195].
groups() ->
[{unused_vars_warn, [],
[unused_vars_warn_basic, unused_vars_warn_lc,
unused_vars_warn_rec, unused_vars_warn_fun,
- unused_vars_OTP_4858]},
+ unused_vars_OTP_4858, unused_unsafe_vars_warn]},
{on_load, [], [on_load_successful, on_load_failing]}].
init_per_suite(Config) ->
@@ -730,6 +731,48 @@ unused_vars_OTP_4858(Config) when is_list(Config) ->
?line [] = run(Config, Ts),
ok.
+unused_unsafe_vars_warn(Config) when is_list(Config) ->
+ Ts = [{unused_unsafe1,
+ <<"t1() ->
+ UnusedVar1 = unused1,
+ try
+ UnusedVar2 = unused2
+ catch
+ _:_ ->
+ ok
+ end,
+ ok.
+ ">>,
+ [warn_unused_vars],
+ {warnings,[{2,erl_lint,{unused_var,'UnusedVar1'}},
+ {4,erl_lint,{unused_var,'UnusedVar2'}}]}},
+ {unused_unsafe2,
+ <<"t2() ->
+ try
+ X = 1
+ catch
+ _:_ -> ok
+ end.
+ ">>,
+ [warn_unused_vars],
+ {warnings,[{3,erl_lint,{unused_var,'X'}}]}},
+ {unused_unsafe2,
+ <<"t3(X, Y) ->
+ X andalso Y.
+ ">>,
+ [warn_unused_vars],
+ []},
+ {unused_unsafe4,
+ <<"t4() ->
+ _ = (catch X = X = 1),
+ _ = case ok of _ -> fun() -> ok end end,
+ fun (X) -> X end.
+ ">>,
+ [warn_unused_vars],
+ []}],
+ run(Config, Ts),
+ ok.
+
export_vars_warn(doc) ->
"Warnings for exported variables";
export_vars_warn(suite) -> [];
@@ -808,7 +851,19 @@ export_vars_warn(Config) when is_list(Config) ->
[],
{error,[{9,erl_lint,{unbound_var,'B'}}],
[{9,erl_lint,{exported_var,'Y',{'receive',2}}},
- {10,erl_lint,{shadowed_var,'B',generate}}]}}
+ {10,erl_lint,{shadowed_var,'B',generate}}]}},
+
+ {exp4,
+ <<"t(X) ->
+ if true -> Z = X end,
+ case X of
+ 1 -> Z;
+ 2 -> X
+ end,
+ Z = X.
+ ">>,
+ [],
+ {warnings,[{7,erl_lint,{exported_var,'Z',{'if',2}}}]}}
],
?line [] = run(Config, Ts),
ok.
@@ -832,8 +887,15 @@ shadow_vars(Config) when is_list(Config) ->
">>,
[nowarn_shadow_vars],
{error,[{9,erl_lint,{unbound_var,'B'}}],
- [{9,erl_lint,{exported_var,'Y',{'receive',2}}}]}}],
-
+ [{9,erl_lint,{exported_var,'Y',{'receive',2}}}]}},
+ {shadow2,
+ <<"t() ->
+ _ = (catch MS = MS = 1), % MS used unsafe
+ _ = case ok of _ -> fun() -> ok end end,
+ fun (MS) -> MS end. % MS not shadowed here
+ ">>,
+ [],
+ []}],
?line [] = run(Config, Ts),
ok.
@@ -958,6 +1020,45 @@ unsafe_vars(Config) when is_list(Config) ->
[warn_unused_vars],
{errors,[{3,erl_lint,{unsafe_var,'X',{'if',2}}},
{4,erl_lint,{unsafe_var,'X',{'if',2}}}],
+ []}},
+ {unsafe8,
+ <<"t8(X) ->
+ case X of _ -> catch _Y = 1 end,
+ _Y."
+ >>,
+ [],
+ {errors,[{3,erl_lint,{unsafe_var,'_Y',{'catch',2}}}],
+ []}},
+ {unsafe9,
+ <<"t9(X) ->
+ case X of
+ 1 ->
+ catch A = 1, % unsafe only here
+ B = 1,
+ C = 1,
+ D = 1;
+ 2 ->
+ A = 2,
+ % B not bound here
+ C = 2,
+ catch D = 2; % unsafe in two clauses
+ 3 ->
+ A = 3,
+ B = 3,
+ C = 3,
+ catch D = 3; % unsafe in two clauses
+ 4 ->
+ A = 4,
+ B = 4,
+ C = 4,
+ D = 4
+ end,
+ {A,B,C,D}."
+ >>,
+ [],
+ {errors,[{24,erl_lint,{unsafe_var,'A',{'catch',4}}},
+ {24,erl_lint,{unsafe_var,'B',{'case',2}}},
+ {24,erl_lint,{unsafe_var,'D',{'case',2}}}],
[]}}
],
?line [] = run(Config, Ts),
@@ -2648,8 +2749,9 @@ otp_11872(Config) when is_list(Config) ->
t() ->
1.
">>,
- {error,[{6,erl_lint,{undefined_type,{product,0}}}],
- [{8,erl_lint,{new_var_arity_type,map}}]} =
+ {error,[{6,erl_lint,{undefined_type,{product,0}}},
+ {8,erl_lint,{undefined_type,{dict,0}}}],
+ [{8,erl_lint,{new_builtin_type,{map,0}}}]} =
run_test2(Config, Ts, []),
ok.
@@ -3080,6 +3182,193 @@ behaviour_multiple(Config) when is_list(Config) ->
?line [] = run(Config, Ts),
ok.
+otp_11861(doc) ->
+ "OTP-11861. behaviour_info() and -callback.";
+otp_11861(suite) -> [];
+otp_11861(Conf) when is_list(Conf) ->
+ CallbackFiles = [callback1, callback2, callback3,
+ bad_behaviour1, bad_behaviour2],
+ lists:foreach(fun(M) ->
+ F = filename:join(?datadir, M),
+ Opts = [{outdir,?privdir}, return],
+ {ok, M, []} = compile:file(F, Opts)
+ end, CallbackFiles),
+ CodePath = code:get_path(),
+ true = code:add_path(?privdir),
+ Ts = [{otp_11861_1,
+ <<"
+ -export([b1/1]).
+ -behaviour(callback1).
+ -behaviour(callback2).
+
+ -spec b1(atom()) -> integer().
+ b1(A) when is_atom(A)->
+ 3.
+ ">>,
+ [],
+ %% b2/1 is optional in both modules
+ {warnings,[{4,erl_lint,
+ {conflicting_behaviours,{b1,1},callback2,3,callback1}}]}},
+ {otp_11861_2,
+ <<"
+ -export([b2/1]).
+ -behaviour(callback1).
+ -behaviour(callback2).
+
+ -spec b2(integer()) -> atom().
+ b2(I) when is_integer(I)->
+ a.
+ ">>,
+ [],
+ %% b2/1 is optional in callback2, but not in callback1
+ {warnings,[{3,erl_lint,{undefined_behaviour_func,{b1,1},callback1}},
+ {4,erl_lint,
+ {conflicting_behaviours,{b2,1},callback2,3,callback1}}]}},
+ {otp_11861_3,
+ <<"
+ -callback b(_) -> atom().
+ -optional_callbacks({b1,1}). % non-existing and ignored
+ ">>,
+ [],
+ []},
+ {otp_11861_4,
+ <<"
+ -callback b(_) -> atom().
+ -optional_callbacks([{b1,1}]). % non-existing
+ ">>,
+ [],
+ %% No behaviour-info(), but callback.
+ {errors,[{3,erl_lint,{undefined_callback,{lint_test,b1,1}}}],[]}},
+ {otp_11861_5,
+ <<"
+ -optional_callbacks([{b1,1}]). % non-existing
+ ">>,
+ [],
+ %% No behaviour-info() and no callback: warning anyway
+ {errors,[{2,erl_lint,{undefined_callback,{lint_test,b1,1}}}],[]}},
+ {otp_11861_6,
+ <<"
+ -optional_callbacks([b1/1]). % non-existing
+ behaviour_info(callbacks) -> [{b1,1}].
+ ">>,
+ [],
+ %% behaviour-info() and no callback: warning anyway
+ {errors,[{2,erl_lint,{undefined_callback,{lint_test,b1,1}}}],[]}},
+ {otp_11861_7,
+ <<"
+ -optional_callbacks([b1/1]). % non-existing
+ -callback b(_) -> atom().
+ behaviour_info(callbacks) -> [{b1,1}].
+ ">>,
+ [],
+ %% behaviour-info() callback: warning
+ {errors,[{2,erl_lint,{undefined_callback,{lint_test,b1,1}}},
+ {3,erl_lint,{behaviour_info,{lint_test,b,1}}}],
+ []}},
+ {otp_11861_8,
+ <<"
+ -callback b(_) -> atom().
+ -optional_callbacks([b/1, {b, 1}]).
+ ">>,
+ [],
+ {errors,[{3,erl_lint,{redefine_optional_callback,{b,1}}}],[]}},
+ {otp_11861_9,
+ <<"
+ -behaviour(gen_server).
+ -export([handle_call/3,handle_cast/2,handle_info/2,
+ code_change/3, init/1, terminate/2]).
+ handle_call(_, _, _) -> ok.
+ handle_cast(_, _) -> ok.
+ handle_info(_, _) -> ok.
+ code_change(_, _, _) -> ok.
+ init(_) -> ok.
+ terminate(_, _) -> ok.
+ ">>,
+ [],
+ []},
+ {otp_11861_9,
+ <<"
+ -behaviour(gen_server).
+ -export([handle_call/3,handle_cast/2,handle_info/2,
+ code_change/3, init/1, terminate/2, format_status/2]).
+ handle_call(_, _, _) -> ok.
+ handle_cast(_, _) -> ok.
+ handle_info(_, _) -> ok.
+ code_change(_, _, _) -> ok.
+ init(_) -> ok.
+ terminate(_, _) -> ok.
+ format_status(_, _) -> ok. % optional callback
+ ">>,
+ [],
+ %% Nothing...
+ []},
+ {otp_11861_10,
+ <<"
+ -optional_callbacks([{b1,1,bad}]). % badly formed and ignored
+ behaviour_info(callbacks) -> [{b1,1}].
+ ">>,
+ [],
+ []},
+ {otp_11861_11,
+ <<"
+ -behaviour(bad_behaviour1).
+ ">>,
+ [],
+ {warnings,[{2,erl_lint,
+ {ill_defined_behaviour_callbacks,bad_behaviour1}}]}},
+ {otp_11861_12,
+ <<"
+ -behaviour(non_existing_behaviour).
+ ">>,
+ [],
+ {warnings,[{2,erl_lint,
+ {undefined_behaviour,non_existing_behaviour}}]}},
+ {otp_11861_13,
+ <<"
+ -behaviour(bad_behaviour_none).
+ ">>,
+ [],
+ {warnings,[{2,erl_lint,{undefined_behaviour,bad_behaviour_none}}]}},
+ {otp_11861_14,
+ <<"
+ -callback b(_) -> atom().
+ ">>,
+ [],
+ []},
+ {otp_11861_15,
+ <<"
+ -optional_callbacks([{b1,1,bad}]). % badly formed
+ -callback b(_) -> atom().
+ ">>,
+ [],
+ []},
+ {otp_11861_16,
+ <<"
+ -callback b(_) -> atom().
+ -callback b(_) -> atom().
+ ">>,
+ [],
+ {errors,[{3,erl_lint,{redefine_callback,{b,1}}}],[]}},
+ {otp_11861_17,
+ <<"
+ -behaviour(bad_behaviour2).
+ ">>,
+ [],
+ {warnings,[{2,erl_lint,{undefined_behaviour_callbacks,
+ bad_behaviour2}}]}},
+ {otp_11861_18,
+ <<"
+ -export([f1/1]).
+ -behaviour(callback3).
+ f1(_) -> ok.
+ ">>,
+ [],
+ []}
+ ],
+ ?line [] = run(Conf, Ts),
+ true = code:set_path(CodePath),
+ ok.
+
otp_7550(doc) ->
"Test that the new utf8/utf16/utf32 types do not allow size or unit specifiers.";
otp_7550(Config) when is_list(Config) ->
@@ -3145,8 +3434,8 @@ format_warn(Config) when is_list(Config) ->
ok.
format_level(Level, Count, Config) ->
- ?line W = get_compilation_warnings(Config, "format",
- [{warn_format, Level}]),
+ ?line W = get_compilation_result(Config, "format",
+ [{warn_format, Level}]),
%% Pick out the 'format' warnings.
?line FW = lists:filter(fun({_Line, erl_lint, {format_error, _}}) -> true;
(_) -> false
@@ -3330,42 +3619,22 @@ bin_syntax_errors(Config) ->
ok.
predef(doc) ->
- "OTP-10342: Predefined types: array(), digraph(), and so on";
+ "OTP-10342: No longer predefined types: array(), digraph(), and so on";
predef(suite) -> [];
predef(Config) when is_list(Config) ->
- W = get_compilation_warnings(Config, "predef", []),
+ W = get_compilation_result(Config, "predef", []),
[] = W,
- W2 = get_compilation_warnings(Config, "predef2", []),
- Tag = deprecated_builtin_type,
- [{7,erl_lint,{Tag,{array,0},{array,array,1},"OTP 18.0"}},
- {12,erl_lint,{Tag,{dict,0},{dict,dict,2},"OTP 18.0"}},
- {17,erl_lint,{Tag,{digraph,0},{digraph,graph},"OTP 18.0"}},
- {27,erl_lint,{Tag,{gb_set,0},{gb_sets,set,1},"OTP 18.0"}},
- {32,erl_lint,{Tag,{gb_tree,0},{gb_trees,tree,2},"OTP 18.0"}},
- {37,erl_lint,{Tag,{queue,0},{queue,queue,1},"OTP 18.0"}},
- {42,erl_lint,{Tag,{set,0},{sets,set,1},"OTP 18.0"}},
- {47,erl_lint,{Tag,{tid,0},{ets,tid},"OTP 18.0"}}] = W2,
- Ts = [{otp_10342_1,
- <<"-compile(nowarn_deprecated_type).
-
- -spec t(dict()) -> non_neg_integer().
-
- t(D) ->
- erlang:phash2(D, 3000).
- ">>,
- {[nowarn_unused_function]},
- []},
- {otp_10342_2,
- <<"-spec t(dict()) -> non_neg_integer().
-
- t(D) ->
- erlang:phash2(D, 3000).
- ">>,
- {[nowarn_unused_function]},
- {warnings,[{1,erl_lint,
- {deprecated_builtin_type,{dict,0},{dict,dict,2},
- "OTP 18.0"}}]}}],
- [] = run(Config, Ts),
+ %% dict(), digraph() and so on were removed in Erlang/OTP 18.0.
+ E2 = get_compilation_result(Config, "predef2", []),
+ Tag = undefined_type,
+ {[{7,erl_lint,{Tag,{array,0}}},
+ {12,erl_lint,{Tag,{dict,0}}},
+ {17,erl_lint,{Tag,{digraph,0}}},
+ {27,erl_lint,{Tag,{gb_set,0}}},
+ {32,erl_lint,{Tag,{gb_tree,0}}},
+ {37,erl_lint,{Tag,{queue,0}}},
+ {42,erl_lint,{Tag,{set,0}}},
+ {47,erl_lint,{Tag,{tid,0}}}],[]} = E2,
ok.
maps(Config) ->
@@ -3398,7 +3667,8 @@ maps(Config) ->
g := 1 + 1,
h := _,
i := (_X = _Y),
- j := (x ! y) }) ->
+ j := (x ! y),
+ <<0:300>> := 33}) ->
{A,F}.
">>,
[],
@@ -3411,9 +3681,10 @@ maps(Config) ->
{errors,[{1,erl_lint,illegal_map_construction},
{1,erl_lint,{unbound_var,'X'}}],
[]}},
- {errors_in_map_keys,
+ {legal_map_construction,
<<"t(V) -> #{ a => 1,
#{a=>V} => 2,
+ #{{a,V}=>V} => 2,
#{ \"hi\" => wazzup, hi => ho } => yep,
[try a catch _:_ -> b end] => nope,
ok => 1.0,
@@ -3425,11 +3696,7 @@ maps(Config) ->
}.
">>,
[],
- {errors,[{2,erl_lint,{illegal_map_key_variable,'V'}},
- {4,erl_lint,illegal_map_key},
- {6,erl_lint,illegal_map_key},
- {8,erl_lint,illegal_map_key},
- {10,erl_lint,illegal_map_key}],[]}},
+ []},
{errors_in_map_keys_pattern,
<<"t(#{ a := 2,
#{} := A,
@@ -3440,8 +3707,14 @@ maps(Config) ->
A.
">>,
[],
- {errors,[{4,erl_lint,illegal_map_key},
- {6,erl_lint,{illegal_map_key_variable,'V'}}],[]}}],
+ {errors,[{4,erl_lint,illegal_map_construction},
+ {6,erl_lint,illegal_map_key}],[]}},
+ {unused_vars_with_empty_maps,
+ <<"t(Foo, Bar, Baz) -> {#{},#{}}.">>,
+ [warn_unused_variables],
+ {warnings,[{1,erl_lint,{unused_var,'Bar'}},
+ {1,erl_lint,{unused_var,'Baz'}},
+ {1,erl_lint,{unused_var,'Foo'}}]}}],
[] = run(Config, Ts),
ok.
@@ -3470,7 +3743,128 @@ maps_type(Config) when is_list(Config) ->
t(M) -> M.
">>,
[],
- {warnings,[{3,erl_lint,{new_var_arity_type,map}}]}}],
+ {warnings,[{3,erl_lint,{new_builtin_type,{map,0}}}]}}],
+ [] = run(Config, Ts),
+ ok.
+
+otp_11851(doc) ->
+ "OTP-11851: More atoms can be used as type names + bug fixes.";
+otp_11851(Config) when is_list(Config) ->
+ Ts = [
+ {otp_11851_1,
+ <<"-export([t/0]).
+ -type range(A, B) :: A | B.
+
+ -type union(A) :: A.
+
+ -type product() :: integer().
+
+ -type tuple(A) :: A.
+
+ -type map(A) :: A.
+
+ -type record() :: a | b.
+
+ -type integer(A) :: A.
+
+ -type atom(A) :: A.
+
+ -type binary(A, B) :: A | B.
+
+ -type 'fun'() :: integer().
+
+ -type 'fun'(X) :: X.
+
+ -type 'fun'(X, Y) :: X | Y.
+
+ -type all() :: range(atom(), integer()) | union(pid()) | product()
+ | tuple(reference()) | map(function()) | record()
+ | integer(atom()) | atom(integer())
+ | binary(pid(), tuple()) | 'fun'(port())
+ | 'fun'() | 'fun'(<<>>, 'none').
+
+ -spec t() -> all().
+
+ t() ->
+ a.
+ ">>,
+ [],
+ []},
+ {otp_11851_2,
+ <<"-export([a/1, b/1, t/0]).
+
+ -callback b(_) -> integer().
+
+ -callback ?MODULE:a(_) -> integer().
+
+ a(_) -> 3.
+
+ b(_) -> a.
+
+ t()-> a.
+ ">>,
+ [],
+ {errors,[{5,erl_lint,{bad_callback,{lint_test,a,1}}}],[]}},
+ {otp_11851_3,
+ <<"-export([a/1]).
+
+ -spec a(_A) -> boolean() when
+ _ :: atom(),
+ _A :: integer().
+
+ a(_) -> true.
+ ">>,
+ [],
+ {errors,[{4,erl_parse,"bad type variable"}],[]}},
+ {otp_11851_4,
+ <<"
+ -spec a(_) -> ok.
+ -spec a(_) -> ok.
+
+ -spec ?MODULE:a(_) -> ok.
+ -spec ?MODULE:a(_) -> ok.
+ ">>,
+ [],
+ {errors,[{3,erl_lint,{redefine_spec,{a,1}}},
+ {5,erl_lint,{redefine_spec,{lint_test,a,1}}},
+ {6,erl_lint,{redefine_spec,{lint_test,a,1}}},
+ {6,erl_lint,{spec_fun_undefined,{a,1}}}],
+ []}}
+ ],
+ [] = run(Config, Ts),
+ ok.
+
+otp_12195(doc) ->
+ "OTP-12195: Check obsolete types (tailor made for OTP 18).";
+otp_12195(Config) when is_list(Config) ->
+ Ts = [{otp_12195_1,
+ <<"-export_type([r1/0]).
+ -type r1() :: erl_scan:line()
+ | erl_scan:column()
+ | erl_scan:location()
+ | erl_anno:line().">>,
+ [],
+ {warnings,[{2,erl_lint,
+ {deprecated_type,{erl_scan,line,0},
+ "deprecated (will be removed in OTP 19); "
+ "use erl_anno:line() instead"}},
+ {3,erl_lint,
+ {deprecated_type,{erl_scan,column,0},
+ "deprecated (will be removed in OTP 19); use "
+ "erl_anno:column() instead"}},
+ {4,erl_lint,
+ {deprecated_type,{erl_scan,location,0},
+ "deprecated (will be removed in OTP 19); "
+ "use erl_anno:location() instead"}}]}},
+ {otp_12195_2,
+ <<"-export_type([r1/0]).
+ -compile(nowarn_deprecated_type).
+ -type r1() :: erl_scan:line()
+ | erl_scan:column()
+ | erl_scan:location()
+ | erl_anno:line().">>,
+ [],
+ []}],
[] = run(Config, Ts),
ok.
@@ -3487,9 +3881,9 @@ run(Config, Tests) ->
end,
lists:foldl(F, [], Tests).
-%% Compiles a test file and returns the list of warnings.
+%% Compiles a test file and returns the list of warnings/errors.
-get_compilation_warnings(Conf, Filename, Warnings) ->
+get_compilation_result(Conf, Filename, Warnings) ->
?line DataDir = ?datadir,
?line File = filename:join(DataDir, Filename),
{ok,Bin} = file:read_file(File++".erl"),
@@ -3498,6 +3892,7 @@ get_compilation_warnings(Conf, Filename, Warnings) ->
Test = lists:nthtail(Start+Length, FileS),
case run_test(Conf, Test, Warnings) of
{warnings, Ws} -> Ws;
+ {errors,Es,Ws} -> {Es,Ws};
[] -> []
end.
diff --git a/lib/stdlib/test/erl_lint_SUITE_data/bad_behaviour1.erl b/lib/stdlib/test/erl_lint_SUITE_data/bad_behaviour1.erl
new file mode 100644
index 0000000000..230f4b4519
--- /dev/null
+++ b/lib/stdlib/test/erl_lint_SUITE_data/bad_behaviour1.erl
@@ -0,0 +1,6 @@
+-module(bad_behaviour1).
+
+-export([behaviour_info/1]).
+
+behaviour_info(callbacks) ->
+ [{a,1,bad}].
diff --git a/lib/stdlib/test/erl_lint_SUITE_data/bad_behaviour2.erl b/lib/stdlib/test/erl_lint_SUITE_data/bad_behaviour2.erl
new file mode 100644
index 0000000000..bb755ce18b
--- /dev/null
+++ b/lib/stdlib/test/erl_lint_SUITE_data/bad_behaviour2.erl
@@ -0,0 +1,6 @@
+-module(bad_behaviour2).
+
+-export([behaviour_info/1]).
+
+behaviour_info(callbacks) ->
+ undefined.
diff --git a/lib/stdlib/test/erl_lint_SUITE_data/callback1.erl b/lib/stdlib/test/erl_lint_SUITE_data/callback1.erl
new file mode 100644
index 0000000000..3cc5b51879
--- /dev/null
+++ b/lib/stdlib/test/erl_lint_SUITE_data/callback1.erl
@@ -0,0 +1,6 @@
+-module(callback1).
+
+-callback b1(I :: integer()) -> atom().
+-callback b2(A :: atom()) -> integer().
+
+-optional_callbacks([{b2,1}]).
diff --git a/lib/stdlib/test/erl_lint_SUITE_data/callback2.erl b/lib/stdlib/test/erl_lint_SUITE_data/callback2.erl
new file mode 100644
index 0000000000..211cf9f115
--- /dev/null
+++ b/lib/stdlib/test/erl_lint_SUITE_data/callback2.erl
@@ -0,0 +1,6 @@
+-module(callback2).
+
+-callback b1(I :: integer()) -> atom().
+-callback b2(A :: atom()) -> integer().
+
+-optional_callbacks([b1/1, b2/1]).
diff --git a/lib/stdlib/test/erl_lint_SUITE_data/callback3.erl b/lib/stdlib/test/erl_lint_SUITE_data/callback3.erl
new file mode 100644
index 0000000000..97b3ecb860
--- /dev/null
+++ b/lib/stdlib/test/erl_lint_SUITE_data/callback3.erl
@@ -0,0 +1,8 @@
+-module(callback3).
+
+-export([behaviour_info/1]).
+
+behaviour_info(callbacks) ->
+ [{f1, 1}];
+behaviour_info(_) ->
+ undefined.
diff --git a/lib/stdlib/test/erl_lint_SUITE_data/predef.erl b/lib/stdlib/test/erl_lint_SUITE_data/predef.erl
index ee9073aa67..3cb7bf40f1 100644
--- a/lib/stdlib/test/erl_lint_SUITE_data/predef.erl
+++ b/lib/stdlib/test/erl_lint_SUITE_data/predef.erl
@@ -5,8 +5,8 @@
-export_type([array/0, digraph/0, gb_set/0]).
-%% Before Erlang/OTP 17.0 local re-definitions of pre-defined opaque
-%% types were ignored but did not generate any warning.
+%% Since Erlang/OTP 18.0 array() and so on are no longer pre-defined,
+%% so there is nothing special about them at all.
-opaque array() :: atom().
-opaque digraph() :: atom().
-opaque gb_set() :: atom().
diff --git a/lib/stdlib/test/erl_pp_SUITE.erl b/lib/stdlib/test/erl_pp_SUITE.erl
index 927fe0b595..afeeb5bfd4 100644
--- a/lib/stdlib/test/erl_pp_SUITE.erl
+++ b/lib/stdlib/test/erl_pp_SUITE.erl
@@ -1,7 +1,7 @@
%%
%% %CopyrightBegin%
%%
-%% Copyright Ericsson AB 2006-2013. All Rights Reserved.
+%% Copyright Ericsson AB 2006-2015. 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
@@ -42,7 +42,6 @@
-export([ func/1, call/1, recs/1, try_catch/1, if_then/1,
receive_after/1, bits/1, head_tail/1,
cond1/1, block/1, case1/1, ops/1, messages/1,
- old_mnemosyne_syntax/1,
import_export/1, misc_attrs/1, dialyzer_attrs/1,
hook/1,
neg_indent/1,
@@ -50,7 +49,7 @@
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,
- otp_10302/1, otp_10820/1, otp_11100/1]).
+ otp_10302/1, otp_10820/1, otp_11100/1, otp_11861/1]).
%% Internal export.
-export([ehook/6]).
@@ -77,13 +76,13 @@ groups() ->
[{expr, [],
[func, call, recs, try_catch, if_then, receive_after,
bits, head_tail, cond1, block, case1, ops,
- messages, old_mnemosyne_syntax, maps_syntax
+ messages, maps_syntax
]},
{attributes, [], [misc_attrs, import_export, dialyzer_attrs]},
{tickets, [],
[otp_6321, otp_6911, otp_6914, otp_8150, otp_8238,
otp_8473, otp_8522, otp_8567, otp_8664, otp_9147,
- otp_10302, otp_10820, otp_11100]}].
+ otp_10302, otp_10820, otp_11100, otp_11861]}].
init_per_suite(Config) ->
Config.
@@ -491,7 +490,7 @@ cond1(Config) when is_list(Config) ->
[{cons,3,{atom,3,a},{cons,3,{atom,3,b},{nil,3}}}]},
{clause,4,[],[[{atom,4,true}]],
[{tuple,5,[{atom,5,x},{atom,5,y}]}]}]},
- ?line CChars = lists:flatten(erl_pp:expr(C)),
+ CChars = flat_expr1(C),
% ?line "cond {foo,bar} -> [a,b]; true -> {x,y} end" = CChars,
?line "cond\n"
" {foo,bar} ->\n"
@@ -558,30 +557,9 @@ messages(Config) when is_list(Config) ->
lists:flatten(erl_pp:form({error,{some,"error"}})),
?line true = "{warning,{some,\"warning\"}}\n" =:=
lists:flatten(erl_pp:form({warning,{some,"warning"}})),
- ?line true = "\n" =:= lists:flatten(erl_pp:form({eof,0})),
+ "\n" = flat_form({eof,0}),
ok.
-old_mnemosyne_syntax(Config) when is_list(Config) ->
- %% Since we have kept the ':-' token,
- %% better test that we can pretty print it.
- R = {rule,12,sales,2,
- [{clause,12,
- [{var,12,'E'},{atom,12,employee}],
- [],
- [{generate,13,
- {var,13,'E'},
- {call,13,{atom,13,table},[{atom,13,employee}]}},
- {match,14,
- {record_field,14,{var,14,'E'},{atom,14,salary}},
- {atom,14,sales}}]}]},
- ?line "sales(E, employee) :-\n"
- " E <- table(employee),\n"
- " E.salary = sales.\n" =
- lists:flatten(erl_pp:form(R)),
- ok.
-
-
-
import_export(suite) ->
[];
import_export(Config) when is_list(Config) ->
@@ -638,59 +616,41 @@ hook(Config) when is_list(Config) ->
do_hook(HookFun) ->
Lc = parse_expr(binary_to_list(<<"[X || X <- [1,2,3]].">>)),
H = HookFun(fun hook/4),
- Expr = {call,0,{atom,0,fff},[{foo,Lc},{foo,Lc},{foo,Lc}]},
+ A0 = erl_anno:new(0),
+ Expr = {call,A0,{atom,A0,fff},[{foo,Lc},{foo,Lc},{foo,Lc}]},
EChars = lists:flatten(erl_pp:expr(Expr, 0, H)),
- Call = {call,0,{atom,0,foo},[Lc]},
- Expr2 = {call,0,{atom,0,fff},[Call,Call,Call]},
+ Call = {call,A0,{atom,A0,foo},[Lc]},
+ Expr2 = {call,A0,{atom,A0,fff},[Call,Call,Call]},
EChars2 = erl_pp:exprs([Expr2]),
?line true = EChars =:= lists:flatten(EChars2),
EsChars = erl_pp:exprs([Expr], H),
?line true = EChars =:= lists:flatten(EsChars),
- F = {function,1,ffff,0,[{clause,1,[],[],[Expr]}]},
+ A1 = erl_anno:new(1),
+ F = {function,A1,ffff,0,[{clause,A1,[],[],[Expr]}]},
FuncChars = lists:flatten(erl_pp:function(F, H)),
- F2 = {function,1,ffff,0,[{clause,1,[],[],[Expr2]}]},
+ F2 = {function,A1,ffff,0,[{clause,A1,[],[],[Expr2]}]},
FuncChars2 = erl_pp:function(F2),
?line true = FuncChars =:= lists:flatten(FuncChars2),
FFormChars = erl_pp:form(F, H),
?line true = FuncChars =:= lists:flatten(FFormChars),
- A = {attribute,1,record,{r,[{record_field,1,{atom,1,a},Expr}]}},
+ A = {attribute,A1,record,{r,[{record_field,A1,{atom,A1,a},Expr}]}},
AChars = lists:flatten(erl_pp:attribute(A, H)),
- A2 = {attribute,1,record,{r,[{record_field,1,{atom,1,a},Expr2}]}},
+ A2 = {attribute,A1,record,{r,[{record_field,A1,{atom,A1,a},Expr2}]}},
AChars2 = erl_pp:attribute(A2),
?line true = AChars =:= lists:flatten(AChars2),
AFormChars = erl_pp:form(A, H),
?line true = AChars =:= lists:flatten(AFormChars),
- R = {rule,0,sales,0,
- [{clause,0,[{var,0,'E'},{atom,0,employee}],[],
- [{generate,2,{var,2,'E'},
- {call,2,{atom,2,table},[{atom,2,employee}]}},
- {match,3,
- {record_field,3,{var,3,'E'},{atom,3,salary}},
- {foo,Expr}}]}]},
- RChars = lists:flatten(erl_pp:rule(R, H)),
- R2 = {rule,0,sales,0,
- [{clause,0,[{var,0,'E'},{atom,0,employee}],[],
- [{generate,2,{var,2,'E'},
- {call,2,{atom,2,table},[{atom,2,employee}]}},
- {match,3,
- {record_field,3,{var,3,'E'},{atom,3,salary}},
- {call,0,{atom,0,foo},[Expr2]}}]}]},
- RChars2 = erl_pp:rule(R2),
- ?line true = RChars =:= lists:flatten(RChars2),
- ARChars = erl_pp:form(R, H),
- ?line true = RChars =:= lists:flatten(ARChars),
-
?line "INVALID-FORM:{foo,bar}:" = lists:flatten(erl_pp:expr({foo,bar})),
%% A list (as before R6), not a list of lists.
- G = [{op,1,'>',{atom,1,a},{foo,{atom,1,b}}}], % not a proper guard
+ G = [{op,A1,'>',{atom,A1,a},{foo,{atom,A1,b}}}], % not a proper guard
GChars = lists:flatten(erl_pp:guard(G, H)),
- G2 = [{op,1,'>',{atom,1,a},
- {call,0,{atom,0,foo},[{atom,1,b}]}}], % not a proper guard
+ G2 = [{op,A1,'>',{atom,A1,a},
+ {call,A0,{atom,A0,foo},[{atom,A1,b}]}}], % not a proper guard
GChars2 = erl_pp:guard(G2),
?line true = GChars =:= lists:flatten(GChars2),
@@ -701,14 +661,14 @@ do_hook(HookFun) ->
?line true = EChars =:= lists:flatten(XEChars2),
%% Note: no leading spaces before "begin".
- Block = {block,0,[{match,0,{var,0,'A'},{integer,0,3}},
- {atom,0,true}]},
+ Block = {block,A0,[{match,A0,{var,A0,'A'},{integer,A0,3}},
+ {atom,A0,true}]},
?line "begin\n A =" ++ _ =
lists:flatten(erl_pp:expr(Block, 17, none)),
%% Special...
?line true =
- "{some,value}" =:= lists:flatten(erl_pp:expr({value,0,{some,value}})),
+ "{some,value}" =:= lists:flatten(erl_pp:expr({value,A0,{some,value}})),
%% Silly...
?line true =
@@ -716,8 +676,8 @@ do_hook(HookFun) ->
flat_expr({'if',0,[{clause,0,[],[],[{atom,0,0}]}]}),
%% More compatibility: before R6
- OldIf = {'if',0,[{clause,0,[],[{atom,0,true}],[{atom,0,b}]}]},
- NewIf = {'if',0,[{clause,0,[],[[{atom,0,true}]],[{atom,0,b}]}]},
+ OldIf = {'if',A0,[{clause,A0,[],[{atom,A0,true}],[{atom,A0,b}]}]},
+ NewIf = {'if',A0,[{clause,A0,[],[[{atom,A0,true}]],[{atom,A0,b}]}]},
OldIfChars = lists:flatten(erl_pp:expr(OldIf)),
NewIfChars = lists:flatten(erl_pp:expr(NewIf)),
?line true = OldIfChars =:= NewIfChars,
@@ -733,7 +693,8 @@ ehook(HE, I, P, H, foo, bar) ->
hook(HE, I, P, H).
hook({foo,E}, I, P, H) ->
- erl_pp:expr({call,0,{atom,0,foo},[E]}, I, P, H).
+ A = erl_anno:new(0),
+ erl_pp:expr({call,A,{atom,A,foo},[E]}, I, P, H).
neg_indent(suite) ->
[];
@@ -816,7 +777,7 @@ otp_6911(Config) when is_list(Config) ->
{var,6,'X'},
[{clause,7,[{atom,7,true}],[],[{integer,7,12}]},
{clause,8,[{atom,8,false}],[],[{integer,8,14}]}]}]}]},
- ?line Chars = lists:flatten(erl_pp:form(F)),
+ Chars = flat_form(F),
?line "thomas(X) ->\n"
" case X of\n"
" true ->\n"
@@ -874,6 +835,7 @@ type_examples() ->
{ex3,<<"-type paren() :: (ann2()). ">>},
{ex4,<<"-type t1() :: atom(). ">>},
{ex5,<<"-type t2() :: [t1()]. ">>},
+ {ex56,<<"-type integer(A) :: A. ">>},
{ex6,<<"-type t3(Atom) :: integer(Atom). ">>},
{ex7,<<"-type '\\'t::4'() :: t3('\\'foobar'). ">>},
{ex8,<<"-type t5() :: {t1(), t3(foo)}. ">>},
@@ -1125,10 +1087,11 @@ otp_10302(Config) when is_list(Config) ->
Opts = [{hook, fun unicode_hook/4},{encoding,unicode}],
Lc = parse_expr("[X || X <- [\"\x{400}\",\"\xFF\"]]."),
- Expr = {call,0,{atom,0,fff},[{foo,{foo,Lc}},{foo,{foo,Lc}}]},
+ A0 = erl_anno:new(0),
+ Expr = {call,A0,{atom,A0,fff},[{foo,{foo,Lc}},{foo,{foo,Lc}}]},
EChars = lists:flatten(erl_pp:expr(Expr, 0, Opts)),
- Call = {call,0,{atom,0,foo},[{call,0,{atom,0,foo},[Lc]}]},
- Expr2 = {call,0,{atom,0,fff},[Call,Call]},
+ Call = {call,A0,{atom,A0,foo},[{call,A0,{atom,A0,foo},[Lc]}]},
+ Expr2 = {call,A0,{atom,A0,fff},[Call,Call]},
EChars2 = erl_pp:exprs([Expr2], U),
EChars = lists:flatten(EChars2),
[$\x{400},$\x{400}] = [C || C <- EChars, C > 255],
@@ -1138,7 +1101,8 @@ otp_10302(Config) when is_list(Config) ->
ok.
unicode_hook({foo,E}, I, P, H) ->
- erl_pp:expr({call,0,{atom,0,foo},[E]}, I, P, H).
+ A = erl_anno:new(0),
+ erl_pp:expr({call,A,{atom,A,foo},[E]}, I, P, H).
otp_10820(doc) ->
"OTP-10820. Unicode filenames.";
@@ -1178,34 +1142,45 @@ otp_11100(Config) when is_list(Config) ->
%% Cannot trigger the use of the hook function with export/import.
"-export([{fy,a}/b]).\n" =
pf({attribute,1,export,[{{fy,a},b}]}),
+ A1 = erl_anno:new(1),
"-type foo() :: integer(INVALID-FORM:{foo,bar}:).\n" =
- pf({attribute,1,type,{foo,{type,1,integer,[{foo,bar}]},[]}}),
- pf({attribute,1,type,
- {a,{type,1,range,[{integer,1,1},{foo,bar}]},[]}}),
+ pf({attribute,A1,type,{foo,{type,A1,integer,[{foo,bar}]},[]}}),
+ pf({attribute,A1,type,
+ {a,{type,A1,range,[{integer,A1,1},{foo,bar}]},[]}}),
"-type foo(INVALID-FORM:{foo,bar}:) :: A.\n" =
- pf({attribute,1,type,{foo,{var,1,'A'},[{foo,bar}]}}),
- "-type foo() :: (INVALID-FORM:{foo,bar}: :: []).\n" =
- pf({attribute,1,type,
- {foo,{paren_type,1,
- [{ann_type,1,[{foo,bar},{type,1,nil,[]}]}]},
+ pf({attribute,A1,type,{foo,{var,A1,'A'},[{foo,bar}]}}),
+ "-type foo() :: INVALID-FORM:{foo,bar}: :: [].\n" =
+ pf({attribute,A1,type,
+ {foo,{paren_type,A1,
+ [{ann_type,A1,[{foo,bar},{type,A1,nil,[]}]}]},
[]}}),
"-type foo() :: <<_:INVALID-FORM:{foo,bar}:>>.\n" =
- pf({attribute,1,type,
- {foo,{type,1,binary,[{foo,bar},{integer,1,0}]},[]}}),
+ pf({attribute,A1,type,
+ {foo,{type,A1,binary,[{foo,bar},{integer,A1,0}]},[]}}),
"-type foo() :: <<_:10, _:_*INVALID-FORM:{foo,bar}:>>.\n" =
- pf({attribute,1,type,
- {foo,{type,1,binary,[{integer,1,10},{foo,bar}]},[]}}),
+ pf({attribute,A1,type,
+ {foo,{type,A1,binary,[{integer,A1,10},{foo,bar}]},[]}}),
"-type foo() :: #r{INVALID-FORM:{foo,bar}: :: integer()}.\n" =
- pf({attribute,1,type,
- {foo,{type,1,record,
- [{atom,1,r},
- {type,1,field_type,
- [{foo,bar},{type,1,integer,[]}]}]},
+ pf({attribute,A1,type,
+ {foo,{type,A1,record,
+ [{atom,A1,r},
+ {type,A1,field_type,
+ [{foo,bar},{type,A1,integer,[]}]}]},
[]}}),
ok.
+otp_11861(doc) ->
+ "OTP-11861. behaviour_info() and -callback.";
+otp_11861(suite) -> [];
+otp_11861(Config) when is_list(Config) ->
+ "-optional_callbacks([bar/0]).\n" =
+ pf({attribute,3,optional_callbacks,[{bar,0}]}),
+ "-optional_callbacks([{bar,1,bad}]).\n" =
+ pf({attribute,4,optional_callbacks,[{bar,1,bad}]}),
+ ok.
+
pf(Form) ->
- lists:flatten(erl_pp:form(Form,none)).
+ lists:flatten(erl_pp:form(Form, none)).
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
@@ -1270,9 +1245,18 @@ strip_module_info(Bin) ->
<<R:Start/binary,_/binary>> = Bin,
R.
-flat_expr(Expr) ->
+flat_expr1(Expr0) ->
+ Expr = erl_parse:new_anno(Expr0),
+ lists:flatten(erl_pp:expr(Expr)).
+
+flat_expr(Expr0) ->
+ Expr = erl_parse:new_anno(Expr0),
lists:flatten(erl_pp:expr(Expr, -1, none)).
+flat_form(Form0) ->
+ Form = erl_parse:new_anno(Form0),
+ lists:flatten(erl_pp:form(Form)).
+
pp_forms(Bin) ->
pp_forms(Bin, none).
diff --git a/lib/stdlib/test/erl_scan_SUITE.erl b/lib/stdlib/test/erl_scan_SUITE.erl
index 9be9f641c8..fb85055b6c 100644
--- a/lib/stdlib/test/erl_scan_SUITE.erl
+++ b/lib/stdlib/test/erl_scan_SUITE.erl
@@ -1,7 +1,7 @@
%%
%% %CopyrightBegin%
%%
-%% Copyright Ericsson AB 1998-2014. All Rights Reserved.
+%% Copyright Ericsson AB 1998-2015. 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
@@ -138,7 +138,7 @@ iso88591(Config) when is_list(Config) ->
A1s = [$h,$ä,$r],
A2s = [$ö,$r,$e],
%% Test parsing atom and variable characters.
- {ok,Ts1,_} = erl_scan:string(V1s ++ " " ++ V2s ++
+ {ok,Ts1,_} = erl_scan_string(V1s ++ " " ++ V2s ++
"\327" ++
A1s ++ " " ++ A2s),
V1s = atom_to_list(element(3, nth(1, Ts1))),
@@ -151,7 +151,7 @@ iso88591(Config) when is_list(Config) ->
%% Test parsing and printing strings.
S1 = V1s ++ "\327" ++ A1s ++ "\250" ++ A2s,
S1s = "\"" ++ S1 ++ "\"",
- {ok,Ts2,_} = erl_scan:string(S1s),
+ {ok,Ts2,_} = erl_scan_string(S1s),
S1 = element(3, nth(1, Ts2)),
S1s = flatten(print(element(3, nth(1, Ts2)))),
ok %It all worked
@@ -219,14 +219,14 @@ atoms() ->
test_string([39,65,200,39], [{atom,{1,1},'AÈ'}]),
test_string("ärlig östen", [{atom,{1,1},ärlig},{atom,{1,7},östen}]),
?line {ok,[{atom,_,'$a'}],{1,6}} =
- erl_scan:string("'$\\a'", {1,1}),
+ erl_scan_string("'$\\a'", {1,1}),
?line test("'$\\a'"),
ok.
punctuations() ->
L = ["<<", "<-", "<=", "<", ">>", ">=", ">", "->", "--",
"-", "++", "+", "=:=", "=/=", "=<", "=>", "==", "=", "/=",
- "/", "||", "|", ":=", ":-", "::", ":"],
+ "/", "||", "|", ":=", "::", ":"],
%% One token at a time:
[begin
W = list_to_atom(S),
@@ -268,24 +268,24 @@ punctuations() ->
comments() ->
?line test("a %%\n b"),
- ?line {ok,[],1} = erl_scan:string("%"),
+ {ok,[],1} = erl_scan_string("%"),
?line test("a %%\n b"),
{ok,[{atom,{1,1},a},{atom,{2,2},b}],{2,3}} =
- erl_scan:string("a %%\n b",{1,1}),
+ erl_scan_string("a %%\n b", {1,1}),
{ok,[{atom,{1,1},a},{comment,{1,3},"%%"},{atom,{2,2},b}],{2,3}} =
- erl_scan:string("a %%\n b",{1,1}, [return_comments]),
+ erl_scan_string("a %%\n b",{1,1}, [return_comments]),
{ok,[{atom,{1,1},a},
{white_space,{1,2}," "},
{white_space,{1,5},"\n "},
{atom,{2,2},b}],
{2,3}} =
- erl_scan:string("a %%\n b",{1,1},[return_white_spaces]),
+ erl_scan_string("a %%\n b",{1,1},[return_white_spaces]),
{ok,[{atom,{1,1},a},
{white_space,{1,2}," "},
{comment,{1,3},"%%"},
{white_space,{1,5},"\n "},
{atom,{2,2},b}],
- {2,3}} = erl_scan:string("a %%\n b",{1,1},[return]),
+ {2,3}} = erl_scan_string("a %%\n b",{1,1},[return]),
ok.
errors() ->
@@ -337,11 +337,11 @@ base_integers() ->
erl_scan:string(Str)
end || {BS,S} <- [{"3","3"},{"15","f"}, {"12","c"}] ],
- ?line {ok,[{integer,1,239},{'@',1}],1} = erl_scan:string("16#ef@"),
+ {ok,[{integer,1,239},{'@',1}],1} = erl_scan_string("16#ef@"),
{ok,[{integer,{1,1},239},{'@',{1,6}}],{1,7}} =
- erl_scan:string("16#ef@", {1,1}, []),
+ erl_scan_string("16#ef@", {1,1}, []),
{ok,[{integer,{1,1},14},{atom,{1,5},g@}],{1,7}} =
- erl_scan:string("16#eg@", {1,1}, []),
+ erl_scan_string("16#eg@", {1,1}, []),
ok.
@@ -382,8 +382,8 @@ dots() ->
{ok,[{'.',{1,1}},{atom,{1,2},a}],{1,3}}}
],
[begin
- R = erl_scan:string(S),
- R2 = erl_scan:string(S, {1,1}, [])
+ R = erl_scan_string(S),
+ R2 = erl_scan_string(S, {1,1}, [])
end || {S, R, R2} <- Dot],
?line {ok,[{dot,_}=T1],{1,2}} = erl_scan:string(".", {1,1}, text),
@@ -417,7 +417,7 @@ dots() ->
{white_space,{1,4},"\n"},
{dot,{2,1}}],
{2,3}}, ""} =
- erl_scan:tokens(C, "\n. ", {1,1}, return), % any loc, any options
+ erl_scan_tokens(C, "\n. ", {1,1}, return), % any loc, any options
?line [test_string(S, R) ||
{S, R} <- [{".$\n", [{'.',{1,1}},{char,{1,2},$\n}]},
@@ -511,7 +511,7 @@ eof() ->
%% An error before R13A.
%% ?line {done,Err={error,{1,erl_scan,scan},1},eof} =
?line {done,{ok,[{atom,1,abra}],1},eof} =
- erl_scan:tokens(C2, eof, 1),
+ erl_scan_tokens(C2, eof, 1),
%% With column.
?line {more, C3} = erl_scan:tokens([]," \n",{1,1}),
@@ -520,7 +520,7 @@ eof() ->
%% An error before R13A.
%% ?line {done,{error,{{1,1},erl_scan,scan},{1,5}},eof} =
?line {done,{ok,[{atom,_,abra}],{1,5}},eof} =
- erl_scan:tokens(C4, eof, 1),
+ erl_scan_tokens(C4, eof, 1),
%% Robert's scanner returns "" as LeftoverChars;
%% the R12B scanner returns eof as LeftoverChars: (eof is correct)
@@ -528,26 +528,26 @@ eof() ->
%% An error before R13A.
%% ?line {done,{error,{1,erl_scan,scan},1},eof} =
?line {done,{ok,[{atom,1,a}],1},eof} =
- erl_scan:tokens(C5,eof,1),
+ erl_scan_tokens(C5,eof,1),
%% With column.
{more, C6} = erl_scan:tokens([], "a", {1,1}),
%% An error before R13A.
%% {done,{error,{1,erl_scan,scan},1},eof} =
{done,{ok,[{atom,{1,1},a}],{1,2}},eof} =
- erl_scan:tokens(C6,eof,1),
+ erl_scan_tokens(C6,eof,1),
%% A dot followed by eof is special:
?line {more, C} = erl_scan:tokens([], "a.", 1),
- ?line {done,{ok,[{atom,1,a},{dot,1}],1},eof} = erl_scan:tokens(C,eof,1),
- ?line {ok,[{atom,1,foo},{dot,1}],1} = erl_scan:string("foo."),
+ {done,{ok,[{atom,1,a},{dot,1}],1},eof} = erl_scan_tokens(C,eof,1),
+ {ok,[{atom,1,foo},{dot,1}],1} = erl_scan_string("foo."),
%% With column.
{more, CCol} = erl_scan:tokens([], "a.", {1,1}),
{done,{ok,[{atom,{1,1},a},{dot,{1,2}}],{1,3}},eof} =
- erl_scan:tokens(CCol,eof,1),
+ erl_scan_tokens(CCol,eof,1),
{ok,[{atom,{1,1},foo},{dot,{1,4}}],{1,5}} =
- erl_scan:string("foo.", {1,1}, []),
+ erl_scan_string("foo.", {1,1}, []),
ok.
@@ -628,23 +628,23 @@ crashes() ->
options() ->
%% line and column are not options, but tested here
?line {ok,[{atom,1,foo},{white_space,1," "},{comment,1,"% bar"}], 1} =
- erl_scan:string("foo % bar", 1, return),
+ erl_scan_string("foo % bar", 1, return),
?line {ok,[{atom,1,foo},{white_space,1," "}],1} =
- erl_scan:string("foo % bar", 1, return_white_spaces),
+ erl_scan_string("foo % bar", 1, return_white_spaces),
?line {ok,[{atom,1,foo},{comment,1,"% bar"}],1} =
- erl_scan:string("foo % bar", 1, return_comments),
+ erl_scan_string("foo % bar", 1, return_comments),
?line {ok,[{atom,17,foo}],17} =
- erl_scan:string("foo % bar", 17),
+ erl_scan_string("foo % bar", 17),
?line {'EXIT',{function_clause,_}} =
(catch {foo,
erl_scan:string("foo % bar", {a,1}, [])}), % type error
?line {ok,[{atom,_,foo}],{17,18}} =
- erl_scan:string("foo % bar", {17,9}, []),
+ erl_scan_string("foo % bar", {17,9}, []),
?line {'EXIT',{function_clause,_}} =
(catch {foo,
erl_scan:string("foo % bar", {1,0}, [])}), % type error
?line {ok,[{foo,1}],1} =
- erl_scan:string("foo % bar",1, [{reserved_word_fun,
+ erl_scan_string("foo % bar",1, [{reserved_word_fun,
fun(W) -> W =:= foo end}]),
?line {'EXIT',{badarg,_}} =
(catch {foo,
@@ -706,8 +706,9 @@ token_info() ->
attributes_info() ->
?line {'EXIT',_} =
(catch {foo,erl_scan:attributes_info(foo)}), % type error
- ?line [{line,18}] = erl_scan:attributes_info(18),
- ?line {location,19} = erl_scan:attributes_info(19, location),
+ [{line,18}] = erl_scan:attributes_info(erl_anno:new(18)),
+ {location,19} =
+ erl_scan:attributes_info(erl_anno:new(19), location),
?line {ok,[{atom,A0,foo}],_} = erl_scan:string("foo", 19, [text]),
?line {location,19} = erl_scan:attributes_info(A0, location),
@@ -735,7 +736,9 @@ attributes_info() ->
set_attribute() ->
F = fun(Line) -> -Line end,
- ?line -2 = erl_scan:set_attribute(line, 2, F),
+ Anno2 = erl_anno:new(2),
+ A0 = erl_scan:set_attribute(line, Anno2, F),
+ {line, -2} = erl_scan:attributes_info(A0, line),
?line {ok,[{atom,A1,foo}],_} = erl_scan:string("foo", {9,17}),
?line A2 = erl_scan:set_attribute(line, A1, F),
?line {line,-9} = erl_scan:attributes_info(A2, line),
@@ -765,10 +768,15 @@ set_attribute() ->
?line {ok,[{atom,A6,foo}],_} = erl_scan:string("foo", 11, [text]),
?line A7 = erl_scan:set_attribute(line, A6, F2),
- ?line {line,{17,11}} = erl_scan:attributes_info(A7, line),
+ %% Incompatible with pre 18:
+ %% {line,{17,11}} = erl_scan:attributes_info(A7, line),
+ {line,17} = erl_scan:attributes_info(A7, line),
?line {location,{17,11}} = % mixed up
erl_scan:attributes_info(A7, location),
- ?line [{line,{17,11}},{text,"foo"}] =
+ %% Incompatible with pre 18:
+ %% [{line,{17,11}},{text,"foo"}] =
+ %% erl_scan:attributes_info(A7, [line,column,text]),
+ [{line,17},{column,11},{text,"foo"}] =
erl_scan:attributes_info(A7, [line,column,text]),
?line {'EXIT',_} =
@@ -776,9 +784,13 @@ set_attribute() ->
?line {'EXIT',{badarg,_}} =
(catch {foo, erl_scan:set_attribute(column, [], F2)}), % type error
+ Attr10 = erl_anno:new(8),
+ Attr20 = erl_scan:set_attribute(line, Attr10,
+ fun(L) -> {nos,'X',L} end),
%% OTP-9412
- ?line 8 = erl_scan:set_attribute(line, [{line,{nos,'X',8}}],
- fun({nos,_V,VL}) -> VL end),
+ Attr30 = erl_scan:set_attribute(line, Attr20,
+ fun({nos,_V,VL}) -> VL end),
+ 8 = erl_anno:to_term(Attr30),
ok.
column_errors() ->
@@ -812,7 +824,7 @@ white_spaces() ->
{white_space,_," "},
{atom,_,a},
{white_space,_,"\n"}],
- _} = erl_scan:string("\r a\n", {1,1}, return),
+ _} = erl_scan_string("\r a\n", {1,1}, return),
?line test("\r a\n"),
L = "{\"a\nb\", \"a\\nb\",\nabc\r,def}.\n\n",
?line {ok,[{'{',_},
@@ -829,7 +841,7 @@ white_spaces() ->
{'}',_},
{dot,_},
{white_space,_,"\n"}],
- _} = erl_scan:string(L, {1,1}, return),
+ _} = erl_scan_string(L, {1,1}, return),
?line test(L),
?line test("\"\n\"\n"),
?line test("\n\r\n"),
@@ -846,7 +858,7 @@ white_spaces() ->
unicode() ->
?line {ok,[{char,1,83},{integer,1,45}],1} =
- erl_scan:string("$\\12345"), % not unicode
+ erl_scan_string("$\\12345"), % not unicode
?line {error,{1,erl_scan,{illegal,character}},1} =
erl_scan:string([1089]),
@@ -858,7 +870,7 @@ unicode() ->
erl_scan:string("'a"++[1089]++"b'", {1,1}),
?line test("\"a"++[1089]++"b\""),
{ok,[{char,1,1}],1} =
- erl_scan:string([$$,$\\,$^,1089], 1),
+ erl_scan_string([$$,$\\,$^,1089], 1),
{error,{1,erl_scan,Error},1} =
erl_scan:string("\"qa\x{aaa}", 1),
@@ -870,13 +882,13 @@ unicode() ->
erl_scan:string("'qa\\x{aaa}'",{1,1}),
{ok,[{char,1,1089}],1} =
- erl_scan:string([$$,1089], 1),
+ erl_scan_string([$$,1089], 1),
{ok,[{char,1,1089}],1} =
- erl_scan:string([$$,$\\,1089], 1),
+ erl_scan_string([$$,$\\,1089], 1),
Qs = "$\\x{aaa}",
{ok,[{char,1,$\x{aaa}}],1} =
- erl_scan:string(Qs, 1),
+ erl_scan_string(Qs, 1),
{ok,[Q2],{1,9}} =
erl_scan:string("$\\x{aaa}", {1,1}, [text]),
[{category,char},{column,1},{length,8},
@@ -884,19 +896,19 @@ unicode() ->
erl_scan:token_info(Q2),
U1 = "\"\\x{aaa}\"",
- {ok,
- [{string,[{line,1},{column,1},{text,"\"\\x{aaa}\""}],[2730]}],
- {1,10}} = erl_scan:string(U1, {1,1}, [text]),
- {ok,[{string,1,[2730]}],1} = erl_scan:string(U1, 1),
+ {ok,[{string,A1,[2730]}],{1,10}} = erl_scan:string(U1, {1,1}, [text]),
+ [{line,1},{column,1},{text,"\"\\x{aaa}\""}] =
+ erl_scan:attributes_info(A1, [line, column, text]),
+ {ok,[{string,1,[2730]}],1} = erl_scan_string(U1, 1),
U2 = "\"\\x41\\x{fff}\\x42\"",
- {ok,[{string,1,[$\x41,$\x{fff},$\x42]}],1} = erl_scan:string(U2, 1),
+ {ok,[{string,1,[$\x41,$\x{fff},$\x42]}],1} = erl_scan_string(U2, 1),
U3 = "\"a\n\\x{fff}\n\"",
- {ok,[{string,1,[$a,$\n,$\x{fff},$\n]}],3} = erl_scan:string(U3, 1),
+ {ok,[{string,1,[$a,$\n,$\x{fff},$\n]}],3} = erl_scan_string(U3, 1),
U4 = "\"\\^\n\\x{aaa}\\^\n\"",
- {ok,[{string,1,[$\n,$\x{aaa},$\n]}],3} = erl_scan:string(U4, 1),
+ {ok,[{string,1,[$\n,$\x{aaa},$\n]}],3} = erl_scan_string(U4, 1),
%% Keep these tests:
?line test(Qs),
@@ -906,15 +918,15 @@ unicode() ->
?line test(U4),
Str1 = "\"ab" ++ [1089] ++ "cd\"",
- {ok,[{string,1,[$a,$b,1089,$c,$d]}],1} = erl_scan:string(Str1, 1),
+ {ok,[{string,1,[$a,$b,1089,$c,$d]}],1} = erl_scan_string(Str1, 1),
{ok,[{string,{1,1},[$a,$b,1089,$c,$d]}],{1,8}} =
- erl_scan:string(Str1, {1,1}),
+ erl_scan_string(Str1, {1,1}),
?line test(Str1),
Comment = "%% "++[1089],
{ok,[{comment,1,[$%,$%,$\s,1089]}],1} =
- erl_scan:string(Comment, 1, [return]),
+ erl_scan_string(Comment, 1, [return]),
{ok,[{comment,{1,1},[$%,$%,$\s,1089]}],{1,5}} =
- erl_scan:string(Comment, {1,1}, [return]),
+ erl_scan_string(Comment, {1,1}, [return]),
ok.
more_chars() ->
@@ -923,12 +935,12 @@ more_chars() ->
%% All kinds of tests...
?line {ok,[{char,_,123}],{1,4}} =
- erl_scan:string("$\\{",{1,1}),
+ erl_scan_string("$\\{",{1,1}),
?line {more, C1} = erl_scan:tokens([], "$\\{", {1,1}),
?line {done,{ok,[{char,_,123}],{1,4}},eof} =
- erl_scan:tokens(C1, eof, 1),
+ erl_scan_tokens(C1, eof, 1),
?line {ok,[{char,1,123},{atom,1,a},{'}',1}],1} =
- erl_scan:string("$\\{a}"),
+ erl_scan_string("$\\{a}"),
?line {error,{{1,1},erl_scan,char},{1,4}} =
erl_scan:string("$\\x", {1,1}),
@@ -993,11 +1005,11 @@ otp_10302(Config) when is_list(Config) ->
{error,{{1,1},erl_scan,{illegal,atom}},{1,12}} =
erl_scan:string("'qa\\x{aaa}'",{1,1}),
- {ok,[{char,1,1089}],1} = erl_scan:string([$$,1089], 1),
- {ok,[{char,1,1089}],1} = erl_scan:string([$$,$\\,1089],1),
+ {ok,[{char,1,1089}],1} = erl_scan_string([$$,1089], 1),
+ {ok,[{char,1,1089}],1} = erl_scan_string([$$,$\\,1089],1),
Qs = "$\\x{aaa}",
- {ok,[{char,1,2730}],1} = erl_scan:string(Qs,1),
+ {ok,[{char,1,2730}],1} = erl_scan_string(Qs, 1),
{ok,[Q2],{1,9}} = erl_scan:string(Qs,{1,1},[text]),
[{category,char},{column,1},{length,8},
{line,1},{symbol,16#aaa},{text,Qs}] =
@@ -1011,19 +1023,19 @@ otp_10302(Config) when is_list(Config) ->
{symbol,[16#aaa]},{text,U1}] = erl_scan:token_info(T1, Tags),
U2 = "\"\\x41\\x{fff}\\x42\"",
- {ok,[{string,1,[65,4095,66]}],1} = erl_scan:string(U2, 1),
+ {ok,[{string,1,[65,4095,66]}],1} = erl_scan_string(U2, 1),
U3 = "\"a\n\\x{fff}\n\"",
- {ok,[{string,1,[97,10,4095,10]}],3} = erl_scan:string(U3, 1),
+ {ok,[{string,1,[97,10,4095,10]}],3} = erl_scan_string(U3, 1),
U4 = "\"\\^\n\\x{aaa}\\^\n\"",
- {ok,[{string,1,[10,2730,10]}],3} = erl_scan:string(U4, 1,[]),
+ {ok,[{string,1,[10,2730,10]}],3} = erl_scan_string(U4, 1,[]),
Str1 = "\"ab" ++ [1089] ++ "cd\"",
{ok,[{string,1,[97,98,1089,99,100]}],1} =
- erl_scan:string(Str1,1),
+ erl_scan_string(Str1,1),
{ok,[{string,{1,1},[97,98,1089,99,100]}],{1,8}} =
- erl_scan:string(Str1, {1,1}),
+ erl_scan_string(Str1, {1,1}),
OK1 = 16#D800-1,
OK2 = 16#DFFF+1,
@@ -1038,19 +1050,19 @@ otp_10302(Config) when is_list(Config) ->
IllegalL = [Illegal1,Illegal2,Illegal3,Illegal4],
[{ok,[{comment,1,[$%,$%,$\s,OK]}],1} =
- erl_scan:string("%% "++[OK], 1, [return]) ||
+ erl_scan_string("%% "++[OK], 1, [return]) ||
OK <- OKL],
{ok,[{comment,_,[$%,$%,$\s,OK1]}],{1,5}} =
- erl_scan:string("%% "++[OK1], {1,1}, [return]),
+ erl_scan_string("%% "++[OK1], {1,1}, [return]),
[{error,{1,erl_scan,{illegal,character}},1} =
erl_scan:string("%% "++[Illegal], 1, [return]) ||
Illegal <- IllegalL],
{error,{{1,1},erl_scan,{illegal,character}},{1,5}} =
erl_scan:string("%% "++[Illegal1], {1,1}, [return]),
- [{ok,[],1} = erl_scan:string("%% "++[OK], 1, []) ||
+ [{ok,[],1} = erl_scan_string("%% "++[OK], 1, []) ||
OK <- OKL],
- {ok,[],{1,5}} = erl_scan:string("%% "++[OK1], {1,1}, []),
+ {ok,[],{1,5}} = erl_scan_string("%% "++[OK1], {1,1}, []),
[{error,{1,erl_scan,{illegal,character}},1} =
erl_scan:string("%% "++[Illegal], 1, []) ||
Illegal <- IllegalL],
@@ -1058,7 +1070,7 @@ otp_10302(Config) when is_list(Config) ->
erl_scan:string("%% "++[Illegal1], {1,1}, []),
[{ok,[{string,{1,1},[OK]}],{1,4}} =
- erl_scan:string("\""++[OK]++"\"",{1,1}) ||
+ erl_scan_string("\""++[OK]++"\"",{1,1}) ||
OK <- OKL],
[{error,{{1,2},erl_scan,{illegal,character}},{1,3}} =
erl_scan:string("\""++[OK]++"\"",{1,1}) ||
@@ -1069,93 +1081,93 @@ otp_10302(Config) when is_list(Config) ->
Illegal <- IllegalL],
{ok,[{char,{1,1},OK1}],{1,3}} =
- erl_scan:string([$$,OK1],{1,1}),
+ erl_scan_string([$$,OK1],{1,1}),
{error,{{1,1},erl_scan,{illegal,character}},{1,2}} =
erl_scan:string([$$,Illegal1],{1,1}),
{ok,[{char,{1,1},OK1}],{1,4}} =
- erl_scan:string([$$,$\\,OK1],{1,1}),
+ erl_scan_string([$$,$\\,OK1],{1,1}),
{error,{{1,1},erl_scan,{illegal,character}},{1,4}} =
erl_scan:string([$$,$\\,Illegal1],{1,1}),
{ok,[{string,{1,1},[55295]}],{1,5}} =
- erl_scan:string("\"\\"++[OK1]++"\"",{1,1}),
+ erl_scan_string("\"\\"++[OK1]++"\"",{1,1}),
{error,{{1,2},erl_scan,{illegal,character}},{1,4}} =
erl_scan:string("\"\\"++[Illegal1]++"\"",{1,1}),
{ok,[{char,{1,1},OK1}],{1,10}} =
- erl_scan:string("$\\x{D7FF}",{1,1}),
+ erl_scan_string("$\\x{D7FF}",{1,1}),
{error,{{1,1},erl_scan,{illegal,character}},{1,10}} =
erl_scan:string("$\\x{D800}",{1,1}),
%% Not erl_scan, but erl_parse.
- {integer,0,1} = erl_parse:abstract(1),
- Float = 3.14, {float,0,Float} = erl_parse:abstract(Float),
- {nil,0} = erl_parse:abstract([]),
+ {integer,0,1} = erl_parse_abstract(1),
+ Float = 3.14, {float,0,Float} = erl_parse_abstract(Float),
+ {nil,0} = erl_parse_abstract([]),
{bin,0,
[{bin_element,0,{integer,0,1},default,default},
{bin_element,0,{integer,0,2},default,default}]} =
- erl_parse:abstract(<<1,2>>),
+ erl_parse_abstract(<<1,2>>),
{cons,0,{tuple,0,[{atom,0,a}]},{atom,0,b}} =
- erl_parse:abstract([{a} | b]),
- {string,0,"str"} = erl_parse:abstract("str"),
+ erl_parse_abstract([{a} | b]),
+ {string,0,"str"} = erl_parse_abstract("str"),
{cons,0,
{integer,0,$a},
{cons,0,{integer,0,55296},{string,0,"c"}}} =
- erl_parse:abstract("a"++[55296]++"c"),
+ erl_parse_abstract("a"++[55296]++"c"),
Line = 17,
- {integer,Line,1} = erl_parse:abstract(1, Line),
- Float = 3.14, {float,Line,Float} = erl_parse:abstract(Float, Line),
- {nil,Line} = erl_parse:abstract([], Line),
+ {integer,Line,1} = erl_parse_abstract(1, Line),
+ Float = 3.14, {float,Line,Float} = erl_parse_abstract(Float, Line),
+ {nil,Line} = erl_parse_abstract([], Line),
{bin,Line,
[{bin_element,Line,{integer,Line,1},default,default},
{bin_element,Line,{integer,Line,2},default,default}]} =
- erl_parse:abstract(<<1,2>>, Line),
+ erl_parse_abstract(<<1,2>>, Line),
{cons,Line,{tuple,Line,[{atom,Line,a}]},{atom,Line,b}} =
- erl_parse:abstract([{a} | b], Line),
- {string,Line,"str"} = erl_parse:abstract("str", Line),
+ erl_parse_abstract([{a} | b], Line),
+ {string,Line,"str"} = erl_parse_abstract("str", Line),
{cons,Line,
{integer,Line,$a},
{cons,Line,{integer,Line,55296},{string,Line,"c"}}} =
- erl_parse:abstract("a"++[55296]++"c", Line),
+ erl_parse_abstract("a"++[55296]++"c", Line),
Opts1 = [{line,17}],
- {integer,Line,1} = erl_parse:abstract(1, Opts1),
- Float = 3.14, {float,Line,Float} = erl_parse:abstract(Float, Opts1),
- {nil,Line} = erl_parse:abstract([], Opts1),
+ {integer,Line,1} = erl_parse_abstract(1, Opts1),
+ Float = 3.14, {float,Line,Float} = erl_parse_abstract(Float, Opts1),
+ {nil,Line} = erl_parse_abstract([], Opts1),
{bin,Line,
[{bin_element,Line,{integer,Line,1},default,default},
{bin_element,Line,{integer,Line,2},default,default}]} =
- erl_parse:abstract(<<1,2>>, Opts1),
+ erl_parse_abstract(<<1,2>>, Opts1),
{cons,Line,{tuple,Line,[{atom,Line,a}]},{atom,Line,b}} =
- erl_parse:abstract([{a} | b], Opts1),
- {string,Line,"str"} = erl_parse:abstract("str", Opts1),
+ erl_parse_abstract([{a} | b], Opts1),
+ {string,Line,"str"} = erl_parse_abstract("str", Opts1),
{cons,Line,
{integer,Line,$a},
{cons,Line,{integer,Line,55296},{string,Line,"c"}}} =
- erl_parse:abstract("a"++[55296]++"c", Opts1),
+ erl_parse_abstract("a"++[55296]++"c", Opts1),
[begin
- {integer,Line,1} = erl_parse:abstract(1, Opts2),
- Float = 3.14, {float,Line,Float} = erl_parse:abstract(Float, Opts2),
- {nil,Line} = erl_parse:abstract([], Opts2),
+ {integer,Line,1} = erl_parse_abstract(1, Opts2),
+ Float = 3.14, {float,Line,Float} = erl_parse_abstract(Float, Opts2),
+ {nil,Line} = erl_parse_abstract([], Opts2),
{bin,Line,
[{bin_element,Line,{integer,Line,1},default,default},
{bin_element,Line,{integer,Line,2},default,default}]} =
- erl_parse:abstract(<<1,2>>, Opts2),
+ erl_parse_abstract(<<1,2>>, Opts2),
{cons,Line,{tuple,Line,[{atom,Line,a}]},{atom,Line,b}} =
- erl_parse:abstract([{a} | b], Opts2),
- {string,Line,"str"} = erl_parse:abstract("str", Opts2),
+ erl_parse_abstract([{a} | b], Opts2),
+ {string,Line,"str"} = erl_parse_abstract("str", Opts2),
{string,Line,[97,1024,99]} =
- erl_parse:abstract("a"++[1024]++"c", Opts2)
+ erl_parse_abstract("a"++[1024]++"c", Opts2)
end || Opts2 <- [[{encoding,unicode},{line,Line}],
[{encoding,utf8},{line,Line}]]],
{cons,0,
{integer,0,97},
{cons,0,{integer,0,1024},{string,0,"c"}}} =
- erl_parse:abstract("a"++[1024]++"c", [{encoding,latin1}]),
+ erl_parse_abstract("a"++[1024]++"c", [{encoding,latin1}]),
ok.
otp_10990(doc) ->
@@ -1172,13 +1184,13 @@ otp_10992(suite) ->
[];
otp_10992(Config) when is_list(Config) ->
{cons,0,{float,0,42.0},{nil,0}} =
- erl_parse:abstract([42.0], [{encoding,unicode}]),
+ erl_parse_abstract([42.0], [{encoding,unicode}]),
{cons,0,{float,0,42.0},{nil,0}} =
- erl_parse:abstract([42.0], [{encoding,utf8}]),
+ erl_parse_abstract([42.0], [{encoding,utf8}]),
{cons,0,{integer,0,65},{cons,0,{float,0,42.0},{nil,0}}} =
- erl_parse:abstract([$A,42.0], [{encoding,unicode}]),
+ erl_parse_abstract([$A,42.0], [{encoding,unicode}]),
{cons,0,{integer,0,65},{cons,0,{float,0,42.0},{nil,0}}} =
- erl_parse:abstract([$A,42.0], [{encoding,utf8}]),
+ erl_parse_abstract([$A,42.0], [{encoding,utf8}]),
ok.
otp_11807(doc) ->
@@ -1187,29 +1199,72 @@ otp_11807(suite) ->
[];
otp_11807(Config) when is_list(Config) ->
{cons,0,{integer,0,97},{cons,0,{integer,0,98},{nil,0}}} =
- erl_parse:abstract("ab", [{encoding,none}]),
+ erl_parse_abstract("ab", [{encoding,none}]),
{cons,0,{integer,0,-1},{nil,0}} =
- erl_parse:abstract([-1], [{encoding,latin1}]),
+ erl_parse_abstract([-1], [{encoding,latin1}]),
ASCII = fun(I) -> I >= 0 andalso I < 128 end,
- {string,0,"xyz"} = erl_parse:abstract("xyz", [{encoding,ASCII}]),
+ {string,0,"xyz"} = erl_parse_abstract("xyz", [{encoding,ASCII}]),
{cons,0,{integer,0,228},{nil,0}} =
- erl_parse:abstract([228], [{encoding,ASCII}]),
+ erl_parse_abstract([228], [{encoding,ASCII}]),
{cons,0,{integer,0,97},{atom,0,a}} =
- erl_parse:abstract("a"++a, [{encoding,latin1}]),
+ erl_parse_abstract("a"++a, [{encoding,latin1}]),
{'EXIT', {{badarg,bad},_}} = % minor backward incompatibility
(catch erl_parse:abstract("string", [{encoding,bad}])),
ok.
test_string(String, ExpectedWithCol) ->
- {ok, ExpectedWithCol, _EndWithCol} = erl_scan:string(String, {1, 1}, []),
+ {ok, ExpectedWithCol, _EndWithCol} = erl_scan_string(String, {1, 1}, []),
Expected = [ begin
{L,_C} = element(2, T),
setelement(2, T, L)
end
|| T <- ExpectedWithCol ],
- {ok, Expected, _End} = erl_scan:string(String),
+ {ok, Expected, _End} = erl_scan_string(String),
test(String).
+erl_scan_string(String) ->
+ erl_scan_string(String, 1, []).
+
+erl_scan_string(String, StartLocation) ->
+ erl_scan_string(String, StartLocation, []).
+
+erl_scan_string(String, StartLocation, Options) ->
+ case erl_scan:string(String, StartLocation, Options) of
+ {ok, Tokens, EndLocation} ->
+ {ok, unopaque_tokens(Tokens), EndLocation};
+ Else ->
+ Else
+ end.
+
+erl_scan_tokens(C, S, L) ->
+ erl_scan_tokens(C, S, L, []).
+
+erl_scan_tokens(C, S, L, O) ->
+ case erl_scan:tokens(C, S, L, O) of
+ {done, {ok, Ts, End}, R} ->
+ {done, {ok, unopaque_tokens(Ts), End}, R};
+ Else ->
+ Else
+ end.
+
+unopaque_tokens([]) ->
+ [];
+unopaque_tokens([Token|Tokens]) ->
+ Attrs = element(2, Token),
+ Term = erl_anno:to_term(Attrs),
+ T = setelement(2, Token, Term),
+ [T | unopaque_tokens(Tokens)].
+
+erl_parse_abstract(Term) ->
+ erl_parse_abstract(Term, []).
+
+erl_parse_abstract(Term, Options) ->
+ Abstr = erl_parse:abstract(Term, Options),
+ unopaque_abstract(Abstr).
+
+unopaque_abstract(Abstr) ->
+ erl_parse:anno_to_term(Abstr).
+
%% test_string(String, Expected, StartLocation, Options) ->
%% {ok, Expected, _End} = erl_scan:string(String, StartLocation, Options),
%% test(String).
@@ -1359,7 +1414,7 @@ select_tokens(Tokens, Tags) ->
simplify([Token|Tokens]) ->
{line,Line} = erl_scan:token_info(Token, line),
- [setelement(2, Token, Line) | simplify(Tokens)];
+ [setelement(2, Token, erl_anno:new(Line)) | simplify(Tokens)];
simplify([]) ->
[].
diff --git a/lib/stdlib/test/ets_SUITE.erl b/lib/stdlib/test/ets_SUITE.erl
index 8dc8b2c291..f47c2c518d 100644
--- a/lib/stdlib/test/ets_SUITE.erl
+++ b/lib/stdlib/test/ets_SUITE.erl
@@ -47,6 +47,7 @@
-export([ordered/1, ordered_match/1, interface_equality/1,
fixtable_next/1, fixtable_insert/1, rename/1, rename_unnamed/1, evil_rename/1,
update_element/1, update_counter/1, evil_update_counter/1, partly_bound/1, match_heavy/1]).
+-export([update_counter_with_default/1]).
-export([member/1]).
-export([memory/1]).
-export([select_fail/1]).
@@ -77,6 +78,7 @@
-export([otp_10182/1]).
-export([ets_all/1]).
-export([memory_check_summary/1]).
+-export([take/1]).
-export([init_per_testcase/2, end_per_testcase/2]).
%% Convenience for manual testing
@@ -98,7 +100,7 @@
misc1_do/1, safe_fixtable_do/1, info_do/1, dups_do/1, heavy_lookup_do/1,
heavy_lookup_element_do/1, member_do/1, otp_5340_do/1, otp_7665_do/1, meta_wb_do/1,
do_heavy_concurrent/1, tab2file2_do/2, exit_large_table_owner_do/2,
- types_do/1, sleeper/0, memory_do/1,
+ types_do/1, sleeper/0, memory_do/1, update_counter_with_default_do/1,
ms_tracee_dummy/1, ms_tracee_dummy/2, ms_tracee_dummy/3, ms_tracee_dummy/4
]).
@@ -115,6 +117,7 @@ init_per_testcase(Case, Config) ->
start_spawn_logger(),
wait_for_test_procs(), %% Ensure previous case cleaned up
Dog=test_server:timetrap(test_server:minutes(20)),
+ put('__ETS_TEST_CASE__', Case),
[{watchdog, Dog}, {test_case, Case} | Config].
end_per_testcase(_Func, Config) ->
@@ -135,7 +138,8 @@ all() ->
{group, heavy}, ordered, ordered_match,
interface_equality, fixtable_next, fixtable_insert,
rename, rename_unnamed, evil_rename, update_element,
- update_counter, evil_update_counter, partly_bound,
+ update_counter, evil_update_counter,
+ update_counter_with_default, partly_bound,
match_heavy, {group, fold}, member, t_delete_object,
t_init_table, t_whitebox, t_delete_all_objects,
t_insert_list, t_test_ms, t_select_delete, t_ets_dets,
@@ -153,6 +157,7 @@ all() ->
otp_9932,
otp_9423,
ets_all,
+ take,
memory_check_summary]. % MUST BE LAST
@@ -212,8 +217,9 @@ memory_check_summary(_Config) ->
ets_test_spawn_logger ! {self(), get_failed_memchecks},
receive {get_failed_memchecks, FailedMemchecks} -> ok end,
io:format("Failed memchecks: ~p\n",[FailedMemchecks]),
- if FailedMemchecks > 3 ->
- ct:fail("Too many failed (~p) memchecks", [FailedMemchecks]);
+ NoFailedMemchecks = length(FailedMemchecks),
+ if NoFailedMemchecks > 3 ->
+ ct:fail("Too many failed (~p) memchecks", [NoFailedMemchecks]);
true ->
ok
end
@@ -1381,7 +1387,7 @@ random_test() ->
{ok,[X]} ->
X;
_ ->
- {A,B,C} = erlang:now(),
+ {A,B,C} = erlang:timestamp(),
random:seed(A,B,C),
get(random_seed)
end,
@@ -1759,6 +1765,14 @@ update_counter_do(Opts) ->
OrdSet = ets_new(ordered_set,[ordered_set | Opts]),
update_counter_for(Set),
update_counter_for(OrdSet),
+ ets:delete_all_objects(Set),
+ ets:delete_all_objects(OrdSet),
+ ets:safe_fixtable(Set, true),
+ ets:safe_fixtable(OrdSet, true),
+ update_counter_for(Set),
+ update_counter_for(OrdSet),
+ ets:safe_fixtable(Set, false),
+ ets:safe_fixtable(OrdSet, false),
ets:delete(Set),
ets:delete(OrdSet),
update_counter_neg(Opts).
@@ -1778,10 +1792,14 @@ update_counter_for(T) ->
?line {NewObj, Ret} = uc_mimic(Obj,Arg3),
ArgHash = erlang:phash2({T,a,Arg3}),
%%io:format("update_counter(~p, ~p, ~p) expecting ~p\n",[T,a,Arg3,Ret]),
+ [DefaultObj] = ets:lookup(T, a),
?line Ret = ets:update_counter(T,a,Arg3),
+ Ret = ets:update_counter(T, b, Arg3, DefaultObj), % Use other key
?line ArgHash = erlang:phash2({T,a,Arg3}),
%%io:format("NewObj=~p~n ",[NewObj]),
?line [NewObj] = ets:lookup(T,a),
+ true = ets:lookup(T, b) =:= [setelement(1, NewObj, b)],
+ ets:delete(T, b),
Myself(NewObj,Times-1,Arg3,Myself)
end,
@@ -2006,6 +2024,44 @@ evil_counter_1(Iter, T) ->
ets:update_counter(T, dracula, 1),
evil_counter_1(Iter-1, T).
+update_counter_with_default(Config) when is_list(Config) ->
+ repeat_for_opts(update_counter_with_default_do).
+
+update_counter_with_default_do(Opts) ->
+ T1 = ets_new(a, [set | Opts]),
+ %% Insert default object.
+ 3 = ets:update_counter(T1, foo, 2, {beaufort,1}),
+ %% Increment.
+ 5 = ets:update_counter(T1, foo, 2, {cabecou,1}),
+ %% Increment with list.
+ [9] = ets:update_counter(T1, foo, [{2,4}], {camembert,1}),
+ %% Same with non-immediate key.
+ 3 = ets:update_counter(T1, {foo,bar}, 2, {{chaource,chevrotin},1}),
+ 5 = ets:update_counter(T1, {foo,bar}, 2, {{cantal,comté},1}),
+ [9] = ets:update_counter(T1, {foo,bar}, [{2,4}], {{emmental,de,savoie},1}),
+ %% Same with ordered set.
+ T2 = ets_new(b, [ordered_set | Opts]),
+ 3 = ets:update_counter(T2, foo, 2, {maroilles,1}),
+ 5 = ets:update_counter(T2, foo, 2, {mimolette,1}),
+ [9] = ets:update_counter(T2, foo, [{2,4}], {morbier,1}),
+ 3 = ets:update_counter(T2, {foo,bar}, 2, {{laguiole},1}),
+ 5 = ets:update_counter(T2, {foo,bar}, 2, {{saint,nectaire},1}),
+ [9] = ets:update_counter(T2, {foo,bar}, [{2,4}], {{rocamadour},1}),
+ %% Arithmetically-equal keys.
+ 3 = ets:update_counter(T2, 1.0, 2, {1,1}),
+ 5 = ets:update_counter(T2, 1, 2, {1,1}),
+ 7 = ets:update_counter(T2, 1, 2, {1.0,1}),
+ %% Same with reversed type difference.
+ 3 = ets:update_counter(T2, 2, 2, {2.0,1}),
+ 5 = ets:update_counter(T2, 2.0, 2, {2.0,1}),
+ 7 = ets:update_counter(T2, 2.0, 2, {2,1}),
+ %% bar is not an integer.
+ {'EXIT',{badarg,_}} = (catch ets:update_counter(T1, qux, 3, {saint,félicien})),
+ %% No third element in default value.
+ {'EXIT',{badarg,_}} = (catch ets:update_counter(T1, qux, [{3,1}], {roquefort,1})),
+
+ ok.
+
fixtable_next(doc) ->
["Check that a first-next sequence always works on a fixed table"];
fixtable_next(suite) ->
@@ -3007,13 +3063,13 @@ time_lookup(Config) when is_list(Config) ->
"~p ets lookups/s",[Values]))}.
time_lookup_do(Opts) ->
- ?line Tab = ets_new(foo,Opts),
- ?line fill_tab(Tab,foo),
- ?line ets:insert(Tab,{{a,key},foo}),
- ?line {Time,_} = ?t:timecall(test_server,do_times,
- [10000,ets,lookup,[Tab,{a,key}]]),
- ?line true = ets:delete(Tab),
- round(10000 / Time). % lookups/s
+ Tab = ets_new(foo,Opts),
+ fill_tab(Tab,foo),
+ ets:insert(Tab,{{a,key},foo}),
+ {Time,_} = ?t:timecall(test_server,do_times,
+ [100000,ets,lookup,[Tab,{a,key}]]),
+ true = ets:delete(Tab),
+ round(100000 / Time). % lookups/s
badlookup(doc) ->
["Check proper return values from bad lookups in existing/non existing "
@@ -3487,12 +3543,9 @@ verify_rescheduling_exit(Config, ForEachData, Flags, Fix, NOTabs, NOProcs) ->
fun () ->
repeat(
fun () ->
- {A, B, C} = now(),
- ?line Name = list_to_atom(
- TestCase
- ++ "-" ++ integer_to_list(A)
- ++ "-" ++ integer_to_list(B)
- ++ "-" ++ integer_to_list(C)),
+ Uniq = erlang:unique_integer([positive]),
+ Name = list_to_atom(TestCase ++ "-" ++
+ integer_to_list(Uniq)),
Tab = ets_new(Name, Flags),
ForEachData(fun(Data) -> ets:insert(Tab, Data) end),
case Fix of
@@ -3770,41 +3823,99 @@ match_object(Config) when is_list(Config) ->
repeat_for_opts(match_object_do).
match_object_do(Opts) ->
- ?line EtsMem = etsmem(),
- ?line Tab = ets_new(foobar, Opts),
- ?line fill_tab(Tab, foo),
- ?line ets:insert(Tab, {{one, 4}, 4}),
- ?line ets:insert(Tab,{{one,5},5}),
- ?line ets:insert(Tab,{{two,4},4}),
- ?line ets:insert(Tab,{{two,5},6}),
- ?line case ets:match_object(Tab, {{one, '_'}, '$0'}) of
+ EtsMem = etsmem(),
+ Tab = ets_new(foobar, Opts),
+ fill_tab(Tab, foo),
+ ets:insert(Tab,{{one,4},4}),
+ ets:insert(Tab,{{one,5},5}),
+ ets:insert(Tab,{{two,4},4}),
+ ets:insert(Tab,{{two,5},6}),
+ ets:insert(Tab, {#{camembert=>cabécou},7}),
+ ets:insert(Tab, {#{"hi"=>"hello","wazzup"=>"awesome","1337"=>"42"},8}),
+ ets:insert(Tab, {#{"hi"=>"hello",#{"wazzup"=>3}=>"awesome","1337"=>"42"},9}),
+ ets:insert(Tab, {#{"hi"=>"hello","wazzup"=>#{"awesome"=>3},"1337"=>"42"},10}),
+ Is = lists:seq(1,100),
+ M1 = maps:from_list([{I,I}||I <- Is]),
+ M2 = maps:from_list([{I,"hi"}||I <- Is]),
+ ets:insert(Tab, {M1,11}),
+ ets:insert(Tab, {M2,12}),
+
+ case ets:match_object(Tab, {{one, '_'}, '$0'}) of
[{{one,5},5},{{one,4},4}] -> ok;
[{{one,4},4},{{one,5},5}] -> ok;
_ -> ?t:fail("ets:match_object() returned something funny.")
end,
- ?line case ets:match_object(Tab, {{two, '$1'}, '$0'}) of
+ case ets:match_object(Tab, {{two, '$1'}, '$0'}) of
[{{two,5},6},{{two,4},4}] -> ok;
[{{two,4},4},{{two,5},6}] -> ok;
_ -> ?t:fail("ets:match_object() returned something funny.")
end,
- ?line case ets:match_object(Tab, {{two, '$9'}, '$4'}) of
+ case ets:match_object(Tab, {{two, '$9'}, '$4'}) of
[{{two,5},6},{{two,4},4}] -> ok;
[{{two,4},4},{{two,5},6}] -> ok;
_ -> ?t:fail("ets:match_object() returned something funny.")
end,
- ?line case ets:match_object(Tab, {{two, '$9'}, '$22'}) of
+ case ets:match_object(Tab, {{two, '$9'}, '$22'}) of
[{{two,5},6},{{two,4},4}] -> ok;
[{{two,4},4},{{two,5},6}] -> ok;
_ -> ?t:fail("ets:match_object() returned something funny.")
end,
- % Check that unsucessful match returns an empty list.
- ?line [] = ets:match_object(Tab, {{three,'$0'}, '$92'}),
+
+ % Check that maps are inspected for variables.
+ [{#{camembert:=cabécou},7}] = ets:match_object(Tab, {#{camembert=>'_'},7}),
+
+ [{#{"hi":="hello",#{"wazzup"=>3}:="awesome","1337":="42"},9}] =
+ ets:match_object(Tab, {#{#{"wazzup"=>3}=>"awesome","hi"=>"hello","1337"=>"42"},9}),
+ [{#{"hi":="hello",#{"wazzup"=>3}:="awesome","1337":="42"},9}] =
+ ets:match_object(Tab, {#{#{"wazzup"=>3}=>"awesome","hi"=>"hello","1337"=>'_'},'_'}),
+ [{#{"hi":="hello","wazzup":=#{"awesome":=3},"1337":="42"},10}] =
+ ets:match_object(Tab, {#{"wazzup"=>'_',"hi"=>'_',"1337"=>'_'},10}),
+
+ %% multiple patterns
+ Pat = {{#{#{"wazzup"=>3}=>"awesome","hi"=>"hello","1337"=>'_'},'$1'},[{is_integer,'$1'}],['$_']},
+ [{#{"hi":="hello",#{"wazzup"=>3}:="awesome","1337":="42"},9}] =
+ ets:select(Tab, [Pat,Pat,Pat,Pat]),
+ case ets:match_object(Tab, {#{"hi"=>"hello","wazzup"=>'_',"1337"=>"42"},'_'}) of
+ [{#{"1337" := "42","hi" := "hello","wazzup" := "awesome"},8},
+ {#{"1337" := "42","hi" := "hello","wazzup" := #{"awesome" := 3}},10}] -> ok;
+ [{#{"1337" := "42","hi" := "hello","wazzup" := #{"awesome" := 3}},10},
+ {#{"1337" := "42","hi" := "hello","wazzup" := "awesome"},8}] -> ok;
+ _ -> ?t:fail("ets:match_object() returned something funny.")
+ end,
+ case ets:match_object(Tab, {#{"hi"=>'_'},'_'}) of
+ [{#{"1337":="42", "hi":="hello"},_},
+ {#{"1337":="42", "hi":="hello"},_},
+ {#{"1337":="42", "hi":="hello"},_}] -> ok;
+ _ -> ?t:fail("ets:match_object() returned something funny.")
+ end,
+
+ %% match large maps
+ [{#{1:=1,2:=2,99:=99,100:=100},11}] = ets:match_object(Tab, {M1,11}),
+ [{#{1:="hi",2:="hi",99:="hi",100:="hi"},12}] = ets:match_object(Tab, {M2,12}),
+ case ets:match_object(Tab, {#{1=>'_',2=>'_'},'_'}) of
+ %% only match a part of the map
+ [{#{1:=1,5:=5,99:=99,100:=100},11},{#{1:="hi",6:="hi",99:="hi"},12}] -> ok;
+ [{#{1:="hi",2:="hi",59:="hi"},12},{#{1:=1,2:=2,39:=39,100:=100},11}] -> ok;
+ _ -> ?t:fail("ets:match_object() returned something funny.")
+ end,
+ case ets:match_object(Tab, {maps:from_list([{I,'_'}||I<-Is]),'_'}) of
+ %% only match a part of the map
+ [{#{1:=1,5:=5,99:=99,100:=100},11},{#{1:="hi",6:="hi",99:="hi"},12}] -> ok;
+ [{#{1:="hi",2:="hi",59:="hi"},12},{#{1:=1,2:=2,39:=39,100:=100},11}] -> ok;
+ _ -> ?t:fail("ets:match_object() returned something funny.")
+ end,
+ {'EXIT',{badarg,_}} = (catch ets:match_object(Tab, {#{'$1'=>'_'},7})),
+ Mve = maps:from_list([{list_to_atom([$$|integer_to_list(I)]),'_'}||I<-Is]),
+ {'EXIT',{badarg,_}} = (catch ets:match_object(Tab, {Mve,11})),
+
+ % Check that unsuccessful match returns an empty list.
+ [] = ets:match_object(Tab, {{three,'$0'}, '$92'}),
% Check that '$0' equals '_'.
Len = length(ets:match_object(Tab, '$0')),
Len = length(ets:match_object(Tab, '_')),
- ?line if Len > 4 -> ok end,
- ?line true = ets:delete(Tab),
- ?line verify_etsmem(EtsMem).
+ if Len > 4 -> ok end,
+ true = ets:delete(Tab),
+ verify_etsmem(EtsMem).
match_object2(suite) -> [];
match_object2(doc) -> ["Tests that db_match_object does not generate "
@@ -3969,21 +4080,39 @@ tab2file(doc) -> ["Check the ets:tab2file function on an empty "
"ets table."];
tab2file(suite) -> [];
tab2file(Config) when is_list(Config) ->
- %% Write an empty ets table to a file, read back and check properties.
- ?line Tab = ets_new(ets_SUITE_foo_tab, [named_table, set, private,
- {keypos, 2}]),
?line FName = filename:join([?config(priv_dir, Config),"tab2file_case"]),
- ?line ok = ets:tab2file(Tab, FName),
- ?line true = ets:delete(Tab),
+ tab2file_do(FName, []),
+ tab2file_do(FName, [{sync,true}]),
+ tab2file_do(FName, [{sync,false}]),
+ {'EXIT',{{badmatch,{error,_}},_}} = (catch tab2file_do(FName, [{sync,yes}])),
+ {'EXIT',{{badmatch,{error,_}},_}} = (catch tab2file_do(FName, [sync])),
+ ok.
+
+tab2file_do(FName, Opts) ->
+ %% Write an empty ets table to a file, read back and check properties.
+ ?line Tab = ets_new(ets_SUITE_foo_tab, [named_table, set, public,
+ {keypos, 2},
+ compressed,
+ {write_concurrency,true},
+ {read_concurrency,true}]),
+ catch file:delete(FName),
+ Res = ets:tab2file(Tab, FName, Opts),
+ true = ets:delete(Tab),
+ ok = Res,
%
?line EtsMem = etsmem(),
?line {ok, Tab2} = ets:file2tab(FName),
- ?line private = ets:info(Tab2, protection),
+ public = ets:info(Tab2, protection),
?line true = ets:info(Tab2, named_table),
?line 2 = ets:info(Tab2, keypos),
?line set = ets:info(Tab2, type),
+ true = ets:info(Tab2, compressed),
+ Smp = erlang:system_info(smp_support),
+ Smp = ets:info(Tab2, read_concurrency),
+ Smp = ets:info(Tab2, write_concurrency),
?line true = ets:delete(Tab2),
?line verify_etsmem(EtsMem).
+
tab2file2(doc) -> ["Check the ets:tab2file function on a ",
"filled set/bag type ets table."];
@@ -4199,7 +4328,7 @@ tabfile_ext4(Config) when is_list(Config) ->
{error,Y} = ets:file2tab(FName,[{verify,true}]),
ets:tab2file(TL,FName,[{extended_info,[md5sum]}]),
{X,Y}
- end || N <- lists:seq(400,500) ],
+ end || N <- lists:seq(500,600) ],
io:format("~p~n",[Res]),
file:delete(FName),
ok.
@@ -4493,16 +4622,16 @@ build_table2(L1,L2,Num) ->
T.
time_match_object(Tab,Match, Res) ->
- T1 = erlang:now(),
+ T1 = erlang:monotonic_time(micro_seconds),
Res = ets:match_object(Tab,Match),
- T2 = erlang:now(),
- nowdiff(T1,T2).
+ T2 = erlang:monotonic_time(micro_seconds),
+ T2 - T1.
time_match(Tab,Match) ->
- T1 = erlang:now(),
+ T1 = erlang:monotonic_time(micro_seconds),
ets:match(Tab,Match),
- T2 = erlang:now(),
- nowdiff(T1,T2).
+ T2 = erlang:monotonic_time(micro_seconds),
+ T2 - T1.
seventyfive_percent_success(_,S,Fa,0) ->
true = (S > ((S + Fa) * 0.75));
@@ -4527,11 +4656,6 @@ fifty_percent_success({M,F,A},S,Fa,N) ->
end.
-nowtonumber({Mega, Secs, Milli}) ->
- Milli + Secs * 1000000 + Mega * 1000000000000.
-nowdiff(T1,T2) ->
- nowtonumber(T2) - nowtonumber(T1).
-
create_random_string(0) ->
[];
@@ -5000,36 +5124,40 @@ colliding_names(Name) ->
grow_shrink(Config) when is_list(Config) ->
?line EtsMem = etsmem(),
- ?line grow_shrink_0(lists:seq(3071, 5000), EtsMem),
- ?line verify_etsmem(EtsMem).
-grow_shrink_0([N|Ns], EtsMem) ->
- ?line grow_shrink_1(N, [set]),
- ?line grow_shrink_1(N, [ordered_set]),
- %% Verifying ets-memory here takes too long time, since
- %% lock-free allocators were introduced...
- %% ?line verify_etsmem(EtsMem),
- grow_shrink_0(Ns, EtsMem);
-grow_shrink_0([], _) -> ok.
-
-grow_shrink_1(N, Flags) ->
- ?line T = ets_new(a, Flags),
- ?line grow_shrink_2(N, N, T),
- ?line ets:delete(T).
+ Set = ets_new(a, [set]),
+ grow_shrink_0(0, 3071, 3000, 5000, Set),
+ ets:delete(Set),
-grow_shrink_2(0, Orig, T) ->
- List = [{I,a} || I <- lists:seq(1, Orig)],
- List = lists:sort(ets:tab2list(T)),
- grow_shrink_3(Orig, T);
-grow_shrink_2(N, Orig, T) ->
+ %OrdSet = ets_new(a, [ordered_set]),
+ %grow_shrink_0(0, lists:seq(3071, 5000), OrdSet),
+ %ets:delete(OrdSet),
+
+ ?line verify_etsmem(EtsMem).
+
+grow_shrink_0(N, _, _, Max, _) when N >= Max ->
+ ok;
+grow_shrink_0(N0, GrowN, ShrinkN, Max, T) ->
+ N1 = grow_shrink_1(N0, GrowN, ShrinkN, T),
+ grow_shrink_0(N1, GrowN, ShrinkN, Max, T).
+
+grow_shrink_1(N0, GrowN, ShrinkN, T) ->
+ N1 = grow_shrink_2(N0+1, N0 + GrowN, T),
+ grow_shrink_3(N1, N1 - ShrinkN, T).
+
+grow_shrink_2(N, GrowTo, _) when N > GrowTo ->
+ %io:format("Grown to ~p\n", [GrowTo]),
+ GrowTo;
+grow_shrink_2(N, GrowTo, T) ->
true = ets:insert(T, {N,a}),
- grow_shrink_2(N-1, Orig, T).
+ grow_shrink_2(N+1, GrowTo, T).
-grow_shrink_3(0, T) ->
- [] = ets:tab2list(T);
-grow_shrink_3(N, T) ->
+grow_shrink_3(N, ShrinkTo, _) when N =< ShrinkTo ->
+ %io:format("Shrunk to ~p\n", [ShrinkTo]),
+ ShrinkTo;
+grow_shrink_3(N, ShrinkTo, T) ->
true = ets:delete(T, N),
- grow_shrink_3(N-1, T).
+ grow_shrink_3(N-1, ShrinkTo, T).
grow_pseudo_deleted(doc) -> ["Grow a table that still contains pseudo-deleted objects"];
grow_pseudo_deleted(suite) -> [];
@@ -5055,17 +5183,29 @@ grow_pseudo_deleted_do(Type) ->
?line Left = ets:info(T,size),
?line Mult = get_kept_objects(T),
filltabstr(T,Mult),
- my_spawn_opt(fun()-> ?line true = ets:info(T,fixed),
- Self ! start,
- io:format("Starting to filltabstr... ~p\n",[now()]),
- filltabstr(T,Mult,Mult+10000),
- io:format("Done with filltabstr. ~p\n",[now()]),
- Self ! done
- end, [link, {scheduler,2}]),
+ my_spawn_opt(
+ fun() ->
+ true = ets:info(T,fixed),
+ Self ! start,
+ io:put_chars("Starting to filltabstr...\n"),
+ do_tc(fun() ->
+ filltabstr(T, Mult, Mult+10000)
+ end,
+ fun(Elapsed) ->
+ io:format("Done with filltabstr in ~p ms\n",
+ [Elapsed])
+ end),
+ Self ! done
+ end, [link, {scheduler,2}]),
?line start = receive_any(),
- io:format("Unfixing table...~p nitems=~p\n",[now(),ets:info(T,size)]),
- ?line true = ets:safe_fixtable(T,false),
- io:format("Unfix table done. ~p nitems=~p\n",[now(),ets:info(T,size)]),
+ io:format("Unfixing table... nitems=~p\n", [ets:info(T, size)]),
+ do_tc(fun() ->
+ true = ets:safe_fixtable(T, false)
+ end,
+ fun(Elapsed) ->
+ io:format("Unfix table done in ~p ms. nitems=~p\n",
+ [Elapsed,ets:info(T, size)])
+ end),
?line false = ets:info(T,fixed),
?line 0 = get_kept_objects(T),
?line done = receive_any(),
@@ -5095,17 +5235,28 @@ shrink_pseudo_deleted_do(Type) ->
[true]}]),
?line Half = ets:info(T,size),
?line Half = get_kept_objects(T),
- my_spawn_opt(fun()-> ?line true = ets:info(T,fixed),
- Self ! start,
- io:format("Starting to delete... ~p\n",[now()]),
- del_one_by_one_set(T,1,Half+1),
- io:format("Done with delete. ~p\n",[now()]),
- Self ! done
- end, [link, {scheduler,2}]),
+ my_spawn_opt(
+ fun()-> true = ets:info(T,fixed),
+ Self ! start,
+ io:put_chars("Starting to delete... ~p\n"),
+ do_tc(fun() ->
+ del_one_by_one_set(T, 1, Half+1)
+ end,
+ fun(Elapsed) ->
+ io:format("Done with delete in ~p ms.\n",
+ [Elapsed])
+ end),
+ Self ! done
+ end, [link, {scheduler,2}]),
?line start = receive_any(),
- io:format("Unfixing table...~p nitems=~p\n",[now(),ets:info(T,size)]),
- ?line true = ets:safe_fixtable(T,false),
- io:format("Unfix table done. ~p nitems=~p\n",[now(),ets:info(T,size)]),
+ io:format("Unfixing table... nitems=~p\n", [ets:info(T, size)]),
+ do_tc(fun() ->
+ true = ets:safe_fixtable(T, false)
+ end,
+ fun(Elapsed) ->
+ io:format("Unfix table done in ~p ms. nitems=~p\n",
+ [Elapsed,ets:info(T, size)])
+ end),
?line false = ets:info(T,fixed),
?line 0 = get_kept_objects(T),
?line done = receive_any(),
@@ -5258,30 +5409,42 @@ smp_unfix_fix_do() ->
?line Deleted = get_kept_objects(T),
{Child, Mref} =
- my_spawn_opt(fun()-> ?line true = ets:info(T,fixed),
- Parent ! start,
- io:format("Child waiting for table to be unfixed... now=~p mem=~p\n",
- [now(),ets:info(T,memory)]),
- repeat_while(fun()-> ets:info(T,fixed) end),
- io:format("Table unfixed. Child Fixating! now=~p mem=~p\n",
- [now(),ets:info(T,memory)]),
- ?line true = ets:safe_fixtable(T,true),
- repeat_while(fun(Key) when Key =< NumOfObjs ->
- ets:delete(T,Key), {true,Key+1};
- (Key) -> {false,Key}
- end,
- Deleted),
- ?line 0 = ets:info(T,size),
- ?line true = get_kept_objects(T) >= Left,
- ?line done = receive_any()
- end,
- [link, monitor, {scheduler,2}]),
+ my_spawn_opt(
+ fun()->
+ true = ets:info(T,fixed),
+ Parent ! start,
+ io:format("Child waiting for table to be unfixed... mem=~p\n",
+ [ets:info(T, memory)]),
+ do_tc(fun() ->
+ repeat_while(fun()-> ets:info(T, fixed) end)
+ end,
+ fun(Elapsed) ->
+ io:format("Table unfixed in ~p ms."
+ " Child Fixating! mem=~p\n",
+ [Elapsed,ets:info(T,memory)])
+ end),
+ true = ets:safe_fixtable(T,true),
+ repeat_while(fun(Key) when Key =< NumOfObjs ->
+ ets:delete(T,Key), {true,Key+1};
+ (Key) -> {false,Key}
+ end,
+ Deleted),
+ 0 = ets:info(T,size),
+ true = get_kept_objects(T) >= Left,
+ done = receive_any()
+ end,
+ [link, monitor, {scheduler,2}]),
?line start = receive_any(),
?line true = ets:info(T,fixed),
- io:format("Parent starting to unfix... ~p\n",[now()]),
- ets:safe_fixtable(T,false),
- io:format("Parent done with unfix. ~p\n",[now()]),
+ io:put_chars("Parent starting to unfix... ~p\n"),
+ do_tc(fun() ->
+ ets:safe_fixtable(T, false)
+ end,
+ fun(Elapsed) ->
+ io:format("Parent done with unfix in ~p ms.\n",
+ [Elapsed])
+ end),
Child ! done,
{'DOWN', Mref, process, Child, normal} = receive_any(),
?line false = ets:info(T,fixed),
@@ -5582,6 +5745,43 @@ ets_all_run() ->
ets_all_run().
+take(Config) when is_list(Config) ->
+ %% Simple test for set tables.
+ T1 = ets_new(a, [set]),
+ [] = ets:take(T1, foo),
+ ets:insert(T1, {foo,bar}),
+ [] = ets:take(T1, bar),
+ [{foo,bar}] = ets:take(T1, foo),
+ [] = ets:tab2list(T1),
+ %% Non-immediate key.
+ ets:insert(T1, {{'not',<<"immediate">>},ok}),
+ [{{'not',<<"immediate">>},ok}] = ets:take(T1, {'not',<<"immediate">>}),
+ %% Same with ordered tables.
+ T2 = ets_new(b, [ordered_set]),
+ [] = ets:take(T2, foo),
+ ets:insert(T2, {foo,bar}),
+ [] = ets:take(T2, bar),
+ [{foo,bar}] = ets:take(T2, foo),
+ [] = ets:tab2list(T2),
+ ets:insert(T2, {{'not',<<"immediate">>},ok}),
+ [{{'not',<<"immediate">>},ok}] = ets:take(T2, {'not',<<"immediate">>}),
+ %% Arithmetically-equal keys.
+ ets:insert(T2, [{1.0,float},{2,integer}]),
+ [{1.0,float}] = ets:take(T2, 1),
+ [{2,integer}] = ets:take(T2, 2.0),
+ [] = ets:tab2list(T2),
+ %% Same with bag.
+ T3 = ets_new(c, [bag]),
+ ets:insert(T3, [{1,1},{1,2},{3,3}]),
+ [{1,1},{1,2}] = ets:take(T3, 1),
+ [{3,3}] = ets:take(T3, 3),
+ [] = ets:tab2list(T3),
+ ets:delete(T1),
+ ets:delete(T2),
+ ets:delete(T3),
+ ok.
+
+
%
% Utility functions:
%
@@ -5730,7 +5930,7 @@ verify_etsmem({MemInfo,AllTabs}) ->
io:format("Actual: ~p", [MemInfo2]),
io:format("Changed tables before: ~p\n",[AllTabs -- AllTabs2]),
io:format("Changed tables after: ~p\n", [AllTabs2 -- AllTabs]),
- ets_test_spawn_logger ! failed_memcheck,
+ ets_test_spawn_logger ! {failed_memcheck, get('__ETS_TEST_CASE__')},
{comment, "Failed memory check"}
end.
@@ -5781,8 +5981,8 @@ spawn_logger(Procs, FailedMemchecks) ->
From ! test_procs_synced,
spawn_logger([From], FailedMemchecks);
- failed_memcheck ->
- spawn_logger(Procs, FailedMemchecks+1);
+ {failed_memcheck, TestCase} ->
+ spawn_logger(Procs, [TestCase|FailedMemchecks]);
{Pid, get_failed_memchecks} ->
Pid ! {get_failed_memchecks, FailedMemchecks},
@@ -5802,7 +6002,7 @@ start_spawn_logger() ->
case whereis(ets_test_spawn_logger) of
Pid when is_pid(Pid) -> true;
_ -> register(ets_test_spawn_logger,
- spawn_opt(fun () -> spawn_logger([], 0) end,
+ spawn_opt(fun () -> spawn_logger([], []) end,
[{priority, max}]))
end.
@@ -6246,3 +6446,10 @@ repeat_for_opts_atom2list(compressed) -> [compressed,void].
ets_new(Name, Opts) ->
%%ets:new(Name, [compressed | Opts]).
ets:new(Name, Opts).
+
+do_tc(Do, Report) ->
+ T1 = erlang:monotonic_time(),
+ Do(),
+ T2 = erlang:monotonic_time(),
+ Elapsed = erlang:convert_time_unit(T2 - T1, native, milli_seconds),
+ Report(Elapsed).
diff --git a/lib/stdlib/test/filelib_SUITE.erl b/lib/stdlib/test/filelib_SUITE.erl
index bd313390b3..146d810189 100644
--- a/lib/stdlib/test/filelib_SUITE.erl
+++ b/lib/stdlib/test/filelib_SUITE.erl
@@ -77,7 +77,8 @@ wildcard_one(Config) when is_list(Config) ->
L = filelib:wildcard(Wc),
L = filelib:wildcard(Wc, erl_prim_loader),
L = filelib:wildcard(Wc, "."),
- L = filelib:wildcard(Wc, Dir)
+ L = filelib:wildcard(Wc, Dir),
+ L = filelib:wildcard(Wc, Dir++"/.")
end),
?line file:set_cwd(OldCwd),
?line ok = file:del_dir(Dir),
diff --git a/lib/stdlib/test/filename_SUITE.erl b/lib/stdlib/test/filename_SUITE.erl
index ecd9cff9f9..70e7ad9788 100644
--- a/lib/stdlib/test/filename_SUITE.erl
+++ b/lib/stdlib/test/filename_SUITE.erl
@@ -1,7 +1,7 @@
%%
%% %CopyrightBegin%
%%
-%% Copyright Ericsson AB 1997-2012. All Rights Reserved.
+%% Copyright Ericsson AB 1997-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
@@ -287,38 +287,66 @@ extension(Config) when is_list(Config) ->
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
join(Config) when is_list(Config) ->
+ %% Whenever joining two elements, test the equivalence between
+ %% join/1 and join/2 (OTP-12158) by using help function
+ %% filename_join/2.
?line "/" = filename:join(["/"]),
?line "/" = filename:join(["//"]),
- ?line "usr/foo.erl" = filename:join("usr","foo.erl"),
- ?line "/src/foo.erl" = filename:join(usr, "/src/foo.erl"),
- ?line "/src/foo.erl" = filename:join(["/src/",'foo.erl']),
- ?line "/src/foo.erl" = filename:join(usr, ["/sr", 'c/foo.erl']),
- ?line "/src/foo.erl" = filename:join("usr", "/src/foo.erl"),
+ "usr/foo.erl" = filename_join("usr","foo.erl"),
+ "/src/foo.erl" = filename_join(usr, "/src/foo.erl"),
+ "/src/foo.erl" = filename_join("/src/",'foo.erl'),
+ "/src/foo.erl" = filename_join(usr, ["/sr", 'c/foo.erl']),
+ "/src/foo.erl" = filename_join("usr", "/src/foo.erl"),
%% Make sure that redundant slashes work too.
?line "a/b/c/d/e/f/g" = filename:join(["a//b/c/////d//e/f/g"]),
- ?line "a/b/c/d/e/f/g" = filename:join(["a//b/c/", "d//e/f/g"]),
- ?line "a/b/c/d/e/f/g" = filename:join(["a//b/c", "d//e/f/g"]),
- ?line "/d/e/f/g" = filename:join(["a//b/c", "/d//e/f/g"]),
- ?line "/d/e/f/g" = filename:join(["a//b/c", "//d//e/f/g"]),
-
- ?line "foo/bar" = filename:join([$f,$o,$o,$/,[]], "bar"),
+ "a/b/c/d/e/f/g" = filename_join("a//b/c/", "d//e/f/g"),
+ "a/b/c/d/e/f/g" = filename_join("a//b/c", "d//e/f/g"),
+ "/d/e/f/g" = filename_join("a//b/c", "/d//e/f/g"),
+ "/d/e/f/g" = filename:join("a//b/c", "//d//e/f/g"),
+
+ "foo/bar" = filename_join([$f,$o,$o,$/,[]], "bar"),
+
+ %% Single dots - should be removed if in the middle of the path,
+ %% but not at the end of the path.
+ "/." = filename:join(["/."]),
+ "/" = filename:join(["/./"]),
+ "/." = filename:join(["/./."]),
+ "./." = filename:join(["./."]),
+
+ "/a/b" = filename_join("/a/.","b"),
+ "/a/b/." = filename_join("/a/.","b/."),
+ "/a/." = filename_join("/a/.","."),
+ "/a/." = filename_join("/a","."),
+ "/a/." = filename_join("/a/.",""),
+ "./." = filename_join("./.","."),
+ "./." = filename_join("./","."),
+ "./." = filename_join("./.",""),
+ "." = filename_join(".",""),
+ "./." = filename_join(".","."),
+
+ %% Trailing slash shall be removed - except the root
+ "/" = filename:join(["/"]),
+ "/" = filename:join(["/./"]),
+ "/a" = filename:join(["/a/"]),
+ "/b" = filename_join("/a/","/b/"),
+ "/a/b" = filename_join("/a/","b/"),
?line case os:type() of
{win32, _} ->
?line "d:/" = filename:join(["D:/"]),
?line "d:/" = filename:join(["D:\\"]),
- ?line "d:/abc" = filename:join(["D:/", "abc"]),
- ?line "d:abc" = filename:join(["D:", "abc"]),
+ "d:/abc" = filename_join("D:/", "abc"),
+ "d:abc" = filename_join("D:", "abc"),
?line "a/b/c/d/e/f/g" =
filename:join(["a//b\\c//\\/\\d/\\e/f\\g"]),
?line "a:usr/foo.erl" =
filename:join(["A:","usr","foo.erl"]),
?line "/usr/foo.erl" =
filename:join(["A:","/usr","foo.erl"]),
- ?line "c:usr" = filename:join("A:","C:usr"),
- ?line "a:usr" = filename:join("A:","usr"),
- ?line "c:/usr" = filename:join("A:", "C:/usr"),
+ "c:usr" = filename_join("A:","C:usr"),
+ "a:usr" = filename_join("A:","usr"),
+ "c:/usr" = filename_join("A:", "C:/usr"),
?line "c:/usr/foo.erl" =
filename:join(["A:","C:/usr","foo.erl"]),
?line "c:usr/foo.erl" =
@@ -329,6 +357,11 @@ join(Config) when is_list(Config) ->
ok
end.
+%% Make sure join([A,B]) is equivalent to join(A,B) (OTP-12158)
+filename_join(A,B) ->
+ Res = filename:join(A,B),
+ Res = filename:join([A,B]).
+
pathtype(Config) when is_list(Config) ->
?line relative = filename:pathtype(".."),
?line relative = filename:pathtype("foo"),
@@ -362,6 +395,8 @@ split(Config) when is_list(Config) ->
?line ["foo", "bar", "hello"]= filename:split("foo////bar//hello"),
?line ["foo", "bar", "hello"]= filename:split(["foo//",'//bar//h',"ello"]),
?line ["foo", "bar", "hello"]= filename:split(["foo//",'//bar//h'|ello]),
+ ["/"] = filename:split("/"),
+ [] = filename:split(""),
case os:type() of
{win32,_} ->
?line ["a:/","msdev","include"] =
@@ -633,6 +668,53 @@ join_bin(Config) when is_list(Config) ->
?line <<"foo/bar">> = filename:join([$f,$o,$o,$/,[]], <<"bar">>),
+ %% Single dots - should be removed if in the middle of the path,
+ %% but not at the end of the path.
+ %% Also test equivalence between join/1 and join/2 (OTP-12158)
+ <<"/.">> = filename:join([<<"/.">>]),
+ <<"/">> = filename:join([<<"/./">>]),
+ <<"/.">> = filename:join([<<"/./.">>]),
+ <<"./.">> = filename:join([<<"./.">>]),
+
+ <<"/a/b">> = filename:join([<<"/a/.">>,<<"b">>]),
+ <<"/a/b">> = filename:join(<<"/a/.">>,<<"b">>),
+
+ <<"/a/b/.">> = filename:join([<<"/a/.">>,<<"b/.">>]),
+ <<"/a/b/.">> = filename:join(<<"/a/.">>,<<"b/.">>),
+
+ <<"/a/.">> = filename:join([<<"/a/.">>,<<".">>]),
+ <<"/a/.">> = filename:join(<<"/a/.">>,<<".">>),
+
+ <<"/a/.">> = filename:join([<<"/a">>,<<".">>]),
+ <<"/a/.">> = filename:join(<<"/a">>,<<".">>),
+
+ <<"/a/.">> = filename:join([<<"/a/.">>,<<"">>]),
+ <<"/a/.">> = filename:join(<<"/a/.">>,<<"">>),
+
+ <<"./.">> = filename:join([<<"./.">>,<<".">>]),
+ <<"./.">> = filename:join(<<"./.">>,<<".">>),
+
+ <<"./.">> = filename:join([<<"./">>,<<".">>]),
+ <<"./.">> = filename:join(<<"./">>,<<".">>),
+
+ <<"./.">> = filename:join([<<"./.">>,<<"">>]),
+ <<"./.">> = filename:join(<<"./.">>,<<"">>),
+
+ <<".">> = filename:join([<<".">>,<<"">>]),
+ <<".">> = filename:join(<<".">>,<<"">>),
+
+ <<"./.">> = filename:join([<<".">>,<<".">>]),
+ <<"./.">> = filename:join(<<".">>,<<".">>),
+
+ %% Trailing slash shall be removed - except the root
+ <<"/">> = filename:join([<<"/">>]),
+ <<"/">> = filename:join([<<"/./">>]),
+ <<"/a">> = filename:join([<<"/a/">>]),
+ <<"/b">> = filename:join([<<"/a/">>,<<"/b/">>]),
+ <<"/b">> = filename:join(<<"/a/">>,<<"/b/">>),
+ <<"/a/b">> = filename:join([<<"/a/">>,<<"b/">>]),
+ <<"/a/b">> = filename:join(<<"/a/">>,<<"b/">>),
+
?line case os:type() of
{win32, _} ->
?line <<"d:/">> = filename:join([<<"D:/">>]),
@@ -687,6 +769,8 @@ split_bin(Config) when is_list(Config) ->
[<<"/">>,<<"usr">>,<<"local">>,<<"bin">>] = filename:split(<<"/usr/local/bin">>),
[<<"foo">>,<<"bar">>]= filename:split(<<"foo/bar">>),
[<<"foo">>, <<"bar">>, <<"hello">>]= filename:split(<<"foo////bar//hello">>),
+ [<<"/">>] = filename:split(<<"/">>),
+ [] = filename:split(<<"">>),
case os:type() of
{win32,_} ->
[<<"a:/">>,<<"msdev">>,<<"include">>] =
diff --git a/lib/stdlib/test/gen_event_SUITE.erl b/lib/stdlib/test/gen_event_SUITE.erl
index 60a1ba8c60..6c28eb00c3 100644
--- a/lib/stdlib/test/gen_event_SUITE.erl
+++ b/lib/stdlib/test/gen_event_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
@@ -106,7 +106,7 @@ start(Config) when is_list(Config) ->
?line {error, {already_started, _}} =
gen_event:start({global, my_dummy_name}),
- exit(Pid6, shutdown),
+ ok = gen_event:stop({global, my_dummy_name}, shutdown, 10000),
receive
{'EXIT', Pid6, shutdown} -> ok
after 10000 ->
@@ -131,90 +131,105 @@ start(Config) when is_list(Config) ->
ok.
-hibernate(suite) -> [];
hibernate(Config) when is_list(Config) ->
- ?line {ok,Pid} = gen_event:start({local, my_dummy_handler}),
- ?line ok = gen_event:add_handler(my_dummy_handler, dummy_h, [self()]),
- ?line [dummy_h] = gen_event:which_handlers(my_dummy_handler),
- ?line true = gen_event:call(my_dummy_handler, dummy_h, hibernate),
- ?line receive after 1000 -> ok end,
- ?line {current_function,{erlang,hibernate,3}} = erlang:process_info(Pid,current_function),
- ?line Pid ! wake,
- ?line receive after 1000 -> ok end,
- ?line true = ({current_function,{erlang,hibernate,3}} =/=
- erlang:process_info(Pid,current_function)),
- ?line later = gen_event:call(my_dummy_handler, dummy_h, hibernate_later),
- ?line true = ({current_function,{erlang,hibernate,3}} =/=
- erlang:process_info(Pid,current_function)),
- ?line receive after 2000 -> ok end,
- ?line {current_function,{erlang,hibernate,3}} = erlang:process_info(Pid,current_function),
- ?line Pid ! wake,
- ?line receive after 1000 -> ok end,
- ?line true = ({current_function,{erlang,hibernate,3}} =/=
- erlang:process_info(Pid,current_function)),
- ?line gen_event:notify(my_dummy_handler,hibernate),
- ?line receive after 1000 -> ok end,
- ?line {current_function,{erlang,hibernate,3}} = erlang:process_info(Pid,current_function),
- ?line gen_event:notify(my_dummy_handler,wakeup),
- ?line receive after 1000 -> ok end,
- ?line true = ({current_function,{erlang,hibernate,3}} =/=
- erlang:process_info(Pid,current_function)),
- ?line gen_event:notify(my_dummy_handler,hibernate),
- ?line receive after 1000 -> ok end,
- ?line {current_function,{erlang,hibernate,3}} = erlang:process_info(Pid,current_function),
- ?line gen_event:sync_notify(my_dummy_handler,wakeup),
- ?line true = ({current_function,{erlang,hibernate,3}} =/=
- erlang:process_info(Pid,current_function)),
- ?line ok = gen_event:sync_notify(my_dummy_handler,hibernate),
- ?line receive after 1000 -> ok end,
- ?line {current_function,{erlang,hibernate,3}} = erlang:process_info(Pid,current_function),
- ?line Pid ! wake,
- ?line receive after 1000 -> ok end,
- ?line true = ({current_function,{erlang,hibernate,3}} =/=
- erlang:process_info(Pid,current_function)),
- ?line ok = gen_event:add_handler(my_dummy_handler, dummy1_h, [self()]),
- ?line [_,_] = gen_event:which_handlers(my_dummy_handler),
- ?line gen_event:notify(my_dummy_handler,hibernate),
- ?line receive after 1000 -> ok end,
- ?line {current_function,{erlang,hibernate,3}} = erlang:process_info(Pid,current_function),
- ?line gen_event:notify(my_dummy_handler,wakeup),
- ?line receive after 1000 -> ok end,
- ?line {current_function,{erlang,hibernate,3}} = erlang:process_info(Pid,current_function),
- ?line Pid ! wake,
- ?line receive after 1000 -> ok end,
- ?line true = ({current_function,{erlang,hibernate,3}} =/=
- erlang:process_info(Pid,current_function)),
- ?line Pid ! gnurf,
- ?line receive after 1000 -> ok end,
- ?line {current_function,{erlang,hibernate,3}} = erlang:process_info(Pid,current_function),
- ?line Pid ! sleep,
- ?line receive after 1000 -> ok end,
- ?line {current_function,{erlang,hibernate,3}} = erlang:process_info(Pid,current_function),
- ?line Pid ! wake,
- ?line receive after 1000 -> ok end,
- ?line true = ({current_function,{erlang,hibernate,3}} =/=
- erlang:process_info(Pid,current_function)),
- ?line ok = gen_event:stop(my_dummy_handler),
- ?line {ok,Pid2} = gen_event:start({local, my_dummy_handler}),
- ?line ok = gen_event:add_handler(my_dummy_handler, dummy_h, [self(),hibernate]),
- ?line receive after 1000 -> ok end,
- ?line {current_function,{erlang,hibernate,3}} = erlang:process_info(Pid2,current_function),
- ?line sys:suspend(my_dummy_handler),
- ?line receive after 1000 -> ok end,
- ?line {current_function,{erlang,hibernate,3}} = erlang:process_info(Pid2,current_function),
- ?line sys:resume(my_dummy_handler),
- ?line receive after 1000 -> ok end,
- ?line {current_function,{erlang,hibernate,3}} = erlang:process_info(Pid2,current_function),
- ?line Pid2 ! wake,
- ?line receive after 1000 -> ok end,
- ?line true = ({current_function,{erlang,hibernate,3}} =/=
- erlang:process_info(Pid2,current_function)),
+ {ok,Pid} = gen_event:start({local, my_dummy_handler}),
+ ok = gen_event:add_handler(my_dummy_handler, dummy_h, [self()]),
+ [dummy_h] = gen_event:which_handlers(my_dummy_handler),
+ true = gen_event:call(my_dummy_handler, dummy_h, hibernate),
+ is_in_erlang_hibernate(Pid),
+
+ Pid ! wake,
+ is_not_in_erlang_hibernate(Pid),
+ later = gen_event:call(my_dummy_handler, dummy_h, hibernate_later),
+ true = ({current_function,{erlang,hibernate,3}} =/=
+ erlang:process_info(Pid, current_function)),
+ is_in_erlang_hibernate(Pid),
+
+ Pid ! wake,
+ is_not_in_erlang_hibernate(Pid),
+ gen_event:notify(my_dummy_handler, hibernate),
+ is_in_erlang_hibernate(Pid),
+ gen_event:notify(my_dummy_handler, wakeup),
+ is_not_in_erlang_hibernate(Pid),
+ gen_event:notify(my_dummy_handler, hibernate),
+ is_in_erlang_hibernate(Pid),
+ gen_event:sync_notify(my_dummy_handler, wakeup),
+ true = ({current_function,{erlang,hibernate,3}} =/=
+ erlang:process_info(Pid, current_function)),
+ ok = gen_event:sync_notify(my_dummy_handler, hibernate),
+ is_in_erlang_hibernate(Pid),
+
+ Pid ! wake,
+ is_not_in_erlang_hibernate(Pid),
+ ok = gen_event:add_handler(my_dummy_handler, dummy1_h, [self()]),
+ [_,_] = gen_event:which_handlers(my_dummy_handler),
+ gen_event:notify(my_dummy_handler, hibernate),
+ is_in_erlang_hibernate(Pid),
+ gen_event:notify(my_dummy_handler, wakeup),
+ is_in_erlang_hibernate(Pid),
+
+ Pid ! wake,
+ is_not_in_erlang_hibernate(Pid),
+
+ Pid ! gnurf,
+ is_in_erlang_hibernate(Pid),
+
+ Pid ! sleep,
+ is_in_erlang_hibernate(Pid),
+
+ Pid ! wake,
+ is_not_in_erlang_hibernate(Pid),
+ ok = gen_event:stop(my_dummy_handler),
+
+ {ok,Pid2} = gen_event:start({local, my_dummy_handler}),
+ ok = gen_event:add_handler(my_dummy_handler, dummy_h,
+ [self(),hibernate]),
+ is_in_erlang_hibernate(Pid2),
+ sys:suspend(my_dummy_handler),
+ is_in_erlang_hibernate(Pid2),
+ sys:resume(my_dummy_handler),
+ is_in_erlang_hibernate(Pid2),
+
+ Pid2 ! wake,
+ is_not_in_erlang_hibernate(Pid2),
-
- ?line ok = gen_event:stop(my_dummy_handler),
+ ok = gen_event:stop(my_dummy_handler),
ok.
+is_in_erlang_hibernate(Pid) ->
+ receive after 1 -> ok end,
+ is_in_erlang_hibernate_1(200, Pid).
+
+is_in_erlang_hibernate_1(0, Pid) ->
+ io:format("~p\n", [erlang:process_info(Pid, current_function)]),
+ ?t:fail(not_in_erlang_hibernate_3);
+is_in_erlang_hibernate_1(N, Pid) ->
+ {current_function,MFA} = erlang:process_info(Pid, current_function),
+ case MFA of
+ {erlang,hibernate,3} ->
+ ok;
+ _ ->
+ receive after 10 -> ok end,
+ is_in_erlang_hibernate_1(N-1, Pid)
+ end.
+
+is_not_in_erlang_hibernate(Pid) ->
+ receive after 1 -> ok end,
+ is_not_in_erlang_hibernate_1(200, Pid).
+
+is_not_in_erlang_hibernate_1(0, Pid) ->
+ io:format("~p\n", [erlang:process_info(Pid, current_function)]),
+ ?t:fail(not_in_erlang_hibernate_3);
+is_not_in_erlang_hibernate_1(N, Pid) ->
+ {current_function,MFA} = erlang:process_info(Pid, current_function),
+ case MFA of
+ {erlang,hibernate,3} ->
+ receive after 10 -> ok end,
+ is_not_in_erlang_hibernate_1(N-1, Pid);
+ _ ->
+ ok
+ end.
add_handler(doc) -> [];
diff --git a/lib/stdlib/test/gen_fsm_SUITE.erl b/lib/stdlib/test/gen_fsm_SUITE.erl
index 39f0442824..f003630535 100644
--- a/lib/stdlib/test/gen_fsm_SUITE.erl
+++ b/lib/stdlib/test/gen_fsm_SUITE.erl
@@ -27,6 +27,9 @@
-export([start1/1, start2/1, start3/1, start4/1, start5/1, start6/1,
start7/1, start8/1, start9/1, start10/1, start11/1, start12/1]).
+-export([stop1/1, stop2/1, stop3/1, stop4/1, stop5/1, stop6/1, stop7/1,
+ stop8/1, stop9/1, stop10/1]).
+
-export([ abnormal1/1, abnormal2/1]).
-export([shutdown/1]).
@@ -66,6 +69,8 @@ groups() ->
[{start, [],
[start1, start2, start3, start4, start5, start6, start7,
start8, start9, start10, start11, start12]},
+ {stop, [],
+ [stop1, stop2, stop3, stop4, stop5, stop6, stop7, stop8, stop9, stop10]},
{abnormal, [], [abnormal1, abnormal2]},
{sys, [],
[sys1, call_format_status, error_format_status, terminate_crash_format,
@@ -281,6 +286,105 @@ start12(Config) when is_list(Config) ->
ok.
+%% Anonymous, reason 'normal'
+stop1(_Config) ->
+ {ok, Pid} = gen_fsm:start(?MODULE, [], []),
+ ok = gen_fsm:stop(Pid),
+ false = erlang:is_process_alive(Pid),
+ {'EXIT',noproc} = (catch gen_fsm:stop(Pid)),
+ ok.
+
+%% Anonymous, other reason
+stop2(_Config) ->
+ {ok,Pid} = gen_fsm:start(?MODULE, [], []),
+ ok = gen_fsm:stop(Pid, other_reason, infinity),
+ false = erlang:is_process_alive(Pid),
+ ok.
+
+%% Anonymous, invalid timeout
+stop3(_Config) ->
+ {ok,Pid} = gen_fsm:start(?MODULE, [], []),
+ {'EXIT',_} = (catch gen_fsm:stop(Pid, other_reason, invalid_timeout)),
+ true = erlang:is_process_alive(Pid),
+ ok = gen_fsm:stop(Pid),
+ false = erlang:is_process_alive(Pid),
+ ok.
+
+%% Registered name
+stop4(_Config) ->
+ {ok,Pid} = gen_fsm:start({local,to_stop},?MODULE, [], []),
+ ok = gen_fsm:stop(to_stop),
+ false = erlang:is_process_alive(Pid),
+ {'EXIT',noproc} = (catch gen_fsm:stop(to_stop)),
+ ok.
+
+%% Registered name and local node
+stop5(_Config) ->
+ {ok,Pid} = gen_fsm:start({local,to_stop},?MODULE, [], []),
+ ok = gen_fsm:stop({to_stop,node()}),
+ false = erlang:is_process_alive(Pid),
+ {'EXIT',noproc} = (catch gen_fsm:stop({to_stop,node()})),
+ ok.
+
+%% Globally registered name
+stop6(_Config) ->
+ {ok, Pid} = gen_fsm:start({global, to_stop}, ?MODULE, [], []),
+ ok = gen_fsm:stop({global,to_stop}),
+ false = erlang:is_process_alive(Pid),
+ {'EXIT',noproc} = (catch gen_fsm:stop({global,to_stop})),
+ ok.
+
+%% 'via' registered name
+stop7(_Config) ->
+ dummy_via:reset(),
+ {ok, Pid} = gen_fsm:start({via, dummy_via, to_stop},
+ ?MODULE, [], []),
+ ok = gen_fsm:stop({via, dummy_via, to_stop}),
+ false = erlang:is_process_alive(Pid),
+ {'EXIT',noproc} = (catch gen_fsm:stop({via, dummy_via, to_stop})),
+ ok.
+
+%% Anonymous on remote node
+stop8(_Config) ->
+ {ok,Node} = test_server:start_node(gen_fsm_SUITE_stop8,slave,[]),
+ Dir = filename:dirname(code:which(?MODULE)),
+ rpc:call(Node,code,add_path,[Dir]),
+ {ok, Pid} = rpc:call(Node,gen_fsm,start,[?MODULE,[],[]]),
+ ok = gen_fsm:stop(Pid),
+ false = rpc:call(Node,erlang,is_process_alive,[Pid]),
+ {'EXIT',noproc} = (catch gen_fsm:stop(Pid)),
+ true = test_server:stop_node(Node),
+ {'EXIT',{{nodedown,Node},_}} = (catch gen_fsm:stop(Pid)),
+ ok.
+
+%% Registered name on remote node
+stop9(_Config) ->
+ {ok,Node} = test_server:start_node(gen_fsm_SUITE_stop9,slave,[]),
+ Dir = filename:dirname(code:which(?MODULE)),
+ rpc:call(Node,code,add_path,[Dir]),
+ {ok, Pid} = rpc:call(Node,gen_fsm,start,[{local,to_stop},?MODULE,[],[]]),
+ ok = gen_fsm:stop({to_stop,Node}),
+ undefined = rpc:call(Node,erlang,whereis,[to_stop]),
+ false = rpc:call(Node,erlang,is_process_alive,[Pid]),
+ {'EXIT',noproc} = (catch gen_fsm:stop({to_stop,Node})),
+ true = test_server:stop_node(Node),
+ {'EXIT',{{nodedown,Node},_}} = (catch gen_fsm:stop({to_stop,Node})),
+ ok.
+
+%% Globally registered name on remote node
+stop10(_Config) ->
+ {ok,Node} = test_server:start_node(gen_fsm_SUITE_stop10,slave,[]),
+ Dir = filename:dirname(code:which(?MODULE)),
+ rpc:call(Node,code,add_path,[Dir]),
+ {ok, Pid} = rpc:call(Node,gen_fsm,start,[{global,to_stop},?MODULE,[],[]]),
+ global:sync(),
+ ok = gen_fsm:stop({global,to_stop}),
+ false = rpc:call(Node,erlang,is_process_alive,[Pid]),
+ {'EXIT',noproc} = (catch gen_fsm:stop({global,to_stop})),
+ true = test_server:stop_node(Node),
+ {'EXIT',noproc} = (catch gen_fsm:stop({global,to_stop})),
+ ok.
+
%% Check that time outs in calls work
abnormal1(suite) -> [];
abnormal1(Config) when is_list(Config) ->
@@ -492,129 +596,123 @@ replace_state(Config) when is_list(Config) ->
ok.
%% Hibernation
-hibernate(suite) -> [];
hibernate(Config) when is_list(Config) ->
OldFl = process_flag(trap_exit, true),
- ?line {ok, Pid0} = gen_fsm:start_link(?MODULE, hiber_now, []),
- ?line receive after 1000 -> ok end,
- ?line {current_function,{erlang,hibernate,3}} =
- erlang:process_info(Pid0,current_function),
- ?line stop_it(Pid0),
+ {ok, Pid0} = gen_fsm:start_link(?MODULE, hiber_now, []),
+ is_in_erlang_hibernate(Pid0),
+ stop_it(Pid0),
test_server:messages_get(),
-
- ?line {ok, Pid} = gen_fsm:start_link(?MODULE, hiber, []),
- ?line true = ({current_function,{erlang,hibernate,3}} =/= erlang:process_info(Pid,current_function)),
- ?line hibernating = gen_fsm:sync_send_event(Pid,hibernate_sync),
- ?line receive after 1000 -> ok end,
- ?line {current_function,{erlang,hibernate,3}} =
- erlang:process_info(Pid,current_function),
- ?line good_morning = gen_fsm:sync_send_event(Pid,wakeup_sync),
- ?line receive after 1000 -> ok end,
- ?line true = ({current_function,{erlang,hibernate,3}} =/= erlang:process_info(Pid,current_function)),
- ?line hibernating = gen_fsm:sync_send_event(Pid,hibernate_sync),
- ?line receive after 1000 -> ok end,
- ?line {current_function,{erlang,hibernate,3}} =
- erlang:process_info(Pid,current_function),
- ?line five_more = gen_fsm:sync_send_event(Pid,snooze_sync),
- ?line receive after 1000 -> ok end,
- ?line {current_function,{erlang,hibernate,3}} =
- erlang:process_info(Pid,current_function),
- ?line good_morning = gen_fsm:sync_send_event(Pid,wakeup_sync),
- ?line receive after 1000 -> ok end,
- ?line true = ({current_function,{erlang,hibernate,3}} =/= erlang:process_info(Pid,current_function)),
- ?line ok = gen_fsm:send_event(Pid,hibernate_async),
- ?line receive after 1000 -> ok end,
- ?line {current_function,{erlang,hibernate,3}} =
- erlang:process_info(Pid,current_function),
- ?line ok = gen_fsm:send_event(Pid,wakeup_async),
- ?line receive after 1000 -> ok end,
- ?line true = ({current_function,{erlang,hibernate,3}} =/= erlang:process_info(Pid,current_function)),
- ?line ok = gen_fsm:send_event(Pid,hibernate_async),
- ?line receive after 1000 -> ok end,
- ?line {current_function,{erlang,hibernate,3}} =
- erlang:process_info(Pid,current_function),
- ?line ok = gen_fsm:send_event(Pid,snooze_async),
- ?line receive after 1000 -> ok end,
- ?line {current_function,{erlang,hibernate,3}} =
- erlang:process_info(Pid,current_function),
- ?line ok = gen_fsm:send_event(Pid,wakeup_async),
- ?line receive after 1000 -> ok end,
- ?line true = ({current_function,{erlang,hibernate,3}} =/= erlang:process_info(Pid,current_function)),
- ?line Pid ! hibernate_later,
- ?line true = ({current_function,{erlang,hibernate,3}} =/= erlang:process_info(Pid,current_function)),
- ?line receive after 2000 -> ok end,
- ?line ({current_function,{erlang,hibernate,3}} = erlang:process_info(Pid,current_function)),
- ?line 'alive!' = gen_fsm:sync_send_event(Pid,'alive?'),
- ?line true = ({current_function,{erlang,hibernate,3}} =/= erlang:process_info(Pid,current_function)),
- ?line Pid ! hibernate_now,
- ?line receive after 1000 -> ok end,
- ?line ({current_function,{erlang,hibernate,3}} = erlang:process_info(Pid,current_function)),
- ?line 'alive!' = gen_fsm:sync_send_event(Pid,'alive?'),
- ?line true = ({current_function,{erlang,hibernate,3}} =/= erlang:process_info(Pid,current_function)),
-
-
- ?line hibernating = gen_fsm:sync_send_all_state_event(Pid,hibernate_sync),
- ?line receive after 1000 -> ok end,
- ?line {current_function,{erlang,hibernate,3}} =
- erlang:process_info(Pid,current_function),
- ?line good_morning = gen_fsm:sync_send_all_state_event(Pid,wakeup_sync),
- ?line receive after 1000 -> ok end,
- ?line true = ({current_function,{erlang,hibernate,3}} =/= erlang:process_info(Pid,current_function)),
- ?line hibernating = gen_fsm:sync_send_all_state_event(Pid,hibernate_sync),
- ?line receive after 1000 -> ok end,
- ?line {current_function,{erlang,hibernate,3}} =
- erlang:process_info(Pid,current_function),
- ?line five_more = gen_fsm:sync_send_all_state_event(Pid,snooze_sync),
- ?line receive after 1000 -> ok end,
- ?line {current_function,{erlang,hibernate,3}} =
- erlang:process_info(Pid,current_function),
- ?line good_morning = gen_fsm:sync_send_all_state_event(Pid,wakeup_sync),
- ?line receive after 1000 -> ok end,
- ?line true = ({current_function,{erlang,hibernate,3}} =/= erlang:process_info(Pid,current_function)),
- ?line ok = gen_fsm:send_all_state_event(Pid,hibernate_async),
- ?line receive after 1000 -> ok end,
- ?line {current_function,{erlang,hibernate,3}} =
- erlang:process_info(Pid,current_function),
- ?line ok = gen_fsm:send_all_state_event(Pid,wakeup_async),
- ?line receive after 1000 -> ok end,
- ?line true = ({current_function,{erlang,hibernate,3}} =/= erlang:process_info(Pid,current_function)),
- ?line ok = gen_fsm:send_all_state_event(Pid,hibernate_async),
- ?line receive after 1000 -> ok end,
- ?line {current_function,{erlang,hibernate,3}} =
- erlang:process_info(Pid,current_function),
- ?line ok = gen_fsm:send_all_state_event(Pid,snooze_async),
- ?line receive after 1000 -> ok end,
- ?line {current_function,{erlang,hibernate,3}} =
- erlang:process_info(Pid,current_function),
- ?line ok = gen_fsm:send_all_state_event(Pid,wakeup_async),
- ?line receive after 1000 -> ok end,
- ?line true = ({current_function,{erlang,hibernate,3}} =/= erlang:process_info(Pid,current_function)),
-
- ?line hibernating = gen_fsm:sync_send_all_state_event(Pid,hibernate_sync),
- ?line receive after 1000 -> ok end,
- ?line {current_function,{erlang,hibernate,3}} =
- erlang:process_info(Pid,current_function),
- ?line sys:suspend(Pid),
- ?line receive after 1000 -> ok end,
- ?line {current_function,{erlang,hibernate,3}} = erlang:process_info(Pid,current_function),
- ?line sys:resume(Pid),
- ?line receive after 1000 -> ok end,
- ?line {current_function,{erlang,hibernate,3}} = erlang:process_info(Pid,current_function),
-
- ?line receive after 1000 -> ok end,
- ?line {current_function,{erlang,hibernate,3}} =
- erlang:process_info(Pid,current_function),
- ?line good_morning = gen_fsm:sync_send_all_state_event(Pid,wakeup_sync),
- ?line receive after 1000 -> ok end,
- ?line true = ({current_function,{erlang,hibernate,3}} =/= erlang:process_info(Pid,current_function)),
- ?line stop_it(Pid),
+ {ok, Pid} = gen_fsm:start_link(?MODULE, hiber, []),
+ true = ({current_function,{erlang,hibernate,3}} =/=
+ erlang:process_info(Pid,current_function)),
+ hibernating = gen_fsm:sync_send_event(Pid, hibernate_sync),
+ is_in_erlang_hibernate(Pid),
+ good_morning = gen_fsm:sync_send_event(Pid, wakeup_sync),
+ is_not_in_erlang_hibernate(Pid),
+ hibernating = gen_fsm:sync_send_event(Pid, hibernate_sync),
+ is_in_erlang_hibernate(Pid),
+ five_more = gen_fsm:sync_send_event(Pid, snooze_sync),
+ is_in_erlang_hibernate(Pid),
+ good_morning = gen_fsm:sync_send_event(Pid, wakeup_sync),
+ is_not_in_erlang_hibernate(Pid),
+ ok = gen_fsm:send_event(Pid, hibernate_async),
+ is_in_erlang_hibernate(Pid),
+ ok = gen_fsm:send_event(Pid, wakeup_async),
+ is_not_in_erlang_hibernate(Pid),
+ ok = gen_fsm:send_event(Pid, hibernate_async),
+ is_in_erlang_hibernate(Pid),
+ ok = gen_fsm:send_event(Pid, snooze_async),
+ is_in_erlang_hibernate(Pid),
+ ok = gen_fsm:send_event(Pid, wakeup_async),
+ is_not_in_erlang_hibernate(Pid),
+
+ Pid ! hibernate_later,
+ true = ({current_function,{erlang,hibernate,3}} =/=
+ erlang:process_info(Pid, current_function)),
+ is_in_erlang_hibernate(Pid),
+
+ 'alive!' = gen_fsm:sync_send_event(Pid,'alive?'),
+ true = ({current_function,{erlang,hibernate,3}} =/=
+ erlang:process_info(Pid, current_function)),
+ Pid ! hibernate_now,
+ is_in_erlang_hibernate(Pid),
+
+ 'alive!' = gen_fsm:sync_send_event(Pid,'alive?'),
+ true = ({current_function,{erlang,hibernate,3}} =/=
+ erlang:process_info(Pid, current_function)),
+
+ hibernating = gen_fsm:sync_send_all_state_event(Pid, hibernate_sync),
+ is_in_erlang_hibernate(Pid),
+ good_morning = gen_fsm:sync_send_all_state_event(Pid, wakeup_sync),
+ is_not_in_erlang_hibernate(Pid),
+ hibernating = gen_fsm:sync_send_all_state_event(Pid, hibernate_sync),
+ is_in_erlang_hibernate(Pid),
+ five_more = gen_fsm:sync_send_all_state_event(Pid, snooze_sync),
+ is_in_erlang_hibernate(Pid),
+ good_morning = gen_fsm:sync_send_all_state_event(Pid, wakeup_sync),
+ is_not_in_erlang_hibernate(Pid),
+ ok = gen_fsm:send_all_state_event(Pid, hibernate_async),
+ is_in_erlang_hibernate(Pid),
+ ok = gen_fsm:send_all_state_event(Pid, wakeup_async),
+ is_not_in_erlang_hibernate(Pid),
+ ok = gen_fsm:send_all_state_event(Pid, hibernate_async),
+ is_in_erlang_hibernate(Pid),
+ ok = gen_fsm:send_all_state_event(Pid, snooze_async),
+ is_in_erlang_hibernate(Pid),
+ ok = gen_fsm:send_all_state_event(Pid, wakeup_async),
+ is_not_in_erlang_hibernate(Pid),
+
+ hibernating = gen_fsm:sync_send_all_state_event(Pid, hibernate_sync),
+ is_in_erlang_hibernate(Pid),
+ sys:suspend(Pid),
+ is_in_erlang_hibernate(Pid),
+ sys:resume(Pid),
+ is_in_erlang_hibernate(Pid),
+ receive after 1000 -> ok end,
+ is_in_erlang_hibernate(Pid),
+
+ good_morning = gen_fsm:sync_send_all_state_event(Pid, wakeup_sync),
+ is_not_in_erlang_hibernate(Pid),
+ stop_it(Pid),
test_server:messages_get(),
process_flag(trap_exit, OldFl),
ok.
+is_in_erlang_hibernate(Pid) ->
+ receive after 1 -> ok end,
+ is_in_erlang_hibernate_1(200, Pid).
+
+is_in_erlang_hibernate_1(0, Pid) ->
+ io:format("~p\n", [erlang:process_info(Pid, current_function)]),
+ ?t:fail(not_in_erlang_hibernate_3);
+is_in_erlang_hibernate_1(N, Pid) ->
+ {current_function,MFA} = erlang:process_info(Pid, current_function),
+ case MFA of
+ {erlang,hibernate,3} ->
+ ok;
+ _ ->
+ receive after 10 -> ok end,
+ is_in_erlang_hibernate_1(N-1, Pid)
+ end.
+is_not_in_erlang_hibernate(Pid) ->
+ receive after 1 -> ok end,
+ is_not_in_erlang_hibernate_1(200, Pid).
+
+is_not_in_erlang_hibernate_1(0, Pid) ->
+ io:format("~p\n", [erlang:process_info(Pid, current_function)]),
+ ?t:fail(not_in_erlang_hibernate_3);
+is_not_in_erlang_hibernate_1(N, Pid) ->
+ {current_function,MFA} = erlang:process_info(Pid, current_function),
+ case MFA of
+ {erlang,hibernate,3} ->
+ receive after 10 -> ok end,
+ is_not_in_erlang_hibernate_1(N-1, Pid);
+ _ ->
+ ok
+ end.
%%sys1(suite) -> [];
%%sys1(_) ->
diff --git a/lib/stdlib/test/gen_server_SUITE.erl b/lib/stdlib/test/gen_server_SUITE.erl
index 0f03fda30a..66341f495f 100644
--- a/lib/stdlib/test/gen_server_SUITE.erl
+++ b/lib/stdlib/test/gen_server_SUITE.erl
@@ -36,6 +36,9 @@
get_state/1, replace_state/1, call_with_huge_message_queue/1
]).
+-export([stop1/1, stop2/1, stop3/1, stop4/1, stop5/1, stop6/1, stop7/1,
+ stop8/1, stop9/1, stop10/1]).
+
% spawn export
-export([spec_init_local/2, spec_init_global/2, spec_init_via/2,
spec_init_default_timeout/2, spec_init_global_default_timeout/2,
@@ -51,7 +54,7 @@
suite() -> [{ct_hooks,[ts_install_cth]}].
all() ->
- [start, crash, call, cast, cast_fast, info, abcast,
+ [start, {group,stop}, crash, call, cast, cast_fast, info, abcast,
multicall, multicall_down, call_remote1, call_remote2,
call_remote3, call_remote_n1, call_remote_n2,
call_remote_n3, spec_init,
@@ -63,7 +66,8 @@ all() ->
call_with_huge_message_queue].
groups() ->
- [].
+ [{stop, [],
+ [stop1, stop2, stop3, stop4, stop5, stop6, stop7, stop8, stop9, stop10]}].
init_per_suite(Config) ->
Config.
@@ -237,6 +241,105 @@ start(Config) when is_list(Config) ->
process_flag(trap_exit, OldFl),
ok.
+%% Anonymous, reason 'normal'
+stop1(_Config) ->
+ {ok, Pid} = gen_server:start(?MODULE, [], []),
+ ok = gen_server:stop(Pid),
+ false = erlang:is_process_alive(Pid),
+ {'EXIT',noproc} = (catch gen_server:stop(Pid)),
+ ok.
+
+%% Anonymous, other reason
+stop2(_Config) ->
+ {ok,Pid} = gen_server:start(?MODULE, [], []),
+ ok = gen_server:stop(Pid, other_reason, infinity),
+ false = erlang:is_process_alive(Pid),
+ ok.
+
+%% Anonymous, invalid timeout
+stop3(_Config) ->
+ {ok,Pid} = gen_server:start(?MODULE, [], []),
+ {'EXIT',_} = (catch gen_server:stop(Pid, other_reason, invalid_timeout)),
+ true = erlang:is_process_alive(Pid),
+ ok = gen_server:stop(Pid),
+ false = erlang:is_process_alive(Pid),
+ ok.
+
+%% Registered name
+stop4(_Config) ->
+ {ok,Pid} = gen_server:start({local,to_stop},?MODULE, [], []),
+ ok = gen_server:stop(to_stop),
+ false = erlang:is_process_alive(Pid),
+ {'EXIT',noproc} = (catch gen_server:stop(to_stop)),
+ ok.
+
+%% Registered name and local node
+stop5(_Config) ->
+ {ok,Pid} = gen_server:start({local,to_stop},?MODULE, [], []),
+ ok = gen_server:stop({to_stop,node()}),
+ false = erlang:is_process_alive(Pid),
+ {'EXIT',noproc} = (catch gen_server:stop({to_stop,node()})),
+ ok.
+
+%% Globally registered name
+stop6(_Config) ->
+ {ok, Pid} = gen_server:start({global, to_stop}, ?MODULE, [], []),
+ ok = gen_server:stop({global,to_stop}),
+ false = erlang:is_process_alive(Pid),
+ {'EXIT',noproc} = (catch gen_server:stop({global,to_stop})),
+ ok.
+
+%% 'via' registered name
+stop7(_Config) ->
+ dummy_via:reset(),
+ {ok, Pid} = gen_server:start({via, dummy_via, to_stop},
+ ?MODULE, [], []),
+ ok = gen_server:stop({via, dummy_via, to_stop}),
+ false = erlang:is_process_alive(Pid),
+ {'EXIT',noproc} = (catch gen_server:stop({via, dummy_via, to_stop})),
+ ok.
+
+%% Anonymous on remote node
+stop8(_Config) ->
+ {ok,Node} = test_server:start_node(gen_server_SUITE_stop8,slave,[]),
+ Dir = filename:dirname(code:which(?MODULE)),
+ rpc:call(Node,code,add_path,[Dir]),
+ {ok, Pid} = rpc:call(Node,gen_server,start,[?MODULE,[],[]]),
+ ok = gen_server:stop(Pid),
+ false = rpc:call(Node,erlang,is_process_alive,[Pid]),
+ {'EXIT',noproc} = (catch gen_server:stop(Pid)),
+ true = test_server:stop_node(Node),
+ {'EXIT',{{nodedown,Node},_}} = (catch gen_server:stop(Pid)),
+ ok.
+
+%% Registered name on remote node
+stop9(_Config) ->
+ {ok,Node} = test_server:start_node(gen_server_SUITE_stop9,slave,[]),
+ Dir = filename:dirname(code:which(?MODULE)),
+ rpc:call(Node,code,add_path,[Dir]),
+ {ok, Pid} = rpc:call(Node,gen_server,start,[{local,to_stop},?MODULE,[],[]]),
+ ok = gen_server:stop({to_stop,Node}),
+ undefined = rpc:call(Node,erlang,whereis,[to_stop]),
+ false = rpc:call(Node,erlang,is_process_alive,[Pid]),
+ {'EXIT',noproc} = (catch gen_server:stop({to_stop,Node})),
+ true = test_server:stop_node(Node),
+ {'EXIT',{{nodedown,Node},_}} = (catch gen_server:stop({to_stop,Node})),
+ ok.
+
+%% Globally registered name on remote node
+stop10(_Config) ->
+ {ok,Node} = test_server:start_node(gen_server_SUITE_stop10,slave,[]),
+ Dir = filename:dirname(code:which(?MODULE)),
+ rpc:call(Node,code,add_path,[Dir]),
+ {ok, Pid} = rpc:call(Node,gen_server,start,[{global,to_stop},?MODULE,[],[]]),
+ global:sync(),
+ ok = gen_server:stop({global,to_stop}),
+ false = rpc:call(Node,erlang,is_process_alive,[Pid]),
+ {'EXIT',noproc} = (catch gen_server:stop({global,to_stop})),
+ true = test_server:stop_node(Node),
+ {'EXIT',noproc} = (catch gen_server:stop({global,to_stop})),
+ ok.
+
crash(Config) when is_list(Config) ->
?line error_logger_forwarder:register(),
@@ -538,15 +641,13 @@ info(Config) when is_list(Config) ->
end,
ok.
-hibernate(suite) -> [];
hibernate(Config) when is_list(Config) ->
OldFl = process_flag(trap_exit, true),
- ?line {ok, Pid0} =
+ {ok, Pid0} =
gen_server:start_link({local, my_test_name_hibernate0},
- gen_server_SUITE, hibernate, []),
- ?line receive after 1000 -> ok end,
- ?line {current_function,{erlang,hibernate,3}} = erlang:process_info(Pid0,current_function),
- ?line ok = gen_server:call(my_test_name_hibernate0, stop),
+ gen_server_SUITE, hibernate, []),
+ is_in_erlang_hibernate(Pid0),
+ ok = gen_server:call(my_test_name_hibernate0, stop),
receive
{'EXIT', Pid0, stopped} ->
ok
@@ -554,70 +655,66 @@ hibernate(Config) when is_list(Config) ->
test_server:fail(gen_server_did_not_die)
end,
- ?line {ok, Pid} =
+ {ok, Pid} =
gen_server:start_link({local, my_test_name_hibernate},
- gen_server_SUITE, [], []),
+ gen_server_SUITE, [], []),
- ?line ok = gen_server:call(my_test_name_hibernate, started_p),
- ?line true = gen_server:call(my_test_name_hibernate, hibernate),
- ?line receive after 1000 -> ok end,
- ?line {current_function,{erlang,hibernate,3}} = erlang:process_info(Pid,current_function),
- ?line Parent = self(),
+ ok = gen_server:call(my_test_name_hibernate, started_p),
+ true = gen_server:call(my_test_name_hibernate, hibernate),
+ is_in_erlang_hibernate(Pid),
+ Parent = self(),
Fun = fun() ->
- receive
- go ->
- ok
- end,
- receive
- after 1000 ->
- ok
- end,
- X = erlang:process_info(Pid,current_function),
+ receive go -> ok end,
+ receive after 1000 -> ok end,
+ X = erlang:process_info(Pid, current_function),
Pid ! continue,
Parent ! {result,X}
end,
- ?line Pid2 = spawn_link(Fun),
- ?line true = gen_server:call(my_test_name_hibernate, {hibernate_noreply,Pid2}),
-
- ?line gen_server:cast(my_test_name_hibernate, hibernate_later),
- ?line true = ({current_function,{erlang,hibernate,3}} =/= erlang:process_info(Pid,current_function)),
- ?line receive after 2000 -> ok end,
- ?line ({current_function,{erlang,hibernate,3}} = erlang:process_info(Pid,current_function)),
- ?line ok = gen_server:call(my_test_name_hibernate, started_p),
- ?line true = ({current_function,{erlang,hibernate,3}} =/= erlang:process_info(Pid,current_function)),
- ?line gen_server:cast(my_test_name_hibernate, hibernate_now),
- ?line receive after 1000 -> ok end,
- ?line ({current_function,{erlang,hibernate,3}} = erlang:process_info(Pid,current_function)),
- ?line ok = gen_server:call(my_test_name_hibernate, started_p),
- ?line true = ({current_function,{erlang,hibernate,3}} =/= erlang:process_info(Pid,current_function)),
- ?line Pid ! hibernate_later,
- ?line true = ({current_function,{erlang,hibernate,3}} =/= erlang:process_info(Pid,current_function)),
- ?line receive after 2000 -> ok end,
- ?line ({current_function,{erlang,hibernate,3}} = erlang:process_info(Pid,current_function)),
- ?line ok = gen_server:call(my_test_name_hibernate, started_p),
- ?line true = ({current_function,{erlang,hibernate,3}} =/= erlang:process_info(Pid,current_function)),
- ?line Pid ! hibernate_now,
- ?line receive after 1000 -> ok end,
- ?line ({current_function,{erlang,hibernate,3}} = erlang:process_info(Pid,current_function)),
- ?line ok = gen_server:call(my_test_name_hibernate, started_p),
- ?line true = ({current_function,{erlang,hibernate,3}} =/= erlang:process_info(Pid,current_function)),
- ?line receive
- {result,R} ->
- ?line {current_function,{erlang,hibernate,3}} = R
- end,
- ?line true = gen_server:call(my_test_name_hibernate, hibernate),
- ?line receive after 1000 -> ok end,
- ?line {current_function,{erlang,hibernate,3}} = erlang:process_info(Pid,current_function),
- ?line sys:suspend(my_test_name_hibernate),
- ?line receive after 1000 -> ok end,
- ?line {current_function,{erlang,hibernate,3}} = erlang:process_info(Pid,current_function),
- ?line sys:resume(my_test_name_hibernate),
- ?line receive after 1000 -> ok end,
- ?line {current_function,{erlang,hibernate,3}} = erlang:process_info(Pid,current_function),
- ?line ok = gen_server:call(my_test_name_hibernate, started_p),
- ?line true = ({current_function,{erlang,hibernate,3}} =/= erlang:process_info(Pid,current_function)),
-
- ?line ok = gen_server:call(my_test_name_hibernate, stop),
+ Pid2 = spawn_link(Fun),
+ true = gen_server:call(my_test_name_hibernate, {hibernate_noreply,Pid2}),
+
+ gen_server:cast(my_test_name_hibernate, hibernate_later),
+ true = ({current_function,{erlang,hibernate,3}} =/=
+ erlang:process_info(Pid, current_function)),
+ is_in_erlang_hibernate(Pid),
+ ok = gen_server:call(my_test_name_hibernate, started_p),
+ true = ({current_function,{erlang,hibernate,3}} =/=
+ erlang:process_info(Pid, current_function)),
+
+ gen_server:cast(my_test_name_hibernate, hibernate_now),
+ is_in_erlang_hibernate(Pid),
+ ok = gen_server:call(my_test_name_hibernate, started_p),
+ true = ({current_function,{erlang,hibernate,3}} =/=
+ erlang:process_info(Pid, current_function)),
+
+ Pid ! hibernate_later,
+ true = ({current_function,{erlang,hibernate,3}} =/=
+ erlang:process_info(Pid, current_function)),
+ is_in_erlang_hibernate(Pid),
+ ok = gen_server:call(my_test_name_hibernate, started_p),
+ true = ({current_function,{erlang,hibernate,3}} =/=
+ erlang:process_info(Pid, current_function)),
+
+ Pid ! hibernate_now,
+ is_in_erlang_hibernate(Pid),
+ ok = gen_server:call(my_test_name_hibernate, started_p),
+ true = ({current_function,{erlang,hibernate,3}} =/=
+ erlang:process_info(Pid, current_function)),
+ receive
+ {result,R} ->
+ {current_function,{erlang,hibernate,3}} = R
+ end,
+
+ true = gen_server:call(my_test_name_hibernate, hibernate),
+ is_in_erlang_hibernate(Pid),
+ sys:suspend(my_test_name_hibernate),
+ is_in_erlang_hibernate(Pid),
+ sys:resume(my_test_name_hibernate),
+ is_in_erlang_hibernate(Pid),
+ ok = gen_server:call(my_test_name_hibernate, started_p),
+ true = ({current_function,{erlang,hibernate,3}} =/= erlang:process_info(Pid,current_function)),
+
+ ok = gen_server:call(my_test_name_hibernate, stop),
receive
{'EXIT', Pid, stopped} ->
ok
@@ -627,6 +724,23 @@ hibernate(Config) when is_list(Config) ->
process_flag(trap_exit, OldFl),
ok.
+is_in_erlang_hibernate(Pid) ->
+ receive after 1 -> ok end,
+ is_in_erlang_hibernate_1(200, Pid).
+
+is_in_erlang_hibernate_1(0, Pid) ->
+ io:format("~p\n", [erlang:process_info(Pid, current_function)]),
+ ?t:fail(not_in_erlang_hibernate_3);
+is_in_erlang_hibernate_1(N, Pid) ->
+ {current_function,MFA} = erlang:process_info(Pid, current_function),
+ case MFA of
+ {erlang,hibernate,3} ->
+ ok;
+ _ ->
+ receive after 10 -> ok end,
+ is_in_erlang_hibernate_1(N-1, Pid)
+ end.
+
%% --------------------------------------
%% Test gen_server:abcast and handle_cast.
%% Test all different return values from
diff --git a/lib/stdlib/test/io_SUITE.erl b/lib/stdlib/test/io_SUITE.erl
index 2203dd8f51..8d53949c40 100644
--- a/lib/stdlib/test/io_SUITE.erl
+++ b/lib/stdlib/test/io_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
@@ -31,7 +31,7 @@
printable_range/1,
io_lib_print_binary_depth_one/1, otp_10302/1, otp_10755/1,
otp_10836/1, io_lib_width_too_small/1,
- io_with_huge_message_queue/1]).
+ io_with_huge_message_queue/1, format_string/1]).
-export([pretty/2]).
@@ -71,7 +71,8 @@ all() ->
io_fread_newlines, otp_8989, io_lib_fread_literal,
printable_range,
io_lib_print_binary_depth_one, otp_10302, otp_10755, otp_10836,
- io_lib_width_too_small, io_with_huge_message_queue].
+ io_lib_width_too_small, io_with_huge_message_queue,
+ format_string].
groups() ->
[].
@@ -1035,7 +1036,14 @@ rp(Term, Col, Ll, D, M, RF) ->
lists:flatten(io_lib:format("~s", [R])).
fmt(Fmt, Args) ->
- lists:flatten(io_lib:format(Fmt, Args)).
+ FormatList = io_lib:scan_format(Fmt, Args),
+ {Fmt2, Args2} = io_lib:unscan_format(FormatList),
+ Chars1 = lists:flatten(io_lib:build_text(FormatList)),
+ Chars2 = lists:flatten(io_lib:format(Fmt2, Args2)),
+ Chars3 = lists:flatten(io_lib:format(Fmt, Args)),
+ Chars1 = Chars2,
+ Chars2 = Chars3,
+ Chars3.
rfd(a, 0) ->
[];
@@ -2261,3 +2269,9 @@ writes(0, _) -> ok;
writes(N, F1) ->
file:write(F1, "hello\n"),
writes(N - 1, F1).
+
+format_string(Config) ->
+ %% All but padding is tested by fmt/2.
+ "xxxxxxsssx" = fmt("~10.4.xs", ["sss"]),
+ "xxxxxxsssx" = fmt("~10.4.*s", [$x, "sss"]),
+ ok.
diff --git a/lib/stdlib/test/io_proto_SUITE.erl b/lib/stdlib/test/io_proto_SUITE.erl
index 76a8109a8d..78432789cd 100644
--- a/lib/stdlib/test/io_proto_SUITE.erl
+++ b/lib/stdlib/test/io_proto_SUITE.erl
@@ -69,12 +69,7 @@
init_per_testcase(_Case, Config) ->
?line Dog = ?t:timetrap(?default_timeout),
- Term = case os:getenv("TERM") of
- List when is_list(List) ->
- List;
- _ ->
- "dumb"
- end,
+ Term = os:getenv("TERM", "dumb"),
os:putenv("TERM","vt100"),
[{watchdog, Dog}, {term, Term} | Config].
end_per_testcase(_Case, Config) ->
@@ -481,149 +476,182 @@ unicode_options(Config) when is_list(Config) ->
ok.
-unicode_options_gen(suite) ->
- [];
-unicode_options_gen(doc) ->
- ["Tests various unicode options on random generated files"];
+%% Tests various unicode options on random generated files.
unicode_options_gen(Config) when is_list(Config) ->
- ?line random:seed(1240,900586,553728),
- ?line PrivDir = ?config(priv_dir,Config),
- ?line AllModes = [utf8,utf16,{utf16,big},{utf16,little},utf32,{utf32,big},{utf32,little}],
- ?line FSize = 17*1024,
- ?line NumItersRead = 2,
- ?line NumItersWrite = 2,
- ?line Dir = filename:join([PrivDir,"GENDATA1"]),
- ?line file:make_dir(Dir),
-
- %dbg:tracer(process,{fun(A,_) -> erlang:display(A) end,true}),
- %dbg:tpl(file_io_server,x),
- %dbg:ctpl(file_io_server,cafu),
- %dbg:tp(unicode,x),
-
- DoOneFile1 = fun(Encoding,N,M) ->
- ?dbg({Encoding,M,N}),
- io:format("Read test: Encoding ~p, Chunk size ~p, Iteration ~p~n",[Encoding,M,N]),
- io:format(standard_error,"Read test: Encoding ~p, Chunk size ~p, Iteration ~p\r\n",[Encoding,M,N]),
- ?line Fname = filename:join([Dir,"genfile_"++enc2str(Encoding)++"_"++integer_to_list(N)]),
- ?dbg(?LINE),
- ?line Ulist = random_unicode(FSize),
- ?dbg(?LINE),
- ?line my_write_file(Fname,Ulist,Encoding),
- ?dbg(?LINE),
- ?line {ok,F1} = file:open(Fname,[read,{encoding,Encoding}]),
-
- ?dbg(?LINE),
- ?line Res1 = read_whole_file(fun(FD) -> io:get_line(FD,'') end,F1),
- ?dbg(?LINE),
- ?line Ulist = unicode:characters_to_list(Res1,unicode),
- ?dbg(?LINE),
- ?line file:close(F1),
- ?line {ok,F2} = file:open(Fname, [read,binary,{encoding,Encoding}]),
- ?line Res2 = read_whole_file(fun(FD) -> io:get_chars(FD,'',M) end,F2),
- ?line Ulist = unicode:characters_to_list(Res2,unicode),
- ?dbg(?LINE),
- ?line file:close(F2),
- ?line {ok,F3} = file:open(Fname, [read,binary,{encoding,Encoding}]),
- ?dbg(?LINE),
-%% case {Encoding,M,N} of
-%% {{utf16,little},10,2} ->
-%% dbg:p(F3,call);
-%% _ ->
-%% ok
-%% end,
-
- ?line Res3 = read_whole_file(fun(FD) -> case io:fread(FD,'',"~ts") of {ok,D} -> D; O -> O end end, F3),
- ?dbg(?LINE),
- ?line Ulist2 = [ X || X <- Ulist,
- X =/= $\n, X =/= $ ],
- ?dbg(?LINE),
- ?line Ulist2 = unicode:characters_to_list(Res3,unicode),
- ?dbg(?LINE),
- ?line file:close(F3),
- ?line {ok,F4} = file:open(Fname, [read,{encoding,Encoding}]),
- ?line Res4 = read_whole_file(fun(FD) -> case io:fread(FD,'',"~tc") of {ok,D} -> D; O -> O end end,F4),
- ?line Ulist3 = [ X || X <- Ulist,
- X =/= $\n ],
- ?line Ulist3 = unicode:characters_to_list(Res4,unicode),
- ?dbg(?LINE),
- ?line file:close(F4),
- ?line file:delete(Fname)
- end,
-
- [ [ [ DoOneFile1(E,N,M) || E <- AllModes ] || M <- [10,1000,128,1024,8192,8193] ] || N <- lists:seq(1,NumItersRead)],
- DoOneFile2 = fun(Encoding,N,M) ->
- ?dbg({Encoding,M,N}),
- io:format("Write test: Encoding ~p, Chunk size ~p, Iteration ~p~n",[Encoding,M,N]),
- io:format(standard_error,"Write test: Encoding ~p, Chunk size ~p, Iteration ~p\r\n",[Encoding,M,N]),
- ?line Fname = filename:join([Dir,"genfile_"++enc2str(Encoding)++"_"++integer_to_list(N)]),
- ?dbg(?LINE),
- ?line Ulist = random_unicode(FSize),
- ?dbg(?LINE),
- ?line {ok,F1} = file:open(Fname,[write,{encoding,Encoding}]),
- ?line io:put_chars(F1,Ulist),
- ?line file:close(F1),
- ?line Ulist = my_read_file(Fname,Encoding),
- ?line file:delete(Fname),
- ?line {ok,F2} = file:open(Fname,[write,binary,{encoding,Encoding}]),
- ?line io:put_chars(F2,Ulist),
- ?line file:close(F2),
- ?line Ulist = my_read_file(Fname,Encoding),
- ?line file:delete(Fname),
- ?line {ok,F3} = file:open(Fname,[write,{encoding,Encoding}]),
- ?line LL = string:tokens(Ulist,"\n"),
- ?line Ulist2 = lists:flatten(LL),
- ?line [ io:format(F3,"~ts",[L]) || L <- LL ],
- ?line file:close(F3),
- ?line Ulist2 = my_read_file(Fname,Encoding),
- ?line file:delete(Fname),
- ?line {ok,F4} = file:open(Fname,[write,{encoding,Encoding}]),
- ?line [ io:format(F4,"~tc",[C]) || C <- Ulist ],
- ?line file:close(F4),
- ?line Ulist = my_read_file(Fname,Encoding),
- ?line file:delete(Fname),
- ?line {ok,F5} = file:open(Fname,[write,{encoding,Encoding}]),
- ?line io:put_chars(F5,unicode:characters_to_binary(Ulist)),
- ?line file:close(F5),
- ?line Ulist = my_read_file(Fname,Encoding),
- ?line file:delete(Fname),
- ok
- end,
- [ [ [ DoOneFile2(E,N,M) || E <- AllModes ] || M <- [10,1000,128,1024,8192,8193] ] || N <- lists:seq(1,NumItersWrite)],
+ random:seed(1240, 900586, 553728),
+ PrivDir = ?config(priv_dir, Config),
+ AllModes = [utf8,utf16,{utf16,big},{utf16,little},
+ utf32,{utf32,big},{utf32,little}],
+ FSize = 9*1024,
+ NumItersRead = 2,
+ NumItersWrite = 2,
+ Dir = filename:join(PrivDir, "GENDATA1"),
+ file:make_dir(Dir),
+
+ DoOneFile1 =
+ fun(Encoding, N, M) ->
+ ?dbg({Encoding,M,N}),
+ io:format("Read test: Encoding ~p, Chunk size ~p, Iteration ~p~n",[Encoding,M,N]),
+ io:format(standard_error,
+ "Read test: Encoding ~p, Chunk size ~p, Iteration ~p\r\n",[Encoding,M,N]),
+ Fname = filename:join(Dir,
+ "genfile_"++enc2str(Encoding)++
+ "_"++integer_to_list(N)),
+ Ulist = random_unicode(FSize),
+ Bin = unicode:characters_to_binary(Ulist, utf8, Encoding),
+ ok = file:write_file(Fname, Bin),
+
+ Read1 = fun(FD) -> io:get_line(FD, '') end,
+ Res1 = read_whole_file(Fname,
+ [read,read_ahead,{encoding,Encoding}],
+ Read1),
+
+ Read2 = fun(FD) -> io:get_chars(FD, '', M) end,
+ Res2 = read_whole_file(Fname,
+ [read,binary,
+ read_ahead,{encoding,Encoding}],
+ Read2),
+
+ Read3 = fun(FD) ->
+ case io:fread(FD, '', "~ts") of
+ {ok,D} -> D;
+ Other -> Other end
+ end,
+ Res3 = read_whole_file(Fname,
+ [read,binary,
+ read_ahead,{encoding,Encoding}],
+ Read3),
+
+ Read4 = fun(FD) ->
+ case io:fread(FD, '', "~ts") of
+ {ok,D} -> D;
+ Other -> Other end
+ end,
+ Res4 = read_whole_file(Fname,
+ [read,read_ahead,{encoding,Encoding}],
+ Read4),
+
+ Ulist2 = [X || X <- Ulist, X =/= $\n, X =/= $\s],
+ Ulist3 = [X || X <- Ulist, X =/= $\n],
+ Ulist = done(Res1),
+ Ulist = done(Res2),
+ Ulist2 = done(Res3),
+ Ulist3 = done(Res4),
+
+ file:delete(Fname)
+ end,
+ [ [ [ DoOneFile1(E, N, M) || E <- AllModes ] ||
+ M <- [10,1000,128,1024,8192,8193] ] ||
+ N <- lists:seq(1, NumItersRead) ],
+
+ DoOneFile2 =
+ fun(Encoding,N,M) ->
+ ?dbg({Encoding,M,N}),
+ io:format("Write test: Encoding ~p, Chunk size ~p, Iteration ~p~n",[Encoding,M,N]),
+ io:format(standard_error,
+ "Write test: Encoding ~p, Chunk size ~p, Iteration ~p\r\n",[Encoding,M,N]),
+ Fname = filename:join(Dir,
+ "genfile_"++enc2str(Encoding)++
+ "_"++integer_to_list(N)),
+ Ulist = random_unicode(FSize),
+
+ Res1 = write_read_file(Fname, 1,
+ [write],
+ Encoding,
+ fun(FD) -> io:put_chars(FD, Ulist) end),
+
+ Res2 = write_read_file(Fname, 2,
+ [write,binary],
+ Encoding,
+ fun(FD) -> io:put_chars(FD, Ulist) end),
+
+ Fun3 = fun(FD) ->
+ _ = [io:format(FD, "~tc", [C]) || C <- Ulist],
+ ok
+ end,
+ Res3 = write_read_file(Fname, 3,
+ [write],
+ Encoding,
+ Fun3),
+
+ Fun4 = fun(FD) ->
+ io:put_chars(FD,
+ unicode:characters_to_binary(Ulist))
+ end,
+ Res4 = write_read_file(Fname, 4,
+ [write],
+ Encoding,
+ Fun4),
+
+ LL = string:tokens(Ulist, "\n"),
+ Fun5 = fun(FD) ->
+ _ = [io:format(FD, "~ts", [L]) || L <- LL],
+ ok
+ end,
+ Res5 = write_read_file(Fname, 5,
+ [write],
+ Encoding,
+ Fun5),
+
+ Ulist2 = lists:flatten(LL),
+ ResBin = done(Res1),
+ ResBin = done(Res2),
+ ResBin = done(Res3),
+ ResBin = done(Res4),
+ Ulist = unicode:characters_to_list(ResBin, Encoding),
+
+ ResBin2 = done(Res5),
+ Ulist2 = unicode:characters_to_list(ResBin2, Encoding),
+
+ ok
+ end,
+ [ [ [ DoOneFile2(E, N, M) || E <- AllModes ] ||
+ M <- [10,1000,128,1024,8192,8193] ] ||
+ N <- lists:seq(1, NumItersWrite) ],
ok.
+read_whole_file(Fname, Options, Fun) ->
+ do(fun() ->
+ do_read_whole_file(Fname, Options, Fun)
+ end).
+do_read_whole_file(Fname, Options, Fun) ->
+ {ok,F} = file:open(Fname, Options),
+ Res = do_read_whole_file_1(Fun, F),
+ ok = file:close(F),
+ unicode:characters_to_list(Res, unicode).
-
-read_whole_file(Fun,F) ->
+do_read_whole_file_1(Fun, F) ->
case Fun(F) of
eof ->
[];
{error,Error} ->
- ?dbg(Error),
receive after 10000 -> ok end,
exit(Error);
Other ->
- %?dbg(Other),
- [Other | read_whole_file(Fun,F)]
+ [Other|do_read_whole_file_1(Fun, F)]
end.
-
+write_read_file(Fname0, N, Options, Enc, Writer) ->
+ Fname = Fname0 ++ "_" ++ integer_to_list(N),
+ do(fun() ->
+ do_write_read_file(Fname, Options, Enc, Writer)
+ end).
+
+do_write_read_file(Fname, Options, Encoding, Writer) ->
+ {ok,F} = file:open(Fname, [{encoding,Encoding}|Options]),
+ Writer(F),
+ ok = file:close(F),
+ {ok,Bin} = file:read_file(Fname),
+ ok = file:delete(Fname),
+ Bin.
+
enc2str(Atom) when is_atom(Atom) ->
atom_to_list(Atom);
enc2str({A1,A2}) when is_atom(A1), is_atom(A2) ->
atom_to_list(A1)++"_"++atom_to_list(A2).
-
-
-my_write_file(Filename,UniList,Encoding) ->
- Bin = unicode:characters_to_binary(UniList,utf8,Encoding),
- file:write_file(Filename,Bin).
-
-my_read_file(Filename,Encoding) ->
- {ok,Bin} = file:read_file(Filename),
- unicode:characters_to_list(Bin,Encoding).
-
random_unicode(0) ->
[];
random_unicode(N) ->
@@ -1738,8 +1766,7 @@ toerl_loop(Port,Acc) ->
end.
millistamp() ->
- {Mega, Secs, Micros} = erlang:now(),
- (Micros div 1000) + Secs * 1000 + Mega * 1000000000.
+ erlang:monotonic_time(milli_seconds).
get_data_within(Port, X, Acc) when X =< 0 ->
?dbg({get_data_within, X, Acc, ?LINE}),
@@ -1937,3 +1964,15 @@ chomp(<<Ch,Rest/binary>>) ->
<<Ch,X/binary>>;
chomp(Atom) ->
Atom.
+
+do(Fun) ->
+ {_,Ref} = spawn_monitor(fun() ->
+ exit(Fun())
+ end),
+ Ref.
+
+done(Ref) ->
+ receive
+ {'DOWN',Ref,process,_,Result} ->
+ Result
+ end.
diff --git a/lib/stdlib/test/lists_SUITE.erl b/lib/stdlib/test/lists_SUITE.erl
index f4589a8e24..01c138d94c 100644
--- a/lib/stdlib/test/lists_SUITE.erl
+++ b/lib/stdlib/test/lists_SUITE.erl
@@ -1704,7 +1704,7 @@ fun_pid(Fun) ->
get_seed() ->
case random:seed() of
undefined ->
- now();
+ erlang:timestamp();
Tuple ->
Tuple
end.
diff --git a/lib/stdlib/test/maps_SUITE.erl b/lib/stdlib/test/maps_SUITE.erl
index dda20a615b..f8f241d834 100644
--- a/lib/stdlib/test/maps_SUITE.erl
+++ b/lib/stdlib/test/maps_SUITE.erl
@@ -34,13 +34,23 @@
-export([init_per_testcase/2]).
-export([end_per_testcase/2]).
--export([t_get_3/1,t_with_2/1,t_without_2/1]).
+-export([t_get_3/1, t_filter_2/1,
+ t_fold_3/1,t_map_2/1,t_size_1/1,
+ t_with_2/1,t_without_2/1]).
+
+%-define(badmap(V,F,Args), {'EXIT', {{badmap,V}, [{maps,F,Args,_}|_]}}).
+%-define(badarg(F,Args), {'EXIT', {badarg, [{maps,F,Args,_}|_]}}).
+% silly broken hipe
+-define(badmap(V,F,_Args), {'EXIT', {{badmap,V}, [{maps,F,_,_}|_]}}).
+-define(badarg(F,_Args), {'EXIT', {badarg, [{maps,F,_,_}|_]}}).
suite() ->
[{ct_hooks, [ts_install_cth]}].
all() ->
- [t_get_3,t_with_2,t_without_2].
+ [t_get_3,t_filter_2,
+ t_fold_3,t_map_2,t_size_1,
+ t_with_2,t_without_2].
init_per_suite(Config) ->
Config.
@@ -63,6 +73,9 @@ t_get_3(Config) when is_list(Config) ->
value1 = maps:get(key1, Map, DefaultValue),
value2 = maps:get(key2, Map, DefaultValue),
DefaultValue = maps:get(key3, Map, DefaultValue),
+
+ %% error case
+ ?badmap(a,get,[[a,b],a,def]) = (catch maps:get([a,b],id(a),def)),
ok.
t_without_2(_Config) ->
@@ -70,6 +83,11 @@ t_without_2(_Config) ->
M0 = maps:from_list([{{k,I},{v,I}}||I<-lists:seq(1,100)]),
M1 = maps:from_list([{{k,I},{v,I}}||I<-lists:seq(1,100) -- Ki]),
M1 = maps:without([{k,I}||I <- Ki],M0),
+
+ %% error case
+ ?badmap(a,without,[[a,b],a]) = (catch maps:without([a,b],id(a))),
+ ?badmap(a,without,[{a,b},a]) = (catch maps:without({a,b},id(a))),
+ ?badarg(without,[a,#{}]) = (catch maps:without(a,#{})),
ok.
t_with_2(_Config) ->
@@ -77,4 +95,63 @@ t_with_2(_Config) ->
M0 = maps:from_list([{{k,I},{v,I}}||I<-lists:seq(1,100)]),
M1 = maps:from_list([{{k,I},{v,I}}||I<-Ki]),
M1 = maps:with([{k,I}||I <- Ki],M0),
+
+ %% error case
+ ?badmap(a,with,[[a,b],a]) = (catch maps:with([a,b],id(a))),
+ ?badmap(a,with,[{a,b},a]) = (catch maps:with({a,b},id(a))),
+ ?badarg(with,[a,#{}]) = (catch maps:with(a,#{})),
+ ok.
+
+t_filter_2(Config) when is_list(Config) ->
+ M = #{a => 2, b => 3, c=> 4, "a" => 1, "b" => 2, "c" => 4},
+ Pred1 = fun(K,V) -> is_atom(K) andalso (V rem 2) =:= 0 end,
+ Pred2 = fun(K,V) -> is_list(K) andalso (V rem 2) =:= 0 end,
+ #{a := 2,c := 4} = maps:filter(Pred1,M),
+ #{"b" := 2,"c" := 4} = maps:filter(Pred2,M),
+ %% error case
+ ?badmap(a,filter,[_,a]) = (catch maps:filter(fun(_,_) -> ok end,id(a))),
+ ?badarg(filter,[<<>>,#{}]) = (catch maps:filter(id(<<>>),#{})),
+ ok.
+
+t_fold_3(Config) when is_list(Config) ->
+ Vs = lists:seq(1,200),
+ M0 = maps:from_list([{{k,I},I}||I<-Vs]),
+ #{ {k,1} := 1, {k,200} := 200} = M0,
+ Tot0 = lists:sum(Vs),
+ Tot1 = maps:fold(fun({k,_},V,A) -> A + V end, 0, M0),
+ true = Tot0 =:= Tot1,
+
+ %% error case
+ ?badmap(a,fold,[_,0,a]) = (catch maps:fold(fun(_,_,_) -> ok end,0,id(a))),
+ ?badarg(fold,[<<>>,0,#{}]) = (catch maps:fold(id(<<>>),0,#{})),
ok.
+
+t_map_2(Config) when is_list(Config) ->
+ Vs = lists:seq(1,200),
+ M0 = maps:from_list([{{k,I},I}||I<-Vs]),
+ #{ {k,1} := 1, {k,200} := 200} = M0,
+ M1 = maps:map(fun({k,_},V) -> V + 42 end, M0),
+ #{ {k,1} := 43, {k,200} := 242} = M1,
+
+ %% error case
+ ?badmap(a,map,[_,a]) = (catch maps:map(fun(_,_) -> ok end, id(a))),
+ ?badarg(map,[<<>>,#{}]) = (catch maps:map(id(<<>>),#{})),
+ ok.
+
+
+t_size_1(Config) when is_list(Config) ->
+ 0 = maps:size(#{}),
+ 10 = maps:size(maps:from_list([{{"k",I},I}||I<-lists:seq(1,10)])),
+ 20 = maps:size(maps:from_list([{{"k",I},I}||I<-lists:seq(1,20)])),
+ 30 = maps:size(maps:from_list([{{"k",I},I}||I<-lists:seq(1,30)])),
+ 40 = maps:size(maps:from_list([{{"k",I},I}||I<-lists:seq(1,40)])),
+ 50 = maps:size(maps:from_list([{{"k",I},I}||I<-lists:seq(1,50)])),
+ 60 = maps:size(maps:from_list([{{"k",I},I}||I<-lists:seq(1,60)])),
+ 600 = maps:size(maps:from_list([{{"k",I},I}||I<-lists:seq(1,600)])),
+
+ %% error case
+ ?badmap(a,size,[a]) = (catch maps:size(id(a))),
+ ?badmap(<<>>,size,[<<>>]) = (catch maps:size(id(<<>>))),
+ ok.
+
+id(I) -> I.
diff --git a/lib/stdlib/test/proc_lib_SUITE.erl b/lib/stdlib/test/proc_lib_SUITE.erl
index 8dca69bac4..b6f1973a05 100644
--- a/lib/stdlib/test/proc_lib_SUITE.erl
+++ b/lib/stdlib/test/proc_lib_SUITE.erl
@@ -1,7 +1,7 @@
%%
%% %CopyrightBegin%
%%
-%% Copyright Ericsson AB 1996-2012. 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
@@ -27,7 +27,7 @@
init_per_group/2,end_per_group/2,
crash/1, sync_start_nolink/1, sync_start_link/1,
spawn_opt/1, sp1/0, sp2/0, sp3/1, sp4/2, sp5/1,
- hibernate/1]).
+ hibernate/1, stop/1]).
-export([ otp_6345/1, init_dont_hang/1]).
-export([hib_loop/1, awaken/1]).
@@ -38,6 +38,7 @@
-export([otp_6345_init/1, init_dont_hang_init/1]).
+-export([system_terminate/4]).
-ifdef(STANDALONE).
-define(line, noop, ).
@@ -49,7 +50,7 @@ suite() -> [{ct_hooks,[ts_install_cth]}].
all() ->
[crash, {group, sync_start}, spawn_opt, hibernate,
- {group, tickets}].
+ {group, tickets}, stop].
groups() ->
[{tickets, [], [otp_6345, init_dont_hang]},
@@ -361,10 +362,94 @@ init_dont_hang(Config) when is_list(Config) ->
exit(Error)
end.
-init_dont_hang_init(Parent) ->
+init_dont_hang_init(_Parent) ->
1 = 2.
+%% Test proc_lib:stop/1,3
+stop(_Config) ->
+ Parent = self(),
+ SysMsgProc =
+ fun() ->
+ receive
+ {system,From,Request} ->
+ sys:handle_system_msg(Request,From,Parent,?MODULE,[],[])
+ end
+ end,
+
+ %% Normal case:
+ %% Process handles system message and terminated with given reason
+ Pid1 = proc_lib:spawn(SysMsgProc),
+ ok = proc_lib:stop(Pid1),
+ false = erlang:is_process_alive(Pid1),
+
+ %% Process does not exit
+ {'EXIT',noproc} = (catch proc_lib:stop(Pid1)),
+
+ %% Badly handled system message
+ DieProc =
+ fun() ->
+ receive
+ {system,_From,_Request} ->
+ exit(die)
+ end
+ end,
+ Pid2 = proc_lib:spawn(DieProc),
+ {'EXIT',{die,_}} = (catch proc_lib:stop(Pid2)),
+
+ %% Hanging process => timeout
+ HangProc =
+ fun() ->
+ receive
+ {system,_From,_Request} ->
+ timer:sleep(5000)
+ end
+ end,
+ Pid3 = proc_lib:spawn(HangProc),
+ {'EXIT',timeout} = (catch proc_lib:stop(Pid3,normal,1000)),
+
+ %% Success case with other reason than 'normal'
+ Pid4 = proc_lib:spawn(SysMsgProc),
+ ok = proc_lib:stop(Pid4,other_reason,infinity),
+ false = erlang:is_process_alive(Pid4),
+
+ %% System message is handled, but process dies with other reason
+ %% than the given (in system_terminate/4 below)
+ Pid5 = proc_lib:spawn(SysMsgProc),
+ {'EXIT',{badmatch,2}} = (catch proc_lib:stop(Pid5,crash,infinity)),
+ false = erlang:is_process_alive(Pid5),
+
+ %% Local registered name
+ Pid6 = proc_lib:spawn(SysMsgProc),
+ register(to_stop,Pid6),
+ ok = proc_lib:stop(to_stop),
+ undefined = whereis(to_stop),
+ false = erlang:is_process_alive(Pid6),
+
+ %% Remote registered name
+ {ok,Node} = test_server:start_node(proc_lib_SUITE_stop,slave,[]),
+ Dir = filename:dirname(code:which(?MODULE)),
+ rpc:call(Node,code,add_path,[Dir]),
+ Pid7 = spawn(Node,SysMsgProc),
+ true = rpc:call(Node,erlang,register,[to_stop,Pid7]),
+ Pid7 = rpc:call(Node,erlang,whereis,[to_stop]),
+ ok = proc_lib:stop({to_stop,Node}),
+ undefined = rpc:call(Node,erlang,whereis,[to_stop]),
+ false = rpc:call(Node,erlang,is_process_alive,[Pid7]),
+
+ %% Local and remote registered name, but non-existing
+ {'EXIT',noproc} = (catch proc_lib:stop(to_stop)),
+ {'EXIT',noproc} = (catch proc_lib:stop({to_stop,Node})),
+
+ true = test_server:stop_node(Node),
+
+ %% Remote registered name, but non-existing node
+ {'EXIT',{{nodedown,Node},_}} = (catch proc_lib:stop({to_stop,Node})),
+ ok.
+system_terminate(crash,_Parent,_Deb,_State) ->
+ 1 = 2;
+system_terminate(Reason,_Parent,_Deb,_State) ->
+ exit(Reason).
%%-----------------------------------------------------------------
%% The error_logger handler used.
diff --git a/lib/stdlib/test/qlc_SUITE.erl b/lib/stdlib/test/qlc_SUITE.erl
index 37fbb5267b..56829fac5c 100644
--- a/lib/stdlib/test/qlc_SUITE.erl
+++ b/lib/stdlib/test/qlc_SUITE.erl
@@ -1,7 +1,7 @@
%%
%% %CopyrightBegin%
%%
-%% Copyright Ericsson AB 2004-2014. All Rights Reserved.
+%% Copyright Ericsson AB 2004-2015. 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
@@ -396,7 +396,8 @@ nomatch(Config) when is_list(Config) ->
qlc:q([3 || {3=4} <- []]).
">>,
[],
- {warnings,[{{2,27},qlc,nomatch_pattern}]}},
+ %% {warnings,[{{2,27},qlc,nomatch_pattern}]}},
+ {warnings,[{2,v3_core,nomatch}]}},
{nomatch2,
<<"nomatch() ->
@@ -407,7 +408,8 @@ nomatch(Config) when is_list(Config) ->
end, [{1},{2}]).
">>,
[],
- {warnings,[{{3,33},qlc,nomatch_pattern}]}},
+ %% {warnings,[{{3,33},qlc,nomatch_pattern}]}},
+ {warnings,[{3,v3_core,nomatch}]}},
{nomatch3,
<<"nomatch() ->
@@ -419,7 +421,8 @@ nomatch(Config) when is_list(Config) ->
end, [{1,2},{2,3}]).
">>,
[],
- {warnings,[{{3,52},qlc,nomatch_pattern}]}},
+ %% {warnings,[{{3,52},qlc,nomatch_pattern}]}},
+ {warnings,[{3,v3_core,nomatch}]}},
{nomatch4,
<<"nomatch() ->
@@ -2487,8 +2490,11 @@ info(Config) when is_list(Config) ->
(catch qlc:info([X || {X} <- []], {n_elements, 0})),
L = lists:seq(1, 1000),
\"[1,2,3,4,5,6,7,8,9,10|'...']\" = qlc:info(L, {n_elements, 10}),
- {cons,1,{integer,1,1},{atom,1,'...'}} =
+ {cons,A1,{integer,A2,1},{atom,A3,'...'}} =
qlc:info(L, [{n_elements, 1},{format,abstract_code}]),
+ 1 = erl_anno:line(A1),
+ 1 = erl_anno:line(A2),
+ 1 = erl_anno:line(A3),
Q = qlc:q([{X} || X <- [a,b,c,d,e,f]]),
{call,_,_,[{cons,_,{atom,_,a},{cons,_,{atom,_,b},{cons,_,{atom,_,c},
{atom,_,'...'}}}},
@@ -2905,7 +2911,8 @@ lookup1(Config) when is_list(Config) ->
[] = qlc:e(Q),
false = lookup_keys(Q)
end, [{1},{a}])">>,
- {warnings,[{{2,37},qlc,nomatch_pattern}]}},
+ %% {warnings,[{{2,37},qlc,nomatch_pattern}]}},
+ []},
<<"etsc(fun(E) ->
Q = qlc:q([X || {X=X,Y=Y}={Y=Y,X=X} <- ets:table(E),
@@ -2933,7 +2940,8 @@ lookup1(Config) when is_list(Config) ->
[] = qlc:e(Q),
false = lookup_keys(Q)
end, [{a},{b}])">>,
- {warnings,[{{2,35},qlc,nomatch_pattern}]}},
+ %% {warnings,[{{2,35},qlc,nomatch_pattern}]}},
+ []},
{cres,
<<"etsc(fun(E) ->
@@ -2941,7 +2949,8 @@ lookup1(Config) when is_list(Config) ->
[] = qlc:e(Q),
false = lookup_keys(Q)
end, [{a},{b}])">>,
- {warnings,[{{2,35},qlc,nomatch_pattern}]}},
+ %% {warnings,[{{2,35},qlc,nomatch_pattern}]}},
+ []},
<<"etsc(fun(E) ->
Q = qlc:q([X || X = <<X>> <- ets:table(E)]),
@@ -2988,7 +2997,8 @@ lookup1(Config) when is_list(Config) ->
[] = qlc:e(Q),
false = lookup_keys(Q)
end, [{a,b,c},{d,e,f}])">>,
- {warnings,[{{2,34},qlc,nomatch_pattern}]}}
+ %% {warnings,[{{2,34},qlc,nomatch_pattern}]}}
+ []}
],
?line run(Config, Ts),
@@ -3021,8 +3031,9 @@ lookup2(Config) when is_list(Config) ->
end, [{3,true},{4,true}])">>,
<<"%% Only guards are inspected. No lookup.
- E1 = create_ets(1, 10),
- E2 = ets:new(join, []),
+ E1 = ets:new(e, [ordered_set]),
+ true = ets:insert(E1, [{1,1}, {2,2}, {3,3}, {4,4}, {5,5}]),
+ E2 = ets:new(join, [ordered_set]),
true = ets:insert(E2, [{true,1},{false,2}]),
Q = qlc:q([{X,Z} || {_,X} <- ets:table(E1),
{Y,Z} <- ets:table(E2),
@@ -3051,7 +3062,8 @@ lookup2(Config) when is_list(Config) ->
[] = qlc:e(Q),
false = lookup_keys(Q)
end, [{1}, {2}])">>,
- {warnings,[{{3,46},qlc,nomatch_filter}]}},
+ %% {warnings,[{{3,46},qlc,nomatch_filter}]}},
+ []},
{cres,
<<"etsc(fun(E) ->
@@ -3060,7 +3072,8 @@ lookup2(Config) when is_list(Config) ->
[] = qlc:e(Q),
false = lookup_keys(Q)
end, [{1}, {2}])">>,
- {warnings,[{{3,43},qlc,nomatch_filter}]}},
+ %% {warnings,[{{3,43},qlc,nomatch_filter}]}},
+ []},
{cres,
<<"etsc(fun(E) ->
@@ -3069,7 +3082,8 @@ lookup2(Config) when is_list(Config) ->
[] = qlc:e(Q),
false = lookup_keys(Q)
end, [{1}, {2}])">>,
- {warnings,[{{3,48},qlc,nomatch_filter}]}},
+ %% {warnings,[{{3,48},qlc,nomatch_filter}]}},
+ []},
<<"etsc(fun(E) ->
Q = qlc:q([{X,Y} || {X,Y} <- ets:table(E),
@@ -3084,7 +3098,8 @@ lookup2(Config) when is_list(Config) ->
[] = qlc:e(Q),
false = lookup_keys(Q)
end, [{[3]},{[3,4]}])">>,
- {warnings,[{{2,61},qlc,nomatch_filter}]}},
+ %% {warnings,[{{2,61},qlc,nomatch_filter}]}},
+ []},
<<"etsc(fun(E) ->
U = 18,
@@ -3116,7 +3131,8 @@ lookup2(Config) when is_list(Config) ->
[] = lists:sort(qlc:e(Q)),
false = lookup_keys(Q)
end, [{2},{3},{4},{8}])">>,
- {warnings,[{{4,44},qlc,nomatch_filter}]}},
+ %% {warnings,[{{4,44},qlc,nomatch_filter}]}},
+ []},
{cres,
<<"etsc(fun(E) ->
@@ -3126,7 +3142,8 @@ lookup2(Config) when is_list(Config) ->
[] = lists:sort(qlc:e(Q)),
false = lookup_keys(Q)
end, [{2},{3},{4},{8}])">>,
- {warnings,[{{4,35},qlc,nomatch_filter}]}},
+ %% {warnings,[{{4,35},qlc,nomatch_filter}]}},
+ []},
<<"F = fun(U) ->
Q = qlc:q([X || {X} <- [a,b,c],
@@ -3142,7 +3159,8 @@ lookup2(Config) when is_list(Config) ->
[] = qlc:e(Q),
false = lookup_keys(Q)
end, [{1,1},{2,1}])">>,
- {warnings,[{{2,61},qlc,nomatch_filter}]}},
+ %% {warnings,[{{2,61},qlc,nomatch_filter}]}},
+ []},
<<"Two = 2.0,
etsc(fun(E) ->
@@ -3203,8 +3221,10 @@ lookup2(Config) when is_list(Config) ->
[] = qlc:e(Q),
false = lookup_keys(Q)
end, [{1,b},{2,3}])">>,
+ %% {warnings,[{2,sys_core_fold,nomatch_guard},
+ %% {3,qlc,nomatch_filter},
+ %% {3,sys_core_fold,{eval_failure,badarg}}]}},
{warnings,[{2,sys_core_fold,nomatch_guard},
- {3,qlc,nomatch_filter},
{3,sys_core_fold,{eval_failure,badarg}}]}},
<<"etsc(fun(E) ->
@@ -3227,7 +3247,8 @@ lookup2(Config) when is_list(Config) ->
[] = qlc:e(Q),
false = lookup_keys(Q)
end, [{{1}},{{2}}])">>,
- {warnings,[{{4,47},qlc,nomatch_filter}]}},
+ %% {warnings,[{{4,47},qlc,nomatch_filter}]}},
+ []},
{cres,
<<"etsc(fun(E) ->
@@ -3237,7 +3258,8 @@ lookup2(Config) when is_list(Config) ->
[] = qlc:e(Q),
false = lookup_keys(Q)
end, [{{1}},{{2}}])">>,
- {warnings,[{{4,47},qlc,nomatch_filter}]}},
+ %% {warnings,[{{4,47},qlc,nomatch_filter}]}},
+ []},
<<"etsc(fun(E) ->
Q = qlc:q([X || {X} <- ets:table(E),
@@ -3297,7 +3319,8 @@ lookup2(Config) when is_list(Config) ->
[] = qlc:e(Q),
false = lookup_keys(Q)
end, [{3}, {4}])">>,
- {warnings,[{{3,44},qlc,nomatch_filter}]}},
+ %% {warnings,[{{3,44},qlc,nomatch_filter}]}},
+ []},
<<"etsc(fun(E) ->
Q = qlc:q([X || {{X,Y}} <- ets:table(E),
@@ -3418,7 +3441,8 @@ lookup2(Config) when is_list(Config) ->
end, [{1},{2}])">>
],
- ?line run(Config, Ts),
+
+ ok = run(Config, Ts),
TsR = [
%% is_record/2,3:
@@ -3456,7 +3480,8 @@ lookup2(Config) when is_list(Config) ->
end, [{keypos,1}], [#r{}])">>
],
- ?line run(Config, <<"-record(r, {a}).\n">>, TsR),
+
+ ok = run(Config, <<"-record(r, {a}).\n">>, TsR),
Ts2 = [
<<"etsc(fun(E) ->
@@ -3566,7 +3591,6 @@ lookup2(Config) when is_list(Config) ->
[{1,2},{2,2}] = qlc:e(Q),
[2] = lookup_keys(Q)
end, [{keypos,1}], [{1},{2},{3}])">>,
-
<<"%% Matchspec only. No cache.
etsc(fun(E) ->
Q = qlc:q([{X,Y} ||
@@ -3578,7 +3602,7 @@ lookup2(Config) when is_list(Config) ->
{generate,_,
{table,{ets,_,[_,[{traverse,_}]]}}}],[]} =
i(Q),
- [{1,2},{1,3},{2,2},{2,3}] = qlc:e(Q),
+ [{1,2},{1,3},{2,2},{2,3}] = lists:sort(qlc:e(Q)),
false = lookup_keys(Q)
end, [{keypos,1}], [{1},{2},{3}])">>,
<<"%% Matchspec only. Cache
@@ -3592,7 +3616,7 @@ lookup2(Config) when is_list(Config) ->
{generate,_,{qlc,_,
[{generate,_,{table,{ets,_,[_,[{traverse,_}]]}}}],
[{cache,ets}]}}],[]} = i(Q),
- [{1,2},{1,3},{2,2},{2,3}] = qlc:e(Q),
+ [{1,2},{1,3},{2,2},{2,3}] = lists:sort(qlc:e(Q)),
false = lookup_keys(Q)
end, [{keypos,1}], [{1},{2},{3}])">>,
<<"%% An empty list. Always unique and cached.
@@ -3645,7 +3669,7 @@ lookup2(Config) when is_list(Config) ->
],
- ?line run(Config, Ts2),
+ ok = run(Config, Ts2),
LTs = [
<<"etsc(fun(E) ->
@@ -3677,7 +3701,8 @@ lookup2(Config) when is_list(Config) ->
end, [{1,a},{2,b}])">>
],
- ?line run(Config, LTs),
+
+ ok = run(Config, LTs),
ok.
@@ -3700,7 +3725,8 @@ lookup_rec(Config) when is_list(Config) ->
[] = qlc:e(Q),
false = lookup_keys(Q)
end, [{keypos,2}], [#r{a = 17}, #r{a = 3}, #r{a = 5}])">>,
- {warnings,[{{4,44},qlc,nomatch_filter}]}},
+ %% {warnings,[{{4,44},qlc,nomatch_filter}]}},
+ []},
<<"%% Compares an integer and a float.
etsc(fun(E) ->
@@ -4004,7 +4030,8 @@ skip_filters(Config) when is_list(Config) ->
[] = qlc:e(Q),
false = lookup_keys(Q)
end, [{1,1},{2,0}])">>,
- {warnings,[{{4,37},qlc,nomatch_filter}]}},
+ %% {warnings,[{{4,37},qlc,nomatch_filter}]}},
+ []},
<<"etsc(fun(E) ->
Q = qlc:q([{A,B,C} ||
@@ -6093,7 +6120,7 @@ otp_6964(Config) when is_list(Config) ->
lists:flatten(qlc:format_error(ErrReply)),
qlc_SUITE:install_error_logger(),
20000 = length(F(warning_msg)),
- {error, joining} = qlc_SUITE:read_error_logger(),
+ {warning, joining} = qlc_SUITE:read_error_logger(),
20000 = length(F(info_msg)),
{info, joining} = qlc_SUITE:read_error_logger(),
20000 = length(F(error_msg)),
@@ -6128,8 +6155,8 @@ otp_6964(Config) when is_list(Config) ->
{error, caching} = qlc_SUITE:read_error_logger(),
{error, caching} = qlc_SUITE:read_error_logger(),
1 = length(F(warning_msg)),
- {error, caching} = qlc_SUITE:read_error_logger(),
- {error, caching} = qlc_SUITE:read_error_logger(),
+ {warning, caching} = qlc_SUITE:read_error_logger(),
+ {warning, caching} = qlc_SUITE:read_error_logger(),
1 = length(F(info_msg)),
{info, caching} = qlc_SUITE:read_error_logger(),
{info, caching} = qlc_SUITE:read_error_logger(),
@@ -6161,7 +6188,7 @@ otp_6964(Config) when is_list(Config) ->
L = F(info_msg),
{info, sorting} = qlc_SUITE:read_error_logger(),
L = F(warning_msg),
- {error, sorting} = qlc_SUITE:read_error_logger(),
+ {warning, sorting} = qlc_SUITE:read_error_logger(),
qlc_SUITE:uninstall_error_logger(),
ets:delete(E1),
ets:delete(E2)">>],
@@ -6188,7 +6215,7 @@ otp_6964(Config) when is_list(Config) ->
R = lists:sort(F(error_msg)),
{error, caching} = qlc_SUITE:read_error_logger(),
R = lists:sort(F(warning_msg)),
- {error, caching} = qlc_SUITE:read_error_logger(),
+ {warning, caching} = qlc_SUITE:read_error_logger(),
qlc_SUITE:uninstall_error_logger(),
ErrReply = F(not_allowed),
{error,qlc,{tmpdir_usage,caching}} = ErrReply,
@@ -6217,8 +6244,9 @@ otp_7238(Config) when is_list(Config) ->
<<"nomatch_1() ->
{qlc:q([X || X={X} <- []]), [t || \"a\"=\"b\" <- []]}.">>,
[],
- {warnings,[{{2,30},qlc,nomatch_pattern},
- {{2,44},v3_core,nomatch}]}},
+ %% {warnings,[{{2,30},qlc,nomatch_pattern},
+ %% {{2,44},v3_core,nomatch}]}},
+ {warnings,[{2,v3_core,nomatch}]}},
%% Not found by qlc...
{nomatch_2,
@@ -6231,7 +6259,8 @@ otp_7238(Config) when is_list(Config) ->
<<"nomatch_3() ->
qlc:q([t || [$a, $b] = \"ba\" <- []]).">>,
[],
- {warnings,[{{2,37},qlc,nomatch_pattern}]}},
+ %% {warnings,[{{2,37},qlc,nomatch_pattern}]}},
+ {warnings,[{2,v3_core,nomatch}]}},
%% Not found by qlc...
{nomatch_4,
@@ -6252,44 +6281,51 @@ otp_7238(Config) when is_list(Config) ->
qlc:q([X || X <- [],
X =:= {X}]).">>,
[],
- {warnings,[{{3,30},qlc,nomatch_filter}]}},
+ %% {warnings,[{{3,30},qlc,nomatch_filter}]}},
+ []},
{nomatch_7,
<<"nomatch_7() ->
qlc:q([X || {X=Y,{Y}=X} <- []]).">>,
[],
- {warnings,[{{2,28},qlc,nomatch_pattern}]}},
+ %% {warnings,[{{2,28},qlc,nomatch_pattern}]}},
+ []},
{nomatch_8,
<<"nomatch_8() ->
qlc:q([X || {X={},X=[]} <- []]).">>,
[],
- {warnings,[{{2,28},qlc,nomatch_pattern}]}},
+ %% {warnings,[{{2,28},qlc,nomatch_pattern}]}},
+ []},
{nomatch_9,
<<"nomatch_9() ->
qlc:q([X || X <- [], X =:= {}, X =:= []]).">>,
[],
- {warnings,[{{2,49},qlc,nomatch_filter}]}},
+ %% {warnings,[{{2,49},qlc,nomatch_filter}]}},
+ []},
{nomatch_10,
<<"nomatch_10() ->
qlc:q([X || X <- [],
((X =:= 1) or (X =:= 2)) and (X =:= 3)]).">>,
[],
- {warnings,[{{3,53},qlc,nomatch_filter}]}},
+ %% {warnings,[{{3,53},qlc,nomatch_filter}]}},
+ []},
{nomatch_11,
<<"nomatch_11() ->
qlc:q([X || X <- [], x =:= []]).">>,
[],
- {warnings,[{{2,39},qlc,nomatch_filter}]}},
+ %% {warnings,[{{2,39},qlc,nomatch_filter}]}},
+ {warnings,[{2,sys_core_fold,nomatch_guard}]}},
{nomatch_12,
<<"nomatch_12() ->
qlc:q([X || X={} <- [], X =:= []]).">>,
[],
- {warnings,[{{2,42},qlc,nomatch_filter}]}},
+ %% {warnings,[{{2,42},qlc,nomatch_filter}]}},
+ []},
{nomatch_13,
<<"nomatch_13() ->
@@ -6297,8 +6333,9 @@ otp_7238(Config) when is_list(Config) ->
X={X} <- [],
Y={Y} <- []]).">>,
[],
- {warnings,[{{3,29},qlc,nomatch_pattern},
- {{4,29},qlc,nomatch_pattern}]}},
+ %% {warnings,[{{3,29},qlc,nomatch_pattern},
+ %% {{4,29},qlc,nomatch_pattern}]}},
+ []},
{nomatch_14,
<<"nomatch_14() ->
@@ -6306,7 +6343,8 @@ otp_7238(Config) when is_list(Config) ->
1 > 0,
1 > X]).">>,
[],
- {warnings,[{{2,29},qlc,nomatch_pattern}]}},
+ %% {warnings,[{{2,29},qlc,nomatch_pattern}]}},
+ []},
{nomatch_15,
<<"nomatch_15() ->
@@ -6315,7 +6353,8 @@ otp_7238(Config) when is_list(Config) ->
1 > 0,
1 > X]).">>,
[],
- {warnings,[{{2,32},qlc,nomatch_pattern}]}},
+ %% {warnings,[{{2,32},qlc,nomatch_pattern}]}},
+ []},
%% Template warning.
{nomatch_template1,
@@ -6553,18 +6592,19 @@ otp_7238(Config) when is_list(Config) ->
?line run(Config, T2),
T3 = [
- {nomatch_6,
- <<"nomatch_6() ->
- qlc:q([X || X <- [],
- X =:= {X}]).">>,
- [],
- {[],["filter evaluates to 'false'"]}},
-
- {nomatch_7,
- <<"nomatch_7() ->
- qlc:q([X || {X=Y,{Y}=X} <- []]).">>,
- [],
- {[],["pattern cannot possibly match"]}}],
+%% {nomatch_6,
+%% <<"nomatch_6() ->
+%% qlc:q([X || X <- [],
+%% X =:= {X}]).">>,
+%% [],
+%% {[],["filter evaluates to 'false'"]}},
+
+%% {nomatch_7,
+%% <<"nomatch_7() ->
+%% qlc:q([X || {X=Y,{Y}=X} <- []]).">>,
+%% [],
+%% {[],["pattern cannot possibly match"]}}
+ ],
?line compile_format(Config, T3),
%% *Very* simple test - just check that it doesn't crash.
@@ -6822,7 +6862,8 @@ otp_6674(Config) when is_list(Config) ->
A == 192, B =:= 192.0,
{Y} <- [{0},{1},{2}],
X == Y]),
- {block,0,
+ A0 = erl_anno:new(0),
+ {block,A0,
[{match,_,_,
{call,_,_,
[{lc,_,_,
@@ -7392,7 +7433,8 @@ try_old_join_info(Config) ->
{ok, M} = compile:file(File, [{outdir, ?datadir}]),
{module, M} = code:load_abs(filename:rootname(File)),
H = M:create_handle(),
- {block,0,
+ A0 = erl_anno:new(0),
+ {block,A0,
[{match,_,_,
{call,_,_,
[{lc,_,_,
@@ -7772,8 +7814,8 @@ table(List, Indices, KeyPos, ParentFun) ->
end,
FormatFun = fun(all) ->
- L = 17,
- {call,L,{remote,L,{atom,1,?MODULE},{atom,L,the_list}},
+ L = erl_anno:new(17),
+ {call,L,{remote,L,{atom,L,?MODULE},{atom,L,the_list}},
[erl_parse:abstract(List, 17)]};
({lookup, Column, Values}) ->
{?MODULE, list_keys, [Values, Column, List]}
@@ -7891,7 +7933,7 @@ run_test(Config, Extra, {cres, Body, Opts, ExpectedCompileReturn}) ->
{module, _} = code:load_abs(AbsFile, Mod),
Ms0 = erlang:process_info(self(),messages),
- Before = {get(), pps(), ets:all(), Ms0},
+ Before = {{get(), ets:all(), Ms0}, pps()},
%% Prepare the check that the qlc module does not call qlc_pt.
_ = [unload_pt() || {file, Name} <- [code:is_loaded(qlc_pt)],
@@ -7921,12 +7963,29 @@ run_test(Config, Extra, {cres, Body, Opts, ExpectedCompileReturn}) ->
run_test(Config, Extra, Body) ->
run_test(Config, Extra, {cres,Body,[]}).
-wait_for_expected(R, Before, SourceFile, Wait) ->
+wait_for_expected(R, {Strict0,PPS0}=Before, SourceFile, Wait) ->
Ms = erlang:process_info(self(),messages),
- After = {get(), pps(), ets:all(), Ms},
+ After = {_,PPS1} = {{get(), ets:all(), Ms}, pps()},
case {R, After} of
{ok, Before} ->
ok;
+ {ok, {Strict0,_}} ->
+ {Ports0,Procs0} = PPS0,
+ {Ports1,Procs1} = PPS1,
+ case {Ports1 -- Ports0, Procs1 -- Procs0} of
+ {[], []} -> ok;
+ _ when Wait ->
+ timer:sleep(1000),
+ wait_for_expected(R, Before, SourceFile, false);
+ {PortsDiff,ProcsDiff} ->
+ io:format("failure, got ~p~n, expected ~p\n",
+ [PPS1, PPS0]),
+ show("Old port", Ports0 -- Ports1),
+ show("New port", PortsDiff),
+ show("Old proc", Procs0 -- Procs1),
+ show("New proc", ProcsDiff),
+ fail(SourceFile)
+ end;
_ when Wait ->
timer:sleep(1000),
wait_for_expected(R, Before, SourceFile, false);
@@ -7993,7 +8052,7 @@ compile_file(Config, Test0, Opts0) ->
case compile:file(File, Opts) of
{ok, _M, Ws} -> warnings(File, Ws);
{error, [{File,Es}], []} -> {errors, Es, []};
- {error, [{File,Es}], [{File,Ws}]} -> {error, Es, Ws}
+ {error, [{File,Es}], [{File,Ws}]} -> {errors, Es, Ws}
end.
comp_compare(T, T) ->
@@ -8058,6 +8117,17 @@ filename(Name, Config) when is_atom(Name) ->
filename(Name, Config) ->
filename:join(?privdir, Name).
+show(_S, []) ->
+ ok;
+show(S, [{Pid, Name, InitCall}|Pids]) when is_pid(Pid) ->
+ io:format("~s: ~w (~w), ~w: ~p~n",
+ [S, Pid, proc_reg_name(Name), InitCall,
+ erlang:process_info(Pid)]),
+ show(S, Pids);
+show(S, [{Port, _}|Ports]) when is_port(Port)->
+ io:format("~s: ~w: ~p~n", [S, Port, erlang:port_info(Port)]),
+ show(S, Ports).
+
pps() ->
{port_list(), process_list()}.
@@ -8070,6 +8140,9 @@ process_list() ->
safe_second_element(process_info(P, initial_call))} ||
P <- processes(), is_process_alive(P)].
+proc_reg_name({registered_name, Name}) -> Name;
+proc_reg_name([]) -> no_reg_name.
+
safe_second_element({_,Info}) -> Info;
safe_second_element(Other) -> Other.
@@ -8105,6 +8178,8 @@ read_error_logger() ->
{error, Why};
{info, Why} ->
{info, Why};
+ {warning, Why} ->
+ {warning, Why};
{error, Pid, Tuple} ->
{error, Pid, Tuple}
after 1000 ->
@@ -8119,8 +8194,7 @@ read_error_logger() ->
init(Tester) ->
{ok, Tester}.
-handle_event({error, _GL, {_Pid, _Msg, [Why, _]}}, Tester)
- when is_atom(Why) ->
+handle_event({error, _GL, {_Pid, _Msg, [Why, _]}}, Tester) when is_atom(Why) ->
Tester ! {error, Why},
{ok, Tester};
handle_event({error, _GL, {_Pid, _Msg, [P, T]}}, Tester) when is_pid(P) ->
@@ -8129,6 +8203,9 @@ handle_event({error, _GL, {_Pid, _Msg, [P, T]}}, Tester) when is_pid(P) ->
handle_event({info_msg, _GL, {_Pid, _Msg, [Why, _]}}, Tester) ->
Tester ! {info, Why},
{ok, Tester};
+handle_event({warning_msg, _GL, {_Pid, _Msg, [Why, _]}}, Tester) when is_atom(Why) ->
+ Tester ! {warning, Why},
+ {ok, Tester};
handle_event(_Event, State) ->
{ok, State}.
diff --git a/lib/stdlib/test/rand_SUITE.erl b/lib/stdlib/test/rand_SUITE.erl
new file mode 100644
index 0000000000..39ce1bd89a
--- /dev/null
+++ b/lib/stdlib/test/rand_SUITE.erl
@@ -0,0 +1,527 @@
+%%
+%% %CopyrightBegin%
+%%
+%% Copyright Ericsson AB 2000-2011. 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
+%% compliance with the License. You should have received a copy of the
+%% Erlang Public License along with this software. If not, it can be
+%% retrieved online at http://www.erlang.org/.
+%%
+%% Software distributed under the License is distributed on an "AS IS"
+%% basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See
+%% the License for the specific language governing rights and limitations
+%% under the License.
+%%
+%% %CopyrightEnd%
+
+-module(rand_SUITE).
+-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
+ ]).
+
+-export([interval_int/1, interval_float/1, seed/1,
+ api_eq/1, reference/1, basic_stats/1,
+ plugin/1, measure/1
+ ]).
+
+-export([test/0, gen/1]).
+
+-include_lib("test_server/include/test_server.hrl").
+
+% Default timetrap timeout (set in init_per_testcase).
+-define(default_timeout, ?t:minutes(3)).
+-define(LOOP, 1000000).
+
+init_per_testcase(_Case, Config) ->
+ Dog = ?t:timetrap(?default_timeout),
+ [{watchdog, Dog} | Config].
+end_per_testcase(_Case, Config) ->
+ Dog = ?config(watchdog, Config),
+ test_server:timetrap_cancel(Dog),
+ ok.
+
+suite() -> [{ct_hooks,[ts_install_cth]}].
+
+all() ->
+ [seed, interval_int, interval_float,
+ api_eq,
+ reference,
+ basic_stats,
+ plugin, measure
+ ].
+
+groups() -> [].
+
+init_per_suite(Config) -> Config.
+end_per_suite(_Config) -> ok.
+
+init_per_group(_GroupName, Config) -> Config.
+end_per_group(_GroupName, Config) -> Config.
+
+%% A simple helper to test without test_server during dev
+test() ->
+ Tests = all(),
+ lists:foreach(fun(Test) ->
+ try
+ ok = ?MODULE:Test([]),
+ io:format("~p: ok~n", [Test])
+ catch _:Reason ->
+ io:format("Failed: ~p: ~p ~p~n",
+ [Test, Reason, erlang:get_stacktrace()])
+ end
+ end, Tests).
+
+algs() ->
+ [exs64, exsplus, exs1024].
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+
+seed(doc) ->
+ ["Test that seed and seed_s and export_seed/0 is working."];
+seed(suite) ->
+ [];
+seed(Config) when is_list(Config) ->
+ Algs = algs(),
+ Test = fun(Alg) ->
+ try seed_1(Alg)
+ catch _:Reason ->
+ test_server:fail({Alg, Reason, erlang:get_stacktrace()})
+ end
+ end,
+ [Test(Alg) || Alg <- Algs],
+ ok.
+
+seed_1(Alg) ->
+ %% Check that uniform seeds automatically,
+ _ = rand:uniform(),
+ S00 = get(rand_seed),
+ erase(),
+ _ = rand:uniform(),
+ false = S00 =:= get(rand_seed), %% hopefully
+
+ %% Choosing algo and seed
+ S0 = rand:seed(Alg, {0, 0, 0}),
+ %% Check that (documented?) process_dict variable is correct
+ S0 = get(rand_seed),
+ S0 = rand:seed_s(Alg, {0, 0, 0}),
+ %% Check that process_dict should not be used for seed_s functionality
+ _ = rand:seed_s(Alg, {1, 0, 0}),
+ S0 = get(rand_seed),
+ %% Test export
+ ES0 = rand:export_seed(),
+ ES0 = rand:export_seed_s(S0),
+ S0 = rand:seed(ES0),
+ S0 = rand:seed_s(ES0),
+ %% seed/1 calls should be unique
+ S1 = rand:seed(Alg),
+ false = (S1 =:= rand:seed_s(Alg)),
+ %% Negative integers works
+ _ = rand:seed_s(Alg, {-1,-1,-1}),
+
+ %% Other term do not work
+ {'EXIT', _} = (catch rand:seed_s(foobar, os:timestamp())),
+ {'EXIT', _} = (catch rand:seed_s(Alg, {asd, 1, 1})),
+ {'EXIT', _} = (catch rand:seed_s(Alg, {0, 234.1234, 1})),
+ {'EXIT', _} = (catch rand:seed_s(Alg, {0, 234, [1, 123, 123]})),
+ ok.
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+
+api_eq(doc) ->
+ ["Check that both api's are consistent with each other."];
+api_eq(suite) ->
+ [];
+api_eq(_Config) ->
+ Algs = algs(),
+ Small = fun(Alg) ->
+ Seed = rand:seed(Alg),
+ io:format("Seed ~p~n",[rand:export_seed_s(Seed)]),
+ api_eq_1(Seed)
+ end,
+ _ = [Small(Alg) || Alg <- Algs],
+ ok.
+
+api_eq_1(S00) ->
+ Check = fun(_, Seed) ->
+ {V0, S0} = rand:uniform_s(Seed),
+ V0 = rand:uniform(),
+ {V1, S1} = rand:uniform_s(1000000, S0),
+ V1 = rand:uniform(1000000),
+ {V2, S2} = rand:normal_s(S1),
+ V2 = rand:normal(),
+ S2
+ end,
+ S1 = lists:foldl(Check, S00, lists:seq(1, 200)),
+ S1 = get(rand_seed),
+ {V0, S2} = rand:uniform_s(S1),
+ V0 = rand:uniform(),
+ S2 = get(rand_seed),
+
+ Exported = rand:export_seed(),
+ Exported = rand:export_seed_s(S2),
+
+ S3 = lists:foldl(Check, S2, lists:seq(1, 200)),
+ S3 = get(rand_seed),
+
+ S4 = lists:foldl(Check, S3, lists:seq(1, 200)),
+ S4 = get(rand_seed),
+ %% Verify that we do not have loops
+ false = S1 =:= S2,
+ false = S2 =:= S3,
+ false = S3 =:= S4,
+
+ S2 = rand:seed(Exported),
+ S3 = lists:foldl(Check, S2, lists:seq(1, 200)),
+ ok.
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+
+interval_int(doc) ->
+ ["Check that uniform/1 returns values within the proper interval."];
+interval_int(suite) ->
+ [];
+interval_int(Config) when is_list(Config) ->
+ Algs = algs(),
+ Small = fun(Alg) ->
+ Seed = rand:seed(Alg),
+ io:format("Seed ~p~n",[rand:export_seed_s(Seed)]),
+ Max = interval_int_1(100000, 7, 0),
+ Max =:= 7 orelse exit({7, Alg, Max})
+ end,
+ _ = [Small(Alg) || Alg <- Algs],
+ %% Test large integers
+ Large = fun(Alg) ->
+ Seed = rand:seed(Alg),
+ io:format("Seed ~p~n",[rand:export_seed_s(Seed)]),
+ Max = interval_int_1(100000, 1 bsl 128, 0),
+ Max > 1 bsl 64 orelse exit({large, Alg, Max})
+ end,
+ [Large(Alg) || Alg <- Algs],
+ ok.
+
+interval_int_1(0, _, Max) -> Max;
+interval_int_1(N, Top, Max) ->
+ X = rand:uniform(Top),
+ if
+ 0 < X, X =< Top ->
+ ok;
+ true ->
+ io:format("X=~p Top=~p 0<~p<~p~n", [X,Top,X,Top]),
+ exit({X, rand:export_seed()})
+ end,
+ interval_int_1(N-1, Top, max(X, Max)).
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+
+interval_float(doc) ->
+ ["Check that uniform/0 returns values within the proper interval."];
+interval_float(suite) ->
+ [];
+interval_float(Config) when is_list(Config) ->
+ Algs = algs(),
+ Test = fun(Alg) ->
+ _ = rand:seed(Alg),
+ interval_float_1(100000)
+ end,
+ [Test(Alg) || Alg <- Algs],
+ ok.
+
+interval_float_1(0) -> ok;
+interval_float_1(N) ->
+ X = rand:uniform(),
+ if
+ 0.0 < X, X < 1.0 ->
+ ok;
+ true ->
+ io:format("X=~p 0<~p<1.0~n", [X,X]),
+ exit({X, rand:export_seed()})
+ end,
+ interval_float_1(N-1).
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+
+reference(doc) -> ["Check if exs64 algorithm generates the proper sequence."];
+reference(suite) -> [];
+reference(Config) when is_list(Config) ->
+ [reference_1(Alg) || Alg <- algs()],
+ ok.
+
+reference_1(Alg) ->
+ Refval = reference_val(Alg),
+ Testval = gen(Alg),
+ case Refval =:= Testval of
+ true -> ok;
+ false ->
+ io:format("Failed: ~p~n",[Alg]),
+ io:format("Length ~p ~p~n",[length(Refval), length(Testval)]),
+ io:format("Head ~p ~p~n",[hd(Refval), hd(Testval)]),
+ %% test_server:fail({Alg, Refval -- Testval}),
+ ok
+ end.
+
+gen(Algo) ->
+ Seed = case Algo of
+ exsplus -> %% Printed with orig 'C' code and this seed
+ rand:seed_s({exsplus, [12345678|12345678]});
+ exs64 -> %% Printed with orig 'C' code and this seed
+ rand:seed_s({exs64, 12345678});
+ exs1024 -> %% Printed with orig 'C' code and this seed
+ rand:seed_s({exs1024, {lists:duplicate(16, 12345678), []}});
+ _ ->
+ rand:seed(Algo, {100, 200, 300})
+ end,
+ gen(?LOOP, Seed, []).
+
+gen(N, State0 = {#{max:=Max}, _}, Acc) when N > 0 ->
+ {Random, State} = rand:uniform_s(Max, State0),
+ case N rem (?LOOP div 100) of
+ 0 -> gen(N-1, State, [Random|Acc]);
+ _ -> gen(N-1, State, Acc)
+ end;
+gen(_, _, Acc) -> lists:reverse(Acc).
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% This just tests the basics so we have not made any serious errors
+%% when making the conversion from the original algorithms.
+%% The algorithms must have good properties to begin with
+%%
+
+basic_stats(doc) -> ["Check that the algorithms generate sound values."];
+basic_stats(suite) -> [];
+basic_stats(Config) when is_list(Config) ->
+ io:format("Testing uniform~n",[]),
+ [basic_uniform_1(?LOOP, rand:seed_s(Alg), 0.0, array:new([{default, 0}]))
+ || Alg <- algs()],
+ [basic_uniform_2(?LOOP, rand:seed_s(Alg), 0, array:new([{default, 0}]))
+ || Alg <- algs()],
+ io:format("Testing normal~n",[]),
+ [basic_normal_1(?LOOP, rand:seed_s(Alg), 0, 0) || Alg <- algs()],
+ ok.
+
+basic_uniform_1(N, S0, Sum, A0) when N > 0 ->
+ {X,S} = rand:uniform_s(S0),
+ I = trunc(X*100),
+ A = array:set(I, 1+array:get(I,A0), A0),
+ basic_uniform_1(N-1, S, Sum+X, A);
+basic_uniform_1(0, {#{type:=Alg}, _}, Sum, A) ->
+ AverN = Sum / ?LOOP,
+ io:format("~.10w: Average: ~.4f~n", [Alg, AverN]),
+ Counters = array:to_list(A),
+ Min = lists:min(Counters),
+ Max = lists:max(Counters),
+ io:format("~.10w: Min: ~p Max: ~p~n", [Alg, Min, Max]),
+
+ %% Verify that the basic statistics are ok
+ %% be gentle we don't want to see to many failing tests
+ abs(0.5 - AverN) < 0.005 orelse test_server:fail({average, Alg, AverN}),
+ abs(?LOOP div 100 - Min) < 1000 orelse test_server:fail({min, Alg, Min}),
+ abs(?LOOP div 100 - Max) < 1000 orelse test_server:fail({max, Alg, Max}),
+ ok.
+
+basic_uniform_2(N, S0, Sum, A0) when N > 0 ->
+ {X,S} = rand:uniform_s(100, S0),
+ A = array:set(X-1, 1+array:get(X-1,A0), A0),
+ basic_uniform_2(N-1, S, Sum+X, A);
+basic_uniform_2(0, {#{type:=Alg}, _}, Sum, A) ->
+ AverN = Sum / ?LOOP,
+ io:format("~.10w: Average: ~.4f~n", [Alg, AverN]),
+ Counters = tl(array:to_list(A)),
+ Min = lists:min(Counters),
+ Max = lists:max(Counters),
+ io:format("~.10w: Min: ~p Max: ~p~n", [Alg, Min, Max]),
+
+ %% Verify that the basic statistics are ok
+ %% be gentle we don't want to see to many failing tests
+ abs(50.5 - AverN) < 0.5 orelse test_server:fail({average, Alg, AverN}),
+ abs(?LOOP div 100 - Min) < 1000 orelse test_server:fail({min, Alg, Min}),
+ abs(?LOOP div 100 - Max) < 1000 orelse test_server:fail({max, Alg, Max}),
+ ok.
+
+basic_normal_1(N, S0, Sum, Sq) when N > 0 ->
+ {X,S} = rand:normal_s(S0),
+ basic_normal_1(N-1, S, X+Sum, X*X+Sq);
+basic_normal_1(0, {#{type:=Alg}, _}, Sum, SumSq) ->
+ Mean = Sum / ?LOOP,
+ StdDev = math:sqrt((SumSq - (Sum*Sum/?LOOP))/(?LOOP - 1)),
+ io:format("~.10w: Average: ~7.4f StdDev ~6.4f~n", [Alg, Mean, StdDev]),
+ %% Verify that the basic statistics are ok
+ %% be gentle we don't want to see to many failing tests
+ abs(Mean) < 0.005 orelse test_server:fail({average, Alg, Mean}),
+ abs(StdDev - 1.0) < 0.005 orelse test_server:fail({stddev, Alg, StdDev}),
+ ok.
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+
+plugin(doc) -> ["Test that the user can write algorithms"];
+plugin(suite) -> [];
+plugin(Config) when is_list(Config) ->
+ _ = lists:foldl(fun(_, S0) ->
+ {V1, S1} = rand:uniform_s(10000, S0),
+ true = is_integer(V1),
+ {V2, S2} = rand:uniform_s(S1),
+ true = is_float(V2),
+ S2
+ end, crypto_seed(), lists:seq(1, 200)),
+ ok.
+
+%% Test implementation
+crypto_seed() ->
+ {#{type=>crypto,
+ max=>(1 bsl 64)-1,
+ next=>fun crypto_next/1,
+ uniform=>fun crypto_uniform/1,
+ uniform_n=>fun crypto_uniform_n/2},
+ <<>>}.
+
+%% Be fair and create bignums i.e. 64bits otherwise use 58bits
+crypto_next(<<Num:64, Bin/binary>>) ->
+ {Num, Bin};
+crypto_next(_) ->
+ crypto_next(crypto:rand_bytes((64 div 8)*100)).
+
+crypto_uniform({Api, Data0}) ->
+ {Int, Data} = crypto_next(Data0),
+ {Int / (1 bsl 64), {Api, Data}}.
+
+crypto_uniform_n(N, {Api, Data0}) when N < (1 bsl 64) ->
+ {Int, Data} = crypto_next(Data0),
+ {(Int rem N)+1, {Api, Data}};
+crypto_uniform_n(N, State0) ->
+ {F,State} = crypto_uniform(State0),
+ {trunc(F * N) + 1, State}.
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+
+%% Not a test but measures the time characteristics of the different algorithms
+measure(Suite) when is_atom(Suite) -> [];
+measure(_Config) ->
+ Algos = [crypto64|algs()],
+ io:format("RNG uniform integer performance~n",[]),
+ _ = measure_1(random, fun(State) -> {int, random:uniform_s(10000, State)} end),
+ _ = [measure_1(Algo, fun(State) -> {int, rand:uniform_s(10000, State)} end) || Algo <- Algos],
+ io:format("RNG uniform float performance~n",[]),
+ _ = measure_1(random, fun(State) -> {uniform, random:uniform_s(State)} end),
+ _ = [measure_1(Algo, fun(State) -> {uniform, rand:uniform_s(State)} end) || Algo <- Algos],
+ io:format("RNG normal float performance~n",[]),
+ io:format("~.10w: not implemented (too few bits)~n", [random]),
+ _ = [measure_1(Algo, fun(State) -> {normal, rand:normal_s(State)} end) || Algo <- Algos],
+ ok.
+
+measure_1(Algo, Gen) ->
+ Parent = self(),
+ Seed = fun(crypto64) -> crypto_seed();
+ (random) -> random:seed(os:timestamp()), get(random_seed);
+ (Alg) -> rand:seed_s(Alg)
+ end,
+
+ Pid = spawn_link(fun() ->
+ Fun = fun() -> measure_2(?LOOP, Seed(Algo), Gen) end,
+ {Time, ok} = timer:tc(Fun),
+ io:format("~.10w: ~pµs~n", [Algo, Time]),
+ Parent ! {self(), ok},
+ normal
+ end),
+ receive
+ {Pid, Msg} -> Msg
+ end.
+
+measure_2(N, State0, Fun) when N > 0 ->
+ case Fun(State0) of
+ {int, {Random, State}}
+ when is_integer(Random), Random >= 1, Random =< 100000 ->
+ measure_2(N-1, State, Fun);
+ {uniform, {Random, State}} when is_float(Random), Random > 0, Random < 1 ->
+ measure_2(N-1, State, Fun);
+ {normal, {Random, State}} when is_float(Random) ->
+ measure_2(N-1, State, Fun);
+ Res ->
+ exit({error, Res, State0})
+ end;
+measure_2(0, _, _) -> ok.
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%%% Data
+reference_val(exs64) ->
+ [16#3737ad0c703ff6c3,16#3868a78fe71adbbd,16#1f01b62b4338b605,16#50876a917437965f,
+ 16#b2edfe32a10e27fc,16#995924551d8ebae1,16#9f1e6b94e94e0b58,16#27ec029eb0e94f8e,
+ 16#bf654e6df7fe5c,16#b7d5ef7b79be65e3,16#4bdba4d1c159126b,16#a9c816fdc701292c,
+ 16#a377b6c89d85ac8b,16#7abb5cd0e5847a6,16#62666f1fc00a0a90,16#1edc3c3d255a8113,
+ 16#dfc764073767f18e,16#381783d577ca4e34,16#49693588c085ddcb,16#da6fcb16dd5163f3,
+ 16#e2357a703475b1b7,16#aaa84c4924b5985a,16#b8fe07bb2bac1e49,16#23973ac0160ff064,
+ 16#1afbc7b023f5d618,16#9f510f7b7caa2a0f,16#d5b0a57f7f5f1084,16#d8c49b66c5f99a29,
+ 16#e920ac3b598b5213,16#1090d7e27e7a7c76,16#81171917168ee74f,16#f08489a3eb6988e,
+ 16#396260c4f0b2ed46,16#4fd0a6a6caefd5b2,16#423dff07a3b888a,16#12718773ebd99987,
+ 16#e50991e540807cb,16#8cfa03bbaa6679d6,16#55bdf86dfbb92dbf,16#eb7145378cce74a8,
+ 16#71856c224c846595,16#20461588dae6e24d,16#c73b3e63ced74bac,16#775b11813dda0c78,
+ 16#91f358e51068ede0,16#399955ef36766bc2,16#4489ee072e8a38b1,16#ba77759d52321ca0,
+ 16#14f519eab5c53db8,16#1f754bd08e4f34c4,16#99e25ca29b2fcfeb,16#da11927c0d9837f8,
+ 16#1eeb0f87009f5a87,16#a7c444d3b0db1089,16#49c7fbf0714849ad,16#4f2b693e7f8265cb,
+ 16#80e1493cbaa8f256,16#186f345bcac2661e,16#330065ae0c698d26,16#5235ed0432c42e93,
+ 16#429792e31ddb10bb,16#8769054bb6533cff,16#1ab382483444201f,16#2216368786fc7b9,
+ 16#1efea1155216da0b,16#782dc868ba595452,16#2b80f6d159617f48,16#407fc35121b2fa1b,
+ 16#90e8be6e618873d1,16#40ad4ec92a8abf8e,16#34e2890f583f435,16#838c0aef0a5d8427,
+ 16#ed4238f4bd6cbcfa,16#7feed11f7a8bb9f0,16#2b0636a93e26c89d,16#481ad4bea5180646,
+ 16#673e5ad861afe1cc,16#298eeb519d69e74d,16#eb1dd06d168c856,16#4770651519ee7ef9,
+ 16#7456ebf1bcf608f1,16#d6200f6fbd61ce05,16#c0695dfab11ab6aa,16#5bff449249983843,
+ 16#7aba88471474c9ac,16#d7e9e4a21c989e91,16#c5e02ee67ccb7ce1,16#4ea8a3a912246153,
+ 16#f2e6db7c9ce4ec43,16#39498a95d46d2470,16#c5294fcb8cce8aa9,16#a918fe444719f3dc,
+ 16#98225f754762c0c0,16#f0721204f2cb43f5,16#b98e77b099d1f2d1,16#691d6f75aee3386,
+ 16#860c7b2354ec24fd,16#33e007bd0fbcb609,16#7170ae9c20fb3d0,16#31d46938fe383a60];
+
+reference_val(exs1024) ->
+ [16#9c61311d0d4a01fd,16#ce963ef5803b703e,16#545dcffb7b644e1a,16#edd56576a8d778d5,
+ 16#16bee799783c6b45,16#336f0b3caeb417fa,16#29291b8be26dedfa,16#1efed996d2e1b1a8,
+ 16#c5c04757bd2dadf9,16#11aa6d194009c616,16#ab2b3e82bdb38a91,16#5011ee46fd2609eb,
+ 16#766db7e5b701a9bb,16#d42cb2632c419f35,16#107c6a2667bf8557,16#3ffbf922cb306967,
+ 16#1e71e3d024ac5131,16#6fdb368ec67a5f06,16#b0d8e72e7aa6d1c1,16#e5705a02dae89e3b,
+ 16#9c24eb68c086a1d3,16#418de330f55f71f0,16#2917ddeb278bc8d2,16#aeba7fba67208f39,
+ 16#10ceaf40f6af1d8d,16#47a6d06811d33132,16#603a661d6caf720a,16#a28bd0c9bcdacb3c,
+ 16#f44754f006909762,16#6e25e8e67ccc43bc,16#174378ce374a549e,16#b5598ae9f57c4e50,
+ 16#ca85807fbcd51dd,16#1816e58d6c3cc32a,16#1b4d630d3c8e96a6,16#c19b1e92b4efc5bd,
+ 16#665597b20ddd721a,16#fdab4eb21b75c0ae,16#86a612dcfea0756c,16#8fc2da192f9a55f0,
+ 16#d7c954eb1af31b5,16#6f5ee45b1b80101b,16#ebe8ea4e5a67cbf5,16#1cb952026b4c1400,
+ 16#44e62caffe7452c0,16#b591d8f3e6d7cbcf,16#250303f8d77b6f81,16#8ef2199aae4c9b8d,
+ 16#a16baa37a14d7b89,16#c006e4d2b2da158b,16#e6ec7abd54c93b31,16#e6b0d79ae2ab6fa7,
+ 16#93e4b30e4ab7d4cd,16#42a01b6a4ef63033,16#9ab1e94fe94976e,16#426644e1de302a1f,
+ 16#8e58569192200139,16#744f014a090107c1,16#15d056801d467c6c,16#51bdad3a8c30225f,
+ 16#abfc61fb3104bd45,16#c610607122272df7,16#905e67c63116ebfc,16#1e4fd5f443bdc18,
+ 16#1945d1745bc55a4c,16#f7cd2b18989595bb,16#f0d273b2c646a038,16#ee9a6fdc6fd5d734,
+ 16#541a518bdb700518,16#6e67ab9a65361d76,16#bcfadc9bfe5b2e06,16#69fa334cf3c11496,
+ 16#9657df3e0395b631,16#fc0d0442160108ec,16#2ee538da7b1f7209,16#8b20c9fae50a5a9e,
+ 16#a971a4b5c2b3b6a,16#ff6241e32489438e,16#8fd6433f45255777,16#6e6c82f10818b0dc,
+ 16#59a8fad3f6af616b,16#7eac34f43f12221c,16#6e429ec2951723ec,16#9a65179767a45c37,
+ 16#a5f8127d1e6fdf35,16#932c50bc633d8d5c,16#f3bbea4e7ebecb8,16#efc3a2bbf6a8674,
+ 16#451644a99971cb6,16#cf70776d652c150d,16#c1fe0dcb87a25403,16#9523417132b2452e,
+ 16#8f98bc30d06b980e,16#bb4b288ecb8daa9a,16#59e54beb32f78045,16#f9ab1562456b9d66,
+ 16#6435f4130304a793,16#b4bb94c2002e1849,16#49a86d1e4bade982,16#457d63d60ed52b95];
+
+reference_val(exsplus) ->
+ [16#bc76c2e638db,16#15ede2ebb16c9fb,16#185ee2c27d6b88d,16#15d5ee9feafc3a5,
+ 16#1862e91dfce3e6b,16#2c9744b0fb69e46,16#78b21bc01cef6b,16#2d16a2fae6c76ba,
+ 16#13dfccb8ff86bce,16#1d9474c59e23f4d,16#d2f67dcd7f0dd6,16#2b6d489d51a0725,
+ 16#1fa52ef484861d8,16#1ae9e2a38f966d4,16#2264ab1e193acca,16#23bbca085039a05,
+ 16#2b6eea06a0af0e1,16#3ad47fa8866ea20,16#1ec2802d612d855,16#36c1982b134d50,
+ 16#296b6a23f5b75e0,16#c5eeb600a9875c,16#2a3fd51d735f9d4,16#56fafa3593a070,
+ 16#13e9d416ec0423e,16#28101a91b23e9dc,16#32e561eb55ce15a,16#94a7dbba66fe4a,
+ 16#2e1845043bcec1f,16#235f7513a1b5146,16#e37af1bf2d63cb,16#2048033824a1639,
+ 16#c255c750995f7,16#2c7542058e89ee3,16#204dfeefbdb62ba,16#f5a936ec63dd66,
+ 16#33b3b7dbbbd8b90,16#c4f0f79026ffe9,16#20ffee2d37aca13,16#2274f931716be2c,
+ 16#29b883902ba9df1,16#1a838cd5312717f,16#2edfc49ff3dc1d6,16#418145cbec84c2,
+ 16#d2d8f1a17d49f,16#d41637bfa4cc6f,16#24437e03a0f5df8,16#3d1d87919b94a90,
+ 16#20d6997b36769b6,16#16f9d7855cd87ca,16#821ef7e2a062a3,16#2c4d11dc4a2da70,
+ 16#24a3b27f56ed26b,16#144b23c8b97387a,16#34a2ced56930d12,16#21cc0544113a017,
+ 16#3e780771f634fb2,16#146c259c02e7e18,16#1d99e4cfad0ef1,16#fdf3dabefc6b3a,
+ 16#7d0806e4d12dfb,16#3e3ae3580532eae,16#2456544200fbd86,16#f83aad4e88db85,
+ 16#37c134779463b4d,16#21a20bf64b6e735,16#1c0585ac88b69f2,16#1b3fcea8dd30e56,
+ 16#334bc301aefd97,16#37066eb7e80a946,16#15a19a6331b570f,16#35e67fa43c3f7d0,
+ 16#152a4020145fb80,16#8d55139491dfbe,16#21d9cba585c059d,16#31475f363654635,
+ 16#2567b17acb7a104,16#39201be3a7681c5,16#6bc675fd26b601,16#334b93232b1b1e3,
+ 16#357c402cb732c6a,16#362e32efe4db46a,16#8edc7ae3da51e5,16#31573376785eac9,
+ 16#6c6145ffa1169d,16#18ec2c393d45359,16#1f1a5f256e7130c,16#131cc2f49b8004f,
+ 16#36f715a249f4ec2,16#1c27629826c50d3,16#914d9a6648726a,16#27f5bf5ce2301e8,
+ 16#3dd493b8012970f,16#be13bed1e00e5c,16#ceef033b74ae10,16#3da38c6a50abe03,
+ 16#15cbd1a421c7a8c,16#22794e3ec6ef3b1,16#26154d26e7ea99f,16#3a66681359a6ab6].
diff --git a/lib/stdlib/test/random_SUITE.erl b/lib/stdlib/test/random_SUITE.erl
index ac9d1a6c06..22c0900651 100644
--- a/lib/stdlib/test/random_SUITE.erl
+++ b/lib/stdlib/test/random_SUITE.erl
@@ -82,7 +82,7 @@ seed(suite) ->
[];
seed(Config) when is_list(Config) ->
?line Self = self(),
- ?line Seed = {S1, S2, S3} = now(),
+ Seed = {S1, S2, S3} = erlang:timestamp(),
?line _ = spawn(fun() ->
random:seed(S1,S2,S3),
Rands = lists:foldl(fun
diff --git a/lib/stdlib/test/select_SUITE.erl b/lib/stdlib/test/select_SUITE.erl
index 546c25f954..201c38b25a 100644
--- a/lib/stdlib/test/select_SUITE.erl
+++ b/lib/stdlib/test/select_SUITE.erl
@@ -211,7 +211,7 @@ init_random(Config) ->
{ok,[X]} ->
X;
_ ->
- {A,B,C} = erlang:now(),
+ {A,B,C} = erlang:timestamp(),
random:seed(A,B,C),
get(random_seed)
end,
diff --git a/lib/stdlib/test/sets_SUITE.erl b/lib/stdlib/test/sets_SUITE.erl
index c0cf1fc7e8..24f5d65f82 100644
--- a/lib/stdlib/test/sets_SUITE.erl
+++ b/lib/stdlib/test/sets_SUITE.erl
@@ -1,7 +1,7 @@
%%
%% %CopyrightBegin%
%%
-%% Copyright Ericsson AB 2004-2013. All Rights Reserved.
+%% Copyright Ericsson AB 2004-2015. 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
@@ -28,7 +28,7 @@
create/1,add_element/1,del_element/1,
subtract/1,intersection/1,union/1,is_subset/1,
is_set/1,fold/1,filter/1,
- take_smallest/1,take_largest/1]).
+ take_smallest/1,take_largest/1, iterate/1]).
-include_lib("test_server/include/test_server.hrl").
@@ -48,7 +48,7 @@ suite() -> [{ct_hooks,[ts_install_cth]}].
all() ->
[create, add_element, del_element, subtract,
intersection, union, is_subset, is_set, fold, filter,
- take_smallest, take_largest].
+ take_smallest, take_largest, iterate].
groups() ->
[].
@@ -426,6 +426,44 @@ take_largest_3(S0, List0, M) ->
take_largest_3(S, List, M)
end.
+iterate(Config) when is_list(Config) ->
+ test_all(fun iterate_1/1).
+
+iterate_1(M) ->
+ case M(module, []) of
+ gb_sets -> iterate_2(M);
+ _ -> ok
+ end,
+ M(empty, []).
+
+iterate_2(M) ->
+ random:seed(1, 2, 42),
+ iter_set(M, 1000).
+
+iter_set(_M, 0) ->
+ ok;
+iter_set(M, N) ->
+ L = [I || I <- lists:seq(1, N)],
+ T = M(from_list, L),
+ L = lists:reverse(iterate_set(M, T)),
+ R = random:uniform(N),
+ S = lists:reverse(iterate_set(M, R, T)),
+ S = [E || E <- L, E >= R],
+ iter_set(M, N-1).
+
+iterate_set(M, Set) ->
+ I = M(iterator, Set),
+ iterate_set_1(M, M(next, I), []).
+
+iterate_set(M, Start, Set) ->
+ I = M(iterator_from, {Start, Set}),
+ iterate_set_1(M, M(next, I), []).
+
+iterate_set_1(_, none, R) ->
+ R;
+iterate_set_1(M, {E, I}, R) ->
+ iterate_set_1(M, M(next, I), [E | R]).
+
%%%
%%% Helper functions.
%%%
diff --git a/lib/stdlib/test/sets_test_lib.erl b/lib/stdlib/test/sets_test_lib.erl
index 86f009a8f9..772139406d 100644
--- a/lib/stdlib/test/sets_test_lib.erl
+++ b/lib/stdlib/test/sets_test_lib.erl
@@ -1,7 +1,7 @@
%%
%% %CopyrightBegin%
%%
-%% Copyright Ericsson AB 2004-2013. All Rights Reserved.
+%% Copyright Ericsson AB 2004-2015. 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
@@ -34,7 +34,10 @@ new(Mod, Eq) ->
(is_empty, S) -> is_empty(Mod, S);
(is_set, S) -> Mod:is_set(S);
(is_subset, {S,Set}) -> is_subset(Mod, Eq, S, Set);
+ (iterator, S) -> Mod:iterator(S);
+ (iterator_from, {Start, S}) -> Mod:iterator_from(Start, S);
(module, []) -> Mod;
+ (next, I) -> Mod:next(I);
(singleton, E) -> singleton(Mod, E);
(size, S) -> Mod:size(S);
(subtract, {S1,S2}) -> subtract(Mod, S1, S2);
diff --git a/lib/stdlib/test/shell_SUITE.erl b/lib/stdlib/test/shell_SUITE.erl
index f841e2c4a6..7c18560498 100644
--- a/lib/stdlib/test/shell_SUITE.erl
+++ b/lib/stdlib/test/shell_SUITE.erl
@@ -1,7 +1,7 @@
%%
%% %CopyrightBegin%
%%
-%% Copyright Ericsson AB 2004-2013. All Rights Reserved.
+%% Copyright Ericsson AB 2004-2015. 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
@@ -404,13 +404,14 @@ records(Config) when is_list(Config) ->
?line ok = file:write_file(Test, Contents),
RR5 = "rr(\"" ++ Test ++ "\", '_', {d,test1}), rl([test1,test2]).",
- ?line [{attribute,1,record,{test1,_}},ok] = scan(RR5),
+ A1 = erl_anno:new(1),
+ [{attribute,A1,record,{test1,_}},ok] = scan(RR5),
RR6 = "rr(\"" ++ Test ++ "\", '_', {d,test2}), rl([test1,test2]).",
- ?line [{attribute,1,record,{test2,_}},ok] = scan(RR6),
+ [{attribute,A1,record,{test2,_}},ok] = scan(RR6),
RR7 = "rr(\"" ++ Test ++
"\", '_', [{d,test1},{d,test2,17}]), rl([test1,test2]).",
- ?line [{attribute,1,record,{test1,_}},{attribute,1,record,{test2,_}},
- ok] = scan(RR7),
+ [{attribute,A1,record,{test1,_}},{attribute,A1,record,{test2,_}},ok] =
+ scan(RR7),
?line PreReply = scan(<<"rr(prim_file).">>), % preloaded...
?line true = is_list(PreReply),
?line Dir = filename:join(?config(priv_dir, Config), "*.erl"),
diff --git a/lib/stdlib/test/stdlib_SUITE.erl b/lib/stdlib/test/stdlib_SUITE.erl
index 3d09bd27ff..8ab30eb62b 100644
--- a/lib/stdlib/test/stdlib_SUITE.erl
+++ b/lib/stdlib/test/stdlib_SUITE.erl
@@ -1,7 +1,7 @@
%%
%% %CopyrightBegin%
%%
-%% Copyright Ericsson AB 1997-2014. All Rights Reserved.
+%% Copyright Ericsson AB 1997-2015. 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
@@ -22,14 +22,7 @@
-module(stdlib_SUITE).
-include_lib("test_server/include/test_server.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]).
--export([init_per_testcase/2, end_per_testcase/2]).
-
-% Test cases must be exported.
--export([app_test/1, appup_test/1]).
+-compile(export_all).
%%
%% all/1
@@ -37,10 +30,10 @@
suite() -> [{ct_hooks,[ts_install_cth]}].
all() ->
- [app_test, appup_test].
+ [app_test, appup_test, assert_test, {group,upgrade}].
groups() ->
- [].
+ [{upgrade,[minor_upgrade,major_upgrade]}].
init_per_suite(Config) ->
Config.
@@ -48,9 +41,13 @@ init_per_suite(Config) ->
end_per_suite(_Config) ->
ok.
+init_per_group(upgrade, Config) ->
+ ct_release_test:init(Config);
init_per_group(_GroupName, Config) ->
Config.
+end_per_group(upgrade, Config) ->
+ ct_release_test:cleanup(Config);
end_per_group(_GroupName, Config) ->
Config.
@@ -165,3 +162,91 @@ check_appup([Vsn|Vsns],Instrs,Expected) ->
end;
check_appup([],_,_) ->
ok.
+
+
+minor_upgrade(Config) ->
+ ct_release_test:upgrade(stdlib,minor,{?MODULE,[]},Config).
+
+major_upgrade(Config) ->
+ ct_release_test:upgrade(stdlib,major,{?MODULE,[]},Config).
+
+%% Version numbers are checked by ct_release_test, so there is nothing
+%% more to check here...
+upgrade_init(CtData,State) ->
+ {ok,{FromVsn,ToVsn}} = ct_release_test:get_app_vsns(CtData,stdlib),
+ case ct_release_test:get_appup(CtData,stdlib) of
+ {ok,{FromVsn,ToVsn,[restart_new_emulator],[restart_new_emulator]}} ->
+ io:format("Upgrade/downgrade ~p <--> ~p",[FromVsn,ToVsn]);
+ {error,{vsn_not_found,_}} when FromVsn==ToVsn ->
+ io:format("No upgrade test for stdlib, same version")
+ end,
+ State.
+upgrade_upgraded(_CtData,State) ->
+ State.
+upgrade_downgraded(_CtData,State) ->
+ State.
+
+
+-include_lib("stdlib/include/assert.hrl").
+-include_lib("stdlib/include/assert.hrl"). % test repeated inclusion
+assert_test(suite) ->
+ [];
+assert_test(doc) ->
+ ["Assert macros test."];
+assert_test(_Config) ->
+ ok = ?assert(true),
+ {'EXIT',{{assert, _},_}} = (catch ?assert(false)),
+ {'EXIT',{{assert, Info1},_}} = (catch ?assert(0)),
+ {not_boolean,0} = lists:keyfind(not_boolean,1,Info1),
+
+ ok = ?assertNot(false),
+ {'EXIT',{{assert, _},_}} = (catch ?assertNot(true)),
+ {'EXIT',{{assert, Info2},_}} = (catch ?assertNot(0)),
+ {not_boolean,0} = lists:keyfind(not_boolean,1,Info2),
+
+ ok = ?assertMatch({foo,_}, {foo,bar}),
+ {'EXIT',{{assertMatch,_},_}} =
+ (catch ?assertMatch({foo,_}, {foo})),
+
+ ok = ?assertMatch({foo,N} when N > 0, {foo,1}),
+ {'EXIT',{{assertMatch,_},_}} =
+ (catch ?assertMatch({foo,N} when N > 0, {foo,0})),
+
+ ok = ?assertNotMatch({foo,_}, {foo,bar,baz}),
+ {'EXIT',{{assertNotMatch,_},_}} =
+ (catch ?assertNotMatch({foo,_}, {foo,baz})),
+
+ ok = ?assertNotMatch({foo,N} when N > 0, {foo,0}),
+ {'EXIT',{{assertNotMatch,_},_}} =
+ (catch ?assertNotMatch({foo,N} when N > 0, {foo,1})),
+
+ ok = ?assertEqual(1.0, 1.0),
+ {'EXIT',{{assertEqual,_},_}} = (catch ?assertEqual(1, 1.0)),
+
+ ok = ?assertNotEqual(1, 1.0),
+ {'EXIT',{{assertNotEqual,_},_}} = (catch ?assertNotEqual(1.0, 1.0)),
+
+ ok = ?assertException(error, badarith, 1/0),
+ ok = ?assertException(exit, foo, exit(foo)),
+ ok = ?assertException(throw, foo, throw(foo)),
+ ok = ?assertException(throw, {foo,_}, throw({foo,bar})),
+ ok = ?assertException(throw, {foo,N} when N > 0, throw({foo,1})),
+ {'EXIT',{{assertException,Why1},_}} =
+ (catch ?assertException(error, badarith, 0/1)),
+ true = lists:keymember(unexpected_success,1,Why1),
+ {'EXIT',{{assertException,Why2},_}} =
+ (catch ?assertException(error, badarith, 1/length(0))),
+ true = lists:keymember(unexpected_exception,1,Why2),
+ {'EXIT',{{assertException,Why3},_}} =
+ (catch ?assertException(throw, {foo,N} when N > 0, throw({foo,0}))),
+ true = lists:keymember(unexpected_exception,1,Why3),
+
+ ok = ?assertNotException(throw, {foo,baz}, throw({foo,bar})),
+ {'EXIT',{{assertNotException,Why4},_}} =
+ (catch ?assertNotException(throw, {foo,bar}, throw({foo,bar}))),
+ true = lists:keymember(unexpected_exception,1,Why4),
+
+ ok = ?assertError(badarith, 1/0),
+ ok = ?assertExit(foo, exit(foo)),
+ ok = ?assertThrow(foo, throw(foo)),
+ ok.
diff --git a/lib/stdlib/test/string_SUITE.erl b/lib/stdlib/test/string_SUITE.erl
index fccd1bef95..e9ea2e3522 100644
--- a/lib/stdlib/test/string_SUITE.erl
+++ b/lib/stdlib/test/string_SUITE.erl
@@ -120,7 +120,7 @@ chr_rchr(suite) ->
chr_rchr(doc) ->
[];
chr_rchr(Config) when is_list(Config) ->
- ?line {_,_,X} = now(),
+ {_,_,X} = erlang:timestamp(),
?line 0 = string:chr("", (X rem (255-32)) + 32),
?line 0 = string:rchr("", (X rem (255-32)) + 32),
?line 1 = string:chr("x", $x),
@@ -144,7 +144,7 @@ str_rstr(suite) ->
str_rstr(doc) ->
[];
str_rstr(Config) when is_list(Config) ->
- ?line {_,_,X} = now(),
+ {_,_,X} = erlang:timestamp(),
?line 0 = string:str("", [(X rem (255-32)) + 32]),
?line 0 = string:rstr("", [(X rem (255-32)) + 32]),
?line 1 = string:str("x", "x"),
@@ -217,21 +217,39 @@ substr(Config) when is_list(Config) ->
?line {'EXIT',_} = (catch string:substr("1234", "1")),
ok.
-tokens(suite) ->
- [];
-tokens(doc) ->
- [];
tokens(Config) when is_list(Config) ->
- ?line [] = string:tokens("",""),
- ?line [] = string:tokens("abc","abc"),
- ?line ["abc"] = string:tokens("abc", ""),
- ?line ["1","2 34","4","5"] = string:tokens("1,2 34,4;5", ";,"),
- %% invalid arg type
- ?line {'EXIT',_} = (catch string:tokens('x,y', ",")),
+ [] = string:tokens("",""),
+ [] = string:tokens("abc","abc"),
+ ["abc"] = string:tokens("abc", ""),
+ ["1","2 34","45","5","6","7"] = do_tokens("1,2 34,45;5,;6;,7", ";,"),
+
%% invalid arg type
- ?line {'EXIT',_} = (catch string:tokens("x,y", ',')),
+ {'EXIT',_} = (catch string:tokens('x,y', ",")),
+ {'EXIT',_} = (catch string:tokens("x,y", ',')),
ok.
+do_tokens(S0, Sep0) ->
+ [H|T] = Sep0,
+ S = [replace_sep(C, T, H) || C <- S0],
+ Sep = [H],
+ io:format("~p ~p\n", [S0,Sep0]),
+ io:format("~p ~p\n", [S,Sep]),
+
+ Res = string:tokens(S0, Sep0),
+ Res = string:tokens(Sep0++S0, Sep0),
+ Res = string:tokens(S0++Sep0, Sep0),
+
+ Res = string:tokens(S, Sep),
+ Res = string:tokens(Sep++S, Sep),
+ Res = string:tokens(S++Sep, Sep),
+
+ Res.
+
+replace_sep(C, Seps, New) ->
+ case lists:member(C, Seps) of
+ true -> New;
+ false -> C
+ end.
chars(suite) ->
[];
diff --git a/lib/stdlib/test/supervisor_SUITE.erl b/lib/stdlib/test/supervisor_SUITE.erl
index 836ea7c030..31d4b44f30 100644
--- a/lib/stdlib/test/supervisor_SUITE.erl
+++ b/lib/stdlib/test/supervisor_SUITE.erl
@@ -37,9 +37,13 @@
sup_start_ignore_child/1, sup_start_ignore_temporary_child/1,
sup_start_ignore_temporary_child_start_child/1,
sup_start_ignore_temporary_child_start_child_simple/1,
- sup_start_error_return/1, sup_start_fail/1, sup_stop_infinity/1,
- sup_stop_timeout/1, sup_stop_brutal_kill/1, child_adm/1,
- child_adm_simple/1, child_specs/1, extra_return/1]).
+ sup_start_ignore_permanent_child_start_child_simple/1,
+ sup_start_error_return/1, sup_start_fail/1,
+ sup_start_map/1, sup_start_map_simple/1,
+ sup_start_map_faulty_specs/1,
+ sup_stop_infinity/1, sup_stop_timeout/1, sup_stop_brutal_kill/1,
+ child_adm/1, child_adm_simple/1, child_specs/1, extra_return/1,
+ sup_flags/1]).
%% Tests concept permanent, transient and temporary
-export([ permanent_normal/1, transient_normal/1,
@@ -51,7 +55,8 @@
temporary_abnormal/1, temporary_bystander/1]).
%% Restart strategy tests
--export([ one_for_one/1,
+-export([ multiple_restarts/1,
+ one_for_one/1,
one_for_one_escalation/1, one_for_all/1,
one_for_all_escalation/1, one_for_all_other_child_fails_restart/1,
simple_one_for_one/1, simple_one_for_one_escalation/1,
@@ -65,7 +70,8 @@
do_not_save_child_specs_for_temporary_children/1,
simple_one_for_one_scale_many_temporary_children/1,
simple_global_supervisor/1, hanging_restart_loop/1,
- hanging_restart_loop_simple/1]).
+ hanging_restart_loop_simple/1, code_change/1, code_change_map/1,
+ code_change_simple/1, code_change_simple_map/1]).
%%-------------------------------------------------------------------------
@@ -73,8 +79,9 @@ suite() ->
[{ct_hooks,[ts_install_cth]}].
all() ->
- [{group, sup_start}, {group, sup_stop}, child_adm,
- child_adm_simple, extra_return, child_specs,
+ [{group, sup_start}, {group, sup_start_map}, {group, sup_stop}, child_adm,
+ child_adm_simple, extra_return, child_specs, sup_flags,
+ multiple_restarts,
{group, restart_one_for_one},
{group, restart_one_for_all},
{group, restart_simple_one_for_one},
@@ -85,7 +92,8 @@ all() ->
count_children, do_not_save_start_parameters_for_temporary_children,
do_not_save_child_specs_for_temporary_children,
simple_one_for_one_scale_many_temporary_children, temporary_bystander,
- simple_global_supervisor, hanging_restart_loop, hanging_restart_loop_simple].
+ simple_global_supervisor, hanging_restart_loop, hanging_restart_loop_simple,
+ code_change, code_change_map, code_change_simple, code_change_simple_map].
groups() ->
[{sup_start, [],
@@ -93,7 +101,10 @@ groups() ->
sup_start_ignore_child, sup_start_ignore_temporary_child,
sup_start_ignore_temporary_child_start_child,
sup_start_ignore_temporary_child_start_child_simple,
+ sup_start_ignore_permanent_child_start_child_simple,
sup_start_error_return, sup_start_fail]},
+ {sup_start_map, [],
+ [sup_start_map, sup_start_map_simple, sup_start_map_faulty_specs]},
{sup_stop, [],
[sup_stop_infinity, sup_stop_timeout,
sup_stop_brutal_kill]},
@@ -242,6 +253,27 @@ sup_start_ignore_temporary_child_start_child_simple(Config)
[1,1,0,1] = get_child_counts(sup_test).
%%-------------------------------------------------------------------------
+%% Tests what happens if child's init-callback returns ignore for a
+%% permanent child when child is started with start_child/2, and the
+%% supervisor is simple_one_for_one.
+%% Child spec shall NOT be saved!!!
+sup_start_ignore_permanent_child_start_child_simple(Config)
+ when is_list(Config) ->
+ process_flag(trap_exit, true),
+ Child1 = {child1, {supervisor_1, start_child, [ignore]},
+ permanent, 1000, worker, []},
+ {ok, Pid} = start_link({ok, {{simple_one_for_one, 2, 3600}, [Child1]}}),
+
+ {ok, undefined} = supervisor:start_child(sup_test, []),
+ {ok, CPid2} = supervisor:start_child(sup_test, []),
+
+ [{undefined, CPid2, worker, []}] = supervisor:which_children(sup_test),
+ [1,1,0,1] = get_child_counts(sup_test),
+
+ %% Regression test: check that the supervisor terminates without error.
+ exit(Pid, shutdown),
+ check_exit_reason(Pid, shutdown).
+%%-------------------------------------------------------------------------
%% Tests what happens if init-callback returns a invalid value.
sup_start_error_return(Config) when is_list(Config) ->
process_flag(trap_exit, true),
@@ -256,6 +288,84 @@ sup_start_fail(Config) when is_list(Config) ->
check_exit_reason(Term).
%%-------------------------------------------------------------------------
+%% Tests that the supervisor process starts correctly with map
+%% startspec, and that the full childspec can be read.
+sup_start_map(Config) when is_list(Config) ->
+ process_flag(trap_exit, true),
+ Child1 = #{id=>child1, start=>{supervisor_1, start_child, []}},
+ Child2 = #{id=>child2,
+ start=>{supervisor_1, start_child, []},
+ shutdown=>brutal_kill},
+ Child3 = #{id=>child3,
+ start=>{supervisor_1, start_child, []},
+ type=>supervisor},
+ {ok, Pid} = start_link({ok, {#{}, [Child1,Child2,Child3]}}),
+
+ %% Check default values
+ {ok,#{id:=child1,
+ start:={supervisor_1,start_child,[]},
+ restart:=permanent,
+ shutdown:=5000,
+ type:=worker,
+ modules:=[supervisor_1]}} = supervisor:get_childspec(Pid, child1),
+ {ok,#{id:=child2,
+ start:={supervisor_1,start_child,[]},
+ restart:=permanent,
+ shutdown:=brutal_kill,
+ type:=worker,
+ modules:=[supervisor_1]}} = supervisor:get_childspec(Pid, child2),
+ {ok,#{id:=child3,
+ start:={supervisor_1,start_child,[]},
+ restart:=permanent,
+ shutdown:=infinity,
+ type:=supervisor,
+ modules:=[supervisor_1]}} = supervisor:get_childspec(Pid, child3),
+ {error,not_found} = supervisor:get_childspec(Pid, child4),
+ terminate(Pid, shutdown).
+
+%%-------------------------------------------------------------------------
+%% Tests that the supervisor process starts correctly with map
+%% startspec, and that the full childspec can be read when using
+%% simple_one_for_one strategy.
+sup_start_map_simple(Config) when is_list(Config) ->
+ process_flag(trap_exit, true),
+ SupFlags = #{strategy=>simple_one_for_one},
+ ChildSpec = #{id=>undefined,
+ start=>{supervisor_1, start_child, []},
+ restart=>temporary},
+ {ok, Pid} = start_link({ok, {SupFlags, [ChildSpec]}}),
+
+ {ok, Child1} = supervisor:start_child(Pid, []),
+ {ok, Child2} = supervisor:start_child(Pid, []),
+ {ok, Child3} = supervisor:start_child(Pid, []),
+
+ Spec = ChildSpec#{type=>worker, shutdown=>5000, modules=>[supervisor_1]},
+
+ {ok, Spec} = supervisor:get_childspec(Pid, Child1),
+ {ok, Spec} = supervisor:get_childspec(Pid, Child2),
+ {ok, Spec} = supervisor:get_childspec(Pid, Child3),
+ {error,not_found} = supervisor:get_childspec(Pid, self()),
+ terminate(Pid, shutdown).
+
+%%-------------------------------------------------------------------------
+%% Tests that the supervisor produces good error messages when start-
+%% and child specs are faulty.
+sup_start_map_faulty_specs(Config) when is_list(Config) ->
+ process_flag(trap_exit, true),
+ Child1 = #{start=>{supervisor_1, start_child, []}},
+ Child2 = #{id=>child2},
+ Child3 = #{id=>child3,
+ start=>{supervisor_1, start_child, []},
+ silly_flag=>true},
+ Child4 = child4,
+ {error,{start_spec,missing_id}} = start_link({ok, {#{}, [Child1]}}),
+ {error,{start_spec,missing_start}} = start_link({ok, {#{}, [Child2]}}),
+ {ok,Pid} = start_link({ok, {#{}, [Child3]}}),
+ terminate(Pid,shutdown),
+ {error,{start_spec,{invalid_child_spec,child4}}} =
+ start_link({ok, {#{}, [Child4]}}).
+
+%%-------------------------------------------------------------------------
%% See sup_stop/1 when Shutdown = infinity, this walue is allowed for
%% children of type supervisor _AND_ worker.
sup_stop_infinity(Config) when is_list(Config) ->
@@ -479,7 +589,7 @@ child_adm_simple(Config) when is_list(Config) ->
%% Tests child specs, invalid formats should be rejected.
child_specs(Config) when is_list(Config) ->
process_flag(trap_exit, true),
- {ok, _Pid} = start_link({ok, {{one_for_one, 2, 3600}, []}}),
+ {ok, Pid} = start_link({ok, {{one_for_one, 2, 3600}, []}}),
{error, _} = supervisor:start_child(sup_test, hej),
%% Bad child specs
@@ -509,6 +619,7 @@ child_specs(Config) when is_list(Config) ->
{error, {invalid_modules,dy}}
= supervisor:start_child(sup_test, B5),
+ {error, {badarg, _}} = supervisor:check_childspecs(B1), % should be list
{error, {invalid_mfa,mfa}} = supervisor:check_childspecs([B1]),
{error, {invalid_restart_type,prmanent}} =
supervisor:check_childspecs([B2]),
@@ -524,6 +635,54 @@ child_specs(Config) when is_list(Config) ->
ok = supervisor:check_childspecs([C3]),
ok = supervisor:check_childspecs([C4]),
ok = supervisor:check_childspecs([C5]),
+
+ {error,{duplicate_child_name,child}} = supervisor:check_childspecs([C1,C2]),
+
+ terminate(Pid, shutdown),
+
+ %% Faulty child specs in supervisor start
+ {error, {start_spec, {invalid_mfa, mfa}}} =
+ start_link({ok, {{one_for_one, 2, 3600}, [B1]}}),
+ {error, {start_spec, {invalid_restart_type, prmanent}}} =
+ start_link({ok, {{simple_one_for_one, 2, 3600}, [B2]}}),
+
+ %% simple_one_for_one needs exactly one child
+ {error,{bad_start_spec,[]}} =
+ start_link({ok, {{simple_one_for_one, 2, 3600}, []}}),
+ {error,{bad_start_spec,[C1,C2]}} =
+ start_link({ok, {{simple_one_for_one, 2, 3600}, [C1,C2]}}),
+
+ ok.
+
+%%-------------------------------------------------------------------------
+%% Test error handling of supervisor flags
+sup_flags(_Config) ->
+ process_flag(trap_exit,true),
+ {error,{supervisor_data,{invalid_strategy,_}}} =
+ start_link({ok, {{none_for_one, 2, 3600}, []}}),
+ {error,{supervisor_data,{invalid_strategy,_}}} =
+ start_link({ok, {#{strategy=>none_for_one}, []}}),
+ {error,{supervisor_data,{invalid_intensity,_}}} =
+ start_link({ok, {{one_for_one, infinity, 3600}, []}}),
+ {error,{supervisor_data,{invalid_intensity,_}}} =
+ start_link({ok, {#{intensity=>infinity}, []}}),
+ {error,{supervisor_data,{invalid_period,_}}} =
+ start_link({ok, {{one_for_one, 2, 0}, []}}),
+ {error,{supervisor_data,{invalid_period,_}}} =
+ start_link({ok, {#{period=>0}, []}}),
+ {error,{supervisor_data,{invalid_period,_}}} =
+ start_link({ok, {{one_for_one, 2, infinity}, []}}),
+ {error,{supervisor_data,{invalid_period,_}}} =
+ start_link({ok, {#{period=>infinity}, []}}),
+
+ %% SupFlags other than a map or a 3-tuple
+ {error,{supervisor_data,{invalid_type,_}}} =
+ start_link({ok, {{one_for_one, 2}, []}}),
+
+ %% Unexpected flags are ignored
+ {ok,Pid} = start_link({ok,{#{silly_flag=>true},[]}}),
+ terminate(Pid,shutdown),
+
ok.
%%-------------------------------------------------------------------------
@@ -764,6 +923,39 @@ temporary_bystander(_Config) ->
[{child1, _, _, _}] = supervisor:which_children(SupPid2).
%%-------------------------------------------------------------------------
+%% Test restarting a process multiple times, being careful not
+%% to exceed the maximum restart frquency.
+multiple_restarts(Config) when is_list(Config) ->
+ process_flag(trap_exit, true),
+ Child1 = #{id => child1,
+ start => {supervisor_1, start_child, []},
+ restart => permanent,
+ shutdown => brutal_kill,
+ type => worker,
+ modules => []},
+ SupFlags = #{strategy => one_for_one,
+ intensity => 1,
+ period => 1},
+ {ok, SupPid} = start_link({ok, {SupFlags, []}}),
+ {ok, CPid1} = supervisor:start_child(sup_test, Child1),
+
+ %% Terminate the process several times, but being careful
+ %% not to exceed the maximum restart intensity.
+ terminate(SupPid, CPid1, child1, abnormal),
+ _ = [begin
+ receive after 2100 -> ok end,
+ [{_, Pid, _, _}|_] = supervisor:which_children(sup_test),
+ terminate(SupPid, Pid, child1, abnormal)
+ end || _ <- [1,2,3]],
+
+ %% Verify that the supervisor is still alive and clean up.
+ ok = supervisor:terminate_child(SupPid, child1),
+ ok = supervisor:delete_child(SupPid, child1),
+ exit(SupPid, kill),
+ ok.
+
+
+%%-------------------------------------------------------------------------
%% Test the one_for_one base case.
one_for_one(Config) when is_list(Config) ->
process_flag(trap_exit, true),
@@ -1647,6 +1839,186 @@ hanging_restart_loop_simple(Config) when is_list(Config) ->
ok.
%%-------------------------------------------------------------------------
+%% Test the code_change function
+code_change(_Config) ->
+ process_flag(trap_exit, true),
+
+ SupFlags = {one_for_one, 0, 1},
+ {ok, Pid} = start_link({ok, {SupFlags, []}}),
+ [] = supervisor:which_children(Pid),
+
+ %% Change supervisor flags
+ S1 = sys:get_state(Pid),
+ ok = fake_upgrade(Pid,{ok, {{one_for_one, 1, 3}, []}}),
+ S2 = sys:get_state(Pid),
+ true = (S1 /= S2),
+
+ %% Faulty childspec
+ FaultyChild = {child1, permanent, brutal_kill, worker, []}, % missing start
+ {error,{error,{invalid_child_spec,FaultyChild}}} =
+ fake_upgrade(Pid,{ok,{SupFlags,[FaultyChild]}}),
+
+ %% Add child1 and child2
+ Child1 = {child1, {supervisor_1, start_child, []},
+ permanent, 2000, worker, []},
+ Child2 = {child2, {supervisor_1, start_child, []},
+ permanent, brutal_kill, worker, []},
+ ok = fake_upgrade(Pid,{ok,{SupFlags,[Child1,Child2]}}),
+ %% Children are not automatically started
+ {ok,_} = supervisor:restart_child(Pid,child1),
+ {ok,_} = supervisor:restart_child(Pid,child2),
+ [{child2,_,_,_},{child1,_,_,_}] = supervisor:which_children(Pid),
+
+ %% Change child1, remove child2 and add child3
+ Child11 = {child1, {supervisor_1, start_child, []},
+ permanent, 1000, worker, []},
+ Child3 = {child3, {supervisor_1, start_child, []},
+ permanent, brutal_kill, worker, []},
+ ok = fake_upgrade(Pid,{ok, {SupFlags, [Child11,Child3]}}),
+ %% Children are not deleted on upgrade, so it is ok that child2 is
+ %% still here
+ [{child2,_,_,_},{child3,_,_,_},{child1,_,_,_}] =
+ supervisor:which_children(Pid),
+
+ %% Ignore during upgrade
+ ok = fake_upgrade(Pid,ignore),
+
+ %% Error during upgrade
+ {error, faulty_return} = fake_upgrade(Pid,faulty_return),
+
+ %% Faulty flags
+ {error,{error, {invalid_intensity,faulty_intensity}}} =
+ fake_upgrade(Pid,{ok, {{one_for_one,faulty_intensity,1}, []}}),
+ {error,{error,{bad_flags, faulty_flags}}} =
+ fake_upgrade(Pid,{ok, {faulty_flags, []}}),
+
+ terminate(Pid,shutdown).
+
+code_change_map(_Config) ->
+ process_flag(trap_exit, true),
+
+ {ok, Pid} = start_link({ok, {#{}, []}}),
+ [] = supervisor:which_children(Pid),
+
+ %% Change supervisor flags
+ S1 = sys:get_state(Pid),
+ ok = fake_upgrade(Pid,{ok, {#{intensity=>1, period=>3}, []}}),
+ S2 = sys:get_state(Pid),
+ true = (S1 /= S2),
+
+ %% Faulty childspec
+ FaultyChild = #{id=>faulty_child},
+ {error,{error,missing_start}} =
+ fake_upgrade(Pid,{ok,{#{},[FaultyChild]}}),
+
+ %% Add child1 and child2
+ Child1 = #{id=>child1,
+ start=>{supervisor_1, start_child, []},
+ shutdown=>2000},
+ Child2 = #{id=>child2,
+ start=>{supervisor_1, start_child, []}},
+ ok = fake_upgrade(Pid,{ok,{#{},[Child1,Child2]}}),
+ %% Children are not automatically started
+ {ok,_} = supervisor:restart_child(Pid,child1),
+ {ok,_} = supervisor:restart_child(Pid,child2),
+ [{child2,_,_,_},{child1,_,_,_}] = supervisor:which_children(Pid),
+ {ok,#{shutdown:=2000}} = supervisor:get_childspec(Pid,child1),
+
+ %% Change child1, remove child2 and add child3
+ Child11 = #{id=>child1,
+ start=>{supervisor_1, start_child, []},
+ shutdown=>1000},
+ Child3 = #{id=>child3,
+ start=>{supervisor_1, start_child, []}},
+ ok = fake_upgrade(Pid,{ok, {#{}, [Child11,Child3]}}),
+ %% Children are not deleted on upgrade, so it is ok that child2 is
+ %% still here
+ [{child2,_,_,_},{child3,_,_,_},{child1,_,_,_}] =
+ supervisor:which_children(Pid),
+ {ok,#{shutdown:=1000}} = supervisor:get_childspec(Pid,child1),
+
+ %% Ignore during upgrade
+ ok = fake_upgrade(Pid,ignore),
+
+ %% Error during upgrade
+ {error, faulty_return} = fake_upgrade(Pid,faulty_return),
+
+ %% Faulty flags
+ {error,{error, {invalid_intensity,faulty_intensity}}} =
+ fake_upgrade(Pid,{ok, {#{intensity=>faulty_intensity}, []}}),
+
+ terminate(Pid,shutdown).
+
+code_change_simple(_Config) ->
+ process_flag(trap_exit, true),
+
+ SimpleChild1 = {child1,{supervisor_1, start_child, []}, permanent,
+ brutal_kill, worker, []},
+ SimpleFlags = {simple_one_for_one, 0, 1},
+ {ok, SimplePid} = start_link({ok, {SimpleFlags,[SimpleChild1]}}),
+ %% Change childspec
+ SimpleChild11 = {child1,{supervisor_1, start_child, []}, permanent,
+ 1000, worker, []},
+ ok = fake_upgrade(SimplePid,{ok,{SimpleFlags,[SimpleChild11]}}),
+
+ %% Attempt to add child
+ SimpleChild2 = {child2,{supervisor_1, start_child, []}, permanent,
+ brutal_kill, worker, []},
+
+ {error, {error, {ok,[_,_]}}} =
+ fake_upgrade(SimplePid,{ok,{SimpleFlags,[SimpleChild1,SimpleChild2]}}),
+
+ %% Attempt to remove child
+ {error, {error, {ok,[]}}} = fake_upgrade(SimplePid,{ok,{SimpleFlags,[]}}),
+
+ terminate(SimplePid,shutdown),
+ ok.
+
+code_change_simple_map(_Config) ->
+ process_flag(trap_exit, true),
+
+ SimpleChild1 = #{id=>child1,
+ start=>{supervisor_1, start_child, []}},
+ SimpleFlags = #{strategy=>simple_one_for_one},
+ {ok, SimplePid} = start_link({ok, {SimpleFlags,[SimpleChild1]}}),
+ %% Change childspec
+ SimpleChild11 = #{id=>child1,
+ start=>{supervisor_1, start_child, []},
+ shutdown=>1000},
+ ok = fake_upgrade(SimplePid,{ok,{SimpleFlags,[SimpleChild11]}}),
+
+ %% Attempt to add child
+ SimpleChild2 = #{id=>child2,
+ start=>{supervisor_1, start_child, []}},
+ {error, {error, {ok, [_,_]}}} =
+ fake_upgrade(SimplePid,{ok,{SimpleFlags,[SimpleChild1,SimpleChild2]}}),
+
+ %% Attempt to remove child
+ {error, {error, {ok, []}}} =
+ fake_upgrade(SimplePid,{ok,{SimpleFlags,[]}}),
+
+ terminate(SimplePid,shutdown),
+ ok.
+
+fake_upgrade(Pid,NewInitReturn) ->
+ ok = sys:suspend(Pid),
+
+ %% Update state to fake code change
+ %% The #state record in supervisor.erl holds the arguments given
+ %% to the callback init function. By replacing these arguments the
+ %% init function will return something new and by that fake a code
+ %% change (see init function above in this module).
+ Fun = fun(State) ->
+ Size = size(State), % 'args' is the last field in #state.
+ setelement(Size,State,NewInitReturn)
+ end,
+ sys:replace_state(Pid,Fun),
+
+ R = sys:change_code(Pid,gen_server,dummy_vsn,[]),
+ ok = sys:resume(Pid),
+ R.
+
+%%-------------------------------------------------------------------------
terminate(Pid, Reason) when Reason =/= supervisor ->
terminate(dummy, Pid, dummy, Reason).
diff --git a/lib/stdlib/test/sys_SUITE.erl b/lib/stdlib/test/sys_SUITE.erl
index f38bc87ae5..047ee9f1fa 100644
--- a/lib/stdlib/test/sys_SUITE.erl
+++ b/lib/stdlib/test/sys_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
@@ -202,14 +202,7 @@ spec_proc(Mod) ->
{Mod,system_get_state},{throw,fail}},_}} ->
ok
end,
- Mod:stop(),
- WaitForUnregister = fun W() ->
- case whereis(Mod) of
- undefined -> ok;
- _ -> timer:sleep(10), W()
- end
- end,
- WaitForUnregister(),
+ ok = sys:terminate(Mod, normal),
{ok,_} = Mod:start_link(4),
ok = case catch sys:replace_state(Mod, fun(_) -> {} end) of
{} ->
@@ -218,8 +211,7 @@ spec_proc(Mod) ->
{Mod,system_replace_state},{throw,fail}},_}} ->
ok
end,
- Mod:stop(),
- WaitForUnregister(),
+ ok = sys:terminate(Mod, normal),
{ok,_} = Mod:start_link(4),
StateFun = fun(_) -> error(fail) end,
ok = case catch sys:replace_state(Mod, StateFun) of
@@ -231,7 +223,7 @@ spec_proc(Mod) ->
{'EXIT',{{callback_failed,StateFun,{error,fail}},_}} ->
ok
end,
- Mod:stop().
+ ok = sys:terminate(Mod, normal).
%%%%%%%%%%%%%%%%%%%%
%% Dummy server
diff --git a/lib/stdlib/test/sys_sp1.erl b/lib/stdlib/test/sys_sp1.erl
index e84ffcfa12..0fb288991f 100644
--- a/lib/stdlib/test/sys_sp1.erl
+++ b/lib/stdlib/test/sys_sp1.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
@@ -17,7 +17,7 @@
%% %CopyrightEnd%
%%
-module(sys_sp1).
--export([start_link/1, stop/0]).
+-export([start_link/1]).
-export([alloc/0, free/1]).
-export([init/1]).
-export([system_continue/3, system_terminate/4,
@@ -31,10 +31,6 @@
start_link(NumCh) ->
proc_lib:start_link(?MODULE, init, [[self(),NumCh]]).
-stop() ->
- ?MODULE ! stop,
- ok.
-
alloc() ->
?MODULE ! {self(), alloc},
receive
@@ -70,11 +66,7 @@ loop(Chs, Parent, Deb) ->
loop(Chs2, Parent, Deb2);
{system, From, Request} ->
sys:handle_system_msg(Request, From, Parent,
- ?MODULE, Deb, Chs);
- stop ->
- sys:handle_debug(Deb, fun write_debug/3,
- ?MODULE, {in, stop}),
- ok
+ ?MODULE, Deb, Chs)
end.
system_continue(Parent, Deb, Chs) ->
diff --git a/lib/stdlib/test/sys_sp2.erl b/lib/stdlib/test/sys_sp2.erl
index 56a5e4d071..a0847b5838 100644
--- a/lib/stdlib/test/sys_sp2.erl
+++ b/lib/stdlib/test/sys_sp2.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
@@ -17,7 +17,7 @@
%% %CopyrightEnd%
%%
-module(sys_sp2).
--export([start_link/1, stop/0]).
+-export([start_link/1]).
-export([alloc/0, free/1]).
-export([init/1]).
-export([system_continue/3, system_terminate/4,
@@ -30,10 +30,6 @@
start_link(NumCh) ->
proc_lib:start_link(?MODULE, init, [[self(),NumCh]]).
-stop() ->
- ?MODULE ! stop,
- ok.
-
alloc() ->
?MODULE ! {self(), alloc},
receive
@@ -45,11 +41,6 @@ free(Ch) ->
?MODULE ! {free, Ch},
ok.
-%% can't use 2-tuple for state here as we do in sys_sp1, since the 2-tuple
-%% is not compatible with the backward compatibility handling for
-%% sys:get_state in sys.erl
--record(state, {alloc,free}).
-
init([Parent,NumCh]) ->
register(?MODULE, self()),
Chs = channels(NumCh),
@@ -74,11 +65,7 @@ loop(Chs, Parent, Deb) ->
loop(Chs2, Parent, Deb2);
{system, From, Request} ->
sys:handle_system_msg(Request, From, Parent,
- ?MODULE, Deb, Chs);
- stop ->
- sys:handle_debug(Deb, fun write_debug/3,
- ?MODULE, {in, stop}),
- ok
+ ?MODULE, Deb, Chs)
end.
system_continue(Parent, Deb, Chs) ->
@@ -91,17 +78,17 @@ write_debug(Dev, Event, Name) ->
io:format(Dev, "~p event = ~p~n", [Name, Event]).
channels(NumCh) ->
- #state{alloc=[], free=lists:seq(1,NumCh)}.
+ {_Allocated=[], _Free=lists:seq(1,NumCh)}.
-alloc(#state{free=[]}=Channels) ->
- {{error, "no channels available"}, Channels};
-alloc(#state{alloc=Allocated, free=[H|T]}) ->
- {H, #state{alloc=[H|Allocated], free=T}}.
+alloc({_, []}) ->
+ {error, "no channels available"};
+alloc({Allocated, [H|T]}) ->
+ {H, {[H|Allocated], T}}.
-free(Ch, #state{alloc=Alloc, free=Free}=Channels) ->
+free(Ch, {Alloc, Free}=Channels) ->
case lists:member(Ch, Alloc) of
true ->
- #state{alloc=lists:delete(Ch, Alloc), free=[Ch|Free]};
+ {lists:delete(Ch, Alloc), [Ch|Free]};
false ->
Channels
end.
diff --git a/lib/stdlib/test/tar_SUITE.erl b/lib/stdlib/test/tar_SUITE.erl
index 9b6d65011e..3b54cd0f34 100644
--- a/lib/stdlib/test/tar_SUITE.erl
+++ b/lib/stdlib/test/tar_SUITE.erl
@@ -89,7 +89,7 @@ borderline_test(Size, TempDir) ->
?line io:format("Testing size ~p", [Size]),
%% Create a file and archive it.
- ?line {_, _, X0} = erlang:now(),
+ X0 = erlang:monotonic_time(),
?line file:write_file(Name, random_byte_list(X0, Size)),
?line ok = erl_tar:create(Archive, [Name]),
?line ok = file:delete(Name),
diff --git a/lib/stdlib/test/timer_SUITE.erl b/lib/stdlib/test/timer_SUITE.erl
index bea2b3fb2a..ae32d98807 100644
--- a/lib/stdlib/test/timer_SUITE.erl
+++ b/lib/stdlib/test/timer_SUITE.erl
@@ -25,14 +25,11 @@
-include_lib("test_server/include/test_server.hrl").
-%% Test suite for timer module. This is a really nasty test it runs a
-%% lot of timeouts and then checks in the end if any of them was
-%% trigggered too early or if any late timeouts was much too
-%% late. What should be added is more testing of the interface
-%% functions I guess. But I don't have time for that now.
+%% Random test of the timer module. This is a really nasty test, as it
+%% runs a lot of timeouts and then checks in the end if any of them
+%% was triggered too early or if any late timeouts was much too late.
%%
-%% Expect it to run for at least 5-10 minutes!
-
+%% Running time on average is about 90 seconds.
%% The main test case in this module is "do_big_test", which
%% orders a large number of timeouts and measures how
@@ -40,15 +37,8 @@
%% also a number of other concurrent processes running "nrev" at the same
%% time. The result is analyzed afterwards by trying to check if the
%% measured values are reasonable. It is hard to determine what is
-%% reasonable on different machines therefore the test can sometimes
-%% fail, even though the timer module is ok. I have checked against
-%% previous versions of the timer module (which contained bugs) and it
-%% seems it fails every time when running the buggy timer modules.
-%%
-%% The solution is to rewrite the test suite. Possible strategies for a
-%% rewrite: smarter math on the measuring data, test cases with varying
-%% amount of load. The test suite should also include tests that test the
-%% interface of the timer module.
+%% reasonable on different machines; therefore the test can sometimes
+%% fail, even though the timer module is ok.
suite() -> [{ct_hooks,[ts_install_cth]}].
@@ -89,10 +79,7 @@ report_result(Error) -> ?line test_server:fail(Error).
big_test(N) ->
C = start_collect(),
system_time(), system_time(), system_time(),
- A1 = element(2, erlang:now()),
- A2 = A1 * 3,
- A3 = element(3, erlang:now()),
- random:seed(A1, A2, A3),
+ random:seed(erlang:timestamp()),
random:uniform(100),random:uniform(100),random:uniform(100),
big_loop(C, N, []),
@@ -146,7 +133,7 @@ big_loop(C, N, Pids) ->
%%Pids2=Pids1,
%% wait a little while
- timer:sleep(random:uniform(200)*10),
+ timer:sleep(random:uniform(200)*3),
%% spawn zero, one or two nrev to get some load ;-/
Pids3 = start_nrev(Pids2, random:uniform(100)),
@@ -166,14 +153,14 @@ start_nrev(Pids, _N) ->
start_after_test(Pids, C, 1) ->
- TO1 = random:uniform(100)*100,
+ TO1 = random:uniform(100)*47,
[s_a_t(C, TO1)|Pids];
start_after_test(Pids, C, 2) ->
- TO1 = random:uniform(100)*100,
- TO2 = TO1 div random:uniform(3) + 200,
+ TO1 = random:uniform(100)*47,
+ TO2 = TO1 div random:uniform(3) + 101,
[s_a_t(C, TO1),s_a_t(C, TO2)|Pids];
start_after_test(Pids, C, N) ->
- TO1 = random:uniform(100)*100,
+ TO1 = random:uniform(100)*47,
start_after_test([s_a_t(C, TO1)|Pids], C, N-1).
s_a_t(C, TimeOut) ->
@@ -199,7 +186,7 @@ a_t(C, TimeOut) ->
maybe_start_i_test(Pids, C, 1) ->
%% ok do it
- TOI = random:uniform(100)*100,
+ TOI = random:uniform(53)*49,
CountI = random:uniform(10) + 3, % at least 4 times
[spawn_link(timer_SUITE, i_t, [C, TOI, CountI])|Pids];
maybe_start_i_test(Pids, _C, _) ->
@@ -374,9 +361,7 @@ res_combine({error,Es}, [{error,E}|T]) ->
system_time() ->
- %%element(1, statistics(wall_clock)).
- {M,S,U} = erlang:now(),
- 1000000000 * M + 1000 * S + (U div 1000).
+ erlang:monotonic_time(milli_seconds).
%% ------------------------------------------------------- %%
diff --git a/lib/stdlib/test/timer_simple_SUITE.erl b/lib/stdlib/test/timer_simple_SUITE.erl
index dc751aad16..3c7e3c5f25 100644
--- a/lib/stdlib/test/timer_simple_SUITE.erl
+++ b/lib/stdlib/test/timer_simple_SUITE.erl
@@ -374,7 +374,6 @@ performance(Mod) ->
big_test(M) ->
Load_Pids = start_nrev(20, M), % Increase if more load wanted :)
- apply(M, sleep, [9000]),
LPids = spawn_timers(5, M, 10000, 5),
apply(M, sleep, [4000]),
@@ -483,8 +482,7 @@ append([],X) ->
X.
system_time() ->
- {M,S,U} = erlang:now(),
- 1000000*(M*1000000 + S) + U.
+ erlang:monotonic_time(micro_seconds).
%% ------------------------------------------------------- %%
diff --git a/lib/stdlib/test/unicode_SUITE.erl b/lib/stdlib/test/unicode_SUITE.erl
index 10b29d0d28..9f5d485df6 100644
--- a/lib/stdlib/test/unicode_SUITE.erl
+++ b/lib/stdlib/test/unicode_SUITE.erl
@@ -29,7 +29,13 @@
random_lists/1,
roundtrips/1,
latin1/1,
- exceptions/1, binaries_errors/1]).
+ exceptions/1,
+ binaries_errors_limit/1,
+ ex_binaries_errors_utf8/1,
+ ex_binaries_errors_utf16_little/1,
+ ex_binaries_errors_utf16_big/1,
+ ex_binaries_errors_utf32_little/1,
+ ex_binaries_errors_utf32_big/1]).
init_per_testcase(Case, Config) when is_atom(Case), is_list(Config) ->
Dog=?t:timetrap(?t:minutes(20)),
@@ -44,10 +50,17 @@ suite() -> [{ct_hooks,[ts_install_cth]}].
all() ->
[utf8_illegal_sequences_bif,
utf16_illegal_sequences_bif, random_lists, roundtrips,
- latin1, exceptions, binaries_errors].
+ latin1, exceptions,
+ binaries_errors_limit,
+ {group,binaries_errors}].
groups() ->
- [].
+ [{binaries_errors,[parallel],
+ [ex_binaries_errors_utf8,
+ ex_binaries_errors_utf16_little,
+ ex_binaries_errors_utf16_big,
+ ex_binaries_errors_utf32_little,
+ ex_binaries_errors_utf32_big]}].
init_per_suite(Config) ->
Config.
@@ -61,15 +74,11 @@ init_per_group(_GroupName, Config) ->
end_per_group(_GroupName, Config) ->
Config.
-binaries_errors(Config) when is_list(Config) ->
+binaries_errors_limit(Config) when is_list(Config) ->
setlimit(10),
ex_binaries_errors_utf8(Config),
setlimit(default),
- ex_binaries_errors_utf8(Config),
- ex_binaries_errors_utf16_little(Config),
- ex_binaries_errors_utf16_big(Config),
- ex_binaries_errors_utf32_little(Config),
- ex_binaries_errors_utf32_big(Config).
+ ok.
ex_binaries_errors_utf8(Config) when is_list(Config) ->
%% Original smoke test, we should not forget the original offset...
@@ -78,8 +87,9 @@ ex_binaries_errors_utf8(Config) when is_list(Config) ->
%% Now, try with longer binary (trapping)
BrokenPart = list_to_binary(lists:seq(128,255)),
BrokenSz = byte_size(BrokenPart),
+ Seq255 = lists:seq(1,255),
[ begin
- OKList = lists:flatten(lists:duplicate(N,lists:seq(1,255))),
+ OKList = lists:flatten(lists:duplicate(N,Seq255)),
OKBin = unicode:characters_to_binary(OKList),
OKLen = length(OKList),
%% Copy to avoid that the binary get's writable
@@ -102,109 +112,84 @@ ex_binaries_errors_utf8(Config) when is_list(Config) ->
ok.
ex_binaries_errors_utf16_little(Config) when is_list(Config) ->
- BrokenPart = << <<X:16/little>> || X <- lists:seq(16#DC00,16#DFFF) >>,
- BrokenSz = byte_size(BrokenPart),
- [ begin
- OKList = lists:flatten(lists:duplicate(N,lists:seq(1,255))),
- OKBin = unicode:characters_to_binary(OKList,unicode,{utf16,little}),
- OKLen = length(OKList),
- %% Copy to avoid that the binary get's writable
- PartlyBroken = binary:copy(<<OKBin/binary, BrokenPart/binary>>),
- PBSz = byte_size(PartlyBroken),
- {error,OKList,DeepBrokenPart} =
- unicode:characters_to_list(PartlyBroken,{utf16,little}),
- BrokenPart = iolist_to_binary(DeepBrokenPart),
- [ begin
- NewList = lists:nthtail(X, OKList),
- NewSz = byte_size(unicode:characters_to_binary(NewList,unicode,{utf16,little})) +
- BrokenSz,
- Chomped = binary:part(PartlyBroken,PBSz - NewSz, NewSz),
- true = (binary:referenced_byte_size(Chomped) =:= PBSz),
- {error,NewList,DeepBrokenPart2} =
- unicode:characters_to_list(Chomped,{utf16,little}),
- BrokenPart = iolist_to_binary(DeepBrokenPart2)
- end || X <- lists:seq(1,OKLen) ]
- end || N <- lists:seq(1,16,3) ],
- ok.
+ ex_binaries_errors_utf16(little).
+
ex_binaries_errors_utf16_big(Config) when is_list(Config) ->
- BrokenPart = << <<X:16/big>> || X <- lists:seq(16#DC00,16#DFFF) >>,
+ ex_binaries_errors_utf16(big).
+
+ex_binaries_errors_utf16(Endian) ->
+ BrokenSeq = lists:seq(16#DC00, 16#DFFF),
+ BrokenPart = case Endian of
+ little ->
+ << <<X:16/little>> || X <- BrokenSeq >>;
+ big ->
+ << <<X:16/big>> || X <- BrokenSeq >>
+ end,
BrokenSz = byte_size(BrokenPart),
+ Seq255 = lists:seq(1, 255),
[ begin
- OKList = lists:flatten(lists:duplicate(N,lists:seq(1,255))),
- OKBin = unicode:characters_to_binary(OKList,unicode,{utf16,big}),
- OKLen = length(OKList),
- %% Copy to avoid that the binary get's writable
- PartlyBroken = binary:copy(<<OKBin/binary, BrokenPart/binary>>),
+ OKList = lists:append(lists:duplicate(N, Seq255)),
+ OKBin = unicode:characters_to_binary(OKList, unicode, {utf16,Endian}),
+ PartlyBroken = iolist_to_binary([OKBin,BrokenPart]),
PBSz = byte_size(PartlyBroken),
{error,OKList,DeepBrokenPart} =
- unicode:characters_to_list(PartlyBroken,{utf16,big}),
+ unicode:characters_to_list(PartlyBroken, {utf16,Endian}),
BrokenPart = iolist_to_binary(DeepBrokenPart),
- [ begin
- NewList = lists:nthtail(X, OKList),
- NewSz = byte_size(unicode:characters_to_binary(NewList,unicode,{utf16,big})) +
- BrokenSz,
- Chomped = binary:part(PartlyBroken,PBSz - NewSz, NewSz),
- true = (binary:referenced_byte_size(Chomped) =:= PBSz),
- {error,NewList,DeepBrokenPart2} =
- unicode:characters_to_list(Chomped,{utf16,big}),
- BrokenPart = iolist_to_binary(DeepBrokenPart2)
- end || X <- lists:seq(1,OKLen) ]
- end || N <- lists:seq(1,16,3) ],
+ utf16_inner_loop(OKList, BrokenPart, BrokenSz,
+ PartlyBroken, PBSz, Endian)
+ end || N <- lists:seq(1, 16, 3) ],
+ ok.
+
+utf16_inner_loop([_|List], BrokenPart, BrokenSz, PartlyBroken, PBSz, Endian) ->
+ Sz = length(List)*2 + BrokenSz,
+ Chomped = binary:part(PartlyBroken, PBSz - Sz, Sz),
+ true = binary:referenced_byte_size(Chomped) =:= PBSz,
+ {error,List,DeepBrokenPart} =
+ unicode:characters_to_list(Chomped, {utf16,Endian}),
+ BrokenPart = iolist_to_binary(DeepBrokenPart),
+ utf16_inner_loop(List, BrokenPart, BrokenSz, PartlyBroken, PBSz, Endian);
+utf16_inner_loop([], _, _, _, _, _) ->
ok.
ex_binaries_errors_utf32_big(Config) when is_list(Config) ->
- BrokenPart = << <<X:32/big>> || X <- lists:seq(16#DC00,16#DFFF) >>,
- BrokenSz = byte_size(BrokenPart),
- [ begin
- OKList = lists:flatten(lists:duplicate(N,lists:seq(1,255))),
- OKBin = unicode:characters_to_binary(OKList,unicode,{utf32,big}),
- OKLen = length(OKList),
- %% Copy to avoid that the binary get's writable
- PartlyBroken = binary:copy(<<OKBin/binary, BrokenPart/binary>>),
- PBSz = byte_size(PartlyBroken),
- {error,OKList,DeepBrokenPart} =
- unicode:characters_to_list(PartlyBroken,{utf32,big}),
- BrokenPart = iolist_to_binary(DeepBrokenPart),
- [ begin
- NewList = lists:nthtail(X, OKList),
- NewSz = byte_size(unicode:characters_to_binary(NewList,unicode,{utf32,big})) +
- BrokenSz,
- Chomped = binary:part(PartlyBroken,PBSz - NewSz, NewSz),
- true = (binary:referenced_byte_size(Chomped) =:= PBSz),
- {error,NewList,DeepBrokenPart2} =
- unicode:characters_to_list(Chomped,{utf32,big}),
- BrokenPart = iolist_to_binary(DeepBrokenPart2)
- end || X <- lists:seq(1,OKLen) ]
- end || N <- lists:seq(1,16,3) ],
- ok.
+ ex_binaries_errors_utf32(big).
ex_binaries_errors_utf32_little(Config) when is_list(Config) ->
- BrokenPart = << <<X:32/little>> || X <- lists:seq(16#DC00,16#DFFF) >>,
+ ex_binaries_errors_utf32(little).
+
+ex_binaries_errors_utf32(Endian) ->
+ BrokenSeq = lists:seq(16#DC00, 16#DFFF),
+ BrokenPart = case Endian of
+ little ->
+ << <<X:32/little>> || X <- BrokenSeq >>;
+ big ->
+ << <<X:32/big>> || X <- BrokenSeq >>
+ end,
BrokenSz = byte_size(BrokenPart),
+ Seq255 = lists:seq(1, 255),
[ begin
- OKList = lists:flatten(lists:duplicate(N,lists:seq(1,255))),
- OKBin = unicode:characters_to_binary(OKList,unicode,{utf32,little}),
- OKLen = length(OKList),
- %% Copy to avoid that the binary get's writable
- PartlyBroken = binary:copy(<<OKBin/binary, BrokenPart/binary>>),
+ OKList = lists:append(lists:duplicate(N, Seq255)),
+ OKBin = unicode:characters_to_binary(OKList, unicode, {utf32,Endian}),
+ PartlyBroken = iolist_to_binary([OKBin,BrokenPart]),
PBSz = byte_size(PartlyBroken),
{error,OKList,DeepBrokenPart} =
- unicode:characters_to_list(PartlyBroken,{utf32,little}),
+ unicode:characters_to_list(PartlyBroken, {utf32,Endian}),
BrokenPart = iolist_to_binary(DeepBrokenPart),
- [ begin
- NewList = lists:nthtail(X, OKList),
- NewSz = byte_size(unicode:characters_to_binary(NewList,unicode,{utf32,little})) +
- BrokenSz,
- Chomped = binary:part(PartlyBroken,PBSz - NewSz, NewSz),
- true = (binary:referenced_byte_size(Chomped) =:= PBSz),
- {error,NewList,DeepBrokenPart2} =
- unicode:characters_to_list(Chomped,{utf32,little}),
- BrokenPart = iolist_to_binary(DeepBrokenPart2)
- end || X <- lists:seq(1,OKLen) ]
- end || N <- lists:seq(1,16,3) ],
+ utf32_inner_loop(OKList, BrokenPart, BrokenSz,
+ PartlyBroken, PBSz, Endian)
+ end || N <- lists:seq(1, 16, 3) ],
ok.
-
+utf32_inner_loop([_|List], BrokenPart, BrokenSz, PartlyBroken, PBSz, Endian) ->
+ Sz = length(List)*4 + BrokenSz,
+ Chomped = binary:part(PartlyBroken, PBSz - Sz, Sz),
+ true = binary:referenced_byte_size(Chomped) =:= PBSz,
+ {error,List,DeepBrokenPart} =
+ unicode:characters_to_list(Chomped, {utf32,Endian}),
+ BrokenPart = iolist_to_binary(DeepBrokenPart),
+ utf32_inner_loop(List, BrokenPart, BrokenSz, PartlyBroken, PBSz, Endian);
+utf32_inner_loop([], _, _, _, _, _) ->
+ ok.
exceptions(Config) when is_list(Config) ->
setlimit(10),
diff --git a/lib/stdlib/test/zip_SUITE.erl b/lib/stdlib/test/zip_SUITE.erl
index a57641ef62..08243f7c4f 100644
--- a/lib/stdlib/test/zip_SUITE.erl
+++ b/lib/stdlib/test/zip_SUITE.erl
@@ -23,7 +23,7 @@
bad_zip/1, unzip_from_binary/1, unzip_to_binary/1,
zip_to_binary/1,
unzip_options/1, zip_options/1, list_dir_options/1, aliases/1,
- openzip_api/1, zip_api/1, unzip_jar/1,
+ openzip_api/1, zip_api/1, open_leak/1, unzip_jar/1,
compress_control/1,
foldl/1]).
@@ -38,7 +38,7 @@ 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, unzip_jar, compress_control, foldl].
+ zip_api, open_leak, unzip_jar, compress_control, foldl].
groups() ->
[].
@@ -84,7 +84,7 @@ borderline_test(Size, TempDir) ->
io:format("Testing size ~p", [Size]),
%% Create a file and archive it.
- {_, _, X0} = erlang:now(),
+ {_, _, X0} = erlang:timestamp(),
file:write_file(Name, random_byte_list(X0, Size)),
{ok, Archive} = zip:zip(Archive, [Name]),
ok = file:delete(Name),
@@ -318,8 +318,46 @@ zip_api(Config) when is_list(Config) ->
%% Clean up.
delete_files([Names]),
+ ok.
+
+open_leak(doc) ->
+ ["Test that zip doesn't leak processes and ports where the "
+ "controlling process dies without closing an zip opened with "
+ "zip:zip_open/1."];
+open_leak(suite) -> [];
+open_leak(Config) when is_list(Config) ->
+ %% Create a zip archive
+ Zip = "zip.zip",
+ {ok, Zip} = zip:zip(Zip, [], []),
+
+ %% Open archive in a another process that dies immediately.
+ ZipSrv = spawn_zip(Zip, [memory]),
+
+ %% Expect the ZipSrv process to die soon after.
+ true = spawned_zip_dead(ZipSrv),
+
+ %% Clean up.
+ delete_files([Zip]),
+
ok.
+spawn_zip(Zip, Options) ->
+ Self = self(),
+ spawn(fun() -> Self ! zip:zip_open(Zip, Options) end),
+ receive
+ {ok, ZipSrv} ->
+ ZipSrv
+ end.
+
+spawned_zip_dead(ZipSrv) ->
+ Ref = monitor(process, ZipSrv),
+ receive
+ {'DOWN', Ref, _, ZipSrv, _} ->
+ true
+ after 1000 ->
+ false
+ end.
+
unzip_options(doc) ->
["Test options for unzip, only cwd and file_list currently"];
unzip_options(suite) ->
@@ -568,7 +606,7 @@ zip_to_binary(Config) when is_list(Config) ->
aliases(doc) ->
["Test using the aliases, extract/2, table/2 and create/3"];
aliases(Config) when is_list(Config) ->
- {_, _, X0} = erlang:now(),
+ {_, _, X0} = erlang:timestamp(),
Size = 100,
B = list_to_binary(random_byte_list(X0, Size)),
%% create