File 0176-erts-Schedule-resource-destructors-always.patch of Package erlang

From 7a0a52a9a1adc8f87365936f4e76739b7850f1b3 Mon Sep 17 00:00:00 2001
From: Sverker Eriksson <sverker@erlang.org>
Date: Tue, 12 Mar 2019 14:56:20 +0100
Subject: [PATCH 1/3] erts: Schedule resource destructors always

to run user NIF code in a more known execution context.

Fixes problems like user calling enif_whereis_pid() in destructor
which may need to release process main lock in order to lock reg_tab.
---
 erts/emulator/beam/erl_bif_info.c             | 23 +++++++++----------
 erts/emulator/beam/erl_binary.h               | 11 +++++++--
 erts/emulator/beam/erl_nif.c                  | 28 ++++++++++++++++++-----
 erts/emulator/beam/erl_process.c              | 32 ++++++++++++++++++---------
 erts/emulator/beam/erl_process.h              |  1 +
 erts/emulator/test/nif_SUITE.erl              | 17 ++++++++++++--
 erts/emulator/test/nif_SUITE_data/nif_SUITE.c |  4 ++--
 7 files changed, 82 insertions(+), 34 deletions(-)

diff --git a/erts/emulator/beam/erl_bif_info.c b/erts/emulator/beam/erl_bif_info.c
index 16c06766fb..83f98461a1 100644
--- a/erts/emulator/beam/erl_bif_info.c
+++ b/erts/emulator/beam/erl_bif_info.c
@@ -4596,18 +4596,17 @@ BIF_RETTYPE erts_debug_set_internal_state_2(BIF_ALIST_2)
 	    }
 	}
 	else if (ERTS_IS_ATOM_STR("wait", BIF_ARG_1)) {
-	    if (ERTS_IS_ATOM_STR("deallocations", BIF_ARG_2)) {
-		int flag = ERTS_DEBUG_WAIT_COMPLETED_DEALLOCATIONS;
-		if (erts_debug_wait_completed(BIF_P, flag)) {
-		    ERTS_BIF_YIELD_RETURN(BIF_P, am_ok);
-		}
-	    }
-	    if (ERTS_IS_ATOM_STR("timer_cancellations", BIF_ARG_2)) {
-		int flag = ERTS_DEBUG_WAIT_COMPLETED_TIMER_CANCELLATIONS;
-		if (erts_debug_wait_completed(BIF_P, flag)) {
-		    ERTS_BIF_YIELD_RETURN(BIF_P, am_ok);
-		}
-	    }
+            int flag = 0;
+	    if (ERTS_IS_ATOM_STR("deallocations", BIF_ARG_2))
+                flag = ERTS_DEBUG_WAIT_COMPLETED_DEALLOCATIONS;
+            else if (ERTS_IS_ATOM_STR("timer_cancellations", BIF_ARG_2))
+		flag = ERTS_DEBUG_WAIT_COMPLETED_TIMER_CANCELLATIONS;
+            else if (ERTS_IS_ATOM_STR("aux_work", BIF_ARG_2))
+                flag = ERTS_DEBUG_WAIT_COMPLETED_AUX_WORK;
+
+            if (flag && erts_debug_wait_completed(BIF_P, flag)) {
+                ERTS_BIF_YIELD_RETURN(BIF_P, am_ok);
+            }
 	}
         else if (ERTS_IS_ATOM_STR("broken_halt", BIF_ARG_1)) {
             erts_proc_unlock(BIF_P, ERTS_PROC_LOCK_MAIN);
diff --git a/erts/emulator/beam/erl_binary.h b/erts/emulator/beam/erl_binary.h
index 08edb43c49..2d6fe78757 100644
--- a/erts/emulator/beam/erl_binary.h
+++ b/erts/emulator/beam/erl_binary.h
@@ -315,6 +315,7 @@ ERTS_GLB_INLINE Binary *erts_bin_drv_alloc(Uint size);
 ERTS_GLB_INLINE Binary *erts_bin_nrml_alloc(Uint size);
 ERTS_GLB_INLINE Binary *erts_bin_realloc_fnf(Binary *bp, Uint size);
 ERTS_GLB_INLINE Binary *erts_bin_realloc(Binary *bp, Uint size);
+ERTS_GLB_INLINE void erts_magic_binary_free(Binary *bp);
 ERTS_GLB_INLINE void erts_bin_free(Binary *bp);
 ERTS_GLB_INLINE void erts_bin_release(Binary *bp);
 ERTS_GLB_INLINE Binary *erts_create_magic_binary_x(Uint size,
@@ -446,6 +447,13 @@ erts_bin_realloc(Binary *bp, Uint size)
     return nbp;
 }
 
+ERTS_GLB_INLINE void
+erts_magic_binary_free(Binary *bp)
+{
+    erts_magic_ref_remove_bin(ERTS_MAGIC_BIN_REFN(bp));
+    erts_free(ERTS_MAGIC_BIN_ATYPE(bp), (void *) bp);
+}
+
 ERTS_GLB_INLINE void
 erts_bin_free(Binary *bp)
 {
@@ -454,8 +462,7 @@ erts_bin_free(Binary *bp)
             /* Destructor took control of the deallocation */
             return;
         }
-	erts_magic_ref_remove_bin(ERTS_MAGIC_BIN_REFN(bp));
-        erts_free(ERTS_MAGIC_BIN_ATYPE(bp), (void *) bp);
+        erts_magic_binary_free(bp);
     }
     else if (bp->intern.flags & BIN_FLAG_DRV)
 	erts_free(ERTS_ALC_T_DRV_BINARY, (void *) bp);
