File 7511-Add-support-for-map-terms-in-ei_x_format-_wo_ver.patch of Package erlang

From 5c05c1e64441c3d5b22bd4282ebeeeab3129059c Mon Sep 17 00:00:00 2001
From: Anton Filippov <anton@filippov.im>
Date: Wed, 30 Aug 2023 11:23:30 +0700
Subject: [PATCH] Add support for map terms in ei_x_format(_wo_ver)

Co-authored-by: Sverker Eriksson <sverker@erlang.org>
---
 lib/erl_interface/doc/src/ei.xml              |  6 ++
 lib/erl_interface/src/misc/ei_format.c        | 58 +++++++++++++++++++
 lib/erl_interface/test/ei_format_SUITE.erl    | 44 +++++++++++++-
 .../ei_format_SUITE_data/ei_format_test.c     | 40 ++++++++++++-
 4 files changed, 143 insertions(+), 5 deletions(-)

diff --git a/lib/erl_interface/doc/src/ei.xml b/lib/erl_interface/doc/src/ei.xml
index 9161279ef7..d17e7a8a7c 100644
--- a/lib/erl_interface/doc/src/ei.xml
+++ b/lib/erl_interface/doc/src/ei.xml
@@ -1276,6 +1276,12 @@ ei_x_format("{~a,~i,~d}", "numbers", 12, 3.14159)
 encodes the tuple {numbers,12,3.14159}</pre>
         <p><c>ei_x_format_wo_ver()</c> formats into a buffer,
           without the initial version byte.</p>
+	<change>
+          <p>
+	    Since OTP 27.0 maps can be encoded with syntax like
+	    <c>"#{k1 => v1, k2 => v2}"</c>.
+	  </p>
+        </change>
       </desc>
     </func>
 
diff --git a/lib/erl_interface/src/misc/ei_format.c b/lib/erl_interface/src/misc/ei_format.c
index 68a3a2ad94..80feb6b933 100644
--- a/lib/erl_interface/src/misc/ei_format.c
+++ b/lib/erl_interface/src/misc/ei_format.c
@@ -62,6 +62,7 @@ static int pquotedatom(const char** fmt, ei_x_buff* x);
 static int pdigit(const char** fmt, ei_x_buff* x);
 static int patom(const char** fmt, ei_x_buff* x);
 static int pstring(const char** fmt, ei_x_buff* x);
+static int pmap(const char ** fmt, union arg **, ei_x_buff * x);
 
 /* format a string into an ei_x_buff, except the version token */
 static int eiformat(const char** fmt, union arg** args, ei_x_buff* x)
@@ -102,6 +103,19 @@ static int eiformat(const char** fmt, union arg** args, ei_x_buff* x)
     case '\'':
 	res = pquotedatom(&p, x);
 	break;
+    case '#':
+	if (*(p + 1) == '{') {
+            p += 2;
+	    res = ei_x_new(&x2);
+	    if (res >= 0)
+                res = pmap(&p, args, &x2);
+	    if (res >= 0)
+		res = ei_x_encode_map_header(x, res);
+	    if (res >= 0)
+		res = ei_x_append(x, &x2);
+	    ei_x_free(&x2);
+	    break;
+	}
     default:
 	if (isdigit((int)*p))
 	    res = pdigit(&p, x);
@@ -374,6 +388,50 @@ static int plist(const char** fmt, union arg** args, ei_x_buff* x, int size)
     return res;
 }
 
+/* encode a map */
+static int pmap(const char ** fmt, union arg ** args, ei_x_buff * x)
+{
+    const char * p = *fmt;
+    int size = 0;
+
+    while (isspace(*p))
+        ++p;
+
+    if (*p == '}') {
+	*fmt = p+1;
+	return size;
+    }
+
+    for(;;) {
+        /* Key */
+        if (eiformat(&p, args, x) < 0)
+            return -1;
+        while (isspace(*p))
+            ++p;
+
+        if (!(p[0] == '=' && p[1] == '>')) {
+            return -1;
+        }
+        p += 2;
+
+        /* Value */
+        if (eiformat(&p, args, x) < 0)
+            return -1;
+        while (isspace(*p))
+            ++p;
+
+        ++size;
+        if (*p == '}') {
+            *fmt = p+1;
+            return size;
+        }
+        if (*p++ != ',')
+            return -1;
+        while (isspace((int)*p))
+            ++p;
+    }
+}
+
 static int read_args(const char* fmt, va_list ap, union arg **argp)
 {
     const char* p = fmt;
diff --git a/lib/erl_interface/test/ei_format_SUITE.erl b/lib/erl_interface/test/ei_format_SUITE.erl
index e074c184c1..1d84111ec7 100644
--- a/lib/erl_interface/test/ei_format_SUITE.erl
+++ b/lib/erl_interface/test/ei_format_SUITE.erl
@@ -29,7 +29,8 @@
          init_per_testcase/2,
          atoms/1,
          tuples/1,
-         lists/1]).
+         lists/1,
+         maps/1]).
 
 -import(runner, [get_term/1]).
 
@@ -40,7 +41,7 @@ suite() ->
     [{ct_hooks,[ts_install_cth]}].
 
 all() -> 
-    [format_wo_ver, atoms, tuples, lists].
+    [format_wo_ver, atoms, tuples, lists, maps].
 
 init_per_testcase(Case, Config) ->
     runner:init_per_testcase(?MODULE, Case, Config).
@@ -100,6 +101,8 @@ tuples(Config) when is_list(Config) ->
     {term, {[], a, b, c}} = get_term(P),
     {term, {[], a, [], b, c}} = get_term(P),
     {term, {[], a, '', b, c}} = get_term(P),
