diff options
Diffstat (limited to 'lib/stdlib/test')
32 files changed, 724 insertions, 730 deletions
diff --git a/lib/stdlib/test/base64_SUITE.erl b/lib/stdlib/test/base64_SUITE.erl index c64a961ffa..7b8650f224 100644 --- a/lib/stdlib/test/base64_SUITE.erl +++ b/lib/stdlib/test/base64_SUITE.erl @@ -1,7 +1,7 @@ %% %% %CopyrightBegin% %% -%% Copyright Ericsson AB 2007-2011. All Rights Reserved. +%% Copyright Ericsson AB 2007-2012. All Rights Reserved. %% %% The contents of this file are subject to the Erlang Public License, %% Version 1.1, (the "License"); you may not use this file except in @@ -20,7 +20,6 @@ -module(base64_SUITE). -include_lib("common_test/include/ct.hrl"). --include("test_server_line.hrl"). %% Test server specific exports -export([all/0, suite/0,groups/0,init_per_suite/1, end_per_suite/1, @@ -33,7 +32,7 @@ mime_decode_to_string/1, roundtrip/1]). init_per_testcase(_, Config) -> - Dog = test_server:timetrap(?t:minutes(2)), + Dog = test_server:timetrap(?t:minutes(4)), NewConfig = lists:keydelete(watchdog, 1, Config), [{watchdog, Dog} | NewConfig]. diff --git a/lib/stdlib/test/dets_SUITE.erl b/lib/stdlib/test/dets_SUITE.erl index 6f77cff2b9..66799f4d05 100644 --- a/lib/stdlib/test/dets_SUITE.erl +++ b/lib/stdlib/test/dets_SUITE.erl @@ -1,7 +1,7 @@ %% %% %CopyrightBegin% %% -%% Copyright Ericsson AB 1996-2011. All Rights Reserved. +%% Copyright Ericsson AB 1996-2012. All Rights Reserved. %% %% The contents of this file are subject to the Erlang Public License, %% Version 1.1, (the "License"); you may not use this file except in @@ -38,7 +38,7 @@ -export([all/0, suite/0,groups/0,init_per_suite/1, end_per_suite/1, init_per_group/2,end_per_group/2, - not_run/1, newly_started/1, basic_v8/1, basic_v9/1, + newly_started/1, basic_v8/1, basic_v9/1, open_v8/1, open_v9/1, sets_v8/1, sets_v9/1, bags_v8/1, bags_v9/1, duplicate_bags_v8/1, duplicate_bags_v9/1, access_v8/1, access_v9/1, dirty_mark/1, dirty_mark2/1, @@ -95,27 +95,25 @@ end_per_testcase(_Case, _Config) -> suite() -> [{ct_hooks,[ts_install_cth]}]. all() -> - case os:type() of - vxworks -> [not_run]; - _ -> - [basic_v8, basic_v9, open_v8, open_v9, sets_v8, sets_v9, - bags_v8, bags_v9, duplicate_bags_v8, duplicate_bags_v9, - newly_started, open_file_v8, open_file_v9, - init_table_v8, init_table_v9, repair_v8, repair_v9, - access_v8, access_v9, oldbugs_v8, oldbugs_v9, - unsafe_assumptions, truncated_segment_array_v8, - truncated_segment_array_v9, dirty_mark, dirty_mark2, - bag_next_v8, bag_next_v9, hash_v8b_v8c, phash, fold_v8, - fold_v9, fixtable_v8, fixtable_v9, match_v8, match_v9, - select_v8, select_v9, update_counter, badarg, - cache_sets_v8, cache_sets_v9, cache_bags_v8, - cache_bags_v9, cache_duplicate_bags_v8, - cache_duplicate_bags_v9, otp_4208, otp_4989, - many_clients, otp_4906, otp_5402, simultaneous_open, - insert_new, repair_continuation, otp_5487, otp_6206, - otp_6359, otp_4738, otp_7146, otp_8070, otp_8856, otp_8898, - otp_8899, otp_8903, otp_8923, otp_9282, otp_9607] - end. + [ + basic_v8, basic_v9, open_v8, open_v9, sets_v8, sets_v9, + bags_v8, bags_v9, duplicate_bags_v8, duplicate_bags_v9, + newly_started, open_file_v8, open_file_v9, + init_table_v8, init_table_v9, repair_v8, repair_v9, + access_v8, access_v9, oldbugs_v8, oldbugs_v9, + unsafe_assumptions, truncated_segment_array_v8, + truncated_segment_array_v9, dirty_mark, dirty_mark2, + bag_next_v8, bag_next_v9, hash_v8b_v8c, phash, fold_v8, + fold_v9, fixtable_v8, fixtable_v9, match_v8, match_v9, + select_v8, select_v9, update_counter, badarg, + cache_sets_v8, cache_sets_v9, cache_bags_v8, + cache_bags_v9, cache_duplicate_bags_v8, + cache_duplicate_bags_v9, otp_4208, otp_4989, + many_clients, otp_4906, otp_5402, simultaneous_open, + insert_new, repair_continuation, otp_5487, otp_6206, + otp_6359, otp_4738, otp_7146, otp_8070, otp_8856, otp_8898, + otp_8899, otp_8903, otp_8923, otp_9282, otp_9607 + ]. groups() -> []. @@ -132,10 +130,6 @@ init_per_group(_GroupName, Config) -> end_per_group(_GroupName, Config) -> Config. -not_run(suite) -> []; -not_run(Conf) when is_list(Conf) -> - {comment, "Not runnable VxWorks/NFS"}. - newly_started(doc) -> ["OTP-3621"]; newly_started(suite) -> @@ -1949,7 +1943,7 @@ match(Config, Version) -> %% match, badarg MSpec = [{'_',[],['$_']}], ?line check_badarg(catch dets:match(no_table, '_'), - dets, safe_fixtable, [no_table,true]), + dets, match, [no_table,'_']), ?line check_badarg(catch dets:match(T, '_', not_a_number), dets, match, [T,'_',not_a_number]), ?line {EC1, _} = dets:select(T, MSpec, 1), @@ -1958,7 +1952,7 @@ match(Config, Version) -> %% match_object, badarg ?line check_badarg(catch dets:match_object(no_table, '_'), - dets, safe_fixtable, [no_table,true]), + dets, match_object, [no_table,'_']), ?line check_badarg(catch dets:match_object(T, '_', not_a_number), dets, match_object, [T,'_',not_a_number]), ?line {EC2, _} = dets:select(T, MSpec, 1), @@ -2127,7 +2121,7 @@ select(Config, Version) -> %% badarg MSpec = [{'_',[],['$_']}], ?line check_badarg(catch dets:select(no_table, MSpec), - dets, safe_fixtable, [no_table,true]), + dets, select, [no_table,MSpec]), ?line check_badarg(catch dets:select(T, <<17>>), dets, select, [T,<<17>>]), ?line check_badarg(catch dets:select(T, []), @@ -2330,7 +2324,7 @@ badarg(Config) when is_list(Config) -> %% match_delete ?line check_badarg(catch dets:match_delete(no_table, '_'), - dets, safe_fixtable, [no_table,true]), + dets, match_delete, [no_table,'_']), %% delete_all_objects ?line check_badarg(catch dets:delete_all_objects(no_table), @@ -2339,17 +2333,19 @@ badarg(Config) when is_list(Config) -> %% select_delete MSpec = [{'_',[],['$_']}], ?line check_badarg(catch dets:select_delete(no_table, MSpec), - dets, safe_fixtable, [no_table,true]), + dets, select_delete, [no_table,MSpec]), ?line check_badarg(catch dets:select_delete(T, <<17>>), dets, select_delete, [T, <<17>>]), %% traverse, fold - ?line check_badarg(catch dets:traverse(no_table, fun(_) -> continue end), - dets, safe_fixtable, [no_table,true]), - ?line check_badarg(catch dets:foldl(fun(_, A) -> A end, [], no_table), - dets, safe_fixtable, [no_table,true]), - ?line check_badarg(catch dets:foldr(fun(_, A) -> A end, [], no_table), - dets, safe_fixtable, [no_table,true]), + TF = fun(_) -> continue end, + ?line check_badarg(catch dets:traverse(no_table, TF), + dets, traverse, [no_table,TF]), + FF = fun(_, A) -> A end, + ?line check_badarg(catch dets:foldl(FF, [], no_table), + dets, foldl, [FF,[],no_table]), + ?line check_badarg(catch dets:foldr(FF, [], no_table), + dets, foldl, [FF,[],no_table]), %% close ?line ok = dets:close(T), diff --git a/lib/stdlib/test/dict_SUITE.erl b/lib/stdlib/test/dict_SUITE.erl index c46fc47b34..df9c769c67 100644 --- a/lib/stdlib/test/dict_SUITE.erl +++ b/lib/stdlib/test/dict_SUITE.erl @@ -53,7 +53,7 @@ end_per_group(_GroupName, Config) -> init_per_testcase(_Case, Config) -> - ?line Dog = ?t:timetrap(?t:minutes(5)), + Dog = ?t:timetrap(?t:minutes(5)), [{watchdog,Dog}|Config]. end_per_testcase(_Case, Config) -> @@ -65,22 +65,22 @@ create(Config) when is_list(Config) -> test_all(fun create_1/1). create_1(M) -> - ?line D0 = M:empty(), - ?line [] = M:to_list(D0), - ?line 0 = M:size(D0), + D0 = M(empty, []), + [] = M(to_list, D0), + 0 = M(size, D0), D0. store(Config) when is_list(Config) -> test_all([{0,132},{253,258},{510,514}], fun store_1/2). store_1(List, M) -> - ?line D0 = M:from_list(List), + D0 = M(from_list, List), %% Make sure that we get the same result by inserting %% elements one at the time. - ?line D1 = foldl(fun({K,V}, Dict) -> M:enter(K, V, Dict) end, - M:empty(), List), - ?line true = M:equal(D0, D1), + D1 = foldl(fun({K,V}, Dict) -> M(enter, {K,V,Dict}) end, + M(empty, []), List), + true = M(equal, {D0,D1}), D0. %%% @@ -98,7 +98,7 @@ dict_mods() -> [Orddict,Dict,Gb]. test_all(Tester) -> - ?line Pids = [spawn_tester(M, Tester) || M <- dict_mods()], + Pids = [spawn_tester(M, Tester) || M <- dict_mods()], collect_all(Pids, []). spawn_tester(M, Tester) -> @@ -106,7 +106,7 @@ spawn_tester(M, Tester) -> spawn_link(fun() -> random:seed(1, 2, 42), S = Tester(M), - Res = {M:size(S),lists:sort(M:to_list(S))}, + Res = {M(size, S),lists:sort(M(to_list, S))}, Parent ! {result,self(),Res} end). diff --git a/lib/stdlib/test/dict_test_lib.erl b/lib/stdlib/test/dict_test_lib.erl index 92a75dad89..7167014310 100644 --- a/lib/stdlib/test/dict_test_lib.erl +++ b/lib/stdlib/test/dict_test_lib.erl @@ -17,67 +17,48 @@ %% %CopyrightEnd% %% --module(dict_test_lib, [Mod,Equal]). +-module(dict_test_lib). --export([module/0,equal/2,empty/0,size/1,to_list/1,from_list/1, - enter/3,delete/2,lookup/2]). +-export([new/2]). -module() -> - Mod. - -equal(X, Y) -> - Equal(X, Y). +new(Mod, Eq) -> + fun (enter, {K,V,D}) -> enter(Mod, K, V, D); + (empty, []) -> empty(Mod); + (equal, {D1,D2}) -> Eq(D1, D2); + (from_list, L) -> from_list(Mod, L); + (module, []) -> Mod; + (size, D) -> Mod:size(D); + (to_list, D) -> to_list(Mod, D) + end. -empty() -> +empty(Mod) -> case erlang:function_exported(Mod, new, 0) of false -> Mod:empty(); true -> Mod:new() end. -size(S) -> - Mod:size(S). - -to_list(S) -> - Mod:to_list(S). +to_list(Mod, D) -> + Mod:to_list(D). -from_list(S) -> +from_list(Mod, L) -> case erlang:function_exported(Mod, from_orddict, 1) of false -> - Mod:from_list(S); + Mod:from_list(L); true -> %% The gb_trees module has no from_list/1 function. %% %% The keys in S are not unique. To make sure %% that we pick the same key/value pairs as %% dict/orddict, first convert the list to an orddict. - Orddict = orddict:from_list(S), + Orddict = orddict:from_list(L), Mod:from_orddict(Orddict) end. %% Store new value into dictionary or update previous value in dictionary. -enter(Key, Val, Dict) -> +enter(Mod, Key, Val, Dict) -> case erlang:function_exported(Mod, store, 3) of false -> Mod:enter(Key, Val, Dict); true -> Mod:store(Key, Val, Dict) end. - -%% Delete an EXISTING key. -delete(Key, Dict) -> - case erlang:function_exported(Mod, delete, 2) of - true -> Mod:delete(Key, Dict); - false -> Mod:erase(Key, Dict) - end. - -%% -> none | {value,Value} -lookup(Key, Dict) -> - case erlang:function_exported(Mod, lookup, 2) of - false -> - case Mod:find(Key, Dict) of - error -> none; - {ok,Value} -> {value,Value} - end; - true -> - Mod:lookup(Key, Dict) - end. diff --git a/lib/stdlib/test/epp_SUITE.erl b/lib/stdlib/test/epp_SUITE.erl index f79414db49..77c615d6d9 100644 --- a/lib/stdlib/test/epp_SUITE.erl +++ b/lib/stdlib/test/epp_SUITE.erl @@ -1,7 +1,7 @@ %% %% %CopyrightBegin% %% -%% Copyright Ericsson AB 1998-2011. All Rights Reserved. +%% Copyright Ericsson AB 1998-2012. All Rights Reserved. %% %% The contents of this file are subject to the Erlang Public License, %% Version 1.1, (the "License"); you may not use this file except in @@ -1236,6 +1236,13 @@ otp_8911(doc) -> otp_8911(suite) -> []; otp_8911(Config) when is_list(Config) -> + case test_server:is_cover() of + true -> + {skip, "Testing cover, so can not run when cover is already running"}; + false -> + do_otp_8911(Config) + end. +do_otp_8911(Config) -> ?line {ok, CWD} = file:get_cwd(), ?line ok = file:set_cwd(?config(priv_dir, Config)), diff --git a/lib/stdlib/test/erl_eval_SUITE.erl b/lib/stdlib/test/erl_eval_SUITE.erl index b0c7d562d5..47792d1052 100644 --- a/lib/stdlib/test/erl_eval_SUITE.erl +++ b/lib/stdlib/test/erl_eval_SUITE.erl @@ -216,13 +216,13 @@ guard_4(doc) -> guard_4(suite) -> []; guard_4(Config) when is_list(Config) -> - ?line check(fun() -> if {erlang,'+'}(3,a) -> true ; true -> false end end, - "if {erlang,'+'}(3,a) -> true ; true -> false end.", - false), - ?line check(fun() -> if {erlang,is_integer}(3) -> true ; true -> false end - end, - "if {erlang,is_integer}(3) -> true ; true -> false end.", - true), + check(fun() -> if erlang:'+'(3,a) -> true ; true -> false end end, + "if erlang:'+'(3,a) -> true ; true -> false end.", + false), + check(fun() -> if erlang:is_integer(3) -> true ; true -> false end + end, + "if erlang:is_integer(3) -> true ; true -> false end.", + true), ?line check(fun() -> [X || X <- [1,2,3], erlang:is_integer(X)] end, "[X || X <- [1,2,3], erlang:is_integer(X)].", [1,2,3]), @@ -230,11 +230,11 @@ guard_4(Config) when is_list(Config) -> end, "if is_atom(is_integer(a)) -> true ; true -> false end.", true), - ?line check(fun() -> if {erlang,is_atom}({erlang,is_integer}(a)) -> true; - true -> false end end, - "if {erlang,is_atom}({erlang,is_integer}(a)) -> true; " - "true -> false end.", - true), + check(fun() -> if erlang:is_atom(erlang:is_integer(a)) -> true; + true -> false end end, + "if erlang:is_atom(erlang:is_integer(a)) -> true; " + "true -> false end.", + true), ?line check(fun() -> if is_atom(3+a) -> true ; true -> false end end, "if is_atom(3+a) -> true ; true -> false end.", false), @@ -1077,11 +1077,6 @@ do_funs(LFH, EFH) -> concat(["begin F1 = fun(F,N) -> apply(", M, ",count_down,[F, N]) end, F1(F1,1000) end."]), 0, ['F1'], LFH, EFH), - ?line check(fun() -> F1 = fun(F,N) -> {?MODULE,count_down}(F,N) - end, F1(F1, 1000) end, - concat(["begin F1 = fun(F,N) -> {", M, - ",count_down}(F, N) end, F1(F1,1000) end."]), - 0, ['F1'], LFH, EFH), ?line check(fun() -> F = fun(F,N) when N > 0 -> apply(F,[F,N-1]); (_F,0) -> ok end, F(F, 1000) @@ -1113,11 +1108,11 @@ do_funs(LFH, EFH) -> true = {2,3} == F(2) end, "begin F = fun(X) -> A = 1+X, {X,A} end, true = {2,3} == F(2) end.", true, ['F'], LFH, EFH), - ?line check(fun() -> F = fun(X) -> {erlang,'+'}(X,2) end, - true = 3 == F(1) end, - "begin F = fun(X) -> {erlang,'+'}(X,2) end," - " true = 3 == F(1) end.", true, ['F'], - LFH, EFH), + check(fun() -> F = fun(X) -> erlang:'+'(X,2) end, + true = 3 == F(1) end, + "begin F = fun(X) -> erlang:'+'(X,2) end," + " true = 3 == F(1) end.", true, ['F'], + LFH, EFH), ?line check(fun() -> F = fun(X) -> byte_size(X) end, ?MODULE:do_apply(F,<<"hej">>) end, concat(["begin F = fun(X) -> size(X) end,", diff --git a/lib/stdlib/test/erl_expand_records_SUITE.erl b/lib/stdlib/test/erl_expand_records_SUITE.erl index 01cdb92d7b..e248934e10 100644 --- a/lib/stdlib/test/erl_expand_records_SUITE.erl +++ b/lib/stdlib/test/erl_expand_records_SUITE.erl @@ -157,7 +157,7 @@ expr(Config) when is_list(Config) -> One = 1 = fun f/1(1), 2 = fun(X) -> X end(One + One), 3 = fun exprec_test:f/1(3), - 4 = {exprec_test,f}(4), + 4 = exprec_test:f(4), 5 = ''.f(5), L = receive {a,message,L0} -> diff --git a/lib/stdlib/test/erl_lint_SUITE.erl b/lib/stdlib/test/erl_lint_SUITE.erl index 9f9d97b619..90a37f6441 100644 --- a/lib/stdlib/test/erl_lint_SUITE.erl +++ b/lib/stdlib/test/erl_lint_SUITE.erl @@ -50,7 +50,8 @@ unsafe_vars_try/1, guard/1, otp_4886/1, otp_4988/1, otp_5091/1, otp_5276/1, otp_5338/1, otp_5362/1, otp_5371/1, otp_7227/1, otp_5494/1, otp_5644/1, otp_5878/1, - otp_5917/1, otp_6585/1, otp_6885/1, export_all/1, + otp_5917/1, otp_6585/1, otp_6885/1, otp_10436/1, + export_all/1, bif_clash/1, behaviour_basic/1, behaviour_multiple/1, otp_7550/1, @@ -80,7 +81,7 @@ all() -> unsafe_vars, unsafe_vars2, unsafe_vars_try, guard, otp_4886, otp_4988, otp_5091, otp_5276, otp_5338, otp_5362, otp_5371, otp_7227, otp_5494, otp_5644, - otp_5878, otp_5917, otp_6585, otp_6885, export_all, + otp_5878, otp_5917, otp_6585, otp_6885, otp_10436, export_all, bif_clash, behaviour_basic, behaviour_multiple, otp_7550, otp_8051, format_warn, {group, on_load}, too_many_arguments]. @@ -1307,44 +1308,30 @@ guard(Config) when is_list(Config) -> foo; t3(A) when erlang:is_record(A, {apa}) -> foo; - t3(A) when {erlang,is_record}(A, {apa}) -> - foo; t3(A) when is_record(A, {apa}, 1) -> foo; t3(A) when erlang:is_record(A, {apa}, 1) -> foo; - t3(A) when {erlang,is_record}(A, {apa}, 1) -> - foo; t3(A) when is_record(A, apa, []) -> foo; t3(A) when erlang:is_record(A, apa, []) -> foo; - t3(A) when {erlang,is_record}(A, apa, []) -> - foo; t3(A) when record(A, apa) -> foo; t3(A) when is_record(A, apa) -> foo; t3(A) when erlang:is_record(A, apa) -> - foo; - t3(A) when {erlang,is_record}(A, apa) -> foo. ">>, [warn_unused_vars, nowarn_obsolete_guard], - {error,[{2,erl_lint,illegal_guard_expr}, - {4,erl_lint,illegal_guard_expr}, - {6,erl_lint,illegal_guard_expr}, - {8,erl_lint,illegal_guard_expr}, - {10,erl_lint,illegal_guard_expr}, - {12,erl_lint,illegal_guard_expr}, - {14,erl_lint,illegal_guard_expr}, - {16,erl_lint,illegal_guard_expr}, - {18,erl_lint,illegal_guard_expr}, - {20,erl_lint,illegal_guard_expr}], - [{8,erl_lint,deprecated_tuple_fun}, - {14,erl_lint,deprecated_tuple_fun}, - {20,erl_lint,deprecated_tuple_fun}, - {28,erl_lint,deprecated_tuple_fun}]}}, + {errors,[{2,erl_lint,illegal_guard_expr}, + {4,erl_lint,illegal_guard_expr}, + {6,erl_lint,illegal_guard_expr}, + {8,erl_lint,illegal_guard_expr}, + {10,erl_lint,illegal_guard_expr}, + {12,erl_lint,illegal_guard_expr}, + {14,erl_lint,illegal_guard_expr}], + []}}, {guard6, <<"-record(apa,{a=a,b=foo:bar()}). apa() -> @@ -2400,6 +2387,28 @@ otp_6885(Config) when is_list(Config) -> []} = run_test2(Config, Ts, []), ok. +otp_10436(doc) -> + "OTP-6885. Warnings for opaque types."; +otp_10436(suite) -> []; +otp_10436(Config) when is_list(Config) -> + Ts = <<"-module(otp_10436). + -export_type([t1/0]). + -opaque t1() :: {i, integer()}. + -opaque t2() :: {a, atom()}. + ">>, + {warnings,[{4,erl_lint,{not_exported_opaque,{t2,0}}}, + {4,erl_lint,{unused_type,{t2,0}}}]} = + run_test2(Config, Ts, []), + Ts2 = <<"-module(otp_10436_2). + -export_type([t1/0, t2/0]). + -opaque t1() :: term(). + -opaque t2() :: any(). + ">>, + {warnings,[{3,erl_lint,{underspecified_opaque,{t1,0}}}, + {4,erl_lint,{underspecified_opaque,{t2,0}}}]} = + run_test2(Config, Ts2, []), + ok. + export_all(doc) -> "OTP-7392. Warning for export_all."; export_all(Config) when is_list(Config) -> @@ -2848,10 +2857,10 @@ otp_8051(doc) -> otp_8051(Config) when is_list(Config) -> Ts = [{otp_8051, <<"-opaque foo() :: bar(). + -export_type([foo/0]). ">>, [], - {error,[{1,erl_lint,{undefined_type,{bar,0}}}], - [{1,erl_lint,{unused_type,{foo,0}}}]}}], + {errors,[{1,erl_lint,{undefined_type,{bar,0}}}],[]}}], ?line [] = run(Config, Ts), ok. diff --git a/lib/stdlib/test/escript_SUITE.erl b/lib/stdlib/test/escript_SUITE.erl index 38c085616d..5b592c65cc 100644 --- a/lib/stdlib/test/escript_SUITE.erl +++ b/lib/stdlib/test/escript_SUITE.erl @@ -64,7 +64,7 @@ end_per_group(_GroupName, Config) -> Config. init_per_testcase(_Case, Config) -> - ?line Dog = ?t:timetrap(?t:minutes(2)), + ?line Dog = ?t:timetrap(?t:minutes(5)), [{watchdog,Dog}|Config]. end_per_testcase(_Case, Config) -> @@ -618,7 +618,7 @@ compile_files([File | Files], SrcDir, OutDir) -> case filename:extension(File) of ".erl" -> AbsFile = filename:join([SrcDir, File]), - case compile:file(AbsFile, [{outdir, OutDir}]) of + case compile:file(AbsFile, [{outdir, OutDir},report_errors]) of {ok, _Mod} -> compile_files(Files, SrcDir, OutDir); Error -> diff --git a/lib/stdlib/test/ets_SUITE.erl b/lib/stdlib/test/ets_SUITE.erl index 95f10b1df3..dc17e5d33c 100644 --- a/lib/stdlib/test/ets_SUITE.erl +++ b/lib/stdlib/test/ets_SUITE.erl @@ -2170,20 +2170,29 @@ heir_do(Opts) -> ?line undefined = ets:info(foo), %% When heir dies and pid reused before founder dies - NextPidIx = erts_debug:get_internal_state(next_pid), - {Founder4,MrefF4} = my_spawn_monitor(fun()->heir_founder(Master,"The dying heir",Opts)end), - {Heir4,MrefH4} = my_spawn_monitor(fun()->heir_heir(Founder4)end), - Founder4 ! {go, Heir4}, - ?line {'DOWN', MrefH4, process, Heir4, normal} = receive_any(), - erts_debug:set_internal_state(next_pid, NextPidIx), - {Heir4,MrefH4_B} = spawn_monitor_with_pid(Heir4, - fun()-> ?line die_please = receive_any() end), - Founder4 ! die_please, - ?line {'DOWN', MrefF4, process, Founder4, normal} = receive_any(), - Heir4 ! die_please, - ?line {'DOWN', MrefH4_B, process, Heir4, normal} = receive_any(), - ?line undefined = ets:info(foo), - + repeat_while(fun() -> + NextPidIx = erts_debug:get_internal_state(next_pid), + {Founder4,MrefF4} = my_spawn_monitor(fun()->heir_founder(Master,"The dying heir",Opts)end), + {Heir4,MrefH4} = my_spawn_monitor(fun()->heir_heir(Founder4)end), + Founder4 ! {go, Heir4}, + ?line {'DOWN', MrefH4, process, Heir4, normal} = receive_any(), + erts_debug:set_internal_state(next_pid, NextPidIx), + DoppelGanger = spawn_monitor_with_pid(Heir4, + fun()-> ?line die_please = receive_any() end), + Founder4 ! die_please, + ?line {'DOWN', MrefF4, process, Founder4, normal} = receive_any(), + case DoppelGanger of + {Heir4,MrefH4_B} -> + Heir4 ! die_please, + ?line {'DOWN', MrefH4_B, process, Heir4, normal} = receive_any(), + ?line undefined = ets:info(foo), + false; + failed -> + io:format("Failed to spawn process with pid ~p\n", [Heir4]), + true % try again + end + end), + ?line verify_etsmem(EtsMem). heir_founder(Master, HeirData, Opts) -> @@ -4208,21 +4217,13 @@ heavy_lookup_element(Config) when is_list(Config) -> repeat_for_opts(heavy_lookup_element_do). heavy_lookup_element_do(Opts) -> - ?line EtsMem = etsmem(), - ?line Tab = ets_new(foobar_table, [set, protected, {keypos, 2} | Opts]), - ?line ok = fill_tab2(Tab, 0, 7000), - case os:type() of - vxworks -> - ?line ?t:do_times(5, ?MODULE, do_lookup_element, - [Tab, 6999, 1]); - % lookup ALL elements 5 times. - _ -> - ?line ?t:do_times(50, ?MODULE, do_lookup_element, - [Tab, 6999, 1]) - % lookup ALL elements 50 times. - end, - ?line true = ets:delete(Tab), - ?line verify_etsmem(EtsMem). + EtsMem = etsmem(), + Tab = ets_new(foobar_table, [set, protected, {keypos, 2} | Opts]), + ok = fill_tab2(Tab, 0, 7000), + % lookup ALL elements 50 times + ?t:do_times(50, ?MODULE, do_lookup_element, [Tab, 6999, 1]), + true = ets:delete(Tab), + verify_etsmem(EtsMem). do_lookup_element(_Tab, 0, _) -> ok; do_lookup_element(Tab, N, M) -> @@ -5795,25 +5796,20 @@ receive_any_spinning(Loops, N, Tries) when N>0 -> spawn_monitor_with_pid(Pid, Fun) when is_pid(Pid) -> - spawn_monitor_with_pid(Pid, Fun, 1, 10). + spawn_monitor_with_pid(Pid, Fun, 10). -spawn_monitor_with_pid(Pid, Fun, N, M) when N > M*10 -> - spawn_monitor_with_pid(Pid, Fun, N, M*10); -spawn_monitor_with_pid(Pid, Fun, N, M) -> - ?line false = is_process_alive(Pid), +spawn_monitor_with_pid(_, _, 0) -> + failed; +spawn_monitor_with_pid(Pid, Fun, N) -> case my_spawn(fun()-> case self() of Pid -> Fun(); _ -> die end end) of - Pid -> + Pid -> {Pid, erlang:monitor(process, Pid)}; Other -> - case N rem M of - 0 -> io:format("Failed ~p times to get pid ~p (current = ~p)\n",[N,Pid,Other]); - _ -> ok - end, - spawn_monitor_with_pid(Pid,Fun,N+1,M) + spawn_monitor_with_pid(Pid,Fun,N-1) end. diff --git a/lib/stdlib/test/filelib_SUITE.erl b/lib/stdlib/test/filelib_SUITE.erl index 1de639a166..1fd7518519 100644 --- a/lib/stdlib/test/filelib_SUITE.erl +++ b/lib/stdlib/test/filelib_SUITE.erl @@ -176,9 +176,64 @@ do_wildcard_5(Dir, Wcf) -> %% Cleanup ?line del(Files), - ?line foreach(fun(D) -> ok = file:del_dir(filename:join(Dir, D)) end, Dirs). + ?line foreach(fun(D) -> ok = file:del_dir(filename:join(Dir, D)) end, Dirs), + do_wildcard_6(Dir, Wcf). + +do_wildcard_6(Dir, Wcf) -> + ok = file:make_dir(filename:join(Dir, "xbin")), + All = ["xbin/a.x","xbin/b.x","xbin/c.x"], + Files = mkfiles(All, Dir), + All = Wcf("xbin/*.x"), + All = Wcf("xbin/*"), + ["xbin"] = Wcf("*"), + All = Wcf("*/*"), + del(Files), + ok = file:del_dir(filename:join(Dir, "xbin")), + do_wildcard_7(Dir, Wcf). + +do_wildcard_7(Dir, Wcf) -> + Dirs = ["blurf","xa","yyy"], + SubDirs = ["blurf/nisse"], + foreach(fun(D) -> + ok = file:make_dir(filename:join(Dir, D)) + end, Dirs ++ SubDirs), + All = ["blurf/nisse/baz","xa/arne","xa/kalle","yyy/arne"], + Files = mkfiles(lists:reverse(All), Dir), + %% Test. + Listing = Wcf("**"), + ["blurf","blurf/nisse","blurf/nisse/baz", + "xa","xa/arne","xa/kalle","yyy","yyy/arne"] = Listing, + Listing = Wcf("**/*"), + ["xa/arne","yyy/arne"] = Wcf("**/arne"), + ["blurf/nisse"] = Wcf("**/nisse"), + [] = Wcf("mountain/**"), + + %% Cleanup + del(Files), + foreach(fun(D) -> + ok = file:del_dir(filename:join(Dir, D)) + end, SubDirs ++ Dirs), + do_wildcard_8(Dir, Wcf). + +do_wildcard_8(Dir, Wcf) -> + Dirs0 = ["blurf"], + Dirs1 = ["blurf/nisse"], + Dirs2 = ["blurf/nisse/a", "blurf/nisse/b"], + foreach(fun(D) -> + ok = file:make_dir(filename:join(Dir, D)) + end, Dirs0 ++ Dirs1 ++ Dirs2), + All = ["blurf/nisse/a/1.txt", "blurf/nisse/b/2.txt", "blurf/nisse/b/3.txt"], + Files = mkfiles(lists:reverse(All), Dir), + %% Test. + All = Wcf("**/blurf/**/*.txt"), + + %% Cleanup + del(Files), + foreach(fun(D) -> + ok = file:del_dir(filename:join(Dir, D)) + end, Dirs2 ++ Dirs1 ++ Dirs0). fold_files(Config) when is_list(Config) -> ?line Dir = filename:join(?config(priv_dir, Config), "fold_files"), diff --git a/lib/stdlib/test/filename_SUITE.erl b/lib/stdlib/test/filename_SUITE.erl index 8817f5a55b..232df6a13f 100644 --- a/lib/stdlib/test/filename_SUITE.erl +++ b/lib/stdlib/test/filename_SUITE.erl @@ -112,19 +112,6 @@ absname(Config) when is_list(Config) -> ?line "/erlang/src" = filename:absname(["/erl",'a','ng',"/",'s',"rc"]), ?line "/erlang/src" = filename:absname("/erlang///src"), ?line "/file_sorter.erl" = filename:absname([file_sorter|'.erl']), - ok; - vxworks -> - Test_dir = ?config(priv_dir, Config), - Test1 = Test_dir ++ "/foo", - Test2 = Test_dir ++ "/ebin", - ?line ok = file:set_cwd(Test_dir), - ?line Test1 = filename:absname(foo), - ?line Test1= filename:absname("foo"), - ?line Test2 = filename:absname("foo/../ebin"), - ?line "/erlang" = filename:absname("/erlang"), - ?line "/erlang/src" = filename:absname("/erlang/src"), - ?line "/erlang/src" = filename:absname(["/erlan",'g/s',"rc"]), - ?line "/erlang/src" = filename:absname("/erlang///src"), ok end. @@ -179,15 +166,6 @@ absname_2(Config) when is_list(Config) -> ?line "/erlang" = filename:absname("/erlang", "/"), ?line "/erlang/src" = filename:absname("/erlang/src", "/"), ?line "/erlang/src" = filename:absname("/erlang///src", "/"), - ok; - vxworks -> - ?line "/usr/foo" = filename:absname(foo, "/usr"), - ?line "/usr/foo" = filename:absname("foo", "/usr"), - ?line "/usr/ebin" = filename:absname("../ebin", "/usr"), - ?line "/usr/ebin" = filename:absname("../ebin", "/usr/src"), - ?line "/erlang" = filename:absname("/erlang", "/usr"), - ?line "/erlang/src" = filename:absname("/erlang/src", "/usr"), - ?line "/erlang/src" = filename:absname("/erlang///src", "/usr"), ok end. @@ -213,11 +191,7 @@ basename_1(Config) when is_list(Config) -> ?line "foo" = filename:basename("A:foo"); {unix, _} -> ?line "strange\\but\\true" = - filename:basename("strange\\but\\true"); - vxworks -> - ?line "foo" = filename:basename(["usr\\foo\\"]), - ?line "foo" = filename:basename("elrond:usr\\foo\\"), - ?line "foo" = filename:basename("disk:/foo") + filename:basename("strange\\but\\true") end, ?line test_server:timetrap_cancel(Dog), ok. @@ -249,15 +223,7 @@ basename_2(Config) when is_list(Config) -> ?line "strange\\but\\true" = filename:basename("strange\\but\\true.erl", ".erl"), ?line "strange\\but\\true" = - filename:basename("strange\\but\\true", ".erl"); - vxworks -> - ?line "foo" = filename:basename("net:foo", ".erl"), - ?line "foo.erl" = filename:basename("net:\\usr\\foo.erl", - ".hrl"), - ?line "foo.erl" = - filename:basename("/disk0:\\usr.hrl\\foo.erl", - ".hrl"), - ?line "foo" = filename:basename("/home\\usr\\foo", ".hrl") + filename:basename("strange\\but\\true", ".erl") end, ?line test_server:timetrap_cancel(Dog), ok. @@ -267,37 +233,25 @@ basename_2(Config) when is_list(Config) -> dirname(Config) when is_list(Config) -> case os:type() of {win32,_} -> - ?line "A:/usr" = filename:dirname("A:/usr/foo.erl"), - ?line "A:usr" = filename:dirname("A:usr/foo.erl"), - ?line "/usr" = filename:dirname("\\usr\\foo.erl"), - ?line "/" = filename:dirname("\\usr"), - ?line "A:" = filename:dirname("A:"); - vxworks -> - ?line "net:/usr" = filename:dirname("net:/usr/foo.erl"), - ?line "/disk0:/usr" = filename:dirname("/disk0:/usr/foo.erl"), - ?line "/usr" = filename:dirname("\\usr\\foo.erl"), - ?line "/usr" = filename:dirname("\\usr"), - ?line "net:" = filename:dirname("net:"); + "A:/usr" = filename:dirname("A:/usr/foo.erl"), + "A:usr" = filename:dirname("A:usr/foo.erl"), + "/usr" = filename:dirname("\\usr\\foo.erl"), + "/" = filename:dirname("\\usr"), + "A:" = filename:dirname("A:"); _ -> true end, - ?line "usr" = filename:dirname("usr///foo.erl"), - ?line "." = filename:dirname("foo.erl"), - ?line "." = filename:dirname("."), - ?line "usr" = filename:dirname('usr/foo.erl'), - ?line "usr" = filename:dirname(['usr','/foo.erl']), - ?line "usr" = filename:dirname(['us','r/foo.erl']), - ?line "usr" = filename:dirname(['usr/','/foo.erl']), - ?line "usr" = filename:dirname(['usr/','foo.erl']), - ?line "usr" = filename:dirname(['usr/'|'foo.erl']), - ?line "usr" = filename:dirname(['usr/f','oo.erl']), - case os:type() of - vxworks -> - ?line "/" = filename:dirname("/"), - ?line "/usr" = filename:dirname("/usr"); - _ -> - ?line "/" = filename:dirname("/"), - ?line "/" = filename:dirname("/usr") - end, + "usr" = filename:dirname("usr///foo.erl"), + "." = filename:dirname("foo.erl"), + "." = filename:dirname("."), + "usr" = filename:dirname('usr/foo.erl'), + "usr" = filename:dirname(['usr','/foo.erl']), + "usr" = filename:dirname(['us','r/foo.erl']), + "usr" = filename:dirname(['usr/','/foo.erl']), + "usr" = filename:dirname(['usr/','foo.erl']), + "usr" = filename:dirname(['usr/'|'foo.erl']), + "usr" = filename:dirname(['usr/f','oo.erl']), + "/" = filename:dirname("/"), + "/" = filename:dirname("/usr"), ok. @@ -319,12 +273,6 @@ extension(Config) when is_list(Config) -> filename:extension("A:/usr.bar/foo.nisse.erl"), ?line "" = filename:extension("A:/usr.bar/foo"), ok; - vxworks -> - ?line "" = filename:extension("/disk0:\\usr\\foo"), - ?line ".erl" = - filename:extension("net:/usr.bar/foo.nisse.erl"), - ?line "" = filename:extension("net:/usr.bar/foo"), - ok; _ -> ok end. @@ -369,25 +317,6 @@ join(Config) when is_list(Config) -> filename:join(["A:","C:usr","foo.erl"]), ?line "d:/foo" = filename:join([$D, $:, $/, []], "foo"), ok; - vxworks -> - ?line "Net:" = filename:join(["Net:/"]), - ?line "net:" = filename:join(["net:\\"]), - ?line "net:/abc" = filename:join(["net:/", "abc"]), - ?line "net:/abc" = filename:join(["net:", "abc"]), - ?line "a/b/c/d/e/f/g" = - filename:join(["a//b\\c//\\/\\d/\\e/f\\g"]), - ?line "net:/usr/foo.erl" = - filename:join(["net:","usr","foo.erl"]), - ?line "/usr/foo.erl" = - filename:join(["net:","/usr","foo.erl"]), - ?line "/target:usr" = filename:join("net:","/target:usr"), - ?line "kernel:/usr" = filename:join("net:", "kernel:/usr"), - ?line "foo:/usr/foo.erl" = - filename:join(["A:","foo:/usr","foo.erl"]), - ?line "/disk0:usr/foo.erl" = - filename:join(["kalle:","/disk0:usr","foo.erl"]), - ?line "D:/foo" = filename:join([$D, $:, $/, []], "foo"), - ok; {unix, _} -> ok end. @@ -406,10 +335,6 @@ pathtype(Config) when is_list(Config) -> {unix, _} -> ?line absolute = filename:pathtype("/"), ?line absolute = filename:pathtype("/usr/local/bin"), - ok; - vxworks -> - ?line absolute = filename:pathtype("/usr/local/bin"), - ?line absolute = filename:pathtype("net:usr/local/bin"), ok end. @@ -424,12 +349,7 @@ rootname(Config) when is_list(Config) -> ok. split(Config) when is_list(Config) -> - case os:type() of - vxworks -> - ?line ["/usr","local","bin"] = filename:split("/usr/local/bin"); - _ -> - ?line ["/","usr","local","bin"] = filename:split("/usr/local/bin") - end, + ?line ["/","usr","local","bin"] = filename:split("/usr/local/bin"), ?line ["foo","bar"]= filename:split("foo/bar"), ?line ["foo", "bar", "hello"]= filename:split("foo////bar//hello"), ?line ["foo", "bar", "hello"]= filename:split(["foo//",'//bar//h',"ello"]), @@ -447,18 +367,6 @@ split(Config) when is_list(Config) -> ?line ["a:","msdev","include"] = filename:split("a:msdev\\include"), ok; - vxworks -> - ?line ["net:","msdev","include"] = - filename:split("net:/msdev/include"), - ?line ["Target:","msdev","include"] = - filename:split("Target:/msdev/include"), - ?line ["msdev","include"] = - filename:split("msdev\\include"), - ?line ["/disk0:","msdev","include"] = - filename:split("/disk0:\\msdev\\include"), - ?line ["a:","msdev","include"] = - filename:split("a:msdev\\include"), - ok; _ -> ok end. @@ -657,56 +565,38 @@ basename_bin_2(Config) when is_list(Config) -> dirname_bin(Config) when is_list(Config) -> case os:type() of {win32,_} -> - ?line <<"A:/usr">> = filename:dirname(<<"A:/usr/foo.erl">>), - ?line <<"A:usr">> = filename:dirname(<<"A:usr/foo.erl">>), - ?line <<"/usr">> = filename:dirname(<<"\\usr\\foo.erl">>), - ?line <<"/">> = filename:dirname(<<"\\usr">>), - ?line <<"A:">> = filename:dirname(<<"A:">>); - vxworks -> - ?line <<"net:/usr">> = filename:dirname(<<"net:/usr/foo.erl">>), - ?line <<"/disk0:/usr">> = filename:dirname(<<"/disk0:/usr/foo.erl">>), - ?line <<"/usr">> = filename:dirname(<<"\\usr\\foo.erl">>), - ?line <<"/usr">> = filename:dirname(<<"\\usr">>), - ?line <<"net:">> = filename:dirname(<<"net:">>); + <<"A:/usr">> = filename:dirname(<<"A:/usr/foo.erl">>), + <<"A:usr">> = filename:dirname(<<"A:usr/foo.erl">>), + <<"/usr">> = filename:dirname(<<"\\usr\\foo.erl">>), + <<"/">> = filename:dirname(<<"\\usr">>), + <<"A:">> = filename:dirname(<<"A:">>); _ -> true end, - ?line <<"usr">> = filename:dirname(<<"usr///foo.erl">>), - ?line <<".">> = filename:dirname(<<"foo.erl">>), - ?line <<".">> = filename:dirname(<<".">>), - case os:type() of - vxworks -> - ?line <<"/">> = filename:dirname(<<"/">>), - ?line <<"/usr">> = filename:dirname(<<"/usr">>); - _ -> - ?line <<"/">> = filename:dirname(<<"/">>), - ?line <<"/">> = filename:dirname(<<"/usr">>) - end, + <<"usr">> = filename:dirname(<<"usr///foo.erl">>), + <<".">> = filename:dirname(<<"foo.erl">>), + <<".">> = filename:dirname(<<".">>), + <<"/">> = filename:dirname(<<"/">>), + <<"/">> = filename:dirname(<<"/usr">>), ok. %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% extension_bin(Config) when is_list(Config) -> - ?line <<".erl">> = filename:extension(<<"A:/usr/foo.erl">>), - ?line <<".erl">> = filename:extension(<<"A:/usr/foo.nisse.erl">>), - ?line <<".erl">> = filename:extension(<<"A:/usr.bar/foo.nisse.erl">>), - ?line <<"">> = filename:extension(<<"A:/usr.bar/foo">>), - ?line <<"">> = filename:extension(<<"A:/usr/foo">>), - ?line case os:type() of - {win32, _} -> - ?line <<"">> = filename:extension(<<"A:\\usr\\foo">>), - ?line <<".erl">> = - filename:extension(<<"A:/usr.bar/foo.nisse.erl">>), - ?line <<"">> = filename:extension(<<"A:/usr.bar/foo">>), - ok; - vxworks -> - ?line <<"">> = filename:extension(<<"/disk0:\\usr\\foo">>), - ?line <<".erl">> = - filename:extension(<<"net:/usr.bar/foo.nisse.erl">>), - ?line <<"">> = filename:extension(<<"net:/usr.bar/foo">>), - ok; - _ -> ok - end. + <<".erl">> = filename:extension(<<"A:/usr/foo.erl">>), + <<".erl">> = filename:extension(<<"A:/usr/foo.nisse.erl">>), + <<".erl">> = filename:extension(<<"A:/usr.bar/foo.nisse.erl">>), + <<"">> = filename:extension(<<"A:/usr.bar/foo">>), + <<"">> = filename:extension(<<"A:/usr/foo">>), + case os:type() of + {win32, _} -> + ?line <<"">> = filename:extension(<<"A:\\usr\\foo">>), + ?line <<".erl">> = + filename:extension(<<"A:/usr.bar/foo.nisse.erl">>), + ?line <<"">> = filename:extension(<<"A:/usr.bar/foo">>), + ok; + _ -> ok + end. %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% @@ -754,50 +644,45 @@ join_bin(Config) when is_list(Config) -> end. pathtype_bin(Config) when is_list(Config) -> - ?line relative = filename:pathtype(<<"..">>), - ?line relative = filename:pathtype(<<"foo">>), - ?line relative = filename:pathtype(<<"foo/bar">>), - ?line relative = filename:pathtype('foo/bar'), + relative = filename:pathtype(<<"..">>), + relative = filename:pathtype(<<"foo">>), + relative = filename:pathtype(<<"foo/bar">>), + relative = filename:pathtype('foo/bar'), case os:type() of {win32, _} -> - ?line volumerelative = filename:pathtype(<<"/usr/local/bin">>), - ?line volumerelative = filename:pathtype(<<"A:usr/local/bin">>), + volumerelative = filename:pathtype(<<"/usr/local/bin">>), + volumerelative = filename:pathtype(<<"A:usr/local/bin">>), ok; {unix, _} -> - ?line absolute = filename:pathtype(<<"/">>), - ?line absolute = filename:pathtype(<<"/usr/local/bin">>), + absolute = filename:pathtype(<<"/">>), + absolute = filename:pathtype(<<"/usr/local/bin">>), ok end. rootname_bin(Config) when is_list(Config) -> - ?line <<"/jam.src/kalle">> = filename:rootname(<<"/jam.src/kalle">>), - ?line <<"/jam.src/foo">> = filename:rootname(<<"/jam.src/foo.erl">>), - ?line <<"/jam.src/foo">> = filename:rootname(<<"/jam.src/foo.erl">>, <<".erl">>), - ?line <<"/jam.src/foo.jam">> = filename:rootname(<<"/jam.src/foo.jam">>, <<".erl">>), - ?line <<"/jam.src/foo.jam">> = filename:rootname(["/jam.sr",'c/foo.j',"am"],<<".erl">>), - ?line <<"/jam.src/foo.jam">> = filename:rootname(["/jam.sr",'c/foo.j'|am],<<".erl">>), + <<"/jam.src/kalle">> = filename:rootname(<<"/jam.src/kalle">>), + <<"/jam.src/foo">> = filename:rootname(<<"/jam.src/foo.erl">>), + <<"/jam.src/foo">> = filename:rootname(<<"/jam.src/foo.erl">>, <<".erl">>), + <<"/jam.src/foo.jam">> = filename:rootname(<<"/jam.src/foo.jam">>, <<".erl">>), + <<"/jam.src/foo.jam">> = filename:rootname(["/jam.sr",'c/foo.j',"am"],<<".erl">>), + <<"/jam.src/foo.jam">> = filename:rootname(["/jam.sr",'c/foo.j'|am],<<".erl">>), ok. split_bin(Config) when is_list(Config) -> - case os:type() of - vxworks -> - ?line [<<"/usr">>,<<"local">>,<<"bin">>] = filename:split(<<"/usr/local/bin">>); - _ -> - ?line [<<"/">>,<<"usr">>,<<"local">>,<<"bin">>] = filename:split(<<"/usr/local/bin">>) - end, - ?line [<<"foo">>,<<"bar">>]= filename:split(<<"foo/bar">>), - ?line [<<"foo">>, <<"bar">>, <<"hello">>]= filename:split(<<"foo////bar//hello">>), + [<<"/">>,<<"usr">>,<<"local">>,<<"bin">>] = filename:split(<<"/usr/local/bin">>), + [<<"foo">>,<<"bar">>]= filename:split(<<"foo/bar">>), + [<<"foo">>, <<"bar">>, <<"hello">>]= filename:split(<<"foo////bar//hello">>), case os:type() of {win32,_} -> - ?line [<<"a:/">>,<<"msdev">>,<<"include">>] = + [<<"a:/">>,<<"msdev">>,<<"include">>] = filename:split(<<"a:/msdev/include">>), - ?line [<<"a:/">>,<<"msdev">>,<<"include">>] = + [<<"a:/">>,<<"msdev">>,<<"include">>] = filename:split(<<"A:/msdev/include">>), - ?line [<<"msdev">>,<<"include">>] = + [<<"msdev">>,<<"include">>] = filename:split(<<"msdev\\include">>), - ?line [<<"a:/">>,<<"msdev">>,<<"include">>] = + [<<"a:/">>,<<"msdev">>,<<"include">>] = filename:split(<<"a:\\msdev\\include">>), - ?line [<<"a:">>,<<"msdev">>,<<"include">>] = + [<<"a:">>,<<"msdev">>,<<"include">>] = filename:split(<<"a:msdev\\include">>), ok; _ -> @@ -814,4 +699,3 @@ t_nativename_bin(Config) when is_list(Config) -> ?line <<"/usr/tmp/arne">> = filename:nativename(<<"/usr/tmp//arne/">>) end. - diff --git a/lib/stdlib/test/gen_fsm_SUITE.erl b/lib/stdlib/test/gen_fsm_SUITE.erl index bdb4ea65b5..22f66a6c14 100644 --- a/lib/stdlib/test/gen_fsm_SUITE.erl +++ b/lib/stdlib/test/gen_fsm_SUITE.erl @@ -281,21 +281,12 @@ start12(Config) when is_list(Config) -> %% Check that time outs in calls work abnormal1(suite) -> []; abnormal1(Config) when is_list(Config) -> - ?line {ok, _Pid} = - gen_fsm:start({local, my_fsm}, gen_fsm_SUITE, [], []), + {ok, _Pid} = gen_fsm:start({local, my_fsm}, gen_fsm_SUITE, [], []), %% timeout call. - case os:type() of - vxworks -> - %% timeout call for VxWorks must be in 16ms increments. - ?line delayed = gen_fsm:sync_send_event(my_fsm, {delayed_answer,1}, 17), - ?line {'EXIT',{timeout,_}} = - (catch gen_fsm:sync_send_event(my_fsm, {delayed_answer,17}, 1)); - _ -> - ?line delayed = gen_fsm:sync_send_event(my_fsm, {delayed_answer,1}, 100), - ?line {'EXIT',{timeout,_}} = - (catch gen_fsm:sync_send_event(my_fsm, {delayed_answer,10}, 1)) - end, + delayed = gen_fsm:sync_send_event(my_fsm, {delayed_answer,1}, 100), + {'EXIT',{timeout,_}} = + (catch gen_fsm:sync_send_event(my_fsm, {delayed_answer,10}, 1)), test_server:messages_get(), ok. diff --git a/lib/stdlib/test/gen_server_SUITE.erl b/lib/stdlib/test/gen_server_SUITE.erl index c930d90e1c..dffeadb423 100644 --- a/lib/stdlib/test/gen_server_SUITE.erl +++ b/lib/stdlib/test/gen_server_SUITE.erl @@ -231,14 +231,6 @@ start(Config) when is_list(Config) -> end, test_server:messages_get(), - %% Must wait for all error messages before going to next test. - %% (otherwise it interferes too much with real time characteristics). - case os:type() of - vxworks -> - receive after 5000 -> ok end; - _ -> - ok - end, process_flag(trap_exit, OldFl), ok. @@ -1054,8 +1046,9 @@ call_with_huge_message_queue(Config) when is_list(Config) -> io:format("Time for empty message queue: ~p", [Time]), io:format("Time for huge message queue: ~p", [NewTime]), + IsCover = test_server:is_cover(), case (NewTime+1) / (Time+1) of - Q when Q < 10 -> + Q when Q < 10; IsCover -> ok; Q -> io:format("Q = ~p", [Q]), diff --git a/lib/stdlib/test/id_transform_SUITE.erl b/lib/stdlib/test/id_transform_SUITE.erl index e1972a100e..ee97ffe7b3 100644 --- a/lib/stdlib/test/id_transform_SUITE.erl +++ b/lib/stdlib/test/id_transform_SUITE.erl @@ -1,7 +1,7 @@ %% %% %CopyrightBegin% %% -%% Copyright Ericsson AB 2003-2011. All Rights Reserved. +%% Copyright Ericsson AB 2003-2012. All Rights Reserved. %% %% The contents of this file are subject to the Erlang Public License, %% Version 1.1, (the "License"); you may not use this file except in @@ -26,7 +26,7 @@ id_transform/1]). -export([check/2,check2/1,g/0,f/1,t/1,t1/1,t2/1,t3/1,t4/1, - t5/1,t6/1,apa/1,new_fun/0]). + t5/1,apa/1,new_fun/0]). % Serves as test... -hej(hopp). @@ -61,7 +61,7 @@ id_transform(Config) when is_list(Config) -> ?line {module,erl_id_trans}=code:load_binary(erl_id_trans,File,Bin), ?line case test_server:purify_is_running() of false -> - Dog = ?t:timetrap(?t:hours(1)), + Dog = ct:timetrap(?t:hours(1)), ?line Res = run_in_test_suite(), ?t:timetrap_cancel(Dog), Res; @@ -388,8 +388,6 @@ t3(A) when is_tuple(A) or is_tuple(A) -> is_tuple; t3(A) when record(A, apa) -> foo; -t3(A) when {erlang,is_record}(A, apa) -> - foo; t3(A) when erlang:is_record(A, apa) -> foo; t3(A) when is_record(A, apa) -> @@ -397,13 +395,10 @@ t3(A) when is_record(A, apa) -> t3(A) when record({apa}, apa) -> {A,foo}. -t4(_) when {erlang,is_record}({apa}, apa) -> - foo. - -t5(A) when erlang:is_record({apa}, apa) -> +t4(A) when erlang:is_record({apa}, apa) -> {A,foo}. -t6(A) when is_record({apa}, apa) -> +t5(A) when is_record({apa}, apa) -> {A,foo}. -record(apa2,{a=a,b=foo:bar()}). diff --git a/lib/stdlib/test/io_SUITE.erl b/lib/stdlib/test/io_SUITE.erl index bb02a879c2..74fcdcc7d2 100644 --- a/lib/stdlib/test/io_SUITE.erl +++ b/lib/stdlib/test/io_SUITE.erl @@ -27,7 +27,8 @@ otp_6282/1, otp_6354/1, otp_6495/1, otp_6517/1, otp_6502/1, manpage/1, otp_6708/1, otp_7084/1, otp_7421/1, io_lib_collect_line_3_wb/1, cr_whitespace_in_string/1, - io_fread_newlines/1, otp_8989/1, io_lib_fread_literal/1]). + io_fread_newlines/1, otp_8989/1, io_lib_fread_literal/1, + io_lib_print_binary_depth_one/1]). %-define(debug, true). @@ -62,7 +63,8 @@ all() -> otp_6282, otp_6354, otp_6495, otp_6517, otp_6502, manpage, otp_6708, otp_7084, otp_7421, io_lib_collect_line_3_wb, cr_whitespace_in_string, - io_fread_newlines, otp_8989, io_lib_fread_literal]. + io_fread_newlines, otp_8989, io_lib_fread_literal, + io_lib_print_binary_depth_one]. groups() -> []. @@ -2021,3 +2023,14 @@ io_lib_fread_literal(Suite) when is_list(Suite) -> ?line {done,{error,{fread,input}},_} = io_lib:fread(C2, eof, " d"), ?line {done,{ok,[]},[]} = io_lib:fread(C2, "d\n", " d"), ok. + +io_lib_print_binary_depth_one(doc) -> + "Test binaries printed with a depth of one behave correctly"; +io_lib_print_binary_depth_one(Suite) when is_list(Suite) -> + ?line "<<>>" = fmt("~W", [<<>>, 1]), + ?line "<<>>" = fmt("~P", [<<>>, 1]), + ?line "<<...>>" = fmt("~W", [<<1>>, 1]), + ?line "<<...>>" = fmt("~P", [<<1>>, 1]), + ?line "<<...>>" = fmt("~W", [<<1:7>>, 1]), + ?line "<<...>>" = fmt("~P", [<<1:7>>, 1]), + ok. diff --git a/lib/stdlib/test/proc_lib_SUITE.erl b/lib/stdlib/test/proc_lib_SUITE.erl index c95089117c..8dca69bac4 100644 --- a/lib/stdlib/test/proc_lib_SUITE.erl +++ b/lib/stdlib/test/proc_lib_SUITE.erl @@ -1,7 +1,7 @@ %% %% %CopyrightBegin% %% -%% Copyright Ericsson AB 1996-2011. All Rights Reserved. +%% Copyright Ericsson AB 1996-2012. All Rights Reserved. %% %% The contents of this file are subject to the Erlang Public License, %% Version 1.1, (the "License"); you may not use this file except in @@ -28,7 +28,7 @@ crash/1, sync_start_nolink/1, sync_start_link/1, spawn_opt/1, sp1/0, sp2/0, sp3/1, sp4/2, sp5/1, hibernate/1]). --export([ otp_6345/1]). +-export([ otp_6345/1, init_dont_hang/1]). -export([hib_loop/1, awaken/1]). @@ -36,7 +36,7 @@ handle_event/2, handle_call/2, handle_info/2, terminate/2]). --export([otp_6345_init/1]). +-export([otp_6345_init/1, init_dont_hang_init/1]). -ifdef(STANDALONE). @@ -52,7 +52,7 @@ all() -> {group, tickets}]. groups() -> - [{tickets, [], [otp_6345]}, + [{tickets, [], [otp_6345, init_dont_hang]}, {sync_start, [], [sync_start_nolink, sync_start_link]}]. init_per_suite(Config) -> @@ -343,6 +343,29 @@ otp_6345_loop() -> otp_6345_loop() end. +%% OTP-9803 +init_dont_hang(suite) -> + []; +init_dont_hang(doc) -> + ["Check that proc_lib:start don't hang if spawned process crashes before proc_lib:init_ack/2"]; +init_dont_hang(Config) when is_list(Config) -> + %% Start should behave as start_link + process_flag(trap_exit, true), + StartLinkRes = proc_lib:start_link(?MODULE, init_dont_hang_init, [self()]), + try + StartLinkRes = proc_lib:start(?MODULE, init_dont_hang_init, [self()], 1000), + StartLinkRes = proc_lib:start(?MODULE, init_dont_hang_init, [self()], 1000, []), + ok + catch _:Error -> + io:format("Error ~p /= ~p ~n",[erlang:get_stacktrace(), StartLinkRes]), + exit(Error) + end. + +init_dont_hang_init(Parent) -> + 1 = 2. + + + %%----------------------------------------------------------------- %% The error_logger handler used. %%----------------------------------------------------------------- diff --git a/lib/stdlib/test/qlc_SUITE.erl b/lib/stdlib/test/qlc_SUITE.erl index 192268f90e..e3090e4a47 100644 --- a/lib/stdlib/test/qlc_SUITE.erl +++ b/lib/stdlib/test/qlc_SUITE.erl @@ -2969,15 +2969,6 @@ lookup1(Config) when is_list(Config) -> [3] = lookup_keys(Q) end, [{1,a},{3,3}])">>, - {cres, - <<"A = 3, - etsc(fun(E) -> - Q = qlc:q([X || X <- ets:table(E), A =:= {erlang,element}(1, X)]), - [{3,3}] = qlc:e(Q), - [3] = lookup_keys(Q) - end, [{1,a},{3,3}])">>, - {warnings,[{3,erl_lint,deprecated_tuple_fun}]}}, - <<"etsc(fun(E) -> A = 3, Q = qlc:q([X || X <- ets:table(E), @@ -3442,14 +3433,6 @@ lookup2(Config) when is_list(Config) -> [r] = lookup_keys(Q) end, [{keypos,1}], [#r{}])">>, {cres, - <<"etsc(fun(E) -> - Q = qlc:q([element(1, X) || X <- ets:table(E), - {erlang,is_record}(X, r, 2)]), - [r] = qlc:e(Q), - [r] = lookup_keys(Q) - end, [{keypos,1}], [#r{}])">>, - {warnings,[{4,erl_lint,deprecated_tuple_fun}]}}, - {cres, <<"etsc(fun(E) -> Q = qlc:q([element(1, X) || X <- ets:table(E), record(X, r)]), @@ -3468,15 +3451,7 @@ lookup2(Config) when is_list(Config) -> is_record(X, r)]), [r] = qlc:e(Q), [r] = lookup_keys(Q) - end, [{keypos,1}], [#r{}])">>, - {cres, - <<"etsc(fun(E) -> - Q = qlc:q([element(1, X) || X <- ets:table(E), - {erlang,is_record}(X, r)]), - [r] = qlc:e(Q), - [r] = lookup_keys(Q) - end, [{keypos,1}], [#r{}])">>, - {warnings,[{4,erl_lint,deprecated_tuple_fun}]}} + end, [{keypos,1}], [#r{}])">> ], ?line run(Config, <<"-record(r, {a}).\n">>, TsR), diff --git a/lib/stdlib/test/re_SUITE.erl b/lib/stdlib/test/re_SUITE.erl index a542745e67..8ee0a13f4c 100644 --- a/lib/stdlib/test/re_SUITE.erl +++ b/lib/stdlib/test/re_SUITE.erl @@ -328,6 +328,12 @@ replace_return(Config) when is_list(Config) -> ?line <<"iXk">> = re:replace("abcdefghijk","(.)(.)(.)(.)(.)(.)(.)(.)(.)(.)","\\9X",[{return,binary}]), ?line <<"jXk">> = re:replace("abcdefghijk","(.)(.)(.)(.)(.)(.)(.)(.)(.)(.)","\\10X",[{return,binary}]), ?line <<"Xk">> = re:replace("abcdefghijk","(.)(.)(.)(.)(.)(.)(.)(.)(.)(.)","\\11X",[{return,binary}]), + ?line <<"9X1">> = re:replace("12345678901","(.)(.)(.)(.)(.)(.)(.)(.)(.)(.)","\\g9X",[{return,binary}]), + ?line <<"0X1">> = re:replace("12345678901","(.)(.)(.)(.)(.)(.)(.)(.)(.)(.)","\\g10X",[{return,binary}]), + ?line <<"X1">> = re:replace("12345678901","(.)(.)(.)(.)(.)(.)(.)(.)(.)(.)","\\g11X",[{return,binary}]), + ?line <<"971">> = re:replace("12345678901","(.)(.)(.)(.)(.)(.)(.)(.)(.)(.)","\\g{9}7",[{return,binary}]), + ?line <<"071">> = re:replace("12345678901","(.)(.)(.)(.)(.)(.)(.)(.)(.)(.)","\\g{10}7",[{return,binary}]), + ?line <<"71">> = re:replace("12345678901","(.)(.)(.)(.)(.)(.)(.)(.)(.)(.)","\\g{11}7",[{return,binary}]), ?line "a\x{400}bcX" = re:replace("a\x{400}bcd","d","X",[global,{return,list},unicode]), ?line <<"a",208,128,"bcX">> = re:replace("a\x{400}bcd","d","X",[global,{return,binary},unicode]), ?line "a\x{400}bcd" = re:replace("a\x{400}bcd","Z","X",[global,{return,list},unicode]), diff --git a/lib/stdlib/test/sets_SUITE.erl b/lib/stdlib/test/sets_SUITE.erl index f284276bd7..e2bcdd18ce 100644 --- a/lib/stdlib/test/sets_SUITE.erl +++ b/lib/stdlib/test/sets_SUITE.erl @@ -35,7 +35,7 @@ -import(lists, [foldl/3,reverse/1]). init_per_testcase(_Case, Config) -> - ?line Dog = ?t:timetrap(?t:minutes(5)), + Dog = ?t:timetrap(?t:minutes(5)), [{watchdog,Dog}|Config]. end_per_testcase(_Case, Config) -> @@ -70,65 +70,65 @@ create(Config) when is_list(Config) -> test_all(fun create_1/1). create_1(M) -> - ?line S0 = M:empty(), - ?line [] = M:to_list(S0), - ?line 0 = M:size(S0), - ?line true = M:is_empty(S0), + S0 = M(empty, []), + [] = M(to_list, S0), + 0 = M(size, S0), + true = M(is_empty, S0), E = make_ref(), - ?line One = M:singleton(E), - ?line 1 = M:size(One), - ?line false = M:is_empty(One), - [E] = M:to_list(One), + One = M(singleton, E), + 1 = M(size, One), + false = M(is_empty, One), + [E] = M(to_list, One), S0. add_element(Config) when is_list(Config) -> test_all([{0,132},{253,258},{510,514}], fun add_element_1/2). add_element_1(List, M) -> - ?line S = M:from_list(List), - ?line SortedSet = lists:usort(List), - ?line SortedSet = lists:sort(M:to_list(S)), + S = M(from_list, List), + SortedSet = lists:usort(List), + SortedSet = lists:sort(M(to_list, S)), %% Make sure that we get the same result by inserting %% elements one at the time. - ?line S2 = foldl(fun(El, Set) -> M:add_element(El, Set) end, - M:empty(), List), - ?line true = M:equal(S, S2), + S2 = foldl(fun(El, Set) -> M(add_element, {El,Set}) end, + M(empty, []), List), + true = M(equal, {S,S2}), %% Insert elements, randomly delete inserted elements, %% and re-inserted all deleted elements at the end. - ?line S3 = add_element_del(List, M, M:empty(), [], []), - ?line true = M:equal(S2, S3), - ?line true = M:equal(S, S3), + S3 = add_element_del(List, M, M(empty, []), [], []), + true = M(equal, {S2,S3}), + true = M(equal, {S,S3}), S. add_element_del([H|T], M, S, Del, []) -> - add_element_del(T, M, M:add_element(H, S), Del, [H]); + add_element_del(T, M, M(add_element, {H,S}), Del, [H]); add_element_del([H|T], M, S0, Del, Inserted) -> - S1 = M:add_element(H, S0), + S1 = M(add_element, {H,S0}), case random:uniform(3) of 1 -> OldEl = lists:nth(random:uniform(length(Inserted)), Inserted), - S = M:del_element(OldEl, S1), + S = M(del_element, {OldEl,S1}), add_element_del(T, M, S, [OldEl|Del], [H|Inserted]); _ -> add_element_del(T, M, S1, Del, [H|Inserted]) end; add_element_del([], M, S, Del, _) -> - M:union(S, M:from_list(Del)). + M(union, {S,M(from_list, Del)}). del_element(Config) when is_list(Config) -> test_all([{0,132},{253,258},{510,514},{1022,1026}], fun del_element_1/2). del_element_1(List, M) -> - ?line S0 = M:from_list(List), - ?line Empty = foldl(fun(El, Set) -> M:del_element(El, Set) end, S0, List), - ?line Empty = M:empty(), - ?line M:is_empty(Empty), - ?line S1 = foldl(fun(El, Set) -> - M:add_element(El, Set) - end, S0, reverse(List)), - ?line true = M:equal(S0, S1), + S0 = M(from_list, List), + Empty = foldl(fun(El, Set) -> M(del_element, {El,Set}) end, S0, List), + Empty = M(empty, []), + true = M(is_empty, Empty), + S1 = foldl(fun(El, Set) -> + M(add_element, {El,Set}) + end, S0, reverse(List)), + true = M(equal, {S0,S1}), S1. subtract(Config) when is_list(Config) -> @@ -138,23 +138,23 @@ subtract(Config) when is_list(Config) -> test_all([{2,69},{126,130},{253,258},511,512,{1023,1030}], fun subtract_1/2). subtract_empty(M) -> - ?line Empty = M:empty(), - ?line true = M:is_empty(M:subtract(Empty, Empty)), - M:subtract(Empty, Empty). + Empty = M(empty, []), + true = M(is_empty, M(subtract, {Empty,Empty})), + M(subtract, {Empty,Empty}). subtract_1(List, M) -> - ?line S0 = M:from_list(List), - ?line Empty = M:empty(), + S0 = M(from_list, List), + Empty = M(empty, []), %% Trivial cases. - ?line true = M:is_empty(M:subtract(Empty, S0)), - ?line true = M:equal(S0, M:subtract(S0, Empty)), + true = M(is_empty, M(subtract, {Empty,S0})), + true = M(equal, {S0,M(subtract, {S0,Empty})}), %% Not so trivial. - ?line subtract_check(List, mutate_some(remove_some(List, 0.4)), M), - ?line subtract_check(List, rnd_list(length(List) div 2 + 5), M), - ?line subtract_check(List, rnd_list(length(List) div 7 + 9), M), - ?line subtract_check(List, mutate_some(List), M). + subtract_check(List, mutate_some(remove_some(List, 0.4)), M), + subtract_check(List, rnd_list(length(List) div 2 + 5), M), + subtract_check(List, rnd_list(length(List) div 7 + 9), M), + subtract_check(List, mutate_some(List), M). subtract_check(A, B, M) -> one_subtract_check(B, A, M), @@ -163,12 +163,12 @@ subtract_check(A, B, M) -> one_subtract_check(A, B, M) -> ASorted = lists:usort(A), BSorted = lists:usort(B), - ASet = M:from_list(A), - BSet = M:from_list(B), - DiffSet = M:subtract(ASet, BSet), + ASet = M(from_list, A), + BSet = M(from_list, B), + DiffSet = M(subtract, {ASet,BSet}), Diff = ASorted -- BSorted, - true = M:equal(DiffSet, M:from_list(Diff)), - Diff = lists:sort(M:to_list(DiffSet)), + true = M(equal, {DiffSet,M(from_list, Diff)}), + Diff = lists:sort(M(to_list, DiffSet)), DiffSet. intersection(Config) when is_list(Config) -> @@ -176,60 +176,60 @@ intersection(Config) when is_list(Config) -> test_all([{1,65},{126,130},{253,259},{499,513},{1023,1025}], fun intersection_1/2). intersection_1(List, M) -> - ?line S0 = M:from_list(List), + S0 = M(from_list, List), %% Intersection with self. - ?line true = M:equal(S0, M:intersection(S0, S0)), - ?line true = M:equal(S0, M:intersection([S0,S0])), - ?line true = M:equal(S0, M:intersection([S0,S0,S0])), - ?line true = M:equal(S0, M:intersection([S0])), + true = M(equal, {S0,M(intersection, {S0,S0})}), + true = M(equal, {S0,M(intersection, [S0,S0])}), + true = M(equal, {S0,M(intersection, [S0,S0,S0])}), + true = M(equal, {S0,M(intersection, [S0])}), %% Intersection with empty. - ?line Empty = M:empty(), - ?line true = M:equal(Empty, M:intersection(S0, Empty)), - ?line true = M:equal(Empty, M:intersection([S0,Empty,S0,Empty])), + Empty = M(empty, []), + true = M(equal, {Empty,M(intersection, {S0,Empty})}), + true = M(equal, {Empty,M(intersection, [S0,Empty,S0,Empty])}), %% The intersection of no sets is undefined. - ?line {'EXIT',_} = (catch M:intersection([])), + {'EXIT',_} = (catch M(intersection, [])), %% Disjoint sets. - ?line Disjoint = [{El} || El <- List], - ?line DisjointSet = M:from_list(Disjoint), - ?line M:is_empty(M:intersection(S0, DisjointSet)), + Disjoint = [{El} || El <- List], + DisjointSet = M(from_list, Disjoint), + true = M(is_empty, M(intersection, {S0,DisjointSet})), %% Disjoint, different sizes. - ?line M:is_empty(M:intersection(S0, M:from_list(remove_some(Disjoint, 0.3)))), - ?line M:is_empty(M:intersection(S0, M:from_list(remove_some(Disjoint, 0.7)))), - ?line M:is_empty(M:intersection(S0, M:from_list(remove_some(Disjoint, 0.9)))), - ?line M:is_empty(M:intersection(M:from_list(remove_some(List, 0.3)), DisjointSet)), - ?line M:is_empty(M:intersection(M:from_list(remove_some(List, 0.5)), DisjointSet)), - ?line M:is_empty(M:intersection(M:from_list(remove_some(List, 0.9)), DisjointSet)), + [begin + SomeRemoved = M(from_list, remove_some(Disjoint, HowMuch)), + true = M(is_empty, M(intersection, {S0,SomeRemoved})), + MoreRemoved = M(from_list, remove_some(List, HowMuch)), + true = M(is_empty, M(intersection, {MoreRemoved,DisjointSet})) + end || HowMuch <- [0.3,0.5,0.7,0.9]], %% Partial overlap (one or more elements in result set). %% The sets have almost the same size. (Almost because a duplicated %% element in the original list could be mutated and not mutated %% at the same time.) - ?line PartialOverlap = mutate_some(List, []), - ?line IntersectionSet = check_intersection(List, PartialOverlap, M), - ?line false = M:is_empty(IntersectionSet), + PartialOverlap = mutate_some(List, []), + IntersectionSet = check_intersection(List, PartialOverlap, M), + false = M(is_empty, IntersectionSet), %% Partial overlap, different set sizes. (Intersection possibly empty.) - ?line check_intersection(List, remove_some(PartialOverlap, 0.1), M), - ?line check_intersection(List, remove_some(PartialOverlap, 0.3), M), - ?line check_intersection(List, remove_some(PartialOverlap, 0.5), M), - ?line check_intersection(List, remove_some(PartialOverlap, 0.7), M), - ?line check_intersection(List, remove_some(PartialOverlap, 0.9), M), + check_intersection(List, remove_some(PartialOverlap, 0.1), M), + check_intersection(List, remove_some(PartialOverlap, 0.3), M), + check_intersection(List, remove_some(PartialOverlap, 0.5), M), + check_intersection(List, remove_some(PartialOverlap, 0.7), M), + check_intersection(List, remove_some(PartialOverlap, 0.9), M), IntersectionSet. check_intersection(Orig, Mutated, M) -> - OrigSet = M:from_list(Orig), - MutatedSet = M:from_list(Mutated), + OrigSet = M(from_list, Orig), + MutatedSet = M(from_list, Mutated), Intersection = [El || El <- Mutated, not is_tuple(El)], SortedIntersection = lists:usort(Intersection), - IntersectionSet = M:intersection(OrigSet, MutatedSet), - true = M:equal(IntersectionSet, M:from_list(SortedIntersection)), - SortedIntersection = lists:sort(M:to_list(IntersectionSet)), + IntersectionSet = M(intersection, {OrigSet,MutatedSet}), + true = M(equal, {IntersectionSet,M(from_list, SortedIntersection)}), + SortedIntersection = lists:sort(M(to_list, IntersectionSet)), IntersectionSet. @@ -239,63 +239,63 @@ union(Config) when is_list(Config) -> test_all([{1,71},{125,129},{254,259},{510,513},{1023,1025}], fun union_1/2). union_1(List, M) -> - ?line S = M:from_list(List), + S = M(from_list, List), %% Union with self and empty. - ?line Empty = M:empty(), - ?line true = M:equal(S, M:union(S, S)), - ?line true = M:equal(S, M:union([S,S])), - ?line true = M:equal(S, M:union([S,S,Empty])), - ?line true = M:equal(S, M:union([S,Empty,S])), - ?line true = M:equal(S, M:union(S, Empty)), - ?line true = M:equal(S, M:union([S])), - ?line true = M:is_empty(M:union([])), + Empty = M(empty, []), + true = M(equal, {S,M(union, {S,S})}), + true = M(equal, {S,M(union, [S,S])}), + true = M(equal, {S,M(union, [S,S,Empty])}), + true = M(equal, {S,M(union, [S,Empty,S])}), + true = M(equal, {S,M(union, {S,Empty})}), + true = M(equal, {S,M(union, [S])}), + true = M(is_empty, M(union, [])), %% Partial overlap. - ?line check_union(List, remove_some(mutate_some(List), 0.9), M), - ?line check_union(List, remove_some(mutate_some(List), 0.7), M), - ?line check_union(List, remove_some(mutate_some(List), 0.5), M), - ?line check_union(List, remove_some(mutate_some(List), 0.3), M), - ?line check_union(List, remove_some(mutate_some(List), 0.1), M), - - ?line check_union(List, mutate_some(remove_some(List, 0.9)), M), - ?line check_union(List, mutate_some(remove_some(List, 0.7)), M), - ?line check_union(List, mutate_some(remove_some(List, 0.5)), M), - ?line check_union(List, mutate_some(remove_some(List, 0.3)), M), - ?line check_union(List, mutate_some(remove_some(List, 0.1)), M). + check_union(List, remove_some(mutate_some(List), 0.9), M), + check_union(List, remove_some(mutate_some(List), 0.7), M), + check_union(List, remove_some(mutate_some(List), 0.5), M), + check_union(List, remove_some(mutate_some(List), 0.3), M), + check_union(List, remove_some(mutate_some(List), 0.1), M), + + check_union(List, mutate_some(remove_some(List, 0.9)), M), + check_union(List, mutate_some(remove_some(List, 0.7)), M), + check_union(List, mutate_some(remove_some(List, 0.5)), M), + check_union(List, mutate_some(remove_some(List, 0.3)), M), + check_union(List, mutate_some(remove_some(List, 0.1)), M). check_union(Orig, Other, M) -> - OrigSet = M:from_list(Orig), - OtherSet = M:from_list(Other), + OrigSet = M(from_list, Orig), + OtherSet = M(from_list, Other), Union = Orig++Other, SortedUnion = lists:usort(Union), - UnionSet = M:union(OrigSet, OtherSet), - SortedUnion = lists:sort(M:to_list(UnionSet)), - M:equal(UnionSet, M:from_list(Union)), + UnionSet = M(union, {OrigSet,OtherSet}), + SortedUnion = lists:sort(M(to_list, UnionSet)), + M(equal, {UnionSet,M(from_list, Union)}), UnionSet. is_subset(Config) when is_list(Config) -> test_all([{1,132},{253,270},{299,311}], fun is_subset_1/2). is_subset_1(List, M) -> - ?line S = M:from_list(List), - ?line Empty = M:empty(), + S = M(from_list, List), + Empty = M(empty, []), %% Subset of empty and self. - ?line true = M:is_subset(Empty, Empty), - ?line true = M:is_subset(Empty, S), - ?line false = M:is_subset(S, Empty), - ?line true = M:is_subset(S, S), + true = M(is_subset, {Empty,Empty}), + true = M(is_subset, {Empty,S}), + false = M(is_subset, {S,Empty}), + true = M(is_subset, {S,S}), %% Other cases. - Res = [?line false = M:is_subset(M:singleton(make_ref()), S), - ?line true = M:is_subset(M:singleton(hd(List)), S), - ?line true = check_subset(remove_some(List, 0.1), List, M), - ?line true = check_subset(remove_some(List, 0.5), List, M), - ?line true = check_subset(remove_some(List, 0.9), List, M), - ?line check_subset(mutate_some(List), List, M), - ?line check_subset(rnd_list(length(List) div 2 + 5), List, M), - ?line subtract_check(List, rnd_list(length(List) div 7 + 9), M) + Res = [false = M(is_subset, {M(singleton, make_ref()),S}), + true = M(is_subset, {M(singleton, hd(List)),S}), + true = check_subset(remove_some(List, 0.1), List, M), + true = check_subset(remove_some(List, 0.5), List, M), + true = check_subset(remove_some(List, 0.9), List, M), + check_subset(mutate_some(List), List, M), + check_subset(rnd_list(length(List) div 2 + 5), List, M), + subtract_check(List, rnd_list(length(List) div 7 + 9), M) ], res_to_set(Res, M, 0, []). @@ -304,12 +304,12 @@ check_subset(X, Y, M) -> check_one_subset(X, Y, M). check_one_subset(X, Y, M) -> - XSet = M:from_list(X), - YSet = M:from_list(Y), + XSet = M(from_list, X), + YSet = M(from_list, Y), SortedX = lists:usort(X), SortedY = lists:usort(Y), IsSubSet = length(SortedY--SortedX) =:= length(SortedY) - length(SortedX), - IsSubSet = M:is_subset(XSet, YSet), + IsSubSet = M(is_subset, {XSet,YSet}), IsSubSet. %% Encode all test results as a set to return. @@ -317,54 +317,54 @@ res_to_set([true|T], M, I, Acc) -> res_to_set(T, M, I+1, [I|Acc]); res_to_set([_|T], M, I, Acc) -> res_to_set(T, M, I+1, Acc); -res_to_set([], M, _, Acc) -> M:from_list(Acc). +res_to_set([], M, _, Acc) -> M(from_list, Acc). is_set(Config) when is_list(Config) -> %% is_set/1 is tested in the other test cases when its argument %% is a set. Here test some arguments that makes it return false. - ?line false = gb_sets:is_set([a,b]), - ?line false = gb_sets:is_set({a,very,bad,tuple}), + false = gb_sets:is_set([a,b]), + false = gb_sets:is_set({a,very,bad,tuple}), - ?line false = sets:is_set([a,b]), - ?line false = sets:is_set({a,very,bad,tuple}), + false = sets:is_set([a,b]), + false = sets:is_set({a,very,bad,tuple}), - ?line false = ordsets:is_set([b,a]), - ?line false = ordsets:is_set({bad,tuple}), + false = ordsets:is_set([b,a]), + false = ordsets:is_set({bad,tuple}), %% Now test values that are known to be bad for all set representations. test_all(fun is_set_1/1). is_set_1(M) -> - ?line false = M:is_set(self()), - ?line false = M:is_set(blurf), - ?line false = M:is_set(make_ref()), - ?line false = M:is_set(<<1,2,3>>), - ?line false = M:is_set(42), - ?line false = M:is_set(math:pi()), - ?line false = M:is_set({}), - M:empty(). + false = M(is_set, self()), + false = M(is_set, blurf), + false = M(is_set, make_ref()), + false = M(is_set, <<1,2,3>>), + false = M(is_set, 42), + false = M(is_set, math:pi()), + false = M(is_set, {}), + M(empty, []). fold(Config) when is_list(Config) -> test_all([{0,71},{125,129},{254,259},{510,513},{1023,1025},{9999,10001}], fun fold_1/2). fold_1(List, M) -> - ?line S = M:from_list(List), - ?line L = M:fold(fun(E, A) -> [E|A] end, [], S), - ?line true = lists:sort(L) =:= lists:usort(List), - M:empty(). + S = M(from_list, List), + L = M(fold, {fun(E, A) -> [E|A] end,[],S}), + true = lists:sort(L) =:= lists:usort(List), + M(empty, []). filter(Config) when is_list(Config) -> test_all([{0,69},{126,130},{254,259},{510,513},{1023,1025},{7999,8000}], fun filter_1/2). filter_1(List, M) -> - ?line S = M:from_list(List), + S = M(from_list, List), IsNumber = fun(X) -> is_number(X) end, - ?line M:equal(M:from_list(lists:filter(IsNumber, List)), - M:filter(IsNumber, S)), - ?line M:filter(fun(X) -> is_atom(X) end, S). + M(equal, {M(from_list, lists:filter(IsNumber, List)), + M(filter, {IsNumber,S})}), + M(filter, {fun(X) -> is_atom(X) end,S}). %%% %%% Test specifics for gb_sets. @@ -375,26 +375,26 @@ take_smallest(Config) when is_list(Config) -> fun take_smallest_1/2). take_smallest_1(List, M) -> - case M:module() of + case M(module, []) of gb_sets -> take_smallest_2(List, M); _ -> ok end, - M:empty(). + M(empty, []). take_smallest_2(List0, M) -> - ?line List = lists:usort(List0), - ?line S = M:from_list(List0), + List = lists:usort(List0), + S = M(from_list, List0), take_smallest_3(S, List, M). take_smallest_3(S0, List0, M) -> - case M:is_empty(S0) of + case M(is_empty, S0) of true -> ok; false -> - ?line Smallest = hd(List0), - ?line Smallest = gb_sets:smallest(S0), - ?line {Smallest,S} = gb_sets:take_smallest(S0), - ?line List = tl(List0), - ?line true = gb_sets:to_list(S) =:= List, + Smallest = hd(List0), + Smallest = gb_sets:smallest(S0), + {Smallest,S} = gb_sets:take_smallest(S0), + List = tl(List0), + true = gb_sets:to_list(S) =:= List, take_smallest_3(S, List, M) end. @@ -403,26 +403,26 @@ take_largest(Config) when is_list(Config) -> fun take_largest_1/2). take_largest_1(List, M) -> - case M:module() of + case M(module, []) of gb_sets -> take_largest_2(List, M); _ -> ok end, - M:empty(). + M(empty, []). take_largest_2(List0, M) -> - ?line List = reverse(lists:usort(List0)), - ?line S = M:from_list(List0), + List = reverse(lists:usort(List0)), + S = M(from_list, List0), take_largest_3(S, List, M). take_largest_3(S0, List0, M) -> - case M:is_empty(S0) of + case M(is_empty, S0) of true -> ok; false -> - ?line Largest = hd(List0), - ?line Largest = gb_sets:largest(S0), - ?line {Largest,S} = gb_sets:take_largest(S0), - ?line List = tl(List0), - ?line true = gb_sets:to_list(S) =:= reverse(List), + Largest = hd(List0), + Largest = gb_sets:largest(S0), + {Largest,S} = gb_sets:take_largest(S0), + List = tl(List0), + true = gb_sets:to_list(S) =:= reverse(List), take_largest_3(S, List, M) end. @@ -441,23 +441,23 @@ sets_mods() -> [Ordsets,Sets,Gb]. test_all(Tester) -> - ?line Res = [begin - random:seed(1, 2, 42), - S = Tester(M), - {M:size(S),lists:sort(M:to_list(S))} - end || M <- sets_mods()], - ?line all_same(Res). + Res = [begin + random:seed(1, 2, 42), + S = Tester(M), + {M(size, S),lists:sort(M(to_list, S))} + end || M <- sets_mods()], + all_same(Res). test_all([{Low,High}|T], Tester) -> test_all(lists:seq(Low, High)++T, Tester); test_all([Sz|T], Tester) when is_integer(Sz) -> List = rnd_list(Sz), - ?line Res = [begin + Res = [begin random:seed(19, 2, Sz), S = Tester(List, M), - {M:size(S),lists:sort(M:to_list(S))} + {M(size, S),lists:sort(M(to_list, S))} end || M <- sets_mods()], - ?line all_same(Res), + all_same(Res), test_all(T, Tester); test_all([], _) -> ok. diff --git a/lib/stdlib/test/sets_test_lib.erl b/lib/stdlib/test/sets_test_lib.erl index bdfb0d59d2..fd4ec2bac3 100644 --- a/lib/stdlib/test/sets_test_lib.erl +++ b/lib/stdlib/test/sets_test_lib.erl @@ -17,91 +17,89 @@ %% %CopyrightEnd% %% --module(sets_test_lib, [Mod,Equal]). - --export([module/0,equal/2,empty/0,from_list/1,to_list/1,singleton/1, - add_element/2,del_element/2,size/1,is_empty/1,is_set/1, - intersection/1,intersection/2,subtract/2, - union/1,union/2,is_subset/2,fold/3,filter/2]). - -module() -> - Mod. - -equal(X, Y) -> - Equal(X, Y). - -empty() -> - Mod:new(). - -from_list(L) -> - Mod:from_list(L). - -to_list(S) -> - Mod:to_list(S). +-module(sets_test_lib). + +-export([new/2]). + +new(Mod, Eq) -> + fun (add_element, {El,S}) -> add_element(Mod, El, S); + (del_element, {El,S}) -> del_element(Mod, El, S); + (empty, []) -> Mod:new(); + (equal, {S1,S2}) -> Eq(S1, S2); + (filter, {F,S}) -> filter(Mod, F, S); + (fold, {F,A,S}) -> fold(Mod, F, A, S); + (from_list, L) -> Mod:from_list(L); + (intersection, {S1,S2}) -> intersection(Mod, Eq, S1, S2); + (intersection, Ss) -> intersection(Mod, Eq, Ss); + (is_empty, S) -> is_empty(Mod, S); + (is_set, S) -> Mod:is_set(S); + (is_subset, {S,Set}) -> is_subset(Mod, Eq, S, Set); + (module, []) -> Mod; + (singleton, E) -> singleton(Mod, E); + (size, S) -> Mod:size(S); + (subtract, {S1,S2}) -> subtract(Mod, S1, S2); + (to_list, S) -> Mod:to_list(S); + (union, {S1,S2}) -> union(Mod, Eq, S1, S2); + (union, Ss) -> union(Mod, Eq, Ss) + end. -singleton(E) -> +singleton(Mod, E) -> case erlang:function_exported(Mod, singleton, 1) of true -> Mod:singleton(E); - false -> from_list([E]) + false -> Mod:from_list([E]) end. -add_element(El, S0) -> +add_element(Mod, El, S0) -> S = Mod:add_element(El, S0), true = Mod:is_element(El, S), - false = is_empty(S), + false = is_empty(Mod, S), true = Mod:is_set(S), S. -del_element(El, S0) -> +del_element(Mod, El, S0) -> S = Mod:del_element(El, S0), false = Mod:is_element(El, S), true = Mod:is_set(S), S. -size(S) -> - Mod:size(S). - -is_empty(S) -> +is_empty(Mod, S) -> true = Mod:is_set(S), case erlang:function_exported(Mod, is_empty, 1) of true -> Mod:is_empty(S); false -> Mod:size(S) == 0 end. -is_set(S) -> - Mod:is_set(S). - -intersection(S1, S2) -> +intersection(Mod, Equal, S1, S2) -> S = Mod:intersection(S1, S2), true = Equal(S, Mod:intersection(S2, S1)), - Disjoint = is_empty(S), + Disjoint = is_empty(Mod, S), Disjoint = Mod:is_disjoint(S1, S2), Disjoint = Mod:is_disjoint(S2, S1), S. -intersection(Ss) -> +intersection(Mod, Equal, Ss) -> S = Mod:intersection(Ss), true = Equal(S, Mod:intersection(lists:reverse(Ss))), S. -subtract(S1, S2) -> +subtract(Mod, S1, S2) -> S = Mod:subtract(S1, S2), true = Mod:is_set(S), true = Mod:size(S) =< Mod:size(S1), S. -union(S1, S2) -> +union(Mod, Equal, S1, S2) -> S = Mod:union(S1, S2), true = Equal(S, Mod:union(S2, S1)), true = Mod:is_set(S), S. -union(Ss) -> +union(Mod, Equal, Ss) -> S = Mod:union(Ss), true = Equal(S, Mod:union(lists:reverse(Ss))), S. -is_subset(S, Set) -> +is_subset(Mod, Equal, S, Set) -> case Mod:is_subset(S, Set) of false -> false; true -> @@ -115,10 +113,10 @@ is_subset(S, Set) -> true end. -fold(F, A, S) -> +fold(Mod, F, A, S) -> true = Mod:is_set(S), Mod:fold(F, A, S). -filter(F, S) -> +filter(Mod, F, S) -> true = Mod:is_set(S), Mod:filter(F, S). diff --git a/lib/stdlib/test/shell_SUITE.erl b/lib/stdlib/test/shell_SUITE.erl index 4b83e42ee0..d49416c150 100644 --- a/lib/stdlib/test/shell_SUITE.erl +++ b/lib/stdlib/test/shell_SUITE.erl @@ -817,9 +817,6 @@ otp_5916(Config) when is_list(Config) -> true = if is_record(#r1{},r1,3) -> true; true -> false end, false = if is_record(#r2{},r1,3) -> true; true -> false end, - true = if {erlang,is_record}(#r1{},r1,3) -> true; true -> false end, - false = if {erlang,is_record}(#r2{},r1,3) -> true; true -> false end, - ok.">>, [ok] = scan(C), ok. @@ -2282,12 +2279,6 @@ otp_5990(doc) -> otp_5990(suite) -> []; otp_5990(Config) when is_list(Config) -> ?line [true] = - scan(<<"rd(foo,{bar}), {erlang,is_record}(#foo{}, foo).">>), - ?line [3] = - scan(<<"rd(foo,{bar}), A = #foo{}, " - "{if {erlang,is_record}(A, foo) -> erlang; " - "true -> not_a_module end, length}([1,2,3]).">>), - ?line [true] = scan(<<"rd('OrdSet', {orddata = {},ordtype = type}), " "S = #'OrdSet'{ordtype = {}}, " "if tuple(S#'OrdSet'.ordtype) -> true; true -> false end.">>), diff --git a/lib/stdlib/test/stdlib.cover b/lib/stdlib/test/stdlib.cover index 61f4f064b9..e71be880cb 100644 --- a/lib/stdlib/test/stdlib.cover +++ b/lib/stdlib/test/stdlib.cover @@ -1,17 +1,2 @@ %% -*- erlang -*- {incl_app,stdlib,details}. - -{excl_mods,stdlib, - [erl_parse, - erl_eval, - ets, - filename, - gen_event, - gen_server, - gen, - lists, - io, - io_lib, - io_lib_format, - io_lib_pretty, - proc_lib]}. diff --git a/lib/stdlib/test/stdlib.spec.vxworks b/lib/stdlib/test/stdlib.spec.vxworks deleted file mode 100644 index ddc804b831..0000000000 --- a/lib/stdlib/test/stdlib.spec.vxworks +++ /dev/null @@ -1,8 +0,0 @@ -{topcase, {dir, "../stdlib_test"}}. -{skip,{dets_SUITE,"Not runnable VxWorks/NFS"}}. -{skip,{slave_SUITE,"VxWorks: slave nodes are not supported"}}. -{skip,{tar_SUITE,errors,"VxWorks filesystem too primitive"}}. -{skip,{tar_SUITE,create_long_names,"VxWorks names too short"}}. -{skip,{epp_SUITE,"Test not adopted to VxWorks"}}. -{skip,{select_SUITE,"Test too memory consuming for VxWorks"}}. -{skip,{beam_lib_SUITE,error,"All sections not present in stripped beam files"}}. diff --git a/lib/stdlib/test/supervisor_SUITE.erl b/lib/stdlib/test/supervisor_SUITE.erl index 767ae3d62c..569c66959e 100644 --- a/lib/stdlib/test/supervisor_SUITE.erl +++ b/lib/stdlib/test/supervisor_SUITE.erl @@ -1,7 +1,7 @@ %% %% %CopyrightBegin% %% -%% Copyright Ericsson AB 1996-2011. All Rights Reserved. +%% Copyright Ericsson AB 1996-2012. All Rights Reserved. %% %% The contents of this file are subject to the Erlang Public License, %% Version 1.1, (the "License"); you may not use this file except in @@ -46,6 +46,7 @@ temporary_normal/1, permanent_shutdown/1, transient_shutdown/1, temporary_shutdown/1, + faulty_application_shutdown/1, permanent_abnormal/1, transient_abnormal/1, temporary_abnormal/1, temporary_bystander/1]). @@ -98,7 +99,8 @@ groups() -> {normal_termination, [], [permanent_normal, transient_normal, temporary_normal]}, {shutdown_termination, [], - [permanent_shutdown, transient_shutdown, temporary_shutdown]}, + [permanent_shutdown, transient_shutdown, temporary_shutdown, + faulty_application_shutdown]}, {abnormal_termination, [], [permanent_abnormal, transient_abnormal, temporary_abnormal]}, @@ -659,6 +661,39 @@ temporary_shutdown(Config) when is_list(Config) -> [0,0,0,0] = get_child_counts(sup_test). %%------------------------------------------------------------------------- +%% Faulty application should shutdown and pass on errors +faulty_application_shutdown(Config) when is_list(Config) -> + + %% Set some paths + AppDir = filename:join(?config(data_dir, Config), "app_faulty"), + EbinDir = filename:join(AppDir, "ebin"), + + %% Start faulty app + code:add_patha(EbinDir), + + %% {error, + %% {{shutdown, + %% {failed_to_start_child, + %% app_faulty, + %% {undef, + %% [{an_undefined_module_with,an_undefined_function,[argument1,argument2], + %% []}, + %% {app_faulty_server,init,1, + %% [{file,"app_faulty/src/app_faulty_server.erl"},{line,16}]}, + %% {gen_server,init_it,6, + %% [{file,"gen_server.erl"},{line,304}]}, + %% {proc_lib,init_p_do_apply,3, + %% [{file,"proc_lib.erl"},{line,227}]}]}}}, + %% {app_faulty,start,[normal,[]]}}} + + {error, Error} = application:start(app_faulty), + {{shutdown, {failed_to_start_child,app_faulty,{undef, CallStack}}}, + {app_faulty,start,_}} = Error, + [{an_undefined_module_with,an_undefined_function,_,_}|_] = CallStack, + ok = application:unload(app_faulty), + ok. + +%%------------------------------------------------------------------------- %% A permanent child should always be restarted. permanent_abnormal(Config) when is_list(Config) -> {ok, SupPid} = start_link({ok, {{one_for_one, 2, 3600}, []}}), diff --git a/lib/stdlib/test/supervisor_SUITE_data/Makefile.src b/lib/stdlib/test/supervisor_SUITE_data/Makefile.src new file mode 100644 index 0000000000..dbc5729f47 --- /dev/null +++ b/lib/stdlib/test/supervisor_SUITE_data/Makefile.src @@ -0,0 +1,15 @@ +EFLAGS=+debug_info + +APP_FAULTY= \ + app_faulty/ebin/app_faulty_sup.@EMULATOR@ \ + app_faulty/ebin/app_faulty_server.@EMULATOR@ \ + app_faulty/ebin/app_faulty.@EMULATOR@ \ + +all: $(APP_FAULTY) + +app_faulty/ebin/app_faulty_server.@EMULATOR@: app_faulty/src/app_faulty_server.erl + erlc $(EFLAGS) -oapp_faulty/ebin app_faulty/src/app_faulty_server.erl +app_faulty/ebin/app_faulty_sup.@EMULATOR@: app_faulty/src/app_faulty_sup.erl + erlc $(EFLAGS) -oapp_faulty/ebin app_faulty/src/app_faulty_sup.erl +app_faulty/ebin/app_faulty.@EMULATOR@: app_faulty/src/app_faulty.erl + erlc $(EFLAGS) -oapp_faulty/ebin app_faulty/src/app_faulty.erl diff --git a/lib/stdlib/test/supervisor_SUITE_data/app_faulty/ebin/app_faulty.app b/lib/stdlib/test/supervisor_SUITE_data/app_faulty/ebin/app_faulty.app new file mode 100644 index 0000000000..d4ab07e485 --- /dev/null +++ b/lib/stdlib/test/supervisor_SUITE_data/app_faulty/ebin/app_faulty.app @@ -0,0 +1,10 @@ +{application, app_faulty, + [{description, "very simple example faulty application"}, + {id, "app_faulty"}, + {vsn, "1.0"}, + {modules, [app_faulty, app_faulty_sup, app_faulty_server]}, + {registered, [app_faulty]}, + {applications, [kernel, stdlib]}, + {env, [{var,val1}]}, + {mod, {app_faulty, []}} + ]}. diff --git a/lib/stdlib/test/supervisor_SUITE_data/app_faulty/src/app_faulty.erl b/lib/stdlib/test/supervisor_SUITE_data/app_faulty/src/app_faulty.erl new file mode 100644 index 0000000000..c65b411cd6 --- /dev/null +++ b/lib/stdlib/test/supervisor_SUITE_data/app_faulty/src/app_faulty.erl @@ -0,0 +1,17 @@ +-module(app_faulty). + +-behaviour(application). + +%% Application callbacks +-export([start/2, stop/1]). + +start(_Type, _StartArgs) -> + case app_faulty_sup:start_link() of + {ok, Pid} -> + {ok, Pid}; + Error -> + Error + end. + +stop(_State) -> + ok. diff --git a/lib/stdlib/test/supervisor_SUITE_data/app_faulty/src/app_faulty_server.erl b/lib/stdlib/test/supervisor_SUITE_data/app_faulty/src/app_faulty_server.erl new file mode 100644 index 0000000000..6628f92210 --- /dev/null +++ b/lib/stdlib/test/supervisor_SUITE_data/app_faulty/src/app_faulty_server.erl @@ -0,0 +1,32 @@ +-module(app_faulty_server). + +-behaviour(gen_server). + +%% API +-export([start_link/0]). + +%% gen_server callbacks +-export([init/1, handle_call/3, handle_cast/2, handle_info/2, + terminate/2, code_change/3]). + +start_link() -> + gen_server:start_link({local, ?MODULE}, ?MODULE, [], []). + +init([]) -> + an_undefined_module_with:an_undefined_function(argument1, argument2), + {ok, []}. + +handle_call(_Request, _From, State) -> + {reply, ok, State}. + +handle_cast(_Msg, State) -> + {noreply, State}. + +handle_info(_Info, State) -> + {noreply, State}. + +terminate(_Reason, _State) -> + ok. + +code_change(_OldVsn, State, _Extra) -> + {ok, State}. diff --git a/lib/stdlib/test/supervisor_SUITE_data/app_faulty/src/app_faulty_sup.erl b/lib/stdlib/test/supervisor_SUITE_data/app_faulty/src/app_faulty_sup.erl new file mode 100644 index 0000000000..8115a88809 --- /dev/null +++ b/lib/stdlib/test/supervisor_SUITE_data/app_faulty/src/app_faulty_sup.erl @@ -0,0 +1,17 @@ +-module(app_faulty_sup). + +-behaviour(supervisor). + +%% API +-export([start_link/0]). + +%% Supervisor callbacks +-export([init/1]). + +start_link() -> + supervisor:start_link(?MODULE, []). + +init([]) -> + AChild = {app_faulty,{app_faulty_server,start_link,[]}, + permanent,2000,worker,[app_faulty_server]}, + {ok,{{one_for_all,0,1}, [AChild]}}. diff --git a/lib/stdlib/test/sys_SUITE.erl b/lib/stdlib/test/sys_SUITE.erl index fe039e8bcc..b2e1d12b2a 100644 --- a/lib/stdlib/test/sys_SUITE.erl +++ b/lib/stdlib/test/sys_SUITE.erl @@ -56,70 +56,60 @@ end_per_group(_GroupName, Config) -> log(suite) -> []; log(Config) when is_list(Config) -> - ?line {ok,_Server} = start(), - ?line ok = sys:log(?server,true), - ?line {ok,-44} = public_call(44), - ?line ok = sys:log(?server,false), - ?line ok = sys:log(?server,print), - ?line stop(), + {ok,_Server} = start(), + ok = sys:log(?server,true), + {ok,-44} = public_call(44), + ok = sys:log(?server,false), + ok = sys:log(?server,print), + stop(), ok. log_to_file(suite) -> []; log_to_file(Config) when is_list(Config) -> TempName = test_server:temp_name(?config(priv_dir,Config) ++ "sys."), - ?line {ok,_Server} = start(), - ?line ok = sys:log_to_file(?server,TempName), - ?line {ok,-44} = public_call(44), - ?line ok = sys:log_to_file(?server,false), - ?line {ok,Fd} = file:open(TempName,[read]), - ?line Msg1 = io:get_line(Fd,''), - ?line Msg2 = io:get_line(Fd,''), - ?line file:close(Fd), - ?line lists:prefix("*DBG* sys_SUITE_server got call {req,44} from ",Msg1), - ?line lists:prefix("*DBG* sys_SUITE_server sent {ok,-44} to ",Msg2), - ?line stop(), + {ok,_Server} = start(), + ok = sys:log_to_file(?server,TempName), + {ok,-44} = public_call(44), + ok = sys:log_to_file(?server,false), + {ok,Fd} = file:open(TempName,[read]), + Msg1 = io:get_line(Fd,''), + Msg2 = io:get_line(Fd,''), + file:close(Fd), + lists:prefix("*DBG* sys_SUITE_server got call {req,44} from ",Msg1), + lists:prefix("*DBG* sys_SUITE_server sent {ok,-44} to ",Msg2), + stop(), ok. stats(suite) -> []; stats(Config) when is_list(Config) -> - ?line Self = self(), - ?line {ok,_Server} = start(), - ?line ok = sys:statistics(?server,true), - ?line {ok,-44} = public_call(44), - ?line {ok,Stats} = sys:statistics(?server,get), - ?line lists:member({messages_in,1},Stats), - ?line lists:member({messages_out,1},Stats), - ?line ok = sys:statistics(?server,false), - ?line {status,_Pid,{module,_Mod},[_PDict,running,Self,_,_]} = + Self = self(), + {ok,_Server} = start(), + ok = sys:statistics(?server,true), + {ok,-44} = public_call(44), + {ok,Stats} = sys:statistics(?server,get), + lists:member({messages_in,1},Stats), + lists:member({messages_out,1},Stats), + ok = sys:statistics(?server,false), + {status,_Pid,{module,_Mod},[_PDict,running,Self,_,_]} = sys:get_status(?server), - ?line {ok,no_statistics} = sys:statistics(?server,get), - ?line stop(), + {ok,no_statistics} = sys:statistics(?server,get), + stop(), ok. trace(suite) -> []; trace(Config) when is_list(Config) -> - ?line {ok,_Server} = start(), - case os:type() of - vxworks -> - ?line test_server:sleep(20000); - _ -> - ?line test_server:sleep(2000) - end, - ?line test_server:capture_start(), - ?line sys:trace(?server,true), - ?line {ok,-44} = public_call(44), + {ok,_Server} = start(), + test_server:sleep(2000), + test_server:capture_start(), + sys:trace(?server,true), + {ok,-44} = public_call(44), %% ho, hum, allow for the io to reach us.. - case os:type() of - vxworks -> - ?line test_server:sleep(10000); - _ -> - ?line test_server:sleep(1000) - end, - ?line test_server:capture_stop(), - ?line [Msg1,Msg2] = test_server:capture_get(), - ?line lists:prefix("*DBG* sys_SUITE_server got call {req,44} from ",Msg1), - ?line lists:prefix("*DBG* sys_SUITE_server sent {ok,-44} to ",Msg2), - ?line stop(), + test_server:sleep(1000), + test_server:capture_stop(), + [Msg1,Msg2] = test_server:capture_get(), + lists:prefix("*DBG* sys_SUITE_server got call {req,44} from ",Msg1), + lists:prefix("*DBG* sys_SUITE_server sent {ok,-44} to ",Msg2), + stop(), ok. suspend(suite) -> []; diff --git a/lib/stdlib/test/timer_SUITE.erl b/lib/stdlib/test/timer_SUITE.erl index f84c72b0f8..1110891ab8 100644 --- a/lib/stdlib/test/timer_SUITE.erl +++ b/lib/stdlib/test/timer_SUITE.erl @@ -32,7 +32,6 @@ %% functions I guess. But I don't have time for that now. %% %% Expect it to run for at least 5-10 minutes! -%% Except for VxWorks of course, where a couple of hours is more apropriate... %% The main test case in this module is "do_big_test", which @@ -77,12 +76,7 @@ end_per_group(_GroupName, Config) -> do_big_test(TConfig) when is_list(TConfig) -> Dog = ?t:timetrap(?t:minutes(20)), Save = process_flag(trap_exit, true), - Result = case os:type() of - vxworks -> - big_test(10); - _ -> - big_test(200) - end, + Result = big_test(200), process_flag(trap_exit, Save), ?t:timetrap_cancel(Dog), report_result(Result). |