File 2511-Add-ei_decode_iodata.patch of Package erlang
From 18e6148e22d95deb17f12cef917448427edd8909 Mon Sep 17 00:00:00 2001
From: Rickard Green <rickard@erlang.org>
Date: Fri, 10 Apr 2020 01:23:41 +0200
Subject: [PATCH] Add ei_decode_iodata()
---
 lib/erl_interface/doc/src/ei.xml                   |  31 +++++
 lib/erl_interface/include/ei.h                     |   1 +
 lib/erl_interface/src/Makefile.in                  |   1 +
 lib/erl_interface/src/decode/decode_iodata.c       | 141 +++++++++++++++++++++
 lib/erl_interface/test/ei_decode_SUITE.erl         |  68 +++++++++-
 .../test/ei_decode_SUITE_data/ei_decode_test.c     |  54 ++++++++
 6 files changed, 294 insertions(+), 2 deletions(-)
 create mode 100644 lib/erl_interface/src/decode/decode_iodata.c
diff --git a/lib/erl_interface/doc/src/ei.xml b/lib/erl_interface/doc/src/ei.xml
index 361021bf50..820fb51c28 100644
--- a/lib/erl_interface/doc/src/ei.xml
+++ b/lib/erl_interface/doc/src/ei.xml
@@ -282,6 +282,37 @@ typedef enum {
       </desc>
     </func>
 
+    <func>
+      <name since="OTP 23.0"><ret>int</ret><nametext>ei_decode_iodata(const char *buf, int *index, int *size, char *outbuf)</nametext></name>
+      <fsummary>Decode iodata().</fsummary>
+      <desc>
+        <p>Decodes a term of the type <seealso marker="system/reference_manual:typespec#types-and-their-syntax"><c>iodata()</c></seealso>. The <c>iodata()</c> term will be
+	flattened an written into the buffer pointed to by the <c>outbuf</c>
+	argument. The byte size of the <c>iodata</c> is written into the
+	integer variable pointed to by the <c>size</c> argument. Both <c>size</c>
+	and <c>outbuf</c> can be set to <c>NULL</c>. The integer pointed to
+	by the <c>index</c> argument is updated to refer to the term
+	following after the <c>iodata()</c> term regardless of the the state
+	of the <c>size</c> and the <c>outbuf</c> arguments.
+	</p>
+	<p>Note that the buffer pointed to by the <c>outbuf</c> argument
+	must be large enough if a non <c>NULL</c> value is passed as
+	<c>outbuf</c>. You typically want to call <c>ei_decode_iodata()</c>
+	twice. First with a non <c>NULL</c> <c>size</c> argument and
+	a <c>NULL</c> <c>outbuf</c> argument in order to determine the
+	size of the buffer needed, and then once again in order to do
+	the actual decoding. Note that the integer pointed to by <c>index</c>
+	will be updated by the call determining the size as well, so you
+	need to reset it before the second call doing the actual decoding.
+	</p>
+	<p>Returns <c>0</c> on success and <c>-1</c> on failure. Failure
+	might be either due to invalid encoding of the term or due to
+	the term not being of the type <c>iodata()</c>. On failure, the
+	integer pointed to by the <c>index</c> argument will be updated
+	to refer to the sub term where the failure was detected.</p>
+      </desc>
+    </func>
+
     <func>
       <name since=""><ret>int</ret><nametext>ei_decode_list_header(const char *buf, int *index, int *arity)</nametext></name>
       <fsummary>Decode a list.</fsummary>
diff --git a/lib/erl_interface/include/ei.h b/lib/erl_interface/include/ei.h
index 6b75a213d0..6859c71c29 100644
--- a/lib/erl_interface/include/ei.h
+++ b/lib/erl_interface/include/ei.h
@@ -568,6 +568,7 @@ int ei_decode_trace(const char *buf, int *index, erlang_trace *p);
 int ei_decode_tuple_header(const char *buf, int *index, int *arity);
 int ei_decode_list_header(const char *buf, int *index, int *arity);
 int ei_decode_map_header(const char *buf, int *index, int *arity);
+int ei_decode_iodata(const char *buf, int* index, int *szp, char *out_buf);
 
 /* 
  * ei_decode_ei_term() returns 1 if term is decoded, 0 if term is OK,
diff --git a/lib/erl_interface/src/Makefile.in b/lib/erl_interface/src/Makefile.in
index 55827ce097..5a07b5542a 100644
--- a/lib/erl_interface/src/Makefile.in
+++ b/lib/erl_interface/src/Makefile.in
@@ -331,6 +331,7 @@ DECODESRC = \
 	decode/decode_double.c \
 	decode/decode_fun.c \
 	decode/decode_intlist.c \
+	decode/decode_iodata.c \
 	decode/decode_list_header.c \
 	decode/decode_long.c \
 	decode/decode_pid.c \
diff --git a/lib/erl_interface/src/decode/decode_iodata.c b/lib/erl_interface/src/decode/decode_iodata.c
new file mode 100644
index 0000000000..2a538d2ad7
--- /dev/null
+++ b/lib/erl_interface/src/decode/decode_iodata.c
@@ -0,0 +1,141 @@
+/*
+ * %CopyrightBegin%
+ * 
+ * Copyright Ericsson AB 2020. All Rights Reserved.
+ * 
+ * Licensed under the Apache License, Version 2.0 (the "License");
+ * you may not use this file except in compliance with the License.
+ * You may obtain a copy of the License at
+ *
+ *     http://www.apache.org/licenses/LICENSE-2.0
+ *
+ * Unless required by applicable law or agreed to in writing, software
+ * distributed under the License is distributed on an "AS IS" BASIS,
+ * WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied.
+ * See the License for the specific language governing permissions and
+ * limitations under the License.
+ * 
+ * %CopyrightEnd%
+ *
+ */
+
+#include "eidef.h"
+#include "eiext.h"
+    
+static int decode_list_ext_iodata(const char *buf, int* index,
+                                  int *szp, unsigned char **pp);
+
+int ei_decode_iodata(const char *buf, int* index, int *szp, char *out_buf)
+{
+    int type, len;
+
+    if (szp)
+        *szp = 0;
+    
+    if (ei_get_type(buf, index, &type, &len) < 0)
+        return -1;
+
+    /* Top level of iodata is either a list or a binary... */
+    
+    switch (type) {
+
+    case ERL_BINARY_EXT: {
+        long llen;
+        if (ei_decode_binary(buf, index, out_buf, &llen) < 0)
+            return -1;
+        if (llen != (long) len)
+            return -1; /* general 64-bit issue with ei api... */
+        if (szp)
+            *szp += len;
+        return 0;
+    }
+
+    case ERL_STRING_EXT:
+        if (ei_decode_string(buf, index, out_buf) < 0)
+            return -1;
+        if (szp)
+            *szp += len;
+        return 0;
+
+    case ERL_NIL_EXT:
+        return ei_decode_list_header(buf, index, NULL);
+
+    case ERL_LIST_EXT: {
+        unsigned char *ptr = (unsigned char *) out_buf;
+        len = 0;
+        return decode_list_ext_iodata(buf, index,
+                                      szp ? szp : &len,
+                                      ptr ? &ptr : NULL);
+    }
+
+    default:
+        return -1; /* Not a list or binary... */
+    }
+}
+    
+static int decode_list_ext_iodata(const char *buf, int* index,
+                                  int *szp, unsigned char **pp)
+{
+    int type, len, i, conses;
+    
+    if (ei_decode_list_header(buf, index, &conses) < 0)
+        return -1;
+    
+    for (i = 0; i <= conses; i++) {
+        
+        if (ei_get_type(buf, index, &type, &len) < 0)
+            return -1;
+
+        switch (type) {
+        case ERL_SMALL_INTEGER_EXT:
+        case ERL_INTEGER_EXT: {
+            long val;
+            if (i == conses)
+                return -1; /* int not allowed in cdr of cons */
+            if (ei_decode_long(buf, index, &val) < 0)
+                return -1;
+            if (val < 0 || 255 < val)
+                return -1;
+            if (pp)
+                *((*pp)++) = (unsigned char) val;
+            *szp += 1;
+            break;
+        }
+        case ERL_BINARY_EXT: {
+            void *p = pp ? *pp : NULL;
+            long llen;
+            if (ei_decode_binary(buf, index, p, &llen) < 0)
+                return -1;
+            if (llen != (long) len)
+                return -1; /* general 64-bit issue with ei api... */
+            if (pp)
+                *pp += len;
+            *szp += len;
+            break;
+        }
+        case ERL_STRING_EXT: {
+            void *p = pp ? *pp : NULL;
+            if (ei_decode_string(buf, index, p) < 0)
+                return -1;
+            if (pp)
+                *pp += len;
+            *szp += len;
+            break;
+        }
+        case ERL_LIST_EXT:
+            if (decode_list_ext_iodata(buf, index, szp, pp) < 0)
+                return -1;
+            break;
+        case ERL_NIL_EXT:
+            if (ei_decode_list_header(buf, index, NULL) < 0)
+                return -1;
+            break;
+        default:
+            /* Not a list, binary, nor byte sized integer... */
+            return -1;
+        }
+    }
+    
+    return 0;
+}
+    
diff --git a/lib/erl_interface/test/ei_decode_SUITE.erl b/lib/erl_interface/test/ei_decode_SUITE.erl
index 475e68ced2..37b51329ea 100644
--- a/lib/erl_interface/test/ei_decode_SUITE.erl
+++ b/lib/erl_interface/test/ei_decode_SUITE.erl
@@ -33,7 +33,8 @@
          test_ei_decode_char/1,
          test_ei_decode_nonoptimal/1,
          test_ei_decode_misc/1,
-         test_ei_decode_utf8_atom/1]).
+         test_ei_decode_utf8_atom/1,
+         test_ei_decode_iodata/1]).
 
 suite() -> [{ct_hooks,[ts_install_cth]}].
 
