aboutsummaryrefslogtreecommitdiffstats
path: root/lib/stdlib/test
diff options
context:
space:
mode:
Diffstat (limited to 'lib/stdlib/test')
-rw-r--r--lib/stdlib/test/binary_module_SUITE.erl28
-rw-r--r--lib/stdlib/test/binref.erl37
-rw-r--r--lib/stdlib/test/erl_eval_SUITE.erl24
-rw-r--r--lib/stdlib/test/erl_internal_SUITE.erl65
-rw-r--r--lib/stdlib/test/erl_lint_SUITE.erl469
-rw-r--r--lib/stdlib/test/erl_lint_SUITE_data/bad_behaviour1.erl6
-rw-r--r--lib/stdlib/test/erl_lint_SUITE_data/bad_behaviour2.erl6
-rw-r--r--lib/stdlib/test/erl_lint_SUITE_data/callback1.erl6
-rw-r--r--lib/stdlib/test/erl_lint_SUITE_data/callback2.erl6
-rw-r--r--lib/stdlib/test/erl_lint_SUITE_data/callback3.erl8
-rw-r--r--lib/stdlib/test/erl_lint_SUITE_data/predef.erl4
-rw-r--r--lib/stdlib/test/erl_pp_SUITE.erl63
-rw-r--r--lib/stdlib/test/erl_scan_SUITE.erl2
-rw-r--r--lib/stdlib/test/filelib_SUITE.erl3
-rw-r--r--lib/stdlib/test/filename_SUITE.erl114
-rw-r--r--lib/stdlib/test/gen_event_SUITE.erl4
-rw-r--r--lib/stdlib/test/gen_fsm_SUITE.erl104
-rw-r--r--lib/stdlib/test/gen_server_SUITE.erl107
-rw-r--r--lib/stdlib/test/proc_lib_SUITE.erl93
-rw-r--r--lib/stdlib/test/qlc_SUITE.erl39
-rw-r--r--lib/stdlib/test/stdlib_SUITE.erl33
-rw-r--r--lib/stdlib/test/supervisor_SUITE.erl305
-rw-r--r--lib/stdlib/test/sys_SUITE.erl16
-rw-r--r--lib/stdlib/test/sys_sp1.erl14
-rw-r--r--lib/stdlib/test/sys_sp2.erl33
25 files changed, 1352 insertions, 237 deletions
diff --git a/lib/stdlib/test/binary_module_SUITE.erl b/lib/stdlib/test/binary_module_SUITE.erl
index 32cec0db6f..f828c70b63 100644
--- a/lib/stdlib/test/binary_module_SUITE.erl
+++ b/lib/stdlib/test/binary_module_SUITE.erl
@@ -506,12 +506,35 @@ do_interesting(Module) ->
?line [<<1,2,3>>,<<6>>] = Module:split(<<1,2,3,4,5,6,7,8>>,
[<<4,5>>,<<7>>,<<8>>],
[global,trim]),
+ ?line [<<1,2,3>>,<<6>>] = Module:split(<<1,2,3,4,5,6,7,8>>,
+ [<<4,5>>,<<7>>,<<8>>],
+ [global,trim_all]),
?line [<<1,2,3,4,5,6,7,8>>] = Module:split(<<1,2,3,4,5,6,7,8>>,
[<<4,5>>,<<7>>,<<8>>],
[global,trim,{scope,{0,4}}]),
?line [<<1,2,3>>,<<6,7,8>>] = Module:split(<<1,2,3,4,5,6,7,8>>,
[<<4,5>>,<<7>>,<<8>>],
[global,trim,{scope,{0,5}}]),
+
+ ?line [<<>>,<<>>,<<3>>,<<6,7,8>>] = Module:split(<<1,2,3,4,5,6,7,8>>,
+ [<<1>>,<<2>>,<<4,5>>],
+ [global,trim]),
+ ?line [<<3>>,<<6,7,8>>] = Module:split(<<1,2,3,4,5,6,7,8>>,
+ [<<1>>,<<2>>,<<4,5>>],
+ [global,trim_all]),
+
+ ?line [<<1,2,3>>,<<>>,<<7,8>>] = Module:split(<<1,2,3,4,5,6,7,8>>,
+ [<<4,5>>,<<6>>],
+ [global,trim]),
+ ?line [<<1,2,3>>,<<7,8>>] = Module:split(<<1,2,3,4,5,6,7,8>>,
+ [<<4,5>>,<<6>>],
+ [global,trim_all]),
+ ?line [<<>>,<<>>,<<3>>,<<>>,<<6>>] = Module:split(<<1,2,3,4,5,6,7,8>>,
+ [<<1>>,<<2>>,<<4>>,<<5>>,<<7>>,<<8>>],
+ [global,trim]),
+ ?line [<<3>>,<<6>>] = Module:split(<<1,2,3,4,5,6,7,8>>,
+ [<<1>>,<<2>>,<<4>>,<<5>>,<<7>>,<<8>>],
+ [global,trim_all]),
?line badarg = ?MASK_ERROR(
Module:replace(<<1,2,3,4,5,6,7,8>>,
[<<4,5>>,<<7>>,<<8>>],<<99>>,
@@ -1247,6 +1270,8 @@ do_random_split_comp(N,NeedleRange,HaystackRange) ->
true = do_split_comp(Needle,Haystack,[]),
true = do_split_comp(Needle,Haystack,[global]),
true = do_split_comp(Needle,Haystack,[global,trim]),
+ true = do_split_comp(Needle,Haystack,[global,trim_all]),
+ true = do_split_comp(Needle,Haystack,[global,trim,trim_all]),
do_random_split_comp(N-1,NeedleRange,HaystackRange).
do_random_split_comp2(0,_,_) ->
ok;
@@ -1257,6 +1282,9 @@ do_random_split_comp2(N,NeedleRange,HaystackRange) ->
_ <- lists:duplicate(NumNeedles,a)],
true = do_split_comp(Needles,Haystack,[]),
true = do_split_comp(Needles,Haystack,[global]),
+ true = do_split_comp(Needles,Haystack,[global,trim]),
+ true = do_split_comp(Needles,Haystack,[global,trim_all]),
+ true = do_split_comp(Needles,Haystack,[global,trim,trim_all]),
do_random_split_comp2(N-1,NeedleRange,HaystackRange).
do_split_comp(N,H,Opts) ->
diff --git a/lib/stdlib/test/binref.erl b/lib/stdlib/test/binref.erl
index 6d96736ef3..a52ea98e5a 100644
--- a/lib/stdlib/test/binref.erl
+++ b/lib/stdlib/test/binref.erl
@@ -155,7 +155,8 @@ split(Haystack,Needles0,Options) ->
true ->
exit(badtype)
end,
- {Part,Global,Trim} = get_opts_split(Options,{nomatch,false,false}),
+ {Part,Global,Trim,TrimAll} =
+ get_opts_split(Options,{nomatch,false,false,false}),
{Start,End,NewStack} =
case Part of
nomatch ->
@@ -180,20 +181,24 @@ split(Haystack,Needles0,Options) ->
[X]
end
end,
- do_split(Haystack,MList,0,Trim)
+ do_split(Haystack,MList,0,Trim,TrimAll)
catch
_:_ ->
erlang:error(badarg)
end.
-do_split(H,[],N,true) when N >= byte_size(H) ->
+do_split(H,[],N,true,_) when N >= byte_size(H) ->
[];
-do_split(H,[],N,_) ->
+do_split(H,[],N,_,true) when N >= byte_size(H) ->
+ [];
+do_split(H,[],N,_,_) ->
[part(H,{N,byte_size(H)-N})];
-do_split(H,[{A,B}|T],N,Trim) ->
+do_split(H,[{A,B}|T],N,Trim,TrimAll) ->
case part(H,{N,A-N}) of
+ <<>> when TrimAll == true ->
+ do_split(H,T,A+B,Trim,TrimAll);
<<>> ->
- Rest = do_split(H,T,A+B,Trim),
+ Rest = do_split(H,T,A+B,Trim,TrimAll),
case {Trim, Rest} of
{true,[]} ->
[];
@@ -201,7 +206,7 @@ do_split(H,[{A,B}|T],N,Trim) ->
[<<>> | Rest]
end;
Oth ->
- [Oth | do_split(H,T,A+B,Trim)]
+ [Oth | do_split(H,T,A+B,Trim,TrimAll)]
end.
@@ -565,14 +570,16 @@ get_opts_match([{scope,{A,B}} | T],_Part) ->
get_opts_match(_,_) ->
throw(badopt).
-get_opts_split([],{Part,Global,Trim}) ->
- {Part,Global,Trim};
-get_opts_split([{scope,{A,B}} | T],{_Part,Global,Trim}) ->
- get_opts_split(T,{{A,B},Global,Trim});
-get_opts_split([global | T],{Part,_Global,Trim}) ->
- get_opts_split(T,{Part,true,Trim});
-get_opts_split([trim | T],{Part,Global,_Trim}) ->
- get_opts_split(T,{Part,Global,true});
+get_opts_split([],{Part,Global,Trim,TrimAll}) ->
+ {Part,Global,Trim,TrimAll};
+get_opts_split([{scope,{A,B}} | T],{_Part,Global,Trim,TrimAll}) ->
+ get_opts_split(T,{{A,B},Global,Trim,TrimAll});
+get_opts_split([global | T],{Part,_Global,Trim,TrimAll}) ->
+ get_opts_split(T,{Part,true,Trim,TrimAll});
+get_opts_split([trim | T],{Part,Global,_Trim,TrimAll}) ->
+ get_opts_split(T,{Part,Global,true,TrimAll});
+get_opts_split([trim_all | T],{Part,Global,Trim,_TrimAll}) ->
+ get_opts_split(T,{Part,Global,Trim,true});
get_opts_split(_,_) ->
throw(badopt).
diff --git a/lib/stdlib/test/erl_eval_SUITE.erl b/lib/stdlib/test/erl_eval_SUITE.erl
index b55324161b..3427f431c5 100644
--- a/lib/stdlib/test/erl_eval_SUITE.erl
+++ b/lib/stdlib/test/erl_eval_SUITE.erl
@@ -1458,6 +1458,30 @@ eep43(Config) when is_list(Config) ->
"lists:map(fun (X) -> X#{price := 0} end,
[#{hello => 0, price => nil}]).",
[#{hello => 0, price => 0}]),
+ check(fun () ->
+ Map = #{ <<33:333>> => "wat" },
+ #{ <<33:333>> := "wat" } = Map
+ end,
+ "begin "
+ " Map = #{ <<33:333>> => \"wat\" }, "
+ " #{ <<33:333>> := \"wat\" } = Map "
+ "end.",
+ #{ <<33:333>> => "wat" }),
+ check(fun () ->
+ K1 = 1,
+ K2 = <<42:301>>,
+ K3 = {3,K2},
+ Map = #{ K1 => 1, K2 => 2, K3 => 3, {2,2} => 4},
+ #{ K1 := 1, K2 := 2, K3 := 3, {2,2} := 4} = Map
+ end,
+ "begin "
+ " K1 = 1, "
+ " K2 = <<42:301>>, "
+ " K3 = {3,K2}, "
+ " Map = #{ K1 => 1, K2 => 2, K3 => 3, {2,2} => 4}, "
+ " #{ K1 := 1, K2 := 2, K3 := 3, {2,2} := 4} = Map "
+ "end.",
+ #{ 1 => 1, <<42:301>> => 2, {3,<<42:301>>} => 3, {2,2} => 4}),
error_check("[camembert]#{}.", {badarg,[camembert]}),
error_check("#{} = 1.", {badmatch,1}),
ok.
diff --git a/lib/stdlib/test/erl_internal_SUITE.erl b/lib/stdlib/test/erl_internal_SUITE.erl
index b6b3c004ea..197a7a33eb 100644
--- a/lib/stdlib/test/erl_internal_SUITE.erl
+++ b/lib/stdlib/test/erl_internal_SUITE.erl
@@ -1,7 +1,7 @@
%%
%% %CopyrightBegin%
%%
-%% Copyright Ericsson AB 1999-2011. All Rights Reserved.
+%% Copyright Ericsson AB 1999-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
@@ -51,7 +51,7 @@ end_per_group(_GroupName, Config) ->
-define(default_timeout, ?t:minutes(2)).
init_per_testcase(_Case, Config) ->
- ?line Dog = test_server:timetrap(?default_timeout),
+ Dog = test_server:timetrap(?default_timeout),
[{watchdog, Dog}|Config].
end_per_testcase(_Case, Config) ->
@@ -63,27 +63,50 @@ behav(suite) -> [];
behav(doc) ->
["Check that the behaviour callbacks are correctly defined"];
behav(_) ->
- ?line check_behav_list([{start,2}, {stop,1}],
- application:behaviour_info(callbacks)),
- ?line check_behav_list([{init,1}, {handle_call,3}, {handle_cast,2},
- {handle_info,2}, {terminate,2}, {code_change,3}],
- gen_server:behaviour_info(callbacks)),
- ?line check_behav_list([{init,1}, {handle_event,3}, {handle_sync_event,4},
- {handle_info,3}, {terminate,3}, {code_change,4}],
- gen_fsm:behaviour_info(callbacks)),
- ?line check_behav_list([{init,1}, {handle_event,2}, {handle_call,2},
- {handle_info,2}, {terminate,2}, {code_change,3}],
- gen_event:behaviour_info(callbacks)),
- ?line check_behav_list( [{init,1}, {terminate,2}],
- supervisor_bridge:behaviour_info(callbacks)),
- ?line check_behav_list([{init,1}],
- supervisor:behaviour_info(callbacks)),
- ok.
+ Modules = [application, gen_server, gen_fsm, gen_event,
+ supervisor_bridge, supervisor],
+ lists:foreach(fun check_behav/1, Modules).
+
+check_behav(Module) ->
+ Callbacks = callbacks(Module),
+ Optional = optional_callbacks(Module),
+ check_behav_list(Callbacks, Module:behaviour_info(callbacks)),
+ check_behav_list(Optional, Module:behaviour_info(optional_callbacks)).
check_behav_list([], []) -> ok;
check_behav_list([L | L1], L2) ->
- ?line true = lists:member(L, L2),
- ?line L3 = lists:delete(L, L2),
+ true = lists:member(L, L2),
+ L3 = lists:delete(L, L2),
check_behav_list(L1, L3).
-
+callbacks(application) ->
+ [{start,2}, {stop,1}];
+callbacks(gen_server) ->
+ [{init,1}, {handle_call,3}, {handle_cast,2},
+ {handle_info,2}, {terminate,2}, {code_change,3},
+ {format_status,2}];
+callbacks(gen_fsm) ->
+ [{init,1}, {handle_event,3}, {handle_sync_event,4},
+ {handle_info,3}, {terminate,3}, {code_change,4},
+ {format_status,2}];
+callbacks(gen_event) ->
+ [{init,1}, {handle_event,2}, {handle_call,2},
+ {handle_info,2}, {terminate,2}, {code_change,3},
+ {format_status,2}];
+callbacks(supervisor_bridge) ->
+ [{init,1}, {terminate,2}];
+callbacks(supervisor) ->
+ [{init,1}].
+
+optional_callbacks(application) ->
+ [];
+optional_callbacks(gen_server) ->
+ [{format_status,2}];
+optional_callbacks(gen_fsm) ->
+ [{format_status,2}];
+optional_callbacks(gen_event) ->
+ [{format_status,2}];
+optional_callbacks(supervisor_bridge) ->
+ [];
+optional_callbacks(supervisor) ->
+ [].
diff --git a/lib/stdlib/test/erl_lint_SUITE.erl b/lib/stdlib/test/erl_lint_SUITE.erl
index ea61b2082b..f8a99f653a 100644
--- a/lib/stdlib/test/erl_lint_SUITE.erl
+++ b/lib/stdlib/test/erl_lint_SUITE.erl
@@ -42,6 +42,7 @@
unused_vars_warn_rec/1,
unused_vars_warn_fun/1,
unused_vars_OTP_4858/1,
+ unused_unsafe_vars_warn/1,
export_vars_warn/1,
shadow_vars/1,
unused_import/1,
@@ -55,7 +56,7 @@
otp_11772/1, otp_11771/1, otp_11872/1,
export_all/1,
bif_clash/1,
- behaviour_basic/1, behaviour_multiple/1,
+ behaviour_basic/1, behaviour_multiple/1, otp_11861/1,
otp_7550/1,
otp_8051/1,
format_warn/1,
@@ -63,7 +64,7 @@
too_many_arguments/1,
basic_errors/1,bin_syntax_errors/1,
predef/1,
- maps/1,maps_type/1
+ maps/1,maps_type/1,otp_11851/1
]).
% Default timetrap timeout (set in init_per_testcase).
@@ -89,16 +90,16 @@ all() ->
otp_5362, otp_5371, otp_7227, otp_5494, otp_5644,
otp_5878, otp_5917, otp_6585, otp_6885, otp_10436, otp_11254,
otp_11772, otp_11771, otp_11872, export_all,
- bif_clash, behaviour_basic, behaviour_multiple,
+ bif_clash, behaviour_basic, behaviour_multiple, otp_11861,
otp_7550, otp_8051, format_warn, {group, on_load},
too_many_arguments, basic_errors, bin_syntax_errors, predef,
- maps, maps_type].
+ maps, maps_type, otp_11851].
groups() ->
[{unused_vars_warn, [],
[unused_vars_warn_basic, unused_vars_warn_lc,
unused_vars_warn_rec, unused_vars_warn_fun,
- unused_vars_OTP_4858]},
+ unused_vars_OTP_4858, unused_unsafe_vars_warn]},
{on_load, [], [on_load_successful, on_load_failing]}].
init_per_suite(Config) ->
@@ -730,6 +731,48 @@ unused_vars_OTP_4858(Config) when is_list(Config) ->
?line [] = run(Config, Ts),
ok.
+unused_unsafe_vars_warn(Config) when is_list(Config) ->
+ Ts = [{unused_unsafe1,
+ <<"t1() ->
+ UnusedVar1 = unused1,
+ try
+ UnusedVar2 = unused2
+ catch
+ _:_ ->
+ ok
+ end,
+ ok.
+ ">>,
+ [warn_unused_vars],
+ {warnings,[{2,erl_lint,{unused_var,'UnusedVar1'}},
+ {4,erl_lint,{unused_var,'UnusedVar2'}}]}},
+ {unused_unsafe2,
+ <<"t2() ->
+ try
+ X = 1
+ catch
+ _:_ -> ok
+ end.
+ ">>,
+ [warn_unused_vars],
+ {warnings,[{3,erl_lint,{unused_var,'X'}}]}},
+ {unused_unsafe2,
+ <<"t3(X, Y) ->
+ X andalso Y.
+ ">>,
+ [warn_unused_vars],
+ []},
+ {unused_unsafe4,
+ <<"t4() ->
+ _ = (catch X = X = 1),
+ _ = case ok of _ -> fun() -> ok end end,
+ fun (X) -> X end.
+ ">>,
+ [warn_unused_vars],
+ []}],
+ run(Config, Ts),
+ ok.
+
export_vars_warn(doc) ->
"Warnings for exported variables";
export_vars_warn(suite) -> [];
@@ -808,7 +851,19 @@ export_vars_warn(Config) when is_list(Config) ->
[],
{error,[{9,erl_lint,{unbound_var,'B'}}],
[{9,erl_lint,{exported_var,'Y',{'receive',2}}},
- {10,erl_lint,{shadowed_var,'B',generate}}]}}
+ {10,erl_lint,{shadowed_var,'B',generate}}]}},
+
+ {exp4,
+ <<"t(X) ->
+ if true -> Z = X end,
+ case X of
+ 1 -> Z;
+ 2 -> X
+ end,
+ Z = X.
+ ">>,
+ [],
+ {warnings,[{7,erl_lint,{exported_var,'Z',{'if',2}}}]}}
],
?line [] = run(Config, Ts),
ok.
@@ -832,8 +887,15 @@ shadow_vars(Config) when is_list(Config) ->
">>,
[nowarn_shadow_vars],
{error,[{9,erl_lint,{unbound_var,'B'}}],
- [{9,erl_lint,{exported_var,'Y',{'receive',2}}}]}}],
-
+ [{9,erl_lint,{exported_var,'Y',{'receive',2}}}]}},
+ {shadow2,
+ <<"t() ->
+ _ = (catch MS = MS = 1), % MS used unsafe
+ _ = case ok of _ -> fun() -> ok end end,
+ fun (MS) -> MS end. % MS not shadowed here
+ ">>,
+ [],
+ []}],
?line [] = run(Config, Ts),
ok.
@@ -958,6 +1020,45 @@ unsafe_vars(Config) when is_list(Config) ->
[warn_unused_vars],
{errors,[{3,erl_lint,{unsafe_var,'X',{'if',2}}},
{4,erl_lint,{unsafe_var,'X',{'if',2}}}],
+ []}},
+ {unsafe8,
+ <<"t8(X) ->
+ case X of _ -> catch _Y = 1 end,
+ _Y."
+ >>,
+ [],
+ {errors,[{3,erl_lint,{unsafe_var,'_Y',{'catch',2}}}],
+ []}},
+ {unsafe9,
+ <<"t9(X) ->
+ case X of
+ 1 ->
+ catch A = 1, % unsafe only here
+ B = 1,
+ C = 1,
+ D = 1;
+ 2 ->
+ A = 2,
+ % B not bound here
+ C = 2,
+ catch D = 2; % unsafe in two clauses
+ 3 ->
+ A = 3,
+ B = 3,
+ C = 3,
+ catch D = 3; % unsafe in two clauses
+ 4 ->
+ A = 4,
+ B = 4,
+ C = 4,
+ D = 4
+ end,
+ {A,B,C,D}."
+ >>,
+ [],
+ {errors,[{24,erl_lint,{unsafe_var,'A',{'catch',4}}},
+ {24,erl_lint,{unsafe_var,'B',{'case',2}}},
+ {24,erl_lint,{unsafe_var,'D',{'case',2}}}],
[]}}
],
?line [] = run(Config, Ts),
@@ -2648,8 +2749,9 @@ otp_11872(Config) when is_list(Config) ->
t() ->
1.
">>,
- {error,[{6,erl_lint,{undefined_type,{product,0}}}],
- [{8,erl_lint,{new_var_arity_type,map}}]} =
+ {error,[{6,erl_lint,{undefined_type,{product,0}}},
+ {8,erl_lint,{undefined_type,{dict,0}}}],
+ [{8,erl_lint,{new_builtin_type,{map,0}}}]} =
run_test2(Config, Ts, []),
ok.
@@ -3080,6 +3182,193 @@ behaviour_multiple(Config) when is_list(Config) ->
?line [] = run(Config, Ts),
ok.
+otp_11861(doc) ->
+ "OTP-11861. behaviour_info() and -callback.";
+otp_11861(suite) -> [];
+otp_11861(Conf) when is_list(Conf) ->
+ CallbackFiles = [callback1, callback2, callback3,
+ bad_behaviour1, bad_behaviour2],
+ lists:foreach(fun(M) ->
+ F = filename:join(?datadir, M),
+ Opts = [{outdir,?privdir}, return],
+ {ok, M, []} = compile:file(F, Opts)
+ end, CallbackFiles),
+ CodePath = code:get_path(),
+ true = code:add_path(?privdir),
+ Ts = [{otp_11861_1,
+ <<"
+ -export([b1/1]).
+ -behaviour(callback1).
+ -behaviour(callback2).
+
+ -spec b1(atom()) -> integer().
+ b1(A) when is_atom(A)->
+ 3.
+ ">>,
+ [],
+ %% b2/1 is optional in both modules
+ {warnings,[{4,erl_lint,
+ {conflicting_behaviours,{b1,1},callback2,3,callback1}}]}},
+ {otp_11861_2,
+ <<"
+ -export([b2/1]).
+ -behaviour(callback1).
+ -behaviour(callback2).
+
+ -spec b2(integer()) -> atom().
+ b2(I) when is_integer(I)->
+ a.
+ ">>,
+ [],
+ %% b2/1 is optional in callback2, but not in callback1
+ {warnings,[{3,erl_lint,{undefined_behaviour_func,{b1,1},callback1}},
+ {4,erl_lint,
+ {conflicting_behaviours,{b2,1},callback2,3,callback1}}]}},
+ {otp_11861_3,
+ <<"
+ -callback b(_) -> atom().
+ -optional_callbacks({b1,1}). % non-existing and ignored
+ ">>,
+ [],
+ []},
+ {otp_11861_4,
+ <<"
+ -callback b(_) -> atom().
+ -optional_callbacks([{b1,1}]). % non-existing
+ ">>,
+ [],
+ %% No behaviour-info(), but callback.
+ {errors,[{3,erl_lint,{undefined_callback,{lint_test,b1,1}}}],[]}},
+ {otp_11861_5,
+ <<"
+ -optional_callbacks([{b1,1}]). % non-existing
+ ">>,
+ [],
+ %% No behaviour-info() and no callback: warning anyway
+ {errors,[{2,erl_lint,{undefined_callback,{lint_test,b1,1}}}],[]}},
+ {otp_11861_6,
+ <<"
+ -optional_callbacks([b1/1]). % non-existing
+ behaviour_info(callbacks) -> [{b1,1}].
+ ">>,
+ [],
+ %% behaviour-info() and no callback: warning anyway
+ {errors,[{2,erl_lint,{undefined_callback,{lint_test,b1,1}}}],[]}},
+ {otp_11861_7,
+ <<"
+ -optional_callbacks([b1/1]). % non-existing
+ -callback b(_) -> atom().
+ behaviour_info(callbacks) -> [{b1,1}].
+ ">>,
+ [],
+ %% behaviour-info() callback: warning
+ {errors,[{2,erl_lint,{undefined_callback,{lint_test,b1,1}}},
+ {3,erl_lint,{behaviour_info,{lint_test,b,1}}}],
+ []}},
+ {otp_11861_8,
+ <<"
+ -callback b(_) -> atom().
+ -optional_callbacks([b/1, {b, 1}]).
+ ">>,
+ [],
+ {errors,[{3,erl_lint,{redefine_optional_callback,{b,1}}}],[]}},
+ {otp_11861_9,
+ <<"
+ -behaviour(gen_server).
+ -export([handle_call/3,handle_cast/2,handle_info/2,
+ code_change/3, init/1, terminate/2]).
+ handle_call(_, _, _) -> ok.
+ handle_cast(_, _) -> ok.
+ handle_info(_, _) -> ok.
+ code_change(_, _, _) -> ok.
+ init(_) -> ok.
+ terminate(_, _) -> ok.
+ ">>,
+ [],
+ []},
+ {otp_11861_9,
+ <<"
+ -behaviour(gen_server).
+ -export([handle_call/3,handle_cast/2,handle_info/2,
+ code_change/3, init/1, terminate/2, format_status/2]).
+ handle_call(_, _, _) -> ok.
+ handle_cast(_, _) -> ok.
+ handle_info(_, _) -> ok.
+ code_change(_, _, _) -> ok.
+ init(_) -> ok.
+ terminate(_, _) -> ok.
+ format_status(_, _) -> ok. % optional callback
+ ">>,
+ [],
+ %% Nothing...
+ []},
+ {otp_11861_10,
+ <<"
+ -optional_callbacks([{b1,1,bad}]). % badly formed and ignored
+ behaviour_info(callbacks) -> [{b1,1}].
+ ">>,
+ [],
+ []},
+ {otp_11861_11,
+ <<"
+ -behaviour(bad_behaviour1).
+ ">>,
+ [],
+ {warnings,[{2,erl_lint,
+ {ill_defined_behaviour_callbacks,bad_behaviour1}}]}},
+ {otp_11861_12,
+ <<"
+ -behaviour(non_existing_behaviour).
+ ">>,
+ [],
+ {warnings,[{2,erl_lint,
+ {undefined_behaviour,non_existing_behaviour}}]}},
+ {otp_11861_13,
+ <<"
+ -behaviour(bad_behaviour_none).
+ ">>,
+ [],
+ {warnings,[{2,erl_lint,{undefined_behaviour,bad_behaviour_none}}]}},
+ {otp_11861_14,
+ <<"
+ -callback b(_) -> atom().
+ ">>,
+ [],
+ []},
+ {otp_11861_15,
+ <<"
+ -optional_callbacks([{b1,1,bad}]). % badly formed
+ -callback b(_) -> atom().
+ ">>,
+ [],
+ []},
+ {otp_11861_16,
+ <<"
+ -callback b(_) -> atom().
+ -callback b(_) -> atom().
+ ">>,
+ [],
+ {errors,[{3,erl_lint,{redefine_callback,{b,1}}}],[]}},
+ {otp_11861_17,
+ <<"
+ -behaviour(bad_behaviour2).
+ ">>,
+ [],
+ {warnings,[{2,erl_lint,{undefined_behaviour_callbacks,
+ bad_behaviour2}}]}},
+ {otp_11861_18,
+ <<"
+ -export([f1/1]).
+ -behaviour(callback3).
+ f1(_) -> ok.
+ ">>,
+ [],
+ []}
+ ],
+ ?line [] = run(Conf, Ts),
+ true = code:set_path(CodePath),
+ ok.
+
otp_7550(doc) ->
"Test that the new utf8/utf16/utf32 types do not allow size or unit specifiers.";
otp_7550(Config) when is_list(Config) ->
@@ -3145,8 +3434,8 @@ format_warn(Config) when is_list(Config) ->
ok.
format_level(Level, Count, Config) ->
- ?line W = get_compilation_warnings(Config, "format",
- [{warn_format, Level}]),
+ ?line W = get_compilation_result(Config, "format",
+ [{warn_format, Level}]),
%% Pick out the 'format' warnings.
?line FW = lists:filter(fun({_Line, erl_lint, {format_error, _}}) -> true;
(_) -> false
@@ -3330,42 +3619,22 @@ bin_syntax_errors(Config) ->
ok.
predef(doc) ->
- "OTP-10342: Predefined types: array(), digraph(), and so on";
+ "OTP-10342: No longer predefined types: array(), digraph(), and so on";
predef(suite) -> [];
predef(Config) when is_list(Config) ->
- W = get_compilation_warnings(Config, "predef", []),
+ W = get_compilation_result(Config, "predef", []),
[] = W,
- W2 = get_compilation_warnings(Config, "predef2", []),
- Tag = deprecated_builtin_type,
- [{7,erl_lint,{Tag,{array,0},{array,array,1},"OTP 18.0"}},
- {12,erl_lint,{Tag,{dict,0},{dict,dict,2},"OTP 18.0"}},
- {17,erl_lint,{Tag,{digraph,0},{digraph,graph},"OTP 18.0"}},
- {27,erl_lint,{Tag,{gb_set,0},{gb_sets,set,1},"OTP 18.0"}},
- {32,erl_lint,{Tag,{gb_tree,0},{gb_trees,tree,2},"OTP 18.0"}},
- {37,erl_lint,{Tag,{queue,0},{queue,queue,1},"OTP 18.0"}},
- {42,erl_lint,{Tag,{set,0},{sets,set,1},"OTP 18.0"}},
- {47,erl_lint,{Tag,{tid,0},{ets,tid},"OTP 18.0"}}] = W2,
- Ts = [{otp_10342_1,
- <<"-compile(nowarn_deprecated_type).
-
- -spec t(dict()) -> non_neg_integer().
-
- t(D) ->
- erlang:phash2(D, 3000).
- ">>,
- {[nowarn_unused_function]},
- []},
- {otp_10342_2,
- <<"-spec t(dict()) -> non_neg_integer().
-
- t(D) ->
- erlang:phash2(D, 3000).
- ">>,
- {[nowarn_unused_function]},
- {warnings,[{1,erl_lint,
- {deprecated_builtin_type,{dict,0},{dict,dict,2},
- "OTP 18.0"}}]}}],
- [] = run(Config, Ts),
+ %% dict(), digraph() and so on were removed in Erlang/OTP 18.0.
+ E2 = get_compilation_result(Config, "predef2", []),
+ Tag = undefined_type,
+ {[{7,erl_lint,{Tag,{array,0}}},
+ {12,erl_lint,{Tag,{dict,0}}},
+ {17,erl_lint,{Tag,{digraph,0}}},
+ {27,erl_lint,{Tag,{gb_set,0}}},
+ {32,erl_lint,{Tag,{gb_tree,0}}},
+ {37,erl_lint,{Tag,{queue,0}}},
+ {42,erl_lint,{Tag,{set,0}}},
+ {47,erl_lint,{Tag,{tid,0}}}],[]} = E2,
ok.
maps(Config) ->
@@ -3398,7 +3667,8 @@ maps(Config) ->
g := 1 + 1,
h := _,
i := (_X = _Y),
- j := (x ! y) }) ->
+ j := (x ! y),
+ <<0:300>> := 33}) ->
{A,F}.
">>,
[],
@@ -3411,9 +3681,10 @@ maps(Config) ->
{errors,[{1,erl_lint,illegal_map_construction},
{1,erl_lint,{unbound_var,'X'}}],
[]}},
- {errors_in_map_keys,
+ {legal_map_construction,
<<"t(V) -> #{ a => 1,
#{a=>V} => 2,
+ #{{a,V}=>V} => 2,
#{ \"hi\" => wazzup, hi => ho } => yep,
[try a catch _:_ -> b end] => nope,
ok => 1.0,
@@ -3425,11 +3696,7 @@ maps(Config) ->
}.
">>,
[],
- {errors,[{2,erl_lint,{illegal_map_key_variable,'V'}},
- {4,erl_lint,illegal_map_key},
- {6,erl_lint,illegal_map_key},
- {8,erl_lint,illegal_map_key},
- {10,erl_lint,illegal_map_key}],[]}},
+ []},
{errors_in_map_keys_pattern,
<<"t(#{ a := 2,
#{} := A,
@@ -3440,8 +3707,8 @@ maps(Config) ->
A.
">>,
[],
- {errors,[{4,erl_lint,illegal_map_key},
- {6,erl_lint,{illegal_map_key_variable,'V'}}],[]}}],
+ {errors,[{4,erl_lint,illegal_map_construction},
+ {6,erl_lint,illegal_map_key}],[]}}],
[] = run(Config, Ts),
ok.
@@ -3470,7 +3737,94 @@ maps_type(Config) when is_list(Config) ->
t(M) -> M.
">>,
[],
- {warnings,[{3,erl_lint,{new_var_arity_type,map}}]}}],
+ {warnings,[{3,erl_lint,{new_builtin_type,{map,0}}}]}}],
+ [] = run(Config, Ts),
+ ok.
+
+otp_11851(doc) ->
+ "OTP-11851: More atoms can be used as type names + bug fixes.";
+otp_11851(Config) when is_list(Config) ->
+ Ts = [
+ {otp_11851_1,
+ <<"-export([t/0]).
+ -type range(A, B) :: A | B.
+
+ -type union(A) :: A.
+
+ -type product() :: integer().
+
+ -type tuple(A) :: A.
+
+ -type map(A) :: A.
+
+ -type record() :: a | b.
+
+ -type integer(A) :: A.
+
+ -type atom(A) :: A.
+
+ -type binary(A, B) :: A | B.
+
+ -type 'fun'() :: integer().
+
+ -type 'fun'(X) :: X.
+
+ -type 'fun'(X, Y) :: X | Y.
+
+ -type all() :: range(atom(), integer()) | union(pid()) | product()
+ | tuple(reference()) | map(function()) | record()
+ | integer(atom()) | atom(integer())
+ | binary(pid(), tuple()) | 'fun'(port())
+ | 'fun'() | 'fun'(<<>>, 'none').
+
+ -spec t() -> all().
+
+ t() ->
+ a.
+ ">>,
+ [],
+ []},
+ {otp_11851_2,
+ <<"-export([a/1, b/1, t/0]).
+
+ -callback b(_) -> integer().
+
+ -callback ?MODULE:a(_) -> integer().
+
+ a(_) -> 3.
+
+ b(_) -> a.
+
+ t()-> a.
+ ">>,
+ [],
+ {errors,[{5,erl_lint,{bad_callback,{lint_test,a,1}}}],[]}},
+ {otp_11851_3,
+ <<"-export([a/1]).
+
+ -spec a(_A) -> boolean() when
+ _ :: atom(),
+ _A :: integer().
+
+ a(_) -> true.
+ ">>,
+ [],
+ {errors,[{4,erl_parse,"bad type variable"}],[]}},
+ {otp_11851_4,
+ <<"
+ -spec a(_) -> ok.
+ -spec a(_) -> ok.
+
+ -spec ?MODULE:a(_) -> ok.
+ -spec ?MODULE:a(_) -> ok.
+ ">>,
+ [],
+ {errors,[{3,erl_lint,{redefine_spec,{a,1}}},
+ {5,erl_lint,{redefine_spec,{lint_test,a,1}}},
+ {6,erl_lint,{redefine_spec,{lint_test,a,1}}},
+ {6,erl_lint,{spec_fun_undefined,{a,1}}}],
+ []}}
+ ],
[] = run(Config, Ts),
ok.
@@ -3487,9 +3841,9 @@ run(Config, Tests) ->
end,
lists:foldl(F, [], Tests).
-%% Compiles a test file and returns the list of warnings.
+%% Compiles a test file and returns the list of warnings/errors.
-get_compilation_warnings(Conf, Filename, Warnings) ->
+get_compilation_result(Conf, Filename, Warnings) ->
?line DataDir = ?datadir,
?line File = filename:join(DataDir, Filename),
{ok,Bin} = file:read_file(File++".erl"),
@@ -3498,6 +3852,7 @@ get_compilation_warnings(Conf, Filename, Warnings) ->
Test = lists:nthtail(Start+Length, FileS),
case run_test(Conf, Test, Warnings) of
{warnings, Ws} -> Ws;
+ {errors,Es,Ws} -> {Es,Ws};
[] -> []
end.
diff --git a/lib/stdlib/test/erl_lint_SUITE_data/bad_behaviour1.erl b/lib/stdlib/test/erl_lint_SUITE_data/bad_behaviour1.erl
new file mode 100644
index 0000000000..230f4b4519
--- /dev/null
+++ b/lib/stdlib/test/erl_lint_SUITE_data/bad_behaviour1.erl
@@ -0,0 +1,6 @@
+-module(bad_behaviour1).
+
+-export([behaviour_info/1]).
+
+behaviour_info(callbacks) ->
+ [{a,1,bad}].
diff --git a/lib/stdlib/test/erl_lint_SUITE_data/bad_behaviour2.erl b/lib/stdlib/test/erl_lint_SUITE_data/bad_behaviour2.erl
new file mode 100644
index 0000000000..bb755ce18b
--- /dev/null
+++ b/lib/stdlib/test/erl_lint_SUITE_data/bad_behaviour2.erl
@@ -0,0 +1,6 @@
+-module(bad_behaviour2).
+
+-export([behaviour_info/1]).
+
+behaviour_info(callbacks) ->
+ undefined.
diff --git a/lib/stdlib/test/erl_lint_SUITE_data/callback1.erl b/lib/stdlib/test/erl_lint_SUITE_data/callback1.erl
new file mode 100644
index 0000000000..3cc5b51879
--- /dev/null
+++ b/lib/stdlib/test/erl_lint_SUITE_data/callback1.erl
@@ -0,0 +1,6 @@
+-module(callback1).
+
+-callback b1(I :: integer()) -> atom().
+-callback b2(A :: atom()) -> integer().
+
+-optional_callbacks([{b2,1}]).
diff --git a/lib/stdlib/test/erl_lint_SUITE_data/callback2.erl b/lib/stdlib/test/erl_lint_SUITE_data/callback2.erl
new file mode 100644
index 0000000000..211cf9f115
--- /dev/null
+++ b/lib/stdlib/test/erl_lint_SUITE_data/callback2.erl
@@ -0,0 +1,6 @@
+-module(callback2).
+
+-callback b1(I :: integer()) -> atom().
+-callback b2(A :: atom()) -> integer().
+
+-optional_callbacks([b1/1, b2/1]).
diff --git a/lib/stdlib/test/erl_lint_SUITE_data/callback3.erl b/lib/stdlib/test/erl_lint_SUITE_data/callback3.erl
new file mode 100644
index 0000000000..97b3ecb860
--- /dev/null
+++ b/lib/stdlib/test/erl_lint_SUITE_data/callback3.erl
@@ -0,0 +1,8 @@
+-module(callback3).
+
+-export([behaviour_info/1]).
+
+behaviour_info(callbacks) ->
+ [{f1, 1}];
+behaviour_info(_) ->
+ undefined.
diff --git a/lib/stdlib/test/erl_lint_SUITE_data/predef.erl b/lib/stdlib/test/erl_lint_SUITE_data/predef.erl
index ee9073aa67..3cb7bf40f1 100644
--- a/lib/stdlib/test/erl_lint_SUITE_data/predef.erl
+++ b/lib/stdlib/test/erl_lint_SUITE_data/predef.erl
@@ -5,8 +5,8 @@
-export_type([array/0, digraph/0, gb_set/0]).
-%% Before Erlang/OTP 17.0 local re-definitions of pre-defined opaque
-%% types were ignored but did not generate any warning.
+%% Since Erlang/OTP 18.0 array() and so on are no longer pre-defined,
+%% so there is nothing special about them at all.
-opaque array() :: atom().
-opaque digraph() :: atom().
-opaque gb_set() :: atom().
diff --git a/lib/stdlib/test/erl_pp_SUITE.erl b/lib/stdlib/test/erl_pp_SUITE.erl
index 927fe0b595..f71446dd64 100644
--- a/lib/stdlib/test/erl_pp_SUITE.erl
+++ b/lib/stdlib/test/erl_pp_SUITE.erl
@@ -1,7 +1,7 @@
%%
%% %CopyrightBegin%
%%
-%% Copyright Ericsson AB 2006-2013. All Rights Reserved.
+%% Copyright Ericsson AB 2006-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
@@ -42,7 +42,6 @@
-export([ func/1, call/1, recs/1, try_catch/1, if_then/1,
receive_after/1, bits/1, head_tail/1,
cond1/1, block/1, case1/1, ops/1, messages/1,
- old_mnemosyne_syntax/1,
import_export/1, misc_attrs/1, dialyzer_attrs/1,
hook/1,
neg_indent/1,
@@ -50,7 +49,7 @@
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,
- otp_10302/1, otp_10820/1, otp_11100/1]).
+ otp_10302/1, otp_10820/1, otp_11100/1, otp_11861/1]).
%% Internal export.
-export([ehook/6]).
@@ -77,13 +76,13 @@ groups() ->
[{expr, [],
[func, call, recs, try_catch, if_then, receive_after,
bits, head_tail, cond1, block, case1, ops,
- messages, old_mnemosyne_syntax, maps_syntax
+ messages, maps_syntax
]},
{attributes, [], [misc_attrs, import_export, dialyzer_attrs]},
{tickets, [],
[otp_6321, otp_6911, otp_6914, otp_8150, otp_8238,
otp_8473, otp_8522, otp_8567, otp_8664, otp_9147,
- otp_10302, otp_10820, otp_11100]}].
+ otp_10302, otp_10820, otp_11100, otp_11861]}].
init_per_suite(Config) ->
Config.
@@ -561,27 +560,6 @@ messages(Config) when is_list(Config) ->
?line true = "\n" =:= lists:flatten(erl_pp:form({eof,0})),
ok.
-old_mnemosyne_syntax(Config) when is_list(Config) ->
- %% Since we have kept the ':-' token,
- %% better test that we can pretty print it.
- R = {rule,12,sales,2,
- [{clause,12,
- [{var,12,'E'},{atom,12,employee}],
- [],
- [{generate,13,
- {var,13,'E'},
- {call,13,{atom,13,table},[{atom,13,employee}]}},
- {match,14,
- {record_field,14,{var,14,'E'},{atom,14,salary}},
- {atom,14,sales}}]}]},
- ?line "sales(E, employee) :-\n"
- " E <- table(employee),\n"
- " E.salary = sales.\n" =
- lists:flatten(erl_pp:form(R)),
- ok.
-
-
-
import_export(suite) ->
[];
import_export(Config) when is_list(Config) ->
@@ -664,26 +642,6 @@ do_hook(HookFun) ->
AFormChars = erl_pp:form(A, H),
?line true = AChars =:= lists:flatten(AFormChars),
- R = {rule,0,sales,0,
- [{clause,0,[{var,0,'E'},{atom,0,employee}],[],
- [{generate,2,{var,2,'E'},
- {call,2,{atom,2,table},[{atom,2,employee}]}},
- {match,3,
- {record_field,3,{var,3,'E'},{atom,3,salary}},
- {foo,Expr}}]}]},
- RChars = lists:flatten(erl_pp:rule(R, H)),
- R2 = {rule,0,sales,0,
- [{clause,0,[{var,0,'E'},{atom,0,employee}],[],
- [{generate,2,{var,2,'E'},
- {call,2,{atom,2,table},[{atom,2,employee}]}},
- {match,3,
- {record_field,3,{var,3,'E'},{atom,3,salary}},
- {call,0,{atom,0,foo},[Expr2]}}]}]},
- RChars2 = erl_pp:rule(R2),
- ?line true = RChars =:= lists:flatten(RChars2),
- ARChars = erl_pp:form(R, H),
- ?line true = RChars =:= lists:flatten(ARChars),
-
?line "INVALID-FORM:{foo,bar}:" = lists:flatten(erl_pp:expr({foo,bar})),
%% A list (as before R6), not a list of lists.
@@ -874,6 +832,7 @@ type_examples() ->
{ex3,<<"-type paren() :: (ann2()). ">>},
{ex4,<<"-type t1() :: atom(). ">>},
{ex5,<<"-type t2() :: [t1()]. ">>},
+ {ex56,<<"-type integer(A) :: A. ">>},
{ex6,<<"-type t3(Atom) :: integer(Atom). ">>},
{ex7,<<"-type '\\'t::4'() :: t3('\\'foobar'). ">>},
{ex8,<<"-type t5() :: {t1(), t3(foo)}. ">>},
@@ -1204,8 +1163,18 @@ otp_11100(Config) when is_list(Config) ->
[]}}),
ok.
+otp_11861(doc) ->
+ "OTP-11861. behaviour_info() and -callback.";
+otp_11861(suite) -> [];
+otp_11861(Config) when is_list(Config) ->
+ "-optional_callbacks([bar/0]).\n" =
+ pf({attribute,3,optional_callbacks,[{bar,0}]}),
+ "-optional_callbacks([{bar,1,bad}]).\n" =
+ pf({attribute,4,optional_callbacks,[{bar,1,bad}]}),
+ ok.
+
pf(Form) ->
- lists:flatten(erl_pp:form(Form,none)).
+ lists:flatten(erl_pp:form(Form, none)).
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
diff --git a/lib/stdlib/test/erl_scan_SUITE.erl b/lib/stdlib/test/erl_scan_SUITE.erl
index 9be9f641c8..6ef947f0e3 100644
--- a/lib/stdlib/test/erl_scan_SUITE.erl
+++ b/lib/stdlib/test/erl_scan_SUITE.erl
@@ -226,7 +226,7 @@ atoms() ->
punctuations() ->
L = ["<<", "<-", "<=", "<", ">>", ">=", ">", "->", "--",
"-", "++", "+", "=:=", "=/=", "=<", "=>", "==", "=", "/=",
- "/", "||", "|", ":=", ":-", "::", ":"],
+ "/", "||", "|", ":=", "::", ":"],
%% One token at a time:
[begin
W = list_to_atom(S),
diff --git a/lib/stdlib/test/filelib_SUITE.erl b/lib/stdlib/test/filelib_SUITE.erl
index bd313390b3..146d810189 100644
--- a/lib/stdlib/test/filelib_SUITE.erl
+++ b/lib/stdlib/test/filelib_SUITE.erl
@@ -77,7 +77,8 @@ wildcard_one(Config) when is_list(Config) ->
L = filelib:wildcard(Wc),
L = filelib:wildcard(Wc, erl_prim_loader),
L = filelib:wildcard(Wc, "."),
- L = filelib:wildcard(Wc, Dir)
+ L = filelib:wildcard(Wc, Dir),
+ L = filelib:wildcard(Wc, Dir++"/.")
end),
?line file:set_cwd(OldCwd),
?line ok = file:del_dir(Dir),
diff --git a/lib/stdlib/test/filename_SUITE.erl b/lib/stdlib/test/filename_SUITE.erl
index ecd9cff9f9..6f1d1a891d 100644
--- a/lib/stdlib/test/filename_SUITE.erl
+++ b/lib/stdlib/test/filename_SUITE.erl
@@ -1,7 +1,7 @@
%%
%% %CopyrightBegin%
%%
-%% Copyright Ericsson AB 1997-2012. All Rights Reserved.
+%% Copyright Ericsson AB 1997-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
@@ -287,38 +287,66 @@ extension(Config) when is_list(Config) ->
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
join(Config) when is_list(Config) ->
+ %% Whenever joining two elements, test the equivalence between
+ %% join/1 and join/2 (OTP-12158) by using help function
+ %% filename_join/2.
?line "/" = filename:join(["/"]),
?line "/" = filename:join(["//"]),
- ?line "usr/foo.erl" = filename:join("usr","foo.erl"),
- ?line "/src/foo.erl" = filename:join(usr, "/src/foo.erl"),
- ?line "/src/foo.erl" = filename:join(["/src/",'foo.erl']),
- ?line "/src/foo.erl" = filename:join(usr, ["/sr", 'c/foo.erl']),
- ?line "/src/foo.erl" = filename:join("usr", "/src/foo.erl"),
+ "usr/foo.erl" = filename_join("usr","foo.erl"),
+ "/src/foo.erl" = filename_join(usr, "/src/foo.erl"),
+ "/src/foo.erl" = filename_join("/src/",'foo.erl'),
+ "/src/foo.erl" = filename_join(usr, ["/sr", 'c/foo.erl']),
+ "/src/foo.erl" = filename_join("usr", "/src/foo.erl"),
%% Make sure that redundant slashes work too.
?line "a/b/c/d/e/f/g" = filename:join(["a//b/c/////d//e/f/g"]),
- ?line "a/b/c/d/e/f/g" = filename:join(["a//b/c/", "d//e/f/g"]),
- ?line "a/b/c/d/e/f/g" = filename:join(["a//b/c", "d//e/f/g"]),
- ?line "/d/e/f/g" = filename:join(["a//b/c", "/d//e/f/g"]),
- ?line "/d/e/f/g" = filename:join(["a//b/c", "//d//e/f/g"]),
-
- ?line "foo/bar" = filename:join([$f,$o,$o,$/,[]], "bar"),
+ "a/b/c/d/e/f/g" = filename_join("a//b/c/", "d//e/f/g"),
+ "a/b/c/d/e/f/g" = filename_join("a//b/c", "d//e/f/g"),
+ "/d/e/f/g" = filename_join("a//b/c", "/d//e/f/g"),
+ "/d/e/f/g" = filename:join("a//b/c", "//d//e/f/g"),
+
+ "foo/bar" = filename_join([$f,$o,$o,$/,[]], "bar"),
+
+ %% Single dots - should be removed if in the middle of the path,
+ %% but not at the end of the path.
+ "/." = filename:join(["/."]),
+ "/" = filename:join(["/./"]),
+ "/." = filename:join(["/./."]),
+ "./." = filename:join(["./."]),
+
+ "/a/b" = filename_join("/a/.","b"),
+ "/a/b/." = filename_join("/a/.","b/."),
+ "/a/." = filename_join("/a/.","."),
+ "/a/." = filename_join("/a","."),
+ "/a/." = filename_join("/a/.",""),
+ "./." = filename_join("./.","."),
+ "./." = filename_join("./","."),
+ "./." = filename_join("./.",""),
+ "." = filename_join(".",""),
+ "./." = filename_join(".","."),
+
+ %% Trailing slash shall be removed - except the root
+ "/" = filename:join(["/"]),
+ "/" = filename:join(["/./"]),
+ "/a" = filename:join(["/a/"]),
+ "/b" = filename_join("/a/","/b/"),
+ "/a/b" = filename_join("/a/","b/"),
?line case os:type() of
{win32, _} ->
?line "d:/" = filename:join(["D:/"]),
?line "d:/" = filename:join(["D:\\"]),
- ?line "d:/abc" = filename:join(["D:/", "abc"]),
- ?line "d:abc" = filename:join(["D:", "abc"]),
+ "d:/abc" = filename_join("D:/", "abc"),
+ "d:abc" = filename_join("D:", "abc"),
?line "a/b/c/d/e/f/g" =
filename:join(["a//b\\c//\\/\\d/\\e/f\\g"]),
?line "a:usr/foo.erl" =
filename:join(["A:","usr","foo.erl"]),
?line "/usr/foo.erl" =
filename:join(["A:","/usr","foo.erl"]),
- ?line "c:usr" = filename:join("A:","C:usr"),
- ?line "a:usr" = filename:join("A:","usr"),
- ?line "c:/usr" = filename:join("A:", "C:/usr"),
+ "c:usr" = filename_join("A:","C:usr"),
+ "a:usr" = filename_join("A:","usr"),
+ "c:/usr" = filename_join("A:", "C:/usr"),
?line "c:/usr/foo.erl" =
filename:join(["A:","C:/usr","foo.erl"]),
?line "c:usr/foo.erl" =
@@ -329,6 +357,11 @@ join(Config) when is_list(Config) ->
ok
end.
+%% Make sure join([A,B]) is equivalent to join(A,B) (OTP-12158)
+filename_join(A,B) ->
+ Res = filename:join(A,B),
+ Res = filename:join([A,B]).
+
pathtype(Config) when is_list(Config) ->
?line relative = filename:pathtype(".."),
?line relative = filename:pathtype("foo"),
@@ -633,6 +666,53 @@ join_bin(Config) when is_list(Config) ->
?line <<"foo/bar">> = filename:join([$f,$o,$o,$/,[]], <<"bar">>),
+ %% Single dots - should be removed if in the middle of the path,
+ %% but not at the end of the path.
+ %% Also test equivalence between join/1 and join/2 (OTP-12158)
+ <<"/.">> = filename:join([<<"/.">>]),
+ <<"/">> = filename:join([<<"/./">>]),
+ <<"/.">> = filename:join([<<"/./.">>]),
+ <<"./.">> = filename:join([<<"./.">>]),
+
+ <<"/a/b">> = filename:join([<<"/a/.">>,<<"b">>]),
+ <<"/a/b">> = filename:join(<<"/a/.">>,<<"b">>),
+
+ <<"/a/b/.">> = filename:join([<<"/a/.">>,<<"b/.">>]),
+ <<"/a/b/.">> = filename:join(<<"/a/.">>,<<"b/.">>),
+
+ <<"/a/.">> = filename:join([<<"/a/.">>,<<".">>]),
+ <<"/a/.">> = filename:join(<<"/a/.">>,<<".">>),
+
+ <<"/a/.">> = filename:join([<<"/a">>,<<".">>]),
+ <<"/a/.">> = filename:join(<<"/a">>,<<".">>),
+
+ <<"/a/.">> = filename:join([<<"/a/.">>,<<"">>]),
+ <<"/a/.">> = filename:join(<<"/a/.">>,<<"">>),
+
+ <<"./.">> = filename:join([<<"./.">>,<<".">>]),
+ <<"./.">> = filename:join(<<"./.">>,<<".">>),
+
+ <<"./.">> = filename:join([<<"./">>,<<".">>]),
+ <<"./.">> = filename:join(<<"./">>,<<".">>),
+
+ <<"./.">> = filename:join([<<"./.">>,<<"">>]),
+ <<"./.">> = filename:join(<<"./.">>,<<"">>),
+
+ <<".">> = filename:join([<<".">>,<<"">>]),
+ <<".">> = filename:join(<<".">>,<<"">>),
+
+ <<"./.">> = filename:join([<<".">>,<<".">>]),
+ <<"./.">> = filename:join(<<".">>,<<".">>),
+
+ %% Trailing slash shall be removed - except the root
+ <<"/">> = filename:join([<<"/">>]),
+ <<"/">> = filename:join([<<"/./">>]),
+ <<"/a">> = filename:join([<<"/a/">>]),
+ <<"/b">> = filename:join([<<"/a/">>,<<"/b/">>]),
+ <<"/b">> = filename:join(<<"/a/">>,<<"/b/">>),
+ <<"/a/b">> = filename:join([<<"/a/">>,<<"b/">>]),
+ <<"/a/b">> = filename:join(<<"/a/">>,<<"b/">>),
+
?line case os:type() of
{win32, _} ->
?line <<"d:/">> = filename:join([<<"D:/">>]),
diff --git a/lib/stdlib/test/gen_event_SUITE.erl b/lib/stdlib/test/gen_event_SUITE.erl
index 60a1ba8c60..576a5adfce 100644
--- a/lib/stdlib/test/gen_event_SUITE.erl
+++ b/lib/stdlib/test/gen_event_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
@@ -106,7 +106,7 @@ start(Config) when is_list(Config) ->
?line {error, {already_started, _}} =
gen_event:start({global, my_dummy_name}),
- exit(Pid6, shutdown),
+ ok = gen_event:stop({global, my_dummy_name}, shutdown, 10000),
receive
{'EXIT', Pid6, shutdown} -> ok
after 10000 ->
diff --git a/lib/stdlib/test/gen_fsm_SUITE.erl b/lib/stdlib/test/gen_fsm_SUITE.erl
index 39f0442824..dabc10aec4 100644
--- a/lib/stdlib/test/gen_fsm_SUITE.erl
+++ b/lib/stdlib/test/gen_fsm_SUITE.erl
@@ -27,6 +27,9 @@
-export([start1/1, start2/1, start3/1, start4/1, start5/1, start6/1,
start7/1, start8/1, start9/1, start10/1, start11/1, start12/1]).
+-export([stop1/1, stop2/1, stop3/1, stop4/1, stop5/1, stop6/1, stop7/1,
+ stop8/1, stop9/1, stop10/1]).
+
-export([ abnormal1/1, abnormal2/1]).
-export([shutdown/1]).
@@ -66,6 +69,8 @@ groups() ->
[{start, [],
[start1, start2, start3, start4, start5, start6, start7,
start8, start9, start10, start11, start12]},
+ {stop, [],
+ [stop1, stop2, stop3, stop4, stop5, stop6, stop7, stop8, stop9, stop10]},
{abnormal, [], [abnormal1, abnormal2]},
{sys, [],
[sys1, call_format_status, error_format_status, terminate_crash_format,
@@ -281,6 +286,105 @@ start12(Config) when is_list(Config) ->
ok.
+%% Anonymous, reason 'normal'
+stop1(_Config) ->
+ {ok, Pid} = gen_fsm:start(?MODULE, [], []),
+ ok = gen_fsm:stop(Pid),
+ false = erlang:is_process_alive(Pid),
+ {'EXIT',noproc} = (catch gen_fsm:stop(Pid)),
+ ok.
+
+%% Anonymous, other reason
+stop2(_Config) ->
+ {ok,Pid} = gen_fsm:start(?MODULE, [], []),
+ ok = gen_fsm:stop(Pid, other_reason, infinity),
+ false = erlang:is_process_alive(Pid),
+ ok.
+
+%% Anonymous, invalid timeout
+stop3(_Config) ->
+ {ok,Pid} = gen_fsm:start(?MODULE, [], []),
+ {'EXIT',_} = (catch gen_fsm:stop(Pid, other_reason, invalid_timeout)),
+ true = erlang:is_process_alive(Pid),
+ ok = gen_fsm:stop(Pid),
+ false = erlang:is_process_alive(Pid),
+ ok.
+
+%% Registered name
+stop4(_Config) ->
+ {ok,Pid} = gen_fsm:start({local,to_stop},?MODULE, [], []),
+ ok = gen_fsm:stop(to_stop),
+ false = erlang:is_process_alive(Pid),
+ {'EXIT',noproc} = (catch gen_fsm:stop(to_stop)),
+ ok.
+
+%% Registered name and local node
+stop5(_Config) ->
+ {ok,Pid} = gen_fsm:start({local,to_stop},?MODULE, [], []),
+ ok = gen_fsm:stop({to_stop,node()}),
+ false = erlang:is_process_alive(Pid),
+ {'EXIT',noproc} = (catch gen_fsm:stop({to_stop,node()})),
+ ok.
+
+%% Globally registered name
+stop6(_Config) ->
+ {ok, Pid} = gen_fsm:start({global, to_stop}, ?MODULE, [], []),
+ ok = gen_fsm:stop({global,to_stop}),
+ false = erlang:is_process_alive(Pid),
+ {'EXIT',noproc} = (catch gen_fsm:stop({global,to_stop})),
+ ok.
+
+%% 'via' registered name
+stop7(_Config) ->
+ dummy_via:reset(),
+ {ok, Pid} = gen_fsm:start({via, dummy_via, to_stop},
+ ?MODULE, [], []),
+ ok = gen_fsm:stop({via, dummy_via, to_stop}),
+ false = erlang:is_process_alive(Pid),
+ {'EXIT',noproc} = (catch gen_fsm:stop({via, dummy_via, to_stop})),
+ ok.
+
+%% Anonymous on remote node
+stop8(_Config) ->
+ {ok,Node} = test_server:start_node(gen_fsm_SUITE_stop8,slave,[]),
+ Dir = filename:dirname(code:which(?MODULE)),
+ rpc:call(Node,code,add_path,[Dir]),
+ {ok, Pid} = rpc:call(Node,gen_fsm,start,[?MODULE,[],[]]),
+ ok = gen_fsm:stop(Pid),
+ false = rpc:call(Node,erlang,is_process_alive,[Pid]),
+ {'EXIT',noproc} = (catch gen_fsm:stop(Pid)),
+ true = test_server:stop_node(Node),
+ {'EXIT',{{nodedown,Node},_}} = (catch gen_fsm:stop(Pid)),
+ ok.
+
+%% Registered name on remote node
+stop9(_Config) ->
+ {ok,Node} = test_server:start_node(gen_fsm_SUITE_stop9,slave,[]),
+ Dir = filename:dirname(code:which(?MODULE)),
+ rpc:call(Node,code,add_path,[Dir]),
+ {ok, Pid} = rpc:call(Node,gen_fsm,start,[{local,to_stop},?MODULE,[],[]]),
+ ok = gen_fsm:stop({to_stop,Node}),
+ undefined = rpc:call(Node,erlang,whereis,[to_stop]),
+ false = rpc:call(Node,erlang,is_process_alive,[Pid]),
+ {'EXIT',noproc} = (catch gen_fsm:stop({to_stop,Node})),
+ true = test_server:stop_node(Node),
+ {'EXIT',{{nodedown,Node},_}} = (catch gen_fsm:stop({to_stop,Node})),
+ ok.
+
+%% Globally registered name on remote node
+stop10(_Config) ->
+ {ok,Node} = test_server:start_node(gen_fsm_SUITE_stop10,slave,[]),
+ Dir = filename:dirname(code:which(?MODULE)),
+ rpc:call(Node,code,add_path,[Dir]),
+ {ok, Pid} = rpc:call(Node,gen_fsm,start,[{global,to_stop},?MODULE,[],[]]),
+ global:sync(),
+ ok = gen_fsm:stop({global,to_stop}),
+ false = rpc:call(Node,erlang,is_process_alive,[Pid]),
+ {'EXIT',noproc} = (catch gen_fsm:stop({global,to_stop})),
+ true = test_server:stop_node(Node),
+ {'EXIT',noproc} = (catch gen_fsm:stop({global,to_stop})),
+ ok.
+
%% Check that time outs in calls work
abnormal1(suite) -> [];
abnormal1(Config) when is_list(Config) ->
diff --git a/lib/stdlib/test/gen_server_SUITE.erl b/lib/stdlib/test/gen_server_SUITE.erl
index 0f03fda30a..30dabf63c5 100644
--- a/lib/stdlib/test/gen_server_SUITE.erl
+++ b/lib/stdlib/test/gen_server_SUITE.erl
@@ -36,6 +36,9 @@
get_state/1, replace_state/1, call_with_huge_message_queue/1
]).
+-export([stop1/1, stop2/1, stop3/1, stop4/1, stop5/1, stop6/1, stop7/1,
+ stop8/1, stop9/1, stop10/1]).
+
% spawn export
-export([spec_init_local/2, spec_init_global/2, spec_init_via/2,
spec_init_default_timeout/2, spec_init_global_default_timeout/2,
@@ -51,7 +54,7 @@
suite() -> [{ct_hooks,[ts_install_cth]}].
all() ->
- [start, crash, call, cast, cast_fast, info, abcast,
+ [start, {group,stop}, crash, call, cast, cast_fast, info, abcast,
multicall, multicall_down, call_remote1, call_remote2,
call_remote3, call_remote_n1, call_remote_n2,
call_remote_n3, spec_init,
@@ -63,7 +66,8 @@ all() ->
call_with_huge_message_queue].
groups() ->
- [].
+ [{stop, [],
+ [stop1, stop2, stop3, stop4, stop5, stop6, stop7, stop8, stop9, stop10]}].
init_per_suite(Config) ->
Config.
@@ -237,6 +241,105 @@ start(Config) when is_list(Config) ->
process_flag(trap_exit, OldFl),
ok.
+%% Anonymous, reason 'normal'
+stop1(_Config) ->
+ {ok, Pid} = gen_server:start(?MODULE, [], []),
+ ok = gen_server:stop(Pid),
+ false = erlang:is_process_alive(Pid),
+ {'EXIT',noproc} = (catch gen_server:stop(Pid)),
+ ok.
+
+%% Anonymous, other reason
+stop2(_Config) ->
+ {ok,Pid} = gen_server:start(?MODULE, [], []),
+ ok = gen_server:stop(Pid, other_reason, infinity),
+ false = erlang:is_process_alive(Pid),
+ ok.
+
+%% Anonymous, invalid timeout
+stop3(_Config) ->
+ {ok,Pid} = gen_server:start(?MODULE, [], []),
+ {'EXIT',_} = (catch gen_server:stop(Pid, other_reason, invalid_timeout)),
+ true = erlang:is_process_alive(Pid),
+ ok = gen_server:stop(Pid),
+ false = erlang:is_process_alive(Pid),
+ ok.
+
+%% Registered name
+stop4(_Config) ->
+ {ok,Pid} = gen_server:start({local,to_stop},?MODULE, [], []),
+ ok = gen_server:stop(to_stop),
+ false = erlang:is_process_alive(Pid),
+ {'EXIT',noproc} = (catch gen_server:stop(to_stop)),
+ ok.
+
+%% Registered name and local node
+stop5(_Config) ->
+ {ok,Pid} = gen_server:start({local,to_stop},?MODULE, [], []),
+ ok = gen_server:stop({to_stop,node()}),
+ false = erlang:is_process_alive(Pid),
+ {'EXIT',noproc} = (catch gen_server:stop({to_stop,node()})),
+ ok.
+
+%% Globally registered name
+stop6(_Config) ->
+ {ok, Pid} = gen_server:start({global, to_stop}, ?MODULE, [], []),
+ ok = gen_server:stop({global,to_stop}),
+ false = erlang:is_process_alive(Pid),
+ {'EXIT',noproc} = (catch gen_server:stop({global,to_stop})),
+ ok.
+
+%% 'via' registered name
+stop7(_Config) ->
+ dummy_via:reset(),
+ {ok, Pid} = gen_server:start({via, dummy_via, to_stop},
+ ?MODULE, [], []),
+ ok = gen_server:stop({via, dummy_via, to_stop}),
+ false = erlang:is_process_alive(Pid),
+ {'EXIT',noproc} = (catch gen_server:stop({via, dummy_via, to_stop})),
+ ok.
+
+%% Anonymous on remote node
+stop8(_Config) ->
+ {ok,Node} = test_server:start_node(gen_server_SUITE_stop8,slave,[]),
+ Dir = filename:dirname(code:which(?MODULE)),
+ rpc:call(Node,code,add_path,[Dir]),
+ {ok, Pid} = rpc:call(Node,gen_server,start,[?MODULE,[],[]]),
+ ok = gen_server:stop(Pid),
+ false = rpc:call(Node,erlang,is_process_alive,[Pid]),
+ {'EXIT',noproc} = (catch gen_server:stop(Pid)),
+ true = test_server:stop_node(Node),
+ {'EXIT',{{nodedown,Node},_}} = (catch gen_server:stop(Pid)),
+ ok.
+
+%% Registered name on remote node
+stop9(_Config) ->
+ {ok,Node} = test_server:start_node(gen_server_SUITE_stop9,slave,[]),
+ Dir = filename:dirname(code:which(?MODULE)),
+ rpc:call(Node,code,add_path,[Dir]),
+ {ok, Pid} = rpc:call(Node,gen_server,start,[{local,to_stop},?MODULE,[],[]]),
+ ok = gen_server:stop({to_stop,Node}),
+ undefined = rpc:call(Node,erlang,whereis,[to_stop]),
+ false = rpc:call(Node,erlang,is_process_alive,[Pid]),
+ {'EXIT',noproc} = (catch gen_server:stop({to_stop,Node})),
+ true = test_server:stop_node(Node),
+ {'EXIT',{{nodedown,Node},_}} = (catch gen_server:stop({to_stop,Node})),
+ ok.
+
+%% Globally registered name on remote node
+stop10(_Config) ->
+ {ok,Node} = test_server:start_node(gen_server_SUITE_stop10,slave,[]),
+ Dir = filename:dirname(code:which(?MODULE)),
+ rpc:call(Node,code,add_path,[Dir]),
+ {ok, Pid} = rpc:call(Node,gen_server,start,[{global,to_stop},?MODULE,[],[]]),
+ global:sync(),
+ ok = gen_server:stop({global,to_stop}),
+ false = rpc:call(Node,erlang,is_process_alive,[Pid]),
+ {'EXIT',noproc} = (catch gen_server:stop({global,to_stop})),
+ true = test_server:stop_node(Node),
+ {'EXIT',noproc} = (catch gen_server:stop({global,to_stop})),
+ ok.
+
crash(Config) when is_list(Config) ->
?line error_logger_forwarder:register(),
diff --git a/lib/stdlib/test/proc_lib_SUITE.erl b/lib/stdlib/test/proc_lib_SUITE.erl
index 8dca69bac4..b6f1973a05 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-2012. 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
@@ -27,7 +27,7 @@
init_per_group/2,end_per_group/2,
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]).
+ hibernate/1, stop/1]).
-export([ otp_6345/1, init_dont_hang/1]).
-export([hib_loop/1, awaken/1]).
@@ -38,6 +38,7 @@
-export([otp_6345_init/1, init_dont_hang_init/1]).
+-export([system_terminate/4]).
-ifdef(STANDALONE).
-define(line, noop, ).
@@ -49,7 +50,7 @@ suite() -> [{ct_hooks,[ts_install_cth]}].
all() ->
[crash, {group, sync_start}, spawn_opt, hibernate,
- {group, tickets}].
+ {group, tickets}, stop].
groups() ->
[{tickets, [], [otp_6345, init_dont_hang]},
@@ -361,10 +362,94 @@ init_dont_hang(Config) when is_list(Config) ->
exit(Error)
end.
-init_dont_hang_init(Parent) ->
+init_dont_hang_init(_Parent) ->
1 = 2.
+%% Test proc_lib:stop/1,3
+stop(_Config) ->
+ Parent = self(),
+ SysMsgProc =
+ fun() ->
+ receive
+ {system,From,Request} ->
+ sys:handle_system_msg(Request,From,Parent,?MODULE,[],[])
+ end
+ end,
+
+ %% Normal case:
+ %% Process handles system message and terminated with given reason
+ Pid1 = proc_lib:spawn(SysMsgProc),
+ ok = proc_lib:stop(Pid1),
+ false = erlang:is_process_alive(Pid1),
+
+ %% Process does not exit
+ {'EXIT',noproc} = (catch proc_lib:stop(Pid1)),
+
+ %% Badly handled system message
+ DieProc =
+ fun() ->
+ receive
+ {system,_From,_Request} ->
+ exit(die)
+ end
+ end,
+ Pid2 = proc_lib:spawn(DieProc),
+ {'EXIT',{die,_}} = (catch proc_lib:stop(Pid2)),
+
+ %% Hanging process => timeout
+ HangProc =
+ fun() ->
+ receive
+ {system,_From,_Request} ->
+ timer:sleep(5000)
+ end
+ end,
+ Pid3 = proc_lib:spawn(HangProc),
+ {'EXIT',timeout} = (catch proc_lib:stop(Pid3,normal,1000)),
+
+ %% Success case with other reason than 'normal'
+ Pid4 = proc_lib:spawn(SysMsgProc),
+ ok = proc_lib:stop(Pid4,other_reason,infinity),
+ false = erlang:is_process_alive(Pid4),
+
+ %% System message is handled, but process dies with other reason
+ %% than the given (in system_terminate/4 below)
+ Pid5 = proc_lib:spawn(SysMsgProc),
+ {'EXIT',{badmatch,2}} = (catch proc_lib:stop(Pid5,crash,infinity)),
+ false = erlang:is_process_alive(Pid5),
+
+ %% Local registered name
+ Pid6 = proc_lib:spawn(SysMsgProc),
+ register(to_stop,Pid6),
+ ok = proc_lib:stop(to_stop),
+ undefined = whereis(to_stop),
+ false = erlang:is_process_alive(Pid6),
+
+ %% Remote registered name
+ {ok,Node} = test_server:start_node(proc_lib_SUITE_stop,slave,[]),
+ Dir = filename:dirname(code:which(?MODULE)),
+ rpc:call(Node,code,add_path,[Dir]),
+ Pid7 = spawn(Node,SysMsgProc),
+ true = rpc:call(Node,erlang,register,[to_stop,Pid7]),
+ Pid7 = rpc:call(Node,erlang,whereis,[to_stop]),
+ ok = proc_lib:stop({to_stop,Node}),
+ undefined = rpc:call(Node,erlang,whereis,[to_stop]),
+ false = rpc:call(Node,erlang,is_process_alive,[Pid7]),
+
+ %% Local and remote registered name, but non-existing
+ {'EXIT',noproc} = (catch proc_lib:stop(to_stop)),
+ {'EXIT',noproc} = (catch proc_lib:stop({to_stop,Node})),
+
+ true = test_server:stop_node(Node),
+
+ %% Remote registered name, but non-existing node
+ {'EXIT',{{nodedown,Node},_}} = (catch proc_lib:stop({to_stop,Node})),
+ ok.
+system_terminate(crash,_Parent,_Deb,_State) ->
+ 1 = 2;
+system_terminate(Reason,_Parent,_Deb,_State) ->
+ exit(Reason).
%%-----------------------------------------------------------------
%% The error_logger handler used.
diff --git a/lib/stdlib/test/qlc_SUITE.erl b/lib/stdlib/test/qlc_SUITE.erl
index 37fbb5267b..4173a40d14 100644
--- a/lib/stdlib/test/qlc_SUITE.erl
+++ b/lib/stdlib/test/qlc_SUITE.erl
@@ -7891,7 +7891,7 @@ run_test(Config, Extra, {cres, Body, Opts, ExpectedCompileReturn}) ->
{module, _} = code:load_abs(AbsFile, Mod),
Ms0 = erlang:process_info(self(),messages),
- Before = {get(), pps(), ets:all(), Ms0},
+ Before = {{get(), ets:all(), Ms0}, pps()},
%% Prepare the check that the qlc module does not call qlc_pt.
_ = [unload_pt() || {file, Name} <- [code:is_loaded(qlc_pt)],
@@ -7921,12 +7921,29 @@ run_test(Config, Extra, {cres, Body, Opts, ExpectedCompileReturn}) ->
run_test(Config, Extra, Body) ->
run_test(Config, Extra, {cres,Body,[]}).
-wait_for_expected(R, Before, SourceFile, Wait) ->
+wait_for_expected(R, {Strict0,PPS0}=Before, SourceFile, Wait) ->
Ms = erlang:process_info(self(),messages),
- After = {get(), pps(), ets:all(), Ms},
+ After = {_,PPS1} = {{get(), ets:all(), Ms}, pps()},
case {R, After} of
{ok, Before} ->
ok;
+ {ok, {Strict0,_}} ->
+ {Ports0,Procs0} = PPS0,
+ {Ports1,Procs1} = PPS1,
+ case {Ports1 -- Ports0, Procs1 -- Procs0} of
+ {[], []} -> ok;
+ _ when Wait ->
+ timer:sleep(1000),
+ wait_for_expected(R, Before, SourceFile, false);
+ {PortsDiff,ProcsDiff} ->
+ io:format("failure, got ~p~n, expected ~p\n",
+ [PPS1, PPS0]),
+ show("Old port", Ports0 -- Ports1),
+ show("New port", PortsDiff),
+ show("Old proc", Procs0 -- Procs1),
+ show("New proc", ProcsDiff),
+ fail(SourceFile)
+ end;
_ when Wait ->
timer:sleep(1000),
wait_for_expected(R, Before, SourceFile, false);
@@ -7993,7 +8010,7 @@ compile_file(Config, Test0, Opts0) ->
case compile:file(File, Opts) of
{ok, _M, Ws} -> warnings(File, Ws);
{error, [{File,Es}], []} -> {errors, Es, []};
- {error, [{File,Es}], [{File,Ws}]} -> {error, Es, Ws}
+ {error, [{File,Es}], [{File,Ws}]} -> {errors, Es, Ws}
end.
comp_compare(T, T) ->
@@ -8058,6 +8075,17 @@ filename(Name, Config) when is_atom(Name) ->
filename(Name, Config) ->
filename:join(?privdir, Name).
+show(_S, []) ->
+ ok;
+show(S, [{Pid, Name, InitCall}|Pids]) when is_pid(Pid) ->
+ io:format("~s: ~w (~w), ~w: ~p~n",
+ [S, Pid, proc_reg_name(Name), InitCall,
+ erlang:process_info(Pid)]),
+ show(S, Pids);
+show(S, [{Port, _}|Ports]) when is_port(Port)->
+ io:format("~s: ~w: ~p~n", [S, Port, erlang:port_info(Port)]),
+ show(S, Ports).
+
pps() ->
{port_list(), process_list()}.
@@ -8070,6 +8098,9 @@ process_list() ->
safe_second_element(process_info(P, initial_call))} ||
P <- processes(), is_process_alive(P)].
+proc_reg_name({registered_name, Name}) -> Name;
+proc_reg_name([]) -> no_reg_name.
+
safe_second_element({_,Info}) -> Info;
safe_second_element(Other) -> Other.
diff --git a/lib/stdlib/test/stdlib_SUITE.erl b/lib/stdlib/test/stdlib_SUITE.erl
index 3d09bd27ff..6669a21b9c 100644
--- a/lib/stdlib/test/stdlib_SUITE.erl
+++ b/lib/stdlib/test/stdlib_SUITE.erl
@@ -22,14 +22,7 @@
-module(stdlib_SUITE).
-include_lib("test_server/include/test_server.hrl").
-
-% Test server specific exports
--export([all/0, suite/0,groups/0,init_per_suite/1, end_per_suite/1,
- init_per_group/2,end_per_group/2]).
--export([init_per_testcase/2, end_per_testcase/2]).
-
-% Test cases must be exported.
--export([app_test/1, appup_test/1]).
+-compile(export_all).
%%
%% all/1
@@ -37,10 +30,10 @@
suite() -> [{ct_hooks,[ts_install_cth]}].
all() ->
- [app_test, appup_test].
+ [app_test, appup_test, {group,upgrade}].
groups() ->
- [].
+ [{upgrade,[minor_upgrade,major_upgrade]}].
init_per_suite(Config) ->
Config.
@@ -48,9 +41,13 @@ init_per_suite(Config) ->
end_per_suite(_Config) ->
ok.
+init_per_group(upgrade, Config) ->
+ ct_release_test:init(Config);
init_per_group(_GroupName, Config) ->
Config.
+end_per_group(upgrade, Config) ->
+ ct_release_test:cleanup(Config);
end_per_group(_GroupName, Config) ->
Config.
@@ -165,3 +162,19 @@ check_appup([Vsn|Vsns],Instrs,Expected) ->
end;
check_appup([],_,_) ->
ok.
+
+
+minor_upgrade(Config) ->
+ ct_release_test:upgrade(stdlib,minor,{?MODULE,[]},Config).
+
+major_upgrade(Config) ->
+ ct_release_test:upgrade(stdlib,major,{?MODULE,[]},Config).
+
+%% Version numbers are checked by ct_release_test, so there is nothing
+%% more to check here...
+upgrade_init(State) ->
+ State.
+upgrade_upgraded(State) ->
+ State.
+upgrade_downgraded(State) ->
+ State.
diff --git a/lib/stdlib/test/supervisor_SUITE.erl b/lib/stdlib/test/supervisor_SUITE.erl
index 836ea7c030..c98654aef7 100644
--- a/lib/stdlib/test/supervisor_SUITE.erl
+++ b/lib/stdlib/test/supervisor_SUITE.erl
@@ -37,9 +37,11 @@
sup_start_ignore_child/1, sup_start_ignore_temporary_child/1,
sup_start_ignore_temporary_child_start_child/1,
sup_start_ignore_temporary_child_start_child_simple/1,
- sup_start_error_return/1, sup_start_fail/1, sup_stop_infinity/1,
- sup_stop_timeout/1, sup_stop_brutal_kill/1, child_adm/1,
- child_adm_simple/1, child_specs/1, extra_return/1]).
+ sup_start_error_return/1, sup_start_fail/1,
+ sup_start_map/1, sup_start_map_faulty_specs/1,
+ sup_stop_infinity/1, sup_stop_timeout/1, sup_stop_brutal_kill/1,
+ child_adm/1, child_adm_simple/1, child_specs/1, extra_return/1,
+ sup_flags/1]).
%% Tests concept permanent, transient and temporary
-export([ permanent_normal/1, transient_normal/1,
@@ -65,7 +67,8 @@
do_not_save_child_specs_for_temporary_children/1,
simple_one_for_one_scale_many_temporary_children/1,
simple_global_supervisor/1, hanging_restart_loop/1,
- hanging_restart_loop_simple/1]).
+ hanging_restart_loop_simple/1, code_change/1, code_change_map/1,
+ code_change_simple/1, code_change_simple_map/1]).
%%-------------------------------------------------------------------------
@@ -73,8 +76,8 @@ suite() ->
[{ct_hooks,[ts_install_cth]}].
all() ->
- [{group, sup_start}, {group, sup_stop}, child_adm,
- child_adm_simple, extra_return, child_specs,
+ [{group, sup_start}, {group, sup_start_map}, {group, sup_stop}, child_adm,
+ child_adm_simple, extra_return, child_specs, sup_flags,
{group, restart_one_for_one},
{group, restart_one_for_all},
{group, restart_simple_one_for_one},
@@ -85,7 +88,8 @@ all() ->
count_children, do_not_save_start_parameters_for_temporary_children,
do_not_save_child_specs_for_temporary_children,
simple_one_for_one_scale_many_temporary_children, temporary_bystander,
- simple_global_supervisor, hanging_restart_loop, hanging_restart_loop_simple].
+ simple_global_supervisor, hanging_restart_loop, hanging_restart_loop_simple,
+ code_change, code_change_map, code_change_simple, code_change_simple_map].
groups() ->
[{sup_start, [],
@@ -94,6 +98,8 @@ groups() ->
sup_start_ignore_temporary_child_start_child,
sup_start_ignore_temporary_child_start_child_simple,
sup_start_error_return, sup_start_fail]},
+ {sup_start_map, [],
+ [sup_start_map, sup_start_map_faulty_specs]},
{sup_stop, [],
[sup_stop_infinity, sup_stop_timeout,
sup_stop_brutal_kill]},
@@ -256,6 +262,60 @@ sup_start_fail(Config) when is_list(Config) ->
check_exit_reason(Term).
%%-------------------------------------------------------------------------
+%% Tests that the supervisor process starts correctly with map
+%% startspec, and that the full childspec can be read.
+sup_start_map(Config) when is_list(Config) ->
+ process_flag(trap_exit, true),
+ Child1 = #{id=>child1, start=>{supervisor_1, start_child, []}},
+ Child2 = #{id=>child2,
+ start=>{supervisor_1, start_child, []},
+ shutdown=>brutal_kill},
+ Child3 = #{id=>child3,
+ start=>{supervisor_1, start_child, []},
+ type=>supervisor},
+ {ok, Pid} = start_link({ok, {#{}, [Child1,Child2,Child3]}}),
+
+ %% Check default values
+ {ok,#{id:=child1,
+ start:={supervisor_1,start_child,[]},
+ restart:=permanent,
+ shutdown:=5000,
+ type:=worker,
+ modules:=[supervisor_1]}} = supervisor:get_childspec(Pid, child1),
+ {ok,#{id:=child2,
+ start:={supervisor_1,start_child,[]},
+ restart:=permanent,
+ shutdown:=brutal_kill,
+ type:=worker,
+ modules:=[supervisor_1]}} = supervisor:get_childspec(Pid, child2),
+ {ok,#{id:=child3,
+ start:={supervisor_1,start_child,[]},
+ restart:=permanent,
+ shutdown:=infinity,
+ type:=supervisor,
+ modules:=[supervisor_1]}} = supervisor:get_childspec(Pid, child3),
+ {error,not_found} = supervisor:get_childspec(Pid, child4),
+ terminate(Pid, shutdown).
+
+%%-------------------------------------------------------------------------
+%% Tests that the supervisor produces good error messages when start-
+%% and child specs are faulty.
+sup_start_map_faulty_specs(Config) when is_list(Config) ->
+ process_flag(trap_exit, true),
+ Child1 = #{start=>{supervisor_1, start_child, []}},
+ Child2 = #{id=>child2},
+ Child3 = #{id=>child3,
+ start=>{supervisor_1, start_child, []},
+ silly_flag=>true},
+ Child4 = child4,
+ {error,{start_spec,missing_id}} = start_link({ok, {#{}, [Child1]}}),
+ {error,{start_spec,missing_start}} = start_link({ok, {#{}, [Child2]}}),
+ {ok,Pid} = start_link({ok, {#{}, [Child3]}}),
+ terminate(Pid,shutdown),
+ {error,{start_spec,{invalid_child_spec,child4}}} =
+ start_link({ok, {#{}, [Child4]}}).
+
+%%-------------------------------------------------------------------------
%% See sup_stop/1 when Shutdown = infinity, this walue is allowed for
%% children of type supervisor _AND_ worker.
sup_stop_infinity(Config) when is_list(Config) ->
@@ -479,7 +539,7 @@ child_adm_simple(Config) when is_list(Config) ->
%% Tests child specs, invalid formats should be rejected.
child_specs(Config) when is_list(Config) ->
process_flag(trap_exit, true),
- {ok, _Pid} = start_link({ok, {{one_for_one, 2, 3600}, []}}),
+ {ok, Pid} = start_link({ok, {{one_for_one, 2, 3600}, []}}),
{error, _} = supervisor:start_child(sup_test, hej),
%% Bad child specs
@@ -509,6 +569,7 @@ child_specs(Config) when is_list(Config) ->
{error, {invalid_modules,dy}}
= supervisor:start_child(sup_test, B5),
+ {error, {badarg, _}} = supervisor:check_childspecs(B1), % should be list
{error, {invalid_mfa,mfa}} = supervisor:check_childspecs([B1]),
{error, {invalid_restart_type,prmanent}} =
supervisor:check_childspecs([B2]),
@@ -524,6 +585,54 @@ child_specs(Config) when is_list(Config) ->
ok = supervisor:check_childspecs([C3]),
ok = supervisor:check_childspecs([C4]),
ok = supervisor:check_childspecs([C5]),
+
+ {error,{duplicate_child_name,child}} = supervisor:check_childspecs([C1,C2]),
+
+ terminate(Pid, shutdown),
+
+ %% Faulty child specs in supervisor start
+ {error, {start_spec, {invalid_mfa, mfa}}} =
+ start_link({ok, {{one_for_one, 2, 3600}, [B1]}}),
+ {error, {start_spec, {invalid_restart_type, prmanent}}} =
+ start_link({ok, {{simple_one_for_one, 2, 3600}, [B2]}}),
+
+ %% simple_one_for_one needs exactly one child
+ {error,{bad_start_spec,[]}} =
+ start_link({ok, {{simple_one_for_one, 2, 3600}, []}}),
+ {error,{bad_start_spec,[C1,C2]}} =
+ start_link({ok, {{simple_one_for_one, 2, 3600}, [C1,C2]}}),
+
+ ok.
+
+%%-------------------------------------------------------------------------
+%% Test error handling of supervisor flags
+sup_flags(_Config) ->
+ process_flag(trap_exit,true),
+ {error,{supervisor_data,{invalid_strategy,_}}} =
+ start_link({ok, {{none_for_one, 2, 3600}, []}}),
+ {error,{supervisor_data,{invalid_strategy,_}}} =
+ start_link({ok, {#{strategy=>none_for_one}, []}}),
+ {error,{supervisor_data,{invalid_intensity,_}}} =
+ start_link({ok, {{one_for_one, infinity, 3600}, []}}),
+ {error,{supervisor_data,{invalid_intensity,_}}} =
+ start_link({ok, {#{intensity=>infinity}, []}}),
+ {error,{supervisor_data,{invalid_period,_}}} =
+ start_link({ok, {{one_for_one, 2, 0}, []}}),
+ {error,{supervisor_data,{invalid_period,_}}} =
+ start_link({ok, {#{period=>0}, []}}),
+ {error,{supervisor_data,{invalid_period,_}}} =
+ start_link({ok, {{one_for_one, 2, infinity}, []}}),
+ {error,{supervisor_data,{invalid_period,_}}} =
+ start_link({ok, {#{period=>infinity}, []}}),
+
+ %% SupFlags other than a map or a 3-tuple
+ {error,{supervisor_data,{invalid_type,_}}} =
+ start_link({ok, {{one_for_one, 2}, []}}),
+
+ %% Unexpected flags are ignored
+ {ok,Pid} = start_link({ok,{#{silly_flag=>true},[]}}),
+ terminate(Pid,shutdown),
+
ok.
%%-------------------------------------------------------------------------
@@ -1647,6 +1756,186 @@ hanging_restart_loop_simple(Config) when is_list(Config) ->
ok.
%%-------------------------------------------------------------------------
+%% Test the code_change function
+code_change(_Config) ->
+ process_flag(trap_exit, true),
+
+ SupFlags = {one_for_one, 0, 1},
+ {ok, Pid} = start_link({ok, {SupFlags, []}}),
+ [] = supervisor:which_children(Pid),
+
+ %% Change supervisor flags
+ S1 = sys:get_state(Pid),
+ ok = fake_upgrade(Pid,{ok, {{one_for_one, 1, 3}, []}}),
+ S2 = sys:get_state(Pid),
+ true = (S1 /= S2),
+
+ %% Faulty childspec
+ FaultyChild = {child1, permanent, brutal_kill, worker, []}, % missing start
+ {error,{error,{invalid_child_spec,FaultyChild}}} =
+ fake_upgrade(Pid,{ok,{SupFlags,[FaultyChild]}}),
+
+ %% Add child1 and child2
+ Child1 = {child1, {supervisor_1, start_child, []},
+ permanent, 2000, worker, []},
+ Child2 = {child2, {supervisor_1, start_child, []},
+ permanent, brutal_kill, worker, []},
+ ok = fake_upgrade(Pid,{ok,{SupFlags,[Child1,Child2]}}),
+ %% Children are not automatically started
+ {ok,_} = supervisor:restart_child(Pid,child1),
+ {ok,_} = supervisor:restart_child(Pid,child2),
+ [{child2,_,_,_},{child1,_,_,_}] = supervisor:which_children(Pid),
+
+ %% Change child1, remove child2 and add child3
+ Child11 = {child1, {supervisor_1, start_child, []},
+ permanent, 1000, worker, []},
+ Child3 = {child3, {supervisor_1, start_child, []},
+ permanent, brutal_kill, worker, []},
+ ok = fake_upgrade(Pid,{ok, {SupFlags, [Child11,Child3]}}),
+ %% Children are not deleted on upgrade, so it is ok that child2 is
+ %% still here
+ [{child2,_,_,_},{child3,_,_,_},{child1,_,_,_}] =
+ supervisor:which_children(Pid),
+
+ %% Ignore during upgrade
+ ok = fake_upgrade(Pid,ignore),
+
+ %% Error during upgrade
+ {error, faulty_return} = fake_upgrade(Pid,faulty_return),
+
+ %% Faulty flags
+ {error,{error, {invalid_intensity,faulty_intensity}}} =
+ fake_upgrade(Pid,{ok, {{one_for_one,faulty_intensity,1}, []}}),
+ {error,{error,{bad_flags, faulty_flags}}} =
+ fake_upgrade(Pid,{ok, {faulty_flags, []}}),
+
+ terminate(Pid,shutdown).
+
+code_change_map(_Config) ->
+ process_flag(trap_exit, true),
+
+ {ok, Pid} = start_link({ok, {#{}, []}}),
+ [] = supervisor:which_children(Pid),
+
+ %% Change supervisor flags
+ S1 = sys:get_state(Pid),
+ ok = fake_upgrade(Pid,{ok, {#{intensity=>1, period=>3}, []}}),
+ S2 = sys:get_state(Pid),
+ true = (S1 /= S2),
+
+ %% Faulty childspec
+ FaultyChild = #{id=>faulty_child},
+ {error,{error,missing_start}} =
+ fake_upgrade(Pid,{ok,{#{},[FaultyChild]}}),
+
+ %% Add child1 and child2
+ Child1 = #{id=>child1,
+ start=>{supervisor_1, start_child, []},
+ shutdown=>2000},
+ Child2 = #{id=>child2,
+ start=>{supervisor_1, start_child, []}},
+ ok = fake_upgrade(Pid,{ok,{#{},[Child1,Child2]}}),
+ %% Children are not automatically started
+ {ok,_} = supervisor:restart_child(Pid,child1),
+ {ok,_} = supervisor:restart_child(Pid,child2),
+ [{child2,_,_,_},{child1,_,_,_}] = supervisor:which_children(Pid),
+ {ok,#{shutdown:=2000}} = supervisor:get_childspec(Pid,child1),
+
+ %% Change child1, remove child2 and add child3
+ Child11 = #{id=>child1,
+ start=>{supervisor_1, start_child, []},
+ shutdown=>1000},
+ Child3 = #{id=>child3,
+ start=>{supervisor_1, start_child, []}},
+ ok = fake_upgrade(Pid,{ok, {#{}, [Child11,Child3]}}),
+ %% Children are not deleted on upgrade, so it is ok that child2 is
+ %% still here
+ [{child2,_,_,_},{child3,_,_,_},{child1,_,_,_}] =
+ supervisor:which_children(Pid),
+ {ok,#{shutdown:=1000}} = supervisor:get_childspec(Pid,child1),
+
+ %% Ignore during upgrade
+ ok = fake_upgrade(Pid,ignore),
+
+ %% Error during upgrade
+ {error, faulty_return} = fake_upgrade(Pid,faulty_return),
+
+ %% Faulty flags
+ {error,{error, {invalid_intensity,faulty_intensity}}} =
+ fake_upgrade(Pid,{ok, {#{intensity=>faulty_intensity}, []}}),
+
+ terminate(Pid,shutdown).
+
+code_change_simple(_Config) ->
+ process_flag(trap_exit, true),
+
+ SimpleChild1 = {child1,{supervisor_1, start_child, []}, permanent,
+ brutal_kill, worker, []},
+ SimpleFlags = {simple_one_for_one, 0, 1},
+ {ok, SimplePid} = start_link({ok, {SimpleFlags,[SimpleChild1]}}),
+ %% Change childspec
+ SimpleChild11 = {child1,{supervisor_1, start_child, []}, permanent,
+ 1000, worker, []},
+ ok = fake_upgrade(SimplePid,{ok,{SimpleFlags,[SimpleChild11]}}),
+
+ %% Attempt to add child
+ SimpleChild2 = {child2,{supervisor_1, start_child, []}, permanent,
+ brutal_kill, worker, []},
+
+ {error, {error, {ok,[_,_]}}} =
+ fake_upgrade(SimplePid,{ok,{SimpleFlags,[SimpleChild1,SimpleChild2]}}),
+
+ %% Attempt to remove child
+ {error, {error, {ok,[]}}} = fake_upgrade(SimplePid,{ok,{SimpleFlags,[]}}),
+
+ terminate(SimplePid,shutdown),
+ ok.
+
+code_change_simple_map(_Config) ->
+ process_flag(trap_exit, true),
+
+ SimpleChild1 = #{id=>child1,
+ start=>{supervisor_1, start_child, []}},
+ SimpleFlags = #{strategy=>simple_one_for_one},
+ {ok, SimplePid} = start_link({ok, {SimpleFlags,[SimpleChild1]}}),
+ %% Change childspec
+ SimpleChild11 = #{id=>child1,
+ start=>{supervisor_1, start_child, []},
+ shutdown=>1000},
+ ok = fake_upgrade(SimplePid,{ok,{SimpleFlags,[SimpleChild11]}}),
+
+ %% Attempt to add child
+ SimpleChild2 = #{id=>child2,
+ start=>{supervisor_1, start_child, []}},
+ {error, {error, {ok, [_,_]}}} =
+ fake_upgrade(SimplePid,{ok,{SimpleFlags,[SimpleChild1,SimpleChild2]}}),
+
+ %% Attempt to remove child
+ {error, {error, {ok, []}}} =
+ fake_upgrade(SimplePid,{ok,{SimpleFlags,[]}}),
+
+ terminate(SimplePid,shutdown),
+ ok.
+
+fake_upgrade(Pid,NewInitReturn) ->
+ ok = sys:suspend(Pid),
+
+ %% Update state to fake code change
+ %% The #state record in supervisor.erl holds the arguments given
+ %% to the callback init function. By replacing these arguments the
+ %% init function will return something new and by that fake a code
+ %% change (see init function above in this module).
+ Fun = fun(State) ->
+ Size = size(State), % 'args' is the last field in #state.
+ setelement(Size,State,NewInitReturn)
+ end,
+ sys:replace_state(Pid,Fun),
+
+ R = sys:change_code(Pid,gen_server,dummy_vsn,[]),
+ ok = sys:resume(Pid),
+ R.
+
+%%-------------------------------------------------------------------------
terminate(Pid, Reason) when Reason =/= supervisor ->
terminate(dummy, Pid, dummy, Reason).
diff --git a/lib/stdlib/test/sys_SUITE.erl b/lib/stdlib/test/sys_SUITE.erl
index f38bc87ae5..047ee9f1fa 100644
--- a/lib/stdlib/test/sys_SUITE.erl
+++ b/lib/stdlib/test/sys_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
@@ -202,14 +202,7 @@ spec_proc(Mod) ->
{Mod,system_get_state},{throw,fail}},_}} ->
ok
end,
- Mod:stop(),
- WaitForUnregister = fun W() ->
- case whereis(Mod) of
- undefined -> ok;
- _ -> timer:sleep(10), W()
- end
- end,
- WaitForUnregister(),
+ ok = sys:terminate(Mod, normal),
{ok,_} = Mod:start_link(4),
ok = case catch sys:replace_state(Mod, fun(_) -> {} end) of
{} ->
@@ -218,8 +211,7 @@ spec_proc(Mod) ->
{Mod,system_replace_state},{throw,fail}},_}} ->
ok
end,
- Mod:stop(),
- WaitForUnregister(),
+ ok = sys:terminate(Mod, normal),
{ok,_} = Mod:start_link(4),
StateFun = fun(_) -> error(fail) end,
ok = case catch sys:replace_state(Mod, StateFun) of
@@ -231,7 +223,7 @@ spec_proc(Mod) ->
{'EXIT',{{callback_failed,StateFun,{error,fail}},_}} ->
ok
end,
- Mod:stop().
+ ok = sys:terminate(Mod, normal).
%%%%%%%%%%%%%%%%%%%%
%% Dummy server
diff --git a/lib/stdlib/test/sys_sp1.erl b/lib/stdlib/test/sys_sp1.erl
index e84ffcfa12..0fb288991f 100644
--- a/lib/stdlib/test/sys_sp1.erl
+++ b/lib/stdlib/test/sys_sp1.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
@@ -17,7 +17,7 @@
%% %CopyrightEnd%
%%
-module(sys_sp1).
--export([start_link/1, stop/0]).
+-export([start_link/1]).
-export([alloc/0, free/1]).
-export([init/1]).
-export([system_continue/3, system_terminate/4,
@@ -31,10 +31,6 @@
start_link(NumCh) ->
proc_lib:start_link(?MODULE, init, [[self(),NumCh]]).
-stop() ->
- ?MODULE ! stop,
- ok.
-
alloc() ->
?MODULE ! {self(), alloc},
receive
@@ -70,11 +66,7 @@ loop(Chs, Parent, Deb) ->
loop(Chs2, Parent, Deb2);
{system, From, Request} ->
sys:handle_system_msg(Request, From, Parent,
- ?MODULE, Deb, Chs);
- stop ->
- sys:handle_debug(Deb, fun write_debug/3,
- ?MODULE, {in, stop}),
- ok
+ ?MODULE, Deb, Chs)
end.
system_continue(Parent, Deb, Chs) ->
diff --git a/lib/stdlib/test/sys_sp2.erl b/lib/stdlib/test/sys_sp2.erl
index 56a5e4d071..a0847b5838 100644
--- a/lib/stdlib/test/sys_sp2.erl
+++ b/lib/stdlib/test/sys_sp2.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
@@ -17,7 +17,7 @@
%% %CopyrightEnd%
%%
-module(sys_sp2).
--export([start_link/1, stop/0]).
+-export([start_link/1]).
-export([alloc/0, free/1]).
-export([init/1]).
-export([system_continue/3, system_terminate/4,
@@ -30,10 +30,6 @@
start_link(NumCh) ->
proc_lib:start_link(?MODULE, init, [[self(),NumCh]]).
-stop() ->
- ?MODULE ! stop,
- ok.
-
alloc() ->
?MODULE ! {self(), alloc},
receive
@@ -45,11 +41,6 @@ free(Ch) ->
?MODULE ! {free, Ch},
ok.
-%% can't use 2-tuple for state here as we do in sys_sp1, since the 2-tuple
-%% is not compatible with the backward compatibility handling for
-%% sys:get_state in sys.erl
--record(state, {alloc,free}).
-
init([Parent,NumCh]) ->
register(?MODULE, self()),
Chs = channels(NumCh),
@@ -74,11 +65,7 @@ loop(Chs, Parent, Deb) ->
loop(Chs2, Parent, Deb2);
{system, From, Request} ->
sys:handle_system_msg(Request, From, Parent,
- ?MODULE, Deb, Chs);
- stop ->
- sys:handle_debug(Deb, fun write_debug/3,
- ?MODULE, {in, stop}),
- ok
+ ?MODULE, Deb, Chs)
end.
system_continue(Parent, Deb, Chs) ->
@@ -91,17 +78,17 @@ write_debug(Dev, Event, Name) ->
io:format(Dev, "~p event = ~p~n", [Name, Event]).
channels(NumCh) ->
- #state{alloc=[], free=lists:seq(1,NumCh)}.
+ {_Allocated=[], _Free=lists:seq(1,NumCh)}.
-alloc(#state{free=[]}=Channels) ->
- {{error, "no channels available"}, Channels};
-alloc(#state{alloc=Allocated, free=[H|T]}) ->
- {H, #state{alloc=[H|Allocated], free=T}}.
+alloc({_, []}) ->
+ {error, "no channels available"};
+alloc({Allocated, [H|T]}) ->
+ {H, {[H|Allocated], T}}.
-free(Ch, #state{alloc=Alloc, free=Free}=Channels) ->
+free(Ch, {Alloc, Free}=Channels) ->
case lists:member(Ch, Alloc) of
true ->
- #state{alloc=lists:delete(Ch, Alloc), free=[Ch|Free]};
+ {lists:delete(Ch, Alloc), [Ch|Free]};
false ->
Channels
end.