Skip to content

Commit 061920d

Browse files
authored
Merge pull request #6193 from frej/frej/nif_start-for-all
compiler: Start all potential nif functions with a nif_start
2 parents f8564a1 + 724da95 commit 061920d

File tree

3 files changed

+118
-13
lines changed

3 files changed

+118
-13
lines changed

lib/compiler/src/v3_core.erl

Lines changed: 49 additions & 11 deletions
Original file line numberDiff line numberDiff line change
@@ -160,7 +160,8 @@
160160
opts=[] :: [compile:option()], %Options.
161161
dialyzer=false :: boolean(), %Help dialyzer or not.
162162
ws=[] :: [warning()], %Warnings.
163-
file=[{file,""}] %File.
163+
file=[{file,""}], %File.
164+
load_nif=false :: boolean() %true if calls erlang:load_nif/2
164165
}).
165166

166167
%% XXX: The following type declarations do not belong in this module
@@ -171,12 +172,16 @@
171172

172173
-record(imodule, {name = [],
173174
exports = ordsets:new(),
174-
nifs = sets:new([{version, 2}]),
175+
nifs = none ::
176+
'none' | sets:set(), % Is a set if the attribute is
177+
% present in the module.
175178
attrs = [],
176179
defs = [],
177180
file = [],
178181
opts = [],
179-
ws = []}).
182+
ws = [],
183+
load_nif=false :: boolean() %true if calls erlang:load_nif/2
184+
}).
180185

