File 2655-erts-Introduce-hash_fetch-as-an-optimized-hash_get.patch of Package erlang

From 18e2d852469fc3c3cdf287de5ca1ed4c73c71c4d Mon Sep 17 00:00:00 2001
From: Lukas Larsson <lukas@erlang.org>
Date: Fri, 9 Aug 2019 14:26:21 +0200
Subject: [PATCH 5/6] erts: Introduce hash_fetch as an optimized hash_get

---
 erts/emulator/beam/export.c   | 49 +++++++++++++-------------------------
 erts/emulator/beam/hash.c     | 11 +--------
 erts/emulator/beam/hash.h     | 17 +++++++++++++
 erts/emulator/beam/register.c | 55 +++++++++----------------------------------
 4 files changed, 46 insertions(+), 86 deletions(-)

diff --git a/erts/emulator/beam/export.c b/erts/emulator/beam/export.c
index c17fb436e2..b928f03b2f 100644
--- a/erts/emulator/beam/export.c
+++ b/erts/emulator/beam/export.c
@@ -196,6 +196,17 @@ init_export_table(void)
     }
 }
 
+static struct export_entry* init_template(struct export_templ* templ,
+					  Eterm m, Eterm f, unsigned a)
+{
+    templ->entry.ep = &templ->exp;
+    templ->entry.slot.index = -1;
+    templ->exp.info.mfa.module = m;
+    templ->exp.info.mfa.function = f;
+    templ->exp.info.mfa.arity = a;
+    return &templ->entry;
+}
+
 /*
  * Return a pointer to the export entry for the given function,
  * or NULL otherwise.  Notes:
@@ -214,41 +225,15 @@ erts_find_export_entry(Eterm m, Eterm f, unsigned int a,ErtsCodeIndex code_ix);
 Export*
 erts_find_export_entry(Eterm m, Eterm f, unsigned int a, ErtsCodeIndex code_ix)
 {
-    HashValue hval = EXPORT_HASH((BeamInstr) m, (BeamInstr) f, (BeamInstr) a);
-    int ix;
-    HashBucket* b;
-
-    ix = hash_get_slot(&export_tables[code_ix].htable, hval);
-    b = export_tables[code_ix].htable.bucket[ix];
-
-    /*
-     * Note: We have inlined the code from hash.c for speed.
-     */
-	
-    while (b != (HashBucket*) 0) {
-	Export* ep = ((struct export_entry*) b)->ep;
-	if (ep->info.mfa.module == m &&
-            ep->info.mfa.function == f &&
-            ep->info.mfa.arity == a) {
-	    return ep;
-	}
-	b = b->next;
-    }
+    struct export_templ templ;
+    struct export_entry *ee =
+        hash_fetch(&export_tables[code_ix].htable,
+                   init_template(&templ, m, f, a),
+                   (H_FUN)export_hash, (HCMP_FUN)export_cmp);
+    if (ee) return ee->ep;
     return NULL;
 }
 
-static struct export_entry* init_template(struct export_templ* templ,
-					  Eterm m, Eterm f, unsigned a)
-{
-    templ->entry.ep = &templ->exp;
-    templ->entry.slot.index = -1;
-    templ->exp.info.mfa.module = m;
-    templ->exp.info.mfa.function = f;
-    templ->exp.info.mfa.arity = a;
-    return &templ->entry;
-}
-
-
 /*
  * Find the export entry for a loaded function.
  * Returns a NULL pointer if the given function is not loaded, or
diff --git a/erts/emulator/beam/hash.c b/erts/emulator/beam/hash.c
index cdab53b3f2..177b7cc3d1 100644
--- a/erts/emulator/beam/hash.c
+++ b/erts/emulator/beam/hash.c
@@ -225,16 +225,7 @@ static void rehash(Hash* h, int grow)
 */
 void* hash_get(Hash* h, void* tmpl)
 {
-    HashValue hval = h->fun.hash(tmpl);
-    int ix = hash_get_slot(h, hval);
-    HashBucket* b = h->bucket[ix];
-
-    while(b != (HashBucket*) 0) {
-	if ((b->hvalue == hval) && (h->fun.cmp(tmpl, (void*)b) == 0))
-	    return (void*) b;
-	b = b->next;
-    }
-    return (void*) 0;
+    return hash_fetch(h, tmpl, h->fun.hash, h->fun.cmp);
 }
 
 /*
diff --git a/erts/emulator/beam/hash.h b/erts/emulator/beam/hash.h
index cbd75f3025..4e8eb6594b 100644
--- a/erts/emulator/beam/hash.h
+++ b/erts/emulator/beam/hash.h
@@ -99,6 +99,7 @@ void* hash_remove(Hash*, void*);
 void  hash_foreach(Hash*, HFOREACH_FUN, void *);
 
 ERTS_GLB_INLINE Uint hash_get_slot(Hash *h, HashValue hv);
+ERTS_GLB_INLINE void* hash_fetch(Hash *, void*, H_FUN, HCMP_FUN);
 
 #if ERTS_GLB_INLINE_INCL_FUNC_DEF
 
@@ -127,6 +128,22 @@ hash_get_slot(Hash *h, HashValue hv)
 #endif
 }
 
+ERTS_GLB_INLINE void* hash_fetch(Hash *h, void* tmpl, H_FUN hash, HCMP_FUN cmp)
+{
+    HashValue hval = hash(tmpl);
+    Uint ix = hash_get_slot(h, hval);
+    HashBucket* b = h->bucket[ix];
+    ASSERT(h->fun.hash == hash);
+    ASSERT(h->fun.cmp == cmp);
+
+    while(b != (HashBucket*) 0) {
+	if ((b->hvalue == hval) && (cmp(tmpl, (void*)b) == 0))
+	    return (void*) b;
+	b = b->next;
+    }
+    return (void*) 0;
+}
+
 #endif /* ERTS_GLB_INLINE_INCL_FUNC_DEF */
 
 #endif
