Sign Up
Log In
Log In
or
Sign Up
Places
All Projects
Status Monitor
Collapse sidebar
home:Ledest:erlang:24
erlang
3542-features-Add-support-for-handling-features...
Overview
Repositories
Revisions
Requests
Users
Attributes
Meta
File 3542-features-Add-support-for-handling-features.patch of Package erlang
From 55b51892b9556c18b2b5aa7607cfe80db9ca4e8d Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Cons=20T=20=C3=85hs?= <cons@erlang.org> Date: Mon, 8 Nov 2021 09:47:47 +0100 Subject: [PATCH 2/7] [features] Add support for handling features * Utility and features specifications in erl_features * Compiler support * Add predefined macros for features * Add support for parsing (long) options to erlc * Conditionally allow 'else' (also used in preprocessor) as keyword * This will be needed for EEP49 * Add feature info in new Meta chunk in beam file * Add warning for atoms that are keywords in features * Add new feature description options to erlc * -list-feature to list existing features in short form * -describe-feature <ftr> to get long description of feature * Runtime support * Store enabled features with persistent_term (only set at startup) * Check features in Meta chunk to determine whether load is allowed * Features use for test (in erl_features) active when env variable OTP_TEST_FEATURES is set to true * init of erl_features is lazy * Using on_load functions only work after code_server is up and running. --- erts/preloaded/src/erlang.erl | 26 +- erts/preloaded/src/erts.app.src | 2 +- lib/compiler/src/compile.erl | 93 ++-- lib/kernel/src/code.erl | 3 +- lib/stdlib/src/Makefile | 1 + lib/stdlib/src/epp.erl | 220 +++++++-- lib/stdlib/src/erl_compile.erl | 82 +++- lib/stdlib/src/erl_features.erl | 564 ++++++++++++++++++++++ lib/stdlib/src/erl_lint.erl | 28 +- lib/stdlib/src/erl_scan.erl | 72 +-- lib/stdlib/src/stdlib.app.src | 1 + lib/stdlib/test/epp_SUITE.erl | 13 +- lib/syntax_tools/src/syntax_tools.app.src | 2 +- 13 files changed, 976 insertions(+), 131 deletions(-) create mode 100644 lib/stdlib/src/erl_features.erl diff --git a/erts/preloaded/src/erlang.erl b/erts/preloaded/src/erlang.erl index b0430f4182..bbdd46dd80 100644 --- a/erts/preloaded/src/erlang.erl +++ b/erts/preloaded/src/erlang.erl @@ -2310,18 +2310,24 @@ is_tuple(_Term) -> -spec load_module(Module, Binary) -> {module, Module} | {error, Reason} when Module :: module(), Binary :: binary(), - Reason :: badfile | not_purged | on_load. + Reason :: badfile | not_purged | on_load | not_allowed. load_module(Mod, Code) -> try - case erlang:prepare_loading(Mod, Code) of - {error,_}=Error -> - Error; - Prep when erlang:is_reference(Prep) -> - case erlang:finish_loading([Prep]) of - ok -> - {module,Mod}; - {Error,[Mod]} -> - {error,Error} + Allowed = (not erlang:module_loaded(erl_features)) + orelse erl_features:load_allowed(Code), + if not Allowed -> + {error, not_allowed}; + true -> + case erlang:prepare_loading(Mod, Code) of + {error,_}=Error -> + Error; + Prep when erlang:is_reference(Prep) -> + case erlang:finish_loading([Prep]) of + ok -> + {module,Mod}; + {Error,[Mod]} -> + {error,Error} + end end end catch diff --git a/lib/compiler/src/compile.erl b/lib/compiler/src/compile.erl index 847ea484ba..d82f53d772 100644 --- a/lib/compiler/src/compile.erl +++ b/lib/compiler/src/compile.erl @@ -1,7 +1,7 @@ %% %% %CopyrightBegin% %% -%% Copyright Ericsson AB 1996-2021. All Rights Reserved. +%% Copyright Ericsson AB 1996-2022. All Rights Reserved. %% %% Licensed under the Apache License, Version 2.0 (the "License"); %% you may not use this file except in compliance with the License. @@ -1018,41 +1018,65 @@ do_parse_module(DefEncoding, #compile{ifile=File,options=Opts,dir=Dir}=St) -> false -> 1 end, - - %% FIXME: Rewrite this when the enable feature EEP has been implemented. - ResWordFun = case proplists:get_value(enable_feature, Opts, []) of - maybe_expr -> - fun('maybe') -> true; - ('else') -> true; - (Other) -> erl_scan:reserved_word(Other) - end; - _ -> - fun erl_scan:reserved_word/1 - end, - - R = epp:parse_file(File, - [{includes,[".",Dir|inc_paths(Opts)]}, - {source_name, SourceName}, - {macros,pre_defs(Opts)}, - {default_encoding,DefEncoding}, - {location,StartLocation}, - {reserved_word_fun,ResWordFun}, - extra]), - case R of - {ok,Forms0,Extra} -> - Encoding = proplists:get_value(encoding, Extra), - Forms = case with_columns(Opts ++ compile_options(Forms0)) of - true -> - Forms0; - false -> - strip_columns(Forms0) - end, - {ok,Forms,St#compile{encoding=Encoding}}; - {error,E} -> - Es = [{St#compile.ifile,[{none,?MODULE,{epp,E}}]}], - {error,St#compile{errors=St#compile.errors ++ Es}} + case erl_features:keyword_fun(Opts, fun erl_scan:f_reserved_word/1) of + {ok, {Features, ResWordFun}} -> + R = epp:parse_file(File, + [{includes,[".",Dir|inc_paths(Opts)]}, + {source_name, SourceName}, + {macros,pre_defs(Opts)}, + {default_encoding,DefEncoding}, + {location,StartLocation}, + {reserved_word_fun, ResWordFun}, + {features, Features}, + extra]), + 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({enable_feature, ..}). + UsedFtrs = proplists:get_value(features, Extra), + St1 = metadata_add_features(UsedFtrs, St), + Forms = case with_columns(Opts ++ compile_options(Forms0)) of + true -> + Forms0; + false -> + strip_columns(Forms0) + end, + {ok,Forms,St1#compile{encoding=Encoding}}; + {error,E} -> + Es = [{St#compile.ifile,[{none,?MODULE,{epp,E}}]}], + {error,St#compile{errors=St#compile.errors ++ Es}} + end; + {error, {Mod, Reason}} -> + Es = [{St#compile.ifile,[{none, Mod, Reason}]}], + {error, St#compile{errors = St#compile.errors ++ Es}} end. +%% The atom to be used in the proplist of the meta chunk indicating +%% the features used when compiling the module. +-define(META_USED_FEATURES, enabled_features). +-define(META_CHUNK_NAME, <<"Meta">>). + +metadata_add_features(Ftrs, #compile{extra_chunks = Extra} = St) -> + MetaData = + case proplists:get_value(?META_CHUNK_NAME, Extra) of + undefined -> + []; + Bin -> + erlang:binary_to_term(Bin) + end, + OldFtrs = proplists:get_value(?META_USED_FEATURES, MetaData, []), + NewFtrs = (Ftrs -- OldFtrs) ++ OldFtrs, + MetaData1 = + proplists:from_map(maps:put(?META_USED_FEATURES, NewFtrs, + proplists:to_map(MetaData))), + Extra1 = proplists:from_map(maps:put(?META_CHUNK_NAME, + erlang:term_to_binary(MetaData1), + proplists:to_map(Extra))), + St#compile{extra_chunks = Extra1}. + with_columns(Opts) -> case proplists:get_value(error_location, Opts, column) of column -> true; @@ -2081,6 +2105,7 @@ pre_load() -> epp, erl_bifs, erl_expand_records, + erl_features, erl_lint, erl_parse, erl_scan, diff --git a/lib/kernel/src/code.erl b/lib/kernel/src/code.erl index 71a570fa7b..3b426600d3 100644 --- a/lib/kernel/src/code.erl +++ b/lib/kernel/src/code.erl @@ -739,7 +739,8 @@ do_start() -> load_code_server_prerequisites() -> %% Please keep the alphabetical order. - Needed = [binary, + Needed = [beam_lib, + binary, ets, filename, gb_sets, diff --git a/lib/stdlib/src/Makefile b/lib/stdlib/src/Makefile index 88f41634fe..b7b5ead962 100644 --- a/lib/stdlib/src/Makefile +++ b/lib/stdlib/src/Makefile @@ -65,6 +65,7 @@ MODULES= \ erl_error \ erl_eval \ erl_expand_records \ + erl_features \ erl_internal \ erl_lint \ erl_parse \ diff --git a/lib/stdlib/src/epp.erl b/lib/stdlib/src/epp.erl index 1f14133039..1c2dbcb3bb 100644 --- a/lib/stdlib/src/epp.erl +++ b/lib/stdlib/src/epp.erl @@ -1,7 +1,7 @@ %% %% %CopyrightBegin% %% -%% Copyright Ericsson AB 1996-2021. All Rights Reserved. +%% Copyright Ericsson AB 1996-2022. All Rights Reserved. %% %% Licensed under the Apache License, Version 2.0 (the "License"); %% you may not use this file except in compliance with the License. @@ -72,9 +72,12 @@ uses = #{} %Macro use structure :: #{name() => [{argspec(), [used()]}]}, default_encoding = ?DEFAULT_ENCODING :: source_encoding(), - pre_opened = false :: boolean(), - fname = [] :: function_name_type(), - erl_scan_opts = [] :: erl_scan:options() + pre_opened = false :: boolean(), + in_prefix = true :: boolean(), + erl_scan_opts = [] :: [_], + features = [] :: [atom()], + else_reserved = false :: boolean(), + fname = [] :: function_name_type() }). %% open(Options) @@ -132,12 +135,14 @@ open(Options) -> Name -> Self = self(), Epp = spawn(fun() -> server(Self, Name, Options) end), + Extra = proplists:get_bool(extra, Options), case epp_request(Epp) of - {ok, Pid, Encoding} -> - case proplists:get_bool(extra, Options) of - true -> {ok, Pid, [{encoding, Encoding}]}; - false -> {ok, Pid} - end; + {ok, Pid, Encoding} when Extra -> + {ok, Pid, [{encoding, Encoding}]}; + {ok, Pid, _} -> + {ok, Pid}; + {ok, Pid} when Extra -> + {ok, Pid, []}; Other -> Other end @@ -240,6 +245,8 @@ format_error({error,Term}) -> io_lib:format("-error(~tp).", [Term]); format_error({warning,Term}) -> io_lib:format("-warning(~tp).", [Term]); +format_error(ftr_after_prefix) -> + "feature directive not allowed after anything interesting"; format_error(E) -> file:format_error(E). -spec scan_file(FileName, Options) -> @@ -298,6 +305,8 @@ parse_file(Ifile, Path, Predefs) -> {'macros', PredefMacros :: macros()} | {'default_encoding', DefEncoding :: source_encoding()} | {'location',StartLocation :: erl_anno:location()} | + {'reserved_word_fun', Fun :: fun((atom()) -> boolean())} | + {'features', [Feature :: atom()]} | 'extra'], Form :: erl_parse:abstract_form() | {'error', ErrorInfo} @@ -312,11 +321,13 @@ parse_file(Ifile, Options) -> {ok,Epp} -> Forms = parse_file(Epp), close(Epp), - {ok,Forms}; + {ok, Forms}; {ok,Epp,Extra} -> Forms = parse_file(Epp), + Epp ! {get_features, self()}, + Ftrs = receive X -> X end, close(Epp), - {ok,Forms,Extra}; + {ok, Forms, [{features, Ftrs} | Extra]}; {error,E} -> {error,E} end. @@ -594,7 +605,8 @@ server(Pid, Name, Options) -> init_server(Pid, FileName, Options, St0) -> SourceName = proplists:get_value(source_name, Options, FileName), Pdm = proplists:get_value(macros, Options, []), - Ms0 = predef_macros(SourceName), + Features = proplists:get_value(features, Options, []), + Ms0 = predef_macros(SourceName, Features), case user_predef(Pdm, Ms0) of {ok,Ms1} -> DefEncoding = proplists:get_value(default_encoding, Options, @@ -605,16 +617,19 @@ init_server(Pid, FileName, Options, St0) -> %% first in path Path = [filename:dirname(FileName) | proplists:get_value(includes, Options, [])], - - ResWordFun = proplists:get_value(reserved_word_fun, Options, - fun erl_scan:reserved_word/1), - + ResWordFun = + proplists:get_value(reserved_word_fun, Options, + fun erl_scan:f_reserved_word/1), %% the default location is 1 for backwards compatibility, not {1,1} AtLocation = proplists:get_value(location, Options, 1), + St = St0#epp{delta=0, name=SourceName, name2=SourceName, path=Path, location=AtLocation, macs=Ms1, default_encoding=DefEncoding, - erl_scan_opts=[{reserved_word_fun,ResWordFun}]}, + erl_scan_opts = + [{reserved_word_fun, ResWordFun}], + features = Features, + else_reserved = ResWordFun('else')}, From = wait_request(St), Anno = erl_anno:new(AtLocation), enter_file_reply(From, file_name(SourceName), Anno, @@ -628,10 +643,11 @@ init_server(Pid, FileName, Options, St0) -> %% Initialise the macro dictionary with the default predefined macros, %% FILE, LINE, MODULE as undefined, MACHINE and MACHINE value. -predef_macros(File) -> +predef_macros(File, EnabledFeatures) -> Machine = list_to_atom(erlang:system_info(machine)), Anno = line1(), OtpVersion = list_to_integer(erlang:system_info(otp_release)), + AvailableFeatures = erl_features:features(), Defs = [{'FILE', {none,[{string,Anno,File}]}}, {'FUNCTION_NAME', undefined}, {'FUNCTION_ARITY', undefined}, @@ -642,10 +658,38 @@ predef_macros(File) -> {'BASE_MODULE_STRING', undefined}, {'MACHINE', {none,[{atom,Anno,Machine}]}}, {Machine, {none,[{atom,Anno,true}]}}, - {'OTP_RELEASE', {none,[{integer,Anno,OtpVersion}]}} + {'OTP_RELEASE', {none,[{integer,Anno,OtpVersion}]}}, + %% FIXME Understand this has to be a list. Is it because + %% it takes an argument? + {'FEATURE_AVAILABLE', [ftr_macro(AvailableFeatures)]}, + {'FEATURE_ENABLED', [ftr_macro(EnabledFeatures)]} ], maps:from_list(Defs). +%% Make macro definition from a list of features. The macro takes one +%% argument and returns true when argument is available as a feature. +ftr_macro(Features) -> + Anno = line1(), + Arg = 'X', + Fexp = fun(Ftr) -> [{'(', Anno}, + {var, Anno, Arg}, + {')', Anno}, + {'==', Anno}, + {atom, Anno, Ftr}] + end, + Body = + case Features of + [] -> [{atom, Anno, false}]; + [Ftr| Ftrs] -> + [{'(', Anno}| + lists:foldl(fun(F, Expr) -> + Fexp(F) ++ [{'orelse', Anno} | Expr] + end, + Fexp(Ftr) ++ [{')', Anno}], + Ftrs)] + end, + {1, {[Arg], Body}}. + %% user_predef(PreDefMacros, Macros) -> %% {ok,MacroDict} | {error,E} %% Add the predefined macros to the macros dictionary. A macro without a @@ -680,6 +724,9 @@ user_predef([], Ms) -> {ok,Ms}. wait_request(St) -> receive {epp_request,From,scan_erl_form} -> From; + {get_features, From} -> + From ! St#epp.features, + wait_request(St); {epp_request,From,macro_defs} -> %% Return the old format to avoid any incompability issues. Defs = [{{atom,K},V} || {K,V} <- maps:to_list(St#epp.macs)], @@ -736,7 +783,11 @@ enter_file2(NewF, Pname, From, St0, AtLocation) -> Anno = erl_anno:new(AtLocation), enter_file_reply(From, Pname, Anno, AtLocation, code), #epp{macs = Ms0, - default_encoding = DefEncoding} = St0, + default_encoding = DefEncoding, + in_prefix = InPrefix, + erl_scan_opts = ScanOpts, + else_reserved = ElseReserved, + features = Ftrs} = St0, Ms = Ms0#{'FILE':={none,[{string,Anno,Pname}]}}, %% update the head of the include path to be the directory of the new %% source file, so that an included file can always include other files @@ -748,6 +799,10 @@ enter_file2(NewF, Pname, From, St0, AtLocation) -> _ = set_encoding(NewF, DefEncoding), #epp{file=NewF,location=AtLocation,name=Pname,name2=Pname,delta=0, sstk=[St0|St0#epp.sstk],path=Path,macs=Ms, + in_prefix = InPrefix, + features = Ftrs, + erl_scan_opts = ScanOpts, + else_reserved = ElseReserved, default_encoding=DefEncoding}. enter_file_reply(From, Name, LocationAnno, AtLocation, Where) -> @@ -789,8 +844,16 @@ leave_file(From, St) -> CurrLoc = add_line(OldLoc, Delta), Anno = erl_anno:new(CurrLoc), Ms0 = St#epp.macs, + InPrefix = St#epp.in_prefix, + Ftrs = St#epp.features, + ElseReserved = St#epp.else_reserved, + ScanOpts = St#epp.erl_scan_opts, Ms = Ms0#{'FILE':={none,[{string,Anno,OldName2}]}}, - NextSt = OldSt#epp{sstk=Sts,macs=Ms,uses=St#epp.uses}, + NextSt = OldSt#epp{sstk=Sts,macs=Ms,uses=St#epp.uses, + in_prefix = InPrefix, + features = Ftrs, + else_reserved = ElseReserved, + erl_scan_opts = ScanOpts}, enter_file_reply(From, OldName, Anno, CurrLoc, code), case OldName2 =:= OldName of true -> @@ -812,27 +875,30 @@ leave_file(From, St) -> %% scan_toks(Tokens, From, EppState) scan_toks(From, St) -> - case io:scan_erl_form(St#epp.file, '', St#epp.location, St#epp.erl_scan_opts) of - {ok,Toks,Cl} -> - scan_toks(Toks, From, St#epp{location=Cl}); - {error,E,Cl} -> - epp_reply(From, {error,E}), - wait_req_scan(St#epp{location=Cl}); - {eof,Cl} -> - leave_file(From, St#epp{location=Cl}); - {error,_E} -> + #epp{file = File, location = Loc, erl_scan_opts = ScanOpts} = St, + case io:scan_erl_form(File, '', Loc, ScanOpts) of + {ok,Toks,Cl} -> + scan_toks(Toks, From, St#epp{location=Cl}); + {error,E,Cl} -> + epp_reply(From, {error,E}), + wait_req_scan(St#epp{location=Cl}); + {eof,Cl} -> + leave_file(From, St#epp{location=Cl}); + {error,_E} -> epp_reply(From, {error,{St#epp.location,epp,cannot_parse}}), - leave_file(wait_request(St), St) %This serious, just exit! + leave_file(wait_request(St), St) %This serious, just exit! end. +scan_toks([{'-',_Lh},{atom,_Ld,feature}=Feature|Toks], From, St) -> + scan_feature(Toks, Feature, From, St); scan_toks([{'-',_Lh},{atom,_Ld,define}=Define|Toks], From, St) -> scan_define(Toks, Define, From, St); scan_toks([{'-',_Lh},{atom,_Ld,undef}=Undef|Toks], From, St) -> - scan_undef(Toks, Undef, From, St); + scan_undef(Toks, Undef, From, leave_prefix(St)); scan_toks([{'-',_Lh},{atom,_Ld,error}=Error|Toks], From, St) -> - scan_err_warn(Toks, Error, From, St); + scan_err_warn(Toks, Error, From, leave_prefix(St)); scan_toks([{'-',_Lh},{atom,_Ld,warning}=Warn|Toks], From, St) -> - scan_err_warn(Toks, Warn, From, St); + scan_err_warn(Toks, Warn, From, leave_prefix(St)); scan_toks([{'-',_Lh},{atom,_Li,include}=Inc|Toks], From, St) -> scan_include(Toks, Inc, From, St); scan_toks([{'-',_Lh},{atom,_Li,include_lib}=IncLib|Toks], From, St) -> @@ -843,7 +909,9 @@ scan_toks([{'-',_Lh},{atom,_Li,ifndef}=IfnDef|Toks], From, St) -> scan_ifndef(Toks, IfnDef, From, St); scan_toks([{'-',_Lh},{atom,_Le,'else'}=Else|Toks], From, St) -> scan_else(Toks, Else, From, St); -scan_toks([{'-',_Lh},{'else',_Le}=Else|Toks], From, St) -> +%% conditionally allow else as a keyword +scan_toks([{'-',_Lh},{'else',_Le}=Else|Toks], From, St) + when St#epp.else_reserved -> scan_else(Toks, Else, From, St); scan_toks([{'-',_Lh},{'if',_Le}=If|Toks], From, St) -> scan_if(Toks, If, From, St); @@ -862,13 +930,37 @@ scan_toks([{'-',_Lh},{atom,_Lf,file}=FileToken|Toks0], From, St) -> scan_toks(Toks0, From, St) -> case catch expand_macros(Toks0, St#epp{fname=Toks0}) of Toks1 when is_list(Toks1) -> + InPrefix = + St#epp.in_prefix + andalso case Toks1 of + [] -> true; + [{'-', _Loc}, Tok | _] -> + in_prefix(Tok); + _ -> + false + end, epp_reply(From, {ok,Toks1}), - wait_req_scan(St#epp{macs=scan_module(Toks1, St#epp.macs)}); + wait_req_scan(St#epp{in_prefix = InPrefix, + macs=scan_module(Toks1, St#epp.macs)}); {error,ErrL,What} -> epp_reply(From, {error,{ErrL,epp,What}}), wait_req_scan(St) end. +%% Determine whether we have passed the prefix where a -feature +%% directive is allowed. +in_prefix({atom, _, Atom}) -> + %% These directives are allowed inside the prefix + lists:member(Atom, ['module', 'feature', + 'if', 'else', 'elif', 'endif', 'ifdef', 'ifndef', + 'define', 'undef', + 'include', 'include_lib']); +in_prefix(_T) -> + false. + +leave_prefix(#epp{} = St) -> + St#epp{in_prefix = false}. + scan_module([{'-',_Ah},{atom,_Am,module},{'(',_Al}|Ts], Ms) -> scan_module_1(Ts, Ms); scan_module([{'-',_Ah},{atom,_Am,extends},{'(',_Al}|Ts], Ms) -> @@ -909,6 +1001,58 @@ scan_err_warn(Toks, {atom,_,Tag}=Token, From, St) -> epp_reply(From, {error,{loc(T),epp,{bad,Tag}}}), wait_req_scan(St). +%% scan a feature directive +scan_feature([{'(', _Ap}, {atom, _Am, Ind}, + {',', _}, {atom, _, Ftr}, {')', _}, {dot, _}], + Feature, From, St) + when St#epp.in_prefix, + (Ind =:= enable + orelse Ind =:= disable) -> + case update_features(St, Ind, Ftr, loc(Feature)) of + {ok, St1} -> + scan_toks(From, St1); + {error, {{Mod, Reason}, ErrLoc}} -> + epp_reply(From, {error, {ErrLoc, Mod, Reason}}), + wait_req_scan(St) + end; +scan_feature([{'(', _Ap}, {atom, _Am, _Ind}, + {',', _}, {atom, _, _Ftr}, {')', _}, {dot, _}| _Toks], + Feature, From, St) when not St#epp.in_prefix -> + epp_reply(From, {error, {loc(Feature), epp, + ftr_after_prefix}}), + wait_req_scan(St); +scan_feature(Toks, {atom, _, Tag} = Token, From, St) -> + T = no_match(Toks, Token), + epp_reply(From, {error,{loc(T),epp,{bad,Tag}}}), + wait_req_scan(St). + +%% FIXME Rewrite this +update_features(St0, Ind, Ftr, Loc) -> + Ftrs0 = St0#epp.features, + ScanOpts = St0#epp.erl_scan_opts, + KeywordFun = + case proplists:get_value(reserved_word_fun, ScanOpts) of + undefined -> fun erl_scan:f_reserved_word/1; + Fun -> Fun + end, + case erl_features:keyword_fun(Ind, Ftr, Ftrs0, KeywordFun) of + {error, Reason} -> + {error, {Reason, Loc}}; + {ok, ResWordFun1, Ftrs1} -> + Macs0 = St0#epp.macs, + Macs1 = Macs0#{'FEATURE_ENABLED' => [ftr_macro(Ftrs1)]}, + %% ?liof("ok!\n", []), + %% FIXME WE need to keep any other scan_opts + %% present. Right now, there are no other, but + %% that might change. + StX = St0#epp{erl_scan_opts = + [{reserved_word_fun, ResWordFun1}], + features = Ftrs1, + else_reserved = ResWordFun1('else'), + macs = Macs1}, + {ok, StX} + end. + %% scan_define(Tokens, DefineToken, From, EppState) scan_define([{'(',_Ap},{Type,_Am,_}=Mac|Toks], Def, From, St) @@ -1328,6 +1472,7 @@ new_location(Ln, {Le,_}, {Lf,_}) -> %% nested conditionals and repeated 'else's. skip_toks(From, St, [I|Sis]) -> + ElseReserved = St#epp.else_reserved, case io:scan_erl_form(St#epp.file, '', St#epp.location, St#epp.erl_scan_opts) of {ok,[{'-',_Ah},{atom,_Ai,ifdef}|_Toks],Cl} -> skip_toks(From, St#epp{location=Cl}, [ifdef,I|Sis]); @@ -1337,7 +1482,8 @@ skip_toks(From, St, [I|Sis]) -> skip_toks(From, St#epp{location=Cl}, ['if',I|Sis]); {ok,[{'-',_Ah},{atom,_Ae,'else'}=Else|_Toks],Cl}-> skip_else(Else, From, St#epp{location=Cl}, [I|Sis]); - {ok,[{'-',_Ah},{'else',_Ae}=Else|_Toks],Cl}-> + %% conditionally allow else as reserved word + {ok,[{'-',_Ah},{'else',_Ae}=Else|_Toks],Cl} when ElseReserved -> skip_else(Else, From, St#epp{location=Cl}, [I|Sis]); {ok,[{'-',_Ah},{atom,_Ae,'elif'}=Elif|Toks],Cl}-> skip_elif(Toks, Elif, From, St#epp{location=Cl}, [I|Sis]); diff --git a/lib/stdlib/src/erl_compile.erl b/lib/stdlib/src/erl_compile.erl index 063d3e700d..87af230c67 100644 --- a/lib/stdlib/src/erl_compile.erl +++ b/lib/stdlib/src/erl_compile.erl @@ -1,7 +1,7 @@ %% %% %CopyrightBegin% %% -%% Copyright Ericsson AB 1997-2021. All Rights Reserved. +%% Copyright Ericsson AB 1997-2022. All Rights Reserved. %% %% Licensed under the Apache License, Version 2.0 (the "License"); %% you may not use this file except in compliance with the License. @@ -109,6 +109,9 @@ compile1(Files, Opts) -> parse_generic_option("b"++Opt, T0, Opts) -> {OutputType,T} = get_option("b", Opt, T0), compile1(T, Opts#options{output_type=list_to_atom(OutputType)}); +%% parse_generic_option("c"++Opt, T0, Opts) -> +%% {InputType,T} = get_option("c", Opt, T0), +%% compile1(T, Opts#options{input_type=[$.| InputType]}); parse_generic_option("D"++Opt, T0, #options{defines=Defs}=Opts) -> {Val0,T} = get_option("D", Opt, T0), {Key0,Val1} = split_at_equals(Val0, []), @@ -171,6 +174,25 @@ parse_generic_option("P", T, #options{specific=Spec}=Opts) -> compile1(T, Opts#options{specific=['P'|Spec]}); parse_generic_option("S", T, #options{specific=Spec}=Opts) -> compile1(T, Opts#options{specific=['S'|Spec]}); +parse_generic_option("enable-feature" ++ Str, T0, + #options{specific = Spec} = Opts) -> + {FtrStr, T} = get_option("enable-feature", Str, T0), + Feature = list_to_atom(FtrStr), + compile1(T, Opts#options{ + specific = Spec ++ [{enable_feature, Feature}]}); +parse_generic_option("disable-feature" ++ Str, T0, + #options{specific = Spec} = Opts) -> + {FtrStr, T} = get_option("disable-feature", Str, T0), + Feature = list_to_atom(FtrStr), + compile1(T, Opts#options{specific = Spec ++ [{disable_feature, Feature}]}); +parse_generic_option("describe-feature" ++ Str, T0, + #options{specific = Spec} = Opts) -> + {FtrStr, T} = get_option("disable-feature", Str, T0), + Feature = list_to_atom(FtrStr), + compile1(T, Opts#options{specific =[{describe_feature, Feature}| Spec]}); +parse_generic_option("list-features", T, + #options{specific = Spec} = Opts) -> + compile1(T, Opts#options{specific =[{list_features, true}| Spec]}); parse_generic_option(Option, _T, _Opts) -> usage(io_lib:format("Unknown option: -~ts\n", [Option])). @@ -230,11 +252,24 @@ usage(Error) -> {"-E","generate listing of expanded code (Erlang compiler)"}, {"-S","generate assembly listing (Erlang compiler)"}, {"-P","generate listing of preprocessed code (Erlang compiler)"}, + {"-enable-feature <feature>", + "enable <feature> when compiling (Erlang compiler)"}, + {"-disable-feature <feature>", + "disable <feature> when compiling (Erlang compiler)"}, + {"-list-features", + "list short descriptions of available feature (Erlang compiler)"}, + {"-describe-feature <feature>", + "show long description of <feature>"}, {"+term","pass the Erlang term unchanged to the compiler"}], + Fmt = fun(K, D) when length(K) < 15 -> + io_lib:format("~-14s ~s\n", [K, D]); + (K, D) -> + io_lib:format("~s\n~-14s ~s\n", [K, "", D]) + end, Msg = [Error, "Usage: erlc [Options] file.ext ...\n", "Options:\n", - [io_lib:format("~-14s ~s\n", [K,D]) || {K,D} <- H]], + [Fmt(K, D) || {K,D} <- H]], throw({error, Msg}). get_option(_Name, [], [[C|_]=Option|T]) when C =/= $- -> @@ -252,14 +287,19 @@ split_at_equals([], Acc) -> {lists:reverse(Acc),[]}. compile2(Files, #options{cwd=Cwd,includes=Incl,outfile=Outfile}=Opts0) -> - Opts = Opts0#options{includes=lists:reverse(Incl)}, - case {Outfile,length(Files)} of - {"", _} -> - compile3(Files, Cwd, Opts); - {[_|_], 1} -> - compile3(Files, Cwd, Opts); - {[_|_], _N} -> - throw({error, "Output file name given, but more than one input file.\n"}) + case show_info(Opts0) of + {ok, Msg} -> + throw({error, Msg}); + false -> + Opts = Opts0#options{includes=lists:reverse(Incl)}, + case {Outfile,length(Files)} of + {"", _} -> + compile3(Files, Cwd, Opts); + {[_|_], 1} -> + compile3(Files, Cwd, Opts); + {[_|_], _N} -> + throw({error, "Output file name given, but more than one input file.\n"}) + end end. %% Compile the list of files, until done or compilation fails. @@ -278,6 +318,28 @@ compile3([File|Rest], Cwd, Options) -> compile3(Rest, Cwd, Options); compile3([], _Cwd, _Options) -> ok. +show_info(#options{specific = Spec}) -> + G = fun G0([]) -> undefined; + G0([E|Es]) -> + case proplists:get_value(E, Spec) of + undefined -> G0(Es); + V -> {E, V} + end + end, + + case G([list_features, describe_feature]) of + {list_features, true} -> + Features = erl_features:features(), + Msg = ["Available features:\n", + [io_lib:format(" ~-13s ~s\n", [Ftr, erl_features:short(Ftr)]) + || Ftr <- Features]], + {ok, Msg}; + {describe_feature, Ftr} -> + {ok, erl_features:long(Ftr)}; + _ -> + false + end. + %% Invoke the appropriate compiler, depending on the file extension. compile_file("", Input, _Output, _Options) -> throw({error, io_lib:format("File has no extension: ~ts~n", [Input])}); diff --git a/lib/stdlib/src/erl_features.erl b/lib/stdlib/src/erl_features.erl new file mode 100644 index 0000000000..d8618f9c3f --- /dev/null +++ b/lib/stdlib/src/erl_features.erl @@ -0,0 +1,564 @@ +%% +%% %CopyrightBegin% +%% +%% Copyright Ericsson AB 2021-2022. All Rights Reserved. +%% +%% Licensed under the Apache License, Version 2.0 (the "License"); +%% you may not use this file except in compliance with the License. +%% You may obtain a copy of the License at +%% +%% http://www.apache.org/licenses/LICENSE-2.0 +%% +%% Unless required by applicable law or agreed to in writing, software +%% distributed under the License is distributed on an "AS IS" BASIS, +%% WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied. +%% See the License for the specific language governing permissions and +%% limitations under the License. +%% +%% %CopyrightEnd% +%% +-module(erl_features). + +%% FIXME divide the exported functions in public and internal for the +%% sake of documentation. +-export([features/0, + feature_info/1, + collect_features/1, + short/1, + long/1, + enabled_features/0, + is_valid_feature/1, + load_allowed/1, + keywords/0, + keywords/1, + keyword_fun/2, + keyword_fun/4, + enable_feature/1, + disable_feature/1, + format_error/1, + format_error/2]). + +-export([features_used/1]). + +-type type() :: 'extension' | 'backwards_incompatible_change'. +-type status() :: 'experimental' + | 'approved' + | 'permanent' + | 'rejected'. +-type release() :: non_neg_integer(). +-type error() :: {?MODULE, {'invalid_features', [atom()]}}. + +-define(VALID_FEATURE(Feature), + (case is_valid_feature(Feature) of + false -> + error(invalid_feature, [Feature], + [{error_info, + #{module => ?MODULE, + cause => #{1 => "unknown feature"}}}]); + true -> ok + end)). + +%% Specification about currently known features. +feature_specs() -> + #{}. + +%% Currently known features +-spec features() -> [atom()]. +features() -> + Map = case persistent_term:get({?MODULE, feature_specs}, none) of + none -> init_specs(); + M -> M + end, + maps:keys(Map). + +is_valid_feature(Ftr) -> + lists:member(Ftr, features()). + +-spec short(atom()) -> iolist(). +short(Feature) -> + #{short := Short, + status := Status} = Info = feature_info(Feature), + #{Status := Release} = Info, + io_lib:format("~-40s ~-12s (~p)", [Short, Status, Release]). + +long(Feature) -> + #{short := Short, + description := Description, + status := Status, + keywords := Keywords, + type := Type} = Info = feature_info(Feature), + StatusFmt = " ~-10s ~-12s (~p)\n", + History = [io_lib:format(StatusFmt, [T, S, R]) + || {T, S, R} <- history(Status, Info)], + KeywordsStrs = + if Keywords == [] -> ""; + true -> + io_lib:format(" ~-10s ~p\n", ["Keywords", Keywords]) + end, + Lines = [{"~s - ~s\n", [Feature, Short]}, + {" ~-10s ~s\n", ["Type", Type]}, + {"~s", [History]}, + {"~s", [KeywordsStrs]}, + {"\n~s\n", [nqTeX(Description)]}], + [io_lib:format(FStr, Args) || {FStr, Args} <- Lines]. + +history(Current, Info) -> + G = fun(Key, S) -> + case maps:find(Key, Info) of + error -> []; + {ok, R} -> [{S, Key, R}] + end + end, + F = fun(Key) -> G(Key, "") end, + History = + case Current of + experimental -> []; + rejected -> F(experimental); + approved -> F(experimental); + permanent -> F(approved) ++ F(experimental) + end, + G(Current, "Status") ++ History. + +%% Dead simple line breaking for better presentation. +nqTeX(String) -> + Words = string:tokens(String, " "), + WithLens = lists:map(fun(W) -> {W, length(W)} end, Words), + adjust(WithLens). + +adjust(WLs) -> + adjust(0, WLs, []). + +adjust(_, [], Ws) -> + lists:reverse(tl(Ws)); +adjust(Col, [{W, L}| WLs], Ws) -> + case Col + L > 72 of + true -> + lists:reverse(["\n"| tl(Ws)]) + ++ adjust(L+1, WLs, [" ", W]); + false -> + adjust(Col + L + 1, WLs, [" ", W| Ws]) + end. + + +-spec feature_info(atom()) -> FeatureInfoMap | no_return() + when + Description :: string(), + FeatureInfoMap :: + #{description := Description, + short := Description, + type := type(), + keywords := [atom()], + status := status(), + experimental => release(), + approved => release(), + permanent => release(), + rejected => release() + }. +feature_info(Feature) -> + ?VALID_FEATURE(Feature), + + Map = persistent_term:get({?MODULE, feature_specs}), + maps:get(Feature, Map). + +%% New keywords for a feature. The current set is just for +%% tests and development. +-spec keywords(atom()) -> [atom()]. +keywords(Ftr) -> + ?VALID_FEATURE(Ftr), + + #{keywords := Keywords} = feature_info(Ftr), + Keywords. + +%% Internal - Ftr is valid +keywords(Ftr, Map) -> + maps:get(keywords, maps:get(Ftr, Map)). + +%% Utilities +%% Returns list of enabled features and a new keywords function +%% -spec keyword_fun_add_feature(atom(), fun((atom()) -> boolean())) -> +%% {'ok', fun((atom()) -> boolean())} +%% | {'error', error()}. +keyword_fun(Opts, KeywordFun) -> + %% Get items enabling or disabling features, preserving order. + IsFtr = fun({enable_feature, _}) -> true; + ({disable_feature, _}) -> true; + (_) -> false + end, + FeatureOps = lists:filter(IsFtr, Opts), + {AddFeatures, DelFeatures} = collect_features(FeatureOps), + %% FIXME check that all features are known at this stage so we + %% don't miss out on reporting any unknown features. + + case keyword_fun_add_features(AddFeatures, KeywordFun) of + {ok, Fun} -> + case keyword_fun_remove_features(DelFeatures, Fun) of + {ok, FunX} -> + {ok, {AddFeatures -- DelFeatures, FunX}}; + {error, _} = Error -> + %% FIXME We are missing potential incorrect + %% features being disabled + Error + end; + {error, _} = Error -> + Error + end. + +%% -spec keyword_fun_add_feature(atom(), fun((atom()) -> boolean())) -> +%% {'ok', fun((atom()) -> boolean())} +%% | {'error', error()}. +keyword_fun(Ind, Feature, Ftrs, KeywordFun) -> + case is_valid_feature(Feature) of + true -> + case Ind of + enable -> + {ok, + add_feature(Feature, KeywordFun), + [Feature | Ftrs]}; + disable -> + {ok, + remove_feature(Feature, KeywordFun), + Ftrs -- [Feature]} + end; + false -> + {error, {?MODULE, {invalid_features, [Feature]}}} + end. + +%% FIXME Rename this to reflect that it returns a function! +add_feature(Feature, F) -> + Words = keywords(Feature), + fun(Word) -> + lists:member(Word, Words) + orelse F(Word) + end. + +%% FIXME Rename this to reflect that it returns a function! +remove_feature(Feature, F) -> + Words = keywords(Feature), + fun(Word) -> + case lists:member(Word, Words) of + true -> false; + false -> F(Word) + end + end. + +-spec keyword_fun_add_features([atom()], fun((atom()) -> boolean())) -> + {'ok', fun((atom()) -> boolean())} + | {'error', error()}. +keyword_fun_add_features(Features, F) -> + case lists:all(fun is_valid_feature/1, Features) of + true -> + {ok, lists:foldl(fun add_feature/2, F, Features)}; + false -> + IsInvalid = fun(Ftr) -> not is_valid_feature(Ftr) end, + Invalid = lists:filter(IsInvalid, Features), + {error, {?MODULE, {invalid_features, Invalid}}} + end. + +-spec keyword_fun_remove_features([atom()], fun((atom()) -> boolean())) -> + {'ok', fun((atom()) -> boolean())} + | {'error', error()}. +keyword_fun_remove_features(Features, F) -> + case lists:all(fun is_valid_feature/1, Features) of + true -> + {ok, lists:foldl(fun remove_feature/2, F, Features)}; + false -> + IsInvalid = fun(Ftr) -> not is_valid_feature(Ftr) end, + Invalid = lists:filter(IsInvalid, Features), + {error, {?MODULE, {invalid_features, Invalid}}} + end. + +format_error(Reason, [{_M, _F, _Args, Info}| _St]) -> + ErrorInfo = proplists:get_value(error_info, Info, #{}), + ErrorMap = maps:get(cause, ErrorInfo), + ErrorMap#{reason => io_lib:format("~p: ~p", [?MODULE, Reason])}. + +format_error({invalid_features, Features}) -> + Fmt = fun F([Ftr]) -> io_lib:fwrite("'~p'", [Ftr]); + F([Ftr1, Ftr2]) -> + io_lib:fwrite("'~p' and '~p'", [Ftr1, Ftr2]); + F([Ftr| Ftrs]) -> + io_lib:fwrite("'~p', ~s", [Ftr, F(Ftrs)]) + end, + case Features of + [Ftr] -> + io_lib:fwrite("the feature ~s does not exist.", [Fmt([Ftr])]); + Ftrs -> + io_lib:fwrite("the features ~s do not exist.", [Fmt(Ftrs)]) + end. + +%% Hold the state of which features are currently enabled. +%% This is almost static, so we go for an almost permanent state, +%% i.e., use persistent_term. +init_features() -> + Map = init_specs(), + + persistent_term:put({?MODULE, enabled_features}, []), + persistent_term:put({?MODULE, keywords}, []), + + RawOps = lists:filter(fun({Tag, _}) -> + Tag == 'enable-feature' + orelse Tag == 'disable-feature'; + (_) -> false + end, + init:get_arguments()), + + Cnv = fun('enable-feature') -> enable_feature; + ('disable-feature') -> disable_feature + end, + + FeatureOps = lists:append(lists:map(fun({Tag, Strings}) -> + lists:map(fun(S) -> + {Tag, S} end, + Strings) + end, + RawOps)), + + %% Convert failure, e.g., too long string for atom, to not + %% being a valid feature. + F = fun({Tag, String}) -> + try + Atom = list_to_atom(String), + case is_valid_feature(Atom) of + true -> {true, {Cnv(Tag), Atom}}; + false when Atom == all -> + {true, {Cnv(Tag), Atom}}; + false -> false + end + catch + _ -> false + end + end, + FOps = lists:filtermap(F, FeatureOps), + {Features, _} = collect_features(FOps), + {Enabled, Keywords} = + lists:foldl(fun(Ftr, {Ftrs, Keys}) -> + case lists:member(Ftr, Ftrs) of + true -> + {Ftrs, Keys}; + false -> + {[Ftr| Ftrs], + keywords(Ftr, Map) ++ Keys} + end + end, + {[], []}, + Features), + + %% Save state + enabled_features(Enabled), + set_keywords(Keywords), + persistent_term:put({?MODULE, init_done}, true), + ok. + +init_specs() -> + Specs = case os:getenv("OTP_TEST_FEATURES") of + "true" -> test_features(); + _ -> feature_specs() + end, + persistent_term:put({?MODULE, feature_specs}, Specs), + Specs. + +ensure_init() -> + case persistent_term:get({?MODULE, init_done}, false) of + true -> ok; + false -> + init_features() + end. + +%% FIXME - remove this. It should not be available at runtime. This +%% is all done by the init code. +enable_feature(Feature) -> + ?VALID_FEATURE(Feature), + + Features = enabled_features(), + case lists:member(Feature, Features) of + true -> + %% already there, maybe raise an error + Features; + false -> + NewFeatures = [Feature| Features], + enabled_features(NewFeatures), + Keywords = keywords(), + New = keywords(Feature), + set_keywords(New ++ Keywords), + NewFeatures + end. + +disable_feature(Feature) -> + ?VALID_FEATURE(Feature), + + Features = enabled_features(), + case lists:member(Feature, Features) of + true -> + NewFeatures = Features -- [Feature], + enabled_features(NewFeatures), + Keywords = keywords(), + Rem = keywords(Feature), + set_keywords(Keywords -- Rem), + NewFeatures; + false -> + %% Not there, possibly raise an error + Features + end. + +enabled_features() -> + ensure_init(), + persistent_term:get({?MODULE, enabled_features}). + +enabled_features(Ftrs) -> + persistent_term:put({?MODULE, enabled_features}, Ftrs). + +keywords() -> + ensure_init(), + persistent_term:get({?MODULE, keywords}). + +set_keywords(Words) -> + persistent_term:put({?MODULE, keywords}, Words). + + +-spec load_allowed(binary()) -> boolean(). +load_allowed(Binary) -> + case erts_internal:beamfile_chunk(Binary, "Meta") of + undefined -> + true; + Meta -> + MetaData = erlang:binary_to_term(Meta), + case proplists:get_value(enabled_features, MetaData) of + undefined -> + true; + Used -> + Enabled = enabled_features(), + lists:all(fun(UFtr) -> + lists:member(UFtr, Enabled) + end, + Used) + end + end. + + +%% Return features used by module or beam file +features_used(Module) when is_atom(Module) -> + case code:get_object_code(Module) of + error -> + not_found; + {_Mod, Bin, _Fname} -> + features_in(Bin) + end; +features_used(FName) when is_list(FName) -> + features_in(FName). + +features_in(NameOrBin) -> + case beam_lib:chunks(NameOrBin, ["Meta"], [allow_missing_chunks]) of + {ok, {_, [{_, missing_chunk}]}} -> + []; + {ok, {_, [{_, Meta}]}} -> + MetaData = erlang:binary_to_term(Meta), + proplists:get_value(enabled_features, MetaData, []); + _ -> + not_found + end. + +approved_features() -> + [Ftr || Ftr <- features(), + maps:get(status, feature_info(Ftr)) == approved]. + +permanent_features() -> + [Ftr || Ftr <- features(), + maps:get(status, feature_info(Ftr)) == permanent]. + +%% Interpret feature ops (enable or disable) to build the full set of +%% features. The meta feature 'all' is expanded to all known +%% features. +collect_features(FOps) -> + %% Features enabled by default + Enabled = approved_features() ++ permanent_features(), + collect_features(FOps, Enabled, []). + +collect_features([], Add, Del) -> + {Add, Del}; +collect_features([{enable_feature, all}| FOps], Add, _Del) -> + All = features(), + Add1 = lists:foldl(fun add_ftr/2, Add, All), + collect_features(FOps, Add1, []); +collect_features([{enable_feature, Feature}| FOps], Add, Del) -> + collect_features(FOps, add_ftr(Feature, Add), Del -- [Feature]); +collect_features([{disable_feature, all}| FOps], _Add, Del) -> + %% Start over + All = features(), + collect_features(FOps, [], Del -- All); +collect_features([{disable_feature, Feature}| FOps], Add, Del) -> + collect_features(FOps, Add -- [Feature], + add_ftr(Feature, Del)). + +add_ftr(F, []) -> + [F]; +add_ftr(F, [F| _] = Fs) -> + Fs; +add_ftr(F, [F0| Fs]) -> + [F0| add_ftr(F, Fs)]. + +%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%% +%%% Test features - not present in a release +test_features() -> + #{ifn_expr => + #{short => "New expression `ifn cond -> body end`", + description => + "Inclusion of expression `ifn cond -> body end`, which " + "evaluates `body` when cond is false. This is a truly " + "experimental feature, present only to show and use the " + "support for experimental features. Not extensively tested. " + "Implementated by a transformation in the parser.", + status => experimental, + experimental => 24, + keywords => ['ifn'], + type => extension}, + ifnot_expr => + #{short => "New expression `ifnot cond -> body end`", + description => + "Inclusion of expression `ifnot cond -> body end`, which " + "evaluates `body` when cond is false. This is a truly " + "experimental feature, present only to show and use the " + "support for experimental features. Not extensively tested. " + "Similar to ifn_expr, but with a deeper implementation.", + status => experimental, + experimental => 25, + keywords => ['ifnot'], + type => extension}, + unless_expr => + #{short => "`unless <cond> -> <bodby> end", + description => + "Introduction of new expression `unless <cond> -> <body> end." + " Truly experimental.", + status => experimental, + experimental => 25, + keywords => ['unless'], + type => extension}, + maps => + #{short => "Add maps as new data type", + description => "Add new low data type maps with syntactic " + "support in Erlang as well native support in the beam. " + "Insert, lookup and delete are asymptotically constant.", + status => permanent, + experimental => 17, + approved => 18, + permanent => 19, + keywords => [], + type => extension}, + cond_expr => + #{short => "Introduce general Lisp style conditional", + description => + "Finally complement the painfully broken `if` " + "with a general conditional as in Lisp from the days of old.", + status => approved, + experimental => 24, + approved => 25, + keywords => [], + type => extension}, + while_expr => + #{short => "Introduce strange iterative expressions", + description => + "Introduce looping constructs, with seemingly " + "destructive assignment and vague semantics.", + status => experimental, + experimental => 25, + keywords => ['while', 'until'], + type => extension}}. diff --git a/lib/stdlib/src/erl_lint.erl b/lib/stdlib/src/erl_lint.erl index 84ae2f6bf9..3ae2bc41c4 100644 --- a/lib/stdlib/src/erl_lint.erl +++ b/lib/stdlib/src/erl_lint.erl @@ -199,6 +199,9 @@ format_error(invalid_call) -> format_error(invalid_record) -> "invalid record expression"; +format_error({future_feature, Ftr, Atom}) -> + io_lib:format("atom '~p' is reserved in the experimental feature '~p'", + [Atom, Ftr]); format_error({attribute,A}) -> io_lib:format("attribute ~tw after function definitions", [A]); format_error({missing_qlc_hrl,A}) -> @@ -588,6 +591,7 @@ module(Forms, FileName) -> 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 = compiler_options(Forms) ++ Opts0, @@ -658,7 +662,10 @@ start(File, Opts) -> true, Opts)}, {nif_inline, bool_option(warn_nif_inline, nowarn_nif_inline, - true, Opts)} + true, Opts)}, + {keyword_warning, + bool_option(warn_keywords, nowarn_keywords, + false, Opts)} ], Enabled1 = [Category || {Category,true} <- Enabled0], Enabled = ordsets:from_list(Enabled1), @@ -4164,7 +4171,22 @@ test_overriden_by_local(Anno, OldTest, Arity, St) -> %% keyword_warning(Anno, Atom, State) -> State. %% Add warning for atoms that will be reserved keywords in the future. %% (Currently, no such keywords to warn for.) -keyword_warning(_Anno, _A, St) -> St. +keyword_warning(Anno, Atom, St) -> + case is_warn_enabled(keyword_warning, St) of + true -> + Ftrs = erl_features:features(), + Reserved = + fun(Ftr) -> + lists:member(Atom, erl_features:keywords(Ftr)) + end, + case lists:filter(Reserved, Ftrs) of + [] -> St; + [Ftr] -> + add_warning(Anno, {future_feature, Ftr, Atom}, St) + end; + false -> + St + end. %% format_function(Anno, ModName, FuncName, [Arg], State) -> State. %% Add warning for bad calls to io:fwrite/format functions. diff --git a/lib/stdlib/src/erl_scan.erl b/lib/stdlib/src/erl_scan.erl index d1c3b94cf3..a30747b5e5 100644 --- a/lib/stdlib/src/erl_scan.erl +++ b/lib/stdlib/src/erl_scan.erl @@ -1,7 +1,7 @@ %% %% %CopyrightBegin% %% -%% Copyright Ericsson AB 1996-2021. All Rights Reserved. +%% Copyright Ericsson AB 1996-2022. All Rights Reserved. %% %% Licensed under the Apache License, Version 2.0 (the "License"); %% you may not use this file except in compliance with the License. @@ -52,7 +52,8 @@ %%% External exports -export([string/1,string/2,string/3,tokens/3,tokens/4, - format_error/1,reserved_word/1]). + format_error/1,reserved_word/1, + f_reserved_word/1]). -export([column/1,end_location/1,line/1,location/1,text/1, category/1,symbol/1]). @@ -1227,32 +1228,43 @@ tabs(8) -> "\t\t\t\t\t\t\t\t"; tabs(9) -> "\t\t\t\t\t\t\t\t\t"; tabs(10) -> "\t\t\t\t\t\t\t\t\t\t". +%% Dynamic version of reserved_word that knows about the possibility +%% that enabled features might change the set of reserved words. -spec reserved_word(Atom :: atom()) -> boolean(). -reserved_word('after') -> true; -reserved_word('begin') -> true; -reserved_word('case') -> true; -reserved_word('try') -> true; -reserved_word('cond') -> true; -reserved_word('catch') -> true; -reserved_word('andalso') -> true; -reserved_word('orelse') -> true; -reserved_word('end') -> true; -reserved_word('fun') -> true; -reserved_word('if') -> true; -reserved_word('let') -> true; -reserved_word('of') -> true; -reserved_word('receive') -> true; -reserved_word('when') -> true; -reserved_word('bnot') -> true; -reserved_word('not') -> true; -reserved_word('div') -> true; -reserved_word('rem') -> true; -reserved_word('band') -> true; -reserved_word('and') -> true; -reserved_word('bor') -> true; -reserved_word('bxor') -> true; -reserved_word('bsl') -> true; -reserved_word('bsr') -> true; -reserved_word('or') -> true; -reserved_word('xor') -> true; -reserved_word(_) -> false. +reserved_word(Atom) -> + case f_reserved_word(Atom) of + true -> true; + false -> + lists:member(Atom, erl_features:keywords()) + end. + +%% Static version of reserved_words. These represent the fixed set of +%% reserved words. +f_reserved_word('after') -> true; +f_reserved_word('begin') -> true; +f_reserved_word('case') -> true; +f_reserved_word('try') -> true; +f_reserved_word('cond') -> true; +f_reserved_word('catch') -> true; +f_reserved_word('andalso') -> true; +f_reserved_word('orelse') -> true; +f_reserved_word('end') -> true; +f_reserved_word('fun') -> true; +f_reserved_word('if') -> true; +f_reserved_word('let') -> true; +f_reserved_word('of') -> true; +f_reserved_word('receive') -> true; +f_reserved_word('when') -> true; +f_reserved_word('bnot') -> true; +f_reserved_word('not') -> true; +f_reserved_word('div') -> true; +f_reserved_word('rem') -> true; +f_reserved_word('band') -> true; +f_reserved_word('and') -> true; +f_reserved_word('bor') -> true; +f_reserved_word('bxor') -> true; +f_reserved_word('bsl') -> true; +f_reserved_word('bsr') -> true; +f_reserved_word('or') -> true; +f_reserved_word('xor') -> true; +f_reserved_word(_) -> false. diff --git a/lib/stdlib/src/stdlib.app.src b/lib/stdlib/src/stdlib.app.src index 9962fef931..fbf0e73149 100644 --- a/lib/stdlib/src/stdlib.app.src +++ b/lib/stdlib/src/stdlib.app.src @@ -46,6 +46,7 @@ erl_error, erl_eval, erl_expand_records, + erl_features, erl_internal, erl_lint, erl_parse, diff --git a/lib/stdlib/test/epp_SUITE.erl b/lib/stdlib/test/epp_SUITE.erl index 30437de302..8e800f8112 100644 --- a/lib/stdlib/test/epp_SUITE.erl +++ b/lib/stdlib/test/epp_SUITE.erl @@ -1609,8 +1609,9 @@ encoding(Config) when is_list(Config) -> epp_parse_file(ErlFile, [{default_encoding,latin1}]), {ok,[{attribute,1,file,_}, {attribute,1,module,encoding}, - {eof,3}],[{encoding,none}]} = + {eof,3}],Extra0} = epp_parse_file(ErlFile, [{default_encoding,latin1},extra]), + none = proplists:get_value(encoding, Extra0), %% Try a latin-1 file with encoding given in a comment. C2 = <<"-module(encoding). @@ -1632,16 +1633,20 @@ encoding(Config) when is_list(Config) -> epp_parse_file(ErlFile, [{default_encoding,utf8}]), {ok,[{attribute,1,file,_}, {attribute,1,module,encoding}, - {eof,4}],[{encoding,latin1}]} = + {eof,4}],Extra1} = epp_parse_file(ErlFile, [extra]), + latin1 = proplists:get_value(encoding, Extra1), + {ok,[{attribute,1,file,_}, {attribute,1,module,encoding}, - {eof,4}],[{encoding,latin1}]} = + {eof,4}],Extra2} = epp_parse_file(ErlFile, [{default_encoding,latin1},extra]), + latin1 = proplists:get_value(encoding, Extra2), {ok,[{attribute,1,file,_}, {attribute,1,module,encoding}, - {eof,4}],[{encoding,latin1}]} = + {eof,4}],Extra3} = epp_parse_file(ErlFile, [{default_encoding,utf8},extra]), + latin1 = proplists:get_value(encoding, Extra3), ok. extends(Config) -> -- 2.34.1
Locations
Projects
Search
Status Monitor
Help
OpenBuildService.org
Documentation
API Documentation
Code of Conduct
Contact
Support
@OBShq
Terms
openSUSE Build Service is sponsored by
The Open Build Service is an
openSUSE project
.
Sign Up
Log In
Places
Places
All Projects
Status Monitor