aboutsummaryrefslogtreecommitdiffstats
path: root/lib/stdlib/test
diff options
context:
space:
mode:
authorHans Bolinder <[email protected]>2014-04-15 09:38:41 +0200
committerHans Bolinder <[email protected]>2014-04-28 11:56:26 +0200
commit146260727638e8a477aeda7828364ce45dc506a0 (patch)
treec54b396192cb875eea1c474baff18c136473b95c /lib/stdlib/test
parent3be1dc100140139b2542cd327cf4f8453d43aca1 (diff)
downloadotp-146260727638e8a477aeda7828364ce45dc506a0.tar.gz
otp-146260727638e8a477aeda7828364ce45dc506a0.tar.bz2
otp-146260727638e8a477aeda7828364ce45dc506a0.zip
Introduce the attribute -optional_callbacks in the context of behaviours
Diffstat (limited to 'lib/stdlib/test')
-rw-r--r--lib/stdlib/test/erl_internal_SUITE.erl65
-rw-r--r--lib/stdlib/test/erl_lint_SUITE.erl191
-rw-r--r--lib/stdlib/test/erl_lint_SUITE_data/bad_behaviour1.erl6
-rw-r--r--lib/stdlib/test/erl_lint_SUITE_data/bad_behaviour2.erl6
-rw-r--r--lib/stdlib/test/erl_lint_SUITE_data/callback1.erl6
-rw-r--r--lib/stdlib/test/erl_lint_SUITE_data/callback2.erl6
-rw-r--r--lib/stdlib/test/erl_lint_SUITE_data/callback3.erl8
-rw-r--r--lib/stdlib/test/erl_pp_SUITE.erl18
8 files changed, 279 insertions, 27 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..5506d3d166 100644
--- a/lib/stdlib/test/erl_lint_SUITE.erl
+++ b/lib/stdlib/test/erl_lint_SUITE.erl
@@ -55,7 +55,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,
@@ -89,7 +89,7 @@ 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].
@@ -3080,6 +3080,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,{lint_test,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) ->
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_pp_SUITE.erl b/lib/stdlib/test/erl_pp_SUITE.erl
index babf3a49eb..d0892c6d79 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.
@@ -1204,8 +1204,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)).
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%