181186
-spec module([form()], [compile:option()]) ->
182187
{'ok',cerl:c_module(),[warning()]}.
@@ -186,19 +191,28 @@ module(Forms0, Opts) ->
186191
Module = foldl(fun (F, Acc) ->
187192
form(F, Acc, Opts)
188193
end, #imodule{}, Forms),
189-
#imodule{name=Mod,exports=Exp0,attrs=As0,defs=Kfs0,ws=Ws} = Module,
194+
#imodule{name=Mod,exports=Exp0,attrs=As0,
195+
defs=Kfs0,ws=Ws,load_nif=LoadNif,nifs=Nifs} = Module,
190196
Exp = case member(export_all, Opts) of
191197
true -> defined_functions(Forms);
192198
false -> Exp0
193199
end,
194200
Cexp = [#c_var{name=FA} || {_,_}=FA <- Exp],
201+
Kfs1 = reverse(Kfs0),
202+
Kfs = if LoadNif and (Nifs =:= none) ->
203+
insert_nif_start(Kfs1);
204+
true ->
205+
Kfs1
206+
end,
195207
As = reverse(As0),
196-
Kfs = reverse(Kfs0),
208+
197209
{ok,#c_module{name=#c_literal{val=Mod},exports=Cexp,attrs=As,defs=Kfs},Ws}.
198210

199-
form({function,_,_,_,_}=F0, #imodule{defs=Defs}=Module, Opts) ->
200-
{F,Ws} = function(F0, Module, Opts),
201-
Module#imodule{defs=[F|Defs],ws=Ws};
211+
form({function,_,_,_,_}=F0,
212+
#imodule{defs=Defs,load_nif=LoadNif0}=Module,
213+
Opts) ->
214+
{F,Ws,LoadNif} = function(F0, Module, Opts),
215+
Module#imodule{defs=[F|Defs],ws=Ws,load_nif=LoadNif or LoadNif0};
202216
form({attribute,_,module,Mod}, Module, _Opts) ->
203217
true = is_atom(Mod),
204218
Module#imodule{name=Mod};
@@ -211,7 +225,13 @@ form({attribute,_,export,Es}, #imodule{exports=Exp0}=Module, _Opts) ->
211225
Exp = ordsets:union(ordsets:from_list(Es), Exp0),
212226
Module#imodule{exports=Exp};
213227
form({attribute,_,nifs,Ns}, #imodule{nifs=Nifs0}=Module, _Opts) ->
214-
Nifs = sets:union(sets:from_list(Ns, [{version,2}]), Nifs0),
228+
Nifs1 = case Nifs0 of
229+
none ->
230+
sets:new([{version, 2}]);
231+
_ ->
232+
Nifs0
233+
end,
234+
Nifs = sets:union(sets:from_list(Ns, [{version,2}]), Nifs1),
215235
Module#imodule{nifs=Nifs};
216236
form({attribute,_,_,_}=F, #imodule{attrs=As}=Module, _Opts) ->
217237
Module#imodule{attrs=[attribute(F)|As]};
@@ -249,9 +269,9 @@ function({function,_,Name,Arity,Cs0}, Module, Opts)
249269
%% ok = function_dump(Name, Arity, "ubody:~n~p~n",[B1]),
250270
{B2,St3} = cbody(B1, Nifs, St2),
251271
%% ok = function_dump(Name, Arity, "cbody:~n~p~n",[B2]),
252-
{B3,#core{ws=Ws}} = lbody(B2, St3),
272+
{B3,#core{ws=Ws,load_nif=LoadNif}} = lbody(B2, St3),
253273
%% ok = function_dump(Name, Arity, "lbody:~n~p~n",[B3]),
254-
{{#c_var{name={Name,Arity}},B3},Ws}
274+
{{#c_var{name={Name,Arity}},B3},Ws,LoadNif}
255275
catch
256276
Class:Error:Stack ->
257277
io:fwrite("Function: ~w/~w\n", [Name,Arity]),
@@ -860,6 +880,9 @@ expr({call,L,{remote,_,M0,F0},As0}, St0) ->
860880
name=#c_literal{val=match_fail},
861881
args=[Tuple]},
862882
{Fail,Aps,St1};
883+
{#c_literal{val=erlang},#c_literal{val=load_nif},[_,_]} ->
884+
{#icall{anno=#a{anno=Anno},module=M1,name=F1,args=As1},
885+
Aps,St1#core{load_nif=true}};
863886
{_,_,_} ->
864887
{#icall{anno=#a{anno=Anno},module=M1,name=F1,args=As1},Aps,St1}
865888
end;
@@ -3031,6 +3054,9 @@ ren_is_subst(_V, []) -> no.
30313054
%% from case/receive. In subblocks/clauses the AfterVars of the block
30323055
%% are just the exported variables.
30333056

3057+
cbody(B0, none, St0) ->
3058+
{B1,_,_,St1} = cexpr(B0, [], St0),
3059+
{B1,St1};
30343060
cbody(B0, Nifs, St0) ->
30353061
{B1,_,_,St1} = cexpr(B0, [], St0),
30363062
B2 = case sets:is_element(St1#core.function,Nifs) of
@@ -3879,6 +3905,18 @@ is_simple(_) -> false.
38793905

38803906
is_simple_list(Es) -> lists:all(fun is_simple/1, Es).
38813907

3908+
insert_nif_start([VF={V,F=#c_fun{body=Body}}|Funs]) ->
3909+
case Body of
3910+
#c_seq{arg=#c_primop{name=#c_literal{val=nif_start}}} ->
3911+
[VF|insert_nif_start(Funs)];
3912+
#c_case{} ->
3913+
NifStart = #c_primop{name=#c_literal{val=nif_start},args=[]},
3914+
[{V,F#c_fun{body=#c_seq{arg=NifStart,body=Body}}}
3915+
|insert_nif_start(Funs)]
3916+
end;
3917+
insert_nif_start([]) ->
3918+
[].
3919+
38823920
%%%
38833921
%%% Handling of warnings.
38843922
%%%

lib/compiler/test/core_SUITE.erl

Lines changed: 52 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -31,7 +31,7 @@
3131
cover_v3_kernel_4/1,cover_v3_kernel_5/1,
3232
non_variable_apply/1,name_capture/1,fun_letrec_effect/1,
3333
get_map_element/1,receive_tests/1,
34-
core_lint/1]).
34+
core_lint/1,nif/1,no_nif/1,no_load_nif/1]).
3535

3636
-include_lib("common_test/include/ct.hrl").
3737

@@ -61,7 +61,7 @@ groups() ->
6161
cover_v3_kernel_4,cover_v3_kernel_5,
6262
non_variable_apply,name_capture,fun_letrec_effect,
6363
get_map_element,receive_tests,
64-
core_lint
64+
core_lint,nif,no_nif,no_load_nif
6565
]}].
6666

6767

@@ -170,3 +170,53 @@ core_lint_function(Exports, Attributes, Body) ->
170170
(_) -> true
171171
end, Errors),
172172
error = compile:forms(Mod, [from_core,clint0,report]).
173+
174+
nif(Conf) ->
175+
%% Check that only the function in the nif attribute starts with nif_start
176+
Funs =
177+
nif_compile_to_cerl(Conf, [{d,'WITH_ATTRIBUTE'},{d,'WITH_LOAD_NIF'}]),
178+
false = nif_first_instruction_is_nif_start(init, 1, Funs),
179+
true = nif_first_instruction_is_nif_start(start, 1, Funs),
180+
false = nif_first_instruction_is_nif_start(module_info, 0, Funs),
181+
false = nif_first_instruction_is_nif_start(module_info, 1, Funs),
182+
ok.
183+
184+
no_nif(Conf) ->
185+
%% Check that all functions start with nif_start
186+
Funs = nif_compile_to_cerl(Conf, [{d,'WITH_LOAD_NIF'}]),
187+
true = nif_first_instruction_is_nif_start(init, 1, Funs),
188+
true = nif_first_instruction_is_nif_start(start, 1, Funs),
189+
true = nif_first_instruction_is_nif_start(module_info, 0, Funs),
190+
true = nif_first_instruction_is_nif_start(module_info, 1, Funs),
191+
ok.
192+
193+
no_load_nif(Conf) ->
194+
%% Check that no functions start with nif_start
195+
Funs = nif_compile_to_cerl(Conf, []),
196+
false = nif_first_instruction_is_nif_start(init, 1, Funs),
197+
false = nif_first_instruction_is_nif_start(start, 1, Funs),
198+
false = nif_first_instruction_is_nif_start(module_info, 0, Funs),
199+
false = nif_first_instruction_is_nif_start(module_info, 1, Funs),
200+
ok.
201+
202+
nif_compile_to_cerl(Conf, Flags) ->
203+
Src = filename:join(proplists:get_value(data_dir, Conf), "nif.erl"),
204+
{ok, _, F} = compile:file(Src, [to_core, binary, deterministic]++Flags),
205+
Defs = cerl:module_defs(F),
206+
[ {cerl:var_name(V),cerl:fun_body(Def)} || {V,Def} <- Defs].
207+
208+
nif_first_instruction_is_nif_start(F, A, [{{F,A},Body}|_]) ->
209+
try
210+
Primop = cerl:seq_arg(Body),
211+
Name = cerl:primop_name(Primop),
212+
0 = cerl:primop_arity(Primop),
213+
nif_start = cerl:atom_val(Name),
214+
true
215+
catch
216+
error:_ ->
217+
false
218+
end;
219+
nif_first_instruction_is_nif_start(F, A, [_|Rest]) ->
220+
nif_first_instruction_is_nif_start(F, A, Rest);
221+
nif_first_instruction_is_nif_start(_, _, []) ->
222+
not_found.
Lines changed: 17 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,17 @@
1+
-module(nif).
2+
3+
-export([init/1, start/1]).
4+
5+
-ifdef(WITH_ATTRIBUTE).
6+
-nifs([start/1]).
7+
-endif.
8+
9+
-ifdef(WITH_LOAD_NIF).
10+
init(File) ->
11+
ok = erlang:load_nif(File, 0).
12+
-else.
13+
init(_File) ->
14+
ok.
15+
-endif.
16+
17+
start(_) -> erlang:nif_error(not_loaded).

0 commit comments

Comments
 (0)