File 3121-Allow-underscore-variables-to-suppress-all-warnings.patch of Package erlang

From 2d14bacec0d68524f2c5b4bdc59d7b60f6268357 Mon Sep 17 00:00:00 2001
From: =?UTF-8?q?Bj=C3=B6rn=20Gustavsson?= <bjorn@erlang.org>
Date: Thu, 29 Oct 2020 07:00:33 +0100
Subject: [PATCH] Allow "underscore variables" to suppress all warnings

Compiler warnings for unused variables can be suppressed by prefixing
the variable name with an underscore (`_`). Other kind of warnings
(such as ignoring the result of an expression without side effects)
can only be ignored by assigning (or, strictly speaking, matching) the
result of the expression to the anonymous variable (`_`). This
distinction can be confusing, so this commit teaches the compiler to
suppress all warnings when an expression is assigned to a variable
that begins with an underscore.

Specification
-------------

Consider this function:

    foobar(A, B, C) ->
        {ignore,A},
        element(1, B),
        ok.

There will be three compiler warnings:

    module.erl:4: Warning: variable 'C' is unused
    module.erl:5: Warning: a term is constructed, but never used
    module.erl:6: Warning: the result of the expression is ignored (suppress the warning by assigning the expression to the _ variable)

The warning for the unused variable `C` can be suppressed by prefixing
the name with `_`. However, trying to suppress the other two warnings
this way:

    foobar(A, B, _C) ->
        _ignored_term = {ignore,A},
        _ignored_result = element(1, B),
        ok.

does not work:

module.erl:5: Warning: a term is constructed, but never used
module.erl:6: Warning: the result of the expression is ignored (suppress the warning by assigning the expression to the _ variable)

Currently, the only way to suppress the warnings is to assign the
expressions to the anonymous variable:

    foobar(A, B, _C) ->
        _ = {ignore,A},
        _ = element(1, B),
        ok.

This commit teaches the compiler to suppress all warnings when the
result is assigned to a variable that begins with `_`.

Motivation
----------

It is confusing that a variable beginning with underscore can suppress only some warnings.

The inability to suppress warnings assigned to a term disallows some
legitimate use cases, such as:

    bar(A, B, C) ->
        _Term = {very_complex_term, {A, B, C}},
        %%io:format("~p\n", [_Term]),
        do_something(A, B, C).

Here the intention is that the comment markers before the
`io:format/2` call can be removed during debugging. Currently, there
will be a warning for the line that binds a term to `_Term` (and a
compilation error if `warnings_as_errors` is enabled).

Another example is that the following code (which currently produces a warning):

    _Assertion = map_get(Key, Map)

will raise a `{badkey,Key}` exception which is more informative than
the `{badmatch,false}` exception raised by:

    true = is_map_key(Key, Map)   %Assertion

Backwards Compatibility
-----------------------

Since the compiler with this change will produce fewer warnings than
before, this change is backwards compatible.
---
 lib/compiler/src/v3_core.erl                | 19 ++++++++--
 lib/compiler/test/warnings_SUITE.erl        | 42 +++++++++++++++------
 system/doc/reference_manual/expressions.xml |  6 +--
 3 files changed, 48 insertions(+), 19 deletions(-)

diff --git a/lib/compiler/src/v3_core.erl b/lib/compiler/src/v3_core.erl
index 74a45b7279..7798859e59 100644
--- a/lib/compiler/src/v3_core.erl
+++ b/lib/compiler/src/v3_core.erl
@@ -691,10 +691,7 @@ expr({call,L,FunExp,As0}, St0) ->
 expr({match,L,P0,E0}, St0) ->
     %% First fold matches together to create aliases.
     {P1,E1} = fold_match(E0, P0),
-    St1 = case P1 of
-	      {var,_,'_'} -> St0#core{wanted=false};
-	      _ -> St0
-	  end,
+    St1 = set_wanted(P1, St0),
     {E2,Eps1,St2} = novars(E1, St1),
     St3 = St2#core{wanted=St0#core.wanted},
     {P2,Eps2,St4} = try
@@ -781,6 +778,19 @@ expr({op,L,Op,L0,R0}, St0) ->
 	    module=#c_literal{anno=LineAnno,val=erlang},
 	    name=#c_literal{anno=LineAnno,val=Op},args=As},Aps,St1}.
 
