File 1318-erts-Stop-freeing-heap-fragments-in-erts_factory_und.patch of Package erlang

From 405497d18c6cc8656694119f1e81fcea62dca45f Mon Sep 17 00:00:00 2001
From: =?UTF-8?q?John=20H=C3=B6gberg?= <john@erlang.org>
Date: Tue, 5 Apr 2022 14:02:42 +0200
Subject: [PATCH] erts: Stop freeing heap fragments in `erts_factory_undo`

When calling BIFs, we grab the heap fragment head from `c_p->mbuf`
for use as a "line in the sand" in `erts_gc_after_bif_call_lhf`.

This is usually fine, but if we're trapping with a factory that
has created several heap fragments and then bail out with
`erts_factory_undo`, we'll hold a reference to a fragment that
no longer exists.

To get around this, we'll reset the used size of the fragments to
zero instead (note that `p->mbuf_sz` is left alone on purpose),
leaving freeing to the GC.
---
 erts/emulator/beam/erl_gc.c      | 12 +++++++
 erts/emulator/beam/erl_message.c | 61 ++++++++++++++++----------------
 2 files changed, 42 insertions(+), 31 deletions(-)

diff --git a/erts/emulator/beam/erl_gc.c b/erts/emulator/beam/erl_gc.c
index b74eaccea8..b8b5d5f6b5 100644
--- a/erts/emulator/beam/erl_gc.c
+++ b/erts/emulator/beam/erl_gc.c
@@ -418,6 +418,18 @@ erts_gc_after_bif_call_lhf(Process* p, ErlHeapFragment *live_hf_end,
 {
     int cost;
 
+#ifdef DEBUG
+    if (live_hf_end != ERTS_INVALID_HFRAG_PTR) {
+        ErlHeapFragment *it = p->mbuf;
+
+        /* `live_hf_end` MUST be part of the heap fragment list. */
+        while (it != live_hf_end) {
+            ASSERT(it);
+            it = it->next;
+        }
+    }
+#endif
+
     if ((p->flags & F_HIBERNATE_SCHED) ||
         (p->sig_qs.flags & FS_HIPE_RECV_LOCKED)) {
 	/*
diff --git a/erts/emulator/beam/erl_message.c b/erts/emulator/beam/erl_message.c
index 9cac1e2677..b07f51fabf 100644
--- a/erts/emulator/beam/erl_message.c
+++ b/erts/emulator/beam/erl_message.c
@@ -1187,6 +1187,10 @@ void erts_factory_proc_init(ErtsHeapFactory* factory, Process* p)
        heap as that completely destroys the DEBUG emulators
        performance. */
     ErlHeapFragment *bp = p->mbuf;
+
+    factory->heap_frags_saved = bp;
+    factory->heap_frags_saved_used = bp ? bp->used_size : 0;
+
     factory->mode     = FACTORY_HALLOC;
     factory->p        = p;
     factory->hp_start = HEAP_TOP(p);
@@ -1197,8 +1201,6 @@ void erts_factory_proc_init(ErtsHeapFactory* factory, Process* p)
     factory->message  = NULL;
     factory->off_heap_saved.first    = p->off_heap.first;
     factory->off_heap_saved.overhead = p->off_heap.overhead;
-    factory->heap_frags_saved = bp;
-    factory->heap_frags_saved_used = bp ? bp->used_size : 0;
     factory->heap_frags = NULL; /* not used */
     factory->alloc_type = 0; /* not used */
 
@@ -1210,6 +1212,13 @@ void erts_factory_proc_prealloc_init(ErtsHeapFactory* factory,
 				     Sint size)
 {
     ErlHeapFragment *bp = p->mbuf;
+
+    /* `bp->used_size` must be set _BEFORE_ we call `HAlloc`, as that will
+     * update the used size and prevent us from undoing the changes later
+     * on. */
+    factory->heap_frags_saved = bp;
+    factory->heap_frags_saved_used = bp ? bp->used_size : 0;
+
     factory->mode     = FACTORY_HALLOC;
     factory->p        = p;
     factory->original_htop = HEAP_TOP(p);
@@ -1224,8 +1233,6 @@ void erts_factory_proc_prealloc_init(ErtsHeapFactory* factory,
     factory->message  = NULL;
     factory->off_heap_saved.first    = p->off_heap.first;
     factory->off_heap_saved.overhead = p->off_heap.overhead;
-    factory->heap_frags_saved = bp;
-    factory->heap_frags_saved_used = bp ? bp->used_size : 0;
     factory->heap_frags = NULL; /* not used */
     factory->alloc_type = 0; /* not used */
 }
@@ -1603,40 +1610,32 @@ void erts_factory_undo(ErtsHeapFactory* factory)
         }
 
         if (factory->mode == FACTORY_HALLOC) {
-            /* Free heap frags
-             */
-            bp = factory->p->mbuf;
-            if (bp != factory->heap_frags_saved) {
-                do {
-                    ErlHeapFragment *next_bp = bp->next;
-                    ASSERT(bp->off_heap.first == NULL);
-                    ERTS_HEAP_FREE(ERTS_ALC_T_HEAP_FRAG, (void *) bp,
-                                   ERTS_HEAP_FRAG_SIZE(bp->alloc_size));
-                    bp = next_bp;
-                } while (bp != factory->heap_frags_saved);
-
-                factory->p->mbuf = bp;
+            /* Reset all the heap fragments we've added. Note that we CANNOT
+             * free them, as someone else might have grabbed a reference to
+             * them (e.g. the callers of `erts_gc_after_bif_call_lhf`).
+             *
+             * The GC will get rid of these later on. Note that we leave
+             * `p->mbuf_sz` untouched to keep the memory pressure of these
+             * fragments. */
+            for (bp = (factory->p)->mbuf;
+                 bp != factory->heap_frags_saved;
+                 bp = bp->next) {
+                ASSERT(bp->off_heap.first == NULL);
+                bp->used_size = 0;
             }
 
-            /* Rollback heap top
-	     */
+            /* Roll back the size of the latest fragment not allocated by us,
+             * as we may have used a part of it. */
+            if (bp != NULL) {
+                ASSERT(bp == factory->heap_frags_saved);
+                bp->used_size = factory->heap_frags_saved_used;
+            }
 
+            /* Roll back heap top */
             ASSERT(HEAP_START(factory->p) <= factory->original_htop);
             ASSERT(factory->original_htop <= HEAP_LIMIT(factory->p));
             HEAP_TOP(factory->p) = factory->original_htop;
 
-
-	    /* Fix last heap frag */
-            if (factory->heap_frags_saved) {
-                ASSERT(factory->heap_frags_saved == factory->p->mbuf);
-                if (factory->hp_start != factory->heap_frags_saved->mem)
-                    factory->heap_frags_saved->used_size = factory->heap_frags_saved_used;
-		else {
-                    factory->p->mbuf = factory->p->mbuf->next;
-                    ERTS_HEAP_FREE(ERTS_ALC_T_HEAP_FRAG, factory->heap_frags_saved,
-                                   ERTS_HEAP_FRAG_SIZE(factory->heap_frags_saved->alloc_size));
-                }
-            }
             if (factory->message) {
                 ASSERT(factory->message->data.attached != ERTS_MSG_COMBINED_HFRAG);
                 ASSERT(!factory->message->data.heap_frag);
-- 
2.34.1

openSUSE Build Service is sponsored by