File 2661-Make-options-in-the-compile-attribute-take-precedenc.patch of Package erlang

From 5bc7545b6acca11b9eca63e004b10b00cb7ac3d4 Mon Sep 17 00:00:00 2001
From: =?UTF-8?q?Bj=C3=B6rn=20Gustavsson?= <bjorn@erlang.org>
Date: Mon, 12 Feb 2024 08:53:52 +0100
Subject: [PATCH] Make options in the `-compile` attribute take precedence

Change the compiler option processing order so that options given
in the `compile()` attribute take precedence over options given
to the compiler, which in turn take precedence over options given
in the environment.

This order makes most sense, as each module might need customized
options.

While at it, remove the undocumented `strict_record_updates` /
`no_strict_record_updates` options. Their naming no longer make any
sense, because record updates are always strict (that is, the source
record must have the correct tag and size). Incorporate the
behavior of `strict_record_updates` to update the record by matching
and building a new tuple into the `dialyzer` option. When dialyzer
is not used, records are updated using `setelement/3`, which is more
efficient in the JIT.

(This is the second attempt to fix #6979, as #8093 did not really
work.)
---
 erts/test/erlc_SUITE.erl                      |  14 -
 .../src/ignorant_directive.erl                |   2 +-
 lib/compiler/src/compile.erl                  |  25 +-
 lib/compiler/test/compile_SUITE.erl           | 252 +++++++++++++++++-
 lib/dialyzer/src/dialyzer_utils.erl           |   2 +-
 lib/stdlib/src/erl_expand_records.erl         |  57 ++--
 lib/stdlib/src/erl_lint.erl                   |   2 +-
 lib/stdlib/test/erl_lint_SUITE.erl            |  13 +-
 8 files changed, 310 insertions(+), 57 deletions(-)

diff --git a/erts/test/erlc_SUITE.erl b/erts/test/erlc_SUITE.erl
index a5ff8355fa..09d3a826ff 100644
--- a/erts/test/erlc_SUITE.erl
+++ b/erts/test/erlc_SUITE.erl
@@ -717,20 +717,6 @@ features_atom_warnings(Config) when is_list(Config) ->
                     atom_warning(while, experimental_ftr_2),
                     skip_lines])),
 
