diff options
Diffstat (limited to 'lib/stdlib/test')
-rw-r--r-- | lib/stdlib/test/dets_SUITE.erl | 24 | ||||
-rw-r--r-- | lib/stdlib/test/erl_eval_SUITE.erl | 23 | ||||
-rw-r--r-- | lib/stdlib/test/erl_lint_SUITE.erl | 15 | ||||
-rw-r--r-- | lib/stdlib/test/ets_SUITE.erl | 35 | ||||
-rw-r--r-- | lib/stdlib/test/supervisor_SUITE.erl | 52 | ||||
-rw-r--r-- | lib/stdlib/test/supervisor_deadlock.erl | 14 |
6 files changed, 148 insertions, 15 deletions
diff --git a/lib/stdlib/test/dets_SUITE.erl b/lib/stdlib/test/dets_SUITE.erl index 7f5e06524a..35e587afcc 100644 --- a/lib/stdlib/test/dets_SUITE.erl +++ b/lib/stdlib/test/dets_SUITE.erl @@ -1876,9 +1876,33 @@ fixtable(Config, Version) when is_list(Config) -> {ok, _} = dets:open_file(T, [{type, duplicate_bag} | Args]), %% In a fixed table, delete and re-insert an object. ok = dets:insert(T, {1, a, b}), + SysBefore = erlang:timestamp(), + MonBefore = erlang:monotonic_time(), dets:safe_fixtable(T, true), + MonAfter = erlang:monotonic_time(), + SysAfter = erlang:timestamp(), + Self = self(), + {FixMonTime,[{Self,1}]} = dets:info(T,safe_fixed_monotonic_time), + {FixSysTime,[{Self,1}]} = dets:info(T,safe_fixed), + true = is_integer(FixMonTime), + true = MonBefore =< FixMonTime, + true = FixMonTime =< MonAfter, + {FstMs,FstS,FstUs} = FixSysTime, + true = is_integer(FstMs), + true = is_integer(FstS), + true = is_integer(FstUs), + case erlang:system_info(time_warp_mode) of + no_time_warp -> + true = timer:now_diff(FixSysTime, SysBefore) >= 0, + true = timer:now_diff(SysAfter, FixSysTime) >= 0; + _ -> + %% ets:info(Tab,safe_fixed) not timewarp safe... + ignore + end, ok = dets:match_delete(T, {1, a, b}), ok = dets:insert(T, {1, a, b}), + {FixMonTime,[{Self,1}]} = dets:info(T,safe_fixed_monotonic_time), + {FixSysTime,[{Self,1}]} = dets:info(T,safe_fixed), dets:safe_fixtable(T, false), 1 = length(dets:match_object(T, '_')), diff --git a/lib/stdlib/test/erl_eval_SUITE.erl b/lib/stdlib/test/erl_eval_SUITE.erl index b9c4ad0a46..c21c4e61ee 100644 --- a/lib/stdlib/test/erl_eval_SUITE.erl +++ b/lib/stdlib/test/erl_eval_SUITE.erl @@ -1,7 +1,7 @@ %% %% %CopyrightBegin% %% -%% Copyright Ericsson AB 1998-2013. All Rights Reserved. +%% Copyright Ericsson AB 1998-2016. 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. @@ -39,6 +39,7 @@ otp_7550/1, otp_8133/1, otp_10622/1, + otp_13228/1, funs/1, try_catch/1, eval_expr_5/1, @@ -83,7 +84,8 @@ all() -> pattern_expr, match_bin, guard_3, guard_4, guard_5, lc, simple_cases, unary_plus, apply_atom, otp_5269, otp_6539, otp_6543, otp_6787, otp_6977, otp_7550, - otp_8133, otp_10622, funs, try_catch, eval_expr_5, zero_width, + otp_8133, otp_10622, otp_13228, + funs, try_catch, eval_expr_5, zero_width, eep37, eep43]. groups() -> @@ -1042,6 +1044,13 @@ otp_10622(Config) when is_list(Config) -> ok. +otp_13228(doc) -> + ["OTP-13228. ERL-32: non-local function handler bug."]; +otp_13228(_Config) -> + LFH = {value, fun(foo, [io_fwrite]) -> worked end}, + EFH = {value, fun({io, fwrite}, [atom]) -> io_fwrite end}, + {value, worked, []} = parse_and_run("foo(io:fwrite(atom)).", LFH, EFH). + funs(doc) -> ["Simple cases, just to cover some code."]; funs(suite) -> @@ -1483,6 +1492,16 @@ eep43(Config) when is_list(Config) -> " #{ K1 := 1, K2 := 2, K3 := 3, {2,2} := 4} = Map " "end.", #{ 1 => 1, <<42:301>> => 2, {3,<<42:301>>} => 3, {2,2} => 4}), + check(fun () -> + X = key, + (fun(#{X := value}) -> true end)(#{X => value}) + end, + "begin " + " X = key, " + " (fun(#{X := value}) -> true end)(#{X => value}) " + "end.", + true), + error_check("[camembert]#{}.", {badmap,[camembert]}), error_check("[camembert]#{nonexisting:=v}.", {badmap,[camembert]}), error_check("#{} = 1.", {badmatch,1}), diff --git a/lib/stdlib/test/erl_lint_SUITE.erl b/lib/stdlib/test/erl_lint_SUITE.erl index 5347ccaf1f..375fb6bc93 100644 --- a/lib/stdlib/test/erl_lint_SUITE.erl +++ b/lib/stdlib/test/erl_lint_SUITE.erl @@ -1,7 +1,7 @@ %% %% %CopyrightBegin% %% -%% Copyright Ericsson AB 1999-2015. All Rights Reserved. +%% Copyright Ericsson AB 1999-2016. 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. @@ -65,7 +65,7 @@ too_many_arguments/1, basic_errors/1,bin_syntax_errors/1, predef/1, - maps/1,maps_type/1,otp_11851/1,otp_12195/1 + maps/1,maps_type/1,otp_11851/1,otp_12195/1, otp_13230/1 ]). % Default timetrap timeout (set in init_per_testcase). @@ -94,7 +94,7 @@ all() -> bif_clash, behaviour_basic, behaviour_multiple, otp_11861, otp_7550, otp_8051, format_warn, {group, on_load}, too_many_arguments, basic_errors, bin_syntax_errors, predef, - maps, maps_type, otp_11851, otp_12195]. + maps, maps_type, otp_11851, otp_12195, otp_13230]. groups() -> [{unused_vars_warn, [], @@ -3877,6 +3877,15 @@ otp_12195(Config) when is_list(Config) -> [] = run(Config, Ts), ok. +otp_13230(doc) -> + "OTP-13230: -deprecated without -module"; +otp_13230(Config) when is_list(Config) -> + Abstr = <<"-deprecated([{frutt,0,next_version}]).">>, + {errors,[{1,erl_lint,undefined_module}, + {1,erl_lint,{bad_deprecated,{frutt,0}}}], + []} = run_test2(Config, Abstr, []), + ok. + run(Config, Tests) -> F = fun({N,P,Ws,E}, BadL) -> case catch run_test(Config, P, Ws) of diff --git a/lib/stdlib/test/ets_SUITE.erl b/lib/stdlib/test/ets_SUITE.erl index ae431d66d9..30a158d9e1 100644 --- a/lib/stdlib/test/ets_SUITE.erl +++ b/lib/stdlib/test/ets_SUITE.erl @@ -3989,15 +3989,37 @@ safe_fixtable_do(Opts) -> ?line true = ets:safe_fixtable(Tab, true), ?line receive after 1 -> ok end, ?line true = ets:safe_fixtable(Tab, false), - ?line false = ets:info(Tab,safe_fixed), - ?line true = ets:safe_fixtable(Tab, true), + false = ets:info(Tab,safe_fixed_monotonic_time), + false = ets:info(Tab,safe_fixed), + SysBefore = erlang:timestamp(), + MonBefore = erlang:monotonic_time(), + true = ets:safe_fixtable(Tab, true), + MonAfter = erlang:monotonic_time(), + SysAfter = erlang:timestamp(), Self = self(), - ?line {{_,_,_},[{Self,1}]} = ets:info(Tab,safe_fixed), + {FixMonTime,[{Self,1}]} = ets:info(Tab,safe_fixed_monotonic_time), + {FixSysTime,[{Self,1}]} = ets:info(Tab,safe_fixed), + true = is_integer(FixMonTime), + true = MonBefore =< FixMonTime, + true = FixMonTime =< MonAfter, + {FstMs,FstS,FstUs} = FixSysTime, + true = is_integer(FstMs), + true = is_integer(FstS), + true = is_integer(FstUs), + case erlang:system_info(time_warp_mode) of + no_time_warp -> + true = timer:now_diff(FixSysTime, SysBefore) >= 0, + true = timer:now_diff(SysAfter, FixSysTime) >= 0; + _ -> + %% ets:info(Tab,safe_fixed) not timewarp safe... + ignore + end, %% Test that an unjustified 'unfix' is a no-op. {Pid,MRef} = my_spawn_monitor(fun() -> true = ets:safe_fixtable(Tab,false) end), {'DOWN', MRef, process, Pid, normal} = receive M -> M end, - ?line true = ets:info(Tab,fixed), - ?line {{_,_,_},[{Self,1}]} = ets:info(Tab,safe_fixed), + true = ets:info(Tab,fixed), + {FixMonTime,[{Self,1}]} = ets:info(Tab,safe_fixed_monotonic_time), + {FixSysTime,[{Self,1}]} = ets:info(Tab,safe_fixed), %% badarg's ?line {'EXIT', {badarg, _}} = (catch ets:safe_fixtable(Tab, foobar)), ?line true = ets:info(Tab,fixed), @@ -4043,6 +4065,7 @@ info_do(Opts) -> ?line undefined = ets:info(non_existing_table_xxyy,type), ?line undefined = ets:info(non_existing_table_xxyy,node), ?line undefined = ets:info(non_existing_table_xxyy,named_table), + ?line undefined = ets:info(non_existing_table_xxyy,safe_fixed_monotonic_time), ?line undefined = ets:info(non_existing_table_xxyy,safe_fixed), ?line verify_etsmem(EtsMem). @@ -5532,7 +5555,7 @@ otp_8166_zombie_creator(T,Deleted) -> [{'=<','$1', Deleted}], [true]}]), Pid ! zombies_created, - repeat_while(fun() -> case ets:info(T,safe_fixed) of + repeat_while(fun() -> case ets:info(T,safe_fixed_monotonic_time) of {_,[_P1,_P2]} -> false; _ -> diff --git a/lib/stdlib/test/supervisor_SUITE.erl b/lib/stdlib/test/supervisor_SUITE.erl index 8cb2a5194a..903ca76575 100644 --- a/lib/stdlib/test/supervisor_SUITE.erl +++ b/lib/stdlib/test/supervisor_SUITE.erl @@ -67,6 +67,7 @@ %% Misc tests -export([child_unlink/1, tree/1, count_children/1, + count_restarting_children/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, @@ -90,7 +91,8 @@ all() -> {group, normal_termination}, {group, shutdown_termination}, {group, abnormal_termination}, child_unlink, tree, - count_children, do_not_save_start_parameters_for_temporary_children, + count_children, count_restarting_children, + 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, simple_global_supervisor, hanging_restart_loop, hanging_restart_loop_simple, @@ -1459,6 +1461,54 @@ count_children(Config) when is_list(Config) -> [1,0,0,0] = get_child_counts(sup_test). %%------------------------------------------------------------------------- +%% Test count_children when some children are restarting +count_restarting_children(Config) when is_list(Config) -> + process_flag(trap_exit, true), + Child = {child, {supervisor_deadlock, start_child_noreg, []}, + permanent, brutal_kill, worker, []}, + %% 2 sek delay on failing restart (see supervisor_deadlock.erl) -> + %% MaxR=20, MaxT=10 should ensure a restart loop when starting and + %% restarting 3 instances of the child (as below) + {ok, SupPid} = start_link({ok, {{simple_one_for_one, 20, 10}, [Child]}}), + + %% Ets table with state read by supervisor_deadlock.erl + ets:new(supervisor_deadlock,[set,named_table,public]), + ets:insert(supervisor_deadlock,{fail_start,false}), + + [1,0,0,0] = get_child_counts(SupPid), + {ok, Ch1_1} = supervisor:start_child(SupPid, []), + [1,1,0,1] = get_child_counts(SupPid), + {ok, Ch1_2} = supervisor:start_child(SupPid, []), + [1,2,0,2] = get_child_counts(SupPid), + {ok, Ch1_3} = supervisor:start_child(SupPid, []), + [1,3,0,3] = get_child_counts(SupPid), + + supervisor_deadlock:restart_child(Ch1_1), + supervisor_deadlock:restart_child(Ch1_2), + supervisor_deadlock:restart_child(Ch1_3), + test_server:sleep(400), + [1,3,0,3] = get_child_counts(SupPid), + [Ch2_1, Ch2_2, Ch2_3] = [C || {_,C,_,_} <- supervisor:which_children(SupPid)], + + ets:insert(supervisor_deadlock,{fail_start,true}), + supervisor_deadlock:restart_child(Ch2_1), + supervisor_deadlock:restart_child(Ch2_2), + test_server:sleep(4000), % allow restart to happen before proceeding + [1,1,0,3] = get_child_counts(SupPid), + + ets:insert(supervisor_deadlock,{fail_start,false}), + test_server:sleep(4000), % allow restart to happen before proceeding + [1,3,0,3] = get_child_counts(SupPid), + + ok = supervisor:terminate_child(SupPid, Ch2_3), + [1,2,0,2] = get_child_counts(SupPid), + [Ch3_1, Ch3_2] = [C || {_,C,_,_} <- supervisor:which_children(SupPid)], + ok = supervisor:terminate_child(SupPid, Ch3_1), + [1,1,0,1] = get_child_counts(SupPid), + ok = supervisor:terminate_child(SupPid, Ch3_2), + [1,0,0,0] = get_child_counts(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/supervisor_deadlock.erl b/lib/stdlib/test/supervisor_deadlock.erl index 288547a972..8d3d1c6f30 100644 --- a/lib/stdlib/test/supervisor_deadlock.erl +++ b/lib/stdlib/test/supervisor_deadlock.erl @@ -11,9 +11,11 @@ init([child]) -> %% terminates immediately {ok, []}; [{fail_start, true}] -> - %% Restart frequency is MaxR=8, MaxT=10, so this will - %% ensure that restart intensity is not reached -> restart - %% loop + %% A restart frequency of MaxR=8, MaxT=10 should ensure + %% that restart intensity is not reached -> restart loop. + %% (Note that if we use simple_one_for_one, and start + %% 'many' child instances, the restart frequency must be + %% ajusted accordingly.) timer:sleep(2000), % NOTE: this could be a gen_server call timeout {stop, error} @@ -41,5 +43,11 @@ code_change(_OldVsn, State, _Extra) -> start_child() -> gen_server:start_link({local, ?MODULE}, ?MODULE, [child], []). +start_child_noreg() -> + gen_server:start_link(?MODULE, [child], []). + restart_child() -> gen_server:cast(supervisor_deadlock, restart). + +restart_child(Pid) -> + gen_server:cast(Pid, restart). |