File 2021-compiler-Eliminate-use-of-the-obsolete-and-and-or-op.patch of Package erlang
From f002e38aa6d13f9c5f6c554fc40cd01b77565cb9 Mon Sep 17 00:00:00 2001
From: =?UTF-8?q?Bj=C3=B6rn=20Gustavsson?= <bjorn@erlang.org>
Date: Fri, 16 Jan 2026 07:22:12 +0100
Subject: [PATCH] compiler: Eliminate use of the obsolete `and` and `or`
operators
---
lib/compiler/src/beam_dict.erl | 4 +---
lib/compiler/src/beam_ssa_opt.erl | 4 +---
lib/compiler/src/beam_types.erl | 22 ++++++++++++----------
lib/compiler/src/cerl_inline.erl | 10 ++++------
lib/compiler/src/sys_pre_attributes.erl | 4 +---
lib/compiler/src/v3_core.erl | 6 ++----
6 files changed, 21 insertions(+), 29 deletions(-)
diff --git a/lib/compiler/src/beam_dict.erl b/lib/compiler/src/beam_dict.erl
index acc18c8a4e..58531dc9a0 100644
--- a/lib/compiler/src/beam_dict.erl
+++ b/lib/compiler/src/beam_dict.erl
@@ -32,8 +32,6 @@
string_table/1,lambda_table/1,literal_table/1,
line_table/1,type_table/1,debug_table/1]).
--compile(nowarn_obsolete_bool_op).
-
-include("beam_types.hrl").
-type label() :: beam_asm:label().
@@ -224,7 +222,7 @@ line([{location,Name,Line}|_], #asm{lines=Lines,num_lines=N,
when is_atom(Instr) ->
{FnameIndex,Dict1} = fname(Name, Dict0),
Key = {FnameIndex,Line},
- ExecLine = ExecLine0 or (Instr =:= executable_line),
+ ExecLine = ExecLine0 orelse Instr =:= executable_line,
case Lines of
#{Key := Index} ->
{Index,Dict1#asm{num_lines=N+1,exec_line=ExecLine}};
diff --git a/lib/compiler/src/beam_ssa_opt.erl b/lib/compiler/src/beam_ssa_opt.erl
index ac7243a076..503a025fe7 100644
--- a/lib/compiler/src/beam_ssa_opt.erl
+++ b/lib/compiler/src/beam_ssa_opt.erl
@@ -40,8 +40,6 @@
-moduledoc false.
-export([module/2]).
--compile(nowarn_obsolete_bool_op).
-
-include("beam_ssa_opt.hrl").
-import(lists, [all/2,append/1,droplast/1,duplicate/2,flatten/1,foldl/3,
@@ -3353,7 +3351,7 @@ unfold_literals([], _, _, Blocks) ->
Blocks.
unfold_update_succ([S|Ss], Safe, SafeMap0) ->
- F = fun(Prev) -> Prev and Safe end,
+ F = fun(Prev) -> Prev andalso Safe end,
SafeMap = maps:update_with(S, F, Safe, SafeMap0),
unfold_update_succ(Ss, Safe, SafeMap);
unfold_update_succ([], _, SafeMap) ->
diff --git a/lib/compiler/src/beam_types.erl b/lib/compiler/src/beam_types.erl
index d2fb473519..6fd6a96039 100644
--- a/lib/compiler/src/beam_types.erl
+++ b/lib/compiler/src/beam_types.erl
@@ -23,8 +23,6 @@
-module(beam_types).
-moduledoc false.
--compile(nowarn_obsolete_bool_op).
-
-define(BEAM_TYPES_INTERNAL, true).
-include("beam_types.hrl").
@@ -843,8 +841,9 @@ glb(#t_atom{elements=[_|_]}=T, #t_atom{elements=any}) ->
glb(#t_atom{elements=any}, #t_atom{elements=[_|_]}=T) ->
T;
glb(#t_bitstring{size_unit=U1,appendable=A1},
- #t_bitstring{size_unit=U2,appendable=A2}) ->
- #t_bitstring{size_unit=U1 * U2 div gcd(U1, U2),appendable=A1 or A2};
+ #t_bitstring{size_unit=U2,appendable=A2})
+ when is_boolean(A1), is_boolean(A2) ->
+ #t_bitstring{size_unit=U1 * U2 div gcd(U1, U2),appendable=A1 orelse A2};
glb(#t_bitstring{size_unit=UnitA,appendable=Appendable}=T,
#t_bs_matchable{tail_unit=UnitB}) ->
Unit = UnitA * UnitB div gcd(UnitA, UnitB),
@@ -973,9 +972,10 @@ glb_tuples(#t_tuple{size=Sz1,exact=Ex1}, #t_tuple{size=Sz2,exact=Ex2})
Ex2, Sz2 < Sz1 ->
none;
glb_tuples(#t_tuple{size=Sz1,exact=Ex1,elements=Es1},
- #t_tuple{size=Sz2,exact=Ex2,elements=Es2}) ->
+ #t_tuple{size=Sz2,exact=Ex2,elements=Es2})
+ when is_boolean(Ex1), is_boolean(Ex2) ->
Size = max(Sz1, Sz2),
- Exact = Ex1 or Ex2,
+ Exact = Ex1 orelse Ex2,
case glb_elements(Es1, Es2) of
none ->
none;
@@ -1039,8 +1039,9 @@ lub(#t_atom{elements=[_|_]=Set1}, #t_atom{elements=[_|_]=Set2}) ->
lub(#t_atom{elements=any}=T, #t_atom{elements=[_|_]}) -> T;
lub(#t_atom{elements=[_|_]}, #t_atom{elements=any}=T) -> T;
lub(#t_bitstring{size_unit=U1,appendable=A1},
- #t_bitstring{size_unit=U2,appendable=A2}) ->
- #t_bitstring{size_unit=gcd(U1, U2),appendable=A1 and A2};
+ #t_bitstring{size_unit=U2,appendable=A2})
+ when is_boolean(A1), is_boolean(A2) ->
+ #t_bitstring{size_unit=gcd(U1, U2),appendable=A1 andalso A2};
lub(#t_bitstring{size_unit=U1}, #t_bs_context{tail_unit=U2}) ->
#t_bs_matchable{tail_unit=gcd(U1, U2)};
lub(#t_bitstring{size_unit=UnitA}, #t_bs_matchable{tail_unit=UnitB}) ->
@@ -1109,8 +1110,9 @@ lub(#t_map{super_key=SKeyA,super_value=SValueA},
SValue = join(SValueA, SValueB),
#t_map{super_key=SKey,super_value=SValue};
lub(#t_tuple{size=Sz,exact=ExactA,elements=EsA},
- #t_tuple{size=Sz,exact=ExactB,elements=EsB}) ->
- Exact = ExactA and ExactB,
+ #t_tuple{size=Sz,exact=ExactB,elements=EsB})
+ when is_boolean(ExactA), is_boolean(ExactB) ->
+ Exact = ExactA andalso ExactB,
Es = lub_tuple_elements(Sz, EsA, EsB),
#t_tuple{size=Sz,exact=Exact,elements=Es};
lub(#t_tuple{size=SzA,elements=EsA}, #t_tuple{size=SzB,elements=EsB}) ->
diff --git a/lib/compiler/src/cerl_inline.erl b/lib/compiler/src/cerl_inline.erl
index 7b11a5afce..be155e6268 100644
--- a/lib/compiler/src/cerl_inline.erl
+++ b/lib/compiler/src/cerl_inline.erl
@@ -39,8 +39,6 @@
-module(cerl_inline).
-moduledoc false.
--compile(nowarn_obsolete_bool_op).
-
-export([core_transform/2, transform/1, transform/2]).
-import(cerl, [abstract/1, alias_pat/1, alias_var/1, apply_args/1,
@@ -1084,7 +1082,7 @@ i_call(E, Ctxt, Ren, Env, S) ->
%% Check if the name of the called function is static. If so,
%% discard the size counts performed above, since the values will
%% not cause any runtime cost.
- Static = is_c_atom(M) and is_c_atom(F),
+ Static = is_c_atom(M) andalso is_c_atom(F),
S3 = case Static of
true ->
revert_size(S, S2);
@@ -2292,7 +2290,7 @@ equivalent(E1, E2, Env) ->
end.
equivalent_lists([E1 | Es1], [E2 | Es2], Env) ->
- equivalent(E1, E2, Env) and equivalent_lists(Es1, Es2, Env);
+ equivalent(E1, E2, Env) andalso equivalent_lists(Es1, Es2, Env);
equivalent_lists([], [], _) ->
true;
equivalent_lists(_, _, _) ->
@@ -2305,7 +2303,7 @@ reduce_bif_call(M, F, As, Env) ->
reduce_bif_call_1(M, F, length(As), As, Env).
reduce_bif_call_1(erlang, element, 2, [X, Y], _Env) ->
- case is_c_int(X) and is_c_tuple(Y) of
+ case is_c_int(X) andalso is_c_tuple(Y) of
true ->
%% We are free to change the relative evaluation order of
%% the elements, so lifting out a particular element is OK.
@@ -2348,7 +2346,7 @@ reduce_bif_call_1(erlang, list_to_tuple, 1, [X], _Env) ->
false
end;
reduce_bif_call_1(erlang, setelement, 3, [X, Y, Z], Env) ->
- case is_c_int(X) and is_c_tuple(Y) of
+ case is_c_int(X) andalso is_c_tuple(Y) of
true ->
%% Here, unless `Z' is a simple expression, we must bind it
%% to a new variable, because in that case, `Z' must be
diff --git a/lib/compiler/src/sys_pre_attributes.erl b/lib/compiler/src/sys_pre_attributes.erl
index 03cc1d6d8d..4bfabe7520 100644
--- a/lib/compiler/src/sys_pre_attributes.erl
+++ b/lib/compiler/src/sys_pre_attributes.erl
@@ -24,8 +24,6 @@
-module(sys_pre_attributes).
-moduledoc false.
--compile(nowarn_obsolete_bool_op).
-
-export([parse_transform/2]).
-define(OPTION_TAG, attributes).
@@ -205,7 +203,7 @@ report_verbose(Format, Args, S) ->
end.
is_warning(S) ->
- lists:member(report_warnings, S#state.options) or is_verbose(S).
+ lists:member(report_warnings, S#state.options) orelse is_verbose(S).
is_verbose(S) ->
lists:member(verbose, S#state.options).
diff --git a/lib/compiler/src/v3_core.erl b/lib/compiler/src/v3_core.erl
index 06151bff64..1ad8cabfc3 100644
--- a/lib/compiler/src/v3_core.erl
+++ b/lib/compiler/src/v3_core.erl
@@ -82,8 +82,6 @@
-module(v3_core).
-moduledoc false.
--compile(nowarn_obsolete_bool_op).
-
-export([module/2,format_error/1]).
-import(lists, [all/2,any/2,append/1,droplast/1,duplicate/2,
@@ -214,7 +212,7 @@ module(Forms0, Opts) ->
end,
Cexp = [#c_var{name=FA} || {_,_}=FA <:- Exp],
Kfs1 = reverse(Kfs0),
- Kfs = if LoadNif and (Nifs =:= none) ->
+ Kfs = if LoadNif, Nifs =:= none ->
insert_nif_start(Kfs1);
true ->
Kfs1
@@ -227,7 +225,7 @@ form({function,_,_,_,_}=F0,
#imodule{defs=Defs,load_nif=LoadNif0}=Module,
Opts) ->
{F,Ws,LoadNif} = function(F0, Module, Opts),
- Module#imodule{defs=[F|Defs],ws=Ws,load_nif=LoadNif or LoadNif0};
+ Module#imodule{defs=[F|Defs],ws=Ws,load_nif=LoadNif orelse LoadNif0};
form({attribute,_,module,Mod}, Module, _Opts) ->
true = is_atom(Mod),
Module#imodule{name=Mod};
--
2.51.0