File 5411-compiler-Make-EPP-respect-deterministic.patch of Package erlang
From af9b14c25f842ac590bc23f9e9dd84a67f765e10 Mon Sep 17 00:00:00 2001
From: Tom Davies <todavies5@gmail.com>
Date: Thu, 28 Apr 2022 05:33:38 -0700
Subject: [PATCH 1/7] compiler: Make EPP respect +deterministic
Makes the EPP module use basenames rather than absolute paths for all
-file attributes / ?FILE macros when +deterministic is set. Previously,
EPP did not respect +deterministic in all scenarios, so build output
could still contain absolute paths.
---
lib/stdlib/doc/src/epp.xml | 4 ++
lib/stdlib/src/epp.erl | 43 ++++++++----
lib/stdlib/test/epp_SUITE.erl | 65 ++++++++++++++++++-
.../epp_SUITE_data/deterministic_include.erl | 6 ++
.../test/epp_SUITE_data/include/baz.hrl | 1 +
5 files changed, 103 insertions(+), 16 deletions(-)
create mode 100644 lib/stdlib/test/epp_SUITE_data/deterministic_include.erl
create mode 100644 lib/stdlib/test/epp_SUITE_data/include/baz.hrl
diff --git a/lib/stdlib/doc/src/epp.xml b/lib/stdlib/doc/src/epp.xml
index 6cd715c55c..c2c24ee34d 100644
--- a/lib/stdlib/doc/src/epp.xml
+++ b/lib/stdlib/doc/src/epp.xml
@@ -131,6 +131,10 @@
attributes inserted during preprocessing, you can do with
<c>{source_name, <anno>SourceName</anno>}</c>. If unset it will
default to the name of the opened file.</p>
+ <p>Setting <c>{deterministic, <anno>Enabled</anno>}</c> will
+ additionally reduce the file name of the implicit -file()
+ attributes inserted during preprocessing to only the basename
+ of the path.</p>
<p>If <c>extra</c> is specified in
<c><anno>Options</anno></c>, the return value is
<c>{ok, <anno>Epp</anno>, <anno>Extra</anno>}</c> instead
diff --git a/lib/stdlib/src/epp.erl b/lib/stdlib/src/epp.erl
index d642b53bf4..214eedfd1b 100644
--- a/lib/stdlib/src/epp.erl
+++ b/lib/stdlib/src/epp.erl
@@ -77,7 +77,8 @@
erl_scan_opts = [] :: [_],
features = [] :: [atom()],
else_reserved = false :: boolean(),
- fname = [] :: function_name_type()
+ fname = [] :: function_name_type(),
+ deterministic = false :: boolean()
}).
%% open(Options)
@@ -119,6 +120,7 @@ open(Name, Path, Pdm) ->
Options :: [{'default_encoding', DefEncoding :: source_encoding()} |
{'includes', IncludePath :: [DirectoryName :: file:name()]} |
{'source_name', SourceName :: file:name()} |
+ {'deterministic', Enabled :: boolean()} |
{'macros', PredefMacros :: macros()} |
{'name',FileName :: file:name()} |
{'location',StartLocation :: erl_anno:location()} |
@@ -623,6 +623,7 @@ init_server(Pid, FileName, Options, St0)
%% the default location is 1 for backwards compatibility, not {1,1}
AtLocation = proplists:get_value(location, Options, 1),
+ Deterministic = proplists:get_value(deterministic, Options, false),
St = St0#epp{delta=0, name=SourceName, name2=SourceName,
path=Path, location=AtLocation, macs=Ms1,
default_encoding=DefEncoding,
@@ -630,11 +631,12 @@ init_server(Pid, FileName, Options, St0)
[{text_fun, keep_ftr_keywords()},
{reserved_word_fun, ResWordFun}],
features = Features,
- else_reserved = ResWordFun('else')},
+ else_reserved = ResWordFun('else'),
+ deterministic = Deterministic},
From = wait_request(St),
Anno = erl_anno:new(AtLocation),
enter_file_reply(From, file_name(SourceName), Anno,
- AtLocation, code),
+ AtLocation, code, Deterministic),
wait_req_scan(St);
{error,E} ->
epp_reply(Pid, {error,E})
@@ -781,14 +785,15 @@ enter_file(NewName, Inc, From, St) ->
enter_file2(NewF, Pname, From, St0, AtLocation) ->
Anno = erl_anno:new(AtLocation),
- enter_file_reply(From, Pname, Anno, AtLocation, code),
+ enter_file_reply(From, Pname, Anno, AtLocation, code, St0#epp.deterministic),
#epp{macs = Ms0,
default_encoding = DefEncoding,
in_prefix = InPrefix,
erl_scan_opts = ScanOpts,
else_reserved = ElseReserved,
- features = Ftrs} = St0,
- Ms = Ms0#{'FILE':={none,[{string,Anno,Pname}]}},
+ features = Ftrs,
+ deterministic = Deterministic} = St0,
+ Ms = Ms0#{'FILE':={none,[{string,Anno,source_name(St0,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
%% relative to its current location (this is also how C does it); note
@@ -803,16 +808,17 @@ enter_file2(NewF, Pname, From, St0, AtLocation) ->
features = Ftrs,
erl_scan_opts = ScanOpts,
else_reserved = ElseReserved,
- default_encoding=DefEncoding}.
+ default_encoding=DefEncoding,
+ deterministic=Deterministic}.
-enter_file_reply(From, Name, LocationAnno, AtLocation, Where) ->
+enter_file_reply(From, Name, LocationAnno, AtLocation, Where, Deterministic) ->
Anno0 = erl_anno:new(AtLocation),
Anno = case Where of
code -> Anno0;
generated -> erl_anno:set_generated(true, Anno0)
end,
Rep = {ok, [{'-',Anno},{atom,Anno,file},{'(',Anno},
- {string,Anno,Name},{',',Anno},
+ {string,Anno,source_name(Deterministic,Name)},{',',Anno},
{integer,Anno,get_line(LocationAnno)},{')',LocationAnno},
{dot,Anno}]},
epp_reply(From, Rep).
@@ -848,13 +854,13 @@ leave_file(From, St) ->
Ftrs = St#epp.features,
ElseReserved = St#epp.else_reserved,
ScanOpts = St#epp.erl_scan_opts,
- Ms = Ms0#{'FILE':={none,[{string,Anno,OldName2}]}},
+ Ms = Ms0#{'FILE':={none,[{string,Anno,source_name(St,OldName2)}]}},
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),
+ enter_file_reply(From, OldName, Anno, CurrLoc, code, St#epp.deterministic),
case OldName2 =:= OldName of
true ->
ok;
@@ -862,7 +868,7 @@ leave_file(From, St) ->
NFrom = wait_request(NextSt),
OldAnno = erl_anno:new(OldLoc),
enter_file_reply(NFrom, OldName2, OldAnno,
- CurrLoc, generated)
+ CurrLoc, generated, St#epp.deterministic)
end,
wait_req_scan(NextSt);
[] ->
@@ -1450,9 +1456,9 @@ scan_file(Tokens0, Tf, From, St) ->
scan_file1([{'(',_Alp},{string,_As,Name},{',',_Ac},{integer,_Ai,Ln},{')',_Arp},
{dot,_Ad}], Tf, From, St) ->
Anno = erl_anno:new(Ln),
- enter_file_reply(From, Name, Anno, loc(Tf), generated),
+ enter_file_reply(From, Name, Anno, loc(Tf), generated, St#epp.deterministic),
Ms0 = St#epp.macs,
- Ms = Ms0#{'FILE':={none,[{string,line1(),Name}]}},
+ Ms = Ms0#{'FILE':={none,[{string,line1(),source_name(St,Name)}]}},
Locf = loc(Tf),
NewLoc = new_location(Ln, St#epp.location, Locf),
Delta = get_line(element(2, Tf))-Ln + St#epp.delta,
@@ -2071,3 +2077,12 @@ interpret_file_attr([Form0 | Forms], Delta, Fs) ->
[Form | interpret_file_attr(Forms, Delta, Fs)];
interpret_file_attr([], _Delta, _Fs) ->
[].
+
+-spec source_name(#epp{} | boolean(), file:filename_all()) -> file:filename_all().
+source_name(Deterministic, Name) when is_boolean(Deterministic) ->
+ case Deterministic of
+ true -> filename:basename(Name);
+ false -> Name
+ end;
+source_name(St, Name) ->
+ source_name(St#epp.deterministic, Name).
diff --git a/lib/stdlib/test/epp_SUITE.erl b/lib/stdlib/test/epp_SUITE.erl
index 027d6ec42a..72fd5af2cc 100644
--- a/lib/stdlib/test/epp_SUITE.erl
+++ b/lib/stdlib/test/epp_SUITE.erl
@@ -29,7 +29,8 @@
otp_8562/1, otp_8665/1, otp_8911/1, otp_10302/1, otp_10820/1,
otp_11728/1, encoding/1, extends/1, function_macro/1,
test_error/1, test_warning/1, otp_14285/1,
- test_if/1,source_name/1,otp_16978/1,otp_16824/1,scan_file/1,file_macro/1]).
+ test_if/1,source_name/1,otp_16978/1,otp_16824/1,scan_file/1,file_macro/1,
+ deterministic_include/1, nondeterministic_include/1]).
-export([epp_parse_erl_form/2]).
@@ -50,6 +51,7 @@ config(data_dir, _) ->
filename:absname("./epp_SUITE_data").
-else.
-include_lib("common_test/include/ct.hrl").
+-include_lib("stdlib/include/assert.hrl").
-export([init_per_testcase/2, end_per_testcase/2]).
init_per_testcase(_, Config) ->
@@ -70,7 +72,8 @@ all() ->
overload_mac, otp_8388, otp_8470, otp_8562,
otp_8665, otp_8911, otp_10302, otp_10820, otp_11728,
encoding, extends, function_macro, test_error, test_warning,
- otp_14285, test_if, source_name, otp_16978, otp_16824, scan_file, file_macro].
+ otp_14285, test_if, source_name, otp_16978, otp_16824, scan_file, file_macro,
+ deterministic_include, nondeterministic_include].
groups() ->
[{upcase_mac, [], [upcase_mac_1, upcase_mac_2]},
@@ -124,6 +127,64 @@ file_macro(Config) when is_list(Config) ->
"Other source" = FileA = FileB,
ok.
+deterministic_include(Config) when is_list(Config) ->
+ DataDir = proplists:get_value(data_dir, Config),
+ File = filename:join(DataDir, "deterministic_include.erl"),
+ {ok, List} = epp:parse_file(File, [{includes, [DataDir]},
+ {deterministic, true},
+ {source_name, "deterministic_include.erl"}]),
+
+ %% In deterministic mode, only basenames, rather than full paths, should
+ %% be written to the -file() attributes resulting from -include and -include_lib
+ ?assert(lists:any(fun
+ ({attribute,_Anno,file,{"baz.hrl",_Line}}) -> true;
+ (_) -> false
+ end,
+ List),
+ "Expected a basename in the -file attribute resulting from " ++
+ "including baz.hrl in deterministic mode."),
+ ?assert(lists:any(fun
+ ({attribute,_Anno,file,{"file.hrl",_Line}}) -> true;
+ (_) -> false
+ end,
+ List),
+ "Expected a basename in the -file attribute resulting from " ++
+ "including file.hrl in deterministic mode."),
+ ok.
+
+nondeterministic_include(Config) when is_list(Config) ->
+ DataDir = proplists:get_value(data_dir, Config),
+ File = filename:join(DataDir, "deterministic_include.erl"),
+ {ok, List} = epp:parse_file(File, [{includes, [DataDir]},
+ {source_name, "deterministic_include.erl"}]),
+
+ %% Outside of deterministic mode, full paths, should be written to
+ %% the -file() attributes resulting from -include and -include_lib
+ %% to make debugging easier.
+ %% We don't try to assume what the full absolute path will be in the
+ %% unit test, since that can depend on the environment and how the
+ %% test is executed. Instead, we just look for whether there is
+ %% the parent directory along with the basename at least.
+ IncludeAbsolutePathSuffix = filename:join("include","baz.hrl"),
+ ?assert(lists:any(fun
+ ({attribute,_Anno,file,{IncludePath,_Line}}) ->
+ lists:suffix(IncludeAbsolutePathSuffix,IncludePath);
+ (_) -> false
+ end,
+ List),
+ "Expected an absolute in the -file attribute resulting from " ++
+ "including baz.hrl outside of deterministic mode."),
+ IncludeLibAbsolutePathSuffix = filename:join("include","file.hrl"),
+ ?assert(lists:any(fun
+ ({attribute,_Anno,file,{IncludePath,_line}}) ->
+ lists:suffix(IncludeLibAbsolutePathSuffix,IncludePath);
+ (_) -> false
+ end,
+ List),
+ "Expected an absolute in the -file attribute resulting from " ++
+ "including file.hrl outside of deterministic mode."),
+ ok.
+
%%% Here is a little reimplementation of epp:parse_file, which times out
%%% after 4 seconds if the epp server doesn't respond. If we use the
%%% regular epp:parse_file, the test case will time out, and then epp
diff --git a/lib/stdlib/test/epp_SUITE_data/deterministic_include.erl b/lib/stdlib/test/epp_SUITE_data/deterministic_include.erl
new file mode 100644
index 0000000000..67763b29a0
--- /dev/null
+++ b/lib/stdlib/test/epp_SUITE_data/deterministic_include.erl
@@ -0,0 +1,6 @@
+-module(deterministic_include).
+
+-export([]).
+
+-include("include/baz.hrl").
+-include_lib("kernel/include/file.hrl").
diff --git a/lib/stdlib/test/epp_SUITE_data/include/baz.hrl b/lib/stdlib/test/epp_SUITE_data/include/baz.hrl
new file mode 100644
index 0000000000..c0ef7a6e51
--- /dev/null
+++ b/lib/stdlib/test/epp_SUITE_data/include/baz.hrl
@@ -0,0 +1 @@
+-define(BAZ, true).
--
2.35.3