File 4941-erl_lint-Warn-on-matching-float-0.0.patch of Package erlang

From 5e193bd4ff0b4b511ecc89f35fcf14aa5989a21c Mon Sep 17 00:00:00 2001
From: =?UTF-8?q?John=20H=C3=B6gberg?= <john@erlang.org>
Date: Tue, 1 Aug 2023 12:59:18 +0200
Subject: [PATCH] erl_lint: Warn on matching float 0.0

---
 lib/stdlib/src/erl_lint.erl        | 33 +++++++++++++++++++++++++++-
 lib/stdlib/test/erl_lint_SUITE.erl | 35 ++++++++++++++++++++++++++++--
 2 files changed, 65 insertions(+), 3 deletions(-)

diff --git a/lib/stdlib/src/erl_lint.erl b/lib/stdlib/src/erl_lint.erl
index 55e53cad3d..893fe4dbae 100644
--- a/lib/stdlib/src/erl_lint.erl
+++ b/lib/stdlib/src/erl_lint.erl
@@ -320,6 +320,9 @@ format_error({illegal_guard_local_call, {F,A}}) ->
     io_lib:format("call to local/imported function ~tw/~w is illegal in guard",
 		  [F,A]);
 format_error(illegal_guard_expr) -> "illegal guard expression";
+format_error(match_float_zero) ->
+    "matching on the float 0.0 will no longer also match -0.0 in OTP 27. If "
+    "you specifically intend to match 0.0 alone, write +0.0 instead.";
 %% --- maps ---
 format_error(illegal_map_construction) ->
     "only association operators '=>' are allowed in map construction";
@@ -672,6 +675,9 @@ start(File, Opts) ->
                       true, Opts)},
          {singleton_typevar,
           bool_option(warn_singleton_typevar, nowarn_singleton_typevar,
+                      true, Opts)},
+         {match_float_zero,
+          bool_option(warn_match_float_zero, nowarn_match_float_zero,
                       true, Opts)}
 	],
     Enabled1 = [Category || {Category,true} <- Enabled0],
@@ -1704,7 +1710,12 @@ pattern({var,Anno,V}, _Vt, Old, St) ->
     pat_var(V, Anno, Old, [], St);
 pattern({char,_Anno,_C}, _Vt, _Old, St) -> {[],[],St};
 pattern({integer,_Anno,_I}, _Vt, _Old, St) -> {[],[],St};
-pattern({float,_Anno,_F}, _Vt, _Old, St) -> {[],[],St};
+pattern({float,Anno,F}, _Vt, _Old, St0) ->
+    St = case F == 0 andalso is_warn_enabled(match_float_zero, St0) of
+             true -> add_warning(Anno, match_float_zero, St0);
+             false -> St0
+         end,
+    {[], [], St};
 pattern({atom,Anno,A}, _Vt, _Old, St) ->
     {[],[],keyword_warning(Anno, A, St)};
 pattern({string,_Anno,_S}, _Vt, _Old, St) -> {[],[],St};
@@ -2149,6 +2160,9 @@ gexpr({op,_,'andalso',L,R}, Vt, St) ->
     gexpr_list([L,R], Vt, St);
 gexpr({op,_,'orelse',L,R}, Vt, St) ->
     gexpr_list([L,R], Vt, St);
+gexpr({op,_Anno,EqOp,L,R}, Vt, St0) when EqOp =:= '=:='; EqOp =:= '=/=' ->
+    St1 = expr_check_match_zero(R, expr_check_match_zero(L, St0)),
+    gexpr_list([L,R], Vt, St1);
 gexpr({op,Anno,Op,L,R}, Vt, St0) ->
     {Avt,St1} = gexpr_list([L,R], Vt, St0),
     case is_gexpr_op(Op, 2) of
@@ -2565,6 +2579,9 @@ expr({op,Anno,Op,L,R}, Vt, St0) when Op =:= 'orelse'; Op =:= 'andalso' ->
     {Evt2,St2} = expr(R, Vt1, St1),
     Evt3 = vtupdate(vtunsafe({Op,Anno}, Evt2, Vt1), Evt2),
     {vtmerge(Evt1, Evt3),St2};