+%% set_wanted(Pattern, St) -> St'.
+%%  Suppress warnings for expressions that are bound to the '_'
+%%  variable and variables that begin with '_'.
+set_wanted({var,_,'_'}, St) ->
+    St#core{wanted=false};
+set_wanted({var,_,Var}, St) ->
+    case atom_to_list(Var) of
+        "_" ++ _ ->
+            St#core{wanted=false};
+        _ ->
+            St
+    end;
+set_wanted(_, St) -> St.
 
 %% sanitize(Pat) -> SanitizedPattern
 %%  Rewrite Pat so that it will be accepted by pattern/2 and will
diff --git a/lib/compiler/test/warnings_SUITE.erl b/lib/compiler/test/warnings_SUITE.erl
index 7fdc08eea2..1229a13e38 100644
--- a/lib/compiler/test/warnings_SUITE.erl
+++ b/lib/compiler/test/warnings_SUITE.erl
@@ -819,6 +819,7 @@ latin1_fallback(Conf) when is_list(Conf) ->
     ok.
 
 underscore(Config) when is_list(Config) ->
+    %% The code template.
     S0 = <<"f(A) ->
               _VAR1 = <<A>>,
               _VAR2 = {ok,A},
@@ -835,26 +836,43 @@ underscore(Config) when is_list(Config) ->
                _VAR1 = #{A=>42},
 	      ok.
 	 ">>,
-    Ts0 = [{underscore0,
-	    S0,
-	    [],
-	    {warnings,[{2,sys_core_fold,useless_building},
-		       {3,sys_core_fold,useless_building},
-		       {4,sys_core_fold,useless_building},
-		       {7,sys_core_fold,result_ignored},
-		       {8,sys_core_fold,{no_effect,{erlang,date,0}}},
-		       {11,sys_core_fold,useless_building},
-		       {14,sys_core_fold,useless_building}
-		      ]}}],
+
+    %% Define all possible warnings.
+    Warnings = [{2,sys_core_fold,useless_building},
+                {3,sys_core_fold,useless_building},
+                {4,sys_core_fold,useless_building},
+                {7,sys_core_fold,result_ignored},
+                {8,sys_core_fold,{no_effect,{erlang,date,0}}},
+                {11,sys_core_fold,useless_building},
+                {14,sys_core_fold,useless_building}],
+
+
+    %% Compile the unmodified template. Assigning to variable that
+    %% begins with '_' should suppress all warnings.
+    Ts0 = [{underscore0,S0,[],[]}],
     [] = run(Config, Ts0),
 
     %% Replace all "_VAR<digit>" variables with a plain underscore.
-    %% Now there should be no warnings.
+    %% There should still be no warnings.
     S1 = re:replace(S0, "_VAR\\d+", "_", [global]),
     io:format("~s\n", [S1]),
     Ts1 = [{underscore1,S1,[],[]}],
     [] = run(Config, Ts1),
 
+    %% Make sure that we get warnings if we remove "_VAR<digit> = ".
+    S2 = re:replace(S0, "_VAR\\d+ = ", "", [global]),
+    io:format("~s\n", [S2]),
+    Ts2 = [{underscore2,S2,[],{warnings,Warnings}}],
+    [] = run(Config, Ts2),
+
+    %% We should also get warnings if we assign to a variables that don't
+    %% begin with underscore (as well as warnings for unused variables from
+    %% erl_lint).
+    S3 = re:replace(S0, "_(?=VAR\\d+)", "", [global]),
+    io:format("~s\n", [S3]),
+    Ts3 = [{underscore2,S3,[],{warnings,Warnings}}],
+    [] = run(Config, Ts3),
+
     ok.
 
 no_warnings(Config) when is_list(Config) ->
diff --git a/system/doc/reference_manual/expressions.xml b/system/doc/reference_manual/expressions.xml
index 9747cc9a04..1a7dddb0b8 100644
--- a/system/doc/reference_manual/expressions.xml
+++ b/system/doc/reference_manual/expressions.xml
@@ -92,9 +92,9 @@ _Height</pre>
     <pre>
 [H|_] = [1,2,3]</pre>
     <p>Variables starting with underscore (_), for example,
-      <c>_Height</c>, are normal variables, not anonymous. They are
-      however ignored by the compiler in the sense that they do not
-      generate any warnings for unused variables.</p>
+      <c>_Height</c>, are normal variables, not anonymous. However,
+      they are ignored by the compiler in the sense that they do not
+      generate warnings.</p>
       <p><em>Example:</em></p>
       <p>The following code:</p>
     <pre>
-- 
2.26.2

openSUSE Build Service is sponsored by