File 2812-parsetools-Let-Yecc-recognize-ERL_COMPILER_OPTIONS.patch of Package erlang
From d84a181c880a4700562b5f4d5521559833ed2955 Mon Sep 17 00:00:00 2001
From: Hans Bolinder <hasse@erlang.org>
Date: Tue, 24 Nov 2020 08:00:38 +0100
Subject: [PATCH 2/3] parsetools: Let Yecc recognize ERL_COMPILER_OPTIONS
---
lib/parsetools/doc/src/yecc.xml | 16 +++
lib/parsetools/src/yecc.erl | 157 ++++++++++++++++++-----------
lib/parsetools/test/yecc_SUITE.erl | 31 +++++-
3 files changed, 141 insertions(+), 63 deletions(-)
diff --git a/lib/parsetools/doc/src/yecc.xml b/lib/parsetools/doc/src/yecc.xml
index 19438c3b5f..74fe22a7a5 100644
--- a/lib/parsetools/doc/src/yecc.xml
+++ b/lib/parsetools/doc/src/yecc.xml
@@ -155,6 +155,22 @@
</func>
</funcs>
+ <section>
+ <title>Default Yecc Options</title>
+ <p>The (host operating system) environment variable
+ <c>ERL_COMPILER_OPTIONS</c> can be used to give default Yecc
+ options. Its value must be a valid Erlang term. If the value is a
+ list, it is used as is. If it is not a list, it is put
+ into a list.</p>
+
+ <p>The list is appended to any options given to
+ <seemfa marker="#file/2">file/2</seemfa>.</p>
+
+ <p>The list can be retrieved with
+ <seemfa marker="compiler:compile#env_compiler_options/0">
+ compile:env_compiler_options/0</seemfa>.</p>
+ </section>
+
<section>
<title>Pre-Processing</title>
<p>A <c>scanner</c> to pre-process the text (program, etc.) to be
diff --git a/lib/parsetools/src/yecc.erl b/lib/parsetools/src/yecc.erl
index 6e132c7660..55bc8a20d4 100644
--- a/lib/parsetools/src/yecc.erl
+++ b/lib/parsetools/src/yecc.erl
@@ -1,7 +1,7 @@
%%
%% %CopyrightBegin%
%%
-%% Copyright Ericsson AB 1996-2018. All Rights Reserved.
+%% Copyright Ericsson AB 1996-2020. 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.
@@ -268,11 +268,14 @@ file(GrammarFile) ->
| 'return_errors' | 'return_warnings' | 'return'
| 'verbose' | 'warnings_as_errors'.
-file(File, Options) ->
+file(File, Options0) when is_list(Options0) ->
case is_filename(File) of
- no -> erlang:error(badarg, [File, Options]);
+ no -> erlang:error(badarg, [File, Options0]);
_ -> ok
end,
+ EnvOpts0 = env_default_opts(),
+ EnvOpts = select_recognized_opts(EnvOpts0),
+ Options = Options0 ++ EnvOpts,
case options(Options) of
badarg ->
erlang:error(badarg, [File, Options]);
@@ -286,7 +289,9 @@ file(File, Options) ->
process_flag(trap_exit, Flag),
Rep
end
- end.
+ end;
+file(File, Option) ->
+ file(File, [Option]).
%% Kept for backward compatibility.
yecc(Infile, Outfile) ->
@@ -311,84 +316,114 @@ yecc(Infilex, Outfilex, Verbose, Includefilex) ->
%%% Local functions
%%%
-options(Options0) when is_list(Options0) ->
- try
- Options = flatmap(fun(return) -> short_option(return, true);
- (report) -> short_option(report, true);
- ({return,T}) -> short_option(return, T);
- ({report,T}) -> short_option(report, T);
- (T) -> [T]
- end, Options0),
- options(Options, [file_attributes, includefile, parserfile,
- report_errors, report_warnings, warnings_as_errors,
- return_errors, return_warnings, time, verbose], [])
- catch error: _ -> badarg
- end;
-options(Option) ->
- options([Option]).
-
-short_option(return, T) ->
- [{return_errors,T}, {return_warnings,T}];
-short_option(report, T) ->
- [{report_errors,T}, {report_warnings,T}].
-
-options(Options0, [Key | Keys], L) when is_list(Options0) ->
- Options = case member(Key, Options0) of
- true ->
- [atom_option(Key) | delete(Key, Options0)];
- false ->
- Options0
- end,
- V = case lists:keyfind(Key, 1, Options) of
- {Key, Filename0} when Key =:= includefile;
- Key =:= parserfile ->
- case is_filename(Filename0) of
- no ->
- badarg;
- Filename ->
- {ok, [{Key, Filename}]}
- end;
- {Key, Bool} = KB when is_boolean(Bool) ->
- {ok, [KB]};
- {Key, _} ->
- badarg;
- false ->
- {ok, [{Key, default_option(Key)}]}
- end,
- case V of
+%% Copied from compile.erl.
+env_default_opts() ->
+ Key = "ERL_COMPILER_OPTIONS",
+ case os:getenv(Key) of
+ false -> [];
+ Str when is_list(Str) ->
+ case erl_scan:string(Str) of
+ {ok,Tokens,_} ->
+ Dot = {dot, erl_anno:new(1)},
+ case erl_parse:parse_term(Tokens ++ [Dot]) of
+ {ok,List} when is_list(List) -> List;
+ {ok,Term} -> [Term];
+ {error,_Reason} ->
+ io:format("Ignoring bad term in ~s\n", [Key]),
+ []
+ end;
+ {error, {_,_,_Reason}, _} ->
+ io:format("Ignoring bad term in ~s\n", [Key]),
+ []
+ end
+ end.
+
+select_recognized_opts(Options0) ->
+ Options = preprocess_options(Options0),
+ AllOptions = all_options(),
+ [Option ||
+ {Name, _} = Option <- Options,
+ lists:member(Name, AllOptions)].
+
+options(Options0) ->
+ Options1 = preprocess_options(Options0),
+ AllOptions = all_options(),
+ case check_options(Options1, AllOptions, []) of
badarg ->
badarg;
- {ok, KeyValueL} ->
- NewOptions = keydelete(Key, 1, Options),
- options(NewOptions, Keys, KeyValueL ++ L)
+ OptionValues ->
+ AllOptionValues =
+ [case lists:keyfind(Option, 1, OptionValues) of
+ false ->
+ {Option, default_option(Option)};
+ OptionValue ->
+ OptionValue
+ end || Option <- AllOptions],
+ foldr(fun({_, false}, L) -> L;
+ ({Option, true}, L) -> [Option | L];
+ (OptionValue, L) -> [OptionValue | L]
+ end, [], AllOptionValues)
+ end.
+
+preprocess_options(Options) ->
+ foldr(fun preproc_opt/2, [], Options).
+
+preproc_opt(return, Os) ->
+ [{return_errors, true}, {return_warnings, true} | Os];
+preproc_opt(report, Os) ->
+ [{report_errors, true}, {report_warnings, true} | Os];
+preproc_opt({return, T}, Os) ->
+ [{return_errors, T}, {return_warnings, T} | Os];
+preproc_opt({report, T}, Os) ->
+ [{report_errors, T}, {report_warnings, T} | Os];
+preproc_opt(Option, Os) ->
+ [try atom_option(Option) catch error:_ -> Option end | Os].
+
+check_options([{Option, FileName0} | Options], AllOptions, L)
+ when Option =:= includefile; Option =:= parserfile ->
+ case is_filename(FileName0) of
+ no ->
+ badarg;
+ Filename ->
+ check_options(Options, AllOptions, [{Option, Filename} | L])
end;
-options([], [], L) ->
- foldl(fun({_,false}, A) -> A;
- ({Tag,true}, A) -> [Tag | A];
- (F, A) -> [F | A]
- end, [], L);
-options(_Options, _, _L) ->
+check_options([{Option, Boolean} | Options], AllOptions, L)
+ when is_boolean(Boolean) ->
+ case lists:member(Option, AllOptions) of
+ true ->
+ check_options(Options, AllOptions, [{Option, Boolean} | L]);
+ false ->
+ badarg
+ end;
+check_options([], _AllOptions, L) ->
+ L;
+check_options(_Options, _, _L) ->
badarg.
+all_options() ->
+ [file_attributes, includefile, parserfile, report_errors,
+ report_warnings, return_errors, return_warnings, time, verbose,
+ warnings_as_errors].
+
default_option(file_attributes) -> true;
default_option(includefile) -> [];
default_option(parserfile) -> [];
default_option(report_errors) -> true;
default_option(report_warnings) -> true;
-default_option(warnings_as_errors) -> false;
default_option(return_errors) -> false;
default_option(return_warnings) -> false;
default_option(time) -> false;
-default_option(verbose) -> false.
+default_option(verbose) -> false;
+default_option(warnings_as_errors) -> false.
atom_option(file_attributes) -> {file_attributes, true};
atom_option(report_errors) -> {report_errors, true};
atom_option(report_warnings) -> {report_warnings, true};
-atom_option(warnings_as_errors) -> {warnings_as_errors,true};
atom_option(return_errors) -> {return_errors, true};
atom_option(return_warnings) -> {return_warnings, true};
atom_option(time) -> {time, true};
atom_option(verbose) -> {verbose, true};
+atom_option(warnings_as_errors) -> {warnings_as_errors, true};
atom_option(Key) -> Key.
is_filename(T) ->
diff --git a/lib/parsetools/test/yecc_SUITE.erl b/lib/parsetools/test/yecc_SUITE.erl
index c9df46f407..4b0f4d81d1 100644
--- a/lib/parsetools/test/yecc_SUITE.erl
+++ b/lib/parsetools/test/yecc_SUITE.erl
@@ -49,7 +49,7 @@
otp_5369/1, otp_6362/1, otp_7945/1, otp_8483/1, otp_8486/1,
otp_7292/1, otp_7969/1, otp_8919/1, otp_10302/1, otp_11269/1,
- otp_11286/1, otp_14285/1, otp_17535/1]).
+ otp_11286/1, otp_14285/1, otp_17023/1, otp_17535/1]).
% Default timetrap timeout (set in init_per_testcase).
-define(default_timeout, ?t:minutes(1)).
@@ -77,7 +77,7 @@ groups() ->
{bugs, [],
[otp_5369, otp_6362, otp_7945, otp_8483, otp_8486, otp_17535]},
{improvements, [], [otp_7292, otp_7969, otp_8919, otp_10302,
- otp_11269, otp_11286, otp_14285]}].
+ otp_11269, otp_11286, otp_14285, otp_17023]}].
init_per_suite(Config) ->
Config.
@@ -2156,6 +2156,33 @@ otp_14285(Config) ->
{ok, _, []} = compile:file(ErlFile, [return]),
ok.
+otp_17023(Config) ->
+ Dir = ?privdir,
+ Filename = filename:join(Dir, "file.yrl"),
+ Ret = [return, {report, true}],
+
+ {'EXIT', {badarg, _}} = (catch yecc:file(Filename, [{noopt,true}])),
+ OldEnv = os:getenv("ERL_COMPILER_OPTIONS"),
+ true = os:putenv("ERL_COMPILER_OPTIONS", "strong_validation"),
+ ok = file:write_file(Filename,<<"
+ Nonterminals nt.
+ Terminals t.
+ Rootsymbol nt.
+ nt -> t : '$2'.
+ ">>),
+ {error,[{_,[{5,yecc,{undefined_pseudo_variable,'$2'}}]}],[]} =
+ yecc:file(Filename, Ret),
+ true = os:putenv("ERL_COMPILER_OPTIONS", "{return, false}"),
+ error = yecc:file(Filename, Ret),
+ error = yecc:file(Filename, [return | Ret]), % overridden
+ case OldEnv of
+ false ->
+ os:unsetenv("ERL_COMPILER_OPTIONS");
+ _ ->
+ os:putenv("ERL_COMPILER_OPTIONS", OldEnv)
+ end,
+ ok.
+
start_node(Name, Args) ->
[_,Host] = string:tokens(atom_to_list(node()), "@"),
ct:log("Trying to start ~w@~s~n", [Name,Host]),
--
2.26.2