File 8121-Issue-8099-Add-binary-join-2-to-stdlib.patch of Package erlang

From 7a3bd5c5121c515cbb7513116e30121b85499cf2 Mon Sep 17 00:00:00 2001
From: Onno Vos <onno-vos-dev@users.noreply.github.com>
Date: Thu, 8 Feb 2024 10:23:45 +0100
Subject: [PATCH] Issue #8099: Add binary:join/2 to stdlib

---
 lib/stdlib/src/binary.erl               | 34 ++++++++++++++++++++++++-
 lib/stdlib/src/erl_stdlib_errors.erl    | 14 ++++++++++
 lib/stdlib/test/binary_module_SUITE.erl | 22 ++++++++++++++--
 3 files changed, 67 insertions(+), 3 deletions(-)

diff --git a/lib/stdlib/doc/src/binary.xml b/lib/stdlib/doc/src/binary.xml
index 503e99d9cd..f7acbee55d 100644
--- a/lib/stdlib/doc/src/binary.xml
+++ b/lib/stdlib/doc/src/binary.xml
@@ -258,6 +258,19 @@
     </func>
 
     <func>
+      <name name="join" arity="2" since="OTP 28.0"/>
+      <fsummary>Joins a list of binaries together by a specified <c>Separator</c>.</fsummary>
+      <desc>
+      <p>Equivalent to <c>iolist_to_binary(lists:join(Separator, Binaries))</c>, but faster.</p>
+      <p><em>Example:</em></p>
+
+<code>
+1> binary:join([&lt;&lt;"a"&gt;&gt;, &lt;&lt;"b"&gt;&gt;, &lt;&lt;"c"&gt;&gt;], &lt;&lt;", "&gt;&gt;).
+&lt;&lt;"a, b, c"&gt;&gt;</code>
+      </desc>
+    </func>
+
+    <func>
       <name name="last" arity="1" since="OTP R14B"/>
       <fsummary>Return the last byte of a binary.</fsummary>
       <desc>
diff --git a/lib/stdlib/src/binary.erl b/lib/stdlib/src/binary.erl
index 503e99d9cd..f7acbee55d 100644
--- a/lib/stdlib/src/binary.erl
+++ b/lib/stdlib/src/binary.erl
@@ -38,7 +38,8 @@ The module is provided according to Erlang Enhancement Proposal (EEP) 31.
 %%
 %% Implemented in this module:
 -export([replace/3, replace/4,
-         encode_hex/1, encode_hex/2, decode_hex/1]).
+         encode_hex/1, encode_hex/2, decode_hex/1,
+         join/2]).
 
 -export_type([cp/0]).
 
@@ -958,6 +959,24 @@ unhex(X) ->
              no, 10, 11, 12, 13, 14, 15, no, no, no, no, no, no, no, no, no  %96
             }).
 
+-spec join([binary()], binary()) -> binary().
+join([], Separator) when is_binary(Separator) -> <<>>;
+join([H], Separator) when is_binary(H), is_binary(Separator) -> H;
+join([H | T]=List, Separator) when is_binary(Separator) ->
+    try
+        Acc = <<>>,                             %Enable private-append optimization
+        join(T, Separator, <<Acc/binary, H/binary>>)
+    catch
+        error:_ ->
+            badarg_with_info([List, Separator])
+    end;
+join(Arg, Separator) ->
+    badarg_with_info([Arg, Separator]).
+
+join([], _Separator, Acc) -> Acc;
+join([H | T], Separator, Acc) ->
+    join(T, Separator, <<Acc/binary, Separator/binary, H/binary>>).
+
 badarg_with_cause(Args, Cause) ->
     erlang:error(badarg, Args, [{error_info, #{module => erl_stdlib_errors,
                                                cause => Cause}}]).
diff --git a/lib/stdlib/src/erl_stdlib_errors.erl b/lib/stdlib/src/erl_stdlib_errors.erl
index b5864c471f..d841a020d8 100644
--- a/lib/stdlib/src/erl_stdlib_errors.erl
+++ b/lib/stdlib/src/erl_stdlib_errors.erl
@@ -100,6 +100,20 @@ format_binary_error(last, [Subject], _) ->
          <<>> -> empty_binary;
         _ -> must_be_binary(Subject)
      end];
