File 0311-erts-Display-large-maps-similarly-to-small-maps.patch of Package erlang

From f8a11c5c5fb67875bd4769ebfbd57a07be76349a Mon Sep 17 00:00:00 2001
From: Magnus Thoang <magnusthoang@gmail.com>
Date: Tue, 22 Nov 2022 22:55:56 +0100
Subject: [PATCH] [erts] Display large maps similarly to small maps

The formatting of large maps done by erlang:display/1 used to reveal
interesting information about the map internals, but was difficult to
read, compared to the formatting of small maps, and did not represent a
map in proper erlang syntax. This commit aims at a formatting that is
proper erlang syntax, still without any sorting of elements.
---
 erts/emulator/beam/erl_printf_term.c | 58 +++++++++++++++-------
 erts/emulator/test/map_SUITE.erl     | 72 ++++++++++++++++++++++++++--
 2 files changed, 111 insertions(+), 19 deletions(-)

diff --git a/erts/emulator/beam/erl_printf_term.c b/erts/emulator/beam/erl_printf_term.c
index 24d6032012..bc87f99a2a 100644
--- a/erts/emulator/beam/erl_printf_term.c
+++ b/erts/emulator/beam/erl_printf_term.c
@@ -726,41 +726,67 @@ print_term(fmtfn_t fn, void* arg, Eterm obj, long *dcount) {
                 switch (MAP_HEADER_TYPE(*head)) {
                 case MAP_HEADER_TAG_HAMT_HEAD_ARRAY:
                 case MAP_HEADER_TAG_HAMT_HEAD_BITMAP:
-                    PRINT_STRING(res, fn, arg, "#<");
-                    PRINT_UWORD(res, fn, arg, 'x', 0, 1, mapval);
-                    PRINT_STRING(res, fn, arg, ">{");
-                    WSTACK_PUSH(s,PRT_CLOSE_TUPLE);
+                    PRINT_STRING(res, fn, arg, "#{");
+                    WSTACK_PUSH(s, PRT_CLOSE_TUPLE);
                     n = hashmap_bitcount(mapval);
                     ASSERT(n < 17);
                     head += 2;
                     if (n > 0) {
+			Eterm* assoc;
+			Eterm key, val;
                         n--;
-                        WSTACK_PUSH(s, head[n]);
-                        WSTACK_PUSH(s, PRT_TERM);
-                        while (n--) {
-                            WSTACK_PUSH(s, PRT_COMMA);
+                        if (is_list(head[n])) {
+                            assoc = list_val(head[n]);
+                            key = CAR(assoc);
+                            val = CDR(assoc);
+                            WSTACK_PUSH5(s, val, PRT_TERM, PRT_ASSOC, key, PRT_TERM);
+                        } else {
                             WSTACK_PUSH(s, head[n]);
                             WSTACK_PUSH(s, PRT_TERM);
+			}
+                        while (n--) {
+                            if (is_list(head[n])) {
+                                assoc = list_val(head[n]);
+                                key = CAR(assoc);
+                                val = CDR(assoc);
+                                WSTACK_PUSH6(s, PRT_COMMA, val, PRT_TERM, PRT_ASSOC, key, PRT_TERM);
+                            } else {
+                                WSTACK_PUSH(s, PRT_COMMA);
+                                WSTACK_PUSH(s, head[n]);
+                                WSTACK_PUSH(s, PRT_TERM);
+                            }
                         }
                     }
                     break;
                 case MAP_HEADER_TAG_HAMT_NODE_BITMAP:
                     n = hashmap_bitcount(mapval);
                     head++;
-                    PRINT_CHAR(res, fn, arg, '<');
-                    PRINT_UWORD(res, fn, arg, 'x', 0, 1, mapval);
-                    PRINT_STRING(res, fn, arg, ">{");
-                    WSTACK_PUSH(s,PRT_CLOSE_TUPLE);
                     ASSERT(n < 17);
                     if (n > 0) {
+			Eterm* assoc;
+			Eterm key, val;
                         n--;
-                        WSTACK_PUSH(s, head[n]);
-                        WSTACK_PUSH(s, PRT_TERM);
-                        while (n--) {
-                            WSTACK_PUSH(s, PRT_COMMA);
+                        if (is_list(head[n])) {
+                            assoc = list_val(head[n]);
+                            key = CAR(assoc);
+                            val = CDR(assoc);
+                            WSTACK_PUSH5(s, val, PRT_TERM, PRT_ASSOC, key, PRT_TERM);
+                        } else {
                             WSTACK_PUSH(s, head[n]);
                             WSTACK_PUSH(s, PRT_TERM);
                         }
+                        while (n--) {
+                            if (is_list(head[n])) {
+                                assoc = list_val(head[n]);
+                                key = CAR(assoc);
+                                val = CDR(assoc);
+                                WSTACK_PUSH6(s, PRT_COMMA, val, PRT_TERM, PRT_ASSOC, key, PRT_TERM);
+                            } else {
+                                WSTACK_PUSH(s, PRT_COMMA);
+                                WSTACK_PUSH(s, head[n]);
+                                WSTACK_PUSH(s, PRT_TERM);
+                            }
+                        }
                     }
                     break;
                 }
diff --git a/erts/emulator/test/map_SUITE.erl b/erts/emulator/test/map_SUITE.erl
index 8769dea81f..7fb2961cad 100644
--- a/erts/emulator/test/map_SUITE.erl
+++ b/erts/emulator/test/map_SUITE.erl
@@ -88,8 +88,11 @@
          t_get_map_elements/1,
          y_regs/1,
 
-         %%Bugs
-         t_large_unequal_bins_same_hash_bug/1]).
+         %% Bugs
+         t_large_unequal_bins_same_hash_bug/1,
+
+	 %% Display
+	 t_map_display/1]).
 
 %% Benchmarks
 -export([benchmarks/1]).
