File 5412-compiler-Make-asn1ct_gen-respect-deterministic.patch of Package erlang

From ebda708801eec74a8313fef050296b9785c1b8ee Mon Sep 17 00:00:00 2001
From: Tom Davies <todavies5@gmail.com>
Date: Thu, 28 Apr 2022 05:52:59 -0700
Subject: [PATCH 2/7] compiler: Make asn1ct_gen respect +deterministic

Makes asn1ct_gen filter out potentially non-deterministic attributes
from generated .erl files when +deterministic is set.
---
 lib/asn1/doc/src/asn1ct.xml            |  7 +++-
 lib/asn1/src/asn1ct_gen.erl            | 18 +++++++++-
 lib/asn1/test/asn1_SUITE.erl           |  3 +-
 lib/asn1/test/test_compile_options.erl | 48 +++++++++++++++++++++++++-
 4 files changed, 72 insertions(+), 4 deletions(-)

diff --git a/lib/asn1/doc/src/asn1ct.xml b/lib/asn1/doc/src/asn1ct.xml
index e4c5a2a3ee..a9a71db629 100644
--- a/lib/asn1/doc/src/asn1ct.xml
+++ b/lib/asn1/doc/src/asn1ct.xml
@@ -83,7 +83,7 @@
 	legacy_bit_string | legacy_erlang_types |
 	noobj | {n2n, EnumTypeName} |{outdir, Dir} | {i, IncludeDir} |
 	asn1config | undec_rest | no_ok_wrapper |
-	{macro_name_prefix, Prefix} | {record_name_prefix, Prefix} | verbose | warnings_as_errors</v>
+	{macro_name_prefix, Prefix} | {record_name_prefix, Prefix} | verbose | warnings_as_errors | deterministic</v>
         <v>OldOption = ber | per</v> 
         <v>Reason = term()</v>
         <v>Prefix = string()</v>
@@ -346,6 +346,11 @@ File3.asn</pre>
           <item>
             <p>Causes warnings to be treated as errors.</p>
           </item>
+          <tag><c>deterministic</c></tag>
+          <item>
+            <p>Causes all non-deterministic options to be stripped from the
+              -asn1_info() attribute.</p>
+          </item>
         </taglist>
         <p>Any more option that is applied is passed to
           the final step when the generated <c>.erl</c> file is compiled.
diff --git a/lib/asn1/src/asn1ct_gen.erl b/lib/asn1/src/asn1ct_gen.erl
index 7f83ae63fd..9950438d4f 100644
--- a/lib/asn1/src/asn1ct_gen.erl
+++ b/lib/asn1/src/asn1ct_gen.erl
@@ -1327,9 +1327,25 @@ gen_head(#gen{options=Options}=Gen, Mod, Hrl) ->
 	0 -> ok;
 	_ -> emit(["-include(\"",Mod,".hrl\").",nl])
     end,
+    Deterministic = proplists:get_bool(deterministic, Options),
+    Options1 =
+        case Deterministic of
+            true ->
+                % compile:keep_compile_option will filter some of these
+                % out of generated .beam files, but this will keep
+                % them out of the generated .erl files
+                lists:filter(
+                    fun({cwd, _}) -> false;
+                       ({outdir, _}) -> false;
+                       ({i, _}) -> false;
+                       (_) -> true end,
+                    Options);
+            false ->
+                Options
+         end,
     emit(["-asn1_info([{vsn,'",asn1ct:vsn(),"'},",nl,
 	  "            {module,'",Mod,"'},",nl,
-	  "            {options,",io_lib:format("~p",[Options]),"}]).",nl,nl]),
+	  "            {options,",io_lib:format("~p",[Options1]),"}]).",nl,nl]),
     JerDefines = case Gen of
                      #gen{erule=jer} ->
                          true;
diff --git a/lib/asn1/test/asn1_SUITE.erl b/lib/asn1/test/asn1_SUITE.erl
index eeb5253c32..2a02f08a95 100644
--- a/lib/asn1/test/asn1_SUITE.erl
+++ b/lib/asn1/test/asn1_SUITE.erl
@@ -1062,7 +1062,8 @@ test_compile_options(Config) ->
     ok = test_compile_options:noobj(Config),
     ok = test_compile_options:record_name_prefix(Config),
     ok = test_compile_options:verbose(Config),
-    ok = test_compile_options:maps(Config).
+    ok = test_compile_options:maps(Config),
+    ok = test_compile_options:determinism(Config).
 
 testDoubleEllipses(Config) -> test(Config, fun testDoubleEllipses/3).
 testDoubleEllipses(Config, Rule, Opts) ->
diff --git a/lib/asn1/test/test_compile_options.erl b/lib/asn1/test/test_compile_options.erl
index f9997d37d0..45e8f39d39 100644
--- a/lib/asn1/test/test_compile_options.erl
+++ b/lib/asn1/test/test_compile_options.erl
@@ -22,10 +22,11 @@
 -module(test_compile_options).
 
 -include_lib("common_test/include/ct.hrl").
+-include_lib("stdlib/include/assert.hrl").
 
 
 -export([wrong_path/1,comp/2,path/1,noobj/1,
-	 record_name_prefix/1,verbose/1,maps/1]).
+	 record_name_prefix/1,verbose/1,maps/1,determinism/1]).
 
 %% OTP-5689
 wrong_path(Config) ->
@@ -150,6 +151,51 @@ do_maps(Erule, InFile, OutDir) ->
 
     ok.
 
+determinism(Config) when is_list(Config) ->
+    DataDir = proplists:get_value(data_dir,Config),
+    OutDir = proplists:get_value(priv_dir,Config),
+    Asn1File = filename:join([DataDir,"Comment.asn"]),
+    ErlFile = filename:join([OutDir,"Comment.erl"]),
+
+    ContainsNonDeterministicOptions =
+       fun
+           ({attribute,_Anno,asn1_info,Elems}) ->
+               lists:any(
+                   fun
+                       ({options, Opts}) ->
+                           lists:any(fun ({i, _}) -> true; (_) -> false end, Opts)
+                           andalso
+                           lists:any(fun ({outdir, _}) -> true; (_) -> false end, Opts)
+                           andalso
+                           lists:any(fun ({cwd, _}) -> true; (_) -> false end, Opts);
+                       (_) ->
+                           false
+                   end,
+                   Elems);
+           (_) ->
+               false
+       end,
+
+    BaseOptions = [{i,DataDir},{outdir,OutDir},{cwd,DataDir},noobj],
+
+    %% Test deterministic compile
+    ok = asn1ct:compile(Asn1File, BaseOptions ++ [deterministic]),
+    {ok, List1} = epp:parse_file(ErlFile, [{includes, [DataDir]},
+                                       {source_name, "Comment.erl"}]),
+    ?assertNot(lists:any(ContainsNonDeterministicOptions, List1),
+            "Expected no debugging option values (i, outdir, cwd) in asn1_info attribute " ++
+            "in deterministic mode"),
+
+    %% Test non-deterministic compile
+    ok = asn1ct:compile(Asn1File, BaseOptions),
+    {ok, List2} = epp:parse_file(ErlFile, [{includes, [DataDir]},
+                                       {source_name, "Comment.erl"}]),
+    ?assert(lists:any(ContainsNonDeterministicOptions, List2),
+            "Expected debugging option values (i, outdir, cwd) in asn1_info attribute " ++
+            "in non-deterministic mode"),
+    ok.
+
+
 outfiles_check(OutDir) ->
     outfiles_check(OutDir,outfiles1()).
 
-- 
2.35.3

openSUSE Build Service is sponsored by