File 2015-erts-Use-table-ref-for-select-continuation.patch of Package erlang

From 05ea5c89f2662e9bc042d3eac40e8a0c8b9f630f Mon Sep 17 00:00:00 2001
From: Sverker Eriksson <sverker@erlang.org>
Date: Mon, 12 Mar 2018 19:41:53 +0100
Subject: [PATCH 3/3] erts: Use table ref for select continuation

and not the name. For more sane named table semantics.

Applies to both select/1 continuation and trap context.
---
 erts/emulator/beam/erl_db.c      |  7 +++++++
 erts/emulator/beam/erl_db.h      |  1 +
 erts/emulator/beam/erl_db_hash.c | 26 ++++++++++++++++++++------
 lib/stdlib/test/ets_SUITE.erl    | 36 +++++++++++++++++++++++++++++++++++-
 4 files changed, 63 insertions(+), 7 deletions(-)

diff --git a/erts/emulator/beam/erl_db.c b/erts/emulator/beam/erl_db.c
index a76d769283..f7ee408991 100644
--- a/erts/emulator/beam/erl_db.c
+++ b/erts/emulator/beam/erl_db.c
@@ -283,6 +283,13 @@ make_tid(Process *c_p, DbTable *tb)
     return erts_mk_magic_ref(&hp, &c_p->off_heap, tb->common.btid);
 }
 
+Eterm
+erts_db_make_tid(Process *c_p, DbTableCommon *tb)
+{
+    return make_tid(c_p, (DbTable*)tb);
+}
+
+
 
 /* 
 ** The meta hash table of all NAMED ets tables
diff --git a/erts/emulator/beam/erl_db.h b/erts/emulator/beam/erl_db.h
index 318e90cb28..eb6da2c9fb 100644
--- a/erts/emulator/beam/erl_db.h
+++ b/erts/emulator/beam/erl_db.h
@@ -128,6 +128,7 @@ extern erts_atomic_t erts_ets_misc_mem_size;
 
 Eterm erts_ets_colliding_names(Process*, Eterm name, Uint cnt);
 Uint erts_db_get_max_tabs(void);
+Eterm erts_db_make_tid(Process *c_p, DbTableCommon *tb);
 
 #ifdef ERTS_ENABLE_LOCK_COUNT
 void erts_lcnt_enable_db_lock_count(DbTable *tb, int enable);
diff --git a/erts/emulator/beam/erl_db_hash.c b/erts/emulator/beam/erl_db_hash.c
index 014dc26414..cb5c496e90 100644
--- a/erts/emulator/beam/erl_db_hash.c
+++ b/erts/emulator/beam/erl_db_hash.c
@@ -1453,20 +1453,24 @@ static ERTS_INLINE int on_mtraversal_simple_trap(Export* trap_function,
 
     BUMP_ALL_REDS(p);
     if (IS_USMALL(0, got)) {
-	hp = HAlloc(p,  base_halloc_sz + 5);
+	hp = HAllocX(p,  base_halloc_sz + 5, ERTS_MAGIC_REF_THING_SIZE);
 	egot = make_small(got);
     }
     else {
-	hp = HAlloc(p, base_halloc_sz + BIG_UINT_HEAP_SIZE + 5);
+	hp = HAllocX(p, base_halloc_sz + BIG_UINT_HEAP_SIZE + 5,
+                     ERTS_MAGIC_REF_THING_SIZE);
 	egot = uint_to_big(got, hp);
 	hp += BIG_UINT_HEAP_SIZE;
     }
 
     if (is_first_trap) {
+        if (is_atom(tid))
+            tid = erts_db_make_tid(p, &tb->common);
         mpb = erts_db_make_match_prog_ref(p, *mpp, &hp);
         *mpp = NULL; /* otherwise the caller will destroy it */
     }
     else {
+        ASSERT(!is_atom(tid));
         mpb = prev_continuation_tptr[3];
     }
 
