diff options
Diffstat (limited to 'lib/stdlib/test')
| -rw-r--r-- | lib/stdlib/test/erl_internal_SUITE.erl | 65 | ||||
| -rw-r--r-- | lib/stdlib/test/erl_lint_SUITE.erl | 453 | ||||
| -rw-r--r-- | lib/stdlib/test/erl_lint_SUITE_data/bad_behaviour1.erl | 6 | ||||
| -rw-r--r-- | lib/stdlib/test/erl_lint_SUITE_data/bad_behaviour2.erl | 6 | ||||
| -rw-r--r-- | lib/stdlib/test/erl_lint_SUITE_data/callback1.erl | 6 | ||||
| -rw-r--r-- | lib/stdlib/test/erl_lint_SUITE_data/callback2.erl | 6 | ||||
| -rw-r--r-- | lib/stdlib/test/erl_lint_SUITE_data/callback3.erl | 8 | ||||
| -rw-r--r-- | lib/stdlib/test/erl_lint_SUITE_data/predef.erl | 4 | ||||
| -rw-r--r-- | lib/stdlib/test/erl_pp_SUITE.erl | 19 | ||||
| -rw-r--r-- | lib/stdlib/test/gen_event_SUITE.erl | 4 | ||||
| -rw-r--r-- | lib/stdlib/test/gen_fsm_SUITE.erl | 104 | ||||
| -rw-r--r-- | lib/stdlib/test/gen_server_SUITE.erl | 107 | ||||
| -rw-r--r-- | lib/stdlib/test/proc_lib_SUITE.erl | 93 | ||||
| -rw-r--r-- | lib/stdlib/test/sys_SUITE.erl | 16 | ||||
| -rw-r--r-- | lib/stdlib/test/sys_sp1.erl | 14 | ||||
| -rw-r--r-- | lib/stdlib/test/sys_sp2.erl | 33 | 
16 files changed, 815 insertions, 129 deletions
| 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..27f95bd3fa 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) -> @@ -3470,7 +3739,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 +3843,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 +3854,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..046b5cf330 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 @@ -50,7 +50,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]). @@ -83,7 +83,7 @@ groups() ->       {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. @@ -874,6 +874,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 +1205,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/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 336065b258..75796ab1b6 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 42694d8b5d..8b6654dd5e 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/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. | 
