File 2114-Add-an-option-to-MODULE-module_info-1-for-listing-NI.patch of Package erlang

From f5af4ec3aec18b7237c11ec6c8b7dd9367002d37 Mon Sep 17 00:00:00 2001
From: =?UTF-8?q?John=20H=C3=B6gberg?= <john@erlang.org>
Date: Wed, 21 Mar 2018 09:29:22 +0100
Subject: [PATCH 2/2] Add an option to ?MODULE:module_info/1 for listing NIFs

---
 erts/emulator/beam/atom.names            |  1 +
 erts/emulator/beam/beam_load.c           | 43 ++++++++++++++++++++++++++++++++
 erts/emulator/test/module_info_SUITE.erl | 15 +++++++++--
 erts/preloaded/src/erlang.erl            |  2 +-
 system/doc/reference_manual/modules.xml  |  6 +++++
 5 files changed, 64 insertions(+), 3 deletions(-)

diff --git a/erts/emulator/beam/atom.names b/erts/emulator/beam/atom.names
index 38b5f0c5e3..6aadde0d18 100644
--- a/erts/emulator/beam/atom.names
+++ b/erts/emulator/beam/atom.names
@@ -673,3 +673,4 @@ atom xor
 atom x86
 atom yes
 atom yield
+atom nifs
diff --git a/erts/emulator/beam/beam_load.c b/erts/emulator/beam/beam_load.c
index 0184c567f1..af620d7432 100644
--- a/erts/emulator/beam/beam_load.c
+++ b/erts/emulator/beam/beam_load.c
@@ -554,6 +554,7 @@ static Eterm get_module_info(Process* p, ErtsCodeIndex code_ix,
 static Eterm exported_from_module(Process* p, ErtsCodeIndex code_ix,
                                   Eterm mod);
 static Eterm functions_in_module(Process* p, BeamCodeHeader*);
+static Eterm nifs_in_module(Process* p, Eterm module);
 static Eterm attributes_for_module(Process* p, BeamCodeHeader*);
 static Eterm compilation_info_for_module(Process* p, BeamCodeHeader*);
 static Eterm md5_of_module(Process* p, BeamCodeHeader*);
@@ -5954,6 +5955,8 @@ get_module_info(Process* p, ErtsCodeIndex code_ix, BeamCodeHeader* code_hdr,
 	return exported_from_module(p, code_ix, module);
     } else if (what == am_functions) {
 	return functions_in_module(p, code_hdr);
+    } else if (what == am_nifs) {
+	return nifs_in_module(p, module);
     } else if (what == am_attributes) {
 	return attributes_for_module(p, code_hdr);
     } else if (what == am_compile) {
@@ -6006,6 +6009,46 @@ functions_in_module(Process* p, /* Process whose heap to use. */
     return result;
 }
 
+/*
+ * Builds a list of all NIFs in the given module:
+ *     [{Name, Arity},...]
+ */
+Eterm
+nifs_in_module(Process* p, Eterm module)
+{
+    Eterm nif_list, *hp;
+    Module *mod;
+
+    mod = erts_get_module(module, erts_active_code_ix());
+    nif_list = NIL;
+
+    if (mod->curr.nif != NULL) {
+        int func_count, func_ix;
+        ErlNifFunc *funcs;
+
+        func_count = erts_nif_get_funcs(mod->curr.nif, &funcs);
+        hp = HAlloc(p, func_count * 5);
+
+        for (func_ix = func_count - 1; func_ix >= 0; func_ix--) {
+            Eterm name, arity, pair;
+            ErlNifFunc *func;
+
+            func = &funcs[func_ix];
+
+            name = am_atom_put(func->name, sys_strlen(func->name));
+            arity = make_small(func->arity);
+
+            pair = TUPLE2(hp, name, arity);
+            hp += 3;
+
+            nif_list = CONS(hp, pair, nif_list);
+            hp += 2;
+        }
+    }
+
+    return nif_list;
+}
+
 /*
  * Returns 'true' if mod has any native compiled functions, otherwise 'false'
  */
diff --git a/erts/emulator/test/module_info_SUITE.erl b/erts/emulator/test/module_info_SUITE.erl
index 0341e63f13..46a3bba732 100644
--- a/erts/emulator/test/module_info_SUITE.erl
+++ b/erts/emulator/test/module_info_SUITE.erl
@@ -23,7 +23,7 @@
 -include_lib("common_test/include/ct.hrl").
 
 -export([all/0, suite/0,
-	 exports/1,functions/1,deleted/1,native/1,info/1]).
+	 exports/1,functions/1,deleted/1,native/1,info/1,nifs/1]).
 
 %%-compile(native).
 
@@ -38,7 +38,7 @@ all() ->
     modules().
 
 modules() ->
-    [exports, functions, deleted, native, info].
+    [exports, functions, deleted, native, info, nifs].
 
 %% Should return all functions exported from this module. (local)
 all_exported() ->
@@ -69,6 +69,17 @@ functions(Config) when is_list(Config) ->
     All = lists:sort(?MODULE:module_info(functions)),
     ok.
 
+nifs(Config) when is_list(Config) ->
+    [] = ?MODULE:module_info(nifs),
+
+    %% erl_tracer is guaranteed to be present and contain these NIFs
+    TraceNIFs = erl_tracer:module_info(nifs),
+    true = lists:member({enabled, 3}, TraceNIFs),
+    true = lists:member({trace, 5}, TraceNIFs),
+    2 = length(TraceNIFs),
+
+    ok.
+
 %% Test that deleted modules cause badarg
 deleted(Config) when is_list(Config) ->
     Data = proplists:get_value(data_dir, Config),
diff --git a/erts/preloaded/src/erlang.erl b/erts/preloaded/src/erlang.erl
index 370ecdc3f6..53d6e55310 100644
--- a/erts/preloaded/src/erlang.erl
+++ b/erts/preloaded/src/erlang.erl
@@ -1904,7 +1904,7 @@ element(_N, _Tuple) ->
 
 %% Not documented
 -type module_info_key() :: attributes | compile | exports | functions | md5
-                         | module | native | native_addresses.
+                         | module | native | native_addresses | nifs.
 -spec erlang:get_module_info(Module, Item) -> ModuleInfo when
       Module :: atom(),
       Item :: module_info_key(),
diff --git a/system/doc/reference_manual/modules.xml b/system/doc/reference_manual/modules.xml
index 4a97bfeb7b..7dc71eb307 100644
--- a/system/doc/reference_manual/modules.xml
+++ b/system/doc/reference_manual/modules.xml
@@ -307,6 +307,12 @@ behaviour_info(callbacks) -> Callbacks.</pre>
 	  all functions in the module.</p>
 	  </item>
 
+        <tag><c>nifs</c></tag>
+	  <item>
+	  <p>Returns a list of <c>{Name,Arity}</c> tuples with
+	  all NIF functions in the module.</p>
+	  </item>
+
         <tag><c>native</c></tag>
 	  <item>
 	  <p>Return <c>true</c> if the module has native compiled code.
-- 
2.16.3

openSUSE Build Service is sponsored by