Skip to content

Commit

Permalink
Merge pull request #9020 from bjorng/bjorn/stdlib/behaviour-warnings/G…
Browse files Browse the repository at this point in the history
…H-8985/OTP-19334

Add options for silencing warnings for behaviours
  • Loading branch information
bjorng authored Nov 11, 2024
2 parents c24e439 + b38327e commit b7fa407
Show file tree
Hide file tree
Showing 5 changed files with 153 additions and 13 deletions.
31 changes: 31 additions & 0 deletions lib/compiler/src/compile.erl
Original file line number Diff line number Diff line change
Expand Up @@ -736,6 +736,37 @@ value are listed.
this kind of warning for the types in `Types`, where `Types` is a tuple
`{TypeName,Arity}` or a list of such tuples.
- **`nowarn_behaviours`** - By default, warnings are emitted for issues
with behaviours. Use this option to turn off all warnings of this kind.
- **`nowarn_conflicting_behaviours`** - By default, warnings are emitted when
a module opts in to multiple behaviours that share the names of one or more
callback functions. Use this option to turn off this kind of warning.
- **`nowarn_undefined_behaviour_func`** - By default, a warning is
emitted when a module that uses a behaviour does not export a
mandatory callback function required by that behaviour. Use this
option to turn off this kind of warning.
- **`nowarn_undefined_behaviour`** - By default, a warning is emitted
when a module attempts to us an unknown behaviour. Use this option
to turn off this kind of warning.
- **`nowarn_undefined_behaviour_callbacks`** - By default, a warning
is emitted when `behaviour_info(callbacks)` in the behaviour module
returns `undefined` instead of a list of callback functions. Use this
option to turn off this kind of warning.
- **`nowarn_ill_defined_behaviour_callbacks`** - By default, a warning
is emitted when `behaviour_info(callbacks)` in the behaviour module
returns a badly formed list of functions. Use this option to turn
off this kind of warning.
- **`nowarn_ill_defined_optional_callbacks`** - By default, a warning
is emitted when `behaviour_info(optional_callbacks)` in the
behaviour module returns a badly formed list of functions. Use this
option to turn off this kind of warning.
Other kinds of warnings are _opportunistic warnings_. They are generated when
the compiler happens to notice potential issues during optimization and code
generation.
Expand Down
67 changes: 57 additions & 10 deletions lib/stdlib/src/erl_lint.erl
Original file line number Diff line number Diff line change
Expand Up @@ -823,6 +823,35 @@ start(File, Opts) ->
true, Opts)},
{update_literal,
bool_option(warn_update_literal, nowarn_update_literal,
true, Opts)},
%% Behaviour warnings.
{behaviours,
bool_option(warn_behaviours,
nowarn_behaviours,
true, Opts)},
{conflicting_behaviours,
bool_option(warn_conflicting_behaviours,
nowarn_conflicting_behaviours,
true, Opts)},
{undefined_behaviour_func,
bool_option(warn_undefined_behaviour_func,
nowarn_undefined_behaviour_func,
true, Opts)},
{undefined_behaviour,
bool_option(warn_undefined_behaviour,
nowarn_undefined_behaviour,
true, Opts)},
{undefined_behaviour_callbacks,
bool_option(warn_undefined_behaviour_callbacks,
nowarn_undefined_behaviour_callbacks,
true, Opts)},
{ill_defined_behaviour_callbacks,
bool_option(warn_ill_defined_behaviour_callbacks,
nowarn_ill_defined_behaviour_callbacks,
true, Opts)},
{ill_defined_optional_callbacks,
bool_option(warn_ill_defined_optional_callbacks,
nowarn_ill_defined_optional_callbacks,
true, Opts)}
],
Enabled1 = [Category || {Category,true} <- Enabled0],
Expand Down Expand Up @@ -1233,8 +1262,13 @@ post_traversal_check(Forms, St0) ->
%% check_behaviour(State0) -> State
%% Check that the behaviour attribute is valid.

