File 1901-Clarify-how-the-features-parsing-state-works.patch of Package erlang

From 2793dfceab3ae66d579d629e27e85828ec53f99e Mon Sep 17 00:00:00 2001
From: Richard Carlsson <carlsson.richard@gmail.com>
Date: Fri, 12 Dec 2025 13:47:12 +0100
Subject: [PATCH 1/8] Clarify how the features parsing state works

---
 lib/compiler/src/compile.erl                 |  6 ++--
 lib/stdlib/src/epp.erl                       |  4 +--
 lib/stdlib/src/erl_features.erl              | 38 ++++++++++++++++----
 lib/stdlib/src/erl_lint.erl                  |  4 +++
 lib/syntax_tools/src/epp_dodger.erl          |  6 ++--
 lib/syntax_tools/src/syntax_tools.app.src    |  2 +-
 lib/syntax_tools/test/syntax_tools_SUITE.erl |  2 +-
 7 files changed, 46 insertions(+), 16 deletions(-)

diff --git a/lib/compiler/src/compile.erl b/lib/compiler/src/compile.erl
index f627aec471..ddd7c65def 100644
--- a/lib/compiler/src/compile.erl
+++ b/lib/compiler/src/compile.erl
@@ -1954,7 +1954,7 @@ do_parse_module(DefEncoding, #compile{ifile=File,options=Opts,dir=Dir}=St) ->
                         false ->
                             1
                     end,
-    case erl_features:keyword_fun(Opts, fun erl_scan:f_reserved_word/1) of
+    case erl_features:init_parse_state(Opts, fun erl_scan:f_reserved_word/1) of
         {ok, {Features, ResWordFun}} ->
             R = epp:parse_file(File,
                                [{includes,[".",Dir|inc_paths(Opts)]},
@@ -1975,8 +1975,8 @@ do_parse_module(DefEncoding, #compile{ifile=File,options=Opts,dir=Dir}=St) ->
             case R of
                 {ok,Forms0,Extra} ->
                     Encoding = proplists:get_value(encoding, Extra),
-                    %% Get features used in the module, indicated by
-                    %% enabling features with -feature(...).
+                    %% epp reports final set of features used by the module,
+                    %% including those given by `-feature(...)` declarations
                     UsedFtrs = proplists:get_value(features, Extra),
                     St1 = metadata_add_features(UsedFtrs, St),
                     Forms = case with_columns(Opts ++ compile_options(Forms0)) of
diff --git a/lib/stdlib/src/epp.erl b/lib/stdlib/src/epp.erl
index f4277109f3..fb813632a0 100644
--- a/lib/stdlib/src/epp.erl
+++ b/lib/stdlib/src/epp.erl
@@ -821,7 +821,7 @@ init_server(Pid, FileName, Options, St0) ->
             Path = [filename:dirname(FileName) |
                     proplists:get_value(includes, Options, [])],
             {ok,{_,ResWordFun0}} =
-                erl_features:keyword_fun([], fun erl_scan:f_reserved_word/1),
+                erl_features:init_parse_state([], fun erl_scan:f_reserved_word/1),
             ResWordFun =
                 proplists:get_value(reserved_word_fun, Options,
                                     ResWordFun0),
@@ -1335,7 +1335,7 @@ update_features(St0, Ind, Ftr, Loc) ->
             undefined -> fun erl_scan:f_reserved_word/1;
             Fun -> Fun
         end,
-    case erl_features:keyword_fun(Ind, Ftr, Ftrs0, KeywordFun) of
+    case erl_features:update_parse_state(Ind, Ftr, Ftrs0, KeywordFun) of
         {error, Reason} ->
             {error, {Reason, Loc}};
         {ok, {Ftrs1, ResWordFun1}} ->
diff --git a/lib/stdlib/src/erl_features.erl b/lib/stdlib/src/erl_features.erl
index 3a84c34447..d2f420bc38 100644
--- a/lib/stdlib/src/erl_features.erl
+++ b/lib/stdlib/src/erl_features.erl
@@ -37,12 +37,15 @@ functions that might be useful when writing tools.
          enabled/0,
          keywords/0,
          keywords/1,
-         keyword_fun/2,
-         keyword_fun/4,
+         init_parse_state/2,
+         update_parse_state/4,
          used/1,
          format_error/1,
          format_error/2]).
 
+%% temporary export for bootstrapping build
+-export([keyword_fun/2, keyword_fun/4]).
+
 -type type() :: 'extension' | 'backwards_incompatible_change'.
 -type status() :: 'experimental'
                   | 'approved'
@@ -220,12 +223,33 @@ keywords(Ftr, Map) ->
     maps:get(keywords, maps:get(Ftr, Map)).
 
 %% Utilities
-%% Returns list of enabled features and a new keywords function
--doc false.
+
+%% temporary aliases for bootstrapping build
+
 -spec keyword_fun([term()], fun((atom()) -> boolean())) ->
           {'ok', {[feature()], fun((atom()) -> boolean())}}
               | {'error', error()}.
 keyword_fun(Opts, KeywordFun) ->
+    init_parse_state(Opts, KeywordFun).
+
+-doc false.
+-spec keyword_fun('enable' | 'disable', feature(), [feature()],
+                  fun((atom()) -> boolean())) ->
+          {'ok', {[feature()], fun((atom()) -> boolean())}}
+              | {'error', error()}.
+keyword_fun(Ind, Feature, Ftrs, KeywordFun) ->
+    update_parse_state(Ind, Feature, Ftrs, KeywordFun).
+
+%% Handles `{feature, F, State}` options and returns the list of enabled
+%% features together with a keywords function, as the initial state for
+%% parsing, starting from the set of statically enabled features. This
+%% is then modified (in epp) using `update_parse_state/4` when a
+%% declaration `-feature(...)` is encountered.
+-doc false.
+-spec init_parse_state([term()], fun((atom()) -> boolean())) ->
+          {'ok', {[feature()], fun((atom()) -> boolean())}}
+              | {'error', error()}.
+init_parse_state(Opts, KeywordFun) ->
     %% Get items enabling or disabling features, preserving order.
     IsFtr = fun({feature, _, enable}) -> true;
                ({feature, _, disable}) -> true;
@@ -242,12 +266,14 @@ keyword_fun(Opts, KeywordFun) ->
             Error
     end.
 
+%% Modifies the given keyword fun to accept/deny keywords when a feature
+%% is turned on or off. Used by epp when scanning feature declarations.
 -doc false.
--spec keyword_fun('enable' | 'disable', feature(), [feature()],
+-spec update_parse_state('enable' | 'disable', feature(), [feature()],
                   fun((atom()) -> boolean())) ->
           {'ok', {[feature()], fun((atom()) -> boolean())}}
               | {'error', error()}.
-keyword_fun(Ind, Feature, Ftrs, KeywordFun) ->
+update_parse_state(Ind, Feature, Ftrs, KeywordFun) ->
     case is_configurable(Feature) of
         true ->
             case Ind of
diff --git a/lib/stdlib/src/erl_lint.erl b/lib/stdlib/src/erl_lint.erl
index a1ef3078d9..7c0e6e685e 100644
--- a/lib/stdlib/src/erl_lint.erl
+++ b/lib/stdlib/src/erl_lint.erl
@@ -798,6 +798,10 @@ start(File, Opts) ->
 		false ->
 		    undefined
 	    end,
+    %% note: `-feature declarations are collected and stripped by epp,
+    %% and the compiler presents the total set of enabled features as
+    %% the option `{features, ...}` to erl_lint and other passes; they
+    %% do not change after the epp pass
     #lint{state = start,
           exports = gb_sets:from_list([{module_info,0},{module_info,1}]),
           compile = Opts,
diff --git a/lib/syntax_tools/src/epp_dodger.erl b/lib/syntax_tools/src/epp_dodger.erl
index a660928575..83725cf871 100644
--- a/lib/syntax_tools/src/epp_dodger.erl
+++ b/lib/syntax_tools/src/epp_dodger.erl
@@ -330,10 +330,10 @@ parse_form(Dev, L0, Parser, Options) ->
     NoFail = proplists:get_bool(no_fail, Options),
     Opt = #opt{clever = proplists:get_bool(clever, Options)},
 
-    %% This has the *potential* to read options for enabling/disabling
-    %% features for the parsing of the file.
+    %% Note that options `{feature, FeatureName, enable|disable}` may
+    %% enable or disable features that affect the parsing of the file.
     {ok, {_Ftrs, ResWordFun}} =
-        erl_features:keyword_fun(Options, fun reserved_word/1),
+        erl_features:init_parse_state(Options, fun reserved_word/1),
 
     case io:scan_erl_form(Dev, "", L0, [{reserved_word_fun,ResWordFun}]) of
         {ok, Ts, L1} ->
diff --git a/lib/syntax_tools/src/syntax_tools.app.src b/lib/syntax_tools/src/syntax_tools.app.src
index 6b7d9ab180..2002671264 100644
--- a/lib/syntax_tools/src/syntax_tools.app.src
+++ b/lib/syntax_tools/src/syntax_tools.app.src
@@ -23,4 +23,4 @@
   {applications, [stdlib]},
   {env, []},
   {runtime_dependencies,
-   ["compiler-9.0","erts-16.0","kernel-10.3","stdlib-7.0"]}]}.
+   ["compiler-9.0","erts-16.0","kernel-10.3","stdlib-@OTP-19927@"]}]}.
diff --git a/lib/syntax_tools/test/syntax_tools_SUITE.erl b/lib/syntax_tools/test/syntax_tools_SUITE.erl
index 43eb7f011d..fb408e40ef 100644
--- a/lib/syntax_tools/test/syntax_tools_SUITE.erl
+++ b/lib/syntax_tools/test/syntax_tools_SUITE.erl
@@ -786,5 +786,5 @@ p_run_loop(Test, List, N, Refs0, Errors0) ->
 res_word_option() ->
     Options = [{feature, maybe_expr, enable}],
     {ok, {_Ftrs, ResWordFun}} =
-        erl_features:keyword_fun(Options, fun erl_scan:f_reserved_word/1),
+        erl_features:init_parse_state(Options, fun erl_scan:f_reserved_word/1),
     {reserved_word_fun, ResWordFun}.
-- 
2.51.0

openSUSE Build Service is sponsored by