@@ -41,7 +42,8 @@ all() ->
     [test_ei_decode_long, test_ei_decode_ulong,
      test_ei_decode_longlong, test_ei_decode_ulonglong,
      test_ei_decode_char, test_ei_decode_nonoptimal,
-     test_ei_decode_misc, test_ei_decode_utf8_atom].
+     test_ei_decode_misc, test_ei_decode_utf8_atom,
+     test_ei_decode_iodata].
 
 init_per_testcase(Case, Config) ->
     runner:init_per_testcase(?MODULE, Case, Config).
@@ -215,6 +217,68 @@ test_ei_decode_utf8_atom(Config) ->
 
 %% ######################################################################## %%
 
+test_ei_decode_iodata(Config) when is_list(Config) ->
+    P = runner:start(Config, ?test_ei_decode_iodata),
+
+    check_decode_iodata(P, [], true),
+    check_decode_iodata(P, $a, false),
+    check_decode_iodata(P, an_atom, false),
+    check_decode_iodata(P, self(), false),
+    check_decode_iodata(P, [$a,$a], true),    
+    check_decode_iodata(P, [$a|$a], false),
+    check_decode_iodata(P, [[$a|$a],$a], false),
+    check_decode_iodata(P, "hej", true),
+    check_decode_iodata(P, <<"hopp san sa">>, true),
+    check_decode_iodata(P, [$a | <<"a">>], true),
+    check_decode_iodata(P, [[[["hej"]]], [$ , <<"hopp">>, $ , "san" | <<" sa">>]], true),
+    check_decode_iodata(P, [[[["hej"]]], [$ , <<"hopp">>, 0, "san" | <<" sa">>]], true),
+    check_decode_iodata(P, [[[["hej"]]], [$ , <<"hopp">>, 256, "san" | <<" sa">>]], false),
+    check_decode_iodata(P, [[[["hej"]]], [$ , <<"hopp">>, -2, "san" | <<" sa">>]], false),
+    check_decode_iodata(P, [[[["hej"]]], [$ , <<"hopp">>, $ , san | <<" sa">>]], false),
+    check_decode_iodata(P, [[[["hej"]]], [$ , <<"hopp">>, $ , "san s" | $a], "  "], false),
+    check_decode_iodata(P, [[[[[[[]|<<"a">>]]]]]], true),
+    check_decode_iodata(P, [[[[[[[[]]]]]]],[[[],[],[]]]], true),
+
+    send_raw(P, <<"done">>),
+    runner:recv_eot(P),
+    ok.
+
+check_decode_iodata(P, Data, Valid) ->
+    io:format("~n~nChecking: ~p~n", [Data]),
+    Expect = case Valid of
+                 true ->
+                     io:format("Expecting decode SUCCESS... ", []),
+                     iolist_to_binary(Data);
+                 false ->
+                     io:format("Expecting decode FAILURE... ", []),
+                     badarg = try
+                                  iolist_to_binary(Data)
+                              catch
+                                  error:badarg ->
+                                      badarg
+                              end,
+                     decode_size_failed
+             end,
+    send_term_as_binary(P, Data),
+    Actual = case runner:get_term(P) of
+                 {bytes, B} when is_binary(B) ->
+                     B;
+                 {bytes, L} when is_list(L) ->
+                     list_to_binary(L);
+                 {term, T} ->
+                     T
+             end,
+    case Expect =:= Actual of
+        true ->
+            io:format("Expected result!~n",[]),
+            ok;
+        false ->
+            io:format("Expect: ~w~nActual: ~w~n", [Expect, Actual]),
+            ct:fail(unexpected_result)
+    end.
+
+%% ######################################################################## %%
+
 send_term_as_binary(Port, Term) when is_port(Port) ->
     Port ! {self(), {command, term_to_binary(Term)}}.
 
