File 2163-stdlib-Fix-unicode-characters-in-format-string.patch of Package erlang

From 04a60f396a27a1513866a47650c46aaf33db5ac1 Mon Sep 17 00:00:00 2001
From: Dan Gudmundsson <dgud@erlang.org>
Date: Mon, 16 Jun 2025 14:46:41 +0200
Subject: [PATCH] stdlib: Fix unicode characters in format string

io_lib:bformat crashed if there where unicode characters in the format string.
---
 lib/stdlib/src/io_lib_format.erl | 4 ++--
 lib/stdlib/test/io_SUITE.erl     | 8 ++++----
 2 files changed, 6 insertions(+), 6 deletions(-)

diff --git a/lib/stdlib/src/io_lib_format.erl b/lib/stdlib/src/io_lib_format.erl
index 4e7614a7e8..f151717281 100644
--- a/lib/stdlib/src/io_lib_format.erl
+++ b/lib/stdlib/src/io_lib_format.erl
@@ -130,11 +130,11 @@ build_bin(Cs, Options) ->
     {P, S, W, Other} = count_small(Res1),
     case P + S + W of
         0 ->
-            iolist_to_binary(Res1);
+            unicode:characters_to_binary(Res1);
         NumOfLimited ->
             RemainingChars = sub(CharsLimit, Other),
             Res = build_limited_bin(Res1, P, NumOfLimited, RemainingChars, 0),
-            iolist_to_binary(Res)  %% Res only contains utf-8 binary or ASCII
+            unicode:characters_to_binary(Res)
     end.
 
 %% Parse all control sequences in the format string.
diff --git a/lib/stdlib/test/io_SUITE.erl b/lib/stdlib/test/io_SUITE.erl
index b2eed5c35d..728a90cc13 100644
--- a/lib/stdlib/test/io_SUITE.erl
+++ b/lib/stdlib/test/io_SUITE.erl
@@ -2200,10 +2200,10 @@ otp_10302(Suite) when is_list(Suite) ->
     "<<\"äppl\"/utf8...>>" = pretty(<<"äpple"/utf8>>, 2),
     "<<\"apel\">>" = pretty(<<"apel">>, 2),
     "<<\"apel\"...>>" = pretty(<<"apelsin">>, 2),
-    "<<\"äppl\">>" = fmt("~tp", [<<"äppl">>]),
-    "<<\"äppl\"...>>" = fmt("~tP", [<<"äpple">>, 2]),
-    "<<0,0,0,0,0,0,1,0>>" = fmt("~p", [<<256:64/unsigned-integer>>]),
-    "<<0,0,0,0,0,0,1,0>>" = fmt("~tp", [<<256:64/unsigned-integer>>]),
+    "═Ω <<\"äppl\">>" = fmt("═Ω ~tp", [<<"äppl">>]),
+    "═Ω <<\"äppl\"...>>" = fmt("═Ω ~tP", [<<"äpple">>, 2]),
+    "═Ω <<0,0,0,0,0,0,1,0>>" = fmt("═Ω ~p", [<<256:64/unsigned-integer>>]),
+    "═Ω <<0,0,0,0,0,0,1,0>>" = fmt("═Ω ~tp", [<<256:64/unsigned-integer>>]),
 
     Chars = lists:seq(0, 512), % just a few...
     [] = [C || C <- Chars, S <- io_lib:write_char_as_latin1(C),
-- 
2.43.0

openSUSE Build Service is sponsored by