diff --git a/erts/emulator/beam/erl_nif.c b/erts/emulator/beam/erl_nif.c
index ebef485b04..365559e2ad 100644
--- a/erts/emulator/beam/erl_nif.c
+++ b/erts/emulator/beam/erl_nif.c
@@ -987,7 +987,7 @@ static Eterm call_whereis(ErlNifEnv *env, Eterm name)
     int scheduler;
 
     execution_state(env, &c_p, &scheduler);
-    ASSERT((c_p && scheduler) || (!c_p && !scheduler));
+    ASSERT(scheduler || !c_p);
 
     if (scheduler < 0) {
         /* dirty scheduler */
@@ -2361,10 +2361,26 @@ int erts_dbg_is_resource_dying(ErtsResource* resource)
 }
 #endif
 
-#  define NIF_RESOURCE_DTOR &nif_resource_dtor
+#define NIF_RESOURCE_DTOR &nif_resource_dtor_prologue
 
-static int nif_resource_dtor(Binary* bin)
+static void run_resource_dtor(void* vbin);
+ 
+static int nif_resource_dtor_prologue(Binary* bin)
 {
+    /*
+     * Schedule user resource destructor as aux work to get a context
+     * where we know what locks we have for example.
+     */
+    Uint sched_id = erts_get_scheduler_id();
+    if (!sched_id)
+        sched_id = 1;
+    erts_schedule_misc_aux_work(sched_id, run_resource_dtor, bin);
+    return 0; /* don't free */
+}
+ 
+static void run_resource_dtor(void* vbin)
+{
+    Binary* bin = (Binary*) vbin;
     ErtsResource* resource = (ErtsResource*) ERTS_MAGIC_BIN_UNALIGNED_DATA(bin);
     ErlNifResourceType* type = resource->type;
     ASSERT(ERTS_MAGIC_BIN_DESTRUCTOR(bin) == NIF_RESOURCE_DTOR);
@@ -2396,11 +2412,11 @@ static int nif_resource_dtor(Binary* bin)
          * If resource->monitors->refc != 0 there are
          * outstanding references to the resource from
          * monitors that has not been removed yet.
-         * nif_resource_dtor() will be called again this
+         * nif_resource_dtor_prologue() will be called again when this
          * reference count reach zero.
          */
         if (refc != 0)
-            return 0; /* we'll be back... */
+            return; /* we'll be back... */
         erts_mtx_destroy(&rm->lock);
     }
 
@@ -2417,7 +2433,7 @@ static int nif_resource_dtor(Binary* bin)
 	steal_resource_type(type);
 	erts_free(ERTS_ALC_T_NIF, type);
     }
