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/erl_lint_SUITE.erl80
-rw-r--r--lib/stdlib/test/ets_SUITE.erl36
-rw-r--r--lib/stdlib/test/sets_SUITE.erl15
-rw-r--r--lib/stdlib/test/sets_test_lib.erl13
-rw-r--r--lib/stdlib/test/zzz_SUITE.erl37
6 files changed, 92 insertions, 92 deletions
diff --git a/lib/stdlib/test/Makefile b/lib/stdlib/test/Makefile
index 8490770f3d..ae2e3d0e2b 100644
--- a/lib/stdlib/test/Makefile
+++ b/lib/stdlib/test/Makefile
@@ -95,7 +95,8 @@ MODULES= \
random_unicode_list \
random_iolist \
error_logger_forwarder \
- maps_SUITE
+ maps_SUITE \
+ zzz_SUITE
ERL_FILES= $(MODULES:%=%.erl)
diff --git a/lib/stdlib/test/erl_lint_SUITE.erl b/lib/stdlib/test/erl_lint_SUITE.erl
index e40f5e9a5d..f9ab83a120 100644
--- a/lib/stdlib/test/erl_lint_SUITE.erl
+++ b/lib/stdlib/test/erl_lint_SUITE.erl
@@ -66,7 +66,7 @@
otp_11851/1,otp_11879/1,otp_13230/1,
record_errors/1, otp_11879_cont/1,
non_latin1_module/1, otp_14323/1,
- get_stacktrace/1, stacktrace_syntax/1,
+ stacktrace_syntax/1,
otp_14285/1, otp_14378/1]).
suite() ->
@@ -88,7 +88,7 @@ all() ->
maps, maps_type, maps_parallel_match,
otp_11851, otp_11879, otp_13230,
record_errors, otp_11879_cont, non_latin1_module, otp_14323,
- get_stacktrace, stacktrace_syntax, otp_14285, otp_14378].
+ stacktrace_syntax, otp_14285, otp_14378].
groups() ->
[{unused_vars_warn, [],
@@ -4055,82 +4055,6 @@ otp_14323(Config) ->
[] = run(Config, Ts),
ok.
-get_stacktrace(Config) ->
- Ts = [{old_catch,
- <<"t1() ->
- catch error(foo),
- erlang:get_stacktrace().
- ">>,
- [],
- {warnings,[{3,erl_lint,{get_stacktrace,after_old_catch}}]}},
- {nowarn_get_stacktrace,
- <<"t1() ->
- catch error(foo),
- erlang:get_stacktrace().
- ">>,
- [nowarn_get_stacktrace],
- []},
- {try_catch,
- <<"t1(X) ->
- try abs(X) of
- _ ->
- erlang:get_stacktrace()
- catch
- _:_ -> ok
- end.
-
- t2() ->
- try error(foo)
- catch _:_ -> ok
- end,
- erlang:get_stacktrace().
-
- t3() ->
- try error(foo)
- catch _:_ ->
- try error(bar)
- catch _:_ ->
- ok
- end,
- erlang:get_stacktrace()
- end.
-
- no_warning(X) ->
- try
- abs(X)
- catch
- _:_ ->
- erlang:get_stacktrace()
- end.
- ">>,
- [],
- {warnings,[{4,erl_lint,{get_stacktrace,wrong_part_of_try}},
- {13,erl_lint,{get_stacktrace,after_try}},
- {22,erl_lint,{get_stacktrace,after_try}}]}},
- {multiple_catch_clauses,
- <<"maybe_error(Arg) ->
- try 5 / Arg
- catch
- error:badarith ->
- _Stacktrace = erlang:get_stacktrace(),
- try io:nl()
- catch
- error:_ -> io:format('internal error')
- end;
- error:badarg ->
- _Stacktrace = erlang:get_stacktrace(),
- try io:format(qwe)
- catch
- error:_ -> io:format('internal error')
- end
- end.
- ">>,
- [],
- []}],
-
- run(Config, Ts),
- ok.
-
stacktrace_syntax(Config) ->
Ts = [{guard,
<<"t1() ->
diff --git a/lib/stdlib/test/ets_SUITE.erl b/lib/stdlib/test/ets_SUITE.erl
index ec4a16b510..02211fa8df 100644
--- a/lib/stdlib/test/ets_SUITE.erl
+++ b/lib/stdlib/test/ets_SUITE.erl
@@ -55,6 +55,7 @@
-export([t_repair_continuation/1]).
-export([t_match_spec_run/1]).
-export([t_bucket_disappears/1]).
+-export([t_named_select/1]).
-export([otp_5340/1]).
-export([otp_6338/1]).
-export([otp_6842_select_1000/1]).
@@ -124,6 +125,7 @@ all() ->
t_init_table, t_whitebox, t_delete_all_objects,
t_insert_list, t_test_ms, t_select_delete, t_select_replace,
t_ets_dets, memory, t_select_reverse, t_bucket_disappears,
+ t_named_select,
select_fail, t_insert_new, t_repair_continuation,
otp_5340, otp_6338, otp_6842_select_1000, otp_7665,
otp_8732, meta_wb, grow_shrink, grow_pseudo_deleted,
@@ -205,6 +207,38 @@ t_bucket_disappears_do(Opts) ->
true = ets:delete(abcd),
verify_etsmem(EtsMem).
+%% OTP-21: Test that select/1 fails if named table was deleted and recreated
+%% and succeeds if table was renamed.
+t_named_select(_Config) ->
+ repeat_for_opts(fun t_named_select_do/1).
+
+t_named_select_do(Opts) ->
+ EtsMem = etsmem(),
+ T = t_name_tid_select,
+ ets_new(T, [named_table | Opts]),
+ ets:insert(T, {1,11}),
+ ets:insert(T, {2,22}),
+ ets:insert(T, {3,33}),
+ MS = [{{'$1', 22}, [], ['$1']}],
+ {[2], Cont1} = ets:select(T, MS, 1),
+ ets:delete(T),
+ {'EXIT',{badarg,_}} = (catch ets:select(Cont1)),
+ ets_new(T, [named_table | Opts]),
+ {'EXIT',{badarg,_}} = (catch ets:select(Cont1)),
+
+ true = ets:insert_new(T, {1,22}),
+ true = ets:insert_new(T, {2,22}),
+ true = ets:insert_new(T, {4,22}),
+ {[A,B], Cont2} = ets:select(T, MS, 2),
+ ets:rename(T, abcd),
+ {[C], '$end_of_table'} = ets:select(Cont2),
+ 7 = A + B + C,
+
+ true = ets:delete(abcd),
+ verify_etsmem(EtsMem).
+
+
+
%% Check ets:match_spec_run/2.
t_match_spec_run(Config) when is_list(Config) ->
@@ -700,7 +734,7 @@ whitebox_2(Opts) ->
ets:delete(T2),
ok.
-select_bound_chunk(Config) ->
+select_bound_chunk(_Config) ->
repeat_for_opts(fun select_bound_chunk_do/1, [all_types]).
select_bound_chunk_do(Opts) ->
diff --git a/lib/stdlib/test/sets_SUITE.erl b/lib/stdlib/test/sets_SUITE.erl
index bec38000b2..7066d07e19 100644
--- a/lib/stdlib/test/sets_SUITE.erl
+++ b/lib/stdlib/test/sets_SUITE.erl
@@ -28,7 +28,7 @@
init_per_testcase/2,end_per_testcase/2,
create/1,add_element/1,del_element/1,
subtract/1,intersection/1,union/1,is_subset/1,
- is_set/1,fold/1,filter/1,
+ is_set/1,is_empty/1,fold/1,filter/1,
take_smallest/1,take_largest/1, iterate/1]).
-include_lib("common_test/include/ct.hrl").
@@ -48,7 +48,7 @@ suite() ->
all() ->
[create, add_element, del_element, subtract,
intersection, union, is_subset, is_set, fold, filter,
- take_smallest, take_largest, iterate].
+ take_smallest, take_largest, iterate, is_empty].
groups() ->
[].
@@ -345,6 +345,17 @@ is_set_1(M) ->
false = M(is_set, {}),
M(empty, []).
+is_empty(Config) when is_list(Config) ->
+ test_all(fun is_empty_1/1).
+
+is_empty_1(M) ->
+ S = M(from_list, [blurf]),
+ Empty = M(empty, []),
+
+ true = M(is_empty, Empty),
+ false = M(is_empty, S),
+ M(empty, []).
+
fold(Config) when is_list(Config) ->
test_all([{0,71},{125,129},{254,259},{510,513},{1023,1025},{9999,10001}],
fun fold_1/2).
diff --git a/lib/stdlib/test/sets_test_lib.erl b/lib/stdlib/test/sets_test_lib.erl
index 9f153822a2..93d027704b 100644
--- a/lib/stdlib/test/sets_test_lib.erl
+++ b/lib/stdlib/test/sets_test_lib.erl
@@ -32,7 +32,7 @@ new(Mod, Eq) ->
(from_list, L) -> Mod:from_list(L);
(intersection, {S1,S2}) -> intersection(Mod, Eq, S1, S2);
(intersection, Ss) -> intersection(Mod, Eq, Ss);
- (is_empty, S) -> is_empty(Mod, S);
+ (is_empty, S) -> Mod:is_empty(S);
(is_set, S) -> Mod:is_set(S);
(is_subset, {S,Set}) -> is_subset(Mod, Eq, S, Set);
(iterator, S) -> Mod:iterator(S);
@@ -56,7 +56,7 @@ singleton(Mod, E) ->
add_element(Mod, El, S0) ->
S = Mod:add_element(El, S0),
true = Mod:is_element(El, S),
- false = is_empty(Mod, S),
+ false = Mod:is_empty(S),
true = Mod:is_set(S),
S.
@@ -66,17 +66,10 @@ del_element(Mod, El, S0) ->
true = Mod:is_set(S),
S.
-is_empty(Mod, S) ->
- true = Mod:is_set(S),
- case erlang:function_exported(Mod, is_empty, 1) of
- true -> Mod:is_empty(S);
- false -> Mod:size(S) == 0
- end.
-
intersection(Mod, Equal, S1, S2) ->
S = Mod:intersection(S1, S2),
true = Equal(S, Mod:intersection(S2, S1)),
- Disjoint = is_empty(Mod, S),
+ Disjoint = Mod:is_empty(S),
Disjoint = Mod:is_disjoint(S1, S2),
Disjoint = Mod:is_disjoint(S2, S1),
S.
diff --git a/lib/stdlib/test/zzz_SUITE.erl b/lib/stdlib/test/zzz_SUITE.erl
new file mode 100644
index 0000000000..59c7fd7404
--- /dev/null
+++ b/lib/stdlib/test/zzz_SUITE.erl
@@ -0,0 +1,37 @@
+%%
+%% %CopyrightBegin%
+%%
+%% Copyright Ericsson AB 2006-2018. All Rights Reserved.
+%%
+%% Licensed under the Apache License, Version 2.0 (the "License");
+%% you may not use this file except in compliance with the License.
+%% You may obtain a copy of the License at
+%%
+%% http://www.apache.org/licenses/LICENSE-2.0
+%%
+%% Unless required by applicable law or agreed to in writing, software
+%% distributed under the License is distributed on an "AS IS" BASIS,
+%% WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied.
+%% See the License for the specific language governing permissions and
+%% limitations under the License.
+%%
+%% %CopyrightEnd%
+%%
+-module(zzz_SUITE).
+
+%% The sole purpose of this test suite is for things we want to run last
+%% before the VM terminates.
+
+-export([all/0]).
+
+-export([lc_graph/1]).
+
+
+all() ->
+ [lc_graph].
+
+lc_graph(_Config) ->
+ %% Create "lc_graph" file in current working dir
+ %% if lock checker is enabled.
+ erts_debug:lc_graph(),
+ ok.