File 0365-erts-Fix-persistent_term_SUITE.patch of Package erlang

From 57a801a7f72eb6fad1d49bebda5baedcb7f88d64 Mon Sep 17 00:00:00 2001
From: Sverker Eriksson <sverker@erlang.org>
Date: Tue, 11 Aug 2020 16:37:15 +0200
Subject: [PATCH] erts: Fix persistent_term_SUITE

to accept memory growth due to hash table hysteresis.
---
 erts/emulator/beam/erl_bif_info.c            |  3 ++
 erts/emulator/beam/erl_bif_persistent.c      | 14 ++++++++
 erts/emulator/beam/global.h                  |  1 +
 erts/emulator/test/persistent_term_SUITE.erl | 37 +++++++++++++++++---
 4 files changed, 51 insertions(+), 4 deletions(-)

diff --git a/erts/emulator/beam/erl_bif_info.c b/erts/emulator/beam/erl_bif_info.c
index d65aa71085..5944497b1f 100644
--- a/erts/emulator/beam/erl_bif_info.c
+++ b/erts/emulator/beam/erl_bif_info.c
@@ -4079,6 +4079,9 @@ BIF_RETTYPE erts_debug_get_internal_state_1(BIF_ALIST_1)
 		BIF_RET(uword_to_big((UWord)mem, hp));
             }
         }
+        else if (ERTS_IS_ATOM_STR("persistent_term", BIF_ARG_1)) {
+            BIF_RET(erts_debug_persistent_term_xtra_info(BIF_P));
+        }
     }
     else if (is_tuple(BIF_ARG_1)) {
 	Eterm* tp = tuple_val(BIF_ARG_1);
diff --git a/erts/emulator/beam/erl_bif_persistent.c b/erts/emulator/beam/erl_bif_persistent.c
index 91cc03fe57..461e8862d8 100644
--- a/erts/emulator/beam/erl_bif_persistent.c
+++ b/erts/emulator/beam/erl_bif_persistent.c
@@ -1481,3 +1481,17 @@ erts_debug_foreach_persistent_term_off_heap(void (*func)(ErlOffHeap *, void *),
     accessed_literal_areas = NULL;
 }
 
+Eterm erts_debug_persistent_term_xtra_info(Process* c_p)
+{
+    HashTable* hash_table = (HashTable *) erts_atomic_read_nob(&the_hash_table);
+    Uint hsz = MAP_SZ(1);
+    Eterm *hp;
+    Eterm buckets, res;
+
+    (void) erts_bld_uint(NULL, &hsz, hash_table->allocated);
+    hp = HAlloc(c_p, hsz);
+    buckets = erts_bld_uint(&hp, NULL, hash_table->allocated);
+    res = MAP1(hp, am_table, buckets);
+    BIF_RET(res);
+}
+
diff --git a/erts/emulator/beam/global.h b/erts/emulator/beam/global.h
index 5e3c283846..179cc287da 100644
--- a/erts/emulator/beam/global.h
+++ b/erts/emulator/beam/global.h
@@ -1313,6 +1313,7 @@ void erts_debug_foreach_persistent_term_off_heap(void (*func)(ErlOffHeap *, void
                                                  void *arg);
 int erts_debug_have_accessed_literal_area(ErtsLiteralArea *lap);
 void erts_debug_save_accessed_literal_area(ErtsLiteralArea *lap);
+Eterm erts_debug_persistent_term_xtra_info(Process* c_p);
 
 /* external.c */
 void erts_init_external(void);
diff --git a/erts/emulator/test/persistent_term_SUITE.erl b/erts/emulator/test/persistent_term_SUITE.erl
index f4511eb483..836a85d5b6 100644
--- a/erts/emulator/test/persistent_term_SUITE.erl
+++ b/erts/emulator/test/persistent_term_SUITE.erl
@@ -685,18 +685,47 @@ do_test_init_restart_cmd(File) ->
 %% and after each test case.
 
 chk() ->
-    {persistent_term:info(), persistent_term:get()}.
+    {xtra_info(), persistent_term:get()}.
 
-chk({Info, _Initial} = Chk) ->
-    Info = persistent_term:info(),
+chk({Info1, _Initial} = Chk) ->
+    #{count := Count, memory := Memory1, table := Table1} = Info1,
+    case xtra_info() of
+        Info1 ->
+            ok;
+        #{count := Count, memory := Memory2, table := Table2}=Info2
+          when Memory2 > Memory1,
+               Table2 > Table1 ->
+            %% Check increased memory is only table growth hysteresis
+            MemDiff = Memory2 - Memory1,
+            TabDiff = (Table2 - Table1) * erlang:system_info(wordsize),
+            {MemDiff,MemDiff} = {MemDiff, TabDiff},
+
+            case (Count / Table2) of
+                Load when Load >= 0.25 ->
+                    ok;
+                _ ->
+                    chk_fail("Hash table too large", Info1, Info2)
+            end;
+        Info2 ->
+            chk_fail("Memory diff", Info1, Info2)
+    end,
     Key = {?MODULE,?FUNCTION_NAME},
-    ok = persistent_term:put(Key, {term,Info}),
+    ok = persistent_term:put(Key, {term,Info1}),
     Term = persistent_term:get(Key),
     true = persistent_term:erase(Key),
     chk_not_stuck(Term, 1),
     [persistent_term:erase(K) || {K, _} <- pget(Chk)],
     ok.
 
+xtra_info() ->
+    maps:merge(persistent_term:info(),
+               erts_debug:get_internal_state(persistent_term)).
+
+chk_fail(Error, Info1, Info2) ->
+    io:format("Info1 = ~p\n", [Info1]),
+    io:format("Info2 = ~p\n", [Info2]),
+    ct:fail(Error).
+
 chk_not_stuck(Term, Timeout) ->
     %% Hash tables to be deleted are put onto a queue.
     %% Make sure that the queue isn't stuck by a table with
-- 
2.26.2

openSUSE Build Service is sponsored by