diff options
Diffstat (limited to 'lib/stdlib/test')
25 files changed, 1335 insertions, 305 deletions
diff --git a/lib/stdlib/test/dets_SUITE.erl b/lib/stdlib/test/dets_SUITE.erl index 6be37cbecf..119b4dc7cb 100644 --- a/lib/stdlib/test/dets_SUITE.erl +++ b/lib/stdlib/test/dets_SUITE.erl @@ -2032,6 +2032,12 @@ match(Config, Version) -> CrashPos = if Version =:= 8 -> 5; Version =:= 9 -> 1 end, crash(Fname, ObjPos2+CrashPos), {ok, _} = dets:open_file(T, Args), + case dets:insert_new(T, Obj) of % OTP-12024 + ok -> + bad_object(dets:sync(T), Fname); + Else3 -> + bad_object(Else3, Fname) + end, io:format("Expect corrupt table:~n"), case ins(T, N) of ok -> 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 babf3a49eb..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. @@ -604,20 +604,20 @@ import_export(Config) when is_list(Config) -> misc_attrs(suite) -> []; misc_attrs(Config) when is_list(Config) -> - ?line ok = pp_forms(<<"-module(m). ">>), - ?line ok = pp_forms(<<"-module(m, [Aafjlksfjdlsjflsdfjlsdjflkdsfjlk," - "Blsjfdlslfjsdf]). ">>), - ?line ok = pp_forms(<<"-export([]). ">>), - ?line ok = pp_forms(<<"-export([foo/2, bar/0]). ">>), - ?line ok = pp_forms(<<"-export([bar/0]). ">>), - ?line ok = pp_forms(<<"-import(lists, []). ">>), - ?line ok = pp_forms(<<"-import(lists, [map/2]). ">>), - ?line ok = pp_forms(<<"-import(lists, [map/2, foreach/2]). ">>), - ?line ok = pp_forms(<<"-'wild '({attr2,3}). ">>), - ?line ok = pp_forms(<<"-record(a, {b,c}). ">>), - ?line ok = pp_forms(<<"-record(' a ', {}). ">>), - ?line ok = pp_forms(<<"-record(' a ', {foo = foo:bar()}). ">>), - + ok = pp_forms(<<"-module(m). ">>), + ok = pp_forms(<<"-module(m, [Aafjlksfjdlsjflsdfjlsdjflkdsfjlk," + "Blsjfdlslfjsdf]). ">>), + ok = pp_forms(<<"-export([]). ">>), + ok = pp_forms(<<"-export([foo/2, bar/0]). ">>), + ok = pp_forms(<<"-export([bar/0]). ">>), + ok = pp_forms(<<"-import(lists, []). ">>), + ok = pp_forms(<<"-import(lists, [map/2]). ">>), + ok = pp_forms(<<"-import(lists, [map/2, foreach/2]). ">>), + ok = pp_forms(<<"-'wild '({attr2,3}). ">>), + ok = pp_forms(<<"-record(a, {b,c}). ">>), + ok = pp_forms(<<"-record(' a ', {}). ">>), + ok = pp_forms(<<"-record(' a ', {foo = foo:bar()}). ">>), + ok = pp_forms(<<"-custom1(#{test1 => init/2, test2 => [val/1, val/2]}). ">>), ok. dialyzer_attrs(suite) -> @@ -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/erl_scan_SUITE.erl b/lib/stdlib/test/erl_scan_SUITE.erl index 35067e8116..9be9f641c8 100644 --- a/lib/stdlib/test/erl_scan_SUITE.erl +++ b/lib/stdlib/test/erl_scan_SUITE.erl @@ -204,20 +204,20 @@ reserved_words() -> [begin ?line {RW, true} = {RW, erl_scan:reserved_word(RW)}, S = atom_to_list(RW), - Ts = [{RW,1}], + Ts = [{RW,{1,1}}], ?line test_string(S, Ts) end || RW <- L], ok. atoms() -> - ?line test_string("a - b", [{atom,1,a},{atom,2,b}]), - ?line test_string("'a b'", [{atom,1,'a b'}]), - ?line test_string("a", [{atom,1,a}]), - ?line test_string("a@2", [{atom,1,a@2}]), - ?line test_string([39,65,200,39], [{atom,1,'AÈ'}]), - ?line test_string("ärlig östen", [{atom,1,ärlig},{atom,1,östen}]), + test_string("a + b", [{atom,{1,1},a},{atom,{2,18},b}]), + test_string("'a b'", [{atom,{1,1},'a b'}]), + test_string("a", [{atom,{1,1},a}]), + test_string("a@2", [{atom,{1,1},a@2}]), + test_string([39,65,200,39], [{atom,{1,1},'AÈ'}]), + test_string("ärlig östen", [{atom,{1,1},ärlig},{atom,{1,7},östen}]), ?line {ok,[{atom,_,'$a'}],{1,6}} = erl_scan:string("'$\\a'", {1,1}), ?line test("'$\\a'"), @@ -230,7 +230,7 @@ punctuations() -> %% One token at a time: [begin W = list_to_atom(S), - Ts = [{W,1}], + Ts = [{W,{1,1}}], ?line test_string(S, Ts) end || S <- L], Three = ["/=:=", "<=:=", "==:=", ">=:="], % three tokens... @@ -246,53 +246,60 @@ punctuations() -> [begin W1 = list_to_atom(S1), W2 = list_to_atom(S2), - Ts = [{W1,1},{W2,1}], + Ts = [{W1,{1,1}},{W2,{1,-L2+1}}], ?line test_string(S, Ts) - end || {S,[{_,S1,S2}|_]} <- SL], + end || {S,[{L2,S1,S2}|_]} <- SL], - PTs1 = [{'!',1},{'(',1},{')',1},{',',1},{';',1},{'=',1},{'[',1}, - {']',1},{'{',1},{'|',1},{'}',1}], + PTs1 = [{'!',{1,1}},{'(',{1,2}},{')',{1,3}},{',',{1,4}},{';',{1,5}}, + {'=',{1,6}},{'[',{1,7}},{']',{1,8}},{'{',{1,9}},{'|',{1,10}}, + {'}',{1,11}}], ?line test_string("!(),;=[]{|}", PTs1), - PTs2 = [{'#',1},{'&',1},{'*',1},{'+',1},{'/',1}, - {':',1},{'<',1},{'>',1},{'?',1},{'@',1}, - {'\\',1},{'^',1},{'`',1},{'~',1}], + PTs2 = [{'#',{1,1}},{'&',{1,2}},{'*',{1,3}},{'+',{1,4}},{'/',{1,5}}, + {':',{1,6}},{'<',{1,7}},{'>',{1,8}},{'?',{1,9}},{'@',{1,10}}, + {'\\',{1,11}},{'^',{1,12}},{'`',{1,13}},{'~',{1,14}}], ?line test_string("#&*+/:<>?@\\^`~", PTs2), - ?line test_string(".. ", [{'..',1}]), - ?line test("1 .. 2"), - ?line test_string("...", [{'...',1}]), + test_string(".. ", [{'..',{1,1}}]), + test_string("1 .. 2", + [{integer,{1,1},1},{'..',{1,3}},{integer,{1,6},2}]), + test_string("...", [{'...',{1,1}}]), ok. comments() -> ?line test("a %%\n b"), ?line {ok,[],1} = erl_scan:string("%"), ?line test("a %%\n b"), - ?line {ok,[{atom,_,a},{atom,_,b}],{2,3}} = + {ok,[{atom,{1,1},a},{atom,{2,2},b}],{2,3}} = erl_scan:string("a %%\n b",{1,1}), - ?line {ok,[{atom,_,a},{comment,_,"%%"},{atom,_,b}],{2,3}} = + {ok,[{atom,{1,1},a},{comment,{1,3},"%%"},{atom,{2,2},b}],{2,3}} = erl_scan:string("a %%\n b",{1,1}, [return_comments]), - ?line {ok,[{atom,_,a}, - {white_space,_," "}, - {white_space,_,"\n "}, - {atom,_,b}], - {2,3}} = + {ok,[{atom,{1,1},a}, + {white_space,{1,2}," "}, + {white_space,{1,5},"\n "}, + {atom,{2,2},b}], + {2,3}} = erl_scan:string("a %%\n b",{1,1},[return_white_spaces]), - ?line {ok,[{atom,_,a}, - {white_space,_," "}, - {comment,_,"%%"}, - {white_space,_,"\n "}, - {atom,_,b}], - {2,3}} = erl_scan:string("a %%\n b",{1,1},[return]), + {ok,[{atom,{1,1},a}, + {white_space,{1,2}," "}, + {comment,{1,3},"%%"}, + {white_space,{1,5},"\n "}, + {atom,{2,2},b}], + {2,3}} = erl_scan:string("a %%\n b",{1,1},[return]), ok. errors() -> ?line {error,{1,erl_scan,{string,$',"qa"}},1} = erl_scan:string("'qa"), %' + {error,{{1,1},erl_scan,{string,$',"qa"}},{1,4}} = %' + erl_scan:string("'qa", {1,1}, []), %' ?line {error,{1,erl_scan,{string,$","str"}},1} = %" erl_scan:string("\"str"), %" + {error,{{1,1},erl_scan,{string,$","str"}},{1,5}} = %" + erl_scan:string("\"str", {1,1}, []), %" ?line {error,{1,erl_scan,char},1} = erl_scan:string("$"), - ?line test_string([34,65,200,34], [{string,1,"AÈ"}]), - ?line test_string("\\", [{'\\',1}]), + {error,{{1,1},erl_scan,char},{1,2}} = erl_scan:string("$", {1,1}, []), + test_string([34,65,200,34], [{string,{1,1},"AÈ"}]), + test_string("\\", [{'\\',{1,1}}]), ?line {'EXIT',_} = (catch {foo, erl_scan:string('$\\a', {1,1})}), % type error ?line {'EXIT',_} = @@ -304,7 +311,7 @@ errors() -> integers() -> [begin I = list_to_integer(S), - Ts = [{integer,1,I}], + Ts = [{integer,{1,1},I}], ?line test_string(S, Ts) end || S <- [[N] || N <- lists:seq($0, $9)] ++ ["2323","000"] ], ok. @@ -313,14 +320,16 @@ base_integers() -> [begin B = list_to_integer(BS), I = erlang:list_to_integer(S, B), - Ts = [{integer,1,I}], + Ts = [{integer,{1,1},I}], ?line test_string(BS++"#"++S, Ts) end || {BS,S} <- [{"2","11"}, {"5","23234"}, {"12","05a"}, {"16","abcdef"}, {"16","ABCDEF"}] ], ?line {error,{1,erl_scan,{base,1}},1} = erl_scan:string("1#000"), + {error,{{1,1},erl_scan,{base,1}},{1,2}} = + erl_scan:string("1#000", {1,1}, []), - ?line test_string("12#bc", [{integer,1,11},{atom,1,c}]), + test_string("12#bc", [{integer,{1,1},11},{atom,{1,5},c}]), [begin Str = BS ++ "#" ++ S, @@ -329,40 +338,53 @@ base_integers() -> end || {BS,S} <- [{"3","3"},{"15","f"}, {"12","c"}] ], ?line {ok,[{integer,1,239},{'@',1}],1} = erl_scan:string("16#ef@"), - ?line {ok,[{integer,1,14},{atom,1,g@}],1} = erl_scan:string("16#eg@"), + {ok,[{integer,{1,1},239},{'@',{1,6}}],{1,7}} = + erl_scan:string("16#ef@", {1,1}, []), + {ok,[{integer,{1,1},14},{atom,{1,5},g@}],{1,7}} = + erl_scan:string("16#eg@", {1,1}, []), ok. floats() -> [begin F = list_to_float(FS), - Ts = [{float,1,F}], + Ts = [{float,{1,1},F}], ?line test_string(FS, Ts) end || FS <- ["1.0","001.17","3.31200","1.0e0","1.0E17", "34.21E-18", "17.0E+14"]], - ?line test_string("1.e2", [{integer,1,1},{'.',1},{atom,1,e2}]), + test_string("1.e2", [{integer,{1,1},1},{'.',{1,2}},{atom,{1,3},e2}]), ?line {error,{1,erl_scan,{illegal,float}},1} = erl_scan:string("1.0e400"), + {error,{{1,1},erl_scan,{illegal,float}},{1,8}} = + erl_scan:string("1.0e400", {1,1}, []), [begin - ?line {error,{1,erl_scan,{illegal,float}},1} = erl_scan:string(S) + {error,{1,erl_scan,{illegal,float}},1} = erl_scan:string(S), + {error,{{1,1},erl_scan,{illegal,float}},{1,_}} = + erl_scan:string(S, {1,1}, []) end || S <- ["1.14Ea"]], ok. dots() -> - Dot = [{".", {ok,[{dot,1}],1}}, - {". ", {ok,[{dot,1}],1}}, - {".\n", {ok,[{dot,1}],2}}, - {".%", {ok,[{dot,1}],1}}, - {".\210",{ok,[{dot,1}],1}}, - {".% öh",{ok,[{dot,1}],1}}, - {".%\n", {ok,[{dot,1}],2}}, - {".$", {error,{1,erl_scan,char},1}}, - {".$\\", {error,{1,erl_scan,char},1}}, - {".a", {ok,[{'.',1},{atom,1,a}],1}} + Dot = [{".", {ok,[{dot,1}],1}, {ok,[{dot,{1,1}}],{1,2}}}, + {". ", {ok,[{dot,1}],1}, {ok,[{dot,{1,1}}],{1,3}}}, + {".\n", {ok,[{dot,1}],2}, {ok,[{dot,{1,1}}],{2,1}}}, + {".%", {ok,[{dot,1}],1}, {ok,[{dot,{1,1}}],{1,3}}}, + {".\210",{ok,[{dot,1}],1}, {ok,[{dot,{1,1}}],{1,3}}}, + {".% öh",{ok,[{dot,1}],1}, {ok,[{dot,{1,1}}],{1,6}}}, + {".%\n", {ok,[{dot,1}],2}, {ok,[{dot,{1,1}}],{2,1}}}, + {".$", {error,{1,erl_scan,char},1}, + {error,{{1,2},erl_scan,char},{1,3}}}, + {".$\\", {error,{1,erl_scan,char},1}, + {error,{{1,2},erl_scan,char},{1,4}}}, + {".a", {ok,[{'.',1},{atom,1,a}],1}, + {ok,[{'.',{1,1}},{atom,{1,2},a}],{1,3}}} ], - ?line [R = erl_scan:string(S) || {S, R} <- Dot], + [begin + R = erl_scan:string(S), + R2 = erl_scan:string(S, {1,1}, []) + end || {S, R, R2} <- Dot], ?line {ok,[{dot,_}=T1],{1,2}} = erl_scan:string(".", {1,1}, text), ?line [{column,1},{length,1},{line,1},{text,"."}] = @@ -379,55 +401,55 @@ dots() -> ?line {error,{{1,2},erl_scan,char},{1,4}} = erl_scan:string(".$\\", {1,1}), - ?line test(". "), - ?line test(". "), - ?line test(".\n"), - ?line test(".\n\n"), - ?line test(".\n\r"), - ?line test(".\n\n\n"), - ?line test(".\210"), - ?line test(".%\n"), - ?line test(".a"), - - ?line test("%. \n. "), + test_string(". ", [{dot,{1,1}}]), + test_string(". ", [{dot,{1,1}}]), + test_string(".\n", [{dot,{1,1}}]), + test_string(".\n\n", [{dot,{1,1}}]), + test_string(".\n\r", [{dot,{1,1}}]), + test_string(".\n\n\n", [{dot,{1,1}}]), + test_string(".\210", [{dot,{1,1}}]), + test_string(".%\n", [{dot,{1,1}}]), + test_string(".a", [{'.',{1,1}},{atom,{1,2},a}]), + + test_string("%. \n. ", [{dot,{2,1}}]), ?line {more,C} = erl_scan:tokens([], "%. ",{1,1}, return), - ?line {done,{ok,[{comment,_,"%. "}, - {white_space,_,"\n"}, - {dot,_}], - {2,3}}, ""} = + {done,{ok,[{comment,{1,1},"%. "}, + {white_space,{1,4},"\n"}, + {dot,{2,1}}], + {2,3}}, ""} = erl_scan:tokens(C, "\n. ", {1,1}, return), % any loc, any options ?line [test_string(S, R) || - {S, R} <- [{".$\n", [{'.',1},{char,1,$\n}]}, - {"$\\\n", [{char,1,$\n}]}, - {"'\\\n'", [{atom,1,'\n'}]}, - {"$\n", [{char,1,$\n}]}] ], + {S, R} <- [{".$\n", [{'.',{1,1}},{char,{1,2},$\n}]}, + {"$\\\n", [{char,{1,1},$\n}]}, + {"'\\\n'", [{atom,{1,1},'\n'}]}, + {"$\n", [{char,{1,1},$\n}]}] ], ok. chars() -> [begin L = lists:flatten(io_lib:format("$\\~.8b", [C])), - Ts = [{char,1,C}], + Ts = [{char,{1,1},C}], ?line test_string(L, Ts) end || C <- lists:seq(0, 255)], %% Leading zeroes... [begin L = lists:flatten(io_lib:format("$\\~3.8.0b", [C])), - Ts = [{char,1,C}], + Ts = [{char,{1,1},C}], ?line test_string(L, Ts) end || C <- lists:seq(0, 255)], %% $\^\n now increments the line... [begin L = "$\\^" ++ [C], - Ts = [{char,1,C band 2#11111}], + Ts = [{char,{1,1},C band 2#11111}], ?line test_string(L, Ts) end || C <- lists:seq(0, 255)], [begin L = "$\\" ++ [C], - Ts = [{char,1,V}], + Ts = [{char,{1,1},V}], ?line test_string(L, Ts) end || {C,V} <- [{$n,$\n}, {$r,$\r}, {$t,$\t}, {$v,$\v}, {$b,$\b}, {$f,$\f}, {$e,$\e}, {$s,$\s}, @@ -440,45 +462,45 @@ chars() -> No = EC ++ Ds ++ X ++ New, [begin L = "$\\" ++ [C], - Ts = [{char,1,C}], + Ts = [{char,{1,1},C}], ?line test_string(L, Ts) end || C <- lists:seq(0, 255) -- No], [begin L = "'$\\" ++ [C] ++ "'", - Ts = [{atom,1,list_to_atom("$"++[C])}], + Ts = [{atom,{1,1},list_to_atom("$"++[C])}], ?line test_string(L, Ts) end || C <- lists:seq(0, 255) -- No], - ?line test_string("\"\\013a\\\n\"", [{string,1,"\va\n"}]), + test_string("\"\\013a\\\n\"", [{string,{1,1},"\va\n"}]), - ?line test_string("'\n'", [{atom,1,'\n'}]), - ?line test_string("\"\n\a\"", [{string,1,"\na"}]), + test_string("'\n'", [{atom,{1,1},'\n'}]), + test_string("\"\n\a\"", [{string,{1,1},"\na"}]), %% No escape [begin L = "$" ++ [C], - Ts = [{char,1,C}], + Ts = [{char,{1,1},C}], ?line test_string(L, Ts) end || C <- lists:seq(0, 255) -- (No ++ [$\\])], - ?line test_string("$\n", [{char,1,$\n}]), + test_string("$\n", [{char,{1,1},$\n}]), ?line {error,{{1,1},erl_scan,char},{1,4}} = erl_scan:string("$\\^",{1,1}), - ?line test_string("$\\\n", [{char,1,$\n}]), + test_string("$\\\n", [{char,{1,1},$\n}]), %% Robert's scanner returns line 1: - ?line test_string("$\\\n", [{char,1,$\n}]), - ?line test_string("$\n\n", [{char,1,$\n}]), + test_string("$\\\n", [{char,{1,1},$\n}]), + test_string("$\n\n", [{char,{1,1},$\n}]), ?line test("$\n\n"), ok. variables() -> - ?line test_string(" \237_Aouåeiyäö", [{var,1,'_Aouåeiyäö'}]), - ?line test_string("A_b_c@", [{var,1,'A_b_c@'}]), - ?line test_string("V@2", [{var,1,'V@2'}]), - ?line test_string("ABDÀ", [{var,1,'ABDÀ'}]), - ?line test_string("Ärlig Östen", [{var,1,'Ärlig'},{var,1,'Östen'}]), + test_string(" \237_Aouåeiyäö", [{var,{1,7},'_Aouåeiyäö'}]), + test_string("A_b_c@", [{var,{1,1},'A_b_c@'}]), + test_string("V@2", [{var,{1,1},'V@2'}]), + test_string("ABDÀ", [{var,{1,1},'ABDÀ'}]), + test_string("Ärlig Östen", [{var,{1,1},'Ärlig'},{var,{1,7},'Östen'}]), ok. eof() -> @@ -508,11 +530,25 @@ eof() -> ?line {done,{ok,[{atom,1,a}],1},eof} = erl_scan:tokens(C5,eof,1), + %% With column. + {more, C6} = erl_scan:tokens([], "a", {1,1}), + %% An error before R13A. + %% {done,{error,{1,erl_scan,scan},1},eof} = + {done,{ok,[{atom,{1,1},a}],{1,2}},eof} = + erl_scan:tokens(C6,eof,1), + %% A dot followed by eof is special: ?line {more, C} = erl_scan:tokens([], "a.", 1), ?line {done,{ok,[{atom,1,a},{dot,1}],1},eof} = erl_scan:tokens(C,eof,1), ?line {ok,[{atom,1,foo},{dot,1}],1} = erl_scan:string("foo."), + %% With column. + {more, CCol} = erl_scan:tokens([], "a.", {1,1}), + {done,{ok,[{atom,{1,1},a},{dot,{1,2}}],{1,3}},eof} = + erl_scan:tokens(CCol,eof,1), + {ok,[{atom,{1,1},foo},{dot,{1,4}}],{1,5}} = + erl_scan:string("foo.", {1,1}, []), + ok. illegal() -> @@ -816,34 +852,34 @@ unicode() -> erl_scan:string([1089]), ?line {error,{{1,1},erl_scan,{illegal,character}},{1,2}} = erl_scan:string([1089], {1,1}), - ?line {error,{1,erl_scan,{illegal,atom}},1} = + {error,{1,erl_scan,{illegal,atom}},1} = erl_scan:string("'a"++[1089]++"b'", 1), - ?line {error,{{1,1},erl_scan,{illegal,atom}},{1,6}} = + {error,{{1,1},erl_scan,{illegal,atom}},{1,6}} = erl_scan:string("'a"++[1089]++"b'", {1,1}), ?line test("\"a"++[1089]++"b\""), - ?line {ok,[{char,1,1}],1} = + {ok,[{char,1,1}],1} = erl_scan:string([$$,$\\,$^,1089], 1), - ?line {error,{1,erl_scan,Error},1} = + {error,{1,erl_scan,Error},1} = erl_scan:string("\"qa\x{aaa}", 1), - ?line "unterminated string starting with \"qa"++[2730]++"\"" = + "unterminated string starting with \"qa"++[2730]++"\"" = erl_scan:format_error(Error), ?line {error,{{1,1},erl_scan,_},{1,11}} = erl_scan:string("\"qa\\x{aaa}",{1,1}), - ?line {error,{{1,1},erl_scan,{illegal,atom}},{1,12}} = + {error,{{1,1},erl_scan,{illegal,atom}},{1,12}} = erl_scan:string("'qa\\x{aaa}'",{1,1}), - ?line {ok,[{char,1,1089}],1} = + {ok,[{char,1,1089}],1} = erl_scan:string([$$,1089], 1), - ?line {ok,[{char,1,1089}],1} = + {ok,[{char,1,1089}],1} = erl_scan:string([$$,$\\,1089], 1), Qs = "$\\x{aaa}", - ?line {ok,[{char,1,$\x{aaa}}],1} = + {ok,[{char,1,$\x{aaa}}],1} = erl_scan:string(Qs, 1), - ?line {ok,[Q2],{1,9}} = + {ok,[Q2],{1,9}} = erl_scan:string("$\\x{aaa}", {1,1}, [text]), - ?line [{category,char},{column,1},{length,8}, + [{category,char},{column,1},{length,8}, {line,1},{symbol,16#aaa},{text,Qs}] = erl_scan:token_info(Q2), @@ -1164,7 +1200,13 @@ otp_11807(Config) when is_list(Config) -> (catch erl_parse:abstract("string", [{encoding,bad}])), ok. -test_string(String, Expected) -> +test_string(String, ExpectedWithCol) -> + {ok, ExpectedWithCol, _EndWithCol} = erl_scan:string(String, {1, 1}, []), + Expected = [ begin + {L,_C} = element(2, T), + setelement(2, T, L) + end + || T <- ExpectedWithCol ], {ok, Expected, _End} = erl_scan:string(String), test(String). diff --git a/lib/stdlib/test/filelib_SUITE.erl b/lib/stdlib/test/filelib_SUITE.erl index 8203a03a7a..146d810189 100644 --- a/lib/stdlib/test/filelib_SUITE.erl +++ b/lib/stdlib/test/filelib_SUITE.erl @@ -1,7 +1,7 @@ %% %% %CopyrightBegin% %% -%% Copyright Ericsson AB 2005-2013. All Rights Reserved. +%% Copyright Ericsson AB 2005-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 @@ -23,7 +23,8 @@ init_per_group/2,end_per_group/2, init_per_testcase/2,end_per_testcase/2, wildcard_one/1,wildcard_two/1,wildcard_errors/1, - fold_files/1,otp_5960/1,ensure_dir_eexist/1,symlinks/1]). + fold_files/1,otp_5960/1,ensure_dir_eexist/1,ensure_dir_symlink/1, + wildcard_symlink/1, is_file_symlink/1, file_props_symlink/1]). -import(lists, [foreach/2]). @@ -43,7 +44,8 @@ suite() -> [{ct_hooks,[ts_install_cth]}]. all() -> [wildcard_one, wildcard_two, wildcard_errors, - fold_files, otp_5960, ensure_dir_eexist, symlinks]. + fold_files, otp_5960, ensure_dir_eexist, ensure_dir_symlink, + wildcard_symlink, is_file_symlink, file_props_symlink]. groups() -> []. @@ -75,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), @@ -86,6 +89,7 @@ wildcard_two(Config) when is_list(Config) -> ?line ok = file:make_dir(Dir), ?line do_wildcard_1(Dir, fun(Wc) -> io:format("~p~n",[{Wc,Dir, X = filelib:wildcard(Wc, Dir)}]),X end), ?line do_wildcard_1(Dir, fun(Wc) -> filelib:wildcard(Wc, Dir++"/") end), + ?line do_wildcard_1(Dir, fun(Wc) -> filelib:wildcard(Wc, Dir++"/.") end), case os:type() of {win32,_} -> ok; @@ -367,9 +371,28 @@ ensure_dir_eexist(Config) when is_list(Config) -> ?line {error, eexist} = filelib:ensure_dir(NeedFileB), ok. -symlinks(Config) when is_list(Config) -> +ensure_dir_symlink(Config) when is_list(Config) -> PrivDir = ?config(priv_dir, Config), - Dir = filename:join(PrivDir, ?MODULE_STRING++"_symlinks"), + Dir = filename:join(PrivDir, "ensure_dir_symlink"), + Name = filename:join(Dir, "same_name_as_file_and_dir"), + ok = filelib:ensure_dir(Name), + ok = file:write_file(Name, <<"some string\n">>), + %% With a symlink to the directory. + Symlink = filename:join(PrivDir, "ensure_dir_symlink_link"), + case file:make_symlink(Dir, Symlink) of + {error,enotsup} -> + {skip,"Symlinks not supported on this platform"}; + {error,eperm} -> + {win32,_} = os:type(), + {skip,"Windows user not privileged to create symlinks"}; + ok -> + SymlinkedName = filename:join(Symlink, "same_name_as_file_and_dir"), + ok = filelib:ensure_dir(SymlinkedName) + end. + +wildcard_symlink(Config) when is_list(Config) -> + PrivDir = ?config(priv_dir, Config), + Dir = filename:join(PrivDir, ?MODULE_STRING++"_wildcard_symlink"), SubDir = filename:join(Dir, "sub"), AFile = filename:join(SubDir, "a_file"), Alias = filename:join(Dir, "symlink"), @@ -387,6 +410,18 @@ symlinks(Config) when is_list(Config) -> basenames(Dir, filelib:wildcard(filename:join(Dir, "*"))), ["symlink"] = basenames(Dir, filelib:wildcard(filename:join(Dir, "symlink"))), + ["sub","symlink"] = + basenames(Dir, filelib:wildcard(filename:join(Dir, "*"), + erl_prim_loader)), + ["symlink"] = + basenames(Dir, filelib:wildcard(filename:join(Dir, "symlink"), + erl_prim_loader)), + ["sub","symlink"] = + basenames(Dir, filelib:wildcard(filename:join(Dir, "*"), + prim_file)), + ["symlink"] = + basenames(Dir, filelib:wildcard(filename:join(Dir, "symlink"), + prim_file)), ok = file:delete(AFile), %% The symlink should still be visible even when its target %% has been deleted. @@ -394,6 +429,18 @@ symlinks(Config) when is_list(Config) -> basenames(Dir, filelib:wildcard(filename:join(Dir, "*"))), ["symlink"] = basenames(Dir, filelib:wildcard(filename:join(Dir, "symlink"))), + ["sub","symlink"] = + basenames(Dir, filelib:wildcard(filename:join(Dir, "*"), + erl_prim_loader)), + ["symlink"] = + basenames(Dir, filelib:wildcard(filename:join(Dir, "symlink"), + erl_prim_loader)), + ["sub","symlink"] = + basenames(Dir, filelib:wildcard(filename:join(Dir, "*"), + prim_file)), + ["symlink"] = + basenames(Dir, filelib:wildcard(filename:join(Dir, "symlink"), + prim_file)), ok end. @@ -402,3 +449,60 @@ basenames(Dir, Files) -> Dir = filename:dirname(F), filename:basename(F) end || F <- Files]. + +is_file_symlink(Config) -> + PrivDir = ?config(priv_dir, Config), + Dir = filename:join(PrivDir, ?MODULE_STRING++"_is_file_symlink"), + SubDir = filename:join(Dir, "sub"), + AFile = filename:join(SubDir, "a_file"), + DirAlias = filename:join(Dir, "dir_symlink"), + FileAlias = filename:join(Dir, "file_symlink"), + ok = file:make_dir(Dir), + ok = file:make_dir(SubDir), + ok = file:write_file(AFile, "not that big\n"), + case file:make_symlink(SubDir, DirAlias) of + {error, enotsup} -> + {skip, "Links not supported on this platform"}; + {error, eperm} -> + {win32,_} = os:type(), + {skip, "Windows user not privileged to create symlinks"}; + ok -> + true = filelib:is_dir(DirAlias), + true = filelib:is_dir(DirAlias, erl_prim_loader), + true = filelib:is_dir(DirAlias, prim_file), + true = filelib:is_file(DirAlias), + true = filelib:is_file(DirAlias, erl_prim_loader), + true = filelib:is_file(DirAlias, prim_file), + ok = file:make_symlink(AFile,FileAlias), + true = filelib:is_file(FileAlias), + true = filelib:is_file(FileAlias, erl_prim_loader), + true = filelib:is_file(FileAlias, prim_file), + true = filelib:is_regular(FileAlias), + true = filelib:is_regular(FileAlias, erl_prim_loader), + true = filelib:is_regular(FileAlias, prim_file), + ok + end. + +file_props_symlink(Config) -> + PrivDir = ?config(priv_dir, Config), + Dir = filename:join(PrivDir, ?MODULE_STRING++"_file_props_symlink"), + AFile = filename:join(Dir, "a_file"), + Alias = filename:join(Dir, "symlink"), + ok = file:make_dir(Dir), + ok = file:write_file(AFile, "not that big\n"), + case file:make_symlink(AFile, Alias) of + {error, enotsup} -> + {skip, "Links not supported on this platform"}; + {error, eperm} -> + {win32,_} = os:type(), + {skip, "Windows user not privileged to create symlinks"}; + ok -> + {_,_} = LastMod = filelib:last_modified(AFile), + LastMod = filelib:last_modified(Alias), + LastMod = filelib:last_modified(Alias, erl_prim_loader), + LastMod = filelib:last_modified(Alias, prim_file), + FileSize = filelib:file_size(AFile), + FileSize = filelib:file_size(Alias), + FileSize = filelib:file_size(Alias, erl_prim_loader), + FileSize = filelib:file_size(Alias, prim_file) + end. 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 8aeec07ae8..75796ab1b6 100644 --- a/lib/stdlib/test/gen_fsm_SUITE.erl +++ b/lib/stdlib/test/gen_fsm_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 @@ -27,11 +27,16 @@ -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]). --export([ sys1/1, call_format_status/1, error_format_status/1, get_state/1, replace_state/1]). +-export([ sys1/1, + call_format_status/1, error_format_status/1, terminate_crash_format/1, + get_state/1, replace_state/1]). -export([hibernate/1,hiber_idle/3,hiber_wakeup/3,hiber_idle/2,hiber_wakeup/2]). @@ -64,9 +69,12 @@ 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, get_state, replace_state]}]. + [sys1, call_format_status, error_format_status, terminate_crash_format, + get_state, replace_state]}]. init_per_suite(Config) -> Config. @@ -278,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) -> @@ -403,7 +510,7 @@ error_format_status(Config) when is_list(Config) -> receive {error,_GroupLeader,{Pid, "** State machine"++_, - [Pid,{_,_,badreturn},idle,StateData,_]}} -> + [Pid,{_,_,badreturn},idle,{formatted,StateData},_]}} -> ok; Other -> ?line io:format("Unexpected: ~p", [Other]), @@ -413,6 +520,29 @@ error_format_status(Config) when is_list(Config) -> process_flag(trap_exit, OldFl), ok. +terminate_crash_format(Config) when is_list(Config) -> + error_logger_forwarder:register(), + OldFl = process_flag(trap_exit, true), + StateData = crash_terminate, + {ok, Pid} = gen_fsm:start(gen_fsm_SUITE, {state_data, StateData}, []), + stop_it(Pid), + receive + {error,_GroupLeader,{Pid, + "** State machine"++_, + [Pid,{_,_,_},idle,{formatted, StateData},_]}} -> + ok; + Other -> + io:format("Unexpected: ~p", [Other]), + ?t:fail() + after 5000 -> + io:format("Timeout: expected error logger msg", []), + ?t:fail() + end, + [] = ?t:messages_get(), + process_flag(trap_exit, OldFl), + ok. + + get_state(Config) when is_list(Config) -> State = self(), {ok, Pid} = gen_fsm:start(?MODULE, {state_data, State}, []), @@ -867,7 +997,8 @@ init({state_data, StateData}) -> init(_) -> {ok, idle, state_data}. - +terminate(_, _State, crash_terminate) -> + exit({crash, terminate}); terminate({From, stopped}, State, _Data) -> From ! {self(), {stopped, State}}, ok; @@ -1005,6 +1136,6 @@ handle_sync_event({get, _Pid}, _From, State, Data) -> {reply, {state, State, Data}, State, Data}. format_status(terminate, [_Pdict, StateData]) -> - StateData; + {formatted, StateData}; format_status(normal, [_Pdict, _StateData]) -> [format_status_called]. diff --git a/lib/stdlib/test/gen_server_SUITE.erl b/lib/stdlib/test/gen_server_SUITE.erl index 960e7f60e7..8b6654dd5e 100644 --- a/lib/stdlib/test/gen_server_SUITE.erl +++ b/lib/stdlib/test/gen_server_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 @@ -32,9 +32,13 @@ spec_init_local_registered_parent/1, spec_init_global_registered_parent/1, otp_5854/1, hibernate/1, otp_7669/1, call_format_status/1, - error_format_status/1, get_state/1, replace_state/1, call_with_huge_message_queue/1 + error_format_status/1, terminate_crash_format/1, + 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, @@ -50,18 +54,20 @@ 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, spec_init_local_registered_parent, spec_init_global_registered_parent, otp_5854, hibernate, - otp_7669, call_format_status, error_format_status, + otp_7669, + call_format_status, error_format_status, terminate_crash_format, get_state, replace_state, call_with_huge_message_queue]. groups() -> - []. + [{stop, [], + [stop1, stop2, stop3, stop4, stop5, stop6, stop7, stop8, stop9, stop10]}]. init_per_suite(Config) -> Config. @@ -235,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(), @@ -273,7 +378,7 @@ crash(Config) when is_list(Config) -> receive {error,_GroupLeader4,{Pid4, "** Generic server"++_, - [Pid4,crash,state4,crashed]}} -> + [Pid4,crash,{formatted, state4},crashed]}} -> ok; Other4a -> ?line io:format("Unexpected: ~p", [Other4a]), @@ -1024,7 +1129,7 @@ error_format_status(Config) when is_list(Config) -> receive {error,_GroupLeader,{Pid, "** Generic server"++_, - [Pid,crash,State,crashed]}} -> + [Pid,crash,{formatted, State},crashed]}} -> ok; Other -> ?line io:format("Unexpected: ~p", [Other]), @@ -1034,6 +1139,31 @@ error_format_status(Config) when is_list(Config) -> process_flag(trap_exit, OldFl), ok. +%% Verify that error when terminating correctly calls our format_status/2 fun +%% +terminate_crash_format(Config) when is_list(Config) -> + error_logger_forwarder:register(), + OldFl = process_flag(trap_exit, true), + State = crash_terminate, + {ok, Pid} = gen_server:start_link(?MODULE, {state, State}, []), + gen_server:call(Pid, stop), + receive {'EXIT', Pid, {crash, terminate}} -> ok end, + receive + {error,_GroupLeader,{Pid, + "** Generic server"++_, + [Pid,stop, {formatted, State},{crash, terminate}]}} -> + ok; + Other -> + io:format("Unexpected: ~p", [Other]), + ?t:fail() + after 5000 -> + io:format("Timeout: expected error logger msg", []), + ?t:fail() + end, + ?t:messages_get(), + process_flag(trap_exit, OldFl), + ok. + %% Verify that sys:get_state correctly returns gen_server state %% get_state(suite) -> @@ -1323,10 +1453,12 @@ terminate({From, stopped}, _State) -> terminate({From, stopped_info}, _State) -> From ! {self(), stopped_info}, ok; +terminate(_, crash_terminate) -> + exit({crash, terminate}); terminate(_Reason, _State) -> ok. format_status(terminate, [_PDict, State]) -> - State; + {formatted, State}; format_status(normal, [_PDict, _State]) -> format_status_called. diff --git a/lib/stdlib/test/io_SUITE.erl b/lib/stdlib/test/io_SUITE.erl index 5a8971c071..3a76275f31 100644 --- a/lib/stdlib/test/io_SUITE.erl +++ b/lib/stdlib/test/io_SUITE.erl @@ -30,7 +30,7 @@ io_fread_newlines/1, otp_8989/1, io_lib_fread_literal/1, printable_range/1, io_lib_print_binary_depth_one/1, otp_10302/1, otp_10755/1, - otp_10836/1]). + otp_10836/1, io_lib_width_too_small/1]). -export([pretty/2]). @@ -69,7 +69,8 @@ all() -> io_lib_collect_line_3_wb, cr_whitespace_in_string, io_fread_newlines, otp_8989, io_lib_fread_literal, printable_range, - io_lib_print_binary_depth_one, otp_10302, otp_10755, otp_10836]. + io_lib_print_binary_depth_one, otp_10302, otp_10755, otp_10836, + io_lib_width_too_small]. groups() -> []. @@ -2213,3 +2214,8 @@ compile_file(File, Text, Config) -> try compile:file(Fname, [return]) after ok %file:delete(Fname) end. + +io_lib_width_too_small(Config) -> + "**" = lists:flatten(io_lib:format("~2.3w", [3.14])), + "**" = lists:flatten(io_lib:format("~2.5w", [3.14])), + ok. diff --git a/lib/stdlib/test/maps_SUITE.erl b/lib/stdlib/test/maps_SUITE.erl index c826ee731a..dda20a615b 100644 --- a/lib/stdlib/test/maps_SUITE.erl +++ b/lib/stdlib/test/maps_SUITE.erl @@ -24,10 +24,7 @@ -include_lib("test_server/include/test_server.hrl"). -% Default timetrap timeout (set in init_per_testcase). -% This should be set relatively high (10-15 times the expected -% max testcasetime). --define(default_timeout, ?t:minutes(4)). +-define(default_timeout, ?t:minutes(1)). % Test server specific exports -export([all/0]). @@ -37,13 +34,13 @@ -export([init_per_testcase/2]). -export([end_per_testcase/2]). --export([get3/1]). +-export([t_get_3/1,t_with_2/1,t_without_2/1]). suite() -> [{ct_hooks, [ts_install_cth]}]. all() -> - [get3]. + [t_get_3,t_with_2,t_without_2]. init_per_suite(Config) -> Config. @@ -52,7 +49,7 @@ end_per_suite(_Config) -> ok. 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) -> @@ -60,10 +57,24 @@ end_per_testcase(_Case, Config) -> test_server:timetrap_cancel(Dog), ok. -get3(Config) when is_list(Config) -> +t_get_3(Config) when is_list(Config) -> Map = #{ key1 => value1, key2 => value2 }, DefaultValue = "Default value", - ?line value1 = maps:get(key1, Map, DefaultValue), - ?line value2 = maps:get(key2, Map, DefaultValue), - ?line DefaultValue = maps:get(key3, Map, DefaultValue), + value1 = maps:get(key1, Map, DefaultValue), + value2 = maps:get(key2, Map, DefaultValue), + DefaultValue = maps:get(key3, Map, DefaultValue), + ok. + +t_without_2(_Config) -> + Ki = [11,22,33,44,55,66,77,88,99], + M0 = maps:from_list([{{k,I},{v,I}}||I<-lists:seq(1,100)]), + M1 = maps:from_list([{{k,I},{v,I}}||I<-lists:seq(1,100) -- Ki]), + M1 = maps:without([{k,I}||I <- Ki],M0), + ok. + +t_with_2(_Config) -> + Ki = [11,22,33,44,55,66,77,88,99], + M0 = maps:from_list([{{k,I},{v,I}}||I<-lists:seq(1,100)]), + M1 = maps:from_list([{{k,I},{v,I}}||I<-Ki]), + M1 = maps:with([{k,I}||I <- Ki],M0), ok. 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/shell_SUITE.erl b/lib/stdlib/test/shell_SUITE.erl index e016432f4d..f841e2c4a6 100644 --- a/lib/stdlib/test/shell_SUITE.erl +++ b/lib/stdlib/test/shell_SUITE.erl @@ -2532,6 +2532,11 @@ otp_6554(Config) when is_list(Config) -> "\n end.\nok.\n" = t(<<"begin F = fun() -> foo end, 1 end. B = F(). C = 17. b().">>), + ?line "3: command not found" = comm_err(<<"#{v(3) => v}.">>), + ?line "3: command not found" = comm_err(<<"#{k => v(3)}.">>), + ?line "3: command not found" = comm_err(<<"#{v(3) := v}.">>), + ?line "3: command not found" = comm_err(<<"#{k := v(3)}.">>), + ?line "3: command not found" = comm_err(<<"(v(3))#{}.">>), %% Tests I'd like to do: (you should try them manually) %% "catch spawn_link(fun() -> timer:sleep(1000), exit(foo) end)." %% "** exception error: foo" should be output after 1 second diff --git a/lib/stdlib/test/stdlib_SUITE.erl b/lib/stdlib/test/stdlib_SUITE.erl index 59821220b4..3d09bd27ff 100644 --- a/lib/stdlib/test/stdlib_SUITE.erl +++ b/lib/stdlib/test/stdlib_SUITE.erl @@ -78,17 +78,29 @@ appup_test(_Config) -> appup_tests(_App,{[],[]}) -> {skip,"no previous releases available"}; -appup_tests(App,{OkVsns,NokVsns}) -> +appup_tests(App,{OkVsns0,NokVsns}) -> application:load(App), {_,_,Vsn} = lists:keyfind(App,1,application:loaded_applications()), AppupFileName = atom_to_list(App) ++ ".appup", AppupFile = filename:join([code:lib_dir(App),ebin,AppupFileName]), {ok,[{Vsn,UpFrom,DownTo}=AppupScript]} = file:consult(AppupFile), ct:log("~p~n",[AppupScript]), - ct:log("Testing ok versions: ~p~n",[OkVsns]), + OkVsns = + case OkVsns0 -- [Vsn] of + OkVsns0 -> + OkVsns0; + Ok -> + ct:log("Current version, ~p, is same as in previous release.~n" + "Removing this from the list of ok versions.", + [Vsn]), + Ok + end, + ct:log("Testing that appup allows upgrade from these versions: ~p~n", + [OkVsns]), check_appup(OkVsns,UpFrom,{ok,[restart_new_emulator]}), check_appup(OkVsns,DownTo,{ok,[restart_new_emulator]}), - ct:log("Testing not ok versions: ~p~n",[NokVsns]), + ct:log("Testing that appup does not allow upgrade from these versions: ~p~n", + [NokVsns]), check_appup(NokVsns,UpFrom,error), check_appup(NokVsns,DownTo,error), ok. 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. |