check_behaviour(St0) ->
behaviour_check(St0#lint.behaviour, St0).
check_behaviour(St) ->
case is_warn_enabled(behaviours, St) of
true ->
behaviour_check(St#lint.behaviour, St);
false ->
St
end.

%% behaviour_check([{Anno,Behaviour}], State) -> State'
%% Check behaviours for existence and defined functions.
Expand All @@ -1258,10 +1292,21 @@ all_behaviour_callbacks([{Anno,B}|Bs], Acc, St0) ->
all_behaviour_callbacks(Bs, [{{Anno,B},Bfs0,OBfs0}|Acc], St);
all_behaviour_callbacks([], Acc, St) -> {reverse(Acc),St}.

add_behaviour_warning(Anno, Warning, St) when is_tuple(Warning) ->
Tag = element(1, Warning),
case is_warn_enabled(Tag, St) of
true ->
add_warning(Anno, Warning, St);
false ->
St
end.

behaviour_callbacks(Anno, B, St0) ->
try B:behaviour_info(callbacks) of
undefined ->
St1 = add_warning(Anno, {undefined_behaviour_callbacks, B}, St0),
St1 = add_behaviour_warning(Anno,
{undefined_behaviour_callbacks, B},
St0),
{[], [], St1};
Funcs ->
case is_fa_list(Funcs) of
Expand All @@ -1277,22 +1322,22 @@ behaviour_callbacks(Anno, B, St0) ->
{Funcs, OptFuncs, St0};
false ->
W = {ill_defined_optional_callbacks, B},
St1 = add_warning(Anno, W, St0),
St1 = add_behaviour_warning(Anno, W, St0),
{Funcs, [], St1}
end
catch
_:_ ->
{Funcs, [], St0}
end;
false ->
St1 = add_warning(Anno,
{ill_defined_behaviour_callbacks, B},
St0),
St1 = add_behaviour_warning(Anno,
{ill_defined_behaviour_callbacks, B},
St0),
{[], [], St1}
end
catch
_:_ ->
St1 = add_warning(Anno, {undefined_behaviour, B}, St0),
St1 = add_behaviour_warning(Anno, {undefined_behaviour, B}, St0),
St2 = check_module_name(B, Anno, St1),
{[], [], St2}
end.
Expand Down Expand Up @@ -1336,7 +1381,7 @@ behaviour_missing_callbacks([{{Anno,B},Bfs0,OBfs}|T], St0) ->
case is_fa(F) of
true ->
M = {undefined_behaviour_func,F,B},
add_warning(Anno, M, S0);
add_behaviour_warning(Anno, M, S0);
false ->
S0 % ill_defined_behaviour_callbacks
end
Expand All @@ -1360,7 +1405,9 @@ behaviour_add_conflicts([{Cb,[{FirstAnno,FirstB}|Cs]}|T], St0) ->
behaviour_add_conflicts([], St) -> St.

behaviour_add_conflict([{Anno,B}|Cs], Cb, FirstL, FirstB, St0) ->
St = add_warning(Anno, {conflicting_behaviours,Cb,B,FirstL,FirstB}, St0),
St = add_behaviour_warning(Anno,
{conflicting_behaviours,Cb,B,FirstL,FirstB},
St0),
behaviour_add_conflict(Cs, Cb, FirstL, FirstB, St);
behaviour_add_conflict([], _, _, _, St) -> St.

Expand Down
57 changes: 55 additions & 2 deletions lib/stdlib/test/erl_lint_SUITE.erl
Original file line number Diff line number Diff line change
Expand Up @@ -3473,6 +3473,15 @@ behaviour_basic(Config) when is_list(Config) ->
{warnings,[{{1,22},erl_lint,{undefined_behaviour_func,{start,2},application}}]}}
],
[] = run(Config, Ts),

Subst0 = #{behaviour1 => [nowarn_undefined_behaviour_func],
behaviour2 => [nowarn_undefined_behaviour_func],
behaviour4 => [nowarn_undefined_behaviour_func]},
[] = run(Config, rewrite(Ts, Subst0)),

