Skip to content

Commit

Permalink
Merge pull request #9484 from dgud/dgud/stdlib/json-error-msg/OTP-19508
Browse files Browse the repository at this point in the history
Improve json decode error messages
  • Loading branch information
dgud authored Feb 26, 2025
2 parents c15c736 + 1259bbb commit d708174
Show file tree
Hide file tree
Showing 3 changed files with 26 additions and 4 deletions.
16 changes: 15 additions & 1 deletion lib/stdlib/src/erl_stdlib_errors.erl
Original file line number Diff line number Diff line change
Expand Up @@ -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
Expand All @@ -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,
Expand Down Expand Up @@ -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) ->
Expand Down
3 changes: 2 additions & 1 deletion lib/stdlib/src/json.erl
Original file line number Diff line number Diff line change
Expand Up @@ -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
Expand Down
11 changes: 9 additions & 2 deletions lib/stdlib/test/json_SUITE.erl
Original file line number Diff line number Diff line change
Expand Up @@ -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
]).


Expand All @@ -75,7 +76,8 @@ all() ->
{group, format},
test_json_test_suite,
{group, properties},
counterexamples
counterexamples,
error_info
].

groups() ->
Expand Down Expand Up @@ -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
%%
Expand Down

0 comments on commit d708174

Please sign in to comment.