File 4231-stdlib-Silence-unused_record-warnings-after-ms_trans.patch of Package erlang

From fbdad6ed4430636d93a2bf959745504c83f7bef2 Mon Sep 17 00:00:00 2001
From: Hans Bolinder <hasse@erlang.org>
Date: Tue, 13 Apr 2021 10:54:03 +0200
Subject: [PATCH] stdlib: Silence unused_record warnings after ms_transform

The parse transform `ms_transform' replaces records with tuples, which
can cause the Erlang code linter to emit warnings about unused
records.

To that end the warnings are suppressed by adding:

-compile({nowarn_unused_record, RecordNames}).

where RecordNames are the names of all replaced records (even if there
are already suppressions present).
---
 lib/stdlib/src/ms_transform.erl        | 79 ++++++++++++++++----------
 lib/stdlib/test/ms_transform_SUITE.erl | 17 ++++--
 2 files changed, 62 insertions(+), 34 deletions(-)

diff --git a/lib/stdlib/src/ms_transform.erl b/lib/stdlib/src/ms_transform.erl
index dd8417a75d..afa886be14 100644
--- a/lib/stdlib/src/ms_transform.erl
+++ b/lib/stdlib/src/ms_transform.erl
@@ -285,6 +285,7 @@ put_filename(Name) ->
 put_records(R) ->
     put(records,R),
     ok.
+
 get_records() ->
     case get(records) of
 	undefined ->
@@ -292,6 +293,17 @@ get_records() ->
 	Else ->
 	    Else
     end.
+
+get_record(RName) ->
+    case lists:keyfind(RName, 1, get_records()) of
+        {RName, FieldList} ->
+            put(records_replaced_by_tuples,
+                [RName|get(records_replaced_by_tuples)]),
+            FieldList;
+        false ->
+            not_found
+    end.
+
 cleanup_filename({Old,OldRec,OldWarnings}) ->
     Ret = case erase(filename) of
 	      undefined ->
@@ -333,11 +345,24 @@ record_field({record_field,_,{atom,_,FieldName},Def}, C) ->
 record_field({typed_record_field,Field,_Type}, C) ->
     record_field(Field, C).
 
-forms([F0|Fs0]) ->
-    F1 = form(F0),
-    Fs1 = forms(Fs0),
-    [F1|Fs1];
-forms([]) -> [].
+forms(Forms0) ->
+    put(records_replaced_by_tuples, []),
+    try
+        Forms = [form(F) || F <- Forms0],
+        %% Add `-compile({nowarn_unused_record, RecordNames}).', where
+        %% RecordNames is the names of all records replaced by tuples,
+        %% in order to silence the code linter's warnings about unused
+        %% records.
+        case get(records_replaced_by_tuples) of
+            [] ->
+                Forms;
+            RNames ->
+                NoWarn = {nowarn_unused_record,[lists:usort(RNames)]},
+                [{attribute,erl_anno:new(0),compile,NoWarn}] ++ Forms
+        end
+    after
+        erase(records_replaced_by_tuples)
+    end.
 
 form({attribute,_,file,{Filename,_}}=Form) ->
     put_filename(Filename),
@@ -350,9 +375,11 @@ form({function,Line,Name0,Arity0,Clauses0}) ->
     {function,Line,Name,Arity,Clauses};
 form(AnyOther) ->
     AnyOther.
+
 function(Name, Arity, Clauses0) ->
     Clauses1 = clauses(Clauses0),
     {Name,Arity,Clauses1}.
+
 clauses([C0|Cs]) ->
     C1 = clause(C0,gb_sets:new()),
     C2 = clauses(Cs),
@@ -529,12 +556,11 @@ tg({call, _Line, {atom, Line2, object},[]},_B) ->
     	    {atom, Line2, '$_'};
 tg({call, Line, {atom, _, is_record}=Call,[Object, {atom,Line3,RName}=R]},B) ->
     MSObject = tg(Object,B),
-    RDefs = get_records(),
-    case lists:keysearch(RName,1,RDefs) of
-	{value, {RName, FieldList}} ->
+    case get_record(RName) of
+	FieldList when is_list(FieldList) ->
 	    RSize = length(FieldList)+1,
 	    {tuple, Line, [Call, MSObject, R, {integer, Line3, RSize}]};
