File 2712-compiler-Run-erl_pp-legalize_vars-1-when-dumping-cod.patch of Package erlang

From bc315e52b7238b9fa175614a215805686cfff214 Mon Sep 17 00:00:00 2001
From: Frej Drejhammar <frej.drejhammar@gmail.com>
Date: Tue, 9 Nov 2021 15:43:59 +0100
Subject: [PATCH 2/2] compiler: Run erl_pp:legalize_vars/1 when dumping code
 using `-E`

When running the compiler using `-E` to produce a listing of the code,
after all source code transformations had been performed, could
produce a module, which when parsed again, was not semantically
equivalent to the input. This patch adds a new pass which is enabled
when `-E` is used and runs erl_pp:legalize_vars/1 on all functions
before producing a listing. erl_pp:legalize_vars/1 will ensure that
the ouput will be semantically equivalent to the input.
---
 lib/compiler/src/compile.erl                  |  9 +++++
 lib/compiler/test/compile_SUITE.erl           | 36 +++++++++++++++++--
 lib/compiler/test/compile_SUITE_data/bigE.erl | 22 ++++++++++++
 3 files changed, 65 insertions(+), 2 deletions(-)
 create mode 100644 lib/compiler/test/compile_SUITE_data/bigE.erl

diff --git a/lib/compiler/src/compile.erl b/lib/compiler/src/compile.erl
index f5f61cbd96..ef46c990a7 100644
--- a/lib/compiler/src/compile.erl
+++ b/lib/compiler/src/compile.erl
@@ -806,6 +806,7 @@ abstr_passes(AbstrStatus) ->
 
          ?pass(expand_records),
          {iff,'dexp',{listing,"expand"}},
+         {iff,'E',?pass(legalize_vars)},
          {iff,'E',{src_listing,"E"}},
          {iff,'to_exp',{done,"E"}},
 
@@ -1422,6 +1423,14 @@ expand_records(Code0, #compile{options=Opts}=St) ->
     Code = erl_expand_records:module(Code0, Opts),
     {ok,Code,St}.
 
+legalize_vars(Code0, St) ->
+    Code = map(fun(F={function,_,_,_,_}) ->
+                       erl_pp:legalize_vars(F);
+                  (F) ->
+                       F
+               end, Code0),
+    {ok,Code,St}.
+
 compile_directives(Forms, #compile{options=Opts0}=St) ->
     Opts = expand_opts(flatten([C || {attribute,_,compile,C} <- Forms])),
     {ok, Forms, St#compile{options=Opts ++ Opts0}}.
diff --git a/lib/compiler/test/compile_SUITE.erl b/lib/compiler/test/compile_SUITE.erl
index efee6b9674..abc570984d 100644
--- a/lib/compiler/test/compile_SUITE.erl
+++ b/lib/compiler/test/compile_SUITE.erl
@@ -26,7 +26,7 @@
 
 -export([all/0, suite/0,groups/0,init_per_suite/1, end_per_suite/1, 
 	 init_per_group/2,end_per_group/2,
-	 app_test/1,appup_test/1,
+	 app_test/1,appup_test/1,bigE_roundtrip/1,
 	 debug_info/4, custom_debug_info/1, custom_compile_info/1,
 	 file_1/1, forms_2/1, module_mismatch/1, outdir/1,
 	 binary/1, makedep/1, cond_and_ifdef/1, listings/1, listings_big/1,
@@ -48,7 +48,8 @@ suite() -> [{ct_hooks,[ts_install_cth]}].
 -spec all() -> all_return_type().
 
 all() -> 
-    [app_test, appup_test, file_1, forms_2, module_mismatch, outdir,
+    [app_test, appup_test, bigE_roundtrip, file_1,
+     forms_2, module_mismatch, outdir,
      binary, makedep, cond_and_ifdef, listings, listings_big,
      other_output, kernel_listing, encrypted_abstr, tuple_calls,
      strict_record, utf8_atoms, utf8_functions, extra_chunks,
@@ -85,6 +86,37 @@ app_test(Config) when is_list(Config) ->
 appup_test(Config) when is_list(Config) ->
     ok = test_server:appup_test(compiler).
 
+%% Check that a file compiled to the abstract form and dumped with -E
+%% can be compiled. We use a file constructed to produce errors if the
+%% dumping fails to legalize compiler generated variable names.
+bigE_roundtrip(Config) when is_list(Config) ->
+    DataDir = proplists:get_value(data_dir, Config),
+    PrivDir = proplists:get_value(priv_dir, Config),
+    Source = filename:join(DataDir, "bigE.erl"),
+    TargetDir = filename:join(PrivDir, "bigE"),
+    Target = filename:join(TargetDir, "bigE.E"),
+    TargetSource = filename:join(TargetDir, "bigE.erl"),
+    ok = file:make_dir(TargetDir),
+    io:format("Source: ~p~nTargetDir: ~p~nTarget: ~p\n",
+              [Source, TargetDir, Target]),
+    case compile:file(Source,
+                      ['E', warnings_as_errors, {outdir, TargetDir}]) of
+        {ok, _} -> ok;
+        Other -> ct:fail({unexpected_result, Other})
+    end,
+    %% Rename the output to .erl so that the compiler accepts it and
+    %% we won't get a warning due to the filename not matching the
+    %% module name.
+    ok = file:rename(Target, TargetSource),
+    case compile:file(TargetSource,
+                      [warnings_as_errors, {outdir, TargetDir}]) of
+        {ok, _} -> ok;
+        Other1 -> ct:fail({unexpected_result, Other1})
+    end,
+    file:delete(TargetSource),
+    file:del_dir(TargetDir),
+    ok.
+
 %% Tests that we can compile and run a simple Erlang program,
 %% using compile:file/1.
 
diff --git a/lib/compiler/test/compile_SUITE_data/bigE.erl b/lib/compiler/test/compile_SUITE_data/bigE.erl
new file mode 100644
index 0000000000..598b8fc965
--- /dev/null
+++ b/lib/compiler/test/compile_SUITE_data/bigE.erl
@@ -0,0 +1,22 @@
+-module(bigE).
+
+-export([f/1]).
+
+-record(r, {a, b}).
+
+f(#r{b = B} = C) ->
+    receive
+	B ->
+	    X = C#r.a,
+            %% The compiler will do a case to extract the `a` field
+            %% using a pattern variable named `rec0`. Without
+            %% legalization the variable will be output as an atom and
+            %% the compiler will report an error as the following `X +
+            %% X` will always fail.
+	    REC0 = X + X,
+            %% If the legalization fails to detect that the default
+            %% legalization of uppercasing the pattern variable would
+            %% collide with the `REC0` below, we will get a warning
+            %% for an unsafe use.
+	    REC0
+    end.
-- 
2.31.1

openSUSE Build Service is sponsored by