File 2061-erts-Refactor-ETS-matching.patch of Package erlang

From 709b4521019c30281281b4938a0f9354c747e037 Mon Sep 17 00:00:00 2001
From: Sverker Eriksson <sverker@erlang.org>
Date: Tue, 22 Sep 2020 20:22:26 +0200
Subject: [PATCH 1/2] erts: Refactor ETS matching

Move out HAlloc of cons cell to the code that actualy needs it.
---
 erts/emulator/beam/erl_db_hash.c | 52 ++++++++++++++++++--------------
 erts/emulator/beam/erl_db_tree.c | 14 ++++-----
 erts/emulator/beam/erl_db_util.c | 17 +++--------
 erts/emulator/beam/erl_db_util.h |  4 +--
 4 files changed, 43 insertions(+), 44 deletions(-)

diff --git a/erts/emulator/beam/erl_db_hash.c b/erts/emulator/beam/erl_db_hash.c
index 79480a0c03..443827bc0c 100644
--- a/erts/emulator/beam/erl_db_hash.c
+++ b/erts/emulator/beam/erl_db_hash.c
@@ -1239,6 +1239,7 @@ struct traverse_context_t_
     Eterm tid;
     Eterm* prev_continuation_tptr;
     enum DbIterSafety safety;
+    enum erts_pam_run_flags pam_flags;
 };
 
 
@@ -1250,7 +1251,6 @@ static int match_traverse(traverse_context_t* ctx,
                           extra_match_validator_t extra_match_validator, /* Optional */
                           Sint chunk_size,      /* If 0, no chunking */
                           Sint iterations_left, /* Nr. of iterations left */
-                          Eterm** hpp,          /* Heap */
                           int lock_for_write,   /* Set to 1 if we're going to delete or
                                                    modify existing terms */
                           Eterm* ret)
