File 4731-stdlib-Warn-when-inlining-is-enabled-in-NIF-modules.patch of Package erlang
From ebc85d1c6b96b4071fc4e9045ba08ef1721bcf30 Mon Sep 17 00:00:00 2001
From: =?UTF-8?q?John=20H=C3=B6gberg?= <john@erlang.org>
Date: Mon, 9 Mar 2020 10:16:46 +0100
Subject: [PATCH] stdlib: Warn when inlining is enabled in NIF modules
---
lib/compiler/doc/src/compile.xml | 8 ++++++++
lib/stdlib/src/erl_lint.erl | 35 +++++++++++++++++++++++++++++++++--
lib/stdlib/test/erl_lint_SUITE.erl | 23 +++++++++++++++++++++--
3 files changed, 62 insertions(+), 4 deletions(-)
diff --git a/lib/compiler/doc/src/compile.xml b/lib/compiler/doc/src/compile.xml
index 549b1049d8..24c574a417 100644
--- a/lib/compiler/doc/src/compile.xml
+++ b/lib/compiler/doc/src/compile.xml
@@ -678,6 +678,14 @@ module.beam: module.erl \
emit warnings for unused locally defined record types.</p>
</item>
+ <tag><c>nowarn_nif_inline</c></tag>
+ <item>
+ <p>By default, warnings are emitted when inlining is enabled in
+ a module that may load NIFs, as the compiler may inline NIF
+ fallbacks by accident. Use this option to turn off this kind of
+ warnings.</p>
+ </item>
+
<tag><c>warn_missing_spec</c></tag>
<item>
<p>By default, warnings are not emitted when a specification
diff --git a/lib/stdlib/src/erl_lint.erl b/lib/stdlib/src/erl_lint.erl
index fee0a1bf05..14b6c4ccb9 100644
--- a/lib/stdlib/src/erl_lint.erl
+++ b/lib/stdlib/src/erl_lint.erl
@@ -31,7 +31,10 @@
-export([is_guard_expr/1]).
-export([bool_option/4,value_option/3,value_option/7]).
--import(lists, [member/2,map/2,foldl/3,foldr/3,mapfoldl/3,all/2,reverse/1]).
+-import(lists, [all/2,any/2,
+ foldl/3,foldr/3,
+ map/2,mapfoldl/3,member/2,
+ reverse/1]).
%% bool_option(OnOpt, OffOpt, Default, Options) -> boolean().
%% value_option(Flag, Default, Options) -> Value.
@@ -206,6 +209,9 @@ format_error({bad_on_load_arity,{F,A}}) ->
io_lib:format("function ~tw/~w has wrong arity (must be 0)", [F,A]);
format_error({undefined_on_load,{F,A}}) ->
io_lib:format("function ~tw/~w undefined", [F,A]);
+format_error(nif_inline) ->
+ "inlining is enabled - local calls to NIFs may call their Erlang "
+ "implementation instead";
format_error(export_all) ->
"export_all flag enabled - all functions will be exported";
@@ -595,6 +601,9 @@ start(File, Opts) ->
false, Opts)},
{removed,
bool_option(warn_removed, nowarn_removed,
+ true, Opts)},
+ {nif_inline,
+ bool_option(warn_nif_inline, nowarn_nif_inline,
true, Opts)}
],
Enabled1 = [Category || {Category,true} <- Enabled0],
@@ -3858,7 +3867,29 @@ has_wildcard_field([]) -> false.
check_remote_function(Line, M, F, As, St0) ->
St1 = deprecated_function(Line, M, F, As, St0),
St2 = check_qlc_hrl(Line, M, F, As, St1),
- format_function(Line, M, F, As, St2).
+ St3 = check_load_nif(Line, M, F, As, St2),
+ format_function(Line, M, F, As, St3).
+
+%% check_load_nif(Line, ModName, FuncName, [Arg], State) -> State
+%% Add warning if erlang:load_nif/2 is called when any kind of inlining has
+%% been enabled.
+check_load_nif(Line, erlang, load_nif, [_, _], St) ->
+ case is_warn_enabled(nif_inline, St) of
+ true -> check_nif_inline(Line, St);
+ false -> St
+ end;
+check_load_nif(_Line, _ModName, _FuncName, _Args, St) ->
+ St.
+
+check_nif_inline(Line, St) ->
+ case any(fun is_inline_opt/1, St#lint.compile) of
+ true -> add_warning(Line, nif_inline, St);
+ false -> St
+ end.
+
+is_inline_opt({inline, [_|_]=_FAs}) -> true;
+is_inline_opt(inline) -> true;
+is_inline_opt(_) -> false.
%% check_qlc_hrl(Line, ModName, FuncName, [Arg], State) -> State
%% Add warning if qlc:q/1,2 has been called but qlc.hrl has not
diff --git a/lib/stdlib/test/erl_lint_SUITE.erl b/lib/stdlib/test/erl_lint_SUITE.erl
index 92667bf6e5..aa941e61b6 100644
--- a/lib/stdlib/test/erl_lint_SUITE.erl
+++ b/lib/stdlib/test/erl_lint_SUITE.erl
@@ -70,7 +70,8 @@
otp_14285/1, otp_14378/1,
external_funs/1,otp_15563/1,
unused_type/1,removed/1, otp_16516/1,
- warn_missing_spec/1]).
+ inline_nifs/1,
+ warn_missing_spec/1].
suite() ->
[{ct_hooks,[ts_install_cth]},
@@ -93,7 +94,7 @@ all() ->
record_errors, otp_11879_cont, non_latin1_module, otp_14323,
stacktrace_syntax, otp_14285, otp_14378, external_funs,
otp_15563, unused_type, removed, otp_16516,
- warn_missing_spec].
+ inline_nifs, warn_missing_spec].
groups() ->
[{unused_vars_warn, [],
@@ -4367,6 +4368,23 @@ several_multi_inits(Config) ->
[] = run(Config, Ts),
ok.
+inline_nifs(Config) ->
+ Ts = [{implicit_inline,
+ <<"-compile(inline).
+ t() -> erlang:load_nif([], []).
+ gurka() -> ok.
+ ">>,
+ [],
+ {warnings,[{2,erl_lint,nif_inline}]}},
+ {explicit_inline,
+ <<"-compile({inline, [gurka/0]}).
+ t() -> erlang:load_nif([], []).
+ gurka() -> ok.
+ ">>,
+ [],
+ {warnings,[{2,erl_lint,nif_inline}]}}],
+ [] = run(Config, Ts).
+
warn_missing_spec(Config) ->
Test = <<"-export([external_with_spec/0, external_no_spec/0]).
--
2.16.4