From ec35c6439d3707801c7527dd2ea01ef0aa0421ed Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Bj=C3=B6rn=20Gustavsson?= Date: Thu, 25 Feb 2016 15:28:25 +0100 Subject: Eliminate use of test_server:fail/0,1 --- lib/stdlib/test/beam_lib_SUITE.erl | 2 +- lib/stdlib/test/dets_SUITE.erl | 8 +-- lib/stdlib/test/epp_SUITE.erl | 3 +- lib/stdlib/test/erl_eval_SUITE.erl | 10 ++-- lib/stdlib/test/erl_expand_records_SUITE.erl | 5 +- lib/stdlib/test/erl_lint_SUITE.erl | 3 +- lib/stdlib/test/erl_pp_SUITE.erl | 3 +- lib/stdlib/test/error_logger_h_SUITE.erl | 2 +- lib/stdlib/test/escript_SUITE.erl | 2 +- lib/stdlib/test/ets_SUITE.erl | 42 +++++++-------- lib/stdlib/test/file_sorter_SUITE.erl | 6 +-- lib/stdlib/test/gen_event_SUITE.erl | 30 +++++------ lib/stdlib/test/gen_fsm_SUITE.erl | 33 ++++++------ lib/stdlib/test/gen_server_SUITE.erl | 76 ++++++++++++++-------------- lib/stdlib/test/io_SUITE.erl | 4 +- lib/stdlib/test/log_mf_h_SUITE.erl | 12 ++--- lib/stdlib/test/proc_lib_SUITE.erl | 30 +++++------ lib/stdlib/test/qlc_SUITE.erl | 5 +- lib/stdlib/test/queue_SUITE.erl | 8 +-- lib/stdlib/test/rand_SUITE.erl | 19 ++++--- lib/stdlib/test/random_SUITE.erl | 4 +- lib/stdlib/test/slave_SUITE.erl | 2 +- lib/stdlib/test/supervisor_SUITE.erl | 46 ++++++++--------- lib/stdlib/test/tar_SUITE.erl | 18 +++---- lib/stdlib/test/timer_SUITE.erl | 2 +- lib/stdlib/test/timer_simple_SUITE.erl | 6 +-- lib/stdlib/test/zip_SUITE.erl | 4 +- 27 files changed, 189 insertions(+), 196 deletions(-) (limited to 'lib/stdlib/test') diff --git a/lib/stdlib/test/beam_lib_SUITE.erl b/lib/stdlib/test/beam_lib_SUITE.erl index fc7e2ac231..37e17306a4 100644 --- a/lib/stdlib/test/beam_lib_SUITE.erl +++ b/lib/stdlib/test/beam_lib_SUITE.erl @@ -771,7 +771,7 @@ ver(S, {error, beam_lib, R}) -> [S|_] = tuple_to_list(R), case lists:flatten(beam_lib:format_error(R)) of [${ | _] -> - test_server:fail({bad_format_error, R}); + ct:fail({bad_format_error, R}); _ -> ok end. diff --git a/lib/stdlib/test/dets_SUITE.erl b/lib/stdlib/test/dets_SUITE.erl index 34e85ab198..d899022bab 100644 --- a/lib/stdlib/test/dets_SUITE.erl +++ b/lib/stdlib/test/dets_SUITE.erl @@ -2547,7 +2547,7 @@ cache_sets(Config, DelayedWrite, Extra, Sz, Version) -> {[],[]} -> ok; {X,Y} -> NoBad = length(X) + length(Y), - test_server:fail({sets,DelayedWrite,Extra,Sz,NoBad}) + ct:fail({sets,DelayedWrite,Extra,Sz,NoBad}) end; true -> ok @@ -2711,7 +2711,7 @@ cache_bags(Config, DelayedWrite, Extra, Sz, Version) -> {[],[]} -> ok; {X,Y} -> NoBad = length(X) + length(Y), - test_server:fail({bags,DelayedWrite,Extra,Sz,NoBad}) + ct:fail({bags,DelayedWrite,Extra,Sz,NoBad}) end; true -> ok @@ -2869,7 +2869,7 @@ cache_dup_bags(Config, DelayedWrite, Extra, Sz, Version) -> {[],[]} -> ok; {X,Y} -> NoBad = length(X) + length(Y), - test_server:fail({dup_bags,DelayedWrite,Extra,Sz,NoBad}) + ct:fail({dup_bags,DelayedWrite,Extra,Sz,NoBad}) end; true -> ok @@ -4489,7 +4489,7 @@ check_pps({Ports0,Procs0} = P0) -> show("New port", PortsDiff), show("Old proc", Procs0 -- Procs1), show("New proc", ProcsDiff), - ?t:fail() + ct:fail(failed) end end end. diff --git a/lib/stdlib/test/epp_SUITE.erl b/lib/stdlib/test/epp_SUITE.erl index a89e29a91b..a2d34ff5c6 100644 --- a/lib/stdlib/test/epp_SUITE.erl +++ b/lib/stdlib/test/epp_SUITE.erl @@ -1680,8 +1680,7 @@ run_test(Config, Test0) -> Reply. fail() -> - io:format("failed~n"), - test_server:fail(). + ct:fail(failed). message_compare(T, T) -> true; diff --git a/lib/stdlib/test/erl_eval_SUITE.erl b/lib/stdlib/test/erl_eval_SUITE.erl index c37a83ff49..19566c4215 100644 --- a/lib/stdlib/test/erl_eval_SUITE.erl +++ b/lib/stdlib/test/erl_eval_SUITE.erl @@ -1523,7 +1523,7 @@ check1(F, String, Result) -> {value, Result, _} -> ok; Other -> - test_server:fail({eval, Other, Result}) + ct:fail({eval, Other, Result}) end. check(F, String, Result, BoundVars, LFH, EFH) -> @@ -1536,11 +1536,11 @@ check(F, String, Result, BoundVars, LFH, EFH) -> true -> ok; false -> - test_server:fail({check, BoundVars, Keys}) + ct:fail({check, BoundVars, Keys}) end, ok; Other -> - test_server:fail({check, Other, Result}) + ct:fail({check, Other, Result}) end. error_check(String, Result) -> @@ -1548,7 +1548,7 @@ error_check(String, Result) -> {'EXIT', {Result,_}} -> ok; Other -> - test_server:fail({eval, Other, Result}) + ct:fail({eval, Other, Result}) end. error_check(String, Result, LFH, EFH) -> @@ -1556,7 +1556,7 @@ error_check(String, Result, LFH, EFH) -> {'EXIT', {Result,_}} -> ok; Other -> - test_server:fail({eval, Other, Result}) + ct:fail({eval, Other, Result}) end. eval_string(String) -> diff --git a/lib/stdlib/test/erl_expand_records_SUITE.erl b/lib/stdlib/test/erl_expand_records_SUITE.erl index 82c76512f2..7fc8e23290 100644 --- a/lib/stdlib/test/erl_expand_records_SUITE.erl +++ b/lib/stdlib/test/erl_expand_records_SUITE.erl @@ -756,7 +756,7 @@ otp_7101(Config) when is_list(Config) -> 4 -> ok; Other -> - ?line ?t:fail({unexpected,Other}) + ct:fail({unexpected,Other}) end. otp_7101_tracer(Parent, N) -> @@ -833,5 +833,4 @@ warnings(File, Ws) -> end. fail() -> - io:format("failed~n"), - ?t:fail(). + ct:fail(failed). diff --git a/lib/stdlib/test/erl_lint_SUITE.erl b/lib/stdlib/test/erl_lint_SUITE.erl index 21db9a5a38..f20b57672e 100644 --- a/lib/stdlib/test/erl_lint_SUITE.erl +++ b/lib/stdlib/test/erl_lint_SUITE.erl @@ -3988,5 +3988,4 @@ call_format_error(L) -> L. fail() -> - io:format("failed~n"), - ?t:fail(). + ct:fail(failed). diff --git a/lib/stdlib/test/erl_pp_SUITE.erl b/lib/stdlib/test/erl_pp_SUITE.erl index eded80d1ad..06c51db7fd 100644 --- a/lib/stdlib/test/erl_pp_SUITE.erl +++ b/lib/stdlib/test/erl_pp_SUITE.erl @@ -1359,8 +1359,7 @@ filename(Name, Config) -> filename:join(?privdir, Name). fail() -> - io:format("failed~n"), - ?t:fail(). + ct:fail(failed). %% +fnu means a peer node has to be started; slave will not do start_node(Name, Xargs) -> diff --git a/lib/stdlib/test/error_logger_h_SUITE.erl b/lib/stdlib/test/error_logger_h_SUITE.erl index b2f1618ff5..eff35347e7 100644 --- a/lib/stdlib/test/error_logger_h_SUITE.erl +++ b/lib/stdlib/test/error_logger_h_SUITE.erl @@ -335,7 +335,7 @@ start_node(Name, Args) -> {ok,Node} -> {ok,Node}; Error -> - test_server:fail(Error) + ct:fail(Error) end. cleanup(File) -> diff --git a/lib/stdlib/test/escript_SUITE.erl b/lib/stdlib/test/escript_SUITE.erl index fc97d7ccfa..9a5b7620ea 100644 --- a/lib/stdlib/test/escript_SUITE.erl +++ b/lib/stdlib/test/escript_SUITE.erl @@ -967,7 +967,7 @@ do_run(Dir, Cmd, Expected0) -> Actual -> io:format("Expected: ~p\n", [Expected]), io:format("Actual: ~p\n", [Actual]), - ?t:fail() + ct:fail(failed) end end. diff --git a/lib/stdlib/test/ets_SUITE.erl b/lib/stdlib/test/ets_SUITE.erl index 19e2acac93..8b1034f24f 100644 --- a/lib/stdlib/test/ets_SUITE.erl +++ b/lib/stdlib/test/ets_SUITE.erl @@ -211,7 +211,7 @@ end_per_group(_GroupName, Config) -> memory_check_summary(_Config) -> case whereis(ets_test_spawn_logger) of undefined -> - ?t:fail("No spawn logger exist"); + ct:fail("No spawn logger exist"); _ -> ets_test_spawn_logger ! {self(), get_failed_memchecks}, receive {get_failed_memchecks, FailedMemchecks} -> ok end, @@ -377,7 +377,7 @@ t_match_spec_run_test(List, MS, Result) -> _ -> io:format("TRACE MATCH FAILED\n"), io:format("Input = ~p\nMST = ~p\nExpected = ~p\nGot = ~p\n", [List, MST, SRes, TRes]), - ?t:fail("TRACE MATCH FAILED") + ct:fail("TRACE MATCH FAILED") end, ok. @@ -400,7 +400,7 @@ ms_tracer_collect(Tracee, Ref, Acc) -> Other -> io:format("Unexpected message = ~p\n", [Other]), - ?t:fail("Unexpected tracer msg") + ct:fail("Unexpected tracer msg") end. @@ -426,7 +426,7 @@ ms_clause_ets_to_trace({Head, Guard, Body}) -> assert_eq(A,A) -> ok; assert_eq(A,B) -> io:format("FAILED MATCH:\n~p\n =/=\n~p\n",[A,B]), - ?t:fail("assert_eq failed"). + ct:fail("assert_eq failed"). t_repair_continuation(suite) -> @@ -1974,7 +1974,7 @@ wait_for_all(Pids0) -> wait_for_all(Pids); Other -> io:format("unexpected: ~p\n", [Other]), - ?line ?t:fail() + ct:fail(failed) end end. @@ -3134,7 +3134,7 @@ check_check(S={T,List,Key}) -> case lists:reverse(ets:lookup(T,Key)) of List -> ok; ETS -> io:format("check failed:\nETS: ~p\nCHK: ~p\n", [ETS,List]), - ?t:fail("Invalid return value from ets:lookup") + ct:fail("Invalid return value from ets:lookup") end, ?line Items = ets:info(T,size), ?line Items = length(List), @@ -3293,7 +3293,7 @@ delete_large_tab_1(Name, Flags, Data, Fix) -> ?line io:format("~s: context switches: ~p", [Name,N]), if N >= 5 -> ?line ok; - true -> ?line ?t:fail() + true -> ct:fail(failed) end end, receive {'DOWN',SchedTracerMon,process,SchedTracer,_} -> ok end, @@ -3781,7 +3781,7 @@ match2_do(Opts) -> {value2_1, key2_wannabe}]), ?line case length(ets:match(Tab, '$1')) of 6 -> ok; - _ -> ?t:fail("Length of matched list is wrong.") + _ -> ct:fail("Length of matched list is wrong.") end, ?line [[value3_1],[value3_2]] = ets:match(Tab, {'$1', key3}), ?line [[key1]] = ets:match(Tab, {value1, '$1'}), @@ -3818,22 +3818,22 @@ match_object_do(Opts) -> case ets:match_object(Tab, {{one, '_'}, '$0'}) of [{{one,5},5},{{one,4},4}] -> ok; [{{one,4},4},{{one,5},5}] -> ok; - _ -> ?t:fail("ets:match_object() returned something funny.") + _ -> ct:fail("ets:match_object() returned something funny.") end, case ets:match_object(Tab, {{two, '$1'}, '$0'}) of [{{two,5},6},{{two,4},4}] -> ok; [{{two,4},4},{{two,5},6}] -> ok; - _ -> ?t:fail("ets:match_object() returned something funny.") + _ -> ct:fail("ets:match_object() returned something funny.") end, case ets:match_object(Tab, {{two, '$9'}, '$4'}) of [{{two,5},6},{{two,4},4}] -> ok; [{{two,4},4},{{two,5},6}] -> ok; - _ -> ?t:fail("ets:match_object() returned something funny.") + _ -> ct:fail("ets:match_object() returned something funny.") end, case ets:match_object(Tab, {{two, '$9'}, '$22'}) of [{{two,5},6},{{two,4},4}] -> ok; [{{two,4},4},{{two,5},6}] -> ok; - _ -> ?t:fail("ets:match_object() returned something funny.") + _ -> ct:fail("ets:match_object() returned something funny.") end, % Check that maps are inspected for variables. @@ -3855,13 +3855,13 @@ match_object_do(Opts) -> {#{"1337" := "42","hi" := "hello","wazzup" := #{"awesome" := 3}},10}] -> ok; [{#{"1337" := "42","hi" := "hello","wazzup" := #{"awesome" := 3}},10}, {#{"1337" := "42","hi" := "hello","wazzup" := "awesome"},8}] -> ok; - _ -> ?t:fail("ets:match_object() returned something funny.") + _ -> ct:fail("ets:match_object() returned something funny.") end, case ets:match_object(Tab, {#{"hi"=>'_'},'_'}) of [{#{"1337":="42", "hi":="hello"},_}, {#{"1337":="42", "hi":="hello"},_}, {#{"1337":="42", "hi":="hello"},_}] -> ok; - _ -> ?t:fail("ets:match_object() returned something funny.") + _ -> ct:fail("ets:match_object() returned something funny.") end, %% match large maps @@ -3871,13 +3871,13 @@ match_object_do(Opts) -> %% only match a part of the map [{#{1:=1,5:=5,99:=99,100:=100},11},{#{1:="hi",6:="hi",99:="hi"},12}] -> ok; [{#{1:="hi",2:="hi",59:="hi"},12},{#{1:=1,2:=2,39:=39,100:=100},11}] -> ok; - _ -> ?t:fail("ets:match_object() returned something funny.") + _ -> ct:fail("ets:match_object() returned something funny.") end, case ets:match_object(Tab, {maps:from_list([{I,'_'}||I<-Is]),'_'}) of %% only match a part of the map [{#{1:=1,5:=5,99:=99,100:=100},11},{#{1:="hi",6:="hi",99:="hi"},12}] -> ok; [{#{1:="hi",2:="hi",59:="hi"},12},{#{1:=1,2:=2,39:=39,100:=100},11}] -> ok; - _ -> ?t:fail("ets:match_object() returned something funny.") + _ -> ct:fail("ets:match_object() returned something funny.") end, {'EXIT',{badarg,_}} = (catch ets:match_object(Tab, {#{'$1'=>'_'},7})), Mve = maps:from_list([{list_to_atom([$$|integer_to_list(I)]),'_'}||I<-Is]), @@ -3908,7 +3908,7 @@ match_object2_do(Opts) -> ?line case catch ets:match_object(Tab, {hej, '$1'}) of {'EXIT', _} -> ets:delete(Tab), - ?t:fail("match_object EXIT:ed"); + ct:fail("match_object EXIT:ed"); [] -> io:format("Nothing matched."); List -> @@ -3947,7 +3947,7 @@ misc1_do(Opts) -> {'EXIT',_Reason} -> ?line verify_etsmem(EtsMem); true -> - ?t:fail("Delete of nonexisting table returned `true'.") + ct:fail("Delete of nonexisting table returned `true'.") end, ok. @@ -4006,7 +4006,7 @@ safe_fixtable_do(Opts) -> {'EXIT', _Reason} -> ?line verify_etsmem(EtsMem); _ -> - ?t:fail("Fixtable on nonexisting table returned `true'") + ct:fail("Fixtable on nonexisting table returned `true'") end, ok. @@ -4435,7 +4435,7 @@ do_lookup_element(Tab, N, M) -> ?line case catch ets:lookup_element(Tab, N, M) of {'EXIT', {badarg, _}} -> case M of - 1 -> ?t:fail("Set #~p reported as empty. Not valid.", + 1 -> ct:fail("Set #~p reported as empty. Not valid.", [N]), exit('Invalid lookup_element'); _ -> ?line do_lookup_element(Tab, N-1, 1) @@ -5011,7 +5011,7 @@ verify(T, Ids) -> ok; _ -> io:format("Failed:\n~p\n", [Errors]), - ?t:fail() + ct:fail(failed) end. verify2([{_N,Id}|RL], [Id|R]) -> diff --git a/lib/stdlib/test/file_sorter_SUITE.erl b/lib/stdlib/test/file_sorter_SUITE.erl index eb8474fe24..6b2ccbd1cc 100644 --- a/lib/stdlib/test/file_sorter_SUITE.erl +++ b/lib/stdlib/test/file_sorter_SUITE.erl @@ -1329,9 +1329,9 @@ c(Fd, Bin0, Size0, NoBytes, HL, L) -> eof when Size0 =:= 0 -> lists:reverse(L); eof -> - test_server:fail({error, premature_eof}); + ct:fail({error, premature_eof}); Error -> - test_server:fail(Error) + ct:fail(Error) end. c1(Fd, B, BinSize, HL, L) -> @@ -1346,7 +1346,7 @@ c1(Fd, B, BinSize, HL, L) -> <> = Bin, E = case catch binary_to_term(BinTerm) of {'EXIT', _} -> - test_server:fail({error, bad_object}); + ct:fail({error, bad_object}); Term -> Term end, diff --git a/lib/stdlib/test/gen_event_SUITE.erl b/lib/stdlib/test/gen_event_SUITE.erl index e14f057720..6386619904 100644 --- a/lib/stdlib/test/gen_event_SUITE.erl +++ b/lib/stdlib/test/gen_event_SUITE.erl @@ -111,7 +111,7 @@ start(Config) when is_list(Config) -> receive {'EXIT', Pid6, shutdown} -> ok after 10000 -> - ?t:fail(exit_gen_event) + ct:fail(exit_gen_event) end, ?line {ok, Pid7} = gen_event:start_link({via, dummy_via, my_dummy_name}), @@ -124,7 +124,7 @@ start(Config) when is_list(Config) -> receive {'EXIT', Pid7, shutdown} -> ok after 10000 -> - ?t:fail(exit_gen_event) + ct:fail(exit_gen_event) end, ?t:messages_get(), @@ -204,7 +204,7 @@ is_in_erlang_hibernate(Pid) -> is_in_erlang_hibernate_1(0, Pid) -> io:format("~p\n", [erlang:process_info(Pid, current_function)]), - ?t:fail(not_in_erlang_hibernate_3); + ct:fail(not_in_erlang_hibernate_3); is_in_erlang_hibernate_1(N, Pid) -> {current_function,MFA} = erlang:process_info(Pid, current_function), case MFA of @@ -221,7 +221,7 @@ is_not_in_erlang_hibernate(Pid) -> is_not_in_erlang_hibernate_1(0, Pid) -> io:format("~p\n", [erlang:process_info(Pid, current_function)]), - ?t:fail(not_in_erlang_hibernate_3); + ct:fail(not_in_erlang_hibernate_3); is_not_in_erlang_hibernate_1(N, Pid) -> {current_function,MFA} = erlang:process_info(Pid, current_function), case MFA of @@ -284,14 +284,14 @@ add_sup_handler(Config) when is_list(Config) -> {gen_event_EXIT, dummy_h, shutdown} -> ok after 1000 -> - ?t:fail({no,{gen_event_EXIT, dummy_h, shutdown}}) + ct:fail({no,{gen_event_EXIT, dummy_h, shutdown}}) end, ?line receive {gen_event_EXIT, {dummy_h,Self}, shutdown} -> ok after 1000 -> - ?t:fail({no,{gen_event_EXIT, {dummy_h,Self}, + ct:fail({no,{gen_event_EXIT, {dummy_h,Self}, shutdown}}) end, ok. @@ -375,7 +375,7 @@ swap_sup_handler(Config) when is_list(Config) -> {gen_event_EXIT, dummy1_h, normal} -> ok after 1000 -> - ?t:fail({no,{gen_event_EXIT, dummy1_h, normal}}) + ct:fail({no,{gen_event_EXIT, dummy1_h, normal}}) end, ?line ok = gen_event:add_sup_handler(my_dummy_handler, {dummy_h,3}, @@ -393,7 +393,7 @@ swap_sup_handler(Config) when is_list(Config) -> {gen_event_EXIT, {dummy1_h,4}, normal} -> ok after 1000 -> - ?t:fail({no,{gen_event_EXIT, {dummy1_h,4}, normal}}) + ct:fail({no,{gen_event_EXIT, {dummy1_h,4}, normal}}) end, ?line ok = gen_event:stop(my_dummy_handler), @@ -744,7 +744,7 @@ call(Config) when is_list(Config) -> {gen_event_EXIT, dummy_h, {return,faulty}} -> ok after 1000 -> - ?t:fail({no, {gen_event_EXIT, dummy_h, {return,faulty}}}) + ct:fail({no, {gen_event_EXIT, dummy_h, {return,faulty}}}) end, ?line [] = gen_event:which_handlers(my_dummy_handler), @@ -757,7 +757,7 @@ call(Config) when is_list(Config) -> {gen_event_EXIT, dummy_h, {'EXIT',_}} -> ok after 1000 -> - ?t:fail({no, {gen_event_EXIT, dummy_h, {'EXIT','_'}}}) + ct:fail({no, {gen_event_EXIT, dummy_h, {'EXIT','_'}}}) end, ?line [] = gen_event:which_handlers(my_dummy_handler), @@ -859,7 +859,7 @@ info(Config) when is_list(Config) -> {gen_event_EXIT, dummy1_h, normal} -> ok after 1000 -> - ?t:fail({no, {gen_event_EXIT, dummy1_h, normal}}) + ct:fail({no, {gen_event_EXIT, dummy1_h, normal}}) end, ?line [] = gen_event:which_handlers(my_dummy_handler), @@ -876,7 +876,7 @@ info(Config) when is_list(Config) -> {gen_event_EXIT, dummy_h, {return,faulty}} -> ok after 1000 -> - ?t:fail({no, {gen_event_EXIT, dummy_h, {return,faulty}}}) + ct:fail({no, {gen_event_EXIT, dummy_h, {return,faulty}}}) end, ?line ok = gen_event:add_sup_handler(my_dummy_handler, dummy_h, [self()]), @@ -886,7 +886,7 @@ info(Config) when is_list(Config) -> {gen_event_EXIT, dummy_h, {'EXIT',_}} -> ok after 1000 -> - ?t:fail({no, {gen_event_EXIT, dummy_h, {'EXIT','_'}}}) + ct:fail({no, {gen_event_EXIT, dummy_h, {'EXIT','_'}}}) end, ?line [] = gen_event:which_handlers(my_dummy_handler), @@ -945,7 +945,7 @@ error_format_status(Config) when is_list(Config) -> ?line receive {gen_event_EXIT,dummy1_h,{'EXIT',_}} -> ok after 5000 -> - ?t:fail(exit_gen_event) + ct:fail(exit_gen_event) end, FmtState = "dummy1_h handler state", receive @@ -956,7 +956,7 @@ error_format_status(Config) when is_list(Config) -> ok; Other -> ?line io:format("Unexpected: ~p", [Other]), - ?line ?t:fail() + ct:fail(failed) end, ?t:messages_get(), ?line ok = gen_event:stop(Pid), diff --git a/lib/stdlib/test/gen_fsm_SUITE.erl b/lib/stdlib/test/gen_fsm_SUITE.erl index c238232ef0..4a772c2169 100644 --- a/lib/stdlib/test/gen_fsm_SUITE.erl +++ b/lib/stdlib/test/gen_fsm_SUITE.erl @@ -433,7 +433,7 @@ shutdown(Config) when is_list(Config) -> receive Any -> ?line io:format("Unexpected: ~p", [Any]), - ?line ?t:fail() + ct:fail(failed) after 500 -> ok end, @@ -515,7 +515,7 @@ error_format_status(Config) when is_list(Config) -> ok; Other -> ?line io:format("Unexpected: ~p", [Other]), - ?line ?t:fail() + ct:fail(failed) end, ?t:messages_get(), process_flag(trap_exit, OldFl), @@ -534,10 +534,10 @@ terminate_crash_format(Config) when is_list(Config) -> ok; Other -> io:format("Unexpected: ~p", [Other]), - ?t:fail() + ct:fail(failed) after 5000 -> io:format("Timeout: expected error logger msg", []), - ?t:fail() + ct:fail(failed) end, _ = ?t:messages_get(), process_flag(trap_exit, OldFl), @@ -687,7 +687,7 @@ is_in_erlang_hibernate(Pid) -> is_in_erlang_hibernate_1(0, Pid) -> io:format("~p\n", [erlang:process_info(Pid, current_function)]), - ?t:fail(not_in_erlang_hibernate_3); + ct:fail(not_in_erlang_hibernate_3); is_in_erlang_hibernate_1(N, Pid) -> {current_function,MFA} = erlang:process_info(Pid, current_function), case MFA of @@ -704,7 +704,7 @@ is_not_in_erlang_hibernate(Pid) -> is_not_in_erlang_hibernate_1(0, Pid) -> io:format("~p\n", [erlang:process_info(Pid, current_function)]), - ?t:fail(not_in_erlang_hibernate_3); + ct:fail(not_in_erlang_hibernate_3); is_not_in_erlang_hibernate_1(N, Pid) -> {current_function,MFA} = erlang:process_info(Pid, current_function), case MFA of @@ -736,7 +736,7 @@ enter_loop(Config) when is_list(Config) -> {'EXIT', Pid1a, normal} -> ok after 5000 -> - ?line test_server:fail(gen_fsm_did_not_die) + ct:fail(gen_fsm_did_not_die) end, %% Unregistered process + {local, Name} @@ -746,7 +746,7 @@ enter_loop(Config) when is_list(Config) -> {'EXIT', Pid1b, process_not_registered} -> ok after 5000 -> - ?line test_server:fail(gen_fsm_did_not_die) + ct:fail(gen_fsm_did_not_die) end, %% Globally registered process + {global, Name} @@ -758,7 +758,7 @@ enter_loop(Config) when is_list(Config) -> {'EXIT', Pid2a, normal} -> ok after 5000 -> - ?line test_server:fail(gen_fsm_did_not_die) + ct:fail(gen_fsm_did_not_die) end, %% Unregistered process + {global, Name} @@ -768,7 +768,7 @@ enter_loop(Config) when is_list(Config) -> {'EXIT', Pid2b, process_not_registered_globally} -> ok after 5000 -> - ?line test_server:fail(gen_fsm_did_not_die) + ct:fail(gen_fsm_did_not_die) end, %% Unregistered process + no name @@ -780,7 +780,7 @@ enter_loop(Config) when is_list(Config) -> {'EXIT', Pid3, normal} -> ok after 5000 -> - ?line test_server:fail(gen_fsm_did_not_die) + ct:fail(gen_fsm_did_not_die) end, %% Process not started using proc_lib @@ -790,7 +790,7 @@ enter_loop(Config) when is_list(Config) -> {'EXIT', Pid4, process_was_not_started_by_proc_lib} -> ok after 5000 -> - ?line test_server:fail(gen_fsm_did_not_die) + ct:fail(gen_fsm_did_not_die) end, %% Make sure I am the parent, ie that ordering a shutdown will @@ -803,7 +803,7 @@ enter_loop(Config) when is_list(Config) -> {'EXIT', Pid5, shutdown} -> ok after 5000 -> - ?line test_server:fail(gen_fsm_did_not_die) + ct:fail(gen_fsm_did_not_die) end, %% Make sure gen_fsm:enter_loop does not accept {local,Name} @@ -816,7 +816,7 @@ enter_loop(Config) when is_list(Config) -> {'EXIT', Pid6a, process_not_registered} -> ok after 1000 -> - ?line test_server:fail(gen_fsm_started) + ct:fail(gen_fsm_started) end, unregister(armitage), @@ -830,7 +830,7 @@ enter_loop(Config) when is_list(Config) -> {'EXIT', Pid6b, process_not_registered_globally} -> ok after 1000 -> - ?line test_server:fail(gen_fsm_started) + ct:fail(gen_fsm_started) end, global:unregister_name(armitage), @@ -841,8 +841,7 @@ enter_loop(Config) when is_list(Config) -> {'EXIT', Pid6c, {process_not_registered_via, dummy_via}} -> ok after 1000 -> - ?line test_server:fail({gen_fsm_started, process_info(self(), - messages)}) + ct:fail({gen_fsm_started, process_info(self(), messages)}) end, dummy_via:unregister_name(armitage), diff --git a/lib/stdlib/test/gen_server_SUITE.erl b/lib/stdlib/test/gen_server_SUITE.erl index 2307d823bf..5f29fc911d 100644 --- a/lib/stdlib/test/gen_server_SUITE.erl +++ b/lib/stdlib/test/gen_server_SUITE.erl @@ -144,7 +144,7 @@ start(Config) when is_list(Config) -> {'EXIT', Pid1, stopped} -> ok after 5000 -> - test_server:fail(not_stopped) + ct:fail(not_stopped) end, %% local register @@ -174,7 +174,7 @@ start(Config) when is_list(Config) -> {'EXIT', Pid3, stopped} -> ok after 5000 -> - test_server:fail(not_stopped) + ct:fail(not_stopped) end, %% global register @@ -202,7 +202,7 @@ start(Config) when is_list(Config) -> {'EXIT', Pid5, stopped} -> ok after 5000 -> - test_server:fail(not_stopped) + ct:fail(not_stopped) end, %% via register @@ -232,7 +232,7 @@ start(Config) when is_list(Config) -> {'EXIT', Pid7, stopped} -> ok after 5000 -> - test_server:fail(not_stopped) + ct:fail(not_stopped) end, test_server:messages_get(), @@ -382,7 +382,7 @@ crash(Config) when is_list(Config) -> ok; Other4a -> ?line io:format("Unexpected: ~p", [Other4a]), - ?line ?t:fail() + ct:fail(failed) end, receive {error_report,_,{Pid4,crash_report,[List4|_]}} -> @@ -390,13 +390,13 @@ crash(Config) when is_list(Config) -> Pid4 = proplists:get_value(pid, List4); Other4 -> ?line io:format("Unexpected: ~p", [Other4]), - ?line ?t:fail() + ct:fail(failed) end, receive Any -> ?line io:format("Unexpected: ~p", [Any]), - ?line ?t:fail() + ct:fail(failed) after 500 -> ok end, @@ -553,7 +553,7 @@ cast(Config) when is_list(Config) -> {Pid, handled_cast} -> ok after 1000 -> - test_server:fail(handle_cast) + ct:fail(handle_cast) end, ?line ok = gen_server:cast(my_test_name, {self(),delayed_cast,1}), @@ -561,7 +561,7 @@ cast(Config) when is_list(Config) -> {Pid, delayed} -> ok after 1000 -> - test_server:fail(delayed_cast) + ct:fail(delayed_cast) end, ?line ok = gen_server:cast(my_test_name, {self(),stop}), @@ -569,7 +569,7 @@ cast(Config) when is_list(Config) -> {Pid, stopped} -> ok after 1000 -> - test_server:fail(stop) + ct:fail(stop) end, ok. @@ -588,7 +588,7 @@ cast_fast(Config) when is_list(Config) -> [{hopp,FalseNode},hopp]), ?line true = test_server:stop_node(Node), ?line if Time > 1.0 -> % Default listen timeout is about 7.0 s - test_server:fail(hanging_cast); + ct:fail(hanging_cast); true -> ok end. @@ -619,7 +619,7 @@ info(Config) when is_list(Config) -> {Pid, handled_info} -> ok after 1000 -> - test_server:fail(handle_info) + ct:fail(handle_info) end, ?line Pid ! {self(),delayed_info,1}, @@ -627,7 +627,7 @@ info(Config) when is_list(Config) -> {Pid, delayed_info} -> ok after 1000 -> - test_server:fail(delayed_info) + ct:fail(delayed_info) end, ?line Pid ! {self(),stop}, @@ -635,7 +635,7 @@ info(Config) when is_list(Config) -> {Pid, stopped_info} -> ok after 1000 -> - test_server:fail(stop_info) + ct:fail(stop_info) end, ok. @@ -650,7 +650,7 @@ hibernate(Config) when is_list(Config) -> {'EXIT', Pid0, stopped} -> ok after 5000 -> - test_server:fail(gen_server_did_not_die) + ct:fail(gen_server_did_not_die) end, {ok, Pid} = @@ -717,7 +717,7 @@ hibernate(Config) when is_list(Config) -> {'EXIT', Pid, stopped} -> ok after 5000 -> - test_server:fail(gen_server_did_not_die) + ct:fail(gen_server_did_not_die) end, process_flag(trap_exit, OldFl), ok. @@ -728,7 +728,7 @@ is_in_erlang_hibernate(Pid) -> is_in_erlang_hibernate_1(0, Pid) -> io:format("~p\n", [erlang:process_info(Pid, current_function)]), - ?t:fail(not_in_erlang_hibernate_3); + ct:fail(not_in_erlang_hibernate_3); is_in_erlang_hibernate_1(N, Pid) -> {current_function,MFA} = erlang:process_info(Pid, current_function), case MFA of @@ -758,7 +758,7 @@ abcast(Config) when is_list(Config) -> {Pid, handled_cast} -> ok after 1000 -> - test_server:fail(abcast) + ct:fail(abcast) end, ?line abcast = gen_server:abcast([node()], my_test_name, @@ -767,7 +767,7 @@ abcast(Config) when is_list(Config) -> {Pid, delayed} -> ok after 1000 -> - test_server:fail(delayed_abcast) + ct:fail(delayed_abcast) end, ?line abcast = gen_server:abcast(my_test_name, {self(),stop}), @@ -775,7 +775,7 @@ abcast(Config) when is_list(Config) -> {Pid, stopped} -> ok after 1000 -> - test_server:fail(abcast_stop) + ct:fail(abcast_stop) end, ok. @@ -817,7 +817,7 @@ multicall(Config) when is_list(Config) -> receive {'EXIT', Pid, stopped} -> ok after 1000 -> - test_server:fail(multicall_stop) + ct:fail(multicall_stop) end, process_flag(trap_exit, OldFl), @@ -867,7 +867,7 @@ spec_init(Config) when is_list(Config) -> {'EXIT', Pid0, stopped} -> ok after 5000 -> - test_server:fail(gen_server_did_not_die) + ct:fail(gen_server_did_not_die) end, ?line {ok, Pid01} = start_link(spec_init_local, [{not_ok, my_server}, []]), @@ -875,7 +875,7 @@ spec_init(Config) when is_list(Config) -> {'EXIT', Pid01, process_not_registered} -> ok after 5000 -> - test_server:fail(gen_server_did_not_die) + ct:fail(gen_server_did_not_die) end, ?line {ok, Pid1} = start_link(spec_init_global, [{ok, my_server}, []]), @@ -885,7 +885,7 @@ spec_init(Config) when is_list(Config) -> {'EXIT', Pid1, stopped} -> ok after 5000 -> - test_server:fail(gen_server_did_not_die) + ct:fail(gen_server_did_not_die) end, ?line {ok, Pid11} = @@ -895,7 +895,7 @@ spec_init(Config) when is_list(Config) -> {'EXIT', Pid11, process_not_registered_globally} -> ok after 5000 -> - test_server:fail(gen_server_did_not_die) + ct:fail(gen_server_did_not_die) end, ?line {ok, Pid2} = start_link(spec_init_anonymous, [[]]), @@ -905,7 +905,7 @@ spec_init(Config) when is_list(Config) -> {'EXIT', Pid2, stopped} -> ok after 5000 -> - test_server:fail(gen_server_did_not_die) + ct:fail(gen_server_did_not_die) end, ?line {ok, Pid3} = start_link(spec_init_anonymous_default_timeout, [[]]), @@ -915,7 +915,7 @@ spec_init(Config) when is_list(Config) -> {'EXIT', Pid3, stopped} -> ok after 5000 -> - test_server:fail(gen_server_did_not_die) + ct:fail(gen_server_did_not_die) end, ?line {ok, Pid4} = @@ -926,7 +926,7 @@ spec_init(Config) when is_list(Config) -> {'EXIT', Pid4, stopped} -> ok after 5000 -> - test_server:fail(gen_server_did_not_die) + ct:fail(gen_server_did_not_die) end, %% Before the OTP-10130 fix this failed because a timeout message @@ -943,7 +943,7 @@ spec_init(Config) when is_list(Config) -> {'EXIT', Pid5, process_was_not_started_by_proc_lib} -> ok after 5000 -> - test_server:fail(gen_server_did_not_die) + ct:fail(gen_server_did_not_die) end, process_flag(trap_exit, OldFlag), ok. @@ -965,7 +965,7 @@ spec_init_local_registered_parent(Config) when is_list(Config) -> {Pid, stopped} -> ok after 1000 -> - test_server:fail(stop) + ct:fail(stop) end, unregister(foobar), ok. @@ -988,7 +988,7 @@ spec_init_global_registered_parent(Config) when is_list(Config) -> {Pid, stopped} -> ok after 1000 -> - test_server:fail(stop) + ct:fail(stop) end, global:unregister_name(foobar), ok. @@ -1012,7 +1012,7 @@ otp_5854(Config) when is_list(Config) -> {'EXIT', Pid1, process_not_registered} -> ok after 1000 -> - ?line test_server:fail(gen_server_started) + ct:fail(gen_server_started) end, unregister(armitage), @@ -1026,7 +1026,7 @@ otp_5854(Config) when is_list(Config) -> {'EXIT', Pid2, process_not_registered_globally} -> ok after 1000 -> - ?line test_server:fail(gen_server_started) + ct:fail(gen_server_started) end, global:unregister_name(armitage), @@ -1038,7 +1038,7 @@ otp_5854(Config) when is_list(Config) -> {'EXIT', Pid3, {process_not_registered_via, dummy_via}} -> ok after 1000 -> - ?line test_server:fail(gen_server_started) + ct:fail(gen_server_started) end, dummy_via:unregister_name(armitage), @@ -1146,7 +1146,7 @@ error_format_status(Config) when is_list(Config) -> ok; Other -> ?line io:format("Unexpected: ~p", [Other]), - ?line ?t:fail() + ct:fail(failed) end, ?t:messages_get(), process_flag(trap_exit, OldFl), @@ -1170,10 +1170,10 @@ terminate_crash_format(Config) when is_list(Config) -> ok; Other -> io:format("Unexpected: ~p", [Other]), - ?t:fail() + ct:fail(failed) after 5000 -> io:format("Timeout: expected error logger msg", []), - ?t:fail() + ct:fail(failed) end, ?t:messages_get(), process_flag(trap_exit, OldFl), @@ -1266,7 +1266,7 @@ do_call_with_huge_message_queue() -> ok; Q -> io:format("Q = ~p", [Q]), - ?line ?t:fail() + ct:fail(failed) end, ok. diff --git a/lib/stdlib/test/io_SUITE.erl b/lib/stdlib/test/io_SUITE.erl index 81fd3786ce..88d0f54d99 100644 --- a/lib/stdlib/test/io_SUITE.erl +++ b/lib/stdlib/test/io_SUITE.erl @@ -2295,7 +2295,7 @@ do_io_with_huge_message_queue(Config) -> ok; Q -> io:format("Q = ~p", [Q]), - ?t:fail() + ct:fail(failed) end, ok. @@ -2368,7 +2368,7 @@ re_fmt(Pattern, Format, Args) -> nomatch -> io:format("Pattern: ~s", [Pattern]), io:format("Result: ~s", [S]), - ?t:fail(); + ct:fail(failed); match -> ok end. diff --git a/lib/stdlib/test/log_mf_h_SUITE.erl b/lib/stdlib/test/log_mf_h_SUITE.erl index 70d03dd46f..8c5aa3d59b 100644 --- a/lib/stdlib/test/log_mf_h_SUITE.erl +++ b/lib/stdlib/test/log_mf_h_SUITE.erl @@ -77,14 +77,14 @@ test(Config) when is_list(Config) -> ?line false = lists:member("4", Files2), ?line true = lists:member("index", Files2), ?line {ok, #file_info{size=Size1,type=regular}} = file:read_file_info(Log1 ++ "/1"), - ?line if Size1 > 500 -> test_server:fail({too_big, Size1}); - true -> ok end, + if Size1 > 500 -> ct:fail({too_big, Size1}); + true -> ok end, ?line {ok, #file_info{size=Size2,type=regular}} = file:read_file_info(Log1 ++ "/2"), - ?line if Size2 > 500 -> test_server:fail({too_big, Size2}); - true -> ok end, + if Size2 > 500 -> ct:fail({too_big, Size2}); + true -> ok end, ?line {ok, #file_info{size=Size3,type=regular}} = file:read_file_info(Log1 ++ "/3"), - ?line if Size3 > 500 -> test_server:fail({too_big, Size3}); - true -> ok end, + if Size3 > 500 -> ct:fail({too_big, Size3}); + true -> ok end, gen_event:delete_handler(Pid, log_mf_h, []), ?line {ok, Index} = read_index_file(Log1), gen_event:add_handler(Pid, log_mf_h, Args1), diff --git a/lib/stdlib/test/proc_lib_SUITE.erl b/lib/stdlib/test/proc_lib_SUITE.erl index a39a82b0df..ad0c06794a 100644 --- a/lib/stdlib/test/proc_lib_SUITE.erl +++ b/lib/stdlib/test/proc_lib_SUITE.erl @@ -152,9 +152,9 @@ analyse_crash(Pid, Expected0, ExpLinks) -> analyse_links(ExpLinks, Links); Unexpected -> io:format("~p\n", [Unexpected]), - test_server:fail(unexpected_message) + ct:fail(unexpected_message) after 5000 -> - test_server:fail(no_crash_report) + ct:fail(no_crash_report) end. analyse_links([H|Es], [{neighbour,N}|Links]) -> @@ -170,7 +170,7 @@ analyse_crash_1([{Key,Pattern}|T], Report) -> case lists:keyfind(Key, 1, Report) of false -> io:format("~p", [Report]), - test_server:fail({missing_key,Key}); + ct:fail({missing_key,Key}); {Key,Info} -> try match_info(Pattern, Info) @@ -179,7 +179,7 @@ analyse_crash_1([{Key,Pattern}|T], Report) -> io:format("key: ~p", [Key]), io:format("pattern: ~p", [Pattern]), io:format("actual: ~p", [Report]), - test_server:fail(no_match) + ct:fail(no_match) end, analyse_crash_1(T, Report) end; @@ -203,7 +203,7 @@ sync_start_nolink(Config) when is_list(Config) -> receive {sync_started, F} -> exit(F, kill), - test_server:fail(async_start) + ct:fail(async_start) after 1000 -> ok end, receive @@ -214,14 +214,14 @@ sync_start_nolink(Config) when is_list(Config) -> {sync_started, _} -> ok after 1000 -> exit(Pid2, kill), - test_server:fail(no_sync_start) + ct:fail(no_sync_start) end, ok. sync_start_link(Config) when is_list(Config) -> _Pid = spawn_link(?MODULE, sp3, [self()]), receive - {sync_started, _} -> test_server:fail(async_start) + {sync_started, _} -> ct:fail(async_start) after 1000 -> ok end, receive @@ -230,7 +230,7 @@ sync_start_link(Config) when is_list(Config) -> end, receive {sync_started, _} -> ok - after 1000 -> test_server:fail(no_sync_start) + after 1000 -> ct:fail(no_sync_start) end, ok. @@ -291,10 +291,10 @@ hibernate(Config) when is_list(Config) -> {loop_data,LoopData} -> ok; Unexpected0 -> ?line io:format("Unexpected: ~p\n", [Unexpected0]), - ?line ?t:fail() + ct:fail(failed) after 1000 -> ?line io:format("Timeout"), - ?line ?t:fail() + ct:fail(failed) end, %% Hibernate the process. @@ -312,10 +312,10 @@ hibernate(Config) when is_list(Config) -> {awaken,LoopData} -> ok; Unexpected1 -> ?line io:format("Unexpected: ~p\n", [Unexpected1]), - ?line ?t:fail() + ct:fail(failed) after 1000 -> ?line io:format("Timeout"), - ?line ?t:fail() + ct:fail(failed) end, %% ... followed by the answer to the actual request. @@ -323,10 +323,10 @@ hibernate(Config) when is_list(Config) -> {loop_data,LoopData} -> ok; Unexpected2 -> ?line io:format("Unexpected: ~p\n", [Unexpected2]), - ?line ?t:fail() + ct:fail(failed) after 1000 -> ?line io:format("Timeout"), - ?line ?t:fail() + ct:fail(failed) end, %% Test that errors are handled correctly after wake up from hibernation... @@ -522,7 +522,7 @@ t_format() -> if Tsz >= Usz -> - ?t:fail(); + ct:fail(failed); true -> ok end, diff --git a/lib/stdlib/test/qlc_SUITE.erl b/lib/stdlib/test/qlc_SUITE.erl index 8beb6a9f3e..d285af54ca 100644 --- a/lib/stdlib/test/qlc_SUITE.erl +++ b/lib/stdlib/test/qlc_SUITE.erl @@ -8171,8 +8171,7 @@ expected(Expected, Got, File) -> fail(File). fail(Source) -> - io:format("failed~n"), - ?t:fail({failed,testcase,on,Source}). + ct:fail({failed,testcase,on,Source}). %% Copied from global_SUITE.erl. @@ -8194,7 +8193,7 @@ read_error_logger() -> {error, Pid, Tuple} after 1000 -> ?line io:format("No reply after 1 s\n", []), - ?line ?t:fail() + ct:fail(failed) end. %%----------------------------------------------------------------- diff --git a/lib/stdlib/test/queue_SUITE.erl b/lib/stdlib/test/queue_SUITE.erl index f6331398a2..d0943e7a2a 100644 --- a/lib/stdlib/test/queue_SUITE.erl +++ b/lib/stdlib/test/queue_SUITE.erl @@ -95,7 +95,7 @@ to_list(Config) when is_list(Config) -> [2,3,4,5] -> ok; Other1 -> - test_server:fail(Other1) + ct:fail(Other1) end, ok. @@ -111,7 +111,7 @@ do_queue_1({out, E}, Q) -> {E, Q1} -> Q1; Other -> - test_server:fail({"out failed", E, Q, Other}) + ct:fail({"out failed", E, Q, Other}) end. @@ -266,7 +266,7 @@ io([peek_r | Tail], Q, Q0, X) -> io([drop | Tail], Q, [], X) -> try queue:drop(Q) of V -> - test_server:fail({?MODULE,?LINE,V}) + ct:fail({?MODULE,?LINE,V}) catch error:empty -> io(Tail, Q, [], X) @@ -277,7 +277,7 @@ io([drop | Tail], Q, [_ | T], X) -> io([drop_r | Tail], Q, [], X) -> try queue:drop_r(Q) of V -> - test_server:fail({?MODULE,?LINE,V}) + ct:fail({?MODULE,?LINE,V}) catch error:empty -> io(Tail, Q, [], X) diff --git a/lib/stdlib/test/rand_SUITE.erl b/lib/stdlib/test/rand_SUITE.erl index c694dbf8e2..b941ac9c53 100644 --- a/lib/stdlib/test/rand_SUITE.erl +++ b/lib/stdlib/test/rand_SUITE.erl @@ -92,7 +92,7 @@ seed(Config) when is_list(Config) -> Test = fun(Alg) -> try seed_1(Alg) catch _:Reason -> - test_server:fail({Alg, Reason, erlang:get_stacktrace()}) + ct:fail({Alg, Reason, erlang:get_stacktrace()}) end end, [Test(Alg) || Alg <- Algs], @@ -265,7 +265,6 @@ reference_1(Alg) -> io:format("Failed: ~p~n",[Alg]), io:format("Length ~p ~p~n",[length(Refval), length(Testval)]), io:format("Head ~p ~p~n",[hd(Refval), hd(Testval)]), - %% test_server:fail({Alg, Refval -- Testval}), ok end. @@ -328,9 +327,9 @@ basic_uniform_1(0, {#{type:=Alg}, _}, Sum, A) -> %% Verify that the basic statistics are ok %% be gentle we don't want to see to many failing tests - abs(0.5 - AverN) < 0.005 orelse test_server:fail({average, Alg, AverN}), - abs(?LOOP div 100 - Min) < 1000 orelse test_server:fail({min, Alg, Min}), - abs(?LOOP div 100 - Max) < 1000 orelse test_server:fail({max, Alg, Max}), + abs(0.5 - AverN) < 0.005 orelse ct:fail({average, Alg, AverN}), + abs(?LOOP div 100 - Min) < 1000 orelse ct:fail({min, Alg, Min}), + abs(?LOOP div 100 - Max) < 1000 orelse ct:fail({max, Alg, Max}), ok. basic_uniform_2(N, S0, Sum, A0) when N > 0 -> @@ -347,9 +346,9 @@ basic_uniform_2(0, {#{type:=Alg}, _}, Sum, A) -> %% Verify that the basic statistics are ok %% be gentle we don't want to see to many failing tests - abs(50.5 - AverN) < 0.5 orelse test_server:fail({average, Alg, AverN}), - abs(?LOOP div 100 - Min) < 1000 orelse test_server:fail({min, Alg, Min}), - abs(?LOOP div 100 - Max) < 1000 orelse test_server:fail({max, Alg, Max}), + abs(50.5 - AverN) < 0.5 orelse ct:fail({average, Alg, AverN}), + abs(?LOOP div 100 - Min) < 1000 orelse ct:fail({min, Alg, Min}), + abs(?LOOP div 100 - Max) < 1000 orelse ct:fail({max, Alg, Max}), ok. basic_normal_1(N, S0, Sum, Sq) when N > 0 -> @@ -361,8 +360,8 @@ basic_normal_1(0, {#{type:=Alg}, _}, Sum, SumSq) -> io:format("~.10w: Average: ~7.4f StdDev ~6.4f~n", [Alg, Mean, StdDev]), %% Verify that the basic statistics are ok %% be gentle we don't want to see to many failing tests - abs(Mean) < 0.005 orelse test_server:fail({average, Alg, Mean}), - abs(StdDev - 1.0) < 0.005 orelse test_server:fail({stddev, Alg, StdDev}), + abs(Mean) < 0.005 orelse ct:fail({average, Alg, Mean}), + abs(StdDev - 1.0) < 0.005 orelse ct:fail({stddev, Alg, StdDev}), ok. %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% diff --git a/lib/stdlib/test/random_SUITE.erl b/lib/stdlib/test/random_SUITE.erl index fe7189d91a..02c2754a44 100644 --- a/lib/stdlib/test/random_SUITE.erl +++ b/lib/stdlib/test/random_SUITE.erl @@ -116,9 +116,9 @@ check_interval(N, Top) -> X = random:uniform(Top), if X < 1 -> - test_server:fail(too_small); + ct:fail(too_small); X > Top -> - test_server:fail(too_large); + ct:fail(too_large); true -> ok end, diff --git a/lib/stdlib/test/slave_SUITE.erl b/lib/stdlib/test/slave_SUITE.erl index 6dbbd60d6f..b7d5024311 100644 --- a/lib/stdlib/test/slave_SUITE.erl +++ b/lib/stdlib/test/slave_SUITE.erl @@ -229,7 +229,7 @@ wait_alive(Node) -> wait_alive_1(10, Node). wait_alive_1(0, Node) -> - ?t:fail({still_not_alive,Node}); + ct:fail({still_not_alive,Node}); wait_alive_1(N, Node) -> case rpc:call(Node, init, get_status, []) of {started,_} -> diff --git a/lib/stdlib/test/supervisor_SUITE.erl b/lib/stdlib/test/supervisor_SUITE.erl index acfe6c9067..fab321f9df 100644 --- a/lib/stdlib/test/supervisor_SUITE.erl +++ b/lib/stdlib/test/supervisor_SUITE.erl @@ -702,7 +702,7 @@ permanent_normal(Config) when is_list(Config) -> true -> ok; false -> - test_server:fail({permanent_child_not_restarted, Child1}) + ct:fail({permanent_child_not_restarted, Child1}) end, [1,1,0,1] = get_child_counts(sup_test). @@ -751,7 +751,7 @@ permanent_shutdown(Config) when is_list(Config) -> true -> ok; false -> - test_server:fail({permanent_child_not_restarted, Child1}) + ct:fail({permanent_child_not_restarted, Child1}) end, [1,1,0,1] = get_child_counts(sup_test), @@ -762,7 +762,7 @@ permanent_shutdown(Config) when is_list(Config) -> true -> ok; false -> - test_server:fail({permanent_child_not_restarted, Child1}) + ct:fail({permanent_child_not_restarted, Child1}) end, [1,1,0,1] = get_child_counts(sup_test). @@ -858,7 +858,7 @@ permanent_abnormal(Config) when is_list(Config) -> true -> ok; false -> - test_server:fail({permanent_child_not_restarted, Child1}) + ct:fail({permanent_child_not_restarted, Child1}) end, [1,1,0,1] = get_child_counts(sup_test). @@ -877,7 +877,7 @@ transient_abnormal(Config) when is_list(Config) -> true -> ok; false -> - test_server:fail({transient_child_not_restarted, Child1}) + ct:fail({transient_child_not_restarted, Child1}) end, [1,1,0,1] = get_child_counts(sup_test). @@ -973,9 +973,9 @@ one_for_one(Config) when is_list(Config) -> if length(Children) == 2 -> case lists:keysearch(CPid2, 2, Children) of {value, _} -> ok; - _ -> test_server:fail(bad_child) + _ -> ct:fail(bad_child) end; - true -> test_server:fail({bad_child_list, Children}) + true -> ct:fail({bad_child_list, Children}) end, [2,2,0,2] = get_child_counts(sup_test), @@ -1026,7 +1026,7 @@ one_for_all(Config) when is_list(Config) -> Children = supervisor:which_children(sup_test), if length(Children) == 2 -> ok; true -> - test_server:fail({bad_child_list, Children}) + ct:fail({bad_child_list, Children}) end, %% Test that no old children is still alive @@ -1101,7 +1101,7 @@ one_for_all_other_child_fails_restart(Config) when is_list(Config) -> {_childName, _Pid} -> exit(SupPid, kill), check_exit([StarterPid, SupPid]), - test_server:fail({restarting_child_not_terminated, Child1Pid2}) + ct:fail({restarting_child_not_terminated, Child1Pid2}) end, %% Let the restart complete. Child1Pid3 = receive {child1, Pid5} -> Pid5 end, @@ -1128,9 +1128,9 @@ simple_one_for_one(Config) when is_list(Config) -> if length(Children) == 2 -> case lists:keysearch(CPid2, 2, Children) of {value, _} -> ok; - _ -> test_server:fail(bad_child) + _ -> ct:fail(bad_child) end; - true -> test_server:fail({bad_child_list, Children}) + true -> ct:fail({bad_child_list, Children}) end, [1,2,0,2] = get_child_counts(sup_test), @@ -1164,9 +1164,9 @@ simple_one_for_one_shutdown(Config) when is_list(Config) -> if T < 1000*ShutdownTime -> %% Because supervisor's children wait before exiting, it can't %% terminate quickly - test_server:fail({shutdown_too_short, T}); + ct:fail({shutdown_too_short, T}); T >= 1000*5*ShutdownTime -> - test_server:fail({shutdown_too_long, T}); + ct:fail({shutdown_too_long, T}); true -> check_exit([SupPid]) end. @@ -1188,9 +1188,9 @@ simple_one_for_one_extra(Config) when is_list(Config) -> if length(Children) == 2 -> case lists:keysearch(CPid2, 2, Children) of {value, _} -> ok; - _ -> test_server:fail(bad_child) + _ -> ct:fail(bad_child) end; - true -> test_server:fail({bad_child_list, Children}) + true -> ct:fail({bad_child_list, Children}) end, [1,2,0,2] = get_child_counts(sup_test), terminate(SupPid, CPid2, child2, abnormal), @@ -1242,7 +1242,7 @@ rest_for_one(Config) when is_list(Config) -> if length(Children) == 3 -> ok; true -> - test_server:fail({bad_child_list, Children}) + ct:fail({bad_child_list, Children}) end, [3,3,0,3] = get_child_counts(sup_test), @@ -1318,7 +1318,7 @@ rest_for_one_other_child_fails_restart(Config) when is_list(Config) -> {child1, _Child1Pid3} -> exit(SupPid, kill), check_exit([StarterPid, SupPid]), - test_server:fail({restarting_started_child, Child1Pid2}) + ct:fail({restarting_started_child, Child1Pid2}) end, StarterPid ! {stop, Self}, check_exit([StarterPid, SupPid]). @@ -1348,7 +1348,7 @@ child_unlink(Config) when is_list(Config) -> ok; _ -> exit(Pid, kill), - test_server:fail(supervisor_hangs) + ct:fail(supervisor_hangs) end. %%------------------------------------------------------------------------- %% Test a basic supervison tree. @@ -1687,7 +1687,7 @@ simple_one_for_one_scale_many_temporary_children(_Config) -> %% The scaling shoul be linear (i.e.10, really), but we %% give some extra here to avoid failing the test %% unecessarily. - ?t:fail({bad_scaling,Scaling}); + ct:fail({bad_scaling,Scaling}); true -> ok end; @@ -2116,14 +2116,14 @@ in_child_list([Pid | Rest], Pids) -> true -> in_child_list(Rest, Pids); false -> - test_server:fail(child_should_be_alive) + ct:fail(child_should_be_alive) end. not_in_child_list([], _) -> true; not_in_child_list([Pid | Rest], Pids) -> case is_in_child_list(Pid, Pids) of true -> - test_server:fail(child_should_not_be_alive); + ct:fail(child_should_not_be_alive); false -> not_in_child_list(Rest, Pids) end. @@ -2144,7 +2144,7 @@ check_exit_reason(Reason) -> {'EXIT', _, Reason} -> ok; {'EXIT', _, Else} -> - test_server:fail({bad_exit_reason, Else}) + ct:fail({bad_exit_reason, Else}) end. check_exit_reason(Pid, Reason) -> @@ -2152,5 +2152,5 @@ check_exit_reason(Pid, Reason) -> {'EXIT', Pid, Reason} -> ok; {'EXIT', Pid, Else} -> - test_server:fail({bad_exit_reason, Else}) + ct:fail({bad_exit_reason, Else}) end. diff --git a/lib/stdlib/test/tar_SUITE.erl b/lib/stdlib/test/tar_SUITE.erl index a22eaa1d3a..6022854809 100644 --- a/lib/stdlib/test/tar_SUITE.erl +++ b/lib/stdlib/test/tar_SUITE.erl @@ -162,7 +162,7 @@ match_output(eof, _Expect, Port) -> kill_port_and_fail(Port, Reason) -> unlink(Port), exit(Port, die), - test_server:fail(Reason). + ct:fail(Reason). make_cmd(Cmd) -> case os:type() of @@ -383,16 +383,16 @@ try_bad(Name0, Reason, Config) -> io:format("Result: ~p", [Expected]), case catch erl_tar:format_error(Reason) of {'EXIT', CrashReason} -> - test_server:fail({format_error, crashed, CrashReason}); + ct:fail({format_error, crashed, CrashReason}); String when is_list(String) -> io:format("format_error(~p) -> ~s", [Reason, String]); Other -> - test_server:fail({format_error, returned, Other}) + ct:fail({format_error, returned, Other}) end; {Other1, Other2} -> io:format("table/2 returned ~p", [Other1]), io:format("extract/2 returned ~p", [Other2]), - test_server:fail({bad_return_value, Other1, Other2}) + ct:fail({bad_return_value, Other1, Other2}) end. errors(doc) -> @@ -423,18 +423,18 @@ try_error(M, F, A, Error) -> {'EXIT', Reason} -> exit(Reason); ok -> - test_server:fail(unexpected_success); + ct:fail(unexpected_success); {error, Error} -> case catch erl_tar:format_error(Error) of {'EXIT', FReason} -> - test_server:fail({format_error, crashed, FReason}); + ct:fail({format_error, crashed, FReason}); String when is_list(String) -> io:format("format_error(~p) -> ~s", [Error, String]); Other -> - test_server:fail({format_error, returned, Other}) + ct:fail({format_error, returned, Other}) end; Other -> - test_server:fail({expected, {error, Error}, actual, Other}) + ct:fail({expected, {error, Error}, actual, Other}) end. %% remove_prefix(Prefix, List) -> ListWithoutPrefix. @@ -850,7 +850,7 @@ start_node(Name, Args) -> ct:log("Trying to start ~w@~s~n", [Name,Host]), case test_server:start_node(Name, peer, [{args,Args}]) of {error,Reason} -> - test_server:fail(Reason); + ct:fail(Reason); {ok,Node} -> ct:log("Node ~p started~n", [Node]), Node diff --git a/lib/stdlib/test/timer_SUITE.erl b/lib/stdlib/test/timer_SUITE.erl index d43f78a481..dcaf399a3f 100644 --- a/lib/stdlib/test/timer_SUITE.erl +++ b/lib/stdlib/test/timer_SUITE.erl @@ -73,7 +73,7 @@ do_big_test(TConfig) when is_list(TConfig) -> report_result(Result). report_result(ok) -> ok; -report_result(Error) -> ?line test_server:fail(Error). +report_result(Error) -> ct:fail(Error). %% ------------------------------------------------------- %% diff --git a/lib/stdlib/test/timer_simple_SUITE.erl b/lib/stdlib/test/timer_simple_SUITE.erl index f3cf34843b..9b0c34435d 100644 --- a/lib/stdlib/test/timer_simple_SUITE.erl +++ b/lib/stdlib/test/timer_simple_SUITE.erl @@ -395,12 +395,12 @@ wait(Pids, ResList, N, M) -> {Pid, ok, Res, T} -> wait(lists:delete(Pid, Pids), [{T, Res} | ResList], N, M); {Pid, Error}-> - ?line test_server:fail(Error), + ct:fail(Error), wait(lists:delete(Pid, Pids), ResList, N+1, M); {'EXIT', Pid, normal} -> wait(lists:delete(Pid, Pids), ResList, N, M); {'EXIT', Pid, Reason} -> - ?line test_server:fail({Pid,Reason}) + ct:fail({Pid,Reason}) end. spawn_timers(0, _, _, _) -> @@ -497,7 +497,7 @@ report_result({Res, 0}) -> report_result({Head, N}) -> io:format("Test Failed: Number of internal tmo ~w~n", [N]), - ?line test_server:fail({Head, N}). + ct:fail({Head, N}). split_list([], AL, IL) -> {AL, IL}; diff --git a/lib/stdlib/test/zip_SUITE.erl b/lib/stdlib/test/zip_SUITE.erl index 135bfd5867..615c1a04a6 100644 --- a/lib/stdlib/test/zip_SUITE.erl +++ b/lib/stdlib/test/zip_SUITE.erl @@ -178,7 +178,7 @@ match_output(eof, Expect, Port) -> kill_port_and_fail(Port, Reason) -> unlink(Port), exit(Port, die), - test_server:fail(Reason). + ct:fail(Reason). make_cmd(Cmd) -> Cmd. @@ -547,7 +547,7 @@ try_bad(Name0, Reason, What, Config) -> io:format("Result: ~p\n", [Expected]); Other -> io:format("unzip/2 returned ~p (expected ~p)\n", [Other, Expected]), - test_server:fail({bad_return_value, Other}) + ct:fail({bad_return_value, Other}) end. unzip_to_binary(doc) -> -- cgit v1.2.3