File 2591-Make-compiler-accept-abstract-format-as-input.patch of Package erlang
From 7d0ca9bbaefebeb4a86c454b3b2f54dddbdfb44f Mon Sep 17 00:00:00 2001
From: Richard Carlsson <carlsson.richard@gmail.com>
Date: Mon, 1 Feb 2021 12:59:41 +0100
Subject: [PATCH] Make compiler accept abstract format as input
---
lib/compiler/doc/src/compile.xml | 23 +++++++++-
lib/compiler/src/compile.erl | 72 +++++++++++++++++++++++++-------
lib/stdlib/src/erl_compile.erl | 1 +
3 files changed, 80 insertions(+), 16 deletions(-)
diff --git a/lib/compiler/doc/src/compile.xml b/lib/compiler/doc/src/compile.xml
index 467f01b9d8..5f22bfb100 100644
--- a/lib/compiler/doc/src/compile.xml
+++ b/lib/compiler/doc/src/compile.xml
@@ -437,6 +437,14 @@ module.beam: module.erl \
parsed code before the code is checked for errors.</p>
</item>
+ <tag><c>from_abstr</c></tag>
+ <item>
+ <p>The input file is expected to contain Erlang terms representing
+ forms in abstract format (default file suffix ".abstr"). Note
+ that the format of such terms can change between releases.</p>
+ <p>See also the <c>no_lint</c> option.</p>
+ </item>
+
<tag><c>from_asm</c></tag>
<item>
<p>The input file is expected to be assembler code (default
@@ -512,13 +520,26 @@ module.beam: module.erl \
</item>
<tag><c>no_line_info</c></tag>
-
<item>
<p>Omits line number information to produce a slightly
smaller output file.
</p>
</item>
+ <tag><c>no_lint</c></tag>
+ <item>
+ <p>Skips the pass that checks for errors and warnings. Only
+ applicable together with the <c>from_abstr</c> option. This is
+ mainly for implementations of other languages on top of Erlang,
+ which have already done their own checks to guarantee
+ correctness of the code.</p>
+ <p>Caveat: When this option is used, there are no guarantees
+ that the code output by the compiler is correct and safe to
+ use. The responsibility for correctness lies on the code or
+ person generating the abstract format. If the code contains
+ errors, the compiler may crash or produce unsafe code.</p>
+ </item>
+
<tag><c>{extra_chunks, [{binary(), binary()}]}</c></tag>
<item>
<p>Pass extra chunks to be stored in the <c>.beam</c> file.
diff --git a/lib/compiler/src/compile.erl b/lib/compiler/src/compile.erl
index 4fec417c6e..14a275d871 100644
--- a/lib/compiler/src/compile.erl
+++ b/lib/compiler/src/compile.erl
@@ -29,7 +29,7 @@
-export([env_compiler_options/0]).
%% Erlc interface.
--export([compile/3,compile_beam/3,compile_asm/3,compile_core/3]).
+-export([compile/3,compile_beam/3,compile_asm/3,compile_core/3,compile_abstr/3]).
%% Utility functions for compiler passes.
-export([run_sub_passes/2]).
@@ -606,6 +606,8 @@ passes_1([Opt|Opts]) ->
passes_1([]) ->
{".erl",[?pass(parse_module)|standard_passes()]}.
+pass(from_abstr) ->
+ {".abstr", [?pass(consult_abstr) | abstr_passes(non_verified_abstr)]};
pass(from_core) ->
{".core",[?pass(parse_core)|core_passes(non_verified_core)]};
pass(from_asm) ->
@@ -616,6 +618,8 @@ pass(_) -> none.
%% that retrieves the module name. The module name is needed for
%% proper diagnostics and for compilation to native code.
+fix_first_pass([{consult_abstr, _} | Passes]) ->
+ [?pass(get_module_name_from_abstr) | Passes];
fix_first_pass([{parse_core,_}|Passes]) ->
[?pass(get_module_name_from_core)|Passes];
fix_first_pass([{beam_consult_asm,_}|Passes]) ->
@@ -787,25 +791,33 @@ standard_passes() ->
{iff,'dpp',{listing,"pp"}},
?pass(lint_module),
- %% Add all -compile() directives to #compile.options
- ?pass(compile_directives),
-
{iff,'P',{src_listing,"P"}},
{iff,'to_pp',{done,"P"}},
- {iff,'dabstr',{listing,"abstr"}},
- {delay,[{iff,debug_info,?pass(save_abstract_code)}]},
+ {iff,'dabstr',{listing,"abstr"}}
+ | abstr_passes(verified_abstr)].
+
+abstr_passes(AbstrStatus) ->
+ case AbstrStatus of
+ non_verified_abstr -> [{unless, no_lint, ?pass(lint_module)}];
+ verified_abstr -> []
+ end ++
+ [
+ %% Add all -compile() directives to #compile.options
+ ?pass(compile_directives),
+
+ {delay,[{iff,debug_info,?pass(save_abstract_code)}]},
- ?pass(expand_records),
- {iff,'dexp',{listing,"expand"}},
- {iff,'E',{src_listing,"E"}},
- {iff,'to_exp',{done,"E"}},
+ ?pass(expand_records),
+ {iff,'dexp',{listing,"expand"}},
+ {iff,'E',{src_listing,"E"}},
+ {iff,'to_exp',{done,"E"}},
- %% Conversion to Core Erlang.
- ?pass(core),
- {iff,'dcore',{listing,"core"}},
- {iff,'to_core0',{done,"core"}}
- | core_passes(verified_core)].
+ %% Conversion to Core Erlang.
+ ?pass(core),
+ {iff,'dcore',{listing,"core"}},
+ {iff,'to_core0',{done,"core"}}
+ | core_passes(verified_core)].
core_passes(CoreStatus) ->
%% Optimization and transforms of Core Erlang code.
@@ -1066,6 +1078,25 @@ find_invalid_unicode([H|T], File0) ->
end;
find_invalid_unicode([], _) -> none.
+consult_abstr(_Code, St) ->
+ case file:consult(St#compile.ifile) of
+ {ok,Forms} ->
+ Encoding = epp:read_encoding(St#compile.ifile),
+ {ok,Forms,St#compile{encoding=Encoding}};
+ {error,E} ->
+ Es = [{St#compile.ifile,[{none,?MODULE,{open,E}}]}],
+ {error,St#compile{errors=St#compile.errors ++ Es}}
+ end.
+
+get_module_name_from_abstr(Forms, St) ->
+ try get_module(Forms) of
+ Mod -> {ok, Forms, St#compile{module = Mod}}
+ catch
+ _:_ ->
+ %% Missing module declaration. Let it crash in a later pass.
+ {ok, Forms, St}
+ end.
+
parse_core(_Code, St) ->
case file:read_file(St#compile.ifile) of
{ok,Bin} ->
@@ -1579,6 +1610,8 @@ keep_compile_option(from_asm, _Deterministic) ->
false;
keep_compile_option(from_core, _Deterministic) ->
false;
+keep_compile_option(from_abstr, _Deterministic) ->
+ false;
%% Parse transform and macros have already been applied.
keep_compile_option({parse_transform, _}, _Deterministic) ->
false;
@@ -1996,6 +2029,15 @@ compile_core(File0, _OutFile, Opts) ->
Other -> Other
end.
+-spec compile_abstr(file:filename(), _, #options{}) -> 'ok' | 'error'.
+
+compile_abstr(File0, _OutFile, Opts) ->
+ File = shorten_filename(File0),
+ case file(File, [from_abstr|make_erl_options(Opts)]) of
+ {ok,_Mod} -> ok;
+ Other -> Other
+ end.
+
shorten_filename(Name0) ->
{ok,Cwd} = file:get_cwd(),
case lists:prefix(Cwd, Name0) of
diff --git a/lib/stdlib/src/erl_compile.erl b/lib/stdlib/src/erl_compile.erl
index 920d26f731..f072bcc6eb 100644
--- a/lib/stdlib/src/erl_compile.erl
+++ b/lib/stdlib/src/erl_compile.erl
@@ -30,6 +30,7 @@
compiler(".erl") -> {compile, compile};
compiler(".S") -> {compile, compile_asm};
+compiler(".abstr") -> {compile, compile_abstr};
compiler(".beam") -> {compile, compile_beam};
compiler(".core") -> {compile, compile_core};
compiler(".mib") -> {snmpc, compile};
--
2.26.2