-    %% Check for keyword warnings.  Not all warnings are checked.
-    %% This file has a -compile attribute for keyword warnings.
-    Compile("ignorant_directive.erl", "",
-            ?OK([atom_warning(ifn, experimental_ftr_1),
-                 skip_lines,
-                 atom_warning(while, experimental_ftr_2),
-                 skip_lines,
-                 atom_warning(until, experimental_ftr_2),
-                 skip_lines])),
-
-    %% Override warning attribute inside file
-    Compile("ignorant_directive.erl", "+nowarn_keywords",
-            ?OK([])),
-
     %% File has quoted atoms which are keywords in experimental_ftr_2.
     %% We should see no warnings.
     Compile("foo.erl", options([longopt(enable, experimental_ftr_2),
diff --git a/erts/test/erlc_SUITE_data/src/ignorant_directive.erl b/erts/test/erlc_SUITE_data/src/ignorant_directive.erl
index 5ad8c23e3c..6255fe0510 100644
--- a/erts/test/erlc_SUITE_data/src/ignorant_directive.erl
+++ b/erts/test/erlc_SUITE_data/src/ignorant_directive.erl
@@ -23,7 +23,7 @@
 
 -module(ignorant_directive).
 
--compile(warn_keywords).
+
 
 -export([foo/0,
          frob/1,
diff --git a/lib/compiler/src/compile.erl b/lib/compiler/src/compile.erl
index cfb9960fb9..a561d46d95 100644
--- a/lib/compiler/src/compile.erl
+++ b/lib/compiler/src/compile.erl
@@ -796,7 +819,7 @@ file(File) -> file(File, ?DEFAULT_OPTIONS).
           CompRet :: comp_ret().
 
 file(File, Opts) when is_list(Opts) ->
-    do_compile({file,File}, Opts++env_default_opts());
+    do_compile({file,File}, env_default_opts() ++ Opts);
 file(File, Opt) ->
     file(File, [Opt|?DEFAULT_OPTIONS]).
 
diff --git a/lib/compiler/test/compile_SUITE.erl b/lib/compiler/test/compile_SUITE.erl
index d212298def..c5b6fa585a 100644
--- a/lib/compiler/test/compile_SUITE.erl
+++ b/lib/compiler/test/compile_SUITE.erl
@@ -39,7 +39,7 @@
          deterministic_docs/1,
          compile_attribute/1, message_printing/1, other_options/1,
          transforms/1, erl_compile_api/1, types_pp/1, bs_init_writable/1,
-         annotations_pp/1
+         annotations_pp/1, option_order/1
 	]).
 
 suite() -> [{ct_hooks,[ts_install_cth]}].
@@ -59,7 +59,8 @@ all() ->
      custom_compile_info, deterministic_include, deterministic_paths,
      deterministic_docs,
      compile_attribute, message_printing, other_options, transforms,
-     erl_compile_api, types_pp, bs_init_writable, annotations_pp].
+     erl_compile_api, types_pp, bs_init_writable, annotations_pp,
+     option_order].
 
 groups() -> 
     [].
@@ -906,10 +907,10 @@ strict_record(Config) when is_list(Config) ->
     {ok,M} = c:c(M, [no_strict_record_tests|Opts]),
     Turtle = test_sloppy(),
 
-    %% The option first given wins.
-    {ok,M} = c:c(M, [no_strict_record_tests,strict_record_tests|Opts]),
-    Turtle = test_sloppy(),
+    %% The option last given wins.
     {ok,M} = c:c(M, [strict_record_tests,no_strict_record_tests|Opts]),
+    Turtle = test_sloppy(),
+    {ok,M} = c:c(M, [no_strict_record_tests,strict_record_tests|Opts]),
     Turtle = test_strict(),
 
     %% Default (possibly influenced by ERL_COMPILER_OPTIONS).
@@ -2120,6 +2121,134 @@ get_annotations(Key, [_|Lines]) ->
 get_annotations(_, []) ->
     [].
 
+option_order(Config) ->
+    Ts = [{spec1,
+           "-compile(nowarn_missing_spec).
+foo() -> ok.
+",
+           [],                                  %Environment
+           [warn_missing_spec],
+           []},
+          {spec2,
+           "foo() -> ok.
+",
+           [{"ERL_COMPILER_OPTIONS", "warn_missing_spec"}],
+           [nowarn_missing_spec],
+           []},
+          {spec3,
+           "-compile(nowarn_missing_spec).
+foo() -> ok.
+",
+           [{"ERL_COMPILER_OPTIONS", "nowarn_missing_spec"}],
+           [warn_missing_spec],
+           []},
+          {spec4,
+           "-compile(warn_missing_spec).
+foo() -> ok.
+",
+           [{"ERL_COMPILER_OPTIONS", "nowarn_missing_spec"}],
+           [],
+           {warnings,[{{2,1},erl_lint,{missing_spec,{foo,0}}}]}
+          },
+          {spec5,
+           "-compile([warn_missing_spec,nowarn_missing_spec]).
+foo() -> ok.
+",
+           [{"ERL_COMPILER_OPTIONS", "nowarn_missing_spec"}],
+           [warn_missing_spec],
+           []},
+          {records1,
+           "-record(r, {x,y}).
+rec_test(#r{x=X,y=Y}) -> X + Y.
+",
+           [],
+           [strict_record_tests],
+           fun(M) ->
+                   try M:rec_test({r,1,2,3}) of
+                       3 ->
+                           fail()
+                   catch
+                       error:function_clause ->
+                           ok
+                   end
+           end},
+          {records2,
+           "-record(r, {x,y}).
+rec_test(R) -> R#r.x + R#r.y.
+",
+           [],
+           [no_strict_record_tests],
+           fun(M) ->
+                   3 = M:rec_test({r,1,2,3}),
+                   ok
+           end},
+          {records3,
+           "-compile(no_strict_record_tests).
+-record(r, {x,y}).
+rec_test(R) -> R#r.x + R#r.y.
+",
+           [],
+           [strict_record_tests],
+           fun(M) ->
+                   3 = M:rec_test({r,1,2,3}),
+                   ok
+           end},
+          {records4,
+           "-record(r, {x,y}).
+rec_test(#r{x=X,y=Y}) -> X + Y.
+",
+           [{"ERL_COMPILER_OPTIONS", "strict_record_tests"}],
+           [],
+           fun(M) ->
+                   try M:rec_test({r,1,2,3}) of
+                       3 ->
+                           fail()
+                   catch
+                       error:function_clause ->
+                           ok
+                   end
+           end},
+          {records5,
+           "-record(r, {x,y}).
+rec_test(R) -> R#r.x + R#r.y.
+",
+           [{"ERL_COMPILER_OPTIONS", "strict_record_tests"}],
+           [no_strict_record_tests],
+           fun(M) ->
+                   3 = M:rec_test({r,1,2,3}),
+                   ok
+           end},
+          {records6,
+           "-compile(no_strict_record_tests).
+-record(r, {x,y}).
+rec_test(R) -> R#r.x + R#r.y.
+",
+           [{"ERL_COMPILER_OPTIONS", "strict_record_tests"}],
+           [],
+           fun(M) ->
+                   3 = M:rec_test({r,1,2,3}),
+                   ok
+           end},
+          {records7,
+           "-record(r, {x,y}).
+rec_test(R) -> R#r.x + R#r.y.
+",
+           [{"ERL_COMPILER_OPTIONS", "no_strict_record_tests"}],
+           [no_strict_record_tests, strict_record_tests],
+           fun(M) ->
+                   try M:rec_test({r,1,2,3}) of
+                       3 ->
+                           fail()
+                   catch
+                       error:{badrecord,{r,1,2,3}} ->
+                           ok
+                   end
+           end}
+
+         ],
+    run(Config, Ts),
+    ok.
+
 %%%
 %%% Utilities.
 %%%
@@ -2149,3 +2290,104 @@ is_lfe_module(File, Ext) ->
 	"lfe_" ++ _ -> true;
 	_ -> false
     end.
+
+%% Compiles a test module and returns the list of errors and warnings.
+
+run(Config, Tests) ->
+    F = fun({N,P,Env,Ws,Run}, _BadL) when is_function(Run, 1) ->
+                case catch run_test(Config, P, Env, Ws, Run) of
+                    ok ->
+                        ok;
+                    Bad ->
+                        io:format("~nTest ~p failed. Expected~n  ~p~n"
+                                  "but got~n  ~p~n", [N, ok, Bad]),
+                        fail()
+                end;
+           ({N,P,Env,Ws,Expected}, BadL)
+              when is_list(Expected); is_tuple(Expected) ->
+                io:format("### ~s\n", [N]),
+                case catch run_test(Config, P, Env, Ws, none) of
+                    Expected ->
+                        BadL;
+                    Bad ->
+                        io:format("~nTest ~p failed. Expected~n  ~p~n"
+                                  "but got~n  ~p~n", [N, Expected, Bad]),
+			fail()
+                end
+        end,
+    lists:foldl(F, [], Tests).
+
+run_test(Conf, Test0, Env, Options, Run) ->
+    run_test_putenv(Env),
+    Module = "warnings" ++ test_lib:uniq(),
+    Filename = Module ++ ".erl",
+    DataDir = proplists:get_value(priv_dir, Conf),
+    Test1 = ["-module(", Module, "). -file( \"", Filename, "\", 1). ", Test0],
+    Test = iolist_to_binary(Test1),
+    File = filename:join(DataDir, Filename),
+    Opts = [binary,export_all,return|Options],
+    ok = file:write_file(File, Test),
+
+    %% Compile once just to print all warnings (and cover more code).
+    _ = compile:file(File, [binary,export_all,report|Options]),
+
+    %% Test result of compilation.
+    {ok, Mod, Beam, Warnings} = compile:file(File, Opts),
+    _ = file:delete(File),
+
+    if
+        is_function(Run, 1) ->
+            {module,Mod} = code:load_binary(Mod, "", Beam),
+            ok = Run(Mod),
+            run_test_unsetenv(Env),
+            true = code:delete(Mod),
+            _ = code:purge(Mod),
+            ok;
+        Run =:= none ->
+            run_test_unsetenv(Env),
+            Res = get_warnings(Warnings),
+            case Res of
+                [] ->
+                    [];
+                {warnings, Ws} ->
+                    print_warnings(Ws, Test),
+                    Res
+            end
+    end.
+
+run_test_putenv(Env) ->
+    _ = [_ = os:putenv(Name, Value) || {Name,Value} <- Env],
+    ok.
+
+run_test_unsetenv(Env) ->
+    _ = [_ = os:unsetenv(Name) || {Name,_Value} <- Env],
+    ok.
+
+get_warnings([]) ->
+    [];
+get_warnings(WsL) ->
+    case WsL of
+        [{_File,Ws}] -> {warnings, Ws};
+        _ -> {warnings, WsL}
+    end.
+
+print_warnings(Warnings, Source) ->
+    Lines = binary:split(Source, <<"\n">>, [global]),
+    Cs = [print_warning(W, Lines) || W <- Warnings],
+    io:put_chars(Cs),
+    ok.
+
+print_warning({{LineNum,Column},Mod,Data}, Lines) ->
+    Line0 = lists:nth(LineNum, Lines),
+    <<Line1:(Column-1)/binary,_/binary>> = Line0,
+    Spaces = re:replace(Line1, <<"[^\t]">>, <<" ">>, [global]),
+    CaretLine = [Spaces,"^"],
+    [io_lib:format("~p:~p: ~ts\n",
+                   [LineNum,Column,Mod:format_error(Data)]),
+     Line0, "\n",
+     CaretLine, "\n\n"];
+print_warning(_, _) ->
+    [].
+
+fail() ->
+    ct:fail(failed).
diff --git a/lib/dialyzer/src/dialyzer_utils.erl b/lib/dialyzer/src/dialyzer_utils.erl
index 0f87656dc6..93eaaa6417 100644
--- a/lib/dialyzer/src/dialyzer_utils.erl
+++ b/lib/dialyzer/src/dialyzer_utils.erl
@@ -767,7 +767,7 @@ sets_filter([Mod|Mods], ExpTypes) ->
 
 src_compiler_opts() ->
   [no_copt, to_core, binary, return_errors,
-   no_inline, strict_record_tests, strict_record_updates,
+   no_inline, strict_record_tests,
    dialyzer, no_spawn_compiler_process].
 
 -spec format_errors([{module(), string()}]) -> [string()].
diff --git a/lib/stdlib/src/erl_expand_records.erl b/lib/stdlib/src/erl_expand_records.erl
index d67e4e3796..2b09006faf 100644
--- a/lib/stdlib/src/erl_expand_records.erl
+++ b/lib/stdlib/src/erl_expand_records.erl
@@ -33,15 +33,15 @@
 
 -import(lists, [map/2,foldl/3,foldr/3,sort/1,reverse/1,duplicate/2]).
 
--record(exprec, {compile=[],	% Compile flags
-		 vcount=0,	% Variable counter
-		 calltype=#{},	% Call types
-		 records=#{},	% Record definitions
-                 raw_records=[],% Raw record forms
-		 strict_ra=[],	% strict record accesses
-		 checked_ra=[], % successfully accessed records
-                 dialyzer=false % Cached value of compile flag 'dialyzer'
-		}).
+-record(exprec, {vcount=0,             % Variable counter
+                 calltype=#{},         % Call types
+                 records=#{},          % Record definitions
+                 raw_records=[],       % Raw record forms
+                 strict_ra=[],         % Strict record accesses
+                 checked_ra=[],        % Successfully accessed records
+                 dialyzer=false,       % Compiler option 'dialyzer'
+                 strict_rec_tests=true :: boolean()
+                }).
 
 -spec(module(AbsForms, CompileOptions) -> AbsForms2 when
       AbsForms :: [erl_parse:abstract_form()],
@@ -57,10 +57,10 @@ module has no references to records, attributes, or code.
 %% erl_lint without errors.
 module(Fs0, Opts0) ->
     put(erl_expand_records_in_guard, false),
-    Opts = compiler_options(Fs0) ++ Opts0,
-    Dialyzer = lists:member(dialyzer, Opts),
-    Calltype = init_calltype(Fs0),
-    St0 = #exprec{compile = Opts, dialyzer = Dialyzer, calltype = Calltype},
+    Opts = Opts0 ++ compiler_options(Fs0),
+    St0 = #exprec{dialyzer = lists:member(dialyzer, Opts),
+                  calltype = init_calltype(Fs0),
+                  strict_rec_tests = strict_record_tests(Opts)},
     {Fs,_St} = forms(Fs0, St0),
     erase(erl_expand_records_in_guard),
     Fs.
@@ -635,7 +635,7 @@ index_expr(F, [_ | Fs], I) -> index_expr(F, Fs, I+1).
 %%  This expansion must be passed through expr again.
 
 get_record_field(Anno, R, Index, Name, St) ->
-    case strict_record_tests(St#exprec.compile) of
+    case St#exprec.strict_rec_tests of
         false ->
             sloppy_get_record_field(Anno, R, Index, Name, St);
         true ->
@@ -686,15 +686,17 @@ sloppy_get_record_field(Anno, R, Index, Name, St) ->
 	  {remote,Anno,{atom,Anno,erlang},{atom,Anno,element}},
 	  [I,R]}, St).
 
-strict_record_tests([strict_record_tests | _]) -> true;
-strict_record_tests([no_strict_record_tests | _]) -> false;
-strict_record_tests([_ | Os]) -> strict_record_tests(Os);
-strict_record_tests([]) -> true.		%Default.
+strict_record_tests(Opts) ->
+    strict_record_tests(Opts, true).
 
-strict_record_updates([strict_record_updates | _]) -> true;
-strict_record_updates([no_strict_record_updates | _]) -> false;
-strict_record_updates([_ | Os]) -> strict_record_updates(Os);
-strict_record_updates([]) -> false.		%Default.
+strict_record_tests([strict_record_tests | Os], _) ->
+    strict_record_tests(Os, true);
+strict_record_tests([no_strict_record_tests | Os], _) ->
+    strict_record_tests(Os, false);
+strict_record_tests([_ | Os], Bool) ->
+    strict_record_tests(Os, Bool);
+strict_record_tests([], Bool) ->
+    Bool.
 
 %% pattern_fields([RecDefField], [Match]) -> [Pattern].
 %%  Build a list of match patterns for the record tuple elements.
@@ -744,13 +746,14 @@ record_update(R, Name, Fs, Us0, St0) ->
     %% to guarantee that it is only evaluated once.
     {Var,St2} = new_var(Anno, St1),
 
-    %% Honor the `strict_record_updates` option needed by `dialyzer`, otherwise
-    %% expand everything to chains of `setelement/3` as that's far more
-    %% efficient in the JIT.
-    StrictUpdates = strict_record_updates(St2#exprec.compile),
+    %% If the `dialyzer` option is in effect, update the record by
+    %% matching out all unmodified fields and building a new tuple.
+    %% Otherwise expand everything to chains of `setelement/3` as
+    %% that is far more efficient in the JIT.
+    Dialyzer = St2#exprec.dialyzer,
     {Update,St} =
         if
-            not StrictUpdates, Us =/= [] ->
+            not Dialyzer, Us =/= [] ->
                 {record_setel(Var, Name, Fs, Us), St2};
             true ->
                 record_match(Var, Name, Anno, Fs, Us, St2)
diff --git a/lib/stdlib/src/erl_lint.erl b/lib/stdlib/src/erl_lint.erl
index 38b914a5d2..d58bb15cda 100644
--- a/lib/stdlib/src/erl_lint.erl
+++ b/lib/stdlib/src/erl_lint.erl
@@ -698,7 +698,7 @@ module(Forms, FileName, Opts0) ->
     %% FIXME Hmm, this is not coherent with the semantics of features
     %% We want the options given on the command line to take
     %% precedence over options in the module.
-    Opts = compiler_options(Forms) ++ Opts0,
+    Opts = Opts0 ++ compiler_options(Forms),
     St = forms(Forms, start(FileName, Opts)),
     return_status(St).
 
diff --git a/lib/stdlib/test/erl_lint_SUITE.erl b/lib/stdlib/test/erl_lint_SUITE.erl
index 588c7234cf..5c36031ed4 100644
--- a/lib/stdlib/test/erl_lint_SUITE.erl
+++ b/lib/stdlib/test/erl_lint_SUITE.erl
@@ -2350,19 +2350,18 @@ otp_5362(Config) when is_list(Config) ->
                       {{15,24},erl_lint,{undefined_field,ok,nix}},
                       {{16,24},erl_lint,{field_name_is_variable,ok,'Var'}}]}},
 
-	  %% Nowarn_bif_clash has changed behaviour as local functions
-	  %% nowdays supersede auto-imported BIFs, why nowarn_bif_clash in itself generates an error
-	  %% (OTP-8579) /PaN
+	  %% `nowarn_bif_clash` has changed behaviour as local functions
+	  %% nowdays supersede auto-imported BIFs. Therefore,
+	  %% `nowarn_bif_clash` in itself generates an error (OTP-8579).
           {otp_5362_4,
-           <<"-compile(nowarn_deprecated_function).
-              -compile(nowarn_bif_clash).
+           <<"-compile(warn_deprecated_function).
+              -compile(warn_bif_clash).
               spawn(A) ->
                   erlang:now(),
                   spawn(A).
            ">>,
            {[nowarn_unused_function,
-             warn_deprecated_function,
-             warn_bif_clash]},
+             warn_deprecated_function]},
            {error,
             [{{5,19},erl_lint,{call_to_redefined_old_bif,{spawn,1}}}],
             [{{4,19},erl_lint,{deprecated,{erlang,now,0},
-- 
2.35.3

openSUSE Build Service is sponsored by