File 0541-Pass-on-declared-features-to-subsequent-passes.patch of Package erlang

From 52707e8030a1d2c61ad72b0d4852adf5b795bd9d Mon Sep 17 00:00:00 2001
From: Richard Carlsson <carlsson.richard@gmail.com>
Date: Thu, 30 Jan 2025 15:16:52 +0100
Subject: [PATCH 1/3] Pass on declared features to subsequent passes

Makes it possible for erl_lint etc to react to -feature declarations
in the module being compiled, not just runtime feature flags.
---
 lib/compiler/src/compile.erl | 10 ++++------
 lib/stdlib/src/erl_lint.erl  |  5 ++---
 2 files changed, 6 insertions(+), 9 deletions(-)

diff --git a/lib/compiler/src/compile.erl b/lib/compiler/src/compile.erl
index 0aaec44059..f627aec471 100644
--- a/lib/compiler/src/compile.erl
+++ b/lib/compiler/src/compile.erl
@@ -1729,7 +1729,6 @@ abstr_passes(AbstrStatus) ->
         verified_abstr -> []
     end ++
         [
-         %% Add all -compile() directives to #compile.options
          ?pass(compile_directives),
 
          {delay,[{iff,debug_info,?pass(save_abstract_code)}]},
@@ -1975,12 +1973,10 @@ do_parse_module(DefEncoding, #compile{ifile=File,options=Opts,dir=Dir}=St) ->
                                         []
                                 end]),
             case R of
-                %% FIXME Extra should include used features as well
                 {ok,Forms0,Extra} ->
                     Encoding = proplists:get_value(encoding, Extra),
                     %% Get features used in the module, indicated by
-                    %% enabling features with
-                    %% -compile({feature, .., enable}).
+                    %% enabling features with -feature(...).
                     UsedFtrs = proplists:get_value(features, Extra),
                     St1 = metadata_add_features(UsedFtrs, St),
                     Forms = case with_columns(Opts ++ compile_options(Forms0)) of
@@ -1989,7 +1985,8 @@ do_parse_module(DefEncoding, #compile{ifile=File,options=Opts,dir=Dir}=St) ->
                                 false ->
                                     strip_columns(Forms0)
                             end,
-                    {ok,Forms,St1#compile{encoding=Encoding}};
+                    {ok,Forms,St1#compile{encoding=Encoding,
+                                          options=[{features, UsedFtrs}|Opts]}};
                 {error,E} ->
                     Es = [{St#compile.ifile,[{none,?MODULE,{epp,E}}]}],
                     {error,St#compile{errors=St#compile.errors ++ Es}}
@@ -2423,6 +2420,7 @@ legalize_vars(Code0, St) ->
                end, Code0),
     {ok,Code,St}.
 
+%% Add all -compile() directives to #compile.options
 compile_directives(Forms, #compile{options=Opts0}=St0) ->
     Opts1 = expand_opts(flatten([C || {attribute,_,compile,C} <- Forms])),
     Opts = Opts1 ++ Opts0,
diff --git a/lib/stdlib/src/erl_lint.erl b/lib/stdlib/src/erl_lint.erl
index fcbff047af..5bd529e505 100644
--- a/lib/stdlib/src/erl_lint.erl
+++ b/lib/stdlib/src/erl_lint.erl
@@ -221,6 +221,7 @@ value_option(Flag, Default, On, OnVal, Off, OffVal, Opts) ->
                    :: #{ta() => #typeinfo{}},
                exp_types=gb_sets:empty()        %Exported types
                    :: gb_sets:set(ta()),
+               features = [],                   %Enabled features
                feature_keywords =               %Keywords in
                                                 %configurable features
                    feature_keywords() :: #{atom() => atom()},
@@ -743,9 +744,6 @@ entries in the list of errors.
       ErrorInfo :: error_info()).
 
 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 = Opts0 ++ compiler_options(Forms),
     St = forms(Forms, start(FileName, Opts)),
     return_status(St).
@@ -780,6 +778,7 @@ start(File, Opts) ->
 				     nowarn_format, 0, Opts),
 	  enabled_warnings = Enabled,
           nowarn_bif_clash = nowarn_function(nowarn_bif_clash, Opts),
+          features = proplists:get_value(features, Opts, []),
           file = File
          }.
 
-- 
2.51.0

openSUSE Build Service is sponsored by