File 2671-compiler-Start-all-potential-nif-functions-with-a-ni.patch of Package erlang
From 724da95cd04d2bc1d6cb89d1988b58b2096d59cd Mon Sep 17 00:00:00 2001
From: Frej Drejhammar <frej.drejhammar@gmail.com>
Date: Fri, 29 Jul 2022 12:06:09 +0200
Subject: [PATCH] compiler: Start all potential nif functions with a nif_start
MIME-Version: 1.0
Content-Type: text/plain; charset=UTF-8
Content-Transfer-Encoding: 8bit
Since OTP 25 the `nifs` attribute can be used to declare which
functions are nifs. When the `nifs` attribute is present, the runtime
system will ensure that only functions listed in the attribute are
replaced by a native implementation when `erlang:load_nif/2` is
called. Functions listed in the `nifs` attribute are flagged by
emitting a `nif_start` operation as the first instruction in the
function.
Due to backwards compatibility, the `nifs` attribute is not required,
so when a module containing a call to `erlang:load_nif/2` is
encountered, the compiler is forced to conservatively assume that in
such a module, all functions are potential nifs. Currently most of the
more powerful compiler optimizations (beam_ssa_opt.erl) are completely
disabled when a module contains a call to `erlang:load_nif/2`. It has
been suggested by Björn Gustavsson and Sverker Eriksson that switching
to a more fine-grained approach where only functions that are
potential nifs are excluded from, or treated as external functions,
during optimization would be an improvement.
This patch extends the v3_core-pass to make all functions start with a
`nif_start` instruction when the `nifs` attribute isn't present in the
module but a call to `erlang:load_nif/2` is. With this change, later
compiler passes can safely assume that a function not starting with a
`nif_start` instruction is not a nif regardless of the presence of a
call to `erlang:load_nif/2` in the module.
---
lib/compiler/src/v3_core.erl | 60 ++++++++++++++++++-----
lib/compiler/test/core_SUITE.erl | 54 +++++++++++++++++++-
lib/compiler/test/core_SUITE_data/nif.erl | 17 +++++++
3 files changed, 118 insertions(+), 13 deletions(-)
create mode 100644 lib/compiler/test/core_SUITE_data/nif.erl
diff --git a/lib/compiler/src/v3_core.erl b/lib/compiler/src/v3_core.erl
index 34959a5834..16b3ac340f 100644
--- a/lib/compiler/src/v3_core.erl
+++ b/lib/compiler/src/v3_core.erl
@@ -160,7 +160,8 @@
opts=[] :: [compile:option()], %Options.
dialyzer=false :: boolean(), %Help dialyzer or not.
ws=[] :: [warning()], %Warnings.
- file=[{file,""}] %File.
+ file=[{file,""}], %File.
+ load_nif=false :: boolean() %true if calls erlang:load_nif/2
}).
%% XXX: The following type declarations do not belong in this module
@@ -171,12 +172,16 @@
-record(imodule, {name = [],
exports = ordsets:new(),
- nifs = sets:new([{version, 2}]),
+ nifs = none ::
+ 'none' | sets:set(), % Is a set if the attribute is
+ % present in the module.
attrs = [],
defs = [],
file = [],
opts = [],
- ws = []}).
+ ws = [],
+ load_nif=false :: boolean() %true if calls erlang:load_nif/2
+ }).
-spec module([form()], [compile:option()]) ->
{'ok',cerl:c_module(),[warning()]}.
@@ -186,19 +191,28 @@ module(Forms0, Opts) ->
Module = foldl(fun (F, Acc) ->
form(F, Acc, Opts)
end, #imodule{}, Forms),
- #imodule{name=Mod,exports=Exp0,attrs=As0,defs=Kfs0,ws=Ws} = Module,
+ #imodule{name=Mod,exports=Exp0,attrs=As0,
+ defs=Kfs0,ws=Ws,load_nif=LoadNif,nifs=Nifs} = Module,
Exp = case member(export_all, Opts) of
true -> defined_functions(Forms);
false -> Exp0
end,
Cexp = [#c_var{name=FA} || {_,_}=FA <- Exp],
+ Kfs1 = reverse(Kfs0),
+ Kfs = if LoadNif and (Nifs =:= none) ->
+ insert_nif_start(Kfs1);
+ true ->
+ Kfs1
+ end,
As = reverse(As0),
- Kfs = reverse(Kfs0),
+
{ok,#c_module{name=#c_literal{val=Mod},exports=Cexp,attrs=As,defs=Kfs},Ws}.
-form({function,_,_,_,_}=F0, #imodule{defs=Defs}=Module, Opts) ->
- {F,Ws} = function(F0, Module, Opts),
- Module#imodule{defs=[F|Defs],ws=Ws};
+form({function,_,_,_,_}=F0,
+ #imodule{defs=Defs,load_nif=LoadNif0}=Module,
+ Opts) ->
+ {F,Ws,LoadNif} = function(F0, Module, Opts),
+ Module#imodule{defs=[F|Defs],ws=Ws,load_nif=LoadNif or LoadNif0};
form({attribute,_,module,Mod}, Module, _Opts) ->
true = is_atom(Mod),
Module#imodule{name=Mod};
@@ -211,7 +225,13 @@ form({attribute,_,export,Es}, #imodule{exports=Exp0}=Module, _Opts) ->
Exp = ordsets:union(ordsets:from_list(Es), Exp0),
Module#imodule{exports=Exp};
form({attribute,_,nifs,Ns}, #imodule{nifs=Nifs0}=Module, _Opts) ->
- Nifs = sets:union(sets:from_list(Ns, [{version,2}]), Nifs0),
+ Nifs1 = case Nifs0 of
+ none ->
+ sets:new([{version, 2}]);
+ _ ->
+ Nifs0
+ end,
+ Nifs = sets:union(sets:from_list(Ns, [{version,2}]), Nifs1),
Module#imodule{nifs=Nifs};
form({attribute,_,_,_}=F, #imodule{attrs=As}=Module, _Opts) ->
Module#imodule{attrs=[attribute(F)|As]};
@@ -249,9 +269,9 @@ function({function,_,Name,Arity,Cs0}, Module, Opts)
%% ok = function_dump(Name, Arity, "ubody:~n~p~n",[B1]),
{B2,St3} = cbody(B1, Nifs, St2),
%% ok = function_dump(Name, Arity, "cbody:~n~p~n",[B2]),
- {B3,#core{ws=Ws}} = lbody(B2, St3),
+ {B3,#core{ws=Ws,load_nif=LoadNif}} = lbody(B2, St3),
%% ok = function_dump(Name, Arity, "lbody:~n~p~n",[B3]),
- {{#c_var{name={Name,Arity}},B3},Ws}
+ {{#c_var{name={Name,Arity}},B3},Ws,LoadNif}
catch
Class:Error:Stack ->
io:fwrite("Function: ~w/~w\n", [Name,Arity]),
@@ -860,6 +880,9 @@ expr({call,L,{remote,_,M0,F0},As0}, St0) ->
name=#c_literal{val=match_fail},
args=[Tuple]},
{Fail,Aps,St1};
+ {#c_literal{val=erlang},#c_literal{val=load_nif},[_,_]} ->
+ {#icall{anno=#a{anno=Anno},module=M1,name=F1,args=As1},
+ Aps,St1#core{load_nif=true}};
{_,_,_} ->
{#icall{anno=#a{anno=Anno},module=M1,name=F1,args=As1},Aps,St1}
end;
@@ -3031,6 +3054,9 @@ ren_is_subst(_V, []) -> no.
%% from case/receive. In subblocks/clauses the AfterVars of the block
%% are just the exported variables.
+cbody(B0, none, St0) ->
+ {B1,_,_,St1} = cexpr(B0, [], St0),
+ {B1,St1};
cbody(B0, Nifs, St0) ->
{B1,_,_,St1} = cexpr(B0, [], St0),
B2 = case sets:is_element(St1#core.function,Nifs) of
@@ -3879,6 +3905,18 @@ is_simple(_) -> false.
is_simple_list(Es) -> lists:all(fun is_simple/1, Es).
+insert_nif_start([VF={V,F=#c_fun{body=Body}}|Funs]) ->
+ case Body of
+ #c_seq{arg=#c_primop{name=#c_literal{val=nif_start}}} ->
+ [VF|insert_nif_start(Funs)];
+ #c_case{} ->
+ NifStart = #c_primop{name=#c_literal{val=nif_start},args=[]},
+ [{V,F#c_fun{body=#c_seq{arg=NifStart,body=Body}}}
+ |insert_nif_start(Funs)]
+ end;
+insert_nif_start([]) ->
+ [].
+
%%%
%%% Handling of warnings.
%%%
diff --git a/lib/compiler/test/core_SUITE.erl b/lib/compiler/test/core_SUITE.erl
index a17ad9c6ad..6bc7b1442d 100644
--- a/lib/compiler/test/core_SUITE.erl
+++ b/lib/compiler/test/core_SUITE.erl
@@ -31,7 +31,7 @@
cover_v3_kernel_4/1,cover_v3_kernel_5/1,
non_variable_apply/1,name_capture/1,fun_letrec_effect/1,
get_map_element/1,receive_tests/1,
- core_lint/1]).
+ core_lint/1,nif/1,no_nif/1,no_load_nif/1]).
-include_lib("common_test/include/ct.hrl").
@@ -61,7 +61,7 @@ groups() ->
cover_v3_kernel_4,cover_v3_kernel_5,
non_variable_apply,name_capture,fun_letrec_effect,
get_map_element,receive_tests,
- core_lint
+ core_lint,nif,no_nif,no_load_nif
]}].
@@ -170,3 +170,53 @@ core_lint_function(Exports, Attributes, Body) ->
(_) -> true
end, Errors),
error = compile:forms(Mod, [from_core,clint0,report]).
+
+nif(Conf) ->
+ %% Check that only the function in the nif attribute starts with nif_start
+ Funs =
+ nif_compile_to_cerl(Conf, [{d,'WITH_ATTRIBUTE'},{d,'WITH_LOAD_NIF'}]),
+ false = nif_first_instruction_is_nif_start(init, 1, Funs),
+ true = nif_first_instruction_is_nif_start(start, 1, Funs),
+ false = nif_first_instruction_is_nif_start(module_info, 0, Funs),
+ false = nif_first_instruction_is_nif_start(module_info, 1, Funs),
+ ok.
+
+no_nif(Conf) ->
+ %% Check that all functions start with nif_start
+ Funs = nif_compile_to_cerl(Conf, [{d,'WITH_LOAD_NIF'}]),
+ true = nif_first_instruction_is_nif_start(init, 1, Funs),
+ true = nif_first_instruction_is_nif_start(start, 1, Funs),
+ true = nif_first_instruction_is_nif_start(module_info, 0, Funs),
+ true = nif_first_instruction_is_nif_start(module_info, 1, Funs),
+ ok.
+
+no_load_nif(Conf) ->
+ %% Check that no functions start with nif_start
+ Funs = nif_compile_to_cerl(Conf, []),
+ false = nif_first_instruction_is_nif_start(init, 1, Funs),
+ false = nif_first_instruction_is_nif_start(start, 1, Funs),
+ false = nif_first_instruction_is_nif_start(module_info, 0, Funs),
+ false = nif_first_instruction_is_nif_start(module_info, 1, Funs),
+ ok.
+
+nif_compile_to_cerl(Conf, Flags) ->
+ Src = filename:join(proplists:get_value(data_dir, Conf), "nif.erl"),
+ {ok, _, F} = compile:file(Src, [to_core, binary, deterministic]++Flags),
+ Defs = cerl:module_defs(F),
+ [ {cerl:var_name(V),cerl:fun_body(Def)} || {V,Def} <- Defs].
+
+nif_first_instruction_is_nif_start(F, A, [{{F,A},Body}|_]) ->
+ try
+ Primop = cerl:seq_arg(Body),
+ Name = cerl:primop_name(Primop),
+ 0 = cerl:primop_arity(Primop),
+ nif_start = cerl:atom_val(Name),
+ true
+ catch
+ error:_ ->
+ false
+ end;
+nif_first_instruction_is_nif_start(F, A, [_|Rest]) ->
+ nif_first_instruction_is_nif_start(F, A, Rest);
+nif_first_instruction_is_nif_start(_, _, []) ->
+ not_found.
diff --git a/lib/compiler/test/core_SUITE_data/nif.erl b/lib/compiler/test/core_SUITE_data/nif.erl
new file mode 100644
index 0000000000..873e20252b
--- /dev/null
+++ b/lib/compiler/test/core_SUITE_data/nif.erl
@@ -0,0 +1,17 @@
+-module(nif).
+
+-export([init/1, start/1]).
+
+-ifdef(WITH_ATTRIBUTE).
+-nifs([start/1]).
+-endif.
+
+-ifdef(WITH_LOAD_NIF).
+init(File) ->
+ ok = erlang:load_nif(File, 0).
+-else.
+init(_File) ->
+ ok.
+-endif.
+
+start(_) -> erlang:nif_error(not_loaded).
--
2.35.3