Sign Up
Log In
Log In
or
Sign Up
Places
All Projects
Status Monitor
Collapse sidebar
home:Ledest:erlang:23
erlang
8136-Add-a-formatter-to-json.patch
Overview
Repositories
Revisions
Requests
Users
Attributes
Meta
File 8136-Add-a-formatter-to-json.patch of Package erlang
From 17cbbf82120ce481cd5f1caa96e487b1bc762a7c Mon Sep 17 00:00:00 2001 From: Dan Gudmundsson <dgud@erlang.org> Date: Fri, 24 May 2024 15:16:16 +0200 Subject: [PATCH] Add a formatter to json To aid debugging or storing a readable file, a formatter is needed. --- lib/stdlib/src/json.erl | 203 ++++++++++++++++++++++++++++++++ lib/stdlib/test/json_SUITE.erl | 205 ++++++++++++++++++++++++++++++++- 2 files changed, 407 insertions(+), 1 deletion(-) diff --git a/lib/stdlib/src/json.erl b/lib/stdlib/src/json.erl index 34d39fa128..a3e366724a 100644 --- a/lib/stdlib/src/json.erl +++ b/lib/stdlib/src/json.erl @@ -49,6 +49,12 @@ standards. The decoder is tested using [JSONTestSuite](https://github.com/nst/JS ]). -export_type([encoder/0, encode_value/0]). +-export([ + format/1, format/2, format/3, + format_value/3 + ]). +-export_type([formatter/0]). + -export([ decode/1, decode/3, decode_start/3, decode_continue/2 ]). @@ -535,6 +541,203 @@ invalid_byte(Bin, Skip) -> error_info(Skip) -> [{error_info, #{cause => #{position => 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 +``` +""". + +-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(). +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 :: encode_value(), Encoder::formatter(), Options :: map()) -> iodata(). +format(Term, Encoder, Options) when is_function(Encoder, 3) -> + Def = #{level => 0, + col => 0, + indent => 2, + max => 100 + }, + [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(). +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) -> + json:encode_binary(Bin); +format_value(Int, _Enc, _State) when is_integer(Int) -> + json:encode_integer(Int); +format_value(Float, _Enc, _State) when is_float(Float) -> + json:encode_float(Float); +format_value(List, UserEnc, State) when is_list(List) -> + 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)), + format_key_value_list(OrderedKV, UserEnc, State); +format_value(Other, _Enc, _State) -> + error({unsupported_type, Other}). + +format_list([Head|Rest], UserEnc, #{level := Level, col := Col0, max := Max} = State0) -> + State1 = State0#{level := Level+1}, + {Len, IndentElement} = indent(State1), + if is_list(Head); %% Indent list in lists + is_map(Head); %% Indent maps + is_binary(Head); %% Indent Strings + Col0 > Max -> %% Throw in the towel + State = State1#{col := Len}, + First = UserEnc(Head, UserEnc, State), + {_, IndLast} = indent(State0), + [$[, IndentElement, First, + format_tail(Rest, UserEnc, State, IndentElement, IndentElement), + IndLast, $] ]; + true -> + First = UserEnc(Head, UserEnc, State1), + Col = Col0 + 1 + erlang:iolist_size(First), + [$[, First, + format_tail(Rest, UserEnc, State1#{col := Col}, [], IndentElement), + $] ] + end; +format_list([], _, _) -> + <<"[]">>. + +format_tail([Head|Tail], Enc, #{max := Max, col := Col0} = State, [], IndentRow) + when Col0 < Max -> + EncHead = Enc(Head, Enc, State), + String = [$,|EncHead], + Col = Col0 + 1 + erlang:iolist_size(EncHead), + [String|format_tail(Tail, Enc, State#{col := Col}, [], IndentRow)]; +format_tail([Head|Tail], Enc, State, [], IndentRow) -> + EncHead = Enc(Head, Enc, State), + String = [[$,|IndentRow]|EncHead], + Col = erlang:iolist_size(String)-2, + [String|format_tail(Tail, Enc, State#{col := Col}, [], IndentRow)]; +format_tail([Head|Tail], Enc, State, IndentAll, IndentRow) -> + %% These are handling their own indentation, so optimize away size calculation + EncHead = Enc(Head, Enc, State), + String = [[$,|IndentAll]|EncHead], + [String|format_tail(Tail, Enc, State, IndentAll, IndentRow)]; +format_tail([], _, _, _, _) -> + []. + +format_key_value_list(KVList, UserEnc, #{level := Level} = State) -> + {_,Indent} = indent(State), + NextState = State#{level := Level+1}, + {KISize, KeyIndent} = indent(NextState), + EncKeyFun = fun(KeyVal, _Fun) -> UserEnc(KeyVal, UserEnc, NextState) end, + Entry = fun(Key, Value) -> + EncKey = key(Key, EncKeyFun), + ValState = NextState#{col := KISize + 2 + erlang:iolist_size(EncKey)}, + [$, , KeyIndent, EncKey, ": " | UserEnc(Value, UserEnc, ValState)] + end, + format_object([Entry(Key,Value) || {Key, Value} <- KVList], Indent). + +format_object([], _) -> <<"{}">>; +format_object([[_Comma,KeyIndent|Entry]], Indent) -> + [_Key,_Colon|Value] = Entry, + {_, Rest} = string:take(Value, [$\s,$\n]), + [CP|_] = string:next_codepoint(Rest), + if CP =:= ${ -> + ["{", KeyIndent, Entry, Indent, "}"]; + CP =:= $[ -> + ["{", KeyIndent, Entry, Indent, "}"]; + true -> + ["{ ", Entry, " }"] + end; +format_object([[_Comma,KeyIndent|Entry] | Rest], Indent) -> + ["{", KeyIndent, Entry, Rest, Indent, "}"]. + +indent(#{level := Level, indent := Indent}) -> + 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(N) -> ["\n", lists:duplicate(N, " ")]. + %% %% Decoding implementation %% diff --git a/lib/stdlib/test/json_SUITE.erl b/lib/stdlib/test/json_SUITE.erl index 6c4c5e13d6..122d8a269c 100644 --- a/lib/stdlib/test/json_SUITE.erl +++ b/lib/stdlib/test/json_SUITE.erl @@ -38,6 +38,9 @@ test_encode_list/1, test_encode_proplist/1, test_encode_escape_all/1, + test_format_list/1, + test_format_map/1, + test_format_fun/1, test_decode_atoms/1, test_decode_numbers/1, test_decode_strings/1, @@ -65,6 +68,7 @@ all() -> [ {group, encode}, {group, decode}, + {group, format}, test_json_test_suite, {group, properties}, counterexamples @@ -82,6 +86,12 @@ groups() -> test_encode_proplist, test_encode_escape_all ]}, + {format, [parallel], [ + test_format_list, + test_format_map, + test_format_fun + ]}, + {decode, [parallel], [ test_decode_atoms, test_decode_numbers, @@ -286,6 +296,198 @@ encode_proplist_checked(Term) -> end, iolist_to_binary(json:encode(Term, Encode)). +%% +%% Formatting tests +%% + +format(Term) -> iolist_to_binary(json:format(Term)). +format(Term, Arg) -> iolist_to_binary(json:format(Term, Arg)). + +test_format_list(_Config) -> + ?assertEqual(~"[]\n", format([])), + + List10 = ~'[1,2,3,4,5,6,7,8,9,10]\n', + ?assertEqual(List10, format(lists:seq(1,10))), + + ListWithLists = ~""" + [ + [1,2], + [3,4] + ] + + """, + ?assertEqual(ListWithLists, format([[1,2],[3,4]])), + + ListWithListWithList = ~""" + [ + [ + [] + ], + [ + [3,4] + ] + ] + + """, + ?assertEqual(ListWithListWithList, format([[[]],[[3,4]]])), + + ListWithMap = ~""" + [ + { "key": 1 } + ] + + """, + ?assertEqual(ListWithMap, format([#{key => 1}])), + + ListList10 = ~""" + [ + [1,2,3,4,5, + 6,7,8,9, + 10] + ] + + """, + ?assertEqual(ListList10, format([lists:seq(1,10)], #{indent => 4, max => 14})), + + ListString = ~""" + [ + "foo", + "bar", + "baz" + ] + + """, + ?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(MapSingleMap, format(#{key1 => #{key3 => val3}, key2 => 42})), + + MapNestedMap = ~""" + { + "key1": { + "key3": true, + "key4": { + "deep1": 4711, + "deep2": "string" + } + }, + "key2": 42 + } + + """, + ?assertEqual(MapNestedMap, format(#{key1 => #{key3 => true, + key4 => #{deep1 => 4711, deep2 => ~'string'}}, + key2 => 42})), + MapIntList = ~""" + { + "key1": [1,2,3,4,5], + "key2": 42 + } + + """, + ?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 + } + + """, + ?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 + } + + """, + ?assertEqual(MapObjList2, format(#{key1 => + [#{key3 => true, key4 => lists:seq(1,10)}, + #{key3 => true, key_longer_name => lists:seq(1,3)}], + key2 => 42}, + #{indent => 1, max => 15} + )), + ok. + + +-record(rec, {a,b,c}). + +test_format_fun(_Config) -> + All = #{types => [[], #{}, true, false, null, #{foo => ~"baz"}], + numbers => [1, -10, 0.0, -0.0, 2.0, -2.0], + strings => [~"three", ~"åäö", ~"mixed_Ω"], + user_data => #rec{a = 1, b = 2, c = 3} + }, + Formatter = fun(#rec{a=A, b=B, c=C}, _Fun, _State) -> + List = [{type, rec}, {a, A}, {b, B}, {c, C}], + encode_proplist(List); + (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} + } + + """, + ?assertEqual(Formatted, format(All, Formatter)), + ok. + + %% %% Decoding tests %% @@ -632,7 +834,8 @@ test_type("i_" ++ _) -> no. test_file(yes, File, Data) -> Parsed = decode(Data), - ?assertEqual(Parsed, decode(iolist_to_binary(encode(Parsed))), File); + ?assertEqual(Parsed, decode(iolist_to_binary(encode(Parsed))), File), + ?assertEqual(Parsed, decode(iolist_to_binary(json:format(Parsed))), File); test_file(no, File, Data) -> ?assertError(_, decode(Data), File). -- 2.43.0
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