@@ -1580,11 +1584,17 @@ static int mtraversal_select_chunk_on_loop_ended(void* context_ptr, Sint slot_ix
                                              been in 'user space' */
             }
             if (rest != NIL || slot_ix >= 0) { /* Need more calls */
-                sc_context_ptr->hp = HAlloc(sc_context_ptr->p, 3 + 7 + ERTS_MAGIC_REF_THING_SIZE);
+                Eterm tid = sc_context_ptr->tid;
+                sc_context_ptr->hp = HAllocX(sc_context_ptr->p,
+                                             3 + 7 + ERTS_MAGIC_REF_THING_SIZE,
+                                             ERTS_MAGIC_REF_THING_SIZE);
                 mpb = erts_db_make_match_prog_ref(sc_context_ptr->p, *mpp, &sc_context_ptr->hp);
+                if (is_atom(tid))
+                    tid = erts_db_make_tid(sc_context_ptr->p,
+                                           &sc_context_ptr->tb->common);
                 continuation = TUPLE6(
                         sc_context_ptr->hp,
-                        sc_context_ptr->tid,
+                        tid,
                         make_small(slot_ix),
                         make_small(sc_context_ptr->chunk_size),
                         mpb, rest,
@@ -1621,12 +1631,16 @@ static int mtraversal_select_chunk_on_trap(void* context_ptr, Sint slot_ix, Sint
     BUMP_ALL_REDS(sc_context_ptr->p);
 
     if (sc_context_ptr->prev_continuation_tptr == NULL) {
+        Eterm tid = sc_context_ptr->tid;
         /* First time we're trapping */
-        hp = HAlloc(sc_context_ptr->p, 7 + ERTS_MAGIC_REF_THING_SIZE);
+        hp = HAllocX(sc_context_ptr->p, 7 + ERTS_MAGIC_REF_THING_SIZE,
+                     ERTS_MAGIC_REF_THING_SIZE);
+        if (is_atom(tid))
+            tid = erts_db_make_tid(sc_context_ptr->p, &sc_context_ptr->tb->common);
         mpb = erts_db_make_match_prog_ref(sc_context_ptr->p, *mpp, &hp);
         continuation = TUPLE6(
                 hp,
-                sc_context_ptr->tid,
+                tid,
                 make_small(slot_ix),
                 make_small(sc_context_ptr->chunk_size),
                 mpb,
diff --git a/lib/stdlib/test/ets_SUITE.erl b/lib/stdlib/test/ets_SUITE.erl
index ec4a16b510..02211fa8df 100644
--- a/lib/stdlib/test/ets_SUITE.erl
+++ b/lib/stdlib/test/ets_SUITE.erl
@@ -55,6 +55,7 @@
 -export([t_repair_continuation/1]).
 -export([t_match_spec_run/1]).
 -export([t_bucket_disappears/1]).
+-export([t_named_select/1]).
 -export([otp_5340/1]).
 -export([otp_6338/1]).
 -export([otp_6842_select_1000/1]).
@@ -125,6 +126,7 @@ all() ->
      t_select_replace_next_bug,
      t_select_pam_stack_overflow_bug,
      t_ets_dets, memory, t_select_reverse, t_bucket_disappears,
+     t_named_select,
      select_fail, t_insert_new, t_repair_continuation,
      otp_5340, otp_6338, otp_6842_select_1000, otp_7665,
      select_mbuf_trapping,
@@ -206,6 +208,38 @@ t_bucket_disappears_do(Opts) ->
     true = ets:delete(abcd),
     verify_etsmem(EtsMem).
 
+%% OTP-21: Test that select/1 fails if named table was deleted and recreated
+%%         and succeeds if table was renamed.
+t_named_select(_Config) ->
+    repeat_for_opts(fun t_named_select_do/1).
+
+t_named_select_do(Opts) ->
+    EtsMem = etsmem(),
+    T = t_name_tid_select,
+    ets_new(T, [named_table | Opts]),
+    ets:insert(T, {1,11}),
+    ets:insert(T, {2,22}),
+    ets:insert(T, {3,33}),
+    MS = [{{'$1', 22}, [], ['$1']}],
+    {[2], Cont1} = ets:select(T, MS, 1),
+    ets:delete(T),
+    {'EXIT',{badarg,_}} = (catch ets:select(Cont1)),
+    ets_new(T, [named_table | Opts]),
+    {'EXIT',{badarg,_}} = (catch ets:select(Cont1)),
+
+    true = ets:insert_new(T, {1,22}),
+    true = ets:insert_new(T, {2,22}),
+    true = ets:insert_new(T, {4,22}),
+    {[A,B], Cont2} = ets:select(T, MS, 2),
+    ets:rename(T, abcd),
+    {[C], '$end_of_table'} = ets:select(Cont2),
+    7 = A + B + C,
+
+    true = ets:delete(abcd),
+    verify_etsmem(EtsMem).
+
+
+
 
 %% Check ets:match_spec_run/2.
 t_match_spec_run(Config) when is_list(Config) ->
@@ -701,7 +735,7 @@ whitebox_2(Opts) ->
     ets:delete(T2),
     ok.
 
-select_bound_chunk(Config) ->
+select_bound_chunk(_Config) ->
     repeat_for_opts(fun select_bound_chunk_do/1, [all_types]).
 
 select_bound_chunk_do(Opts) ->
-- 
2.16.3

openSUSE Build Service is sponsored by