File 0954-erts-Fix-down-stop-called-on-purged-NIF-module.patch of Package erlang
From 27d68f28c85bdb8368c66633a879facf1ae1fa3e Mon Sep 17 00:00:00 2001
From: Sverker Eriksson <sverker@erlang.org>
Date: Wed, 15 Jan 2020 16:49:27 +0100
Subject: [PATCH] erts: Fix down/stop called on purged NIF module
by postponing unload until all resource objects with any callbacks
(not just dtor) have been deallocated.
---
erts/emulator/beam/erl_nif.c | 21 ++++++--
erts/emulator/test/nif_SUITE.erl | 62 +++++++++++++++++++--
erts/emulator/test/nif_SUITE_data/nif_mod.c | 78 ++++++++++++++++++++++++---
erts/emulator/test/nif_SUITE_data/nif_mod.erl | 4 +-
4 files changed, 150 insertions(+), 15 deletions(-)
diff --git a/erts/emulator/beam/erl_nif.c b/erts/emulator/beam/erl_nif.c
index 1fbe362330..3d3bd4578d 100644
--- a/erts/emulator/beam/erl_nif.c
+++ b/erts/emulator/beam/erl_nif.c
@@ -2209,6 +2209,10 @@ static ErlNifResourceType* find_resource_type(Eterm module, Eterm name)
#define in_area(ptr,start,nbytes) \
((UWord)((char*)(ptr) - (char*)(start)) < (nbytes))
+static ERTS_INLINE int rt_have_callbacks(ErlNifResourceType* rt)
+{
+ return rt->dtor != NULL;
+}
static void close_lib(struct erl_module_nif* lib)
{
@@ -2231,7 +2235,7 @@ static void steal_resource_type(ErlNifResourceType* type)
{
struct erl_module_nif* lib = type->owner;
- if (type->dtor != NULL
+ if (rt_have_callbacks(type)
&& erts_refc_dectest(&lib->rt_dtor_cnt, 0) == 0
&& lib->mod == NULL) {
/* last type with destructor gone, close orphan lib */
@@ -2244,6 +2248,11 @@ static void steal_resource_type(ErlNifResourceType* type)
}
}
+static void resource_dtor_nop(ErlNifEnv* env, void* obj)
+{
+ /* do nothing */
+}
+
/* The opened_rt_list is used by enif_open_resource_type()
* in order to rollback "creates" and "take-overs" in case the load fails.
*/
@@ -2306,6 +2315,12 @@ ErlNifResourceType* open_resource_type(ErlNifEnv* env,
sys_memzero(&ort->new_callbacks, sizeof(ErlNifResourceTypeInit));
ASSERT(sizeof_init > 0 && sizeof_init <= sizeof(ErlNifResourceTypeInit));
sys_memcpy(&ort->new_callbacks, init, sizeof_init);
+ if (!ort->new_callbacks.dtor && (ort->new_callbacks.down ||
+ ort->new_callbacks.stop)) {
+ /* Set dummy dtor for fast rt_have_callbacks()
+ * This case should be rare anyway */
+ ort->new_callbacks.dtor = resource_dtor_nop;
+ }
ort->next = opened_rt_list;
opened_rt_list = ort;
}
@@ -2362,7 +2377,7 @@ static void commit_opened_resource_types(struct erl_module_nif* lib)
type->stop = ort->new_callbacks.stop;
type->down = ort->new_callbacks.down;
- if (type->dtor != NULL) {
+ if (rt_have_callbacks(type)) {
erts_refc_inc(&lib->rt_dtor_cnt, 1);
}
erts_refc_inc(&lib->rt_cnt, 1);
@@ -4413,7 +4428,7 @@ erts_unload_nif(struct erl_module_nif* lib)
rt->next = NULL;
rt->prev = NULL;
if (erts_refc_dectest(&rt->refc, 0) == 0) {
- if (rt->dtor != NULL) {
+ if (rt_have_callbacks(rt)) {
erts_refc_dec(&lib->rt_dtor_cnt, 0);
}
erts_refc_dec(&lib->rt_cnt, 0);
diff --git a/erts/emulator/test/nif_SUITE.erl b/erts/emulator/test/nif_SUITE.erl
index b824daea67..6a8f7607cd 100644
--- a/erts/emulator/test/nif_SUITE.erl
+++ b/erts/emulator/test/nif_SUITE.erl
@@ -38,6 +38,7 @@
monitor_process_b/1,
monitor_process_c/1,
monitor_process_d/1,
+ monitor_process_purge/1,
demonitor_process/1,
monitor_frenzy/1,
hipe/1,
@@ -67,6 +68,7 @@
nif_phash2/1,
nif_whereis/1, nif_whereis_parallel/1,
nif_whereis_threaded/1, nif_whereis_proxy/1,
+ id/1,
nif_ioq/1
]).
@@ -76,6 +78,9 @@
-define(is_resource, is_reference).
+-define(RT_CREATE,1).
+-define(RT_TAKEOVER,2).
+
suite() -> [{ct_hooks,[ts_install_cth]}].
all() ->
@@ -125,6 +130,7 @@ groups() ->
monitor_process_b,
monitor_process_c,
monitor_process_d,
+ monitor_process_purge,
demonitor_process]}].
@@ -823,6 +829,57 @@ monitor_process_d(Config) ->
ok.
+%% OTP-16399: Test fire resource monitor after the NIF module been purged.
+monitor_process_purge(Config) ->
+ Data = proplists:get_value(data_dir, Config),
+ File = filename:join(Data, "nif_mod"),
+ {ok,nif_mod,NifModBin} = compile:file(File, [binary,return_errors]),
+
+ monitor_process_purge_do(Config, NifModBin, resource_dtor_A),
+ erlang:garbage_collect(),
+ receive after 10 -> ok end,
+ [{{resource_dtor_A_v1,_},1,4,104},
+ {unload,1,5,105}] = nif_mod_call_history(),
+
+ %% This used to crash VM as only resources with destructor
+ %% prevented NIF lib from being unloaded.
+ monitor_process_purge_do(Config, NifModBin, null),
+ erlang:garbage_collect(),
+ receive after 10 -> ok end,
+ [{unload,1,4,104}] = nif_mod_call_history(),
+ ok.
+
+monitor_process_purge_do(Config, NifModBin, Dtor) ->
+ io:format("Test with destructor = ~p\n", [Dtor]),
+
+ {module,nif_mod} = erlang:load_module(nif_mod,NifModBin),
+
+ ok = nif_mod:load_nif_lib(Config, 1, [{resource_type, 0, ?RT_CREATE,
+ "monitor_process_purge", Dtor,
+ ?RT_CREATE, resource_down_D}
+ ]),
+ hold_nif_mod_priv_data(nif_mod:get_priv_data_ptr()),
+ [{load,1,1,101},
+ {get_priv_data_ptr,1,2,102}] = nif_mod_call_history(),
+
+ {Pid,MRef} = spawn_opt(fun() ->
+ receive
+ return -> ok
+ end
+ end,
+ [link, monitor]),
+ RBin = <<"blahblah">>,
+ R = nif_mod:make_new_resource(0, RBin),
+ 0 = nif_mod:monitor_process(0, R, Pid),
+ true = erlang:delete_module(nif_mod),
+ true = erlang:purge_module(nif_mod),
+ Pid ! return,
+ [{'DOWN', MRef, process, Pid, normal}] = flush(),
+ [{{resource_down_D_v1,RBin},1,3,103}] = nif_mod_call_history(),
+ keep_alive(R),
+ ok.
+
+
%% Test basic demonitoring
demonitor_process(Config) ->
ensure_lib_loaded(Config),
@@ -1414,10 +1471,6 @@ resource_binary_do() ->
ResInfo = get_resource(binary_resource_type,ResBin2),
ResInfo.
-
--define(RT_CREATE,1).
--define(RT_TAKEOVER,2).
-
%% Test resource takeover by module upgrade
resource_takeover(Config) when is_list(Config) ->
TmpMem = tmpmem(),
@@ -3458,6 +3511,7 @@ last_resource_dtor_call() ->
Bin.
id(I) -> I.
+keep_alive(Term) -> ?MODULE:id(Term).
%% The NIFs:
lib_version() -> undefined.
diff --git a/erts/emulator/test/nif_SUITE_data/nif_mod.c b/erts/emulator/test/nif_SUITE_data/nif_mod.c
index 885b8ebaf8..d8c1ca2a2e 100644
--- a/erts/emulator/test/nif_SUITE_data/nif_mod.c
+++ b/erts/emulator/test/nif_SUITE_data/nif_mod.c
@@ -23,6 +23,10 @@
#include "nif_mod.h"
+#if ERL_NIF_MAJOR_VERSION*100 + ERL_NIF_MINOR_VERSION >= 215
+# define HAVE_ENIF_MONITOR_PROCESS
+#endif
+
#define CHECK(X) ((void)((X) || (check_abort(__LINE__),1)))
#ifdef __GNUC__
static void check_abort(unsigned line) __attribute__((noreturn));
@@ -42,6 +46,7 @@ static ERL_NIF_TERM am_null;
static ERL_NIF_TERM am_resource_type;
static ERL_NIF_TERM am_resource_dtor_A;
static ERL_NIF_TERM am_resource_dtor_B;
+static ERL_NIF_TERM am_resource_down_D;
static ERL_NIF_TERM am_return;
static NifModPrivData* priv_data(ErlNifEnv* env)
@@ -56,6 +61,7 @@ static void init(ErlNifEnv* env)
am_resource_type = enif_make_atom(env, "resource_type");
am_resource_dtor_A = enif_make_atom(env, "resource_dtor_A");
am_resource_dtor_B = enif_make_atom(env, "resource_dtor_B");
+ am_resource_down_D = enif_make_atom(env, "resource_down_D");
am_return = enif_make_atom(env, "return");
}
@@ -107,8 +113,26 @@ static void resource_dtor_B(ErlNifEnv* env, void* a)
enif_sizeof_resource(a));
}
-/* {resource_type, Ix|null, ErlNifResourceFlags in, "TypeName", dtor(A|B|null), ErlNifResourceFlags out}*/
-static void open_resource_type(ErlNifEnv* env, const ERL_NIF_TERM* arr)
+#ifdef HAVE_ENIF_MONITOR_PROCESS
+static void resource_down_D(ErlNifEnv* env, void* a, ErlNifPid* pid, ErlNifMonitor* mon)
+{
+ const char down_name[] = "resource_down_D_v" STRINGIFY(NIF_LIB_VER);
+
+ add_call_with_arg(env, priv_data(env), down_name, (const char*)a,
+ enif_sizeof_resource(a));
+}
+#endif
+
+
+/* {resource_type,
+ Ix|null,
+ ErlNifResourceFlags in,
+ "TypeName",
+ dtor(A|B|null),
+ ErlNifResourceFlags out
+ [, down(D|null)]}
+*/
+static void open_resource_type(ErlNifEnv* env, int arity, const ERL_NIF_TERM* arr)
{
NifModPrivData* data = priv_data(env);
char rt_name[30];
@@ -132,10 +156,27 @@ static void open_resource_type(ErlNifEnv* env, const ERL_NIF_TERM* arr)
CHECK(enif_is_identical(arr[4], am_resource_dtor_B));
dtor = resource_dtor_B;
}
-
- got_ptr = enif_open_resource_type(env, NULL, rt_name, dtor,
- flags.e, &got_res.e);
-
+#ifdef HAVE_ENIF_MONITOR_PROCESS
+ if (arity == 7) {
+ ErlNifResourceTypeInit init;
+ init.dtor = dtor;
+ init.stop = NULL;
+ if (enif_is_identical(arr[6], am_null)) {
+ init.down = NULL;
+ }
+ else {
+ CHECK(enif_is_identical(arr[6], am_resource_down_D));
+ init.down = resource_down_D;
+ }
+ got_ptr = enif_open_resource_type_x(env, rt_name, &init,
+ flags.e, &got_res.e);
+ }
+ else
+#endif
+ {
+ got_ptr = enif_open_resource_type(env, NULL, rt_name, dtor,
+ flags.e, &got_res.e);
+ }
if (enif_get_uint(env, arr[1], &ix) && ix < RT_MAX && got_ptr != NULL) {
data->rt_arr[ix] = got_ptr;
}
@@ -163,7 +204,8 @@ static void do_load_info(ErlNifEnv* env, ERL_NIF_TERM load_info, int* retvalp)
CHECK(enif_get_tuple(env, head, &arity, &arr));
switch (arity) {
case 6:
- open_resource_type(env, arr);
+ case 7:
+ open_resource_type(env, arity, arr);
break;
case 2:
CHECK(arr[0] == am_return);
@@ -290,6 +332,25 @@ static ERL_NIF_TERM get_resource(ErlNifEnv* env, int argc, const ERL_NIF_TERM ar
return enif_make_binary(env, &obin);
}
+#ifdef HAVE_ENIF_MONITOR_PROCESS
+static ERL_NIF_TERM monitor_process(ErlNifEnv* env, int argc, const ERL_NIF_TERM argv[])
+{
+ NifModPrivData* data = priv_data(env);
+ ErlNifPid pid;
+ unsigned ix;
+ void* obj;
+ int ret;
+
+ if (!enif_get_uint(env, argv[0], &ix) || ix >= RT_MAX
+ || !enif_get_resource(env, argv[1], data->rt_arr[ix], &obj)
+ || !enif_get_local_pid(env, argv[2], &pid)) {
+ return enif_make_badarg(env);
+ }
+ ret = enif_monitor_process(env, obj, &pid, NULL);
+ return enif_make_int(env, ret);
+}
+#endif
+
static ErlNifFunc nif_funcs[] =
{
{"lib_version", 0, lib_version},
@@ -297,6 +358,9 @@ static ErlNifFunc nif_funcs[] =
{"get_priv_data_ptr", 0, get_priv_data_ptr},
{"make_new_resource", 2, make_new_resource},
{"get_resource", 2, get_resource}
+#ifdef HAVE_ENIF_MONITOR_PROCESS
+ ,{"monitor_process", 3, monitor_process}
+#endif
};
#if NIF_LIB_VER != 3
diff --git a/erts/emulator/test/nif_SUITE_data/nif_mod.erl b/erts/emulator/test/nif_SUITE_data/nif_mod.erl
index 8019cfcf82..f3b9dcfaf3 100644
--- a/erts/emulator/test/nif_SUITE_data/nif_mod.erl
+++ b/erts/emulator/test/nif_SUITE_data/nif_mod.erl
@@ -23,7 +23,8 @@
-include_lib("common_test/include/ct.hrl").
-export([load_nif_lib/2, load_nif_lib/3, start/0, lib_version/0,
- get_priv_data_ptr/0, make_new_resource/2, get_resource/2]).
+ get_priv_data_ptr/0, make_new_resource/2, get_resource/2,
+ monitor_process/3]).
-export([loop/0, upgrade/1]).
@@ -89,6 +90,7 @@ nif_api_version() -> %NIF
get_priv_data_ptr() -> ?nif_stub.
make_new_resource(_,_) -> ?nif_stub.
get_resource(_,_) -> ?nif_stub.
+monitor_process(_,_,_) -> ?nif_stub.
nif_stub_error(Line) ->
exit({nif_not_loaded,module,?MODULE,line,Line}).
--
2.16.4