Skip to content

Commit

Permalink
Make the compiler report 'and'/'or' operators as obsolete
Browse files Browse the repository at this point in the history
  • Loading branch information
richcarl committed Nov 26, 2024
1 parent 171fb25 commit f87ae5a
Show file tree
Hide file tree
Showing 2 changed files with 38 additions and 24 deletions.
28 changes: 21 additions & 7 deletions lib/stdlib/src/erl_lint.erl
Original file line number Diff line number Diff line change
Expand Up @@ -366,11 +366,15 @@ format_error_1({redefine_bif_import,{F,A}}) ->
import directive overrides auto-imported BIF ~w/~w --
use "-compile({no_auto_import,[~w/~w]})." to resolve name clash
""", [F,A,F,A]};
format_error_1({deprecated, MFA, String, Rel}) ->
format_error_1({deprecated, MFA, String, Rel}) when is_tuple(MFA) ->
format_error_1({deprecated, format_mfa(MFA), String, Rel});
format_error_1({deprecated, Thing, String, Rel}) when is_list(String) ->
{~"~s is deprecated and will be removed in ~s; ~s",
[format_mfa(MFA), Rel, String]};
format_error_1({deprecated, MFA, String}) when is_list(String) ->
{~"~s is deprecated; ~s", [format_mfa(MFA), String]};
[Thing, Rel, String]};
format_error_1({deprecated, MFA, String}) when is_tuple(MFA) ->
format_error_1({deprecated, format_mfa(MFA), String});
format_error_1({deprecated, Thing, String}) when is_list(String) ->
{~"~s is deprecated; ~s", [Thing, String]};
format_error_1({deprecated_type, {M1, F1, A1}, String, Rel}) ->
{~"the type ~p:~p~s is deprecated and will be removed in ~s; ~s",
[M1, F1, gen_type_paren(A1), Rel, String]};
Expand Down Expand Up @@ -2449,14 +2453,23 @@ gexpr({op,_Anno,EqOp,L,R}, Vt, St0) when EqOp =:= '=:='; EqOp =:= '=/=' ->
gexpr({op,Anno,Op,L,R}, Vt, St0) ->
{Avt,St1} = gexpr_list([L,R], Vt, St0),
case is_gexpr_op(Op, 2) of
true -> {Avt,St1};
true -> {Avt,warn_obsolete_op(Op, 2, Anno, St1)};
false -> {Avt,add_error(Anno, illegal_guard_expr, St1)}
end;
%% Everything else is illegal! You could put explicit tests here to
%% better error diagnostics.
gexpr(E, _Vt, St) ->
{[],add_error(element(2, E), illegal_guard_expr, St)}.

warn_obsolete_op(Op, A, Anno, St) ->
case {Op, A} of
{'and', 2} ->
add_warning(Anno, {deprecated, "'and'", "use 'andalso' instead", "OTP 29"}, St);
{'or', 2} ->
add_warning(Anno, {deprecated, "'or'", "use 'orelse' instead", "OTP 29"}, St);
_ -> St
end.

%% gexpr_list(Expressions, VarTable, State) ->
%% {UsedVarTable,State'}

Expand Down Expand Up @@ -2869,8 +2882,9 @@ expr({op,Anno,Op,L,R}, Vt, St0) when Op =:= 'orelse'; Op =:= 'andalso' ->
expr({op,_Anno,EqOp,L,R}, Vt, St0) when EqOp =:= '=:='; EqOp =:= '=/=' ->
St = expr_check_match_zero(R, expr_check_match_zero(L, St0)),
expr_list([L,R], Vt, St); %They see the same variables
expr({op,_Anno,_Op,L,R}, Vt, St) ->
expr_list([L,R], Vt, St); %They see the same variables
expr({op,Anno,Op,L,R}, Vt, St) ->
St1 = warn_obsolete_op(Op, 2, Anno, St),
expr_list([L,R], Vt, St1); %They see the same variables
%% The following are not allowed to occur anywhere!
expr({remote,_Anno,M,_F}, _Vt, St) ->
{[],add_error(erl_parse:first_anno(M), illegal_expr, St)};
Expand Down
34 changes: 17 additions & 17 deletions lib/stdlib/test/erl_lint_SUITE.erl
Original file line number Diff line number Diff line change
Expand Up @@ -608,7 +608,7 @@ unused_vars_warn_fun(Config) when is_list(Config) ->
E;
a([A,B,C,D,E]) -> % E unused.
fun() ->
(C == <<A:A>>) and (<<17:B>> == D)
(C == <<A:A>>) andalso (<<17:B>> == D)
end.
">>,
[warn_unused_vars],
Expand Down Expand Up @@ -1790,33 +1790,33 @@ guard(Config) when is_list(Config) ->
[]},
{guard4,
<<"-record(apa, {}).
t3(A) when float(A) or float(A) -> % coercing... (badarg)
t3(A) when float(A) orelse float(A) -> % coercing... (badarg)
float;
t3(A) when is_atom(A) or is_atom(A) ->
t3(A) when is_atom(A) orelse is_atom(A) ->
is_atom;
t3(A) when is_binary(A) or is_binary(A) ->
t3(A) when is_binary(A) orelse is_binary(A) ->
is_binary;
t3(A) when is_float(A) or is_float(A) ->
t3(A) when is_float(A) orelse is_float(A) ->
is_float;
t3(A) when is_function(A) or is_function(A) ->
t3(A) when is_function(A) orelse is_function(A) ->
is_function;
t3(A) when is_integer(A) or is_integer(A) ->
t3(A) when is_integer(A) orelse is_integer(A) ->
is_integer;
t3(A) when is_list(A) or is_list(A) ->
t3(A) when is_list(A) orelse is_list(A) ->
is_list;
t3(A) when is_number(A) or is_number(A) ->
t3(A) when is_number(A) orelse is_number(A) ->
is_number;
t3(A) when is_pid(A) or is_pid(A) ->
t3(A) when is_pid(A) orelse is_pid(A) ->
is_pid;
t3(A) when is_port(A) or is_port(A) ->
t3(A) when is_port(A) orelse is_port(A) ->
is_port;
t3(A) when is_record(A, apa) or is_record(A, apa) ->
t3(A) when is_record(A, apa) orelse is_record(A, apa) ->
is_record;
t3(A) when is_record(A, apa, 1) or is_record(A, apa, 1) ->
t3(A) when is_record(A, apa, 1) orelse is_record(A, apa, 1) ->
is_record;
t3(A) when is_reference(A) or is_reference(A) ->
t3(A) when is_reference(A) orelse is_reference(A) ->
is_reference;
t3(A) when is_tuple(A) or is_tuple(A) ->
t3(A) when is_tuple(A) orelse is_tuple(A) ->
is_tuple.
">>,
[nowarn_obsolete_guard],
Expand Down Expand Up @@ -1869,7 +1869,7 @@ guard(Config) when is_list(Config) ->
{guard7,
<<"-record(apa,{}).
t() ->
[X || X <- [1,#apa{},3], (3+is_record(X, apa)) or
[X || X <- [1,#apa{},3], (3+is_record(X, apa)) orelse
(is_record(X, apa)*2)].
">>,
[],
Expand Down Expand Up @@ -2927,7 +2927,7 @@ otp_5878(Config) when is_list(Config) ->
t() ->
case x() of
_ when l()
or
orelse
l() ->
foo
end.
Expand Down

0 comments on commit f87ae5a

Please sign in to comment.