diff options
Diffstat (limited to 'lib/stdlib/test')
-rw-r--r-- | lib/stdlib/test/dets_SUITE.erl | 4 | ||||
-rw-r--r-- | lib/stdlib/test/ets_SUITE.erl | 2 | ||||
-rw-r--r-- | lib/stdlib/test/gen_statem_SUITE.erl | 11 | ||||
-rw-r--r-- | lib/stdlib/test/io_SUITE.erl | 56 | ||||
-rw-r--r-- | lib/stdlib/test/lists_SUITE.erl | 20 | ||||
-rw-r--r-- | lib/stdlib/test/sets_SUITE.erl | 15 | ||||
-rw-r--r-- | lib/stdlib/test/sets_test_lib.erl | 13 | ||||
-rw-r--r-- | lib/stdlib/test/stdlib_bench_SUITE.erl | 16 |
8 files changed, 98 insertions, 39 deletions
diff --git a/lib/stdlib/test/dets_SUITE.erl b/lib/stdlib/test/dets_SUITE.erl index d667bd82a2..7d82790b82 100644 --- a/lib/stdlib/test/dets_SUITE.erl +++ b/lib/stdlib/test/dets_SUITE.erl @@ -3275,16 +3275,16 @@ otp_8856(Config) when is_list(Config) -> {ok, _} = dets:open_file(Tab, [{type, bag}, {file, File}]), spawn(fun()-> Me ! {1, dets:insert(Tab, [])} end), spawn(fun()-> Me ! {2, dets:insert_new(Tab, [])} end), - ok = dets:close(Tab), receive {1, ok} -> ok end, receive {2, true} -> ok end, + ok = dets:close(Tab), file:delete(File), {ok, _} = dets:open_file(Tab, [{type, set}, {file, File}]), spawn(fun() -> dets:delete(Tab, 0) end), spawn(fun() -> Me ! {3, dets:insert_new(Tab, {0,0})} end), - ok = dets:close(Tab), receive {3, true} -> ok end, + ok = dets:close(Tab), file:delete(File), ok. diff --git a/lib/stdlib/test/ets_SUITE.erl b/lib/stdlib/test/ets_SUITE.erl index 8b651f4b43..ec4a16b510 100644 --- a/lib/stdlib/test/ets_SUITE.erl +++ b/lib/stdlib/test/ets_SUITE.erl @@ -3649,7 +3649,7 @@ verify_rescheduling_exit(Config, ForEachData, Flags, Fix, NOTabs, NOProcs) -> XScheds = count_exit_sched(TP), io:format("~p XScheds=~p~n", [TP, XScheds]), - true = XScheds >= 5 + true = XScheds >= 3 end, TPs), stop_loopers(LPs), diff --git a/lib/stdlib/test/gen_statem_SUITE.erl b/lib/stdlib/test/gen_statem_SUITE.erl index 7c8a386116..3f48fe1590 100644 --- a/lib/stdlib/test/gen_statem_SUITE.erl +++ b/lib/stdlib/test/gen_statem_SUITE.erl @@ -1,7 +1,7 @@ %% %% %CopyrightBegin% %% -%% Copyright Ericsson AB 2016-2017. All Rights Reserved. +%% Copyright Ericsson AB 2016-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. @@ -832,9 +832,14 @@ event_types(_Config) -> %% Abusing the internal format of From... #{init => fun () -> - {ok, start, undefined} + {ok, start1, undefined, + [{next_event,internal,0}]} end, - start => + start1 => + fun (internal, 0, undefined) -> + {next_state, start2, undefined} + end, + start2 => fun ({call,_} = Call, Req, undefined) -> {next_state, state1, undefined, [{next_event,internal,1}, diff --git a/lib/stdlib/test/io_SUITE.erl b/lib/stdlib/test/io_SUITE.erl index ac61e3753b..6f4e7ad7e0 100644 --- a/lib/stdlib/test/io_SUITE.erl +++ b/lib/stdlib/test/io_SUITE.erl @@ -1905,29 +1905,61 @@ otp_10836(Suite) when is_list(Suite) -> %% OTP-10755. The 'l' modifier otp_10755(Suite) when is_list(Suite) -> + %% printing plain ascii characters S = "string", "\"string\"" = fmt("~p", [S]), "[115,116,114,105,110,103]" = fmt("~lp", [S]), "\"string\"" = fmt("~P", [S, 2]), "[115|...]" = fmt("~lP", [S, 2]), - {'EXIT',{badarg,_}} = (catch fmt("~ltp", [S])), - {'EXIT',{badarg,_}} = (catch fmt("~tlp", [S])), - {'EXIT',{badarg,_}} = (catch fmt("~ltP", [S])), - {'EXIT',{badarg,_}} = (catch fmt("~tlP", [S])), + %% printing latin1 chars, with and without modifiers + T = {[255],list_to_atom([255]),[a,b,c]}, + "{\"ÿ\",ÿ,[a,b,c]}" = fmt("~p", [T]), + "{\"ÿ\",ÿ,[a,b,c]}" = fmt("~tp", [T]), + "{[255],ÿ,[a,b,c]}" = fmt("~lp", [T]), + "{[255],ÿ,[a,b,c]}" = fmt("~ltp", [T]), + "{[255],ÿ,[a,b,c]}" = fmt("~tlp", [T]), + "{\"ÿ\",ÿ,...}" = fmt("~P", [T,3]), + "{\"ÿ\",ÿ,...}" = fmt("~tP", [T,3]), + "{[255],ÿ,...}" = fmt("~lP", [T,3]), + "{[255],ÿ,...}" = fmt("~ltP", [T,3]), + "{[255],ÿ,...}" = fmt("~tlP", [T,3]), + %% printing unicode chars, with and without modifiers + U = {[666],list_to_atom([666]),[a,b,c]}, + "{[666],'\\x{29A}',[a,b,c]}" = fmt("~p", [U]), + case io:printable_range() of + unicode -> + "{\"ʚ\",'ʚ',[a,b,c]}" = fmt("~tp", [U]), + "{\"ʚ\",'ʚ',...}" = fmt("~tP", [U,3]); + latin1 -> + "{[666],'ʚ',[a,b,c]}" = fmt("~tp", [U]), + "{[666],'ʚ',...}" = fmt("~tP", [U,3]) + end, + "{[666],'\\x{29A}',[a,b,c]}" = fmt("~lp", [U]), + "{[666],'ʚ',[a,b,c]}" = fmt("~ltp", [U]), + "{[666],'ʚ',[a,b,c]}" = fmt("~tlp", [U]), + "{[666],'\\x{29A}',...}" = fmt("~P", [U,3]), + "{[666],'\\x{29A}',...}" = fmt("~lP", [U,3]), + "{[666],'ʚ',...}" = fmt("~ltP", [U,3]), + "{[666],'ʚ',...}" = fmt("~tlP", [U,3]), + %% the compiler should catch uses of ~l with other than pP Text = "-module(l_mod).\n" "-export([t/0]).\n" "t() ->\n" " S = \"string\",\n" - " io:format(\"~ltp\", [S]),\n" - " io:format(\"~tlp\", [S]),\n" - " io:format(\"~ltP\", [S, 1]),\n" - " io:format(\"~tlP\", [S, 1]).\n", + " io:format(\"~lw\", [S]),\n" + " io:format(\"~lW\", [S, 1]),\n" + " io:format(\"~ltw\", [S]),\n" + " io:format(\"~tlw\", [S]),\n" + " io:format(\"~ltW\", [S, 1]),\n" + " io:format(\"~tlW\", [S, 1]).\n", {ok,l_mod,[{_File,Ws}]} = compile_file("l_mod.erl", Text, Suite), - ["format string invalid (invalid control ~lt)", - "format string invalid (invalid control ~tl)", - "format string invalid (invalid control ~lt)", - "format string invalid (invalid control ~tl)"] = + ["format string invalid (invalid control ~lw)", + "format string invalid (invalid control ~lW)", + "format string invalid (invalid control ~ltw)", + "format string invalid (invalid control ~ltw)", + "format string invalid (invalid control ~ltW)", + "format string invalid (invalid control ~ltW)"] = [lists:flatten(M:format_error(E)) || {_L,M,E} <- Ws], ok. diff --git a/lib/stdlib/test/lists_SUITE.erl b/lib/stdlib/test/lists_SUITE.erl index 7c99244b36..837ab4e97e 100644 --- a/lib/stdlib/test/lists_SUITE.erl +++ b/lib/stdlib/test/lists_SUITE.erl @@ -1,7 +1,7 @@ %% %% %CopyrightBegin% %% -%% Copyright Ericsson AB 1997-2017. All Rights Reserved. +%% Copyright Ericsson AB 1997-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. @@ -57,7 +57,7 @@ filter_partition/1, join/1, otp_5939/1, otp_6023/1, otp_6606/1, otp_7230/1, - suffix/1, subtract/1, droplast/1, hof/1]). + suffix/1, subtract/1, droplast/1, search/1, hof/1]). %% Sort randomized lists until stopped. %% @@ -121,7 +121,7 @@ groups() -> {zip, [parallel], [zip_unzip, zip_unzip3, zipwith, zipwith3]}, {misc, [parallel], [reverse, member, dropwhile, takewhile, filter_partition, suffix, subtract, join, - hof, droplast]} + hof, droplast, search]} ]. init_per_suite(Config) -> @@ -2615,6 +2615,20 @@ droplast(Config) when is_list(Config) -> ok. +%% Test lists:search/2 +search(Config) when is_list(Config) -> + F = fun(I) -> I rem 2 =:= 0 end, + F2 = fun(A, B) -> A > B end, + + {value, 2} = lists:search(F, [1,2,3,4]), + false = lists:search(F, [1,3,5,7]), + false = lists:search(F, []), + + %% Error cases. + {'EXIT',{function_clause,_}} = (catch lists:search(badfun, [])), + {'EXIT',{function_clause,_}} = (catch lists:search(F2, [])), + ok. + %% Briefly test the common high-order functions to ensure they %% are covered. hof(Config) when is_list(Config) -> 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/stdlib_bench_SUITE.erl b/lib/stdlib/test/stdlib_bench_SUITE.erl index 294898a932..2364e8376f 100644 --- a/lib/stdlib/test/stdlib_bench_SUITE.erl +++ b/lib/stdlib/test/stdlib_bench_SUITE.erl @@ -348,12 +348,16 @@ do_tests(Test, ParamSet, Config) -> {Parallelism, Message} = bench_params(ParamSet), Fun = create_clients(Message, ServerMod, Client, Parallelism), {TotalLoops, AllPidTime} = run_test(Fun), - PerSecond = ?CALLS_PER_LOOP * round((1000 * TotalLoops) / AllPidTime), - ct_event:notify( - #event{ - name = benchmark_data, - data = [{suite,BenchmarkSuite},{value,PerSecond}]}), - PerSecond. + try ?CALLS_PER_LOOP * round((1000 * TotalLoops) / AllPidTime) of + PerSecond -> + ct_event:notify( + #event{ + name = benchmark_data, + data = [{suite,BenchmarkSuite},{value,PerSecond}]}), + PerSecond + catch error:badarith -> + "Time measurement is not working" + end. -define(COUNTER, n). |