File 0209-compiler-Disallow-_-as-record-field-key-without-effe.patch of Package erlang

From e361707e1a70306773aa90d1f6d9941f0f12f1cd Mon Sep 17 00:00:00 2001
From: Hans Bolinder <hasse@erlang.org>
Date: Fri, 28 Feb 2020 14:43:21 +0100
Subject: [PATCH 1/2] compiler: Disallow '_' as record field key without effect

There is no way to fix:

  -record(r, {f}).
  f(#r{f = 3, _ = V}) -> V.

Compilation with 'E' showed why:

  f({r, 3}) ->
      V.
---
 lib/stdlib/src/erl_lint.erl        | 16 ++++++++++---
 lib/stdlib/test/erl_lint_SUITE.erl | 47 +++++++++++++++++++++++++++++++++++---
 2 files changed, 57 insertions(+), 6 deletions(-)

diff --git a/lib/stdlib/src/erl_lint.erl b/lib/stdlib/src/erl_lint.erl
index 5163b0df1d..7b86015594 100644
--- a/lib/stdlib/src/erl_lint.erl
+++ b/lib/stdlib/src/erl_lint.erl
@@ -2,7 +2,7 @@
 %%
 %% %CopyrightBegin%
 %%
-%% Copyright Ericsson AB 1996-2019. All Rights Reserved.
+%% Copyright Ericsson AB 1996-2020. All Rights Reserved.
 %%
 %% Licensed under the Apache License, Version 2.0 (the "License");
 %% you may not use this file except in compliance with the License.
@@ -272,6 +272,8 @@ format_error({redefine_record,T}) ->
     io_lib:format("record ~tw already defined", [T]);
 format_error({redefine_field,T,F}) ->
     io_lib:format("field ~tw already defined in record ~tw", [F,T]);
+format_error(bad_multi_field_init) ->
+    io_lib:format("'_' initializes no omitted fields", []);
 format_error({undefined_field,T,F}) ->
     io_lib:format("field ~tw undefined in record ~tw", [F,T]);
 format_error(illegal_record_info) ->
@@ -1544,7 +1546,8 @@ pattern({record,Line,Name,Pfs}, Vt, Old, Bvt, St) ->
     case dict:find(Name, St#lint.records) of
         {ok,{_Line,Fields}} ->
             St1 = used_record(Name, St),
-            pattern_fields(Pfs, Name, Fields, Vt, Old, Bvt, St1);
+            St2 = check_multi_field_init(Pfs, Line, Fields, St1),
+            pattern_fields(Pfs, Name, Fields, Vt, Old, Bvt, St2);
         error -> {[],[],add_error(Line, {undefined_record,Name}, St)}
     end;
 pattern({bin,_,Fs}, Vt, Old, Bvt, St) ->
@@ -1575,7 +1578,14 @@ pattern_list(Ps, Vt, Old, Bvt0, St) ->
                   {vtmerge_pat(Pvt, Psvt),vtmerge_pat(Bvt,Bvt1),St1}
           end, {[],[],St}, Ps).
 
-
+%% Check for '_' initializing no fields.
+check_multi_field_init(Fs, Line, Fields, St) ->
+    case
+        has_wildcard_field(Fs) andalso init_fields(Fs, Line, Fields) =:= []
+    of
+        true -> add_error(Line, bad_multi_field_init, St);
+        false -> St
+    end.
 
 %% reject_invalid_alias(Pat, Expr, Vt, St) -> St'
 %%  Reject aliases for binary patterns at the top level.
diff --git a/lib/stdlib/test/erl_lint_SUITE.erl b/lib/stdlib/test/erl_lint_SUITE.erl
index c27b928a5a..0533aef4d2 100644
--- a/lib/stdlib/test/erl_lint_SUITE.erl
+++ b/lib/stdlib/test/erl_lint_SUITE.erl
@@ -1,7 +1,7 @@
 %%
 %% %CopyrightBegin%
 %%
-%% Copyright Ericsson AB 1999-2019. All Rights Reserved.
+%% Copyright Ericsson AB 1999-2020. All Rights Reserved.
 %%
 %% Licensed under the Apache License, Version 2.0 (the "License");
 %% you may not use this file except in compliance with the License.
@@ -68,7 +68,7 @@
          non_latin1_module/1, otp_14323/1,
          otp_15563/1,
          get_stacktrace/1, otp_14285/1, otp_14378/1,
-         unused_type/1]).
+         unused_type/1, otp_16516/1]).
 
 suite() ->
     [{ct_hooks,[ts_install_cth]},
@@ -91,7 +91,7 @@ all() ->
      record_errors, otp_11879_cont, non_latin1_module, otp_14323,
      otp_15563,
      get_stacktrace, otp_14285, otp_14378,
-     unused_type].
+     unused_type, otp_16516].
 
 groups() -> 
     [{unused_vars_warn, [],
@@ -4220,6 +4220,47 @@ removed(Config) when is_list(Config) ->
     [] = run(Config, Ts),
     ok.
 
+otp_16516(Config) when is_list(Config) ->
+    "'_' initializes no omitted fields" =
+        format_error(bad_multi_field_init),
+    Ts = [{otp_16516_1,
+           <<"-record(r, {f}).
+              t(#r{f = 17, _ = V}) ->
+                  V.
+              u(#r{_ = V, f = 17}) ->
+                  V.
+              -record(r1, {f, g = 17}).
+              g(#r1{f = 3, _ = 42}) ->
+                g.
+             ">>,
+           [],
+           {errors,[{2,erl_lint,bad_multi_field_init},
+                    {4,erl_lint,bad_multi_field_init}],[]}},
+          {otp_16516_2,
+           %% No error since "_ = '_'" is actually used as a catch-all
+           %% initialization. V is unused (as compilation with the 'E'
+           %% option shows), but no warning about V being unused is
+           %% output.
+           <<"-record(r, {f}).
+              t(V) ->
+                  #r{f = 3, _ = V}.
+              u(V) ->
+                  #r{_ = V, f = 3}.
+             ">>,
+           [],
+           []},
+          {otp_16516_3,
+           %% No error in this case either. And no unused variable warning.
+           <<"-record(r, {f}).
+              t(V) when #r{f = 3, _ = V} =:= #r{f = 3} ->
+                  a.
+              u(V) when #r{_ = V, f = 3} =:= #r{f = 3} ->
+                  a.
+             ">>,
+           [],
+           []}],
+    [] = run(Config, Ts).
+
 format_error(E) ->
     lists:flatten(erl_lint:format_error(E)).
 
-- 
2.16.4

openSUSE Build Service is sponsored by