File 6451-Improve-json-decode-error-messages.patch of Package erlang

From 1259bbb354844825d810f68edf85c7b4f5a254b5 Mon Sep 17 00:00:00 2001
From: Dan Gudmundsson <dgud@erlang.org>
Date: Mon, 24 Feb 2025 12:37:39 +0100
Subject: [PATCH] Improve json decode error messages

When printing errors include the position that the error occured at
if included in the error.
---
 lib/stdlib/src/erl_stdlib_errors.erl | 16 +++++++++++++++-
 lib/stdlib/src/json.erl              |  3 ++-
 lib/stdlib/test/json_SUITE.erl       | 11 +++++++++--
 3 files changed, 26 insertions(+), 4 deletions(-)

diff --git a/lib/stdlib/src/erl_stdlib_errors.erl b/lib/stdlib/src/erl_stdlib_errors.erl
index d841a020d8..8bcc999b1e 100644
--- a/lib/stdlib/src/erl_stdlib_errors.erl
+++ b/lib/stdlib/src/erl_stdlib_errors.erl
@@ -27,7 +27,7 @@
       StackTrace :: erlang:stacktrace(),
       ErrorMap :: #{pos_integer() => unicode:chardata()}.
 
-format_error(_Reason, [{M,F,As,Info}|_]) ->
+format_error(Reason, [{M,F,As,Info}|_]) ->
     ErrorInfoMap = proplists:get_value(error_info, Info, #{}),
     Cause = maps:get(cause, ErrorInfoMap, none),
     Res = case M of
@@ -47,6 +47,8 @@ format_error(_Reason, [{M,F,As,Info}|_]) ->
                   format_unicode_error(F, As);
               io ->
                   format_io_error(F, As, Cause);
+              json ->
+                  format_json_error(F, As, Reason, Cause);
               _ ->
                   []
           end,
@@ -633,6 +635,18 @@ check_io_arguments([Type|TypeT], [Arg|ArgT], No) ->
              check_io_arguments(TypeT, ArgT, No+1)]
     end.
 
+format_json_error(_F, _As, {invalid_byte, Int}, #{position := Position}) ->
+    Str = if 32 =< Int, Int < 127 ->
+                  io_lib:format("invalid byte 16#~2.16.0B '~c' at byte position ~w",
+                                [Int, Int, Position]);
+             true ->
+                  io_lib:format("invalid byte 16#~2.16.0B at byte position ~w",
+                                [Int, Position])
+          end,
+    [{general, Str}];
+format_json_error(_, _, _, _) ->
+    [""].
+
 format_ets_error(delete_object, Args, Cause) ->
     format_object(Args, Cause);
 format_ets_error(give_away, [_Tab,Pid,_Gift]=Args, Cause) ->
diff --git a/lib/stdlib/src/json.erl b/lib/stdlib/src/json.erl
index bfa333eda3..19bf772e2a 100644
--- a/lib/stdlib/src/json.erl
+++ b/lib/stdlib/src/json.erl
@@ -541,7 +541,8 @@ invalid_byte(Bin, Skip) ->
     error({invalid_byte, Byte}, none, error_info(Skip)).
 
 error_info(Skip) ->
-    [{error_info, #{cause => #{position => Skip}}}].
+    [{error_info, #{cause => #{position => Skip},
+                    module => erl_stdlib_errors}}].
 
 %%
 %% Format implementation
diff --git a/lib/stdlib/test/json_SUITE.erl b/lib/stdlib/test/json_SUITE.erl
index 70f92848fe..01e98e9018 100644
--- a/lib/stdlib/test/json_SUITE.erl
+++ b/lib/stdlib/test/json_SUITE.erl
@@ -56,7 +56,8 @@
     property_integer_roundtrip/1,
     property_float_roundtrip/1,
     property_object_roundtrip/1,
-    property_escape_all/1
+    property_escape_all/1,
+    error_info/1
 ]).
 
 
@@ -75,7 +76,8 @@ all() ->
         {group, format},
         test_json_test_suite,
         {group, properties},
-        counterexamples
+        counterexamples,
+        error_info
     ].
 
 groups() ->
@@ -1042,6 +1044,11 @@ test_file(yes, File, Data) ->
 test_file(no, File, Data) ->
     ?assertError(_, decode(Data), File).
 
+error_info(_) ->
+    L = [{decode, [~'["valid string", not_valid'], [allow_rename, unexplained]}],
+    error_info_lib:test_error_info(json, L,  [allow_nyi]).
+
+
 %%
 %% Property tests
 %%
-- 
2.43.0

openSUSE Build Service is sponsored by