Skip to content

Commit f87ae5a

Browse files
committed
Make the compiler report 'and'/'or' operators as obsolete
1 parent 171fb25 commit f87ae5a

File tree

2 files changed

+38
-24
lines changed

2 files changed

+38
-24
lines changed

lib/stdlib/src/erl_lint.erl

Lines changed: 21 additions & 7 deletions
Original file line numberDiff line numberDiff line change
@@ -366,11 +366,15 @@ format_error_1({redefine_bif_import,{F,A}}) ->
366366
import directive overrides auto-imported BIF ~w/~w --
367367
use "-compile({no_auto_import,[~w/~w]})." to resolve name clash
368368
""", [F,A,F,A]};
369-
format_error_1({deprecated, MFA, String, Rel}) ->
369+
format_error_1({deprecated, MFA, String, Rel}) when is_tuple(MFA) ->
370+
format_error_1({deprecated, format_mfa(MFA), String, Rel});
371+
format_error_1({deprecated, Thing, String, Rel}) when is_list(String) ->
370372
{~"~s is deprecated and will be removed in ~s; ~s",
371-
[format_mfa(MFA), Rel, String]};
372-
format_error_1({deprecated, MFA, String}) when is_list(String) ->
373-
{~"~s is deprecated; ~s", [format_mfa(MFA), String]};
373+
[Thing, Rel, String]};
374+
format_error_1({deprecated, MFA, String}) when is_tuple(MFA) ->
375+
format_error_1({deprecated, format_mfa(MFA), String});
376+
format_error_1({deprecated, Thing, String}) when is_list(String) ->
377+
{~"~s is deprecated; ~s", [Thing, String]};
374378
format_error_1({deprecated_type, {M1, F1, A1}, String, Rel}) ->
375379
{~"the type ~p:~p~s is deprecated and will be removed in ~s; ~s",
376380
[M1, F1, gen_type_paren(A1), Rel, String]};
@@ -2449,14 +2453,23 @@ gexpr({op,_Anno,EqOp,L,R}, Vt, St0) when EqOp =:= '=:='; EqOp =:= '=/=' ->
24492453
gexpr({op,Anno,Op,L,R}, Vt, St0) ->
24502454
{Avt,St1} = gexpr_list([L,R], Vt, St0),
24512455
case is_gexpr_op(Op, 2) of
2452-
true -> {Avt,St1};
2456+
true -> {Avt,warn_obsolete_op(Op, 2, Anno, St1)};
24532457
false -> {Avt,add_error(Anno, illegal_guard_expr, St1)}
24542458
end;
24552459
%% Everything else is illegal! You could put explicit tests here to
24562460
%% better error diagnostics.
24572461
gexpr(E, _Vt, St) ->
24582462
{[],add_error(element(2, E), illegal_guard_expr, St)}.
24592463

2464+
warn_obsolete_op(Op, A, Anno, St) ->
2465+
case {Op, A} of
2466+
{'and', 2} ->
2467+
add_warning(Anno, {deprecated, "'and'", "use 'andalso' instead", "OTP 29"}, St);
2468+
{'or', 2} ->
2469+
add_warning(Anno, {deprecated, "'or'", "use 'orelse' instead", "OTP 29"}, St);
2470+
_ -> St
2471+
end.
2472+
24602473
%% gexpr_list(Expressions, VarTable, State) ->
24612474
%% {UsedVarTable,State'}
24622475

@@ -2869,8 +2882,9 @@ expr({op,Anno,Op,L,R}, Vt, St0) when Op =:= 'orelse'; Op =:= 'andalso' ->
28692882
expr({op,_Anno,EqOp,L,R}, Vt, St0) when EqOp =:= '=:='; EqOp =:= '=/=' ->
28702883
St = expr_check_match_zero(R, expr_check_match_zero(L, St0)),
28712884
expr_list([L,R], Vt, St); %They see the same variables
2872-
expr({op,_Anno,_Op,L,R}, Vt, St) ->
2873-
expr_list([L,R], Vt, St); %They see the same variables
2885+
expr({op,Anno,Op,L,R}, Vt, St) ->
2886+
St1 = warn_obsolete_op(Op, 2, Anno, St),
2887+
expr_list([L,R], Vt, St1); %They see the same variables
28742888
%% The following are not allowed to occur anywhere!
28752889
expr({remote,_Anno,M,_F}, _Vt, St) ->
28762890
{[],add_error(erl_parse:first_anno(M), illegal_expr, St)};

lib/stdlib/test/erl_lint_SUITE.erl

Lines changed: 17 additions & 17 deletions
Original file line numberDiff line numberDiff line change
@@ -608,7 +608,7 @@ unused_vars_warn_fun(Config) when is_list(Config) ->
608608
E;
609609
a([A,B,C,D,E]) -> % E unused.
610610
fun() ->
611-
(C == <<A:A>>) and (<<17:B>> == D)
611+
(C == <<A:A>>) andalso (<<17:B>> == D)
612612
end.
613613
">>,
614614
[warn_unused_vars],
@@ -1790,33 +1790,33 @@ guard(Config) when is_list(Config) ->
17901790
[]},
17911791
{guard4,
17921792
<<"-record(apa, {}).
1793-
t3(A) when float(A) or float(A) -> % coercing... (badarg)
1793+
t3(A) when float(A) orelse float(A) -> % coercing... (badarg)
17941794
float;
1795-
t3(A) when is_atom(A) or is_atom(A) ->
1795+
t3(A) when is_atom(A) orelse is_atom(A) ->
17961796
is_atom;
1797-
t3(A) when is_binary(A) or is_binary(A) ->
1797+
t3(A) when is_binary(A) orelse is_binary(A) ->
17981798
is_binary;
1799-
t3(A) when is_float(A) or is_float(A) ->
1799+
t3(A) when is_float(A) orelse is_float(A) ->
18001800
is_float;
1801-
t3(A) when is_function(A) or is_function(A) ->
1801+
t3(A) when is_function(A) orelse is_function(A) ->
18021802
is_function;
1803-
t3(A) when is_integer(A) or is_integer(A) ->
1803+
t3(A) when is_integer(A) orelse is_integer(A) ->
18041804
is_integer;
1805-
t3(A) when is_list(A) or is_list(A) ->
1805+
t3(A) when is_list(A) orelse is_list(A) ->
18061806
is_list;
1807-
t3(A) when is_number(A) or is_number(A) ->
1807+
t3(A) when is_number(A) orelse is_number(A) ->
18081808
is_number;
1809-
t3(A) when is_pid(A) or is_pid(A) ->
1809+
t3(A) when is_pid(A) orelse is_pid(A) ->
18101810
is_pid;
1811-
t3(A) when is_port(A) or is_port(A) ->
1811+
t3(A) when is_port(A) orelse is_port(A) ->
18121812
is_port;
1813-
t3(A) when is_record(A, apa) or is_record(A, apa) ->
1813+
t3(A) when is_record(A, apa) orelse is_record(A, apa) ->
18141814
is_record;
1815-
t3(A) when is_record(A, apa, 1) or is_record(A, apa, 1) ->
1815+
t3(A) when is_record(A, apa, 1) orelse is_record(A, apa, 1) ->
18161816
is_record;
1817-
t3(A) when is_reference(A) or is_reference(A) ->
1817+
t3(A) when is_reference(A) orelse is_reference(A) ->
18181818
is_reference;
1819-
t3(A) when is_tuple(A) or is_tuple(A) ->
1819+
t3(A) when is_tuple(A) orelse is_tuple(A) ->
18201820
is_tuple.
18211821
">>,
18221822
[nowarn_obsolete_guard],
@@ -1869,7 +1869,7 @@ guard(Config) when is_list(Config) ->
18691869
{guard7,
18701870
<<"-record(apa,{}).
18711871
t() ->
1872-
[X || X <- [1,#apa{},3], (3+is_record(X, apa)) or
1872+
[X || X <- [1,#apa{},3], (3+is_record(X, apa)) orelse
18731873
(is_record(X, apa)*2)].
18741874
">>,
18751875
[],
@@ -2927,7 +2927,7 @@ otp_5878(Config) when is_list(Config) ->
29272927
t() ->
29282928
case x() of
29292929
_ when l()
2930-
or
2930+
orelse
29312931
l() ->
29322932
foo
29332933
end.

0 commit comments

Comments
 (0)