Skip to content

Commit 2079bb1

Browse files
committed
Make the compiler report 'and'/'or' operators as obsolete
1 parent 709aed9 commit 2079bb1

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
@@ -370,11 +370,15 @@ format_error_1({redefine_bif_import,{F,A}}) ->
370370
import directive overrides auto-imported BIF ~w/~w --
371371
use "-compile({no_auto_import,[~w/~w]})." to resolve name clash
372372
""", [F,A,F,A]};
373-
format_error_1({deprecated, MFA, String, Rel}) ->
373+
format_error_1({deprecated, MFA, String, Rel}) when is_tuple(MFA) ->
374+
format_error_1({deprecated, format_mfa(MFA), String, Rel});
375+
format_error_1({deprecated, Thing, String, Rel}) when is_list(String) ->
374376
{~"~s is deprecated and will be removed in ~s; ~s",
375-
[format_mfa(MFA), Rel, String]};
376-
format_error_1({deprecated, MFA, String}) when is_list(String) ->
377-
{~"~s is deprecated; ~s", [format_mfa(MFA), String]};
377+
[Thing, Rel, String]};
378+
format_error_1({deprecated, MFA, String}) when is_tuple(MFA) ->
379+
format_error_1({deprecated, format_mfa(MFA), String});
380+
format_error_1({deprecated, Thing, String}) when is_list(String) ->
381+
{~"~s is deprecated; ~s", [Thing, String]};
378382
format_error_1({deprecated_type, {M1, F1, A1}, String, Rel}) ->
379383
{~"the type ~p:~p~s is deprecated and will be removed in ~s; ~s",
380384
[M1, F1, gen_type_paren(A1), Rel, String]};
@@ -2485,14 +2489,23 @@ gexpr({op,_Anno,EqOp,L,R}, Vt, St0) when EqOp =:= '=:='; EqOp =:= '=/=' ->
24852489
gexpr({op,Anno,Op,L,R}, Vt, St0) ->
24862490
{Avt,St1} = gexpr_list([L,R], Vt, St0),
24872491
case is_gexpr_op(Op, 2) of
2488-
true -> {Avt,St1};
2492+
true -> {Avt,warn_obsolete_op(Op, 2, Anno, St1)};
24892493
false -> {Avt,add_error(Anno, illegal_guard_expr, St1)}
24902494
end;
24912495
%% Everything else is illegal! You could put explicit tests here to
24922496
%% better error diagnostics.
24932497
gexpr(E, _Vt, St) ->
24942498
{[],add_error(element(2, E), illegal_guard_expr, St)}.
24952499

2500+
warn_obsolete_op(Op, A, Anno, St) ->
2501+
case {Op, A} of
2502+
{'and', 2} ->
2503+
add_warning(Anno, {deprecated, "'and'", "use 'andalso' instead", "OTP 29"}, St);
2504+
{'or', 2} ->
2505+
add_warning(Anno, {deprecated, "'or'", "use 'orelse' instead", "OTP 29"}, St);
2506+
_ -> St
2507+
end.
2508+
24962509
%% gexpr_list(Expressions, VarTable, State) ->
24972510
%% {UsedVarTable,State'}
24982511

@@ -2857,8 +2870,9 @@ expr({op,Anno,Op,L,R}, Vt, St0) when Op =:= 'orelse'; Op =:= 'andalso' ->
28572870
expr({op,_Anno,EqOp,L,R}, Vt, St0) when EqOp =:= '=:='; EqOp =:= '=/=' ->
28582871
St = expr_check_match_zero(R, expr_check_match_zero(L, St0)),
28592872
expr_list([L,R], Vt, St); %They see the same variables
2860-
expr({op,_Anno,_Op,L,R}, Vt, St) ->
2861-
expr_list([L,R], Vt, St); %They see the same variables
2873+
expr({op,Anno,Op,L,R}, Vt, St) ->
2874+
St1 = warn_obsolete_op(Op, 2, Anno, St),
2875+
expr_list([L,R], Vt, St1); %They see the same variables
28622876
%% The following are not allowed to occur anywhere!
28632877
expr({remote,_Anno,M,_F}, _Vt, St) ->
28642878
{[],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
@@ -616,7 +616,7 @@ unused_vars_warn_fun(Config) when is_list(Config) ->
616616
E;
617617
a([A,B,C,D,E]) -> % E unused.
618618
fun() ->
619-
(C == <<A:A>>) and (<<17:B>> == D)
619+
(C == <<A:A>>) andalso (<<17:B>> == D)
620620
end.
621621
">>,
622622
[warn_unused_vars],
@@ -1846,33 +1846,33 @@ guard(Config) when is_list(Config) ->
18461846
[]},
18471847
{guard4,
18481848
<<"-record(apa, {}).
1849-
t3(A) when float(A) or float(A) -> % coercing... (badarg)
1849+
t3(A) when float(A) orelse float(A) -> % coercing... (badarg)
18501850
float;
1851-
t3(A) when is_atom(A) or is_atom(A) ->
1851+
t3(A) when is_atom(A) orelse is_atom(A) ->
18521852
is_atom;
1853-
t3(A) when is_binary(A) or is_binary(A) ->
1853+
t3(A) when is_binary(A) orelse is_binary(A) ->
18541854
is_binary;
1855-
t3(A) when is_float(A) or is_float(A) ->
1855+
t3(A) when is_float(A) orelse is_float(A) ->
18561856
is_float;
1857-
t3(A) when is_function(A) or is_function(A) ->
1857+
t3(A) when is_function(A) orelse is_function(A) ->
18581858
is_function;
1859-
t3(A) when is_integer(A) or is_integer(A) ->
1859+
t3(A) when is_integer(A) orelse is_integer(A) ->
18601860
is_integer;
1861-
t3(A) when is_list(A) or is_list(A) ->
1861+
t3(A) when is_list(A) orelse is_list(A) ->
18621862
is_list;
1863-
t3(A) when is_number(A) or is_number(A) ->
1863+
t3(A) when is_number(A) orelse is_number(A) ->
18641864
is_number;
1865-
t3(A) when is_pid(A) or is_pid(A) ->
1865+
t3(A) when is_pid(A) orelse is_pid(A) ->
18661866
is_pid;
1867-
t3(A) when is_port(A) or is_port(A) ->
1867+
t3(A) when is_port(A) orelse is_port(A) ->
18681868
is_port;
1869-
t3(A) when is_record(A, apa) or is_record(A, apa) ->
1869+
t3(A) when is_record(A, apa) orelse is_record(A, apa) ->
18701870
is_record;
1871-
t3(A) when is_record(A, apa, 1) or is_record(A, apa, 1) ->
1871+
t3(A) when is_record(A, apa, 1) orelse is_record(A, apa, 1) ->
18721872
is_record;
1873-
t3(A) when is_reference(A) or is_reference(A) ->
1873+
t3(A) when is_reference(A) orelse is_reference(A) ->
18741874
is_reference;
1875-
t3(A) when is_tuple(A) or is_tuple(A) ->
1875+
t3(A) when is_tuple(A) orelse is_tuple(A) ->
18761876
is_tuple.
18771877
">>,
18781878
[nowarn_obsolete_guard],
@@ -1925,7 +1925,7 @@ guard(Config) when is_list(Config) ->
19251925
{guard7,
19261926
<<"-record(apa,{}).
19271927
t() ->
1928-
[X || X <- [1,#apa{},3], (3+is_record(X, apa)) or
1928+
[X || X <- [1,#apa{},3], (3+is_record(X, apa)) orelse
19291929
(is_record(X, apa)*2)].
19301930
">>,
19311931
[],
@@ -2993,7 +2993,7 @@ otp_5878(Config) when is_list(Config) ->
29932993
t() ->
29942994
case x() of
29952995
_ when l()
2996-
or
2996+
orelse
29972997
l() ->
29982998
foo
29992999
end.

0 commit comments

Comments
 (0)