aboutsummaryrefslogtreecommitdiffstats
path: root/lib/stdlib/test
diff options
context:
space:
mode:
Diffstat (limited to 'lib/stdlib/test')
-rw-r--r--lib/stdlib/test/Makefile3
-rw-r--r--lib/stdlib/test/binary_module_SUITE.erl50
-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/erl_anno_SUITE.erl1
-rw-r--r--lib/stdlib/test/ets_SUITE.erl31
-rw-r--r--lib/stdlib/test/io_proto_SUITE.erl2
-rw-r--r--lib/stdlib/test/maps_SUITE.erl21
-rw-r--r--lib/stdlib/test/qlc_SUITE.erl18
-rw-r--r--lib/stdlib/test/rand_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/stdlib_SUITE.erl67
-rw-r--r--lib/stdlib/test/supervisor_SUITE.erl23
-rw-r--r--lib/stdlib/test/unicode_SUITE.erl3
15 files changed, 268 insertions, 57 deletions
diff --git a/lib/stdlib/test/Makefile b/lib/stdlib/test/Makefile
index 61eb34d565..d4ab674486 100644
--- a/lib/stdlib/test/Makefile
+++ b/lib/stdlib/test/Makefile
@@ -107,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 5248870744..8d26c77c9b 100644
--- a/lib/stdlib/test/binary_module_SUITE.erl
+++ b/lib/stdlib/test/binary_module_SUITE.erl
@@ -993,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) ->
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/erl_anno_SUITE.erl b/lib/stdlib/test/erl_anno_SUITE.erl
index 7632fbd324..d024f6907d 100644
--- a/lib/stdlib/test/erl_anno_SUITE.erl
+++ b/lib/stdlib/test/erl_anno_SUITE.erl
@@ -89,7 +89,6 @@ is_anno(_Config) ->
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}]),
- false = erl_anno:is_anno([{location,1},{text,[a,b,c]}]),
true = erl_anno:is_anno(erl_anno:new(1)),
A0 = erl_anno:new({1, 17}),
diff --git a/lib/stdlib/test/ets_SUITE.erl b/lib/stdlib/test/ets_SUITE.erl
index 5d1d4b7358..9f0135b68c 100644
--- a/lib/stdlib/test/ets_SUITE.erl
+++ b/lib/stdlib/test/ets_SUITE.erl
@@ -3063,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 "
@@ -4080,12 +4080,22 @@ tab2file(doc) -> ["Check the ets:tab2file function on an empty "
"ets table."];
tab2file(suite) -> [];
tab2file(Config) when is_list(Config) ->
+ ?line FName = filename:join([?config(priv_dir, Config),"tab2file_case"]),
+ 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, private,
{keypos, 2}]),
- ?line FName = filename:join([?config(priv_dir, Config),"tab2file_case"]),
- ?line ok = ets:tab2file(Tab, FName),
- ?line true = ets:delete(Tab),
+ 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),
@@ -4095,6 +4105,7 @@ tab2file(Config) when is_list(Config) ->
?line set = ets:info(Tab2, type),
?line true = ets:delete(Tab2),
?line verify_etsmem(EtsMem).
+
tab2file2(doc) -> ["Check the ets:tab2file function on a ",
"filled set/bag type ets table."];
diff --git a/lib/stdlib/test/io_proto_SUITE.erl b/lib/stdlib/test/io_proto_SUITE.erl
index 858a78b1d2..78432789cd 100644
--- a/lib/stdlib/test/io_proto_SUITE.erl
+++ b/lib/stdlib/test/io_proto_SUITE.erl
@@ -482,7 +482,7 @@ unicode_options_gen(Config) when is_list(Config) ->
PrivDir = ?config(priv_dir, Config),
AllModes = [utf8,utf16,{utf16,big},{utf16,little},
utf32,{utf32,big},{utf32,little}],
- FSize = 17*1024,
+ FSize = 9*1024,
NumItersRead = 2,
NumItersWrite = 2,
Dir = filename:join(PrivDir, "GENDATA1"),
diff --git a/lib/stdlib/test/maps_SUITE.erl b/lib/stdlib/test/maps_SUITE.erl
index 1d9c041a74..f8f241d834 100644
--- a/lib/stdlib/test/maps_SUITE.erl
+++ b/lib/stdlib/test/maps_SUITE.erl
@@ -34,18 +34,21 @@
-export([init_per_testcase/2]).
-export([end_per_testcase/2]).
--export([t_get_3/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,_}|_]}}).
+%-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_get_3,t_filter_2,
t_fold_3,t_map_2,t_size_1,
t_with_2,t_without_2].
@@ -99,6 +102,16 @@ t_with_2(_Config) ->
?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),
diff --git a/lib/stdlib/test/qlc_SUITE.erl b/lib/stdlib/test/qlc_SUITE.erl
index 348c308f5d..56829fac5c 100644
--- a/lib/stdlib/test/qlc_SUITE.erl
+++ b/lib/stdlib/test/qlc_SUITE.erl
@@ -6120,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)),
@@ -6155,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(),
@@ -6188,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)">>],
@@ -6215,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,
@@ -8178,6 +8178,8 @@ read_error_logger() ->
{error, Why};
{info, Why} ->
{info, Why};
+ {warning, Why} ->
+ {warning, Why};
{error, Pid, Tuple} ->
{error, Pid, Tuple}
after 1000 ->
@@ -8192,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) ->
@@ -8202,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
index 9a1f37aa75..39ce1bd89a 100644
--- a/lib/stdlib/test/rand_SUITE.erl
+++ b/lib/stdlib/test/rand_SUITE.erl
@@ -33,7 +33,7 @@
-include_lib("test_server/include/test_server.hrl").
% Default timetrap timeout (set in init_per_testcase).
--define(default_timeout, ?t:minutes(1)).
+-define(default_timeout, ?t:minutes(3)).
-define(LOOP, 1000000).
init_per_testcase(_Case, Config) ->
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/stdlib_SUITE.erl b/lib/stdlib/test/stdlib_SUITE.erl
index 206eb4fd74..8ab30eb62b 100644
--- a/lib/stdlib/test/stdlib_SUITE.erl
+++ b/lib/stdlib/test/stdlib_SUITE.erl
@@ -30,7 +30,7 @@
suite() -> [{ct_hooks,[ts_install_cth]}].
all() ->
- [app_test, appup_test, {group,upgrade}].
+ [app_test, appup_test, assert_test, {group,upgrade}].
groups() ->
[{upgrade,[minor_upgrade,major_upgrade]}].
@@ -185,3 +185,68 @@ 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/supervisor_SUITE.erl b/lib/stdlib/test/supervisor_SUITE.erl
index 9dcf19707c..015b09f35e 100644
--- a/lib/stdlib/test/supervisor_SUITE.erl
+++ b/lib/stdlib/test/supervisor_SUITE.erl
@@ -37,6 +37,7 @@
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_ignore_permanent_child_start_child_simple/1,
sup_start_error_return/1, sup_start_fail/1,
sup_start_map/1, sup_start_map_faulty_specs/1,
sup_stop_infinity/1, sup_stop_timeout/1, sup_stop_brutal_kill/1,
@@ -99,6 +100,7 @@ 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_faulty_specs]},
@@ -250,6 +252,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),
diff --git a/lib/stdlib/test/unicode_SUITE.erl b/lib/stdlib/test/unicode_SUITE.erl
index 613be99ccd..9f5d485df6 100644
--- a/lib/stdlib/test/unicode_SUITE.erl
+++ b/lib/stdlib/test/unicode_SUITE.erl
@@ -87,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