Sign Up
Log In
Log In
or
Sign Up
Places
All Projects
Status Monitor
Collapse sidebar
home:Ledest:erlang:23
erlang
8140-Add-json-format-functions-for-key-value-li...
Overview
Repositories
Revisions
Requests
Users
Attributes
Meta
File 8140-Add-json-format-functions-for-key-value-lists.patch of Package erlang
From dd84bb57afd67134de78220a690da8416492e2d2 Mon Sep 17 00:00:00 2001 From: Svilen Ivanov <isvilen@applicata.bg> Date: Wed, 2 Oct 2024 17:57:57 +0300 Subject: [PATCH] Add json format functions for key-value lists Support formating key-value lists while preserve their ordering. Co-authored-by: Viacheslav Katsuba <v.katsuba.dev@gmail.com> Co-authored-by: Maria Scott <67057258+Maria-12648430@users.noreply.github.com> --- lib/stdlib/src/json.erl | 66 ++++++++++-- lib/stdlib/test/json_SUITE.erl | 182 +++++++++++++++++++++++++++++++++ 2 files changed, 241 insertions(+), 7 deletions(-) diff --git a/lib/stdlib/src/json.erl b/lib/stdlib/src/json.erl index d3437e0c4a..5654e47a3e 100644 --- a/lib/stdlib/src/json.erl +++ b/lib/stdlib/src/json.erl @@ -51,7 +51,9 @@ standards. The decoder is tested using [JSONTestSuite](https://github.com/nst/JS -export([ format/1, format/2, format/3, - format_value/3 + format_value/3, + format_key_value_list/3, + format_key_value_list_checked/3 ]). -export_type([formatter/0]). @@ -694,17 +696,47 @@ format_tail([Head|Tail], Enc, State, IndentAll, IndentRow) -> format_tail([], _, _, _, _) -> []. +-spec format_key_value_list([{term(), term()}], Encode::formatter(), State::map()) -> iodata(). 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). + EntryFun = 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(lists:map(EntryFun, KVList), Indent). + +-spec format_key_value_list_checked([{term(), term()}], Encoder::formatter(), State::map()) -> iodata(). +format_key_value_list_checked(KVList, UserEnc, State) when is_function(UserEnc, 3) -> + {_,Indent} = indent(State), + format_object(do_format_checked(KVList, UserEnc, State), Indent). + +do_format_checked([], _, _) -> + []; + +do_format_checked(KVList, UserEnc, #{level := Level} = State) -> + NextState = State#{level := Level + 1}, + {KISize, KeyIndent} = indent(NextState), + EncKeyFun = fun(KeyVal, _Fun) -> UserEnc(KeyVal, UserEnc, NextState) end, + EncListFun = + fun({Key, Value}, {Acc, Visited0}) -> + EncKey = iolist_to_binary(key(Key, EncKeyFun)), + case is_map_key(EncKey, Visited0) of + true -> + error({duplicate_key, Key}); + false -> + Visited1 = Visited0#{EncKey => true}, + ValState = NextState#{col := KISize + 2 + erlang:iolist_size(EncKey)}, + EncEntry = [$, , KeyIndent, EncKey, ": " + | UserEnc(Value, UserEnc, ValState)], + {[EncEntry | Acc], Visited1} + end + end, + {EncKVList, _} = lists:foldl(EncListFun, {[], #{}}, KVList), + lists:reverse(EncKVList). format_object([], _) -> <<"{}">>; format_object([[_Comma,KeyIndent|Entry]], Indent) -> diff --git a/lib/stdlib/test/json_SUITE.erl b/lib/stdlib/test/json_SUITE.erl index 3ac56f1ed2..70f92848fe 100644 --- a/lib/stdlib/test/json_SUITE.erl +++ b/lib/stdlib/test/json_SUITE.erl @@ -39,6 +39,7 @@ test_encode_proplist/1, test_encode_escape_all/1, test_format_list/1, + test_format_proplist/1, test_format_map/1, test_format_fun/1, test_decode_atoms/1, @@ -91,6 +92,7 @@ groups() -> ]}, {format, [parallel], [ test_format_list, + test_format_proplist, test_format_map, test_format_fun ]}, @@ -362,6 +364,178 @@ test_format_list(_Config) -> ?assertEqual(ListString, format([<<"foo">>, <<"bar">>, <<"baz">>], #{indent => 3})), ok. +test_format_proplist(_Config) -> + Formatter = fun({kvlist, KVList}, Fun, State) -> + json:format_key_value_list(KVList, Fun, State); + ({kvlist_checked, KVList}, Fun, State) -> + json:format_key_value_list_checked(KVList, Fun, State); + (Other, Fun, State) -> + json:format_value(Other, Fun, State) + end, + + ?assertEqual(<< + "{\n" + " \"a\": 1,\n" + " \"b\": \"str\"\n" + "}\n" + >>, format({kvlist, [{a, 1}, {b, <<"str">>}]}, Formatter)), + + ?assertEqual(<< + "{\n" + " \"a\": 1,\n" + " \"b\": \"str\"\n" + "}\n" + >>, format({kvlist_checked, [{a, 1}, {b, <<"str">>}]}, Formatter)), + + ?assertEqual(<< + "{\n" + " \"10\": 1.0,\n" + " \"1.0\": 10,\n" + " \"a\": \"αβ\",\n" + " \"αβ\": \"a\"\n" + "}\n" + /utf8>>, format({kvlist, [{10, 1.0}, + {1.0, 10}, + {a, <<"αβ"/utf8>>}, + {<<"αβ"/utf8>>, a} + ]}, Formatter)), + + ?assertEqual(<< + "{\n" + " \"10\": 1.0,\n" + " \"1.0\": 10,\n" + " \"a\": \"αβ\",\n" + " \"αβ\": \"a\"\n" + "}\n" + /utf8>>, format({kvlist_checked, [{10, 1.0}, + {1.0, 10}, + {a, <<"αβ"/utf8>>}, + {<<"αβ"/utf8>>, a} + ]}, Formatter)), + + ?assertEqual(<< + "{\n" + " \"a\": 1,\n" + " \"b\": {\n" + " \"aa\": 10,\n" + " \"bb\": 20\n" + " },\n" + " \"c\": \"str\"\n" + "}\n" + >>, format({kvlist, [{a, 1}, + {b, {kvlist, [{aa, 10}, {bb, 20}]}}, + {c, <<"str">>} + ]}, Formatter)), + + ?assertEqual(<< + "[{\n" + " \"a1\": 1,\n" + " \"b1\": [{\n" + " \"a11\": 1,\n" + " \"b11\": 2\n" + " },{\n" + " \"a12\": 3,\n" + " \"b12\": 4\n" + " }],\n" + " \"c1\": \"str1\"\n" + " },\n" + " {\n" + " \"a2\": 2,\n" + " \"b2\": [{\n" + " \"a21\": 5,\n" + " \"b21\": 6\n" + " },{\n" + " \"a22\": 7,\n" + " \"b22\": 8\n" + " }],\n" + " \"c2\": \"str2\"\n" + " }]\n" + >>, format([{kvlist, [{a1, 1}, + {b1, [{kvlist, [{a11, 1}, {b11, 2}]}, + {kvlist, [{a12, 3}, {b12, 4}]} + ]}, + {c1, <<"str1">>} + ]}, + {kvlist, [{a2, 2}, + {b2, [{kvlist, [{a21, 5}, {b21, 6}]} + ,{kvlist, [{a22, 7}, {b22, 8}]} + ]}, + {c2, <<"str2">>} + ]} + ], Formatter)), + + ?assertEqual(<< + "{\n" + " \"a\": 1,\n" + " \"b\": {\n" + " \"aa\": 10,\n" + " \"bb\": 20\n" + " },\n" + " \"c\": \"str\"\n" + "}\n" + >>, format({kvlist_checked, [{a, 1}, + {b, {kvlist_checked, [{aa, 10}, {bb,20}]}}, + {c, <<"str">>} + ]}, Formatter)), + + ?assertEqual(<< + "[{\n" + " \"a1\": 1,\n" + " \"b1\": [{\n" + " \"a11\": 1,\n" + " \"b11\": 2\n" + " },{\n" + " \"a12\": 3,\n" + " \"b12\": 4\n" + " }],\n" + " \"c1\": \"str1\"\n" + " },\n" + " {\n" + " \"a2\": 2,\n" + " \"b2\": [{\n" + " \"a21\": 5,\n" + " \"b21\": 6\n" + " },{\n" + " \"a22\": 7,\n" + " \"b22\": 8\n" + " }],\n" + " \"c2\": \"str2\"\n" + " }]\n" + >>, format([{kvlist_checked, + [{a1, 1}, + {b1, [{kvlist_checked, [{a11, 1}, {b11, 2}]}, + {kvlist_checked, [{a12, 3}, {b12, 4}]} + ]}, + {c1, <<"str1">>} + ]}, + {kvlist_checked, + [{a2, 2}, + {b2, [{kvlist_checked, [{a21, 5}, {b21, 6}]} + ,{kvlist_checked, [{a22, 7}, {b22, 8}]} + ]}, + {c2, <<"str2">>} + ]} + ], Formatter)), + + + ?assertError({duplicate_key, a}, + format({kvlist_checked, [{a, 1}, {b, <<"str">>}, {a, 2}]}, Formatter)), + + %% on invalid input exact error is not specified + ?assertError(_, format({kvlist, [{a, 1}, b]}, Formatter)), + + ?assertError(_, format({kvlist, x}, Formatter)), + + ?assertError(_, format({kvlist, [{#{}, 1}]}, Formatter)), + + ?assertError(_, format({kvlist_checked, [{a, 1}, b]}, Formatter)), + + ?assertError(_, format({kvlist_checked, x}, Formatter)), + + ?assertError(_, format({kvlist_checked, [{#{}, 1}]}, Formatter)), + + ok. + test_format_map(_Config) -> ?assertEqual(<<"{}\n>>, format(#{})), ?assertEqual(<<"{ \"key\": \"val\" }\n">>, format(#{key => val})), -- 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