File 5414-compiler-Make-yecc-respect-deterministic.patch of Package erlang

From 883d86c779172d42a36b013125f671796a3767f6 Mon Sep 17 00:00:00 2001
From: Tom Davies <todavies5@gmail.com>
Date: Thu, 28 Apr 2022 06:14:37 -0700
Subject: [PATCH 4/7] compiler: Make yecc respect +deterministic

Makes generated yecc parsers use only basenames in generated -file
attributes rather than absolute paths when +deterministic is set.
---
 lib/parsetools/doc/src/yecc.xml    |  5 +++
 lib/parsetools/src/yecc.erl        | 17 +++++++---
 lib/parsetools/test/yecc_SUITE.erl | 50 ++++++++++++++++++++++++++++--
 3 files changed, 66 insertions(+), 6 deletions(-)

diff --git a/lib/parsetools/doc/src/yecc.xml b/lib/parsetools/doc/src/yecc.xml
index 218cec5330..4d639d1f21 100644
--- a/lib/parsetools/doc/src/yecc.xml
+++ b/lib/parsetools/doc/src/yecc.xml
@@ -134,6 +134,11 @@
             is <c>column</c>, the location includes a line number and
             a column number. Default is <c>column</c>.
           </item>
+          <tag><c>{deterministic, boolean()}</c></tag>
+          <item>
+            <p>Causes generated -file() attributes to only include the
+              basename of the file path.</p>
+          </item>
         </taglist>
         <p>Any of the Boolean options can be set to <c>true</c> by 
           stating the name of the option. For example, <c>verbose</c>
diff --git a/lib/parsetools/src/yecc.erl b/lib/parsetools/src/yecc.erl
index 5b2a9efe4d..7833c6a120 100644
--- a/lib/parsetools/src/yecc.erl
+++ b/lib/parsetools/src/yecc.erl
@@ -141,9 +141,10 @@ compile(Input0, Output0,
     Output = shorten_filename(Output0),
     Includefile = lists:sublist(Includes, 1),
     Werror = proplists:get_bool(warnings_as_errors, Specific),
+    Deterministic = proplists:get_bool(deterministic, Specific),
     Opts = [{parserfile,Output}, {includefile,Includefile}, {verbose,Verbose},
             {report_errors, true}, {report_warnings, WarnLevel > 0},
-	    {warnings_as_errors, Werror}],
+	    {warnings_as_errors, Werror}, {deterministic, Deterministic}],
     case file(Input, Opts) of
         {ok, _OutFile} ->
             ok;
@@ -265,6 +266,7 @@ file(GrammarFile) ->
               | {'parserfile', Parserfile :: file:filename()}
               | {'verbose', boolean()}
               | {'warnings_as_errors', boolean()}
+              | {'deterministic', boolean()}
               | 'report_errors' | 'report_warnings' | 'report'
               | 'return_errors' | 'return_warnings' | 'return'
               | 'verbose' | 'warnings_as_errors'.
@@ -407,7 +409,7 @@ check_options(_Options, _, _L) ->
 all_options() ->
     [error_location, file_attributes, includefile, parserfile,
      report_errors, report_warnings, return_errors, return_warnings,
-     time, verbose, warnings_as_errors].
+     time, verbose, warnings_as_errors, deterministic].
 
 default_option(error_location) -> column;
 default_option(file_attributes) -> true;
@@ -419,7 +421,8 @@ default_option(return_errors) -> false;
 default_option(return_warnings) -> false;
 default_option(time) -> false;
 default_option(verbose) -> false;
-default_option(warnings_as_errors) -> false.
+default_option(warnings_as_errors) -> false;
+default_option(deterministic) -> false.
 
 atom_option(file_attributes) -> {file_attributes, true};
 atom_option(report_errors) -> {report_errors, true};
@@ -429,6 +432,7 @@ atom_option(return_warnings) -> {return_warnings, true};
 atom_option(time) -> {time, true};
 atom_option(verbose) -> {verbose, true};
 atom_option(warnings_as_errors) -> {warnings_as_errors, true};
+atom_option(deterministic) -> {deterministic, true};
 atom_option(Key) -> Key.
 
 is_filename(T) ->