-    return 1;
+    erts_magic_binary_free((Binary*)vbin);
 }
 
 void erts_resource_stop(ErtsResource* resource, ErlNifEvent e,
diff --git a/erts/emulator/beam/erl_process.c b/erts/emulator/beam/erl_process.c
index cc02fbad1e..438d88c346 100644
--- a/erts/emulator/beam/erl_process.c
+++ b/erts/emulator/beam/erl_process.c
@@ -2375,9 +2375,12 @@ struct debug_lop {
 static void later_thr_debug_wait_completed(void *vlop)
 {
     struct debug_lop *lop = vlop;
-    erts_aint32_t count = (erts_aint32_t) erts_no_schedulers;
-    count += 1; /* aux thread */
-    if (erts_atomic32_dec_read_mb(&debug_wait_completed_count) == count) {
+
+    if (erts_atomic32_dec_read_mb(&debug_wait_completed_count) == 1) {
+        erts_aint32_t count = (erts_aint32_t) erts_no_schedulers;
+        count += 1; /* aux thread */
+        erts_atomic32_set_nob(&debug_wait_completed_count, count);
+
         /* scheduler threads */
         erts_schedule_multi_misc_aux_work(0,
                                           erts_no_schedulers,
@@ -2395,19 +2398,28 @@ static void later_thr_debug_wait_completed(void *vlop)
 static void
 init_thr_debug_wait_completed(void *vproc)
 {
-    struct debug_lop* lop = erts_alloc(ERTS_ALC_T_DEBUG,
-                                       sizeof(struct debug_lop));
-    lop->proc = vproc;
-    erts_schedule_thr_prgr_later_op(later_thr_debug_wait_completed, lop, &lop->lop);
+    if (debug_wait_completed_flags == ERTS_DEBUG_WAIT_COMPLETED_AUX_WORK) {
+        if (erts_atomic32_dec_read_mb(&debug_wait_completed_count) == 1) {
+            erts_atomic32_set_nob(&debug_wait_completed_count, 0);
+            erts_resume((Process *) vproc, (ErtsProcLocks) 0);
+            erts_proc_dec_refc((Process *) vproc);
+        }
+    }
+    else {
+        struct debug_lop* lop = erts_alloc(ERTS_ALC_T_DEBUG,
+                                           sizeof(struct debug_lop));
+        lop->proc = vproc;
+        erts_schedule_thr_prgr_later_op(later_thr_debug_wait_completed, lop, &lop->lop);
+    }
 }
 
 
 int
 erts_debug_wait_completed(Process *c_p, int flags)
 {
-    /* Only one process at a time can do this */
-    erts_aint32_t count = (erts_aint32_t) (2*erts_no_schedulers);
-    count += 1; /* aux thread */
+    /* Only one process at a time can do this, +1 to mark as busy */
+    erts_aint32_t count = (erts_aint32_t) (erts_no_schedulers + 1);
+
     if (0 == erts_atomic32_cmpxchg_mb(&debug_wait_completed_count,
 				      count,
 				      0)) {
diff --git a/erts/emulator/beam/erl_process.h b/erts/emulator/beam/erl_process.h
index 43937f216c..434b528c55 100644
--- a/erts/emulator/beam/erl_process.h
+++ b/erts/emulator/beam/erl_process.h
@@ -1850,6 +1850,7 @@ Uint erts_debug_nbalance(void);
 
 #define ERTS_DEBUG_WAIT_COMPLETED_DEALLOCATIONS		(1 << 0)
 #define ERTS_DEBUG_WAIT_COMPLETED_TIMER_CANCELLATIONS	(1 << 1)
+#define ERTS_DEBUG_WAIT_COMPLETED_AUX_WORK		(1 << 2)
 
 int erts_debug_wait_completed(Process *c_p, int flags);
 
diff --git a/erts/emulator/test/nif_SUITE.erl b/erts/emulator/test/nif_SUITE.erl
index ca5f90621f..6ca0990a8a 100644
--- a/erts/emulator/test/nif_SUITE.erl
+++ b/erts/emulator/test/nif_SUITE.erl
@@ -28,6 +28,7 @@
 -include_lib("stdlib/include/assert.hrl").
 
 -export([all/0, suite/0, groups/0,
+         init_per_suite/1, end_per_suite/1,
          init_per_group/2, end_per_group/2,
 	 init_per_testcase/2, end_per_testcase/2,
          basic/1, reload_error/1, upgrade/1, heap_frag/1,
@@ -105,6 +106,14 @@ all() ->
      nif_whereis, nif_whereis_parallel, nif_whereis_threaded,
      nif_ioq].
 
+init_per_suite(Config) ->
+    erts_debug:set_internal_state(available_internal_state, true),
+    Config.
+
+end_per_suite(_Config) ->
+    catch erts_debug:set_internal_state(available_internal_state, false),
+    ok.
+
 groups() ->
     [{G, [], api_repeaters()} || G <- api_groups()]
         ++
@@ -114,7 +123,6 @@ groups() ->
                     monitor_process_d,
                     demonitor_process]}].
 
-
 api_groups() -> [api_latest, api_2_4, api_2_0].
 
 api_repeaters() -> [upgrade, resource_takeover, t_on_load].
@@ -1711,6 +1719,7 @@ read_resource(Type, {Holder,Id}) ->
 forget_resource({Holder,Id}) ->
     Holder ! {self(), forget, Id},
     {Holder, forget_ok, Id} = receive_any(),
+    erts_debug:set_internal_state(wait, aux_work),
     ok.
 
 
@@ -3327,6 +3336,10 @@ make_unaligned_binary(Bin0) ->
     <<0:3,Bin:Size/binary,31:5>> = id(<<0:3,Bin0/binary,31:5>>),
     Bin.
 
+last_resource_dtor_call() ->
+    erts_debug:set_internal_state(wait, aux_work),
+    last_resource_dtor_call_nif().
+
 id(I) -> I.
 
 %% The NIFs:
@@ -3354,7 +3367,7 @@ make_resource(_) -> ?nif_stub.
 get_resource(_,_) -> ?nif_stub.
 release_resource(_) -> ?nif_stub.
 release_resource_from_thread(_) -> ?nif_stub.
-last_resource_dtor_call() -> ?nif_stub.
+last_resource_dtor_call_nif() -> ?nif_stub.
 make_new_resource(_,_) -> ?nif_stub.
 check_is(_,_,_,_,_,_,_,_,_,_,_) -> ?nif_stub.
 check_is_exception() -> ?nif_stub.
diff --git a/erts/emulator/test/nif_SUITE_data/nif_SUITE.c b/erts/emulator/test/nif_SUITE_data/nif_SUITE.c
index f2ce6dbe67..17ba3ce297 100644
--- a/erts/emulator/test/nif_SUITE_data/nif_SUITE.c
+++ b/erts/emulator/test/nif_SUITE_data/nif_SUITE.c
@@ -866,7 +866,7 @@ static ERL_NIF_TERM iolist_2_bin(ErlNifEnv* env, int argc, const ERL_NIF_TERM ar
     return enif_make_binary(env,&obin);
 }
 
-static ERL_NIF_TERM last_resource_dtor_call(ErlNifEnv* env, int argc, const ERL_NIF_TERM argv[])
+static ERL_NIF_TERM last_resource_dtor_call_nif(ErlNifEnv* env, int argc, const ERL_NIF_TERM argv[])
 {
     ERL_NIF_TERM ret;
     if (resource_dtor_last != NULL) {
@@ -3512,7 +3512,7 @@ static ErlNifFunc nif_funcs[] =
     {"get_resource", 2, get_resource},
     {"release_resource", 1, release_resource},
     {"release_resource_from_thread", 1, release_resource_from_thread},
-    {"last_resource_dtor_call", 0, last_resource_dtor_call},
+    {"last_resource_dtor_call_nif", 0, last_resource_dtor_call_nif},
     {"make_new_resource", 2, make_new_resource},
     {"check_is", 11, check_is},
     {"check_is_exception", 0, check_is_exception},
-- 
2.16.4

openSUSE Build Service is sponsored by