+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
 %% The following are not allowed to occur anywhere!
@@ -2573,6 +2590,20 @@ expr({remote,_Anno,M,_F}, _Vt, St) ->
 expr({ssa_check_when,_Anno,_WantedResult,_Args,_Tag,_Exprs}, _Vt, St) ->
     {[], St}.
 
+%% Checks whether 0.0 occurs naked in the LHS or RHS of an equality check. Note
+%% that we do not warn when it's being used as arguments for expressions in
+%% in general: `A =:= abs(0.0)` is fine.
+expr_check_match_zero({float,Anno,F}, St) ->
+    case F == 0 andalso is_warn_enabled(match_float_zero, St) of
+        true -> add_warning(Anno, match_float_zero, St);
+        false -> St
+    end;
+expr_check_match_zero({cons,_Anno,H,T}, St) ->
+    expr_check_match_zero(H, expr_check_match_zero(T, St));
+expr_check_match_zero({tuple,_Anno,Es}, St) ->
+    foldl(fun expr_check_match_zero/2, St, Es);
+expr_check_match_zero(_Expr, St) ->
+    St.
 
 %% expr_list(Expressions, Variables, State) ->
 %%      {UsedVarTable,State}
diff --git a/lib/stdlib/test/erl_lint_SUITE.erl b/lib/stdlib/test/erl_lint_SUITE.erl
index 81bc3e9a0d..3c45dd1cb9 100644
--- a/lib/stdlib/test/erl_lint_SUITE.erl
+++ b/lib/stdlib/test/erl_lint_SUITE.erl
@@ -80,7 +80,8 @@
          unused_record/1,
          unused_type2/1,
          eep49/1,
-         redefined_builtin_type/1]).
+         redefined_builtin_type/1,
+         match_float_zero/1]).
 
 suite() ->
     [{ct_hooks,[ts_install_cth]},
@@ -110,7 +110,8 @@ all() ->
      underscore_match, unused_record, unused_type2,
      eep49,
      redefined_builtin_type,
-     singleton_type_var_errors].
+     singleton_type_var_errors,
+     match_float_zero].
 
 groups() -> 
     [{unused_vars_warn, [],
@@ -5064,6 +5066,35 @@ redefined_builtin_type(Config) ->
     [] = run(Config, Ts),
     ok.
 
+match_float_zero(Config) ->
+    Ts = [{float_zero_1,
+           <<"t(+0.0) -> ok.\n"
+             "k(-0.0) -> ok.\n">>,
+           [],
+           []},
+          {float_zero_2,
+           <<"t(0.0) -> ok.\n"
+             "k({0.0}) -> ok.\n">>,
+           [],
+           {warnings,[{{1,23},erl_lint,match_float_zero},
+                      {{2,4},erl_lint,match_float_zero}]}},
+          {float_zero_3,
+           <<"t(A) when A =:= 0.0 -> ok;\n" %% Should warn.
+             "t(A) when A =:= {0.0} -> ok.\n" %% Should warn.
+             "k(A) -> A =:= 0.0.\n" %% Should warn.
+             "q(A) -> A =:= {0.0}.\n" %% Should warn.
+             "z(A) when A =:= +0.0 -> ok;\n" %% Should not warn.
+             "z(A) when A =:= {+0.0} -> ok.\n">>, %% Should not warn.
+           [],
+           {warnings,[{{1,37},erl_lint,match_float_zero},
+                      {{2,18},erl_lint,match_float_zero},
+                      {{3,15},erl_lint,match_float_zero},
+                      {{4,16},erl_lint,match_float_zero}]}}
+         ],
+    [] = run(Config, Ts),
+
+    ok.
+
 format_error(E) ->
     lists:flatten(erl_lint:format_error(E)).
 
-- 
2.35.3

openSUSE Build Service is sponsored by