diff --git a/erts/emulator/beam/register.c b/erts/emulator/beam/register.c
index edf1e5b0cb..8e44b527a2 100644
--- a/erts/emulator/beam/register.c
+++ b/erts/emulator/beam/register.c
@@ -265,10 +265,8 @@ Eterm
 erts_whereis_name_to_id(Process *c_p, Eterm name)
 {
     Eterm res = am_undefined;
-    HashValue hval;
-    int ix;
-    HashBucket* b;
     ErtsProcLocks c_p_locks = 0;
+    RegProc *rp, tmpl;
     if (c_p) {
         c_p_locks = ERTS_PROC_LOCK_MAIN;
         ERTS_CHK_HAVE_ONLY_MAIN_PROC_LOCK(c_p);
@@ -278,29 +276,14 @@ erts_whereis_name_to_id(Process *c_p, Eterm name)
     if (c_p && !c_p_locks)
         erts_proc_lock(c_p, ERTS_PROC_LOCK_MAIN);
 
-    hval = REG_HASH(name);
-    ix = hash_get_slot(&process_reg, hval);
-    b = process_reg.bucket[ix];
+    tmpl.name = name;
+    rp = hash_fetch(&process_reg, &tmpl, (H_FUN)reg_hash, (HCMP_FUN)reg_cmp);
 
-    /*
-     * Note: We have inlined the code from hash.c for speed.
-     */
-	
-    while (b) {
-	RegProc* rp = (RegProc *) b;
-	if (rp->name == name) {
-	    /*
-	     * SMP NOTE: No need to lock registered entity since it cannot
-	     * be removed without acquiring write reg lock and id on entity
-	     * is read only.
-	     */
-	    if (rp->p)
-		res = rp->p->common.id;
-	    else if (rp->pt)
-		res = rp->pt->common.id;
-	    break;
-	}
-	b = b->next;
+    if (rp) {
+        if (rp->p)
+            res = rp->p->common.id;
+        else if (rp->pt)
+            res = rp->pt->common.id;
     }
 
     reg_read_unlock();
@@ -321,10 +304,7 @@ erts_whereis_name(Process *c_p,
 		  Port** port,
                   int lock_port)
 {
-    RegProc* rp = NULL;
-    HashValue hval;
-    int ix;
-    HashBucket* b;
+    RegProc* rp = NULL, tmpl;
     ErtsProcLocks current_c_p_locks;
     Port *pending_port = NULL;
 
@@ -342,21 +322,8 @@ erts_whereis_name(Process *c_p,
      * - current_c_p_locks (either c_p_locks or 0) on c_p
      */
 
-    hval = REG_HASH(name);
-    ix = hash_get_slot(&process_reg, hval);
-    b = process_reg.bucket[ix];
-
-    /*
-     * Note: We have inlined the code from hash.c for speed.
-     */
-
-    while (b) {
-	if (((RegProc *) b)->name == name) {
-	    rp = (RegProc *) b;
-	    break;
-	}
-	b = b->next;
-    }
+    tmpl.name = name;
+    rp = hash_fetch(&process_reg, &tmpl, (H_FUN)reg_hash, (HCMP_FUN)reg_cmp);
 
     if (proc) {
 	if (!rp)
-- 
2.16.4

openSUSE Build Service is sponsored by