File 4221-compiler-Add-option-nowarn_unused_record-RecordNames.patch of Package erlang

From ba1eb7326df36828acd5b5cb07d3ccda39bb9e41 Mon Sep 17 00:00:00 2001
From: Hans Bolinder <hasse@erlang.org>
Date: Wed, 14 Apr 2021 15:08:50 +0200
Subject: [PATCH] compiler: Add option {nowarn_unused_record, RecordNames}

Also document option `nowarn_unused_type'.
---
 lib/compiler/doc/src/compile.xml   | 16 ++++++++++++++--
 lib/stdlib/src/erl_lint.erl        | 16 ++++++++++++----
 lib/stdlib/test/erl_lint_SUITE.erl | 29 +++++++++++++++++++++++++++--
 3 files changed, 53 insertions(+), 8 deletions(-)

diff --git a/lib/compiler/doc/src/compile.xml b/lib/compiler/doc/src/compile.xml
index 8906b1c2eb..073d9b4c25 100644
--- a/lib/compiler/doc/src/compile.xml
+++ b/lib/compiler/doc/src/compile.xml
@@ -745,8 +745,20 @@ module.beam: module.erl \
 
 	  <tag><c>nowarn_unused_record</c></tag>
           <item>
-            <p>Turns off warnings for unused record types. Default is to 
-	    emit warnings for unused locally defined record types.</p>
+            <p>Turns off warnings for unused record definitions. Default is to
+	    emit warnings for unused locally defined records.</p>
+          </item>
+
+	  <tag><c>{nowarn_unused_record, RecordNames}</c></tag>
+          <item>
+            <p>Turns off warnings for unused record definitions. Default is to
+	    emit warnings for unused locally defined records.</p>
+          </item>
+
+	  <tag><c>nowarn_unused_type</c></tag>
+          <item>
+            <p>Turns off warnings for unused type declarations. Default is to
+	    emit warnings for unused local type declarations.</p>
           </item>
 
           <tag><c>nowarn_nif_inline</c></tag>
diff --git a/lib/stdlib/src/erl_lint.erl b/lib/stdlib/src/erl_lint.erl
index 4cfc3306cb..157e7ecbd4 100644
--- a/lib/stdlib/src/erl_lint.erl
+++ b/lib/stdlib/src/erl_lint.erl
@@ -1354,19 +1354,27 @@ check_unused_records(Forms, St0) ->
     AttrFiles = [File || {attribute,_L,file,{File,_Line}} <- Forms],
     case {is_warn_enabled(unused_record, St0),AttrFiles} of
         {true,[FirstFile|_]} ->
+            %% There are no line numbers in St0#lint.compile.
+            RecAnno = [{Rec, Anno} ||
+                          {attribute, Anno, compile, Args} <- Forms,
+                          {nowarn_unused_record, Recs0} <- lists:flatten([Args]),
+                          Rec <- lists:flatten([Recs0])],
+            St1 = foldl(fun ({Rec, Anno}, St2) ->
+                                exist_record(Anno, Rec, St2)
+                        end, St0, RecAnno),
             %% The check is a bit imprecise in that uses from unused
             %% functions count.
-            Usage = St0#lint.usage,
+            Usage = St1#lint.usage,
             UsedRecords = Usage#usage.used_records,
             URecs = gb_sets:fold(fun (Used, Recs) ->
                                          maps:remove(Used, Recs)
-                                 end, St0#lint.records, UsedRecords),
+                                 end, St1#lint.records, UsedRecords),
             Unused = [{Name,FileLine} ||
                          {Name,{FileLine,_Fields}} <- maps:to_list(URecs),
-                         element(1, loc(FileLine, St0)) =:= FirstFile],
+                         element(1, loc(FileLine, St1)) =:= FirstFile],
             foldl(fun ({N,L}, St) ->
                           add_warning(L, {unused_record, N}, St)
-                  end, St0, Unused);
+                  end, St1, Unused);
         _ ->
             St0
     end.
diff --git a/lib/stdlib/test/erl_lint_SUITE.erl b/lib/stdlib/test/erl_lint_SUITE.erl
index 49e49944b9..69b9b7dc42 100644
--- a/lib/stdlib/test/erl_lint_SUITE.erl
+++ b/lib/stdlib/test/erl_lint_SUITE.erl
@@ -73,7 +73,8 @@
          external_funs/1,otp_15456/1,otp_15563/1,
          unused_type/1,removed/1, otp_16516/1,
          inline_nifs/1,
-         warn_missing_spec/1]).
+         warn_missing_spec/1,
+         unused_record/1]).
 
 suite() ->
     [{ct_hooks,[ts_install_cth]},
@@ -97,7 +98,8 @@ all() ->
      record_errors, otp_11879_cont, non_latin1_module, otp_14323,
      stacktrace_syntax, otp_14285, otp_14378, external_funs,
      otp_15456, otp_15563, unused_type, removed, otp_16516,
-     inline_nifs, warn_missing_spec].
+     inline_nifs, warn_missing_spec,
+     unused_record].
 
 groups() -> 
     [{unused_vars_warn, [],
@@ -4581,6 +4582,30 @@ warn_missing_spec(Config) ->
                         {11, erl_lint, {missing_spec, {internal_no_spec, 0}}}]}}
     ]).
 
+unused_record(Config) when is_list(Config) ->
+    Ts = [{unused_record_1,
+          <<"-export([t/0]).
+             -record(a, {x,y}).
+             -compile({nowarn_unused_record,a}).
+              t() ->
+                  a.
+            ">>,
+           {[]},
+           []},
+          {unused_record_2,
+          <<"-export([t/0]).
+             -record(a, {x,y}).
+             -compile(nowarn_unused_record).
+              t() ->
+                  a.
+            ">>,
+           {[]},
+           []}
+         ],
+    [] = run(Config, Ts),
+
+    ok.
+
 format_error(E) ->
     lists:flatten(erl_lint:format_error(E)).
 
-- 
2.26.2

openSUSE Build Service is sponsored by