diff options
Diffstat (limited to 'lib/stdlib/test')
-rw-r--r-- | lib/stdlib/test/edlin_expand_SUITE.erl | 165 | ||||
-rw-r--r-- | lib/stdlib/test/epp_SUITE.erl | 32 | ||||
-rw-r--r-- | lib/stdlib/test/erl_eval_SUITE.erl | 19 | ||||
-rw-r--r-- | lib/stdlib/test/erl_expand_records_SUITE.erl | 21 | ||||
-rw-r--r-- | lib/stdlib/test/erl_lint_SUITE.erl | 19 | ||||
-rw-r--r-- | lib/stdlib/test/erl_pp_SUITE.erl | 23 | ||||
-rw-r--r-- | lib/stdlib/test/ets_SUITE.erl | 18 | ||||
-rw-r--r-- | lib/stdlib/test/expand_test.erl | 6 | ||||
-rw-r--r-- | lib/stdlib/test/expand_test1.erl | 4 | ||||
-rw-r--r-- | lib/stdlib/test/stdlib_SUITE.erl | 63 |
10 files changed, 246 insertions, 124 deletions
diff --git a/lib/stdlib/test/edlin_expand_SUITE.erl b/lib/stdlib/test/edlin_expand_SUITE.erl index 0cd2688e2e..43c980e994 100644 --- a/lib/stdlib/test/edlin_expand_SUITE.erl +++ b/lib/stdlib/test/edlin_expand_SUITE.erl @@ -26,11 +26,11 @@ -include_lib("test_server/include/test_server.hrl"). -% Default timetrap timeout (set in init_per_testcase). +%% Default timetrap timeout (set in init_per_testcase). -define(default_timeout, ?t:minutes(1)). init_per_testcase(_Case, Config) -> - ?line Dog = ?t:timetrap(?default_timeout), + Dog = ?t:timetrap(?default_timeout), [{watchdog, Dog} | Config]. end_per_testcase(_Case, Config) -> Dog = ?config(watchdog, Config), @@ -67,20 +67,21 @@ normal(doc) -> normal(suite) -> []; normal(Config) when is_list(Config) -> - ?line {module,expand_test} = c:l(expand_test), - % These tests might fail if another module with the prefix "expand_" happens - % to also be loaded. - ?line {yes, "test:", []} = edlin_expand:expand(lists:reverse("expand_")), - ?line {no, [], []} = edlin_expand:expand(lists:reverse("expandXX_")), - ?line {no,[], - [{"a_fun_name",1}, - {"a_less_fun_name",1}, - {"b_comes_after_a",1}, - {"module_info",0}, - {"module_info",1}]} = edlin_expand:expand(lists:reverse("expand_test:")), - ?line {yes,[],[{"a_fun_name",1}, - {"a_less_fun_name",1}]} = edlin_expand:expand( - lists:reverse("expand_test:a_")), + {module,expand_test} = c:l(expand_test), + %% These tests might fail if another module with the prefix + %% "expand_" happens to also be loaded. + {yes, "test:", []} = do_expand("expand_"), + {no, [], []} = do_expand("expandXX_"), + {no,[], + [{"a_fun_name",1}, + {"a_less_fun_name",1}, + {"b_comes_after_a",1}, + {"expand0arity_entirely",0}, + {"module_info",0}, + {"module_info",1}]} = do_expand("expand_test:"), + {yes,[],[{"a_fun_name",1}, + {"a_less_fun_name",1}]} = do_expand("expand_test:a_"), + {yes,"arity_entirely()",[]} = do_expand("expand_test:expand0"), ok. quoted_fun(doc) -> @@ -88,38 +89,35 @@ quoted_fun(doc) -> quoted_fun(suite) -> []; quoted_fun(Config) when is_list(Config) -> - ?line {module,expand_test} = c:l(expand_test), - ?line {module,expand_test1} = c:l(expand_test1), + {module,expand_test} = c:l(expand_test), + {module,expand_test1} = c:l(expand_test1), %% should be no colon after test this time - ?line {yes, "test", []} = edlin_expand:expand(lists:reverse("expand_")), - ?line {no, [], []} = edlin_expand:expand(lists:reverse("expandXX_")), - ?line {no,[],[{"'#weird-fun-name'",0}, - {"'Quoted_fun_name'",0}, - {"'Quoted_fun_too'",0}, - {"a_fun_name",1}, - {"a_less_fun_name",1}, - {"b_comes_after_a",1}, - {"module_info",0}, - {"module_info",1}]} = edlin_expand:expand( - lists:reverse("expand_test1:")), - ?line {yes,"_",[]} = edlin_expand:expand( - lists:reverse("expand_test1:a")), - ?line {yes,[],[{"a_fun_name",1}, - {"a_less_fun_name",1}]} = edlin_expand:expand( - lists:reverse("expand_test1:a_")), - ?line {yes,[], - [{"'#weird-fun-name'",0}, + {yes, "test", []} = do_expand("expand_"), + {no, [], []} = do_expand("expandXX_"), + {no,[],[{"'#weird-fun-name'",1}, {"'Quoted_fun_name'",0}, - {"'Quoted_fun_too'",0}]} = edlin_expand:expand( - lists:reverse("expand_test1:'")), - ?line {yes,"uoted_fun_",[]} = edlin_expand:expand( - lists:reverse("expand_test1:'Q")), - ?line {yes,[], - [{"'Quoted_fun_name'",0}, - {"'Quoted_fun_too'",0}]} = edlin_expand:expand( - lists:reverse("expand_test1:'Quoted_fun_")), - ?line {yes,"weird-fun-name'(",[]} = edlin_expand:expand( - lists:reverse("expand_test1:'#")), + {"'Quoted_fun_too'",0}, + {"a_fun_name",1}, + {"a_less_fun_name",1}, + {"b_comes_after_a",1}, + {"module_info",0}, + {"module_info",1}]} = do_expand("expand_test1:"), + {yes,"_",[]} = do_expand("expand_test1:a"), + {yes,[],[{"a_fun_name",1}, + {"a_less_fun_name",1}]} = do_expand("expand_test1:a_"), + {yes,[], + [{"'#weird-fun-name'",1}, + {"'Quoted_fun_name'",0}, + {"'Quoted_fun_too'",0}]} = do_expand("expand_test1:'"), + {yes,"uoted_fun_",[]} = do_expand("expand_test1:'Q"), + {yes,[], + [{"'Quoted_fun_name'",0}, + {"'Quoted_fun_too'",0}]} = do_expand("expand_test1:'Quoted_fun_"), + {yes,"weird-fun-name'(",[]} = do_expand("expand_test1:'#"), + + %% Since there is a module_info/1 as well as a module_info/0 + %% there should not be a closing parenthesis added. + {yes,"(",[]} = do_expand("expand_test:module_info"), ok. quoted_module(doc) -> @@ -127,51 +125,46 @@ quoted_module(doc) -> quoted_module(suite) -> []; quoted_module(Config) when is_list(Config) -> - ?line {module,'ExpandTestCaps'} = c:l('ExpandTestCaps'), - ?line {yes, "Caps':", []} = edlin_expand:expand(lists:reverse("'ExpandTest")), - ?line {no,[], - [{"a_fun_name",1}, - {"a_less_fun_name",1}, - {"b_comes_after_a",1}, - {"module_info",0}, - {"module_info",1}]} = edlin_expand:expand(lists:reverse("'ExpandTestCaps':")), - ?line {yes,[],[{"a_fun_name",1}, - {"a_less_fun_name",1}]} = edlin_expand:expand( - lists:reverse("'ExpandTestCaps':a_")), + {module,'ExpandTestCaps'} = c:l('ExpandTestCaps'), + {yes, "Caps':", []} = do_expand("'ExpandTest"), + {no,[], + [{"a_fun_name",1}, + {"a_less_fun_name",1}, + {"b_comes_after_a",1}, + {"module_info",0}, + {"module_info",1}]} = do_expand("'ExpandTestCaps':"), + {yes,[],[{"a_fun_name",1}, + {"a_less_fun_name",1}]} = do_expand("'ExpandTestCaps':a_"), ok. quoted_both(suite) -> []; quoted_both(Config) when is_list(Config) -> - ?line {module,'ExpandTestCaps'} = c:l('ExpandTestCaps'), - ?line {module,'ExpandTestCaps1'} = c:l('ExpandTestCaps1'), + {module,'ExpandTestCaps'} = c:l('ExpandTestCaps'), + {module,'ExpandTestCaps1'} = c:l('ExpandTestCaps1'), %% should be no colon (or quote) after test this time - ?line {yes, "Caps", []} = edlin_expand:expand(lists:reverse("'ExpandTest")), - ?line {no,[],[{"'#weird-fun-name'",0}, - {"'Quoted_fun_name'",0}, - {"'Quoted_fun_too'",0}, - {"a_fun_name",1}, - {"a_less_fun_name",1}, - {"b_comes_after_a",1}, - {"module_info",0}, - {"module_info",1}]} = edlin_expand:expand( - lists:reverse("'ExpandTestCaps1':")), - ?line {yes,"_",[]} = edlin_expand:expand( - lists:reverse("'ExpandTestCaps1':a")), - ?line {yes,[],[{"a_fun_name",1}, - {"a_less_fun_name",1}]} = edlin_expand:expand( - lists:reverse("'ExpandTestCaps1':a_")), - ?line {yes,[], - [{"'#weird-fun-name'",0}, + {yes, "Caps", []} = do_expand("'ExpandTest"), + {no,[],[{"'#weird-fun-name'",0}, {"'Quoted_fun_name'",0}, - {"'Quoted_fun_too'",0}]} = edlin_expand:expand( - lists:reverse("'ExpandTestCaps1':'")), - ?line {yes,"uoted_fun_",[]} = edlin_expand:expand( - lists:reverse("'ExpandTestCaps1':'Q")), - ?line {yes,[], - [{"'Quoted_fun_name'",0}, - {"'Quoted_fun_too'",0}]} = edlin_expand:expand( - lists:reverse("'ExpandTestCaps1':'Quoted_fun_")), - ?line {yes,"weird-fun-name'(",[]} = edlin_expand:expand( - lists:reverse("'ExpandTestCaps1':'#")), + {"'Quoted_fun_too'",0}, + {"a_fun_name",1}, + {"a_less_fun_name",1}, + {"b_comes_after_a",1}, + {"module_info",0}, + {"module_info",1}]} = do_expand("'ExpandTestCaps1':"), + {yes,"_",[]} = do_expand("'ExpandTestCaps1':a"), + {yes,[],[{"a_fun_name",1}, + {"a_less_fun_name",1}]} = do_expand("'ExpandTestCaps1':a_"), + {yes,[], + [{"'#weird-fun-name'",0}, + {"'Quoted_fun_name'",0}, + {"'Quoted_fun_too'",0}]} = do_expand("'ExpandTestCaps1':'"), + {yes,"uoted_fun_",[]} = do_expand("'ExpandTestCaps1':'Q"), + {yes,[], + [{"'Quoted_fun_name'",0}, + {"'Quoted_fun_too'",0}]} = do_expand("'ExpandTestCaps1':'Quoted_fun_"), + {yes,"weird-fun-name'()",[]} = do_expand("'ExpandTestCaps1':'#"), ok. + +do_expand(String) -> + edlin_expand:expand(lists:reverse(String)). diff --git a/lib/stdlib/test/epp_SUITE.erl b/lib/stdlib/test/epp_SUITE.erl index 0cbdf76270..0b4726c07a 100644 --- a/lib/stdlib/test/epp_SUITE.erl +++ b/lib/stdlib/test/epp_SUITE.erl @@ -1,7 +1,7 @@ %% %% %CopyrightBegin% %% -%% Copyright Ericsson AB 1998-2013. All Rights Reserved. +%% Copyright Ericsson AB 1998-2014. 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 @@ -25,7 +25,8 @@ variable_1/1, otp_4870/1, otp_4871/1, otp_5362/1, pmod/1, not_circular/1, skip_header/1, otp_6277/1, otp_7702/1, otp_8130/1, overload_mac/1, otp_8388/1, otp_8470/1, otp_8503/1, - otp_8562/1, otp_8665/1, otp_8911/1, otp_10302/1, otp_10820/1]). + otp_8562/1, otp_8665/1, otp_8911/1, otp_10302/1, otp_10820/1, + otp_11728/1]). -export([epp_parse_erl_form/2]). @@ -67,7 +68,7 @@ all() -> {group, variable}, otp_4870, otp_4871, otp_5362, pmod, not_circular, skip_header, otp_6277, otp_7702, otp_8130, overload_mac, otp_8388, otp_8470, otp_8503, otp_8562, - otp_8665, otp_8911, otp_10302, otp_10820]. + otp_8665, otp_8911, otp_10302, otp_10820, otp_11728]. groups() -> [{upcase_mac, [], [upcase_mac_1, upcase_mac_2]}, @@ -1387,6 +1388,31 @@ do_otp_10820(File, C, PC) -> true = test_server:stop_node(Node), ok. +otp_11728(doc) -> + ["OTP-11728. Bugfix circular macro."]; +otp_11728(suite) -> + []; +otp_11728(Config) when is_list(Config) -> + Dir = ?config(priv_dir, Config), + H = <<"-define(MACRO,[[]++?MACRO]).">>, + HrlFile = filename:join(Dir, "otp_11728.hrl"), + ok = file:write_file(HrlFile, H), + C = <<"-module(otp_11728). + -compile(export_all). + + -include(\"otp_11728.hrl\"). + + function_name()-> + A=?MACRO, % line 7 + ok">>, + ErlFile = filename:join(Dir, "otp_11728.erl"), + ok = file:write_file(ErlFile, C), + {ok, L} = epp:parse_file(ErlFile, [Dir], []), + true = lists:member({error,{7,epp,{circular,'MACRO',none}}}, L), + _ = file:delete(HrlFile), + _ = file:delete(ErlFile), + ok. + check(Config, Tests) -> eval_tests(Config, fun check_test/2, Tests). diff --git a/lib/stdlib/test/erl_eval_SUITE.erl b/lib/stdlib/test/erl_eval_SUITE.erl index c4b6b35e72..b194c7cb41 100644 --- a/lib/stdlib/test/erl_eval_SUITE.erl +++ b/lib/stdlib/test/erl_eval_SUITE.erl @@ -42,7 +42,8 @@ try_catch/1, eval_expr_5/1, zero_width/1, - eep37/1]). + eep37/1, + eep43/1]). %% %% Define to run outside of test server @@ -82,7 +83,7 @@ all() -> simple_cases, unary_plus, apply_atom, otp_5269, otp_6539, otp_6543, otp_6787, otp_6977, otp_7550, otp_8133, otp_10622, funs, try_catch, eval_expr_5, zero_width, - eep37]. + eep37, eep43]. groups() -> []. @@ -1424,6 +1425,20 @@ eep37(Config) when is_list(Config) -> 720), ok. +eep43(Config) when is_list(Config) -> + check(fun () -> #{} end, " #{}.", #{}), + check(fun () -> #{a => b} end, "#{a => b}.", #{a => b}), + check(fun () -> + Map = #{a => b}, + {Map#{a := b},Map#{a => c},Map#{d => e}} + end, + "begin " + " Map = #{a => B=b}, " + " {Map#{a := B},Map#{a => c},Map#{d => e}} " + "end.", + {#{a => b},#{a => c},#{a => b,d => e}}), + ok. + %% Check the string in different contexts: as is; in fun; from compiled code. check(F, String, Result) -> check1(F, String, Result), diff --git a/lib/stdlib/test/erl_expand_records_SUITE.erl b/lib/stdlib/test/erl_expand_records_SUITE.erl index 94b4397a9c..43e679f7ed 100644 --- a/lib/stdlib/test/erl_expand_records_SUITE.erl +++ b/lib/stdlib/test/erl_expand_records_SUITE.erl @@ -38,7 +38,7 @@ -export([attributes/1, expr/1, guard/1, init/1, pattern/1, strict/1, update/1, otp_5915/1, otp_7931/1, otp_5990/1, - otp_7078/1, otp_7101/1]). + otp_7078/1, otp_7101/1, maps/1]). % Default timetrap timeout (set in init_per_testcase). -define(default_timeout, ?t:minutes(1)). @@ -56,7 +56,7 @@ suite() -> [{ct_hooks,[ts_install_cth]}]. all() -> [attributes, expr, guard, init, - pattern, strict, update, {group, tickets}]. + pattern, strict, update, maps, {group, tickets}]. groups() -> [{tickets, [], @@ -402,7 +402,22 @@ update(Config) when is_list(Config) -> ], ?line run(Config, Ts), ok. - + +maps(Config) when is_list(Config) -> + Ts = [<<"-record(rr, {a,b,c}). + t() -> + R0 = id(#rr{a=1,b=2,c=3}), + R1 = id(#rr{a=4,b=5,c=6}), + [{R0,R1}] = + maps:to_list(#{#rr{a=1,b=2,c=3} => #rr{a=4,b=5,c=6}}), + #{#rr{a=1,b=2,c=3} := #rr{a=1,b=2,c=3}} = + #{#rr{a=1,b=2,c=3} => R1}#{#rr{a=1,b=2,c=3} := R0}, + ok. + + id(X) -> X. + ">>], + run(Config, Ts, [strict_record_tests]), + ok. otp_5915(doc) -> "Strict record tests in guards."; diff --git a/lib/stdlib/test/erl_lint_SUITE.erl b/lib/stdlib/test/erl_lint_SUITE.erl index 6e9a9dd7bf..48f50d5f43 100644 --- a/lib/stdlib/test/erl_lint_SUITE.erl +++ b/lib/stdlib/test/erl_lint_SUITE.erl @@ -2827,7 +2827,24 @@ bif_clash(Config) when is_list(Config) -> {6,erl_lint,{illegal_guard_local_call,{is_tuple,1}}}, {7,erl_lint,{illegal_guard_local_call,{is_list,1}}}, {8,erl_lint,{illegal_guard_local_call,{is_record,3}}}, - {9,erl_lint,{illegal_guard_local_call,{is_record,3}}}],[]}} + {9,erl_lint,{illegal_guard_local_call,{is_record,3}}}],[]}}, + %% We can also suppress all auto imports at once + {clash22, + <<"-export([size/1, binary_part/2]). + -compile(no_auto_import). + size([]) -> + 0; + size({N,_}) -> + N; + size([_|T]) -> + 1+size(T). + binary_part({B,_},{X,Y}) -> + binary_part(B,{X,Y}); + binary_part(B,{X,Y}) -> + binary:part(B,X,Y). + ">>, + [], + []} ], ?line [] = run(Config, Ts), diff --git a/lib/stdlib/test/erl_pp_SUITE.erl b/lib/stdlib/test/erl_pp_SUITE.erl index cc744ee76b..390322a5fa 100644 --- a/lib/stdlib/test/erl_pp_SUITE.erl +++ b/lib/stdlib/test/erl_pp_SUITE.erl @@ -46,6 +46,7 @@ import_export/1, misc_attrs/1, dialyzer_attrs/1, hook/1, neg_indent/1, + maps_syntax/1, otp_6321/1, otp_6911/1, otp_6914/1, otp_8150/1, otp_8238/1, otp_8473/1, otp_8522/1, otp_8567/1, otp_8664/1, otp_9147/1, @@ -76,7 +77,8 @@ groups() -> [{expr, [], [func, call, recs, try_catch, if_then, receive_after, bits, head_tail, cond1, block, case1, ops, - messages, old_mnemosyne_syntax]}, + messages, old_mnemosyne_syntax, maps_syntax + ]}, {attributes, [], [misc_attrs, import_export, dialyzer_attrs]}, {tickets, [], [otp_6321, otp_6911, otp_6914, otp_8150, otp_8238, @@ -975,6 +977,25 @@ count_atom(L, A) when is_list(L) -> count_atom(_, _) -> 0. +maps_syntax(doc) -> "Maps syntax"; +maps_syntax(suite) -> []; +maps_syntax(Config) when is_list(Config) -> + Ts = [{map_fun_1, + <<"t() ->\n" + " M0 = #{ 1 => hi, hi => 42, 1.0 => {hi,world}},\n" + " M1 = M0#{ 1 := hello, new_val => 1337 },\n" + " map_fun_2:val(M1).\n">>}, + {map_fun_2, + <<"val(#{ 1 := V1, hi := V2, new_val := V3}) -> {V1,V2,V3}.\n">>}], + compile(Config, Ts), + + ok = pp_expr(<<"#{}">>), + ok = pp_expr(<<"#{ a => 1, <<\"hi\">> => \"world\", 33 => 1.0 }">>), + ok = pp_expr(<<"#{ a := V1, <<\"hi\">> := V2 } = M">>), + ok = pp_expr(<<"M#{ a => V1, <<\"hi\">> := V2 }">>), + ok. + + otp_8567(doc) -> "OTP_8567. Avoid duplicated 'undefined' in record field types."; otp_8567(suite) -> []; diff --git a/lib/stdlib/test/ets_SUITE.erl b/lib/stdlib/test/ets_SUITE.erl index 82c3e7ecaf..8dc8b2c291 100644 --- a/lib/stdlib/test/ets_SUITE.erl +++ b/lib/stdlib/test/ets_SUITE.erl @@ -1,7 +1,7 @@ %% %% %CopyrightBegin% %% -%% Copyright Ericsson AB 1996-2013. All Rights Reserved. +%% Copyright Ericsson AB 1996-2014. 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 @@ -75,6 +75,7 @@ -export([otp_9932/1]). -export([otp_9423/1]). -export([otp_10182/1]). +-export([ets_all/1]). -export([memory_check_summary/1]). -export([init_per_testcase/2, end_per_testcase/2]). @@ -151,6 +152,7 @@ all() -> otp_10182, otp_9932, otp_9423, + ets_all, memory_check_summary]. % MUST BE LAST @@ -5565,7 +5567,19 @@ otp_10182(Config) when is_list(Config) -> ets:delete(Db), In = Out. - +%% Test that ets:all include/exclude tables that we know are created/deleted +ets_all(Config) when is_list(Config) -> + Pids = [spawn_link(fun() -> ets_all_run() end) || _ <- [1,2]], + receive after 3*1000 -> ok end, + [begin unlink(P), exit(P,kill) end || P <- Pids], + ok. + +ets_all_run() -> + Table = ets:new(undefined, []), + true = lists:member(Table, ets:all()), + ets:delete(Table), + false = lists:member(Table, ets:all()), + ets_all_run(). % diff --git a/lib/stdlib/test/expand_test.erl b/lib/stdlib/test/expand_test.erl index 63e4bc3aa0..b9db32c352 100644 --- a/lib/stdlib/test/expand_test.erl +++ b/lib/stdlib/test/expand_test.erl @@ -20,7 +20,8 @@ -export([a_fun_name/1, a_less_fun_name/1, - b_comes_after_a/1]). + b_comes_after_a/1, + expand0arity_entirely/0]). a_fun_name(X) -> X. @@ -30,3 +31,6 @@ a_less_fun_name(X) -> b_comes_after_a(X) -> X. + +expand0arity_entirely () -> + ok. diff --git a/lib/stdlib/test/expand_test1.erl b/lib/stdlib/test/expand_test1.erl index 11b6fec0f3..1d375e5677 100644 --- a/lib/stdlib/test/expand_test1.erl +++ b/lib/stdlib/test/expand_test1.erl @@ -23,7 +23,7 @@ b_comes_after_a/1, 'Quoted_fun_name'/0, 'Quoted_fun_too'/0, - '#weird-fun-name'/0]). + '#weird-fun-name'/1]). a_fun_name(X) -> X. @@ -40,5 +40,5 @@ b_comes_after_a(X) -> 'Quoted_fun_too'() -> too. -'#weird-fun-name'() -> +'#weird-fun-name'(_) -> weird. diff --git a/lib/stdlib/test/stdlib_SUITE.erl b/lib/stdlib/test/stdlib_SUITE.erl index 8fff5e2e05..b0d6913636 100644 --- a/lib/stdlib/test/stdlib_SUITE.erl +++ b/lib/stdlib/test/stdlib_SUITE.erl @@ -25,7 +25,6 @@ % Default timetrap timeout (set in init_per_testcase). -define(default_timeout, ?t:minutes(1)). --define(application, stdlib). % Test server specific exports -export([all/0, suite/0,groups/0,init_per_suite/1, end_per_suite/1, @@ -78,17 +77,18 @@ app_test(Config) when is_list(Config) -> ?t:app_test(stdlib), ok. -%% Test that appup allows upgrade from/downgrade to a maximum of two -%% major releases back. +%% Test that appup allows upgrade from/downgrade to a maximum of one +%% major release back. appup_test(_Config) -> - do_appup_tests(create_test_vsns()). + appup_tests(stdlib,create_test_vsns(stdlib)). -do_appup_tests({[],[]}) -> +appup_tests(_App,{[],[]}) -> {skip,"no previous releases available"}; -do_appup_tests({OkVsns,NokVsns}) -> - application:load(stdlib), - {_,_,Vsn} = lists:keyfind(stdlib,1,application:loaded_applications()), - AppupFile = filename:join([code:lib_dir(stdlib),ebin,"stdlib.appup"]), +appup_tests(App,{OkVsns,NokVsns}) -> + application:load(App), + {_,_,Vsn} = lists:keyfind(App,1,application:loaded_applications()), + AppupFileName = atom_to_list(App) ++ ".appup", + AppupFile = filename:join([code:lib_dir(App),ebin,AppupFileName]), {ok,[{Vsn,UpFrom,DownTo}=AppupScript]} = file:consult(AppupFile), ct:log("~p~n",[AppupScript]), ct:log("Testing ok versions: ~p~n",[OkVsns]), @@ -99,13 +99,12 @@ do_appup_tests({OkVsns,NokVsns}) -> check_appup(NokVsns,DownTo,error), ok. -create_test_vsns() -> +create_test_vsns(App) -> This = erlang:system_info(otp_release), FirstMajor = previous_major(This), SecondMajor = previous_major(FirstMajor), - ThirdMajor = previous_major(SecondMajor), - Ok = stdlib_vsn([FirstMajor,SecondMajor]), - Nok0 = stdlib_vsn([ThirdMajor]), + Ok = app_vsn(App,[FirstMajor]), + Nok0 = app_vsn(App,[SecondMajor]), Nok = case Ok of [Ok1|_] -> [Ok1 ++ ",1" | Nok0]; % illegal @@ -121,18 +120,36 @@ previous_major("r"++Rel) -> previous_major(Rel) -> integer_to_list(list_to_integer(Rel)-1). -stdlib_vsn([R|Rs]) -> - case test_server:is_release_available(R) of - true -> - {ok,N} = test_server:start_node(prevrel,peer,[{erl,[{release,R}]}]), - As = rpc:call(N,application,which_applications,[]), - {_,_,KV} = lists:keyfind(stdlib,1,As), - test_server:stop_node(N), - [KV|stdlib_vsn(Rs)]; +app_vsn(App,[R|Rs]) -> + OldRel = + case test_server:is_release_available(R) of + true -> + {release,R}; + false -> + case ct:get_config({otp_releases,list_to_atom(R)}) of + undefined -> + false; + Prog0 -> + case os:find_executable(Prog0) of + false -> + false; + Prog -> + {prog,Prog} + end + end + end, + case OldRel of false -> - stdlib_vsn(Rs) + app_vsn(App,Rs); + _ -> + {ok,N} = test_server:start_node(prevrel,peer,[{erl,[OldRel]}]), + _ = rpc:call(N,application,load,[App]), + As = rpc:call(N,application,loaded_applications,[]), + {_,_,V} = lists:keyfind(App,1,As), + test_server:stop_node(N), + [V|app_vsn(App,Rs)] end; -stdlib_vsn([]) -> +app_vsn(_App,[]) -> []. check_appup([Vsn|Vsns],Instrs,Expected) -> |