Subst = #{K => [nowarn_behaviours] || K := _ <- Subst0},
[] = run(Config, rewrite(Ts, Subst)),

ok.

%% Basic tests with multiple behaviours.
Expand Down Expand Up @@ -3570,12 +3579,21 @@ behaviour_multiple(Config) when is_list(Config) ->
{conflicting_behaviours,{init,1},supervisor,{1,22},gen_server}}]}}
],
[] = run(Config, Ts),

Subst = #{behaviour3 => [nowarn_undefined_behaviour_func,
nowarn_conflicting_behaviours],
american_behavior3 => [nowarn_undefined_behaviour_func,
nowarn_conflicting_behaviours],
behaviour4 => [nowarn_conflicting_behaviours]},
[] = run(Config, rewrite(Ts, Subst)),

ok.

%% OTP-11861. behaviour_info() and -callback.
otp_11861(Conf) when is_list(Conf) ->
CallbackFiles = [callback1, callback2, callback3,
bad_behaviour1, bad_behaviour2],
bad_behaviour1, bad_behaviour2,
bad_behaviour3],
lists:foreach(fun(M) ->
F = filename:join(?datadir, M),
Opts = [{outdir,?privdir}, return],
Expand Down Expand Up @@ -3756,9 +3774,31 @@ otp_11861(Conf) when is_list(Conf) ->
f1(_) -> ok.
">>,
[],
[]}
[]},

{otp_11861_19,
<<"
-export([good/1]).
-behaviour(bad_behaviour3).
good(_) -> ok.
">>,
[],
{warnings,[{{3,16},erl_lint,{ill_defined_optional_callbacks,bad_behaviour3}}]}}
],
[] = run(Conf, Ts),

Subst0 = #{otp_11861_1 => [nowarn_conflicting_behaviours],
otp_11861_11 => [nowarn_ill_defined_behaviour_callbacks],
otp_11861_12 => [nowarn_undefined_behaviour],
otp_11861_13 => [nowarn_undefined_behaviour],
otp_11861_17 => [nowarn_undefined_behaviour_callbacks],
otp_11861_19 => [nowarn_ill_defined_optional_callbacks]
},
[] = run(Conf, rewrite(Ts, Subst0)),

Subst = #{K => [nowarn_behaviours] || K := _ <- Subst0},
[] = run(Conf, rewrite(Ts, Subst)),

true = code:set_path(CodePath),
ok.

Expand Down Expand Up @@ -5475,6 +5515,19 @@ illegal_zip_generator(Config) ->
%%% Common utilities.
%%%

rewrite([{Name,Code,[],{warnings,_}}=H|T], Subst) ->
case Subst of
#{Name := Opts} ->
io:format("~s: testing with options ~p\n", [Name,Opts]),
[{Name,Code,Opts,[]}|rewrite(T, Subst)];
#{} ->
[H|rewrite(T, Subst)]
end;
rewrite([H|T], Subst) ->
[H|rewrite(T, Subst)];
rewrite([], _Subst) ->
[].

format_error(E) ->
lists:flatten(erl_lint:format_error(E)).

Expand Down
4 changes: 3 additions & 1 deletion lib/stdlib/test/erl_lint_SUITE_data/bad_behaviour1.erl
Original file line number Diff line number Diff line change
Expand Up @@ -3,4 +3,6 @@
-export([behaviour_info/1]).

behaviour_info(callbacks) ->
[{a,1,bad}].
[{a,1,bad}];
behaviour_info(optional_callbacks) ->
[{b,1,bad}].
7 changes: 7 additions & 0 deletions lib/stdlib/test/erl_lint_SUITE_data/bad_behaviour3.erl
Original file line number Diff line number Diff line change
@@ -0,0 +1,7 @@
-module(bad_behaviour3).
-export([behaviour_info/1]).

behaviour_info(callbacks) ->
[{good,1}];
behaviour_info(optional_callbacks) ->
[{b,1,bad}].

0 comments on commit b7fa407

Please sign in to comment.