@@ -1326,7 +1326,7 @@ static int match_traverse(traverse_context_t* ctx,
                 if (tb->common.compress)
                     obj = db_alloc_tmp_uncompressed(&tb->common, obj);
                 match_res = db_match_dbterm_uncompressed(&tb->common, ctx->p, mpi.mp,
-                                                         obj, hpp, 2);
+                                                         obj, ctx->pam_flags);
                 saved_current = *current_ptr;
                 if (ctx->on_match_res(ctx, slot_ix, &current_ptr, match_res)) {
                     ++got;
@@ -1396,7 +1396,6 @@ done:
 static int match_traverse_continue(traverse_context_t* ctx,
                                    Sint chunk_size,      /* If 0, no chunking */
                                    Sint iterations_left, /* Nr. of iterations left */
-                                   Eterm** hpp,          /* Heap */
                                    Sint slot_ix,         /* Slot index to resume traversal from */
                                    Sint got,             /* Matched terms counter */
                                    Binary** mpp,         /* Existing match program */
@@ -1451,7 +1450,7 @@ static int match_traverse_continue(traverse_context_t* ctx,
                 if (tb->common.compress)
                     obj = db_alloc_tmp_uncompressed(&tb->common, obj);
                 match_res = db_match_dbterm_uncompressed(&tb->common, ctx->p, *mpp,
-                                                         obj, hpp, 2);
+                                                         obj, ctx->pam_flags);
                 saved_current = *current_ptr;
                 if (ctx->on_match_res(ctx, slot_ix, &current_ptr, match_res)) {
                     ++got;
@@ -1593,7 +1592,6 @@ static ERTS_INLINE int unpack_simple_continuation(Eterm continuation,
 
 typedef struct {
     traverse_context_t base;
-    Eterm* hp;
     Sint chunk_size;
     Eterm match_list;
 } select_chunk_context_t;
@@ -1611,7 +1609,8 @@ static int select_chunk_on_match_res(traverse_context_t* ctx_base, Sint slot_ix,
 {
     select_chunk_context_t* ctx = (select_chunk_context_t*) ctx_base;
     if (is_value(match_res)) {
-        ctx->match_list = CONS(ctx->hp, match_res, ctx->match_list);
+        Eterm* hp = HAlloc(ctx->base.p, 2);
+        ctx->match_list = CONS(hp, match_res, ctx->match_list);
         return 1;
     }
     return 0;
@@ -1638,6 +1637,7 @@ static int select_chunk_on_loop_ended(traverse_context_t* ctx_base,
             Eterm continuation;
             Eterm rest = NIL;
             Sint rest_size = 0;
+            Eterm* hp;
 
             if (got > ctx->chunk_size) { /* Split list in return value and 'rest' */
                 Eterm tmp = ctx->match_list;
@@ -1653,29 +1653,29 @@ static int select_chunk_on_loop_ended(traverse_context_t* ctx_base,
             }
             if (rest != NIL || slot_ix >= 0) { /* Need more calls */
                 Eterm tid = ctx->base.tid;
-                ctx->hp = HAllocX(ctx->base.p,
+                hp = HAllocX(ctx->base.p,
                                   3 + 7 + ERTS_MAGIC_REF_THING_SIZE,
                                   ERTS_MAGIC_REF_THING_SIZE);
-                mpb = erts_db_make_match_prog_ref(ctx->base.p, *mpp, &ctx->hp);
+                mpb = erts_db_make_match_prog_ref(ctx->base.p, *mpp, &hp);
                 if (is_atom(tid))
                     tid = erts_db_make_tid(ctx->base.p,
                                            &ctx->base.tb->common);
                 continuation = TUPLE6(
-                        ctx->hp,
+                        hp,
                         tid,
                         make_small(slot_ix),
                         make_small(ctx->chunk_size),
                         mpb, rest,
                         make_small(rest_size));
                 *mpp = NULL; /* Otherwise the caller will destroy it */
-                ctx->hp += 7;
-                *ret = TUPLE2(ctx->hp, ctx->match_list, continuation);
+                hp += 7;
+                *ret = TUPLE2(hp, ctx->match_list, continuation);
                 return DB_ERROR_NONE;
             } else { /* All data is exhausted */
                 if (ctx->match_list != NIL) { /* No more data to search but still a
                                                             result to return to the caller */
-                    ctx->hp = HAlloc(ctx->base.p, 3);
-                    *ret = TUPLE2(ctx->hp, ctx->match_list, am_EOT);
+                    hp = HAlloc(ctx->base.p, 3);
+                    *ret = TUPLE2(hp, ctx->match_list, am_EOT);
                     return DB_ERROR_NONE;
                 } else { /* Reached the end of the ttable with no data to return */
                     *ret = am_EOT;
@@ -1757,7 +1757,7 @@ static int db_select_chunk_hash(Process *p, DbTable *tbl, Eterm tid,
     ctx.base.tid = tid;
     ctx.base.prev_continuation_tptr = NULL;
     ctx.base.safety = safety;
-    ctx.hp = NULL;
+    ctx.base.pam_flags = ERTS_PAM_COPY_RESULT;
     ctx.chunk_size = chunk_size;
     ctx.match_list = NIL;
 
@@ -1766,7 +1766,7 @@ static int db_select_chunk_hash(Process *p, DbTable *tbl, Eterm tid,
             pattern, NULL,
             ctx.chunk_size,
             MAX_SELECT_CHUNK_ITERATIONS,
-            &ctx.hp, 0,
+            0,
             ret);
 }
 
@@ -1887,13 +1887,13 @@ static int db_select_continue_hash(Process* p, DbTable* tbl, Eterm continuation,
     ctx.base.tid = tid;
     ctx.base.prev_continuation_tptr = tptr;
     ctx.base.safety = *safety_p;
-    ctx.hp = NULL;
+    ctx.base.pam_flags = ERTS_PAM_COPY_RESULT;
     ctx.chunk_size = chunk_size;
     ctx.match_list = match_list;
 
     return match_traverse_continue(
         &ctx.base, ctx.chunk_size,
-        iterations_left, &ctx.hp, slot_ix, got, &mp, 0,
+        iterations_left, slot_ix, got, &mp, 0,
         ret);
 
 badparam:
@@ -1963,11 +1963,12 @@ static int db_select_count_hash(Process *p, DbTable *tbl, Eterm tid,
     ctx.tid = tid;
     ctx.prev_continuation_tptr = NULL;
     ctx.safety = safety;
+    ctx.pam_flags = ERTS_PAM_TMP_RESULT;
 
     return match_traverse(
             &ctx,
             pattern, NULL,
-            chunk_size, iterations_left, NULL, 0,
+            chunk_size, iterations_left, 0,
             ret);
 }
 
@@ -2001,11 +2002,12 @@ static int db_select_count_continue_hash(Process* p, DbTable* tbl,
     ctx.tid = tid;
     ctx.prev_continuation_tptr = tptr;
     ctx.safety = *safety_p;
+    ctx.pam_flags = ERTS_PAM_TMP_RESULT;
 
     return match_traverse_continue(
             &ctx, chunk_size,
             MAX_SELECT_COUNT_ITERATIONS,
-            NULL, slot_ix, got, &mp, 0,
+            slot_ix, got, &mp, 0,
             ret);
 }
 
@@ -2109,6 +2111,7 @@ static int db_select_delete_hash(Process *p, DbTable *tbl, Eterm tid,
     ctx.base.tid = tid;
     ctx.base.prev_continuation_tptr = NULL;
     ctx.base.safety = safety;
+    ctx.base.pam_flags = ERTS_PAM_TMP_RESULT;
     ctx.fixated_by_me = ctx.base.tb->common.is_thread_safe ? 0 : 1;
     ctx.last_pseudo_delete = (Uint) -1;
     ctx.free_us = NULL;
@@ -2117,7 +2120,7 @@ static int db_select_delete_hash(Process *p, DbTable *tbl, Eterm tid,
             &ctx.base,
             pattern, NULL,
             chunk_size,
-            MAX_SELECT_DELETE_ITERATIONS, NULL, 1,
+            MAX_SELECT_DELETE_ITERATIONS, 1,
             ret);
 }
 
@@ -2150,6 +2153,7 @@ static int db_select_delete_continue_hash(Process* p, DbTable* tbl,
     ctx.base.tid = tid;
     ctx.base.prev_continuation_tptr = tptr;
     ctx.base.safety = *safety_p;
+    ctx.base.pam_flags = ERTS_PAM_TMP_RESULT;
     ctx.fixated_by_me = ONLY_WRITER(p, ctx.base.tb) ? 0 : 1;
     ctx.last_pseudo_delete = (Uint) -1;
     ctx.free_us = NULL;
@@ -2157,7 +2161,7 @@ static int db_select_delete_continue_hash(Process* p, DbTable* tbl,
     return match_traverse_continue(
             &ctx.base, chunk_size,
             MAX_SELECT_DELETE_ITERATIONS,
-            NULL, slot_ix, got, &mp, 1,
+            slot_ix, got, &mp, 1,
             ret);
 }
 
@@ -2251,12 +2255,13 @@ static int db_select_replace_hash(Process *p, DbTable *tbl, Eterm tid,
     ctx.tid = tid;
     ctx.prev_continuation_tptr = NULL;
     ctx.safety = safety;
+    ctx.pam_flags = ERTS_PAM_TMP_RESULT;
 
     return match_traverse(
             &ctx,
             pattern, db_match_keeps_key,
             chunk_size,
-            MAX_SELECT_REPLACE_ITERATIONS, NULL, 1,
+            MAX_SELECT_REPLACE_ITERATIONS, 1,
             ret);
 }
 
@@ -2291,11 +2296,12 @@ static int db_select_replace_continue_hash(Process* p, DbTable* tbl,
     ctx.tid = tid;
     ctx.prev_continuation_tptr = tptr;
     ctx.safety = *safety_p;
+    ctx.pam_flags = ERTS_PAM_TMP_RESULT;
 
     return match_traverse_continue(
             &ctx, chunk_size,
             MAX_SELECT_REPLACE_ITERATIONS,
-            NULL, slot_ix, got, &mp, 1,
+            slot_ix, got, &mp, 1,
             ret);
 }
 
diff --git a/erts/emulator/beam/erl_db_tree.c b/erts/emulator/beam/erl_db_tree.c
index 015232e4f3..441d22805a 100644
--- a/erts/emulator/beam/erl_db_tree.c
+++ b/erts/emulator/beam/erl_db_tree.c
@@ -3838,7 +3838,6 @@ static int doit_select(DbTableCommon *tb, TreeDbTerm *this,
 {
     struct select_context *sc = (struct select_context *) ptr;
     Eterm ret;
-    Eterm* hp;
 
     sc->lastobj = this->dbterm.tpl;
     
@@ -3851,8 +3850,9 @@ static int doit_select(DbTableCommon *tb, TreeDbTerm *this,
 			   GETKEY_WITH_POS(sc->keypos, this->dbterm.tpl)) > 0))) {
 	return 0;
     }
-    ret = db_match_dbterm(tb, sc->p,sc->mp, &this->dbterm, &hp, 2);
+    ret = db_match_dbterm(tb, sc->p, sc->mp, &this->dbterm, ERTS_PAM_COPY_RESULT);
     if (is_value(ret)) {
+        Eterm *hp = HAlloc(sc->p, 2);
 	sc->accum = CONS(hp, ret, sc->accum);
     }
     if (--(sc->max) <= 0) {
@@ -3876,7 +3876,7 @@ static int doit_select_count(DbTableCommon *tb, TreeDbTerm *this,
 			  GETKEY_WITH_POS(sc->keypos, this->dbterm.tpl)) > 0)) {
 	return 0;
     }
-    ret = db_match_dbterm(tb, sc->p, sc->mp, &this->dbterm, NULL, 0);
+    ret = db_match_dbterm(tb, sc->p, sc->mp, &this->dbterm, ERTS_PAM_TMP_RESULT);
     if (ret == am_true) {
 	++(sc->got);
     }
@@ -3892,7 +3892,6 @@ static int doit_select_chunk(DbTableCommon *tb, TreeDbTerm *this,
 {
     struct select_context *sc = (struct select_context *) ptr;
     Eterm ret;
-    Eterm* hp;
 
     sc->lastobj = this->dbterm.tpl;
     
@@ -3906,8 +3905,9 @@ static int doit_select_chunk(DbTableCommon *tb, TreeDbTerm *this,
 	return 0;
     }
 
-    ret = db_match_dbterm(tb, sc->p, sc->mp, &this->dbterm, &hp, 2);
+    ret = db_match_dbterm(tb, sc->p, sc->mp, &this->dbterm, ERTS_PAM_COPY_RESULT);
     if (is_value(ret)) {
+        Eterm *hp = HAlloc(sc->p, 2);
 	++(sc->got);
 	sc->accum = CONS(hp, ret, sc->accum);
     }
@@ -3935,7 +3935,7 @@ static int doit_select_delete(DbTableCommon *tb, TreeDbTerm *this,
 	cmp_partly_bound(sc->end_condition, 
 			 GETKEY_WITH_POS(sc->keypos, this->dbterm.tpl)) > 0)
 	return 0;
-    ret = db_match_dbterm(tb, sc->p, sc->mp, &this->dbterm, NULL, 0);
+    ret = db_match_dbterm(tb, sc->p, sc->mp, &this->dbterm, ERTS_PAM_TMP_RESULT);
     if (ret == am_true) {
 	key = GETKEY(sc->tb, this->dbterm.tpl);
 	linkout_tree(sc->tb, sc->common.root, key, sc->stack);
@@ -3967,7 +3967,7 @@ static int doit_select_replace(DbTableCommon *tb, TreeDbTerm **this,
     obj = &(*this)->dbterm;
     if (tb->compress)
         obj = db_alloc_tmp_uncompressed(tb, obj);
-    ret = db_match_dbterm_uncompressed(tb, sc->p, sc->mp, obj, NULL, 0);
+    ret = db_match_dbterm_uncompressed(tb, sc->p, sc->mp, obj, ERTS_PAM_TMP_RESULT);
 
     if (is_value(ret)) {
         TreeDbTerm* new;
diff --git a/erts/emulator/beam/erl_db_util.c b/erts/emulator/beam/erl_db_util.c
index 7525bd8fd5..0043996601 100644
--- a/erts/emulator/beam/erl_db_util.c
+++ b/erts/emulator/beam/erl_db_util.c
@@ -5334,34 +5334,27 @@ void db_free_tmp_uncompressed(DbTerm* obj)
 }
 
 Eterm db_match_dbterm_uncompressed(DbTableCommon* tb, Process* c_p, Binary* bprog,
-                                   DbTerm* obj, Eterm** hpp, Uint extra)
+                                   DbTerm* obj, enum erts_pam_run_flags flags)
 {
-    enum erts_pam_run_flags flags;
+
     Uint32 dummy;
     Eterm res;
 
-    flags = (hpp ?
-             ERTS_PAM_COPY_RESULT | ERTS_PAM_CONTIGUOUS_TUPLE :
-             ERTS_PAM_TMP_RESULT  | ERTS_PAM_CONTIGUOUS_TUPLE);
-
     res = db_prog_match(c_p, c_p,
                         bprog, make_tuple(obj->tpl), NULL, 0,
-			flags, &dummy);
+			flags|ERTS_PAM_CONTIGUOUS_TUPLE, &dummy);
 
-    if (is_value(res) && hpp!=NULL) {
-	*hpp = HAlloc(c_p, extra);
-    }
     return res;
 }
 
 Eterm db_match_dbterm(DbTableCommon* tb, Process* c_p, Binary* bprog,
-                      DbTerm* obj, Eterm** hpp, Uint extra)
+                      DbTerm* obj, enum erts_pam_run_flags flags)
 {
     Eterm res;
     if (tb->compress) {
         obj = db_alloc_tmp_uncompressed(tb, obj);
     }
-    res = db_match_dbterm_uncompressed(tb, c_p, bprog, obj, hpp, extra);
+    res = db_match_dbterm_uncompressed(tb, c_p, bprog, obj, flags);
     if (tb->compress) {
         db_free_tmp_uncompressed(obj);
     }
diff --git a/erts/emulator/beam/erl_db_util.h b/erts/emulator/beam/erl_db_util.h
index 5e91e1511a..aee4c3b5f6 100644
--- a/erts/emulator/beam/erl_db_util.h
+++ b/erts/emulator/beam/erl_db_util.h
@@ -525,9 +525,9 @@ Binary *db_match_compile(Eterm *matchexpr, Eterm *guards,
 /* Returns newly allocated MatchProg binary with refc == 0*/
 
 Eterm db_match_dbterm_uncompressed(DbTableCommon* tb, Process* c_p, Binary* bprog,
-                                   DbTerm* obj, Eterm** hpp, Uint extra);
+                                   DbTerm* obj, enum erts_pam_run_flags);
 Eterm db_match_dbterm(DbTableCommon* tb, Process* c_p, Binary* bprog,
-		      DbTerm* obj, Eterm** hpp, Uint extra);
+                      DbTerm *obj, enum erts_pam_run_flags);
 
 Eterm db_prog_match(Process *p, Process *self,
                     Binary *prog, Eterm term,
-- 
2.26.2

openSUSE Build Service is sponsored by