File 0586-parsetools-Fix-compiler-warning-in-generated-code.patch of Package erlang

From 33e7948d29c6b67f10939fd0b66e1f1079f3ebe1 Mon Sep 17 00:00:00 2001
From: Hans Bolinder <hasse@erlang.org>
Date: Fri, 23 Jul 2021 15:37:17 +0200
Subject: [PATCH] parsetools: Fix compiler warning in generated code

See also https://github.com/erlang/otp/issues/5067.
---
 lib/parsetools/src/yecc.erl        | 24 +++++++------
 lib/parsetools/test/yecc_SUITE.erl | 56 ++++++++++++++++++++++--------
 2 files changed, 54 insertions(+), 26 deletions(-)

diff --git a/lib/parsetools/src/yecc.erl b/lib/parsetools/src/yecc.erl
index df811505b5..98b7102293 100644
--- a/lib/parsetools/src/yecc.erl
+++ b/lib/parsetools/src/yecc.erl
@@ -2092,7 +2092,7 @@ output_goto(St, [{_Nonterminal, []} | Go], StateInfo) ->
     output_goto(St, Go, StateInfo);
 output_goto(St0, [{Nonterminal, List} | Go], StateInfo) ->
     F = function_name(St0, yeccgoto, Nonterminal),
-    St05 = fwrite(St0, <<"-dialyzer({nowarn_function, ~w/7}).\n">>, [F]),
+    St05 = output_nowarn(St0, F, '', 7),
     St10 = output_goto1(St05, List, F, StateInfo, true),
     St = output_goto_fini(F, Nonterminal, St10),
     output_goto(St, Go, StateInfo);
@@ -2181,8 +2181,7 @@ output_actions(St0, StateJumps, StateInfo) ->
     SelS = [{State,Called} || 
                {{State,_JActions}, {State,Called}} <- 
                    lists:zip(StateJumps, lists:keysort(1, Sel))],
-    St05 =
-        fwrite(St0, <<"-dialyzer({nowarn_function, yeccpars2/7}).\n">>, []),
+    St05 = output_nowarn(St0, yeccpars2, '', 7),
     St10 = foldl(fun({State, Called}, St_0) ->
                          {State, #state_info{state_repr = IState}} = 
                              lookup_state(StateInfo, State),
@@ -2227,13 +2226,8 @@ output_state_actions(St0, State, State, {Actions, Jump}, SI) ->
 output_state_actions(St, State, JState, _XActions, _SI) ->
     fwrite(St, <<"%% yeccpars2_~w: see yeccpars2_~w\n\n">>, [State, JState]).
 
-output_state_actions_begin(St, State, Actions) ->
-    case [yes || {_, #reduce{}} <- Actions] of
-        [] ->
-            fwrite(St, <<"-dialyzer({nowarn_function, yeccpars2_~w/7}).\n">>,
-                   [State]); % Only when yeccerror(T) is output.
-        _ -> St
-    end.
+output_state_actions_begin(St, State, _Actions) ->
+    output_nowarn(St, yeccpars2_, State, 7).
 
 output_state_actions1(St, State, [], IsFirst, normal, _SI) ->
     output_state_actions_fini(State, IsFirst, St);
@@ -2383,7 +2377,8 @@ output_inlined(St0, FunctionName, Reduce, Infile) ->
 
     CodeStartLine = lists:max([0, Line0 - 4]),
     St10 = fwrite(St5, <<"-compile({inline,~w/1}).\n">>, [FunctionName]),
-    St20 = output_file_directive(St10, Infile, CodeStartLine),
+    St15 = output_nowarn(St10, FunctionName, '', 1),
+    St20 = output_file_directive(St15, Infile, CodeStartLine),
     St30 = fwrite(St20, <<"~w(__Stack0) ->\n">>, [FunctionName]),
     %% Currently the (old) inliner emits less code if matching the
     %% stack inside the body rather than in the head...
@@ -2402,6 +2397,13 @@ output_inlined(St0, FunctionName, Reduce, Infile) ->
     fwrite(St, <<" [begin\n  ~ts\n  end | ~s].\n\n">>,
            [pp_tokens(Tokens, Line0, St#yecc.encoding), Stack]).
 
+output_nowarn(St, Function, Suffix, Arity) ->
+    S = case Suffix of '' -> ""; _ -> integer_to_list(Suffix) end,
+    St1 = fwrite(St, <<"-dialyzer({nowarn_function, ~w~s/~w}).\n">>,
+                 [Function, S, Arity]),
+    fwrite(St1, <<"-compile({nowarn_unused_function,  ~w~s/~w}).\n">>,
+                 [Function, S, Arity]).
+
 inlined_function_name(St, State, Terminal) ->
     End = case Terminal of
               "Cat" -> [];
diff --git a/lib/parsetools/test/yecc_SUITE.erl b/lib/parsetools/test/yecc_SUITE.erl
index e4747d8513..3804b632c7 100644
--- a/lib/parsetools/test/yecc_SUITE.erl
+++ b/lib/parsetools/test/yecc_SUITE.erl
@@ -49,7 +49,7 @@
 	 otp_5369/1, otp_6362/1, otp_7945/1, otp_8483/1, otp_8486/1,
 	 
 	 otp_7292/1, otp_7969/1, otp_8919/1, otp_10302/1, otp_11269/1,
-         otp_11286/1, otp_14285/1]).
+         otp_11286/1, otp_14285/1, otp_17535/1]).
 
 % Default timetrap timeout (set in init_per_testcase).
 -define(default_timeout, ?t:minutes(1)).
@@ -75,7 +75,7 @@ groups() ->
      {examples, [],
       [empty, prec, yeccpre, lalr, old_yecc, other_examples]},
      {bugs, [],
-      [otp_5369, otp_6362, otp_7945, otp_8483, otp_8486]},
+      [otp_5369, otp_6362, otp_7945, otp_8483, otp_8486, otp_17535]},
      {improvements, [], [otp_7292, otp_7969, otp_8919, otp_10302,
                          otp_11269, otp_11286, otp_14285]}].
 
@@ -338,10 +338,12 @@ syntax(Config) when is_list(Config) ->
     fun() ->
             {error,[{_,[{5,_,["syntax error before: ","bad"]}]},
                           {_,[{L1,_,{undefined_function,{yeccpars2_2_,1}}},
-                              {L2,_,{bad_inline,{yeccpars2_2_,1}}}]}],
+                              {L2,_,{bad_inline,{yeccpars2_2_,1}}},
+                              {_,_,{undefined_function,{yeccpars2_2_,1}}},
+                              {_,_,{bad_nowarn_unused_function,{yeccpars2_2_,1}}}]}],
                    []} = compile:file(Parserfile1, [basic_validation,return]),
