File 0891-stdlib-ets_SUITE-fixtable_iter_bag.patch of Package erlang

From ea69ed4a5885281b01a774b3efbc87184fe6db5f Mon Sep 17 00:00:00 2001
From: Sverker Eriksson <sverker@erlang.org>
Date: Thu, 4 Jul 2019 18:17:29 +0200
Subject: [PATCH] stdlib: ets_SUITE:fixtable_iter_bag

Turns out the bug in ets:next() that I tried to provoke
with this new test wasn't really there. Oh well.
---
 erts/emulator/beam/erl_db_hash.c |   3 +-
 lib/stdlib/test/ets_SUITE.erl    | 134 ++++++++++++++++++++++++++++++++++++++-
 2 files changed, 134 insertions(+), 3 deletions(-)

diff --git a/erts/emulator/beam/erl_db_hash.c b/erts/emulator/beam/erl_db_hash.c
index 42d7909a08..73d74ba47f 100644
--- a/erts/emulator/beam/erl_db_hash.c
+++ b/erts/emulator/beam/erl_db_hash.c
@@ -762,7 +762,7 @@ static int db_next_hash(Process *p, DbTable *tbl, Eterm key, Eterm *ret)
     b = next(tb, &ix, &lck, b);
     if (tb->common.status & (DB_BAG | DB_DUPLICATE_BAG)) {
 	while (b != 0) {
-	    if (!has_live_key(tb, b, key, hval)) {
+	    if (!has_key(tb, b, key, hval)) {
 		break;
 	    }
 	    b = next(tb, &ix, &lck, b);
@@ -772,6 +772,7 @@ static int db_next_hash(Process *p, DbTable *tbl, Eterm key, Eterm *ret)
 	*ret = am_EOT;
     }
     else {
+        ASSERT(!is_pseudo_deleted(b));
 	*ret = db_copy_key(p, tbl, &b->dbterm);
 	RUNLOCK_HASH(lck);
     }    
diff --git a/lib/stdlib/test/ets_SUITE.erl b/lib/stdlib/test/ets_SUITE.erl
index 433b812fd5..dd94c1693b 100644
--- a/lib/stdlib/test/ets_SUITE.erl
+++ b/lib/stdlib/test/ets_SUITE.erl
@@ -46,7 +46,8 @@
 -export([do_lookup/2, do_lookup_element/3]).
 
 -export([ordered/1, ordered_match/1, interface_equality/1,
-	 fixtable_next/1, fixtable_insert/1, rename/1, rename_unnamed/1, evil_rename/1,
+	 fixtable_next/1, fixtable_iter_bag/1,
+         fixtable_insert/1, rename/1, rename_unnamed/1, evil_rename/1,
 	 update_element/1, update_counter/1, evil_update_counter/1, partly_bound/1, match_heavy/1]).
 -export([update_counter_with_default/1]).
 -export([update_counter_table_growth/1]).
@@ -138,7 +139,7 @@ all() ->
      {group, match}, t_match_spec_run,
      {group, lookup_element}, {group, misc}, {group, files},
      {group, heavy}, ordered, ordered_match,
-     interface_equality, fixtable_next, fixtable_insert,
+     interface_equality, fixtable_next, fixtable_iter_bag, fixtable_insert,
      rename, rename_unnamed, evil_rename, update_element,
      update_counter, evil_update_counter,
      update_counter_with_default, partly_bound,
@@ -2106,6 +2107,135 @@ do_fixtable_next(Tab) ->
     ?line false = ets:info(Tab, fixed),
     ?line ets:delete(Tab).
 
+%% Check that iteration of bags find all live objects and nothing else.
+fixtable_iter_bag(Config) when is_list(Config) ->
+    repeat_for_opts(fun fixtable_iter_do/1,
+                    [write_concurrency,[bag,duplicate_bag]]).
+
+fixtable_iter_do(Opts) ->
+    EtsMem = etsmem(),
+    do_fixtable_iter_bag(ets_new(fixtable_iter_bag,Opts)),
+    verify_etsmem(EtsMem).
+
+do_fixtable_iter_bag(T) ->
+    MaxValues = 4,
+    %% Create 1 to MaxValues objects for each key
+    %% and then delete every possible combination of those objects
+    %% in every possible order.
+    %% Then test iteration returns all live objects and nothing else.
+
+    CrDelOps = [begin
+                    Values = lists:seq(1,N),
+                    %% All ways of deleting any number of the Values in any order
+                    Combos = combs(Values),
+                    DeleteOps = concat_lists([perms(C) || C <- Combos]),
+                    {N, DeleteOps}
+                end
+                || N <- lists:seq(1,MaxValues)],
+
+    %%io:format("~p\n", [CrDelOps]),
+
+    NKeys = lists:foldl(fun({_, DeleteOps}, Cnt) ->
+                               Cnt + length(DeleteOps)
+                       end,
+                       0,
+                       CrDelOps),
+
+    io:format("Create ~p keys\n", [NKeys]),
+
+    %% Fixate even before inserts just to maintain small table size
+    %% and increase likelyhood of different keys in same bucket.
+    ets:safe_fixtable(T,true),
+    InsRes = [begin
+                  [begin
+                       Key = {NValues,ValueList},
+                       [begin
+                            Tpl = {Key, V},
+                            %%io:format("Insert object ~p", [Tpl]),
+                            ets:insert(T, Tpl),
+                            Tpl
+                        end
+                        || V <- lists:seq(1,NValues)]
+                   end
+                   || ValueList <- DeleteOps]
+              end
+              || {NValues, DeleteOps} <- CrDelOps],
+
+    Inserted = lists:flatten(InsRes),
+    InSorted = lists:sort(Inserted),
+    InSorted = lists:usort(Inserted),  %% No duplicates
+    NObjs = length(Inserted),
+
+    DelRes = [begin
+                  [begin
+                       Key = {NValues,ValueList},
+                       [begin
+                            Tpl = {Key, V},
+                            %%io:format("Delete object ~p", [Tpl]),
+                            ets:delete_object(T, Tpl),
+                            Tpl
+                        end
+                        || V <- ValueList]
+                   end
+                   || ValueList <- DeleteOps]
+              end
+              || {NValues, DeleteOps} <- CrDelOps],
+
+    Deleted = lists:flatten(DelRes),
+    DelSorted = lists:sort(Deleted),
+    DelSorted = lists:usort(Deleted),  %% No duplicates
+    NDels = length(Deleted),
+    
+    %% Nr of keys where all values were deleted.
+    NDeletedKeys = lists:sum([factorial(N) || N <- lists:seq(1,MaxValues)]),
+
+    CountKeysFun = fun Me(K1, Cnt) ->
+                           case ets:next(T, K1) of
+                               '$end_of_table' ->
+                                   Cnt;
+                               K2 ->
+                                   Objs = ets:lookup(T, K2),
+                                   [{{NValues, ValueList}, _V} | _] = Objs,
+                                   ExpectedLive = NValues - length(ValueList),
+                                   ExpectedLive = length(Objs),
+                                   Me(K2, Cnt+1)
+                           end
+                   end,
+
+    ExpectedKeys = NKeys - NDeletedKeys,
+    io:format("Expected keys: ~p\n", [ExpectedKeys]),
+    FoundKeys = CountKeysFun(ets:first(T), 1),
+    io:format("Found keys: ~p\n", [FoundKeys]),
+    ExpectedKeys = FoundKeys,
+
+    ExpectedObjs = NObjs - NDels,
+    io:format("Expected objects: ~p\n", [ExpectedObjs]),
+    FoundObjs = ets:select_count(T, [{{'_','_'}, [], [true]}]),
+    io:format("Found objects: ~p\n", [FoundObjs]),
+    ExpectedObjs = FoundObjs,
+
+    ets:delete(T).
+
+%% All permutations of list
+perms([]) -> [[]];
+perms(L)  -> [[H|T] || H <- L, T <- perms(L--[H])].
+
+%% All combinations of picking the element (or not) from list
+combs([]) -> [[]];
+combs([H|T]) ->
+    Tcombs = combs(T),
+    Tcombs ++ [[H | C] || C <- Tcombs].
+
+factorial(0) -> 1;
+factorial(N) when N > 0 ->
+    N * factorial(N - 1).
+
+concat_lists([]) ->
+    [];
+concat_lists([H|T]) ->
+    H ++ concat_lists(T).
+
+
 fixtable_insert(doc) ->    
     ["Check inserts of deleted keys in fixed bags"];
 fixtable_insert(suite) ->
-- 
2.16.4

openSUSE Build Service is sponsored by