+    {term, {[], a, '', b, M}} = get_term(P),
+    #{c:=3} = M,
 
     runner:recv_eot(P),
     ok.
@@ -123,6 +126,8 @@ lists(Config) when is_list(Config) ->
     {term, [[], a, '', b, c]} = get_term(P),
     {term, [[x, 2], [y, 3], [z, 4]]}= get_term(P),
     {term, [{a,b},{c,d}]} = get_term(P),
+    {term, [{a,b},M]} = get_term(P),
+    #{c:=d} = M,
     %% {term, [{name, 'Madonna'}, {age, 21}, {data, [{addr, "E-street", 42}]}]} = get_term(P),
 
     {term, [{pi, F1}, {'cos(70)', F2}]} = get_term(P),
@@ -149,10 +154,43 @@ lists(Config) when is_list(Config) ->
     ok.
 
 
+%% Tests formatting various maps
+
+maps(Config) when is_list(Config) ->
+    P = runner:start(Config, ?maps),
+
+    {term, M1} = get_term(P),
+    0 = maps:size(M1),
+    {term, M1} = get_term(P),
+
+    {term, M2} = get_term(P),
+    true = (M2 =:= #{a => 1}),
+    {term, M2} = get_term(P),
+
+    {term, M3} = get_term(P),
+    true = (M3 =:= #{a => 1, b => 2}),
+    {term, M3} = get_term(P),
+
+    {term, M4} = get_term(P),
+    true = (M4 =:= #{[a] => 1, 2 => [b,c], "3" => {c,d}}),
+    {term, M4} = get_term(P),
+
+    {term, M5} = get_term(P),
+    true = (M5 =:= #{a => [], [] => #{2=>d}}),
+    {term, M5} = get_term(P),
+
+    [{term, {"FAILED ei_x_format",_,_}} = get_term(P)
+     || _ <- lists:seq(1,10)],
+
+    runner:recv_eot(P),
+    ok.
+
+
 format_wo_ver(Config) when is_list(Config) ->
     P = runner:start(Config, ?format_wo_ver),
 
-    {term, [-1, 2, $c, {a, "b"}, {c, 10}]} = get_term(P),
+    {term, [-1, 2, $c, {a, "b"}, {c, 10}, M]} = get_term(P),
+    #{d := 32} = M,
 
     runner:recv_eot(P),
     ok.
diff --git a/lib/erl_interface/test/ei_format_SUITE_data/ei_format_test.c b/lib/erl_interface/test/ei_format_SUITE_data/ei_format_test.c
index ef6011b491..f9b0f40c26 100644
--- a/lib/erl_interface/test/ei_format_SUITE_data/ei_format_test.c
+++ b/lib/erl_interface/test/ei_format_SUITE_data/ei_format_test.c
@@ -32,7 +32,11 @@ send_format2(char* format, char* p)
 {
     ei_x_buff x;
     ei_x_new(&x);
-    ei_x_format(&x, format, p);
+    if (ei_x_format(&x, format, p) != 0) {
+        x.index = 0;
+        ei_x_format(&x, "{~s, ~s, ~s}", "FAILED ei_x_format", format,
+                    p?p:"NULL");
+    }
     send_bin_term(&x);
     free(x.buff);
 }
@@ -93,6 +97,7 @@ TESTCASE(tuples)
     send_format("{[], a, b, c}");
     send_format("{[], a, [], b, c}");
     send_format("{[], a, '', b, c}");
+    send_format("{[], a, '', b, #{c=>3}}");
 
     report(1);
 }
@@ -123,6 +128,7 @@ TESTCASE(lists)
     send_format("[[], a, '', b, c]");
     send_format("[[x, 2], [y, 3], [z, 4]]");
     send_format("[{a,b},{c,d}]"); /* OTP-4777 */
+    send_format("[{a,b},#{c=>d}]");
 
     ei_x_new(&x);
 /*
@@ -174,6 +180,36 @@ TESTCASE(lists)
     report(1);
 }
 
+TESTCASE(maps)
+{
+    ei_init();
+
+    send_format("#{}");
+    send_format("#{ }");
+    send_format("#{a=>1}");
+    send_format("#{ a => 1 }");
+    send_format("#{a=>1, b=>2}");
+    send_format("#{ a => 1 , b=>2 }");
+    send_format("#{[a]=>1,2=>[b,c],\"3\"=>{c,d}}");
+    send_format("#{ [a] => 1 , 2 => [b,c] , \"3\" => {c,d} }");
+    send_format("#{a=>[],[]=>#{2=>d}}");
+    send_format("#{ a => [] , [] => #{ 2 => d } }");
+
+    /* Incorrect map syntax */
+    send_format("#{a= >1}");
+    send_format("#{,a=>1}");
+    send_format("#{a=>1,}");
+    send_format("#{=>1}");
+    send_format("#{a=>1,,b=>2}");
+    send_format("#{a=>}");
+    send_format("#{a=>1=>2=>3}");
+    send_format("#{a}");
+    send_format("#{a=}");
+    send_format("#{a>}");
+
+    report(1);
+}
+
 TESTCASE(format_wo_ver) {
 /* OTP-6795 
  * make example with format_wo_ver 
@@ -183,7 +219,7 @@ TESTCASE(format_wo_ver) {
     ei_init();
 
     ei_x_new (&x);
-    ei_x_format(&x, "[-1, +2, ~c, {~a,~s},{~a,~i}]", 'c', "a", "b", "c", 10);
+    ei_x_format(&x, "[-1, +2, ~c, {~a,~s},{~a,~i}, #{d=>~i}]", 'c', "a", "b", "c", 10, 32);
     send_bin_term(&x);
 
     free(x.buff);
-- 
2.35.3

openSUSE Build Service is sponsored by