No build reason found for pool:s390x

File 1372-erts-Fix-db_match-hashmap-copy-bug.patch of Package erlang

From c7dbdaa611f7306d4173188c2284d46a6b324d24 Mon Sep 17 00:00:00 2001
From: Lukas Larsson <lukas@erlang.org>
Date: Mon, 2 Oct 2023 16:59:38 +0200
Subject: [PATCH 2/2] erts: Fix db_match hashmap copy bug

If the body of a matchspec would return a hashmap with
a variable ('$1', '$_' etc) as one of the keys or values
and the variable was not an immidiate, the term would not
be copied to the receiving processes heap. This would
later corrupt the term in the table as the GC could
place move markers in it.

Also fixed an issue with the stack-estimation logic for
when such a hashmap was encountered.

Closes: #7683
---
 erts/emulator/beam/erl_db_util.c | 101 ++++++++++++++++++++++++------
 lib/stdlib/test/ets_SUITE.erl    | 104 +++++++++++++++++++++++++++++++
 2 files changed, 186 insertions(+), 19 deletions(-)

diff --git a/erts/emulator/beam/erl_db_util.c b/erts/emulator/beam/erl_db_util.c
index 98cde1a030..acaff470ff 100644
--- a/erts/emulator/beam/erl_db_util.c
+++ b/erts/emulator/beam/erl_db_util.c
@@ -3977,9 +3977,9 @@ dmc_map(DMCContext *context, DMCHeap *heap, DMC_STACK_TYPE(UWord) *text,
         Eterm t, int *constant)
 {
     int nelems;
-    int constant_values, constant_keys;
     DMCRet ret;
     if (is_flatmap(t)) {
+        int constant_values, constant_keys;
         flatmap_t *m = (flatmap_t *)flatmap_val(t);
         Eterm *values = flatmap_get_values(m);
         int textpos = DMC_STACK_NUM(*text);
@@ -4030,54 +4030,114 @@ dmc_map(DMCContext *context, DMCHeap *heap, DMC_STACK_TYPE(UWord) *text,
         return retOk;
     } else {
         DECLARE_WSTACK(wstack);
+        DMC_STACK_TYPE(UWord) instr_save;
         Eterm *kv;
-        int c;
+        int c = 0;
         int textpos = DMC_STACK_NUM(*text);
-        int stackpos = context->stack_used;
+        int preventive_bumps = 0;
 
         ASSERT(is_hashmap(t));
 
         hashmap_iterator_init(&wstack, t, 1);
-        constant_values = 1;
         nelems = hashmap_size(t);
 
-        /* Check if all keys and values are constants */
-        while ((kv=hashmap_iterator_prev(&wstack)) != NULL && constant_values) {
+        /* Check if all keys and values are constants. We do preventive_bumps for
+           all constants we find so that if we find a non-constant, the stack
+           depth will be correct. */
+        while ((kv=hashmap_iterator_prev(&wstack)) != NULL) {
             if ((ret = dmc_expr(context, heap, text, CAR(kv), &c)) != retOk) {
                 DESTROY_WSTACK(wstack);
                 return ret;
             }
-            if (!c)
-                constant_values = 0;
+
+            if (!c) break;
+
+            ++context->stack_used;
+            ++preventive_bumps;
+
             if ((ret = dmc_expr(context, heap, text, CDR(kv), &c)) != retOk) {
                 DESTROY_WSTACK(wstack);
                 return ret;
             }
-            if (!c)
-                constant_values = 0;
+                        
+            if (!c) break;
+
+            ++context->stack_used;
+            ++preventive_bumps;
+            
         }
 
-        if (constant_values) {
+        context->stack_used -= preventive_bumps;
+
+        /* c is true if we iterated through the entire hashmap without
+           encountering any variables */
+        if (c) {
             ASSERT(DMC_STACK_NUM(*text) == textpos);
             *constant = 1;
             DESTROY_WSTACK(wstack);
             return retOk;
         }
 
-        /* reset the program to the original position and re-emit everything */
-        DMC_STACK_NUM(*text) = textpos;
-        context->stack_used = stackpos;
+        /* Reset the iterator */
+        hashmap_iterator_init(&wstack, t, 1);
 
-        *constant = 0;
+        /* If we found any constants before the variable. */
+        if (preventive_bumps != 0) {
 
-        hashmap_iterator_init(&wstack, t, 1);
+            /* Save all the instructions needed for the non-constant we
+               found in the body. */
+            DMC_INIT_STACK(instr_save);
+            while (DMC_STACK_NUM(*text) > textpos) {
+                DMC_PUSH(instr_save, DMC_POP(*text));
+            }
 
-        while ((kv=hashmap_iterator_prev(&wstack)) != NULL) {
-            /* push key */
-            if ((ret = dmc_expr(context, heap, text, CAR(kv), &c)) != retOk) {
+            /* Re-emit all the constants, we use the preventive_bumps counter to
+               know how many constants we found before the first variable. */
+            while ((kv=hashmap_iterator_prev(&wstack)) != NULL) {
+                do_emit_constant(context, text, CAR(kv));
+                if (--preventive_bumps == 0) {
+                    break;
+                }
+                do_emit_constant(context, text, CDR(kv));
+                if (--preventive_bumps == 0) {
+                    preventive_bumps = -1;
+                    break;
+                }
+            }
+
+            /* Emit the non-constant we found */
+            while(!DMC_EMPTY(instr_save)) {
+                DMC_PUSH(*text, DMC_POP(instr_save));
+            }
+
+            DMC_FREE(instr_save);
+
+        } else {
+            preventive_bumps = -1;
+        }
+
+        /* If the first variable was a key, we skip the key this iteration
+           and only emit only the value (CDR). */
+        if (preventive_bumps == -1) {
+            kv=hashmap_iterator_prev(&wstack);
+            if ((ret = dmc_expr(context, heap, text, CDR(kv), &c)) != retOk) {
                 DESTROY_WSTACK(wstack);
                 return ret;
             }
+            if (c) {
+                do_emit_constant(context, text, CDR(kv));
+            }
+        }
+
+        /* Emit the remaining key-value pairs in the hashmap */
+        while ((kv=hashmap_iterator_prev(&wstack)) != NULL) {
+        
+            /* push key */
+            if ((ret = dmc_expr(context, heap, text, CAR(kv), &c)) != retOk) {
+                    DESTROY_WSTACK(wstack);
+                    return ret;
+                }
+
             if (c) {
                 do_emit_constant(context, text, CAR(kv));
             }
@@ -4087,13 +4147,16 @@ dmc_map(DMCContext *context, DMCHeap *heap, DMC_STACK_TYPE(UWord) *text,
                 DESTROY_WSTACK(wstack);
                 return ret;
             }
+            
             if (c) {
                 do_emit_constant(context, text, CDR(kv));
             }
         }
+        ASSERT(preventive_bumps <= 0);
         DMC_PUSH2(*text, matchMkHashMap, nelems);
         context->stack_used -= 2*nelems - 1;  /* n keys & values => 1 map */
         DESTROY_WSTACK(wstack);
+        *constant = 0;
         return retOk;
     }
 }
diff --git a/lib/stdlib/test/ets_SUITE.erl b/lib/stdlib/test/ets_SUITE.erl
index 1e823e0b1c..d322521a0e 100644
--- a/lib/stdlib/test/ets_SUITE.erl
+++ b/lib/stdlib/test/ets_SUITE.erl
@@ -45,6 +45,7 @@
 	 t_select_delete/1,t_select_replace/1,t_select_replace_next_bug/1,
          t_select_pam_stack_overflow_bug/1,
          t_select_flatmap_term_copy_bug/1,
+         t_select_hashmap_term_copy_bug/1,
          t_ets_dets/1]).
 -export([t_insert_list/1, t_insert_list_bag/1, t_insert_list_duplicate_bag/1,
          t_insert_list_set/1, t_insert_list_delete_set/1,
@@ -154,6 +155,7 @@ all() ->
      t_select_replace_next_bug,
      t_select_pam_stack_overflow_bug,
      t_select_flatmap_term_copy_bug,
+     t_select_hashmap_term_copy_bug,
      t_ets_dets, memory, t_select_reverse, t_bucket_disappears,
      t_named_select, select_fixtab_owner_change,
      select_fail, t_insert_new, t_repair_continuation,
@@ -1939,6 +1941,108 @@ t_select_flatmap_term_copy_bug(_Config) ->
     ets:delete(T),
     ok.
 
+%% When a variable was used as key or value in ms body,
+%% the matched value would not be copied to the heap of
+%% the calling process.
+t_select_hashmap_term_copy_bug(_Config) ->
+
+    T = ets:new(a,[]),
+    Dollar1 = list_to_binary(lists:duplicate(36,$a)),
+    ets:insert(T, {Dollar1}),
+
+    {LargeMapSize, FlatmapSize} =
+        case erlang:system_info(emu_type) of
+            debug -> {40, 3};
+            _ -> {250, 32}
+        end,
+
+    LM = maps:from_keys(lists:seq(1,LargeMapSize), 1),
+
+    lists:foreach(
+      fun(Key) ->
+              V = ets:select(T, [{{'$1'},[], [LM#{ Key => '$1' }]}]),
+              erlang:garbage_collect(),
+              V = ets:select(T, [{{'$1'},[], [LM#{ Key => '$1' }]}]),
+              erlang:garbage_collect(),
+
+              V = [LM#{ Key => Dollar1 }]
+      end, maps:keys(LM)),
+    
+    %% Create a hashmap with enough keys before and after the '$1' for it to
+    %% remain a hashmap when we remove those keys.
+    LMWithDollar = make_lm_with_dollar(LM#{ '$1' => a }, LargeMapSize, FlatmapSize),
+
+    %% Test that hashmap with '$1' in first position works
+    %% We rely on that fact that maps:keys return the keys
+    %% in iteration order.
+    lists:foldl(
+      fun
+          (Key, M = #{ '$1' := A }) when map_size(M) > FlatmapSize ->
+
+              V = ets:select(T, [{{'$1'},[], [M]}]),
+              erlang:garbage_collect(),
+              V = ets:select(T, [{{'$1'},[], [M]}]),
+              erlang:garbage_collect(),
+
+              V = [(maps:remove('$1',M))#{ Dollar1 => A }],
+
+              maps:remove(Key, M);
+          (_, M) when map_size(M) > FlatmapSize ->
+              M
+      end, LMWithDollar, maps:keys(LMWithDollar)),
+
+    %% Test that hashmap with '$1' in last position works
+    %% We rely on that fact that maps:keys return the keys
+    %% in iteration order.
+    lists:foldl(
+      fun
+          (Key, M = #{ '$1' := A }) ->
+
+              V = ets:select(T, [{{'$1'},[], [M]}]),
+              erlang:garbage_collect(),
+              V = ets:select(T, [{{'$1'},[], [M]}]),
+              erlang:garbage_collect(),
+
+              V = [(maps:remove('$1',M))#{ Dollar1 => A }],
+
+              maps:remove(Key, M);
+          (_, M) when map_size(M) > FlatmapSize ->
+              M
+      end, LMWithDollar, lists:reverse(maps:keys(LMWithDollar))),
+    
+    %% Test hashmap with a key-value pair that are variable
+    V3 = ets:select(T, [{{'$1'},[], [LM#{ '$1' => '$1' }]}]),
+    erlang:garbage_collect(),
+    V3 = ets:select(T, [{{'$1'},[], [LM#{ '$1' => '$1' }]}]),
+    erlang:garbage_collect(),
+
+    V3 = [LM#{ Dollar1 => Dollar1 }],
+
+    %% Test hashmap with all constant keys and values
+    V4 = ets:select(T, [{{'$1'},[], [LM#{ a => a }]}]),
+    erlang:garbage_collect(),
+    V4 = ets:select(T, [{{'$1'},[], [LM#{ a => a }]}]),
+    erlang:garbage_collect(),
+
+    V4 = [LM#{ a => a }],
+
+    ets:delete(T),
+    ok.
+
+%% Create a hashmap that always has FlatmapSize keys before and after '$1'.
+%% Since the atom index of '$1' is used as hash, we cannot know before the
+%% code is run where exactly it will be placed, so in the rare cases when
+%% there isn't enough keys in the map, we insert more until there are enough.
+make_lm_with_dollar(Map, LargeMapSize, FlatmapSize) ->
+    {KeysBefore, KeysAfter} = lists:splitwith(fun erlang:is_integer/1, maps:keys(Map)),
+    if length(KeysBefore) =< FlatmapSize;
+       length(KeysAfter) - 1 =< FlatmapSize ->
+            NewMap = maps:from_keys(lists:seq(LargeMapSize, LargeMapSize*2), 1),
+            make_lm_with_dollar(maps:merge(Map, NewMap), LargeMapSize*2, FlatmapSize);
+       true ->
+            Map
+    end.
+
 %% Test that partly bound keys gives faster matches.
 partly_bound(Config) when is_list(Config) ->
     case os:type() of
-- 
2.35.3

openSUSE Build Service is sponsored by