Skip to content

Commit

Permalink
Merge branch 'maint'
Browse files Browse the repository at this point in the history
* maint:
  Let `json:decode/3` keep whitespaces
  • Loading branch information
dgud committed Sep 23, 2024
2 parents 347b120 + 2ef18fe commit 951d24a
Show file tree
Hide file tree
Showing 2 changed files with 26 additions and 8 deletions.
7 changes: 5 additions & 2 deletions lib/stdlib/src/json.erl
Original file line number Diff line number Diff line change
Expand Up @@ -1393,8 +1393,11 @@ continue(<<Rest/bits>>, Original, Skip, Acc, Stack0, Decode, Value) ->
end.

terminate(<<Byte, Rest/bits>>, Original, Skip, Acc, Value) when ?is_ws(Byte) ->
terminate(Rest, Original, Skip + 1, Acc, Value);
terminate(<<Rest/bits>>, _Original, _Skip, Acc, Value) ->
terminate(Rest, Original, Skip, Acc, Value);
terminate(<<>>, _, _Skip, Acc, Value) ->
{Value, Acc, <<>>};
terminate(<<_/bits>>, Original, Skip, Acc, Value) ->
<<_:Skip/binary, Rest/binary>> = Original,
{Value, Acc, Rest}.

-spec unexpected_utf8(binary(), non_neg_integer()) -> no_return().
Expand Down
27 changes: 21 additions & 6 deletions lib/stdlib/test/json_SUITE.erl
Original file line number Diff line number Diff line change
Expand Up @@ -58,6 +58,9 @@
property_escape_all/1
]).


-define(is_ws(X), X =:= $\s; X =:= $\t; X =:= $\r; X =:= $\n).

suite() ->
[
{ct_hooks, [ts_install_cth]},
Expand Down Expand Up @@ -646,7 +649,7 @@ test_decode_whitespace(_Config) ->

%% add extra whitespace
ews(Str) ->
unicode:characters_to_binary(string:replace(Str, <<" ">>, <<" \s\t\r\n">>)).
unicode:characters_to_binary(string:replace(Str, <<" ">>, <<" \s\t\r\n">>, all)).

test_decode_api(_Config) ->
put(history, []),
Expand Down Expand Up @@ -757,10 +760,15 @@ test_decode_api_stream(_Config) ->
"numbers": [1, -10, 0.0, -0.0, 2.0, -2.0, 31e2, 31e-2, 0.31e2, -0.31e2, 0.13e-2],
"strings": ["three", "åäö", "mixed_Ω"],
"escaped": ["\\n", "\\u2603", "\\ud834\\uDD1E", "\\n\xc3\xb1"]
}#,
}
#,
ok = stream_decode(Types),

Multiple = ~#12345 1.30 "String1" -0.31e2\n["an array"]12345#,
{12345, ok, B1} = json:decode(ews(~# 12345 "foo" #), ok, #{}),
<<" \s\t\r\n", _/binary>> = B1,
{<<"foo">>, ok, <<>>} = json:decode(B1, ok, #{}),

Multiple = ~#12345 1.30 "String1" -0.31e2\n["an array"]12345\n#,
ok = multi_stream_decode(Multiple),
ok.

Expand Down Expand Up @@ -794,22 +802,29 @@ multi_stream_decode(Strs) ->
{R1, [], ContBin} ->
multi_stream_decode(ContBin);
Other ->
io:format("~p '~ts'~n~p~n", [R1,ContBin, Other]),
io:format("~p '~tp'~n~p~n", [R1,ContBin, Other]),
error
end.

byte_loop(Bin) ->
{continue, State} = json:decode_start(<<>>, [], #{}),
byte_loop(Bin, State, []).

byte_loop(<<Byte, Rest/binary>>, State0, Bytes) ->
byte_loop(<<Byte, Rest/binary>> = Orig, State0, Bytes) ->
%% io:format("cont with '~s' ~p~n",[lists:reverse([Byte|Bytes]), State0]),
case json:decode_continue(<<Byte>>, State0) of
{continue, State} ->
byte_loop(Rest, State, [Byte|Bytes]);
{Result, [], <<>>} ->
%% trim to match the binary in return value
{Result, [], string:trim(Rest, leading)}
case string:trim(Rest, leading) of
<<>> ->
{Result, [], <<>>};
_ when ?is_ws(Byte) ->
{Result, [], Orig};
_ ->
{Result, [], Rest}
end
end;
byte_loop(<<>>, State, _Bytes) ->
json:decode_continue(end_of_input, State).
Expand Down

0 comments on commit 951d24a

Please sign in to comment.