diff options
Diffstat (limited to 'lib/stdlib/test')
-rw-r--r-- | lib/stdlib/test/binary_module_SUITE.erl | 29 | ||||
-rw-r--r-- | lib/stdlib/test/erl_pp_SUITE.erl | 29 | ||||
-rw-r--r-- | lib/stdlib/test/ets_SUITE.erl | 56 | ||||
-rw-r--r-- | lib/stdlib/test/gen_server_SUITE.erl | 4 | ||||
-rw-r--r-- | lib/stdlib/test/id_transform_SUITE.erl | 9 | ||||
-rw-r--r-- | lib/stdlib/test/io_SUITE.erl | 44 | ||||
-rw-r--r-- | lib/stdlib/test/io_proto_SUITE.erl | 3 | ||||
-rw-r--r-- | lib/stdlib/test/rand_SUITE.erl | 28 | ||||
-rw-r--r-- | lib/stdlib/test/select_SUITE.erl | 30 | ||||
-rw-r--r-- | lib/stdlib/test/supervisor_SUITE.erl | 12 | ||||
-rw-r--r-- | lib/stdlib/test/unicode_SUITE.erl | 24 |
11 files changed, 99 insertions, 169 deletions
diff --git a/lib/stdlib/test/binary_module_SUITE.erl b/lib/stdlib/test/binary_module_SUITE.erl index 55fdcdd054..c5cfea5e9e 100644 --- a/lib/stdlib/test/binary_module_SUITE.erl +++ b/lib/stdlib/test/binary_module_SUITE.erl @@ -19,9 +19,7 @@ %% -module(binary_module_SUITE). --export([all/0, suite/0,groups/0,init_per_suite/1, end_per_suite/1, - init_per_testcase/2, end_per_testcase/2, - init_per_group/2,end_per_group/2, +-export([all/0, suite/0, interesting/1,scope_return/1,random_ref_comp/1,random_ref_sr_comp/1, random_ref_fla_comp/1,parts/1, bin_to_list/1, list_to_bin/1, copy/1, referenced/1,guard/1,encode_decode/1,badargs/1,longest_common_trap/1]). @@ -30,15 +28,9 @@ -include_lib("common_test/include/ct.hrl"). -init_per_testcase(_Case, Config) -> - Config. - -end_per_testcase(_Case, _Config) -> - ok. - suite() -> [{ct_hooks,[ts_install_cth]}, - {timetrap,{minutes,30}}]. + {timetrap,{minutes,10}}]. all() -> [scope_return,interesting, random_ref_fla_comp, random_ref_sr_comp, @@ -46,21 +38,6 @@ all() -> referenced, guard, encode_decode, badargs, longest_common_trap]. -groups() -> - []. - -init_per_suite(Config) -> - Config. - -end_per_suite(_Config) -> - ok. - -init_per_group(_GroupName, Config) -> - Config. - -end_per_group(_GroupName, Config) -> - Config. - -define(MASK_ERROR(EXPR),mask_error((catch (EXPR)))). @@ -961,6 +938,7 @@ random_parts(X,N) -> %% Test pseudorandomly generated cases against reference implementation. random_ref_comp(Config) when is_list(Config) -> + ct:timetrap({minutes,30}), %% valgrind needs a lot of time put(success_counter,0), rand:seed(exsplus, {1271,769940,559934}), Nr = {1,40}, @@ -991,6 +969,7 @@ random_ref_comp(Config) when is_list(Config) -> %% Test pseudorandomly generated cases against reference implementation %% of split and replace. random_ref_sr_comp(Config) when is_list(Config) -> + ct:timetrap({minutes,30}), %% valgrind needs a lot put(success_counter,0), rand:seed(exsplus, {1271,769940,559934}), Nr = {1,40}, diff --git a/lib/stdlib/test/erl_pp_SUITE.erl b/lib/stdlib/test/erl_pp_SUITE.erl index a48ba7b5b7..a103f6dc53 100644 --- a/lib/stdlib/test/erl_pp_SUITE.erl +++ b/lib/stdlib/test/erl_pp_SUITE.erl @@ -50,7 +50,8 @@ 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_11861/1, pr_1014/1]). + otp_10302/1, otp_10820/1, otp_11100/1, otp_11861/1, pr_1014/1, + otp_13662/1]). %% Internal export. -export([ehook/6]). @@ -79,7 +80,7 @@ groups() -> {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_11861, pr_1014]}]. + otp_10302, otp_10820, otp_11100, otp_11861, pr_1014, otp_13662]}]. init_per_suite(Config) -> Config. @@ -1112,19 +1113,37 @@ pr_1014(Config) -> ok = pp_forms(<<"-type t() :: #{any() => _}. ">>), ok = pp_forms(<<"-type t() :: #{_ => any()}. ">>), ok = pp_forms(<<"-type t() :: #{any() => any()}. ">>), - ok = pp_forms(<<"-type t() :: #{...}. ">>), - ok = pp_forms(<<"-type t() :: #{atom() := integer(), ...}. ">>), + ok = pp_forms(<<"-type t() :: #{atom() := integer(), any() => any()}. ">>), FileName = filename('pr_1014.erl', Config), C = <<"-module pr_1014.\n" "-compile export_all.\n" "-type m() :: #{..., a := integer()}.\n">>, ok = file:write_file(FileName, C), - {error,[{_,[{3,erl_parse,["syntax error before: ","','"]}]}],_} = + {error,[{_,[{3,erl_parse,["syntax error before: ","'...'"]}]}],_} = compile:file(FileName, [return]), ok. +otp_13662(Config) -> + Include = "abcdefghijabcdefghijabcdefghijabcdefghijabcde" + "fghij-xxxxxxxxxxxxxxxxxxxxxxxxxxxxxx.hrl", + IncludeFile = filename(Include, Config), + ok = file:write_file(IncludeFile, <<>>), + Ts = [{otp_13662, + <<"-file(\"abcdefghijabcdefghijabcdefghijabcdefghijabcde\"\n + \"fghij-xxxxxxxxxxxxxxxxxxxxxxxxxxxxxx.erl\", 0).\n + -include(\"abcdefghijabcdefghijabcdefghijabcdefghijabcde\" + \"fghij-xxxxxxxxxxxxxxxxxxxxxxxxxxxxxx.hrl\").\n + -include_lib(\"abcdefghijabcdefghijabcdefghijabcdefghijabcde\" + \"fghij-xxxxxxxxxxxxxxxxxxxxxxxxxxxxxx.hrl\"). + -compile(export_all).\n + t() ->\n + \"aaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaa\"\n + \"aaaaaaaaaaaaaaaaaaaaaa\".\n">>} + ], + compile(Config, Ts). + %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% compile(Config, Tests) -> diff --git a/lib/stdlib/test/ets_SUITE.erl b/lib/stdlib/test/ets_SUITE.erl index 15e3142408..40764a943d 100644 --- a/lib/stdlib/test/ets_SUITE.erl +++ b/lib/stdlib/test/ets_SUITE.erl @@ -125,7 +125,7 @@ end_per_testcase(_Func, _Config) -> suite() -> [{ct_hooks,[ts_install_cth]}, - {timetrap,{minutes,20}}]. + {timetrap,{minutes,5}}]. all() -> [{group, new}, {group, insert}, {group, lookup}, @@ -215,7 +215,7 @@ memory_check_summary(_Config) -> receive {get_failed_memchecks, FailedMemchecks} -> ok end, io:format("Failed memchecks: ~p\n",[FailedMemchecks]), NoFailedMemchecks = length(FailedMemchecks), - if NoFailedMemchecks > 3 -> + if NoFailedMemchecks > 300 -> ct:fail("Too many failed (~p) memchecks", [NoFailedMemchecks]); true -> ok @@ -604,9 +604,9 @@ memory(Config) when is_list(Config) -> memory_do(Opts) -> L = [T1,T2,T3,T4] = fill_sets_int(1000,Opts), XR1 = case mem_mode(T1) of - {normal,_} -> {13836,13046,13046,13052}; %{13862,13072,13072,13078}; - {compressed,4} -> {11041,10251,10251,10252}; %{11067,10277,10277,10278}; - {compressed,8} -> {10050,9260,9260,9260} %{10076,9286,9286,9286} + {normal,_} -> {13836,13560,13560,13566}; %{13836,13046,13046,13052} + {compressed,4} -> {11041,10865,10865,10866}; %{11041,10251,10251,10252} + {compressed,8} -> {10050,9774,9774,9774} % {10050,9260,9260,9260} end, XRes1 = adjust_xmem(L, XR1), Res1 = {?S(T1),?S(T2),?S(T3),?S(T4)}, @@ -620,9 +620,9 @@ memory_do(Opts) -> end, L), XR2 = case mem_mode(T1) of - {normal,_} -> {13826,13037,13028,13034}; %{13852,13063,13054,13060}; - {compressed,4} -> {11031,10242,10233,10234}; %{11057,10268,10259,10260}; - {compressed,8} -> {10040,9251,9242,9242} %10066,9277,9268,9268} + {normal,_} -> {13826,13551,13542,13548}; %{13826,13037,13028,13034}; + {compressed,4} -> {11031,10856,10747,10748}; %{11031,10242,10233,10234}; + {compressed,8} -> {10040,9765,9756,9756} %{10040,9251,9242,9242} end, XRes2 = adjust_xmem(L, XR2), Res2 = {?S(T1),?S(T2),?S(T3),?S(T4)}, @@ -636,9 +636,9 @@ memory_do(Opts) -> end, L), XR3 = case mem_mode(T1) of - {normal,_} -> {13816,13028,13010,13016}; %{13842,13054,13036,13042}; - {compressed,4} -> {11021,10233,10215,10216}; %{11047,10259,10241,10242}; - {compressed,8} -> {10030,9242,9224,9224} %{10056,9268,9250,9250} + {normal,_} -> {13816,13542,13524,13530}; %{13816,13028,13010,13016} + {compressed,4} -> {11021,10747,10729,10730}; %{11021,10233,10215,10216} + {compressed,8} -> {10030,9756,9738,9738} %{10030,9242,9224,9224} end, XRes3 = adjust_xmem(L, XR3), Res3 = {?S(T1),?S(T2),?S(T3),?S(T4)}, @@ -698,7 +698,7 @@ chk_normal_tab_struct_size() -> io:format("?TAB_STRUCT_SZ=~p~n", [?TAB_STRUCT_SZ]), ok. -adjust_xmem([T1,T2,T3,T4], {A0,B0,C0,D0} = _Mem0) -> +adjust_xmem([_T1,_T2,_T3,_T4], {A0,B0,C0,D0} = _Mem0) -> %% Adjust for 64-bit, smp, and os: %% Table struct size may differ. @@ -2809,16 +2809,22 @@ privacy_do(Opts) -> privacy_check(pub,prot,priv), Owner ! {shift,1,{pub,prot,priv}}, - receive {Pub1,Prot1,Priv1} -> ok end, - privacy_check(Pub1,Prot1,Priv1), + receive + {Pub1,Prot1,Priv1} -> + ok = privacy_check(Pub1,Prot1,Priv1), + Owner ! {shift,2,{Pub1,Prot1,Priv1}} + end, - Owner ! {shift,2,{Pub1,Prot1,Priv1}}, - receive {Pub2,Prot2,Priv2} -> ok end, - privacy_check(Pub2,Prot2,Priv2), + receive + {Pub2,Prot2,Priv2} -> + ok = privacy_check(Pub2,Prot2,Priv2), + Owner ! {shift,0,{Pub2,Prot2,Priv2}} + end, - Owner ! {shift,0,{Pub2,Prot2,Priv2}}, - receive {Pub2,Prot2,Priv2} -> ok end, - privacy_check(Pub2,Prot2,Priv2), + receive + {Pub3,Prot3,Priv3} -> + ok = privacy_check(Pub3,Prot3,Priv3) + end, Owner ! die, receive {'EXIT',Owner,_} -> ok end, @@ -2836,7 +2842,8 @@ privacy_check(Pub,Prot,Priv) -> {'EXIT',{badarg,_}} = (catch ets:insert(Priv,{3,foo})), %% check that it really wasn't written, either - [] = ets:lookup(Prot,foo). + [] = ets:lookup(Prot,foo), + ok. privacy_owner(Boss, Opts) -> ets_new(pub, [public,named_table | Opts]), @@ -3197,7 +3204,6 @@ delete_large_named_table_1(Name, Flags, Data, Fix) -> true = ets:safe_fixtable(Tab, true), lists:foreach(fun({K,_}) -> ets:delete(Tab, K) end, Data) end, - Parent = self(), {Pid, MRef} = my_spawn_opt(fun() -> receive ets_new -> @@ -3297,6 +3303,7 @@ exit_large_table_owner_do(Opts,{FEData,Config}) -> verify_rescheduling_exit(Config, FEData, Opts, false, 1, 1). exit_many_large_table_owner(Config) when is_list(Config) -> + ct:timetrap({minutes,30}), %% valgrind needs a lot %%Data = [{erlang:phash2(I, 16#ffffff),I} || I <- lists:seq(1, 500000)], FEData = fun(Do) -> repeat_while(fun(500000) -> {false,ok}; (I) -> Do({erlang:phash2(I, 16#ffffff),I}), @@ -4270,6 +4277,7 @@ do_lookup_element(Tab, N, M) -> heavy_concurrent(Config) when is_list(Config) -> + ct:timetrap({minutes,30}), %% valgrind needs a lot of time repeat_for_opts(do_heavy_concurrent). do_heavy_concurrent(Opts) -> @@ -5342,12 +5350,12 @@ verify_table_load(T) -> Stats = ets:info(T,stats), {Buckets,AvgLen,StdDev,ExpSD,_MinLen,_MaxLen,_} = Stats, ok = if - AvgLen > 7 -> + AvgLen > 2 -> io:format("Table overloaded: Stats=~p\n~p\n", [Stats, ets:info(T)]), false; - Buckets>256, AvgLen < 6 -> + Buckets>256, AvgLen < 0.5 -> io:format("Table underloaded: Stats=~p\n~p\n", [Stats, ets:info(T)]), false; diff --git a/lib/stdlib/test/gen_server_SUITE.erl b/lib/stdlib/test/gen_server_SUITE.erl index 3242511f4a..338cd3dc0a 100644 --- a/lib/stdlib/test/gen_server_SUITE.erl +++ b/lib/stdlib/test/gen_server_SUITE.erl @@ -185,7 +185,7 @@ start(Config) when is_list(Config) -> gen_server:start({global, my_test_name}, gen_server_SUITE, [], []), ok = gen_server:call({global, my_test_name}, stop), - ct:sleep(1), + busy_wait_for_process(Pid4,600), {'EXIT', {noproc,_}} = (catch gen_server:call(Pid4, started_p, 10)), %% global register linked @@ -214,7 +214,7 @@ start(Config) when is_list(Config) -> gen_server:start({via, dummy_via, my_test_name}, gen_server_SUITE, [], []), ok = gen_server:call({via, dummy_via, my_test_name}, stop), - ct:sleep(1), + busy_wait_for_process(Pid6,600), {'EXIT', {noproc,_}} = (catch gen_server:call(Pid6, started_p, 10)), %% via register linked diff --git a/lib/stdlib/test/id_transform_SUITE.erl b/lib/stdlib/test/id_transform_SUITE.erl index 54f452825f..3d4ae1a189 100644 --- a/lib/stdlib/test/id_transform_SUITE.erl +++ b/lib/stdlib/test/id_transform_SUITE.erl @@ -61,13 +61,8 @@ id_transform(Config) when is_list(Config) -> "erl_id_trans.erl"]), {ok,erl_id_trans,Bin} = compile:file(File,[binary]), {module,erl_id_trans} = code:load_binary(erl_id_trans, File, Bin), - case test_server:purify_is_running() of - false -> - ct:timetrap({hours,1}), - run_in_test_suite(); - true -> - {skip,"Valgrind (too slow)"} - end. + ct:timetrap({hours,1}), + run_in_test_suite(). run_in_test_suite() -> SuperDir = filename:dirname(filename:dirname(code:which(?MODULE))), diff --git a/lib/stdlib/test/io_SUITE.erl b/lib/stdlib/test/io_SUITE.erl index be6b470ca7..7d48cbc97c 100644 --- a/lib/stdlib/test/io_SUITE.erl +++ b/lib/stdlib/test/io_SUITE.erl @@ -19,10 +19,7 @@ %% -module(io_SUITE). --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]). +-export([all/0, suite/0]). -export([error_1/1, float_g/1, otp_5403/1, otp_5813/1, otp_6230/1, otp_6282/1, otp_6354/1, otp_6495/1, otp_6517/1, otp_6502/1, @@ -51,12 +48,6 @@ -define(privdir(Conf), proplists:get_value(priv_dir, Conf)). -endif. -init_per_testcase(_Case, Config) -> - Config. - -end_per_testcase(_Case, _Config) -> - ok. - suite() -> [{ct_hooks,[ts_install_cth]}, {timetrap,{minutes,1}}]. @@ -72,22 +63,6 @@ all() -> io_lib_width_too_small, io_with_huge_message_queue, format_string, maps, coverage]. -groups() -> - []. - -init_per_suite(Config) -> - Config. - -end_per_suite(_Config) -> - ok. - -init_per_group(_GroupName, Config) -> - Config. - -end_per_group(_GroupName, Config) -> - Config. - - %% Error cases for output. error_1(Config) when is_list(Config) -> %% We don't do erroneous output on stdout - the test server @@ -952,7 +927,7 @@ otp_6708(Config) when is_list(Config) -> otp_7084() -> - [{timetrap,{minutes,3}}]. + [{timetrap,{minutes,6}}]. %% valgrind needs a lot of time %% OTP-7084. Printing floating point numbers nicely. otp_7084(Config) when is_list(Config) -> @@ -1830,13 +1805,14 @@ bad_printable_range(Config) when is_list(Config) -> Cmd = lists:concat([lib:progname()," +pcunnnnnicode -run erlang halt"]), P = open_port({spawn, Cmd}, [stderr_to_stdout, {line, 200}]), ok = receive - {P, {data, {eol , "bad range of printable characters" ++ _}}} -> - ok; - Other -> - Other - after 1000 -> - timeout - end, + {P, {data, {eol , "bad range of printable characters" ++ _}}} -> + ok; + Other -> + Other + %% valgrind needs a lot of time + after 6000 -> + timeout + end, catch port_close(P), flush_from_port(P), ok. diff --git a/lib/stdlib/test/io_proto_SUITE.erl b/lib/stdlib/test/io_proto_SUITE.erl index 4e39f011f6..1e286a9306 100644 --- a/lib/stdlib/test/io_proto_SUITE.erl +++ b/lib/stdlib/test/io_proto_SUITE.erl @@ -75,7 +75,7 @@ end_per_testcase(_Case, Config) -> suite() -> [{ct_hooks,[ts_install_cth]}, - {timetrap,{minutes,20}}]. + {timetrap,{minutes,5}}]. all() -> [setopts_getopts, unicode_options, unicode_options_gen, @@ -462,6 +462,7 @@ unicode_options(Config) when is_list(Config) -> %% Tests various unicode options on random generated files. unicode_options_gen(Config) when is_list(Config) -> + ct:timetrap({minutes,30}), %% valgrind needs a alot of time random:seed(1240, 900586, 553728), PrivDir = proplists:get_value(priv_dir, Config), AllModes = [utf8,utf16,{utf16,big},{utf16,little}, diff --git a/lib/stdlib/test/rand_SUITE.erl b/lib/stdlib/test/rand_SUITE.erl index 1bcdc3ccd0..cb778c96d4 100644 --- a/lib/stdlib/test/rand_SUITE.erl +++ b/lib/stdlib/test/rand_SUITE.erl @@ -18,18 +18,13 @@ %% %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([all/0, suite/0,groups/0]). -export([interval_int/1, interval_float/1, seed/1, api_eq/1, reference/1, basic_stats_uniform_1/1, basic_stats_uniform_2/1, basic_stats_normal/1, - plugin/1, measure/1 - ]). + plugin/1, measure/1]). -export([test/0, gen/1]). @@ -37,12 +32,6 @@ -define(LOOP, 1000000). -init_per_testcase(_Case, Config) -> - Config. - -end_per_testcase(_Case, _Config) -> - ok. - suite() -> [{ct_hooks,[ts_install_cth]}, {timetrap,{minutes,3}}]. @@ -52,19 +41,12 @@ all() -> api_eq, reference, {group, basic_stats}, - plugin, measure - ]. + plugin, measure]. groups() -> [{basic_stats, [parallel], [basic_stats_uniform_1, basic_stats_uniform_2, basic_stats_normal]}]. -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(), @@ -285,16 +267,19 @@ gen(_, _, Acc) -> lists:reverse(Acc). %% Check that the algorithms generate sound values. basic_stats_uniform_1(Config) when is_list(Config) -> + ct:timetrap({minutes,6}), %% valgrind needs a lot of time [basic_uniform_1(?LOOP, rand:seed_s(Alg), 0.0, array:new([{default, 0}])) || Alg <- algs()], ok. basic_stats_uniform_2(Config) when is_list(Config) -> + ct:timetrap({minutes,6}), %% valgrind needs a lot of time [basic_uniform_2(?LOOP, rand:seed_s(Alg), 0, array:new([{default, 0}])) || Alg <- algs()], ok. basic_stats_normal(Config) when is_list(Config) -> + ct:timetrap({minutes,6}), %% valgrind needs a lot of time io:format("Testing normal~n",[]), [basic_normal_1(?LOOP, rand:seed_s(Alg), 0, 0) || Alg <- algs()], ok. @@ -395,6 +380,7 @@ crypto_uniform_n(N, State0) -> %% Not a test but measures the time characteristics of the different algorithms measure(Suite) when is_atom(Suite) -> []; measure(_Config) -> + ct:timetrap({minutes,6}), %% valgrind needs a lot of time Algos = [crypto64|algs()], io:format("RNG uniform integer performance~n",[]), _ = measure_1(random, fun(State) -> {int, random:uniform_s(10000, State)} end), diff --git a/lib/stdlib/test/select_SUITE.erl b/lib/stdlib/test/select_SUITE.erl index e999d040c9..22b6d37e5d 100644 --- a/lib/stdlib/test/select_SUITE.erl +++ b/lib/stdlib/test/select_SUITE.erl @@ -59,42 +59,20 @@ config(priv_dir,_) -> ".". -else. %% When run in test server. --export([all/0, suite/0,groups/0,init_per_suite/1, end_per_suite/1, - init_per_group/2,end_per_group/2,select_test/1, - init_per_testcase/2, end_per_testcase/2, - return_values/1]). - -init_per_testcase(_Case, Config) -> - Config. - -end_per_testcase(_Case, _Config) -> - ok. +-export([all/0, suite/0, + select_test/1, return_values/1]). suite() -> [{ct_hooks,[ts_install_cth]}, - {timetrap,{minutes,20}}]. + {timetrap,{minutes,1}}]. all() -> [return_values, select_test]. -groups() -> - []. - -init_per_suite(Config) -> - Config. - -end_per_suite(_Config) -> - ok. - -init_per_group(_GroupName, Config) -> - Config. - -end_per_group(_GroupName, Config) -> - Config. - %% Test select in numerous ways. select_test(Config) when is_list(Config) -> + ct:timetrap({minutes,40}), %% valgrinds needs a lot of time do_test(Config). %% Test return values in specific situations for select/3 and select/1. diff --git a/lib/stdlib/test/supervisor_SUITE.erl b/lib/stdlib/test/supervisor_SUITE.erl index 3f1aa0e7a3..cd2c6b0cbb 100644 --- a/lib/stdlib/test/supervisor_SUITE.erl +++ b/lib/stdlib/test/supervisor_SUITE.erl @@ -66,7 +66,7 @@ %% Misc tests -export([child_unlink/1, tree/1, count_children/1, - count_restarting_children/1, + count_restarting_children/1, get_callback_module/1, do_not_save_start_parameters_for_temporary_children/1, do_not_save_child_specs_for_temporary_children/1, simple_one_for_one_scale_many_temporary_children/1, @@ -91,7 +91,7 @@ all() -> {group, normal_termination}, {group, shutdown_termination}, {group, abnormal_termination}, child_unlink, tree, - count_children, count_restarting_children, + count_children, count_restarting_children, get_callback_module, 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, @@ -1507,6 +1507,14 @@ count_restarting_children(Config) when is_list(Config) -> [1,0,0,0] = get_child_counts(SupPid). %%------------------------------------------------------------------------- +%% Test get_callback_module +get_callback_module(Config) when is_list(Config) -> + Child = {child, {supervisor_1, start_child, []}, temporary, 1000, + worker, []}, + {ok, SupPid} = start_link({ok, {{simple_one_for_one, 2, 3600}, [Child]}}), + supervisor_SUITE = supervisor:get_callback_module(SupPid). + +%%------------------------------------------------------------------------- %% Temporary children shall not be restarted so they should not save %% start parameters, as it potentially can take up a huge amount of %% memory for no purpose. diff --git a/lib/stdlib/test/unicode_SUITE.erl b/lib/stdlib/test/unicode_SUITE.erl index 81a591f433..07d63bdf22 100644 --- a/lib/stdlib/test/unicode_SUITE.erl +++ b/lib/stdlib/test/unicode_SUITE.erl @@ -21,10 +21,7 @@ -include_lib("common_test/include/ct.hrl"). --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([all/0, suite/0,groups/0, utf8_illegal_sequences_bif/1, utf16_illegal_sequences_bif/1, random_lists/1, @@ -38,12 +35,6 @@ ex_binaries_errors_utf32_little/1, ex_binaries_errors_utf32_big/1]). -init_per_testcase(_Case, Config) -> - Config. - -end_per_testcase(_Case, _Config) -> - ok. - suite() -> [{ct_hooks,[ts_install_cth]}, {timetrap,{minutes,20}}]. @@ -63,18 +54,6 @@ groups() -> ex_binaries_errors_utf32_little, ex_binaries_errors_utf32_big]}]. -init_per_suite(Config) -> - Config. - -end_per_suite(_Config) -> - ok. - -init_per_group(_GroupName, Config) -> - Config. - -end_per_group(_GroupName, Config) -> - Config. - binaries_errors_limit(Config) when is_list(Config) -> setlimit(10), ex_binaries_errors_utf8(Config), @@ -761,6 +740,7 @@ leading_lo_surrogate_bif(HiSurr, LoSurr, End) when LoSurr =< End -> leading_lo_surrogate_bif(_, _, _) -> ok. utf8_illegal_sequences_bif(Config) when is_list(Config) -> + ct:timetrap({minutes,40}), %% valgrind needs a lot setlimit(10), ex_utf8_illegal_sequences_bif(Config), setlimit(default), |