@@ -168,7 +171,10 @@ groups() ->
        y_regs,
 
        %% Bugs
-       t_large_unequal_bins_same_hash_bug]},
+       t_large_unequal_bins_same_hash_bug,
+
+       %% Display
+       t_map_display]},
     {benchmarks, [{repeat,10}], [benchmarks]}].
 
 run_once() ->
@@ -3498,6 +3504,8 @@ t_large_unequal_bins_same_hash_bug(Config) when is_list(Config) ->
               io:format("~p ~p~n", [erlang:phash2(Map3), maps:size(Map3)])
       end).
 
+
+
 make_map(0) -> 
     #{};
 make_map(Size) ->
@@ -3542,6 +3550,64 @@ total_memory() ->
 	    undefined
     end.
 
+%% This test case checks that maps larger than 32 elements are readable
+%% when displayed.
+t_map_display(Config) when is_list(Config) ->
+    verify_map_term(make_nontrivial_map(33)),
+    verify_map_term(make_nontrivial_map(253)),
+    verify_map_term({a, make_nontrivial_map(77)}),
+    verify_map_term([make_nontrivial_map(42),
+                     {a,make_nontrivial_map(99)},
+                     make_nontrivial_map(77)]),
+
+    ok.
+
+make_nontrivial_map(N) ->
+    make_nontrivial_map(N, 32).
+
+make_nontrivial_map(N, Effort) ->
+    L = [begin
+             Key = case I rem 64 of
+                       33 when Effort > 16 ->
+                           make_nontrivial_map(I, Effort div 2);
+                       _ ->
+                           I
+                   end,
+             Value = case I rem 5 of
+                         0 ->
+                             I * I;
+                         1 ->
+                             if
+                                 Effort > 16 ->
+                                     make_nontrivial_map(33, Effort div 2);
+                                 true ->
+                                     make_map(Effort)
+                             end;
+                         2 ->
+                             lists:seq(0, I rem 16);
+                         3 ->
+                             list_to_tuple(lists:seq(0, I rem 16));
+                         4 ->
+                             float(I)
+                     end,
+             {Key, Value}
+         end || I <- lists:seq(1, N)],
+    maps:from_list(L).
+
+verify_map_term(Term) ->
+    Printed = string:chomp(erts_debug:display(Term)),
+    {ok,Tokens,1} = erl_scan:string(Printed ++ "."),
+    {ok,ParsedTerm} = erl_parse:parse_term(Tokens),
+
+    case ParsedTerm of
+        Term ->
+            ok;
+        Other ->
+            io:format("Expected:\n~p\n", [Term]),
+            io:format("Got:\n~p", [Other]),
+            ct:fail(failed)
+    end.
+
 %%%
 %%% Benchmarks
 %%%
-- 
2.35.3

openSUSE Build Service is sponsored by