diff options
Diffstat (limited to 'lib/stdlib/test')
-rw-r--r-- | lib/stdlib/test/calendar_SUITE.erl | 68 | ||||
-rw-r--r-- | lib/stdlib/test/erl_lint_SUITE.erl | 76 | ||||
-rw-r--r-- | lib/stdlib/test/gen_fsm_SUITE.erl | 12 | ||||
-rw-r--r-- | lib/stdlib/test/gen_statem_SUITE.erl | 43 | ||||
-rw-r--r-- | lib/stdlib/test/stdlib_bench_SUITE.erl | 79 | ||||
-rw-r--r-- | lib/stdlib/test/stdlib_bench_SUITE_data/generic_server.erl | 4 | ||||
-rw-r--r-- | lib/stdlib/test/stdlib_bench_SUITE_data/generic_statem.erl | 10 | ||||
-rw-r--r-- | lib/stdlib/test/unicode_util_SUITE.erl | 27 |
8 files changed, 229 insertions, 90 deletions
diff --git a/lib/stdlib/test/calendar_SUITE.erl b/lib/stdlib/test/calendar_SUITE.erl index 55118e251c..df62c0921d 100644 --- a/lib/stdlib/test/calendar_SUITE.erl +++ b/lib/stdlib/test/calendar_SUITE.erl @@ -183,14 +183,15 @@ rfc3339(Config) when is_list(Config) -> D = [{time_designator, $\s}], Z = [{offset, "Z"}], - "1985-04-12T23:20:50.52Z" = test_parse("1985-04-12T23:20:50.52Z", Ms), - "1985-04-12T23:20:50.52Z" = test_parse("1985-04-12t23:20:50.52z", Ms), - "1985-04-12T21:20:50.52Z" = + "1985-04-12T23:20:50.520Z" = test_parse("1985-04-12T23:20:50.52Z", Ms), + "1985-04-12T23:20:50.520Z" = test_parse("1985-04-12t23:20:50.52z", Ms), + "1985-04-12T21:20:50.520Z" = test_parse("1985-04-12T23:20:50.52+02:00", Ms), "1985-04-12T23:20:50Z" = test_parse("1985-04-12T23:20:50.52Z", S), - "1985-04-12T23:20:50.52Z" = test_parse("1985-04-12T23:20:50.52Z", Ms), - "1985-04-12T23:20:50.52Z" = test_parse("1985-04-12t23:20:50.52z", Mys), - "1985-04-12 21:20:50.52Z" = + "1985-04-12T23:20:50.520Z" = test_parse("1985-04-12T23:20:50.52Z", Ms), + "1985-04-12T23:20:50.520000Z" = + test_parse("1985-04-12t23:20:50.52z", Mys), + "1985-04-12 21:20:50.520000000Z" = test_parse("1985-04-12 23:20:50.52+02:00", Ns++D), "1985-04-12T23:20:50Z" = test_parse("1985-04-12T23:20:50.52Z"), "1996-12-20T00:39:57Z" = test_parse("1996-12-19T16:39:57-08:00"), @@ -221,17 +222,20 @@ rfc3339(Config) when is_list(Config) -> "1970-01-02T00:00:00Z" = test_parse("1970-01-01T23:59:60Z"), "1970-01-02T00:00:00Z" = test_parse("1970-01-01T23:59:60.5Z"), "1970-01-02T00:00:00Z" = test_parse("1970-01-01T23:59:60.55Z"), - "1970-01-02T00:00:00.55Z" = test_parse("1970-01-01T23:59:60.55Z", Ms), - "1970-01-02T00:00:00.55Z" = test_parse("1970-01-01T23:59:60.55Z", Mys), - "1970-01-02T00:00:00.55Z" = test_parse("1970-01-01T23:59:60.55Z", Ns), + "1970-01-02T00:00:00.550Z" = test_parse("1970-01-01T23:59:60.55Z", Ms), + "1970-01-02T00:00:00.550000Z" = + test_parse("1970-01-01T23:59:60.55Z", Mys), + "1970-01-02T00:00:00.550000000Z" = + test_parse("1970-01-01T23:59:60.55Z", Ns), "1970-01-02T00:00:00.999999Z" = test_parse("1970-01-01T23:59:60.999999Z", Mys), - "1970-01-02T00:00:01Z" = + "1970-01-02T00:00:01.000Z" = test_parse("1970-01-01T23:59:60.999999Z", Ms), "1970-01-01T00:00:00Z" = test_parse("1970-01-01T00:00:00+00:00"), "1970-01-01T00:00:00Z" = test_parse("1970-01-01T00:00:00-00:00"), "1969-12-31T00:01:00Z" = test_parse("1970-01-01T00:00:00+23:59"), - "1918-11-11T09:00:00Z" = test_parse("1918-11-11T11:00:00+02:00", Mys), + "1918-11-11T09:00:00.000000Z" = + test_parse("1918-11-11T11:00:00+02:00", Mys), "1970-01-01T00:00:00.000001Z" = test_parse("1970-01-01T00:00:00.000001Z", Mys), @@ -242,26 +246,26 @@ rfc3339(Config) when is_list(Config) -> test_time(erlang:system_time(millisecond), Ms), test_time(erlang:system_time(microsecond), Mys++[{offset, "-02:20"}]), - T = erlang:system_time(second), - TS = do_format(T, []), - TS = do_format(T * 1000, Ms), - TS = do_format(T * 1000 * 1000, Mys), - TS = do_format(T * 1000 * 1000 * 1000, Ns), - 946720800 = TO = do_parse("2000-01-01 10:00:00Z", []), Str = "2000-01-01T10:02:00+00:02", Str = do_format(TO, [{offset, 120}]), - Str = do_format(TO * 1000, [{offset, 120 * 1000}]++Ms), - Str = do_format(TO * 1000 * 1000, [{offset, 120 * 1000 * 1000}]++Mys), - Str = do_format(TO * 1000 * 1000 * 1000, - [{offset, 120 * 1000 * 1000 * 1000}]++Ns), + "2000-01-01T10:02:00.000+00:02" = + do_format(TO * 1000, [{offset, 120 * 1000}]++Ms), + "2000-01-01T10:02:00.000000+00:02" = + do_format(TO * 1000 * 1000, [{offset, 120 * 1000 * 1000}]++Mys), + "2000-01-01T10:02:00.000000000+00:02" = + do_format(TO * 1000 * 1000 * 1000, + [{offset, 120 * 1000 * 1000 * 1000}]++Ns), NStr = "2000-01-01T09:58:00-00:02", NStr = do_format(TO, [{offset, -120}]), - NStr = do_format(TO * 1000, [{offset, -120 * 1000}]++Ms), - NStr = do_format(TO * 1000 * 1000, [{offset, -120 * 1000 * 1000}]++Mys), - NStr = do_format(TO * 1000 * 1000 * 1000, - [{offset, -120 * 1000 * 1000 * 1000}]++Ns), + "2000-01-01T09:58:00.000-00:02" = + do_format(TO * 1000, [{offset, -120 * 1000}]++Ms), + "2000-01-01T09:58:00.000000-00:02" = + do_format(TO * 1000 * 1000, [{offset, -120 * 1000 * 1000}]++Mys), + "2000-01-01T09:58:00.000000000-00:02" = + do_format(TO * 1000 * 1000 * 1000, + [{offset, -120 * 1000 * 1000 * 1000}]++Ns), 543210000 = do_parse("1970-01-01T00:00:00.54321Z", Ns), 54321000 = do_parse("1970-01-01T00:00:00.054321Z", Ns), @@ -278,18 +282,18 @@ rfc3339(Config) when is_list(Config) -> -1613833200000000 = do_parse("1918-11-11T11:00:00+02:00", Mys), -1613833200000000 = do_parse("1918-11-11T09:00:00Z", Mys), - "1970-01-01T00:00:00Z" = do_format_z(0, Mys), + "1970-01-01T00:00:00.000000Z" = do_format_z(0, Mys), "1970-01-01T00:00:01Z" = do_format_z(1, S), "1970-01-01T00:00:00.001Z" = do_format_z(1, Ms), "1970-01-01T00:00:00.000001Z" = do_format_z(1, Mys), "1970-01-01T00:00:00.000000001Z" = do_format_z(1, Ns), - "1970-01-01T00:00:01Z" = do_format_z(1000000, Mys), - "1970-01-01T00:00:00.54321Z" = do_format_z(543210, Mys), + "1970-01-01T00:00:01.000000Z" = do_format_z(1000000, Mys), + "1970-01-01T00:00:00.543210Z" = do_format_z(543210, Mys), "1970-01-01T00:00:00.543Z" = do_format_z(543, Ms), - "1970-01-01T00:00:00.54321Z" = do_format_z(543210000, Ns), - "1970-01-01T00:00:06.54321Z" = do_format_z(6543210, Mys), - "1979-06-21T12:12:12Z" = do_format_z(298815132000000, Mys), - "1918-11-11T13:00:00Z" = do_format_z(-1613818800000000, Mys), + "1970-01-01T00:00:00.543210000Z" = do_format_z(543210000, Ns), + "1970-01-01T00:00:06.543210Z" = do_format_z(6543210, Mys), + "1979-06-21T12:12:12.000000Z" = do_format_z(298815132000000, Mys), + "1918-11-11T13:00:00.000000Z" = do_format_z(-1613818800000000, Mys), ok. %% diff --git a/lib/stdlib/test/erl_lint_SUITE.erl b/lib/stdlib/test/erl_lint_SUITE.erl index c1613a7273..e791da48cf 100644 --- a/lib/stdlib/test/erl_lint_SUITE.erl +++ b/lib/stdlib/test/erl_lint_SUITE.erl @@ -67,7 +67,8 @@ record_errors/1, otp_11879_cont/1, non_latin1_module/1, otp_14323/1, stacktrace_syntax/1, - otp_14285/1, otp_14378/1]). + otp_14285/1, otp_14378/1, + external_funs/1,otp_15456/1]). suite() -> [{ct_hooks,[ts_install_cth]}, @@ -88,7 +89,8 @@ all() -> maps, maps_type, maps_parallel_match, otp_11851, otp_11879, otp_13230, record_errors, otp_11879_cont, non_latin1_module, otp_14323, - stacktrace_syntax, otp_14285, otp_14378]. + stacktrace_syntax, otp_14285, otp_14378, external_funs, + otp_15456]. groups() -> [{unused_vars_warn, [], @@ -2118,6 +2120,61 @@ otp_5362(Config) when is_list(Config) -> [] = run(Config, Ts), ok. +%% OTP-15456. All compiler options can now be given in the option list +%% (as opposed to only in files). +otp_15456(Config) when is_list(Config) -> + Ts = [ + %% {nowarn_deprecated_function,[{M,F,A}]} can now be given + %% in the option list as well as in an attribute. + %% Wherever it occurs, it is not affected by + %% warn_deprecated_function. + {otp_15456_1, + <<"-compile({nowarn_deprecated_function,{erlang,now,0}}). + -export([foo/0]). + + foo() -> + {erlang:now(), random:seed0(), random:seed(1, 2, 3), + random:uniform(), random:uniform(42)}. + ">>, + {[{nowarn_deprecated_function,{random,seed0,0}}, + {nowarn_deprecated_function,[{random,uniform,0}, + {random,uniform,1}]}, + %% There should be no warnings when attempting to + %% turn of warnings for functions that are not + %% deprecated or not used in the module. + {nowarn_deprecated_function,{random,uniform_s,1}}, + {nowarn_deprecated_function,{erlang,abs,1}}, + warn_deprecated_function]}, + {warnings,[{5,erl_lint, + {deprecated,{random,seed,3}, + "the 'random' module is deprecated; " + "use the 'rand' module instead"}}]}}, + + %% {nowarn_unused_function,[{M,F,A}]} can be given + %% in the option list as well as in an attribute. + %% It was incorrectly documented to only work when + %% given in an attribute. + {otp_15456_2, + <<"-compile({nowarn_unused_function,foo/0}). + foo() -> ok. + bar() -> ok. + foobar() -> ok. + barf(_) -> ok. + other() -> ok. + ">>, + {[{nowarn_unused_function,[{bar,0},{foobar,0}]}, + {nowarn_unused_function,{barf,1}}, + %% There should be no warnings when attempting to + %% turn of warnings for unused functions that are not + %% defined in the module. + {nowarn_unused_function,{not_defined_in_module,1}}, + warn_unused_function]}, + {warnings,[{6,erl_lint,{unused_function,{other,0}}}]} + }], + + [] = run(Config, Ts), + ok. + %% OTP-5371. Aliases for bit syntax expressions are no longer allowed. otp_5371(Config) when is_list(Config) -> Ts = [{otp_5371_1, @@ -4134,6 +4191,21 @@ otp_14285(Config) -> run(Config, Ts), ok. +external_funs(Config) when is_list(Config) -> + Ts = [{external_funs_1, + %% ERL-762: Unused variable warning not being emitted. + <<"f() -> + BugVar = process_info(self()), + if true -> fun m:f/1 end. + f(M, F) -> + BugVar = process_info(self()), + if true -> fun M:F/1 end.">>, + [], + {warnings,[{2,erl_lint,{unused_var,'BugVar'}}, + {5,erl_lint,{unused_var,'BugVar'}}]}}], + run(Config, Ts), + ok. + format_error(E) -> lists:flatten(erl_lint:format_error(E)). diff --git a/lib/stdlib/test/gen_fsm_SUITE.erl b/lib/stdlib/test/gen_fsm_SUITE.erl index a8264e5a84..62d9d0e0ae 100644 --- a/lib/stdlib/test/gen_fsm_SUITE.erl +++ b/lib/stdlib/test/gen_fsm_SUITE.erl @@ -521,14 +521,16 @@ error_format_status(Config) when is_list(Config) -> error_logger_forwarder:register(), OldFl = process_flag(trap_exit, true), StateData = "called format_status", + Parent = self(), {ok, Pid} = gen_fsm:start(gen_fsm_SUITE, {state_data, StateData}, []), %% bad return value in the gen_fsm loop {'EXIT',{{bad_return_value, badreturn},_}} = (catch gen_fsm:sync_send_event(Pid, badreturn)), receive {error,_GroupLeader,{Pid, - "** State machine"++_, - [Pid,{_,_,badreturn},idle,{formatted,StateData},_]}} -> + "** State machine "++_, + [Pid,badreturn,Parent,idle,{formatted,StateData}, + {bad_return_value,badreturn}|_]}} -> ok; Other -> io:format("Unexpected: ~p", [Other]), @@ -541,12 +543,14 @@ terminate_crash_format(Config) when is_list(Config) -> error_logger_forwarder:register(), OldFl = process_flag(trap_exit, true), StateData = crash_terminate, + Parent = self(), {ok, Pid} = gen_fsm:start(gen_fsm_SUITE, {state_data, StateData}, []), stop_it(Pid), receive {error,_GroupLeader,{Pid, - "** State machine"++_, - [Pid,{_,_,_},idle,{formatted, StateData},_]}} -> + "** State machine "++_, + [Pid,stop,Parent,idle,{formatted, StateData}, + {crash,terminate}|_]}} -> ok; Other -> io:format("Unexpected: ~p", [Other]), diff --git a/lib/stdlib/test/gen_statem_SUITE.erl b/lib/stdlib/test/gen_statem_SUITE.erl index 017939fdd6..16cf8f43f9 100644 --- a/lib/stdlib/test/gen_statem_SUITE.erl +++ b/lib/stdlib/test/gen_statem_SUITE.erl @@ -513,7 +513,9 @@ abnormal1dirty(Config) -> %% trap exit since we must link to get the real bad_return_ error abnormal2(Config) -> OldFl = process_flag(trap_exit, true), - {ok,Pid} = gen_statem:start_link(?MODULE, start_arg(Config, []), []), + {ok,Pid} = + gen_statem:start_link( + ?MODULE, start_arg(Config, []), [{debug,[log]}]), %% bad return value in the gen_statem loop {{{bad_return_from_state_function,badreturn},_},_} = @@ -531,7 +533,9 @@ abnormal2(Config) -> %% trap exit since we must link to get the real bad_return_ error abnormal3(Config) -> OldFl = process_flag(trap_exit, true), - {ok,Pid} = gen_statem:start_link(?MODULE, start_arg(Config, []), []), + {ok,Pid} = + gen_statem:start_link( + ?MODULE, start_arg(Config, []), [{debug,[log]}]), %% bad return value in the gen_statem loop {{{bad_action_from_state_function,badaction},_},_} = @@ -549,7 +553,9 @@ abnormal3(Config) -> %% trap exit since we must link to get the real bad_return_ error abnormal4(Config) -> OldFl = process_flag(trap_exit, true), - {ok,Pid} = gen_statem:start_link(?MODULE, start_arg(Config, []), []), + {ok,Pid} = + gen_statem:start_link( + ?MODULE, start_arg(Config, []), [{debug,[log]}]), %% bad return value in the gen_statem loop BadTimeout = {badtimeout,4711,ouch}, @@ -689,7 +695,10 @@ state_enter(_Config) -> end}, {ok,STM} = gen_statem:start_link( - ?MODULE, {map_statem,Machine,[state_enter]}, [{debug,[trace]}]), + ?MODULE, {map_statem,Machine,[state_enter]}, + [{debug,[trace,{log,17}]}]), + ok = sys:log(STM, false), + ok = sys:log(STM, true), [{1,enter,start,start}] = flush(), {2,echo,start} = gen_statem:call(STM, echo), @@ -708,6 +717,11 @@ state_enter(_Config) -> {13,internal,start,wait}] = flush(), {14,repeat,start} = gen_statem:call(STM, repeat), [{15,enter,start,start}] = flush(), + + {ok,Log} = sys:log(STM, get), + io:format("sys:log ~p~n", [Log]), + ok = sys:log(STM, print), + {16,stop} = gen_statem:call(STM, {stop,bye}), [{'EXIT',STM,bye}] = flush(), @@ -1470,7 +1484,8 @@ enter_loop(_Config) -> %% Locally registered process + {local,Name} {ok,Pid1a} = - proc_lib:start_link(?MODULE, enter_loop, [local,local]), + proc_lib:start_link( + ?MODULE, enter_loop, [local,local,[{debug,[{log,7}]}]]), yes = gen_statem:call(Pid1a, 'alive?'), stopped = gen_statem:call(Pid1a, stop), receive @@ -1482,7 +1497,8 @@ enter_loop(_Config) -> %% Unregistered process + {local,Name} {ok,Pid1b} = - proc_lib:start_link(?MODULE, enter_loop, [anon,local]), + proc_lib:start_link( + ?MODULE, enter_loop, [anon,local,[{debug,[log]}]]), receive {'EXIT',Pid1b,process_not_registered} -> ok @@ -1591,6 +1607,9 @@ enter_loop(_Config) -> ok = verify_empty_msgq(). enter_loop(Reg1, Reg2) -> + enter_loop(Reg1, Reg2, []). +%% +enter_loop(Reg1, Reg2, Opts) -> process_flag(trap_exit, true), case Reg1 of local -> register(armitage, self()); @@ -1602,15 +1621,15 @@ enter_loop(Reg1, Reg2) -> case Reg2 of local -> gen_statem:enter_loop( - ?MODULE, [], state0, [], {local,armitage}); + ?MODULE, Opts, state0, [], {local,armitage}); global -> gen_statem:enter_loop( - ?MODULE, [], state0, [], {global,armitage}); + ?MODULE, Opts, state0, [], {global,armitage}); via -> gen_statem:enter_loop( - ?MODULE, [], state0, [], {via, dummy_via, armitage}); + ?MODULE, Opts, state0, [], {via, dummy_via, armitage}); anon -> - gen_statem:enter_loop(?MODULE, [], state0, []) + gen_statem:enter_loop(?MODULE, Opts, state0, []) end. undef_code_change(_Config) -> @@ -1642,7 +1661,9 @@ undef_terminate2(_Config) -> undef_in_terminate(_Config) -> Data = {undef_in_terminate, {?MODULE, terminate}}, - {ok, Statem} = gen_statem:start(?MODULE, {data, Data}, []), + {ok, Statem} = + gen_statem:start( + ?MODULE, {data, Data}, [{debug,[log]}]), try gen_statem:stop(Statem), ct:fail(should_crash) diff --git a/lib/stdlib/test/stdlib_bench_SUITE.erl b/lib/stdlib/test/stdlib_bench_SUITE.erl index b937eeb06a..3456442088 100644 --- a/lib/stdlib/test/stdlib_bench_SUITE.erl +++ b/lib/stdlib/test/stdlib_bench_SUITE.erl @@ -38,7 +38,9 @@ groups() -> [norm_nfc_list, norm_nfc_deep_l, norm_nfc_binary, string_lexemes_list, string_lexemes_binary ]}, - {binary, [{repeat, 5}], + %% Only run 1 binary match repeat as it is very slow pre OTP-22. + %% The results seem to be stable enough anyway + {binary, [{repeat, 1}], [match_single_pattern_no_match, matches_single_pattern_no_match, matches_single_pattern_eventual_match, @@ -65,9 +67,9 @@ cases(gen_server) -> [simple, simple_timer, simple_mon, simple_timer_mon, generic, generic_timer]; cases(gen_statem) -> - [generic, generic_fsm, generic_fsm_transit, - generic_statem, generic_statem_transit, - generic_statem_complex]. + [generic, generic_log, generic_log100, generic_fsm, generic_fsm_transit, + generic_statem, generic_statem_log, generic_statem_log100, + generic_statem_transit, generic_statem_complex]. init_per_group(gen_server, Config) -> compile_servers(Config), @@ -164,19 +166,19 @@ norm_data(Config) -> match_single_pattern_no_match(_Config) -> Binary = binary:copy(<<"ugbcfuysabfuqyfikgfsdalpaskfhgjsdgfjwsalp">>, 1000000), - comment(test(binary, match, [Binary, <<"o">>])). + comment(test(100, binary, match, [Binary, <<"o">>])). matches_single_pattern_no_match(_Config) -> Binary = binary:copy(<<"ugbcfuysabfuqyfikgfsdalpaskfhgjsdgfjwsalp">>, 1000000), - comment(test(binary, matches, [Binary, <<"o">>])). + comment(test(100, binary, matches, [Binary, <<"o">>])). matches_single_pattern_eventual_match(_Config) -> Binary = binary:copy(<<"ugbcfuysabfuqyfikgfsdalpaskfhgjsdgfjwsal\n">>, 1000000), - comment(test(binary, matches, [Binary, <<"\n">>])). + comment(test(100, binary, matches, [Binary, <<"\n">>])). matches_single_pattern_frequent_match(_Config) -> Binary = binary:copy(<<"abc\n">>, 1000000), - comment(test(binary, matches, [Binary, <<"abc">>])). + comment(test(100, binary, matches, [Binary, <<"abc">>])). %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% @@ -233,9 +235,11 @@ list() -> random_byte_list(?SIZE). test(Mod, Fun, Args) -> - F = fun() -> loop(?N, Mod, Fun, Args) end, + test(?N, Mod, Fun, Args). +test(Iter, Mod, Fun, Args) -> + F = fun() -> loop(Iter, Mod, Fun, Args) end, {Time, ok} = timer:tc(fun() -> lspawn(F) end), - report_mfa(Time, Mod). + report_mfa(Iter, Time, Mod). loop(0, _M, _F, _A) -> garbage_collect(), ok; loop(N, M, F, A) -> @@ -248,8 +252,8 @@ lspawn(Fun) -> {'DOWN', Ref, process, Pid, Rep} -> Rep end. -report_mfa(Time, Mod) -> - Tps = round((?N*1000000)/Time), +report_mfa(Iter, Time, Mod) -> + Tps = round((Iter*1000000)/Time), ct_event:notify(#event{name = benchmark_data, data = [{suite, "stdlib_" ++ atom_to_list(Mod)}, {value, Tps}]}), @@ -290,12 +294,24 @@ simple_timer_mon(Config) when is_list(Config) -> generic(Config) when is_list(Config) -> comment(do_tests(generic, single_small, Config)). +generic_log(Config) when is_list(Config) -> + comment(do_tests(generic_log, single_small, Config)). + +generic_log100(Config) when is_list(Config) -> + comment(do_tests(generic_log100, single_small, Config)). + generic_timer(Config) when is_list(Config) -> comment(do_tests(generic_timer, single_small, Config)). generic_statem(Config) when is_list(Config) -> comment(do_tests(generic_statem, single_small, Config)). +generic_statem_log(Config) when is_list(Config) -> + comment(do_tests(generic_statem_log, single_small, Config)). + +generic_statem_log100(Config) when is_list(Config) -> + comment(do_tests(generic_statem_log100, single_small, Config)). + generic_statem_transit(Config) when is_list(Config) -> comment(do_tests(generic_statem_transit, single_small, Config)). @@ -367,9 +383,9 @@ norm(T, Ref) -> do_tests(Test, ParamSet, Config) -> BenchmarkSuite = ?config(benchmark_suite, Config), - {Client, ServerMod} = bench(Test), + {Client, ServerMod, ServerArg} = bench(Test), {Parallelism, Message} = bench_params(ParamSet), - Fun = create_clients(Message, ServerMod, Client, Parallelism), + Fun = create_clients(Message, ServerMod, ServerArg, Client, Parallelism), {TotalLoops, AllPidTime} = run_test(Fun), try ?CALLS_PER_LOOP * round((1000 * TotalLoops) / AllPidTime) of PerSecond -> @@ -484,27 +500,35 @@ generic_fsm_transit_client(N, M, P) -> generic_fsm_transit_client(N+1, M, P). bench(simple) -> - {fun simple_client/3, simple_server}; + {fun simple_client/3, simple_server, term}; bench(simple_timer) -> - {fun simple_client_timer/3, simple_server_timer}; + {fun simple_client_timer/3, simple_server_timer, term}; bench(simple_mon) -> - {fun simple_client_mon/3, simple_server_mon}; + {fun simple_client_mon/3, simple_server_mon, term}; bench(simple_timer_mon) -> - {fun simple_client_timer_mon/3, simple_server_timer_mon}; + {fun simple_client_timer_mon/3, simple_server_timer_mon, term}; bench(generic) -> - {fun generic_client/3, generic_server}; + {fun generic_client/3, generic_server, [term]}; +bench(generic_log) -> + {fun generic_client/3, generic_server, [term,{debug,[log]}]}; +bench(generic_log100) -> + {fun generic_client/3, generic_server, [term,{debug,[{log,100}]}]}; bench(generic_timer) -> - {fun generic_timer_client/3, generic_server_timer}; + {fun generic_timer_client/3, generic_server_timer, term}; bench(generic_statem) -> - {fun generic_statem_client/3, generic_statem}; + {fun generic_statem_client/3, generic_statem, [term]}; +bench(generic_statem_log) -> + {fun generic_statem_client/3, generic_statem, [term,{debug,[log]}]}; +bench(generic_statem_log100) -> + {fun generic_statem_client/3, generic_statem, [term,{debug,[{log,100}]}]}; bench(generic_statem_transit) -> - {fun generic_statem_transit_client/3, generic_statem}; + {fun generic_statem_transit_client/3, generic_statem, [term]}; bench(generic_statem_complex) -> - {fun generic_statem_complex_client/3, generic_statem_complex}; + {fun generic_statem_complex_client/3, generic_statem_complex, term}; bench(generic_fsm) -> - {fun generic_fsm_client/3, generic_fsm}; + {fun generic_fsm_client/3, generic_fsm, term}; bench(generic_fsm_transit) -> - {fun generic_fsm_transit_client/3, generic_fsm}. + {fun generic_fsm_transit_client/3, generic_fsm, term}. %% -> {Parallelism, MessageTerm} bench_params(single_small) -> {1, small()}; @@ -532,10 +556,9 @@ parallelism() -> _ -> 1 end. -create_clients(M, ServerMod, Client, Parallel) -> +create_clients(M, ServerMod, ServerArg, Client, Parallel) -> fun() -> - State = term, - ServerPid = ServerMod:start(State), + ServerPid = ServerMod:start(ServerArg), PidRefs = [spawn_monitor(fun() -> Client(0, M, ServerPid) end) || _ <- lists:seq(1, Parallel)], timer:sleep(?MAX_TIME), diff --git a/lib/stdlib/test/stdlib_bench_SUITE_data/generic_server.erl b/lib/stdlib/test/stdlib_bench_SUITE_data/generic_server.erl index abd61dcdef..3707d00dee 100644 --- a/lib/stdlib/test/stdlib_bench_SUITE_data/generic_server.erl +++ b/lib/stdlib/test/stdlib_bench_SUITE_data/generic_server.erl @@ -8,8 +8,8 @@ -define(GEN_SERVER, gen_server). -start(State) -> - {ok, Pid} = ?GEN_SERVER:start(?MODULE, State, []), +start([State|Opts]) -> + {ok, Pid} = ?GEN_SERVER:start(?MODULE, State, Opts), Pid. init(State) -> diff --git a/lib/stdlib/test/stdlib_bench_SUITE_data/generic_statem.erl b/lib/stdlib/test/stdlib_bench_SUITE_data/generic_statem.erl index 2e0491f060..b106619568 100644 --- a/lib/stdlib/test/stdlib_bench_SUITE_data/generic_statem.erl +++ b/lib/stdlib/test/stdlib_bench_SUITE_data/generic_statem.erl @@ -28,8 +28,8 @@ %% API -start(Data) -> - {ok, Pid} = gen_statem:start(?MODULE, Data, []), +start([Data|Opts]) -> + {ok, Pid} = gen_statem:start(?MODULE, Data, Opts), Pid. stop(P) -> @@ -52,7 +52,9 @@ init(Data) -> state1({call, From}, {reply, M}, Data) -> {keep_state, Data, {reply, From, M}}; state1({call, From}, {transit, M}, Data) -> - {next_state, state2, Data, {reply, From, M}}. + {next_state, state2, Data, + [{reply, From, M},{state_timeout,5000,5000}]}. state2({call, From}, {transit, M}, Data) -> - {next_state, state1, Data, {reply, From, M}}. + {next_state, state1, Data, + [{reply, From, M},{state_timeout,5000,5000}]}. diff --git a/lib/stdlib/test/unicode_util_SUITE.erl b/lib/stdlib/test/unicode_util_SUITE.erl index 962b307b07..044b4e5834 100644 --- a/lib/stdlib/test/unicode_util_SUITE.erl +++ b/lib/stdlib/test/unicode_util_SUITE.erl @@ -126,17 +126,30 @@ verify_gc(Line0, N, Acc) -> %io:format("Line: ~s~n",[Line]), [Data|_Comments] = string:tokens(Line, "#"), - %io:format("Data: ~w~n",[string:tokens(Data, " \t")]), + %% io:format("Data: ~w~n",[string:tokens(Data, " \t")]), {Str,Res} = gc_test_data(string:tokens(Data, " \t"), [], [[]]), - try - Res = fetch(Str, fun unicode_util:gc/1), - Acc - catch _Cl:{badmatch, Other} -> + %% io:format("InputStr: ~w ~w~n",[Str,unicode:characters_to_binary(Str)]), + case verify_gc(Str, Res, N, Line) andalso + verify_gc(unicode:characters_to_binary(Str), Res, N, Line0) of + true -> Acc; + false -> Acc+1 + end. + +verify_gc({error,_,[CP|_]}=Err, _Res, N, Line) -> + IsSurrogate = 16#D800 =< CP andalso CP =< 16#DFFF, + %% Surrogat is not valid in utf8 encoding only utf16 + IsSurrogate orelse + io:format("~w: ~ts~n Error in unicode:characters_to_binary ~w~n", [N, Line, Err]), + IsSurrogate; +verify_gc(Str, Res, N, Line) -> + try fetch(Str, fun unicode_util:gc/1) of + Res -> true; + Other -> io:format("Failed: ~p~nInput: ~ts~n\t=> ~w |~ts|~n",[N, Line, Str, Str]), io:format("Expected: ~p~n", [Res]), io:format("Got: ~w~n", [Other]), - Acc+1; - Cl:R:Stacktrace -> + false + catch Cl:R:Stacktrace -> io:format("~p: ~ts => |~tp|~n",[N, Line, Str]), io:format("Expected: ~p~n", [Res]), erlang:raise(Cl,R,Stacktrace) |