-	_ ->
+	not_found ->
 	    throw({error,Line3,{?ERR_GENBADREC+B#tgd.eb,RName}})
     end;
 tg({call, Line, {atom, Line2, FunName},ParaList},B) ->
@@ -593,9 +619,8 @@ tg({var,Line,VarName},B) ->
 	    {atom, Line, AtomName}
     end;
 tg({record_field,Line,Object,RName,{atom,_Line1,KeyName}},B) ->
-    RDefs = get_records(),
-    case lists:keysearch(RName,1,RDefs) of
-	{value, {RName, FieldList}} ->
+    case get_record(RName) of
+	FieldList when is_list(FieldList) ->
 	    case lists:keysearch(KeyName,1, FieldList) of
 		{value, {KeyName,Position,_}} ->
 		    NewObject = tg(Object,B),
@@ -605,12 +630,11 @@ tg({record_field,Line,Object,RName,{atom,_Line1,KeyName}},B) ->
 		    throw({error,Line,{?ERR_GENBADFIELD+B#tgd.eb, RName, 
 				       KeyName}})
 	    end;
-	_ ->
+	not_found ->
 	    throw({error,Line,{?ERR_GENBADREC+B#tgd.eb,RName}})
     end;
 
 tg({record,Line,RName,RFields},B) ->
-    RDefs = get_records(),
     KeyList0 = lists:foldl(fun({record_field,_,{atom,_,Key},Value},
 				     L) ->
 					 NV = tg(Value,B),
@@ -639,8 +663,8 @@ tg({record,Line,RName,RFields},B) ->
 	_ ->
 	    ok
     end,
-    case lists:keysearch(RName,1,RDefs) of
-	{value, {RName, FieldList0}} ->
+    case get_record(RName) of
+	FieldList0 when is_list(FieldList0) ->
 	    FieldList1 = lists:foldl(
 			   fun({FN,_,Def},Acc) ->
 				   El = case lists:keysearch(FN,1,KeyList) of
@@ -663,14 +687,13 @@ tg({record,Line,RName,RFields},B) ->
 	    check_undef_field(RName,Line,KeyList,FieldList0,
 			      ?ERR_GENBADFIELD+B#tgd.eb),
 	    {tuple,Line,[{tuple,Line,[{atom,Line,RName}|FieldList1]}]};
-	_ ->
+	not_found ->
 	    throw({error,Line,{?ERR_GENBADREC+B#tgd.eb,RName}})
     end;
 
 tg({record_index,Line,RName,{atom,Line2,KeyName}},B) ->
-    RDefs = get_records(), 
-    case lists:keysearch(RName,1,RDefs) of
-	{value, {RName, FieldList}} ->
+    case get_record(RName) of
+	FieldList when is_list(FieldList) ->
 	    case lists:keysearch(KeyName,1, FieldList) of
 		{value, {KeyName,Position,_}} ->
 		    {integer, Line2, Position};
@@ -678,12 +701,11 @@ tg({record_index,Line,RName,{atom,Line2,KeyName}},B) ->
 		    throw({error,Line2,{?ERR_GENBADFIELD+B#tgd.eb, RName, 
 				       KeyName}})
 	    end;
-	_ ->
+	not_found ->
 	    throw({error,Line,{?ERR_GENBADREC+B#tgd.eb,RName}})
     end;
 
 tg({record,Line,{var,Line2,_VName}=AVName, RName,RFields},B) ->
-    RDefs = get_records(),
     MSVName = tg(AVName,B),
     KeyList = lists:foldl(fun({record_field,_,{atom,_,Key},Value},
 				     L) ->
@@ -694,8 +716,8 @@ tg({record,Line,{var,Line2,_VName}=AVName, RName,RFields},B) ->
 				 end,
 				 [],
 				 RFields),
-    case lists:keysearch(RName,1,RDefs) of
-	{value, {RName, FieldList0}} ->
+    case get_record(RName) of
+	FieldList0 when is_list(FieldList0) ->
 	    FieldList1 = lists:foldl(
 			   fun({FN,Pos,_},Acc) ->
 				   El = case lists:keysearch(FN,1,KeyList) of
@@ -716,7 +738,7 @@ tg({record,Line,{var,Line2,_VName}=AVName, RName,RFields},B) ->
 	    check_undef_field(RName,Line,KeyList,FieldList0,
 			      ?ERR_GENBADFIELD+B#tgd.eb),
 	    {tuple,Line,[{tuple,Line,[{atom,Line,RName}|FieldList1]}]};
-	_ ->
+	not_found ->
 	    throw({error,Line,{?ERR_GENBADREC+B#tgd.eb,RName}})
     end;
 
@@ -761,7 +783,6 @@ toplevel_head_match(Other,B,_OB) ->
 
 th({record,Line,RName,RFields},B,OB) ->
     % youch...
-    RDefs = get_records(),
     {KeyList0,NewB} = lists:foldl(fun({record_field,_,{atom,_,Key},Value},
 				     {L,B0}) ->
 					 {NV,B1} = th(Value,B0,OB),
@@ -789,8 +810,8 @@ th({record,Line,RName,RFields},B,OB) ->
 	_ ->
 	    ok
     end,
-    case lists:keysearch(RName,1,RDefs) of
-	{value, {RName, FieldList0}} ->
+    case get_record(RName) of
+	FieldList0 when is_list(FieldList0) ->
 	    FieldList1 = lists:foldl(
 			   fun({FN,_,_},Acc) ->
 				   El = case lists:keysearch(FN,1,KeyList) of
@@ -808,7 +829,7 @@ th({record,Line,RName,RFields},B,OB) ->
 	    check_undef_field(RName,Line,KeyList,FieldList0,
 			      ?ERR_HEADBADFIELD),
 	    {{tuple,Line,[{atom,Line,RName}|FieldList1]},NewB};
-	_ ->
+	not_found ->
 	    throw({error,Line,{?ERR_HEADBADREC,RName}})
     end;
 th({match,Line,_,_},_,_) ->
diff --git a/lib/stdlib/test/ms_transform_SUITE.erl b/lib/stdlib/test/ms_transform_SUITE.erl
index 6ac38b73fa..0aefda4724 100644
--- a/lib/stdlib/test/ms_transform_SUITE.erl
+++ b/lib/stdlib/test/ms_transform_SUITE.erl
@@ -45,6 +45,7 @@
 -export([no_warnings/1]).
 -export([eep37/1]).
 -export([otp_14454/1]).
+-export([unused_record/1]).
 
 init_per_testcase(_Func, Config) ->
     Config.
@@ -61,7 +62,7 @@ all() ->
      record_index, multipass, bitsyntax, binary_bifs, record_defaults,
      andalso_orelse, float_1_function, action_function,
      warnings, no_warnings, top_match, old_guards, autoimported,
-     semicolon, eep37, otp_14454].
+     semicolon, eep37, otp_14454, unused_record].
 
 groups() -> 
     [].
@@ -804,6 +805,13 @@ otp_14454(Config) when is_list(Config) ->
           <<"ets:fun2ms(fun(A) -> A band ( erlang:'bsl'(-(-17), 3)) end)">>),
     ok.
 
+%% OTP-17186.
+unused_record(Config) when is_list(Config) ->
+    setup(Config),
+    Record = <<"-record(r, {f}).\n\n">>,
+    Expr = <<"ets:fun2ms(fun(#r{}) -> e end)">>,
+    [] = compile_ww(Record, Expr),
+    ok.
 
 %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 %% Helpers
@@ -864,8 +873,7 @@ compile_ww(Records,Expr) ->
     file:write_file(FN,Prog),
     {ok,Forms} = epp:parse_file(FN,"",""),
     {ok,tmp,_Bin,Wlist} = compile:forms(Forms,[return_warnings,
-					       nowarn_unused_vars,
-					       nowarn_unused_record]),
+					       nowarn_unused_vars]),
     Wlist.
 
 compile_no_ww(Expr) ->
@@ -878,8 +886,7 @@ compile_no_ww(Expr) ->
     file:write_file(FN,Prog),
     {ok,Forms} = epp:parse_file(FN,"",""),
     {ok,tmp,_Bin,Wlist} = compile:forms(Forms,[return_warnings,
-					       nowarn_unused_vars,
-					       nowarn_unused_record]),
+					       nowarn_unused_vars]),
     Wlist.
 
 do_eval(String) ->
-- 
2.26.2

openSUSE Build Service is sponsored by