-            L1 = 31 + SzYeccPre,
-            L2 = 39 + SzYeccPre
+            L1 = 36 + SzYeccPre,
+            L2 = 45 + SzYeccPre
     end(),
 
     %% Bad macro in action. OTP-7224.
@@ -356,10 +358,12 @@ syntax(Config) when is_list(Config) ->
     fun() ->
             {error,[{_,[{5,_,{undefined,'F',1}}]},
                           {_,[{L1,_,{undefined_function,{yeccpars2_2_,1}}},
-                              {L2,_,{bad_inline,{yeccpars2_2_,1}}}]}],
+                              {L2,_,{bad_inline,{yeccpars2_2_,1}}},
+                        {_,_,{undefined_function,{yeccpars2_2_,1}}},
+                        {_,_,{bad_nowarn_unused_function,{yeccpars2_2_,1}}}]}],
                    []} = compile:file(Parserfile1, [basic_validation,return]),
-            L1 = 31 + SzYeccPre,
-            L2 = 39 + SzYeccPre
+            L1 = 36 + SzYeccPre,
+            L2 = 45 + SzYeccPre
     end(),
 
     %% Check line numbers. OTP-7224.
@@ -1618,11 +1622,13 @@ otp_7292(Config) when is_list(Config) ->
             {error,
                    [{_,[{5,_,["syntax error before: ","bad"]}]},
                     {_,[{L1,_,{undefined_function,{yeccpars2_2_,1}}},
-                        {L2,_,{bad_inline,{yeccpars2_2_,1}}}]}],
+                        {L2,_,{bad_inline,{yeccpars2_2_,1}}},
+                        {_,_,{undefined_function,{yeccpars2_2_,1}}},
+                        {_,_,{bad_nowarn_unused_function,{yeccpars2_2_,1}}}]}],
                    [{_,[{16,_,{unused_function,{foo,0}}}]}]} = 
                 compile:file(Parserfile1, [basic_validation, return]),
-            L1 = 41 + SzYeccPre,
-            L2 = 49 + SzYeccPre
+            L1 = 46 + SzYeccPre,
+            L2 = 55 + SzYeccPre
     end(),
 
     YeccPre = filename:join(Dir, "yeccpre.hrl"),
@@ -1636,11 +1642,13 @@ otp_7292(Config) when is_list(Config) ->
             {error,
                    [{_,[{5,_,["syntax error before: ","bad"]}]},
                     {_,[{L1,_,{undefined_function,{yeccpars2_2_,1}}},
-                        {L2,_,{bad_inline,{yeccpars2_2_,1}}}]}],
+                        {L2,_,{bad_inline,{yeccpars2_2_,1}}},
+                        {_,_,{undefined_function,{yeccpars2_2_,1}}},
+                        {_,_,{bad_nowarn_unused_function,{yeccpars2_2_,1}}}]}],
                    [{_,[{16,_,{unused_function,{foo,0}}}]}]} = 
                 compile:file(Parserfile1, [basic_validation, return]),
-            L1 = 40 + SzYeccPre,
-            L2 = 48 + SzYeccPre
+            L1 = 45 + SzYeccPre,
+            L2 = 54 + SzYeccPre
     end(),
 
     file:delete(YeccPre),
@@ -2130,6 +2138,24 @@ otp_17023(Config) ->
 
     ok.
 
+otp_17535(doc) ->
+    "GH-5067. Compiler finds unused functions.";
+otp_17535(suite) -> [];
+otp_17535(Config) when is_list(Config) ->
+    Dir = ?privdir,
+    Filename = filename:join(Dir, "OTP-17535.yrl"),
+    Ret = [return, {report, true}],
+    J = <<"Nonterminals start statem.
+          Terminals  'if'.
+          Rootsymbol start.
+          start -> statem : b.
+          statem -> 'if' statem : a.
+          Erlang code.">>,
+    ok = file:write_file(Filename, J),
+    {ok, ErlFile, []} = yecc:file(Filename, Ret),
+    {ok, _, []} = compile:file(ErlFile, [return]),
+    ok.
+
 start_node(Name, Args) ->
     [_,Host] = string:tokens(atom_to_list(node()), "@"),
     ct:log("Trying to start ~w@~s~n", [Name,Host]),
-- 
2.26.2

openSUSE Build Service is sponsored by