@@ -2695,7 +2699,12 @@ nl(#yecc{outport = Outport, line = Line}=St) ->
     St#yecc{line = Line + 1}.
 
 format_filename(Filename0, St) ->
-    Filename = filename:flatten(Filename0),
+    Deterministic = proplists:get_bool(deterministic, St#yecc.options),
+    Filename =
+      case Deterministic of
+        true -> filename:basename(filename:flatten(Filename0));
+        false -> filename:flatten(Filename0)
+      end,
     case lists:keyfind(encoding, 1, io:getopts(St#yecc.outport)) of
         {encoding, unicode} -> io_lib:write_string(Filename);
         _ ->                   io_lib:write_string_as_latin1(Filename)
diff --git a/lib/parsetools/test/yecc_SUITE.erl b/lib/parsetools/test/yecc_SUITE.erl
index c0f03edd9e..16a6b47ade 100644
--- a/lib/parsetools/test/yecc_SUITE.erl
+++ b/lib/parsetools/test/yecc_SUITE.erl
@@ -22,6 +22,7 @@
 %-define(debug, true).
 
 -include_lib("stdlib/include/erl_compile.hrl").
+-include_lib("stdlib/include/assert.hrl").
 
 -ifdef(debug).
 -define(config(X,Y), foo).
@@ -40,7 +41,7 @@
 -export([app_test/1,
 	 
 	 file/1, syntax/1, compile/1, rules/1, expect/1,
-	 conflicts/1,
+	 conflicts/1, deterministic/1,
 	 
 	 empty/1, prec/1, yeccpre/1, lalr/1, old_yecc/1, 
 	 other_examples/1,
@@ -70,7 +71,7 @@ all() ->
 
 groups() -> 
     [{checks, [],
-      [file, syntax, compile, rules, expect, conflicts]},
+      [file, syntax, compile, rules, expect, conflicts, deterministic]},
      {examples, [],
       [empty, prec, yeccpre, lalr, old_yecc, other_examples]},
      {bugs, [],
@@ -926,6 +927,41 @@ conflicts(Config) when is_list(Config) ->
     file:delete(Filename),
     ok.
 
+deterministic(doc) ->
+    "Check yecc respects the +deterministic flag.";
+deterministic(suite) -> [];
+deterministic(Config) when is_list(Config) ->
+    Dir = ?privdir,
+    Filename = filename:join(Dir, "file.yrl"),
+    Parserfile = filename:join(Dir, "file.erl"),
+    ok = file:write_file(Filename,
+                               <<"Nonterminals nt.
+                                  Terminals t.
+                                  Rootsymbol nt.
+                                  nt -> t.">>),
+
+    %% Generated yecc parsers need to include the yeccpre.hrl
+    %% header file, so we'll get a -file attribute corresponding
+    %% to that include. In deterministic mode, that include should
+    %% only use the basename, "yeccpre.hrl", but otherwise, it should
+    %% contain the full path.
+
+    AbsolutePathSuffix = "/lib/parsetools/include/yeccpre.hrl",
+
+    ok = yecc:compile(Filename, Parserfile, #options{specific=[deterministic]}),
+    {ok, FormsDet} = epp:parse_file(Parserfile,[]),
+    ?assertMatch(false, search_for_file_attr(AbsolutePathSuffix, FormsDet)),
+    ?assertMatch({value, _}, search_for_file_attr("yeccpre.hrl", FormsDet)),
+    file:delete(Parserfile),
+
+    ok = yecc:compile(Filename, Parserfile, #options{}),
+    {ok, Forms} = epp:parse_file(Parserfile,[]),
+    ?assertMatch({value, _}, search_for_file_attr(AbsolutePathSuffix, Forms)),
+    file:delete(Parserfile),
+
+    file:delete(Filename),
+    ok.
+
 empty(doc) ->
     "'$empty'.";
 empty(suite) -> [];
@@ -2284,3 +2320,13 @@ process_list() ->
 
 safe_second_element({_,Info}) -> Info;
 safe_second_element(Other) -> Other.
+
+search_for_file_attr(PartialFilePath, Forms) ->
+    lists:search(fun
+                   ({attribute, _, file, {FileAttr, _}}) ->
+                      case string:find(FileAttr, PartialFilePath) of
+                        nomatch -> false;
+                        _ -> true
+                      end;
+                   (_) -> false end,
+                 Forms).
-- 
2.35.3

openSUSE Build Service is sponsored by