diff --git a/lib/erl_interface/test/ei_decode_SUITE_data/ei_decode_test.c b/lib/erl_interface/test/ei_decode_SUITE_data/ei_decode_test.c
index 29542b1c6c..961137f36c 100644
--- a/lib/erl_interface/test/ei_decode_SUITE_data/ei_decode_test.c
+++ b/lib/erl_interface/test/ei_decode_SUITE_data/ei_decode_test.c
@@ -19,6 +19,7 @@
  */
 
 #include <string.h>
+#include <stdlib.h>
 
 #ifdef VXWORKS
 #include "reclaim.h"
@@ -771,6 +772,59 @@ TESTCASE(test_ei_decode_utf8_atom)
 
 /* ******************************************************************** */
 
+TESTCASE(test_ei_decode_iodata)
+{
+    ei_init();
+
+    while (1) {
+        char *buf, *data;
+        int len, index, saved_index, err;
+
+        buf = read_packet(&len);
+
+        if (len == 4
+            && buf[0] == 'd'
+            && buf[1] == 'o'
+            && buf[2] == 'n'
+            && buf[3] == 'e') {
+            break;
+        }
+        
+        index = 0;
+        err = ei_decode_version(buf, &index, NULL);
+        if (err != 0)
+            fail1("ei_decode_version returned %d", err);
+        saved_index = index;
+        err = ei_decode_iodata(buf, &index, &len, NULL);
+        if (err != 0) {
+            ei_x_buff x;
+            ei_x_new_with_version(&x);
+            ei_x_encode_atom(&x, "decode_size_failed");
+            send_bin_term(&x);
+            ei_x_free(&x);
+            continue;
+        }
+        data = malloc(len);
+        err = ei_decode_iodata(buf, &saved_index, NULL, (unsigned char *) data);
+        if (err != 0) {
+            ei_x_buff x;
+            ei_x_new_with_version(&x);
+            ei_x_encode_atom(&x, "decode_data_failed");
+            send_bin_term(&x);
+            ei_x_free(&x);
+            free(data);
+            continue;
+        }
+
+        send_buffer(data, len);
+        free(data);
+    }
+
+    report(1);
+}
+
+/* ******************************************************************** */
+
 int ei_decode_my_atom_as(const char *buf, int *index, char *to,
 			 struct my_atom *atom) {
   erlang_char_encoding was,result;
-- 
2.16.4