Sign Up
Log In
Log In
or
Sign Up
Places
All Projects
Status Monitor
Collapse sidebar
home:Ledest:erlang:24
erlang
otp_src_25.3.2.14-lib-stdlib-json-compat.patch
Overview
Repositories
Revisions
Requests
Users
Attributes
Meta
File otp_src_25.3.2.14-lib-stdlib-json-compat.patch of Package erlang
diff -Ndurp otp_src_25.3.2.14/lib/stdlib/src/json.erl otp_src_25.3.2.14-lib-stdlib-json-compat/lib/stdlib/src/json.erl --- otp_src_25.3.2.14/lib/stdlib/src/json.erl 2024-10-11 08:45:35.441679844 +0300 +++ otp_src_25.3.2.14-lib-stdlib-json-compat/lib/stdlib/src/json.erl 2024-10-11 09:11:52.597648654 +0300 @@ -19,16 +19,6 @@ %% % @format %% -module(json). --moduledoc """ -A library for encoding and decoding JSON. - -This module implements [EEP68](https://github.com/erlang/eep/blob/master/eeps/eep-0068.md). - -Both encoder and decoder fully conform to -[RFC 8259](https://tools.ietf.org/html/rfc8259) and -[ECMA 404](https://ecma-international.org/publications-and-standards/standards/ecma-404/) -standards. The decoder is tested using [JSONTestSuite](https://github.com/nst/JSONTestSuite). -""". -dialyzer(no_improper_lists). @@ -95,11 +85,8 @@ standards. The decoder is tested using [ %% Encoding implementation %% --type encoder() :: fun((dynamic(), encoder()) -> iodata()). +-type encoder() :: fun((any(), encoder()) -> iodata()). --doc """ -Simple JSON value encodeable with `json:encode/1`. -""". -type encode_value() :: integer() | float() @@ -112,76 +99,18 @@ Simple JSON value encodeable with `json: -type encode_map(Value) :: #{binary() | atom() | integer() => Value}. --doc """ -Generates JSON corresponding to `Term`. - -Supports basic data mapping: - -| **Erlang** | **JSON** | -|------------------------|----------| -| `integer() \| float()` | Number | -| `true \| false ` | Boolean | -| `null` | Null | -| `binary()` | String | -| `atom()` | String | -| `list()` | Array | -| `#{binary() => _}` | Object | -| `#{atom() => _}` | Object | -| `#{integer() => _}` | Object | - -This is equivalent to `encode(Term, fun json:encode_value/2)`. - -## Examples - -```erlang -> iolist_to_binary(json:encode(#{foo => <<"bar">>})). -<<"{\"foo\":\"bar\"}">> -``` -""". --doc(#{since => <<"OTP 27.0">>}). -spec encode(encode_value()) -> iodata(). encode(Term) -> encode(Term, fun do_encode/2). --doc """ -Generates JSON corresponding to `Term`. - -Can be customised with the `Encoder` callback. -The callback will be recursively called for all the data -to be encoded and is expected to return the corresponding -encoded JSON as iodata. - -Various `encode_*` functions in this module can be used -to help in constructing such callbacks. - -## Examples - -An encoder that uses a heuristic to differentiate object-like -lists of key-value pairs from plain lists: - -```erlang -> encoder([{_, _} | _] = Value, Encode) -> json:encode_key_value_list(Value, Encode); -> encoder(Other, Encode) -> json:encode_value(Other, Encode). -> custom_encode(Value) -> json:encode(Value, fun(Value, Encode) -> encoder(Value, Encode) end). -> iolist_to_binary(custom_encode([{a, []}, {b, 1}])). -<<"{\"a\":[],\"b\":1}">> -``` -""". --doc(#{since => <<"OTP 27.0">>}). --spec encode(dynamic(), encoder()) -> iodata(). +-spec encode(any(), encoder()) -> iodata(). encode(Term, Encoder) when is_function(Encoder, 2) -> Encoder(Term, Encoder). --doc """ -Default encoder used by `json:encode/1`. - -Recursively calls `Encode` on all the values in `Value`. -""". --spec encode_value(dynamic(), encoder()) -> iodata(). --doc(#{since => <<"OTP 27.0">>}). +-spec encode_value(any(), encoder()) -> iodata(). encode_value(Value, Encode) -> do_encode(Value, Encode). --spec do_encode(dynamic(), encoder()) -> iodata(). +-spec do_encode(any(), encoder()) -> iodata(). do_encode(Value, Encode) when is_atom(Value) -> encode_atom(Value, Encode); do_encode(Value, _Encode) when is_binary(Value) -> @@ -197,39 +126,18 @@ do_encode(Value, Encode) when is_map(Val do_encode(Other, _Encode) -> error({unsupported_type, Other}). --doc """ -Default encoder for atoms used by `json:encode/1`. - -Encodes the atom `null` as JSON `null`, -atoms `true` and `false` as JSON booleans, -and everything else as JSON strings calling the `Encode` -callback with the corresponding binary. -""". -spec encode_atom(atom(), encoder()) -> iodata(). --doc(#{since => <<"OTP 27.0">>}). encode_atom(null, _Encode) -> <<"null">>; encode_atom(true, _Encode) -> <<"true">>; encode_atom(false, _Encode) -> <<"false">>; encode_atom(Other, Encode) -> Encode(atom_to_binary(Other, utf8), Encode). --doc """ -Default encoder for integers as JSON numbers used by `json:encode/1`. -""". --doc(#{since => <<"OTP 27.0">>}). -spec encode_integer(integer()) -> iodata(). encode_integer(Integer) -> integer_to_binary(Integer). --doc """ -Default encoder for floats as JSON numbers used by `json:encode/1`. -""". --doc(#{since => <<"OTP 27.0">>}). -spec encode_float(float()) -> iodata(). encode_float(Float) -> float_to_binary(Float, [short]). --doc """ -Default encoder for lists as JSON arrays used by `json:encode/1`. -""". --doc(#{since => <<"OTP 27.0">>}). -spec encode_list(list(), encoder()) -> iodata(). encode_list(List, Encode) when is_list(List) -> do_encode_list(List, Encode). @@ -242,57 +150,21 @@ do_encode_list([First | Rest], Encode) w list_loop([], _Encode) -> "]"; list_loop([Elem | Rest], Encode) -> [$,, Encode(Elem, Encode) | list_loop(Rest, Encode)]. --doc """ -Default encoder for maps as JSON objects used by `json:encode/1`. - -Accepts maps with atom, binary, integer, or float keys. -""". --doc(#{since => <<"OTP 27.0">>}). --spec encode_map(encode_map(dynamic()), encoder()) -> iodata(). +-spec encode_map(encode_map(any()), encoder()) -> iodata(). encode_map(Map, Encode) when is_map(Map) -> do_encode_map(Map, Encode). do_encode_map(Map, Encode) when is_function(Encode, 2) -> - encode_object([[$,, key(Key, Encode), $: | Encode(Value, Encode)] || Key := Value <- Map]). - --doc """ -Encoder for maps as JSON objects. - -Accepts maps with atom, binary, integer, or float keys. -Verifies that no duplicate keys will be produced in the -resulting JSON object. - -## Errors + encode_object([[$,, key(Key, Encode), $:|Encode(Value, Encode)] || {Key, Value} <- maps:to_list(Map)]). -Raises `error({duplicate_key, Key})` if there are duplicates. -""". --doc(#{since => <<"OTP 27.0">>}). -spec encode_map_checked(map(), encoder()) -> iodata(). encode_map_checked(Map, Encode) -> do_encode_checked(maps:to_list(Map), Encode). --doc """ -Encoder for lists of key-value pairs as JSON objects. - -Accepts lists with atom, binary, integer, or float keys. -""". --doc(#{since => <<"OTP 27.0">>}). -spec encode_key_value_list([{term(), term()}], encoder()) -> iodata(). encode_key_value_list(List, Encode) when is_function(Encode, 2) -> encode_object([[$,, key(Key, Encode), $: | Encode(Value, Encode)] || {Key, Value} <- List]). --doc """ -Encoder for lists of key-value pairs as JSON objects. - -Accepts lists with atom, binary, integer, or float keys. -Verifies that no duplicate keys will be produced in the -resulting JSON object. - -## Errors - -Raises `error({duplicate_key, Key})` if there are duplicates. -""". --doc(#{since => <<"OTP 27.0">>}). -spec encode_key_value_list_checked([{term(), term()}], encoder()) -> iodata(). encode_key_value_list_checked(List, Encode) -> do_encode_checked(List, Encode). @@ -324,30 +196,10 @@ key(Key, _Encode) when is_float(Key) -> encode_object([]) -> <<"{}">>; encode_object([[_Comma | Entry] | Rest]) -> ["{", Entry, Rest, "}"]. --doc """ -Default encoder for binaries as JSON strings used by `json:encode/1`. - -## Errors - -* `error(unexpected_end)` if the binary contains incomplete UTF-8 sequences. -* `error({invalid_byte, Byte})` if the binary contains invalid UTF-8 sequences. -""". --doc(#{since => <<"OTP 27.0">>}). -spec encode_binary(binary()) -> iodata(). encode_binary(Bin) when is_binary(Bin) -> escape_binary(Bin). --doc """ -Encoder for binaries as JSON strings producing pure-ASCII JSON. - -For any non-ASCII unicode character, a corresponding `\\uXXXX` sequence is used. - -## Errors - -* `error(unexpected_end)` if the binary contains incomplete UTF-8 sequences. -* `error({invalid_byte, Byte})` if the binary contains invalid UTF-8 sequences. -""". --doc(#{since => <<"OTP 27.0">>}). -spec encode_binary_escape_all(binary()) -> iodata(). encode_binary_escape_all(Bin) when is_binary(Bin) -> escape_all(Bin). @@ -544,79 +396,22 @@ error_info(Skip) -> %% Format implementation %% --type formatter() :: fun((Term :: dynamic(), Encoder :: formatter(), State :: map()) -> iodata()). - --doc """ -Generates formatted JSON corresponding to `Term`. - -Similiar to `encode/1` but with added whitespaces for formatting. - -```erlang -> io:put_chars(json:format(#{foo => <<"bar">>, baz => 52})). -{ - "baz": 52, - "foo": "bar" -} -ok -``` -""". +-type formatter() :: fun((Term :: any(), Encoder :: formatter(), State :: map()) -> iodata()). --doc(#{since => ~"OTP @OTP-19112@"}). -spec format(Term :: encode_value()) -> iodata(). format(Term) -> Enc = fun format_value/3, format(Term, Enc, #{}). --doc """ -Generates formatted JSON corresponding to `Term`. - -Equivalent to `format(Term, fun json:format_value/3, Options)` or `format(Term, Encoder, #{})` -""". --doc(#{since => ~"OTP @OTP-19112@"}). - -spec format(Term :: encode_value(), Opts :: map()) -> iodata(); - (Term :: dynamic(), Encoder::formatter()) -> iodata(). + (Term :: any(), Encoder::formatter()) -> iodata(). format(Term, Options) when is_map(Options) -> Enc = fun format_value/3, format(Term, Enc, Options); format(Term, Encoder) when is_function(Encoder, 3) -> format(Term, Encoder, #{}). --doc """ -Generates formatted JSON corresponding to `Term`. - -Similar to `encode/2`, can be customised with the `Encoder` callback and `Options`. - -`Options` can include 'indent' to specify number of spaces per level and 'max' which loosely limits -the width of lists. - -The `Encoder` will get a 'State' argument which contains the 'Options' maps merged with other data -when recursing through 'Term'. - -`format_value/3` or various `encode_*` functions in this module can be used -to help in constructing such callbacks. - -```erlang -> formatter({posix_time, SysTimeSecs}, Encode, State) -> - TimeStr = calendar:system_time_to_rfc3339(SysTimeSecs, [{offset, "Z"}]), - json:format_value(unicode:characters_to_binary(TimeStr), Encode, State); -> formatter(Other, Encode, State) -> json:format_value(Other, Encode, State). -> -> Fun = fun(Value, Encode, State) -> formatter(Value, Encode, State) end. -> Options = #{indent => 4}. -> Term = #{id => 1, time => {posix_time, erlang:system_time(seconds)}}. -> -> io:put_chars(json:format(Term, Fun, Options)). -{ - "id": 1, - "time": "2024-05-23T16:07:48Z" -} -ok -``` -""". --doc(#{since => ~"OTP @OTP-19112@"}). - --spec format(Term :: dynamic(), Encoder::formatter(), Options :: map()) -> iodata(). +-spec format(Term :: any(), Encoder::formatter(), Options :: map()) -> iodata(). format(Term, Encoder, Options) when is_function(Encoder, 3) -> Def = #{level => 0, col => 0, @@ -625,15 +420,7 @@ format(Term, Encoder, Options) when is_f }, [Encoder(Term, Encoder, maps:merge(Def, Options)),$\n]. --doc """ -Default format function used by `json:format/1`. - -Recursively calls `Encode` on all the values in `Value`, -and indents objects and lists. -""". --doc(#{since => ~"OTP @OTP-19112@"}). - --spec format_value(Value::dynamic(), Encode::formatter(), State::map()) -> iodata(). +-spec format_value(Value::any(), Encode::formatter(), State::map()) -> iodata(). format_value(Atom, UserEnc, State) when is_atom(Atom) -> json:encode_atom(Atom, fun(Value, Enc) -> UserEnc(Value, Enc, State) end); format_value(Bin, _Enc, _State) when is_binary(Bin) -> @@ -646,7 +433,7 @@ format_value(List, UserEnc, State) when format_list(List, UserEnc, State); format_value(Map, UserEnc, State) when is_map(Map) -> %% Ensure order of maps are the same in each export - OrderedKV = maps:to_list(maps:iterator(Map, ordered)), + OrderedKV = lists:keysort(1, maps:to_list(Map)), format_key_value_list(OrderedKV, UserEnc, State); format_value(Other, _Enc, _State) -> error({unsupported_type, Other}). @@ -724,17 +511,17 @@ indent(#{level := Level, indent := Inden Steps = Level * Indent, {Steps, steps(Steps)}. -steps(0) -> ~"\n"; -steps(2) -> ~"\n "; -steps(4) -> ~"\n "; -steps(6) -> ~"\n "; -steps(8) -> ~"\n "; -steps(10) -> ~"\n "; -steps(12) -> ~"\n "; -steps(14) -> ~"\n "; -steps(16) -> ~"\n "; -steps(18) -> ~"\n "; -steps(20) -> ~"\n "; +steps(0) -> <<"\n">>; +steps(2) -> <<"\n ">>; +steps(4) -> <<"\n ">>; +steps(6) -> <<"\n ">>; +steps(8) -> <<"\n ">>; +steps(10) -> <<"\n ">>; +steps(12) -> <<"\n ">>; +steps(14) -> <<"\n ">>; +steps(16) -> <<"\n ">>; +steps(18) -> <<"\n ">>; +steps(20) -> <<"\n ">>; steps(N) -> ["\n", lists:duplicate(N, " ")]. %% @@ -744,13 +531,13 @@ steps(N) -> ["\n", lists:duplicate(N, " -define(ARRAY, array). -define(OBJECT, object). --type from_binary_fun() :: fun((binary()) -> dynamic()). --type array_start_fun() :: fun((Acc :: dynamic()) -> ArrayAcc :: dynamic()). --type array_push_fun() :: fun((Value :: dynamic(), Acc :: dynamic()) -> NewAcc :: dynamic()). --type array_finish_fun() :: fun((ArrayAcc :: dynamic(), OldAcc :: dynamic()) -> {dynamic(), dynamic()}). --type object_start_fun() :: fun((Acc :: dynamic()) -> ObjectAcc :: dynamic()). --type object_push_fun() :: fun((Key :: dynamic(), Value :: dynamic(), Acc :: dynamic()) -> NewAcc :: dynamic()). --type object_finish_fun() :: fun((ObjectAcc :: dynamic(), OldAcc :: dynamic()) -> {dynamic(), dynamic()}). +-type from_binary_fun() :: fun((binary()) -> any()). +-type array_start_fun() :: fun((Acc :: any()) -> ArrayAcc :: any()). +-type array_push_fun() :: fun((Value :: any(), Acc :: any()) -> NewAcc :: any()). +-type array_finish_fun() :: fun((ArrayAcc :: any(), OldAcc :: any()) -> {any(), any()}). +-type object_start_fun() :: fun((Acc :: any()) -> ObjectAcc :: any()). +-type object_push_fun() :: fun((Key :: any(), Value :: any(), Acc :: any()) -> NewAcc :: any()). +-type object_finish_fun() :: fun((ObjectAcc :: any(), OldAcc :: any()) -> {any(), any()}). -type decoders() :: #{ array_start => array_start_fun(), @@ -778,7 +565,7 @@ steps(N) -> ["\n", lists:duplicate(N, " null = null :: term() }). --type acc() :: dynamic(). +-type acc() :: any(). -type stack() :: [?ARRAY | ?OBJECT | binary() | acc()]. -type decode() :: #decode{}. @@ -793,33 +580,6 @@ steps(N) -> ["\n", lists:duplicate(N, " | list(decode_value()) | #{binary() => decode_value()}. --doc """ -Parses a JSON value from `Binary`. - -Supports basic data mapping: - -| **JSON** | **Erlang** | -|----------|------------------------| -| Number | `integer() \| float()` | -| Boolean | `true \| false` | -| Null | `null` | -| String | `binary()` | -| Object | `#{binary() => _}` | - -## Errors - -* `error(unexpected_end)` if `Binary` contains incomplete JSON value -* `error({invalid_byte, Byte})` if `Binary` contains unexpected byte or invalid UTF-8 byte -* `error({invalid_sequence, Bytes})` if `Binary` contains invalid UTF-8 escape - -## Example - -```erlang -> json:decode(<<"{\"foo\": 1}">>). -#{<<"foo">> => 1} -``` -""". --doc(#{since => <<"OTP 27.0">>}). -spec decode(binary()) -> decode_value(). decode(Binary) when is_binary(Binary) -> case value(Binary, Binary, 0, ok, [], #decode{}) of @@ -835,51 +595,8 @@ decode(Binary) when is_binary(Binary) -> error(unexpected_end) end. --doc """ -Parses a JSON value from `Binary`. - -Similar to `decode/1` except the decoding process -can be customized with the callbacks specified in -`Decoders`. The callbacks will use the `Acc` value -as the initial accumulator. - -Any leftover, unparsed data in `Binary` will be returned. - -## Default callbacks - -All callbacks are optional. If not provided, they will fall back to -implementations used by the `decode/1` function: - -* for `array_start`: `fun(_) -> [] end` -* for `array_push`: `fun(Elem, Acc) -> [Elem | Acc] end` -* for `array_finish`: `fun(Acc, OldAcc) -> {lists:reverse(Acc), OldAcc} end` -* for `object_start`: `fun(_) -> [] end` -* for `object_push`: `fun(Key, Value, Acc) -> [{Key, Value} | Acc] end` -* for `object_finish`: `fun(Acc, OldAcc) -> {maps:from_list(Acc), OldAcc} end` -* for `float`: `fun erlang:binary_to_float/1` -* for `integer`: `fun erlang:binary_to_integer/1` -* for `string`: `fun (Value) -> Value end` -* for `null`: the atom `null` - -## Errors - -* `error({invalid_byte, Byte})` if `Binary` contains unexpected byte or invalid UTF-8 byte -* `error({invalid_sequence, Bytes})` if `Binary` contains invalid UTF-8 escape -* `error(unexpected_end)` if `Binary` contains incomplete JSON value - -## Example - -Decoding object keys as atoms: - -```erlang -> Push = fun(Key, Value, Acc) -> [{binary_to_existing_atom(Key), Value} | Acc] end. -> json:decode(<<"{\"foo\": 1}">>, ok, #{object_push => Push}). -{#{foo => 1},ok,<<>>} -``` -""". --doc(#{since => <<"OTP 27.0">>}). --spec decode(binary(), dynamic(), decoders()) -> - {Result :: dynamic(), Acc :: dynamic(), binary()}. +-spec decode(binary(), any(), decoders()) -> + {Result :: any(), Acc :: any(), binary()}. decode(Binary, Acc0, Decoders) when is_binary(Binary) -> Decode = maps:fold(fun parse_decoder/3, #decode{}, Decoders), case value(Binary, Binary, 0, Acc0, [], Decode) of @@ -893,40 +610,14 @@ decode(Binary, Acc0, Decoders) when is_b Result end. --doc """ -Begin parsing a stream of bytes of a JSON value. - -Similar to `decode/3` but returns when a complete JSON value can be parsed or -returns `{continue, State}` for incomplete data, -the `State` can be fed to the `decode_continue/2` function when more data is available. -""". --doc(#{since => <<"OTP 27.0">>}). --spec decode_start(binary(), dynamic(), decoders()) -> - {Result :: dynamic(), Acc :: dynamic(), binary()} | {continue, continuation_state()}. +-spec decode_start(binary(), any(), decoders()) -> + {Result :: any(), Acc :: any(), binary()} | {continue, continuation_state()}. decode_start(Binary, Acc, Decoders) when is_binary(Binary) -> Decode = maps:fold(fun parse_decoder/3, #decode{}, Decoders), value(Binary, Binary, 0, Acc, [], Decode). --doc """ -Continue parsing a stream of bytes of a JSON value. - -Similar to `decode_start/3`, if the function returns `{continue, State}` and -there is no more data, use `end_of_input` instead of a binary. - -```erlang -> {continue, State} = json:decode_start(<<"{\"foo\":">>, ok, #{}). -> json:decode_continue(<<"1}">>, State). -{#{foo => 1},ok,<<>>} -``` -```erlang -> {continue, State} = json:decode_start(<<"123">>, ok, #{}). -> json:decode_continue(end_of_input, State). -{123,ok,<<>>} -``` -""". --doc(#{since => <<"OTP 27.0">>}). -spec decode_continue(binary() | end_of_input, Opaque::term()) -> - {Result :: dynamic(), Acc :: dynamic(), binary()} | {continue, continuation_state()}. + {Result :: any(), Acc :: any(), binary()} | {continue, continuation_state()}. decode_continue(end_of_input, State) -> case State of {_, Acc, [], _Decode, {number, Val}} -> @@ -1125,7 +816,7 @@ string_ascii(Binary, Original, Skip, Acc string(Other, Original, Skip, Acc, Stack, Decode, Len) end. --spec string(binary(), binary(), integer(), acc(), stack(), decode(), integer()) -> dynamic(). +-spec string(binary(), binary(), integer(), acc(), stack(), decode(), integer()) -> any(). string(<<Byte, Rest/bits>>, Orig, Skip, Acc, Stack, Decode, Len) when ?is_ascii_plain(Byte) -> string(Rest, Orig, Skip, Acc, Stack, Decode, Len + 1); string(<<$\\, Rest/bits>>, Orig, Skip, Acc, Stack, Decode, Len) -> @@ -1168,7 +859,7 @@ string_ascii(Binary, Original, Skip, Acc string(Other, Original, Skip, Acc, Stack, Decode, Start, Len, SAcc) end. --spec string(binary(), binary(), integer(), acc(), stack(), decode(), integer(), integer(), binary()) -> dynamic(). +-spec string(binary(), binary(), integer(), acc(), stack(), decode(), integer(), integer(), binary()) -> any(). string(<<Byte, Rest/bits>>, Orig, Skip, Acc, Stack, Decode, Start, Len, SAcc) when ?is_ascii_plain(Byte) -> string(Rest, Orig, Skip, Acc, Stack, Decode, Start, Len + 1, SAcc); string(<<$\\, Rest/bits>>, Orig, Skip, Acc, Stack, Decode, Start, Len, SAcc) -> diff -Ndurp otp_src_25.3.2.14/lib/stdlib/test/json_SUITE.erl otp_src_25.3.2.14-lib-stdlib-json-compat/lib/stdlib/test/json_SUITE.erl --- otp_src_25.3.2.14/lib/stdlib/test/json_SUITE.erl 2024-10-11 08:45:35.441679844 +0300 +++ otp_src_25.3.2.14-lib-stdlib-json-compat/lib/stdlib/test/json_SUITE.erl 2024-10-11 09:11:32.614056275 +0300 @@ -311,143 +311,133 @@ format(Term) -> iolist_to_binary(json:fo format(Term, Arg) -> iolist_to_binary(json:format(Term, Arg)). test_format_list(_Config) -> - ?assertEqual(~"[]\n", format([])), + ?assertEqual(<<"[]\n">>, format([])), - List10 = ~'[1,2,3,4,5,6,7,8,9,10]\n', + List10 = <<"[1,2,3,4,5,6,7,8,9,10]\n">>, ?assertEqual(List10, format(lists:seq(1,10))), - ListWithLists = ~""" - [ - [1,2], - [3,4] - ] - - """, + ListWithLists = << + "[\n" + " [1,2],\n" + " [3,4]\n" + "]\n" + >>, ?assertEqual(ListWithLists, format([[1,2],[3,4]])), - ListWithListWithList = ~""" - [ - [ - [] - ], - [ - [3,4] - ] - ] - - """, + ListWithListWithList = << + "[\n" + " [\n" + " []\n" + " ],\n" + " [\n" + " [3,4]\n" + " ]\n" + "]\n" + >>, ?assertEqual(ListWithListWithList, format([[[]],[[3,4]]])), - ListWithMap = ~""" - [ - { "key": 1 } - ] - - """, + ListWithMap = << + "[\n" + " { \"key\": 1 }\n" + "]\n" + >>, ?assertEqual(ListWithMap, format([#{key => 1}])), - ListList10 = ~""" - [ - [1,2,3,4,5, - 6,7,8,9, - 10] - ] - - """, + ListList10 = << + "[\n" + " [1,2,3,4,5,\n" + " 6,7,8,9,\n" + " 10]\n" + "]\n" + >>, ?assertEqual(ListList10, format([lists:seq(1,10)], #{indent => 4, max => 14})), - ListString = ~""" - [ - "foo", - "bar", - "baz" - ] - - """, - ?assertEqual(ListString, format([~"foo", ~"bar", ~"baz"], #{indent => 3})), + ListString = << + "[\n" + " \"foo\",\n" + " \"bar\",\n" + " \"baz\"\n" + "]\n" + >>, + ?assertEqual(ListString, format([<<"foo">>, <<"bar">>, <<"baz">>], #{indent => 3})), ok. test_format_map(_Config) -> - ?assertEqual(~'{}\n', format(#{})), - ?assertEqual(~'{ "key": "val" }\n', format(#{key => val})), - MapSingleMap = ~""" - { - "key1": { "key3": "val3" }, - "key2": 42 - } - - """, + ?assertEqual(<<"{}\n>>, format(#{})), + ?assertEqual(<<"{ \"key\": \"val\" }\n">>, format(#{key => val})), + MapSingleMap = << + "{\n" + " \"key1\": { \"key3\": \"val3\" },\n" + " \"key2\": 42\n" + "}\n" + >>, ?assertEqual(MapSingleMap, format(#{key1 => #{key3 => val3}, key2 => 42})), - MapNestedMap = ~""" - { - "key1": { - "key3": true, - "key4": { - "deep1": 4711, - "deep2": "string" - } - }, - "key2": 42 - } - - """, + MapNestedMap = << + "{\n" + " \"key1\": {\n" + " \"key3\": true,\n" + " \"key4\": {\n" + " \"deep1\": 4711,\n" + " \"deep2\": \"string\"\n" + " }\n" + " },\n" + " \"key2\": 42\n" + "}\n" + >>, ?assertEqual(MapNestedMap, format(#{key1 => #{key3 => true, - key4 => #{deep1 => 4711, deep2 => ~'string'}}, + key4 => #{deep1 => 4711, deep2 => <<"string">>}}, key2 => 42})), - MapIntList = ~""" - { - "key1": [1,2,3,4,5], - "key2": 42 - } - - """, + MapIntList = << + "{\n" + " \"key1\": [1,2,3,4,5],\n" + " \"key2\": 42\n" + "}\n" + >>, ?assertEqual(MapIntList, format(#{key1 => lists:seq(1,5), key2 => 42})), - MapObjList = ~""" - { - "key1": [ - { - "key3": true, - "key4": [1,2,3,4,5] - }, - { - "key3": true, - "key4": [1,2,3,4,5] - } - ], - "key2": 42 - } - - """, + MapObjList = << + "{\n" + " \"key1\": [\n" + " {\n" + " \"key3\": true,\n" + " \"key4\": [1,2,3,4,5]\n" + " },\n" + " {\n" + " \"key3\": true,\n" + " \"key4\": [1,2,3,4,5]\n" + " }\n" + " ],\n" + " \"key2\": 42\n" + "}\n" + >>, ?assertEqual(MapObjList, format(#{key1 => [#{key3 => true, key4 => lists:seq(1,5)}, #{key3 => true, key4 => lists:seq(1,5)}], key2 => 42})), - MapObjList2 = ~""" - { - "key1": [ - { - "key3": true, - "key4": [1,2, - 3,4,5,6,7,8, - 9,10] - }, - { - "key3": true, - "key_longer_name": [ - 1, - 2, - 3 - ] - } - ], - "key2": 42 - } - - """, + MapObjList2 = << + "{\n" + " \"key1\": [\n" + " {\n" + " \"key3\": true,\n" + " \"key4\": [1,2,\n" + " 3,4,5,6,7,8,\n" + " 9,10]\n" + " },\n" + " {\n" + " \"key3\": true,\n" + " \"key_longer_name\": [\n" + " 1,\n" + " 2,\n" + " 3\n" + " ]\n" + " }\n" + " ],\n" + " \"key2\": 42\n" + "}\n" + >>, ?assertEqual(MapObjList2, format(#{key1 => [#{key3 => true, key4 => lists:seq(1,10)}, #{key3 => true, key_longer_name => lists:seq(1,3)}], @@ -460,9 +450,9 @@ test_format_map(_Config) -> -record(rec, {a,b,c}). test_format_fun(_Config) -> - All = #{types => [[], #{}, true, false, null, #{foo => ~"baz"}], + All = #{types => [[], #{}, true, false, null, #{foo => <<"baz">>}], numbers => [1, -10, 0.0, -0.0, 2.0, -2.0], - strings => [~"three", ~"åäö", ~"mixed_Ω"], + strings => [<<"three">>, <<"åäö"/utf8>>, <<"mixed_Ω"/utf8>>], user_data => #rec{a = 1, b = 2, c = 3} }, Formatter = fun(#rec{a=A, b=B, c=C}, _Fun, _State) -> @@ -471,26 +461,25 @@ test_format_fun(_Config) -> (Other, Fun, State) -> json:format_value(Other, Fun, State) end, - Formatted = ~""" - { - "numbers": [1,-10,0.0,-0.0,2.0,-2.0], - "strings": [ - "three", - "åäö", - "mixed_Ω" - ], - "types": [ - [], - {}, - true, - false, - null, - { "foo": "baz" } - ], - "user_data": {"type":"rec","a":1,"b":2,"c":3} - } - - """, + Formatted = << + "{\n" + " \"numbers\": [1,-10,0.0,-0.0,2.0,-2.0],\n" + " \"strings\": [\n" + " \"three\",\n" + " \"åäö\",\n" + " \"mixed_Ω\"\n" + " ],\n" + " \"types\": [\n" + " [],\n" + " {},\n" + " true,\n" + " false,\n" + " null,\n" + " { \"foo\": \"baz\" }\n" + " ],\n" + " \"user_data\": {\"type\":\"rec\",\"a\":1,\"b\":2,\"c\":3}\n" + "}\n" + /utf8>>, ?assertEqual(Formatted, format(All, Formatter)), ok. @@ -756,19 +745,19 @@ set_history(Ty, Acc, Res) -> Res. test_decode_api_stream(_Config) -> - Types = ~#{"types": [[], {}, true, false, null, {"foo": "baz"}], - "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"] - } - #, + Types = <<"{\"types\": [[], {}, true, false, null, {\"foo\": \"baz\"}], + \"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\"] + } + "/utf8>>, ok = stream_decode(Types), - {12345, ok, B1} = json:decode(ews(~# 12345 "foo" #), ok, #{}), + {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#, + Multiple = <<"12345 1.30 \"String1\" -0.31e2\n[\"an array\"]12345\n">>, ok = multi_stream_decode(Multiple), ok.
Locations
Projects
Search
Status Monitor
Help
OpenBuildService.org
Documentation
API Documentation
Code of Conduct
Contact
Support
@OBShq
Terms
openSUSE Build Service is sponsored by
The Open Build Service is an
openSUSE project
.
Sign Up
Log In
Places
Places
All Projects
Status Monitor