+format_binary_error(join, [Binaries,Separator], _) ->
+    case must_be_binary(Separator) of
+        [] when is_list(Binaries) ->
+            case must_be_list(Binaries) of
+                [] ->
+                    [<<"not a list of binaries">>, []];
+                Error ->
+                    [Error, []]
+            end;
+        [] ->
+            [must_be_list(Binaries), []];
+        Error ->
+            [[], Error]
+    end;
 format_binary_error(list_to_bin, [_], _) ->
     [not_iodata];
 format_binary_error(longest_common_prefix, [_], _) ->
diff --git a/lib/stdlib/test/binary_module_SUITE.erl b/lib/stdlib/test/binary_module_SUITE.erl
index 27eb7de92c..3d9efd919e 100644
--- a/lib/stdlib/test/binary_module_SUITE.erl
+++ b/lib/stdlib/test/binary_module_SUITE.erl
@@ -23,7 +23,7 @@
 	 interesting/1,scope_return/1,random_ref_comp/1,random_ref_sr_comp/1,
 	 random_ref_fla_comp/1,parts/1, bin_to_list/1, list_to_bin/1,
 	 copy/1, referenced/1,guard/1,encode_decode/1,badargs/1,longest_common_trap/1,
-         check_no_invalid_read_bug/1,error_info/1, hex_encoding/1]).
+         check_no_invalid_read_bug/1,error_info/1, hex_encoding/1, join/1]).
 
 -export([random_number/1, make_unaligned/1]).
 
@@ -38,7 +38,7 @@ all() ->
      random_ref_comp, parts, bin_to_list, list_to_bin, copy,
      referenced, guard, encode_decode, badargs,
      longest_common_trap, check_no_invalid_read_bug,
-     error_info, hex_encoding].
+     error_info, hex_encoding, join].
 
 
 -define(MASK_ERROR(EXPR),mask_error((catch (EXPR)))).
@@ -260,6 +260,13 @@ badargs(Config) when is_list(Config) ->
     badarg = ?MASK_ERROR(binary:encode_hex([])),
     badarg = ?MASK_ERROR(binary:encode_hex(#{})),
     badarg = ?MASK_ERROR(binary:encode_hex(foo)),
+
+    badarg = ?MASK_ERROR(binary:join(<<"">>, ",")),
+    badarg = ?MASK_ERROR(binary:join([""], <<",">>)),
+    badarg = ?MASK_ERROR(binary:join([123], <<",">>)),
+    badarg = ?MASK_ERROR(binary:join(123, <<",">>)),
+    badarg = ?MASK_ERROR(binary:join(#{}, <<",">>)),
+    badarg = ?MASK_ERROR(binary:join(foo, <<",">>)),
     ok.
 
 %% Whitebox test to force special trap conditions in
@@ -1454,6 +1461,12 @@ error_info(_Config) ->
          {last,[<<1:1>>]},
          {last,[<<>>]},
 
+         {join,[no_list,<<>>]},
+         {join,[[a|b],<<>>]},
+         {join,[[a],<<>>]},
+         {join,[[],<<1:7>>]},
+         {join,[[],bad_separator]},
+
          {list_to_bin,[<<1,2,3>>]},
          {list_to_bin,[{1,2,3}]},
 
@@ -1581,6 +1594,11 @@ do_hex_roundtrip(Bytes) ->
             ok
     end.
 
+join(Config) when is_list(Config) ->
+    <<"a, b, c">> = binary:join([<<"a">>, <<"b">>, <<"c">>], <<", ">>),
+    <<"a">> = binary:join([<<"a">>], <<", ">>),
+    <<>> = binary:join([], <<", ">>).
+
 %%%
 %%% Utilities.
 %%%
-- 
2.43.0

openSUSE Build Service is sponsored by