Skip to content

Commit 0f854d9

Browse files
committed
Merge remote-tracking branch 'upstream/pr/8889' into maint
OTP-19320 * upstream/pr/8889: Add json format functions for key-value lists
2 parents 3c63564 + dd84bb5 commit 0f854d9

File tree

2 files changed

+241
-7
lines changed

2 files changed

+241
-7
lines changed

lib/stdlib/src/json.erl

Lines changed: 59 additions & 7 deletions
Original file line numberDiff line numberDiff line change
@@ -51,7 +51,9 @@ standards. The decoder is tested using [JSONTestSuite](https://github.com/nst/JS
5151

5252
-export([
5353
format/1, format/2, format/3,
54-
format_value/3
54+
format_value/3,
55+
format_key_value_list/3,
56+
format_key_value_list_checked/3
5557
]).
5658
-export_type([formatter/0]).
5759

@@ -694,17 +696,67 @@ format_tail([Head|Tail], Enc, State, IndentAll, IndentRow) ->
694696
format_tail([], _, _, _, _) ->
695697
[].
696698

699+
-doc """
700+
Format function for lists of key-value pairs as JSON objects.
701+
702+
Accepts lists with atom, binary, integer, or float keys.
703+
""".
704+
-doc(#{since => <<"OTP 27.2">>}).
705+
706+
-spec format_key_value_list([{term(), term()}], Encode::formatter(), State::map()) -> iodata().
697707
format_key_value_list(KVList, UserEnc, #{level := Level} = State) ->
698708
{_,Indent} = indent(State),
699709
NextState = State#{level := Level+1},
700710
{KISize, KeyIndent} = indent(NextState),
701711
EncKeyFun = fun(KeyVal, _Fun) -> UserEnc(KeyVal, UserEnc, NextState) end,
702-
Entry = fun(Key, Value) ->
703-
EncKey = key(Key, EncKeyFun),
704-
ValState = NextState#{col := KISize + 2 + erlang:iolist_size(EncKey)},
705-
[$, , KeyIndent, EncKey, ": " | UserEnc(Value, UserEnc, ValState)]
706-
end,
707-
format_object([Entry(Key,Value) || {Key, Value} <- KVList], Indent).
712+
EntryFun = fun({Key, Value}) ->
713+
EncKey = key(Key, EncKeyFun),
714+
ValState = NextState#{col := KISize + 2 + erlang:iolist_size(EncKey)},
715+
[$, , KeyIndent, EncKey, ": " | UserEnc(Value, UserEnc, ValState)]
716+
end,
717+
format_object(lists:map(EntryFun, KVList), Indent).
718+
719+
-doc """
720+
Format function for lists of key-value pairs as JSON objects.
721+
722+
Accepts lists with atom, binary, integer, or float keys.
723+
Verifies that no duplicate keys will be produced in the
724+
resulting JSON object.
725+
726+
## Errors
727+
728+
Raises `error({duplicate_key, Key})` if there are duplicates.
729+
""".
730+
-doc(#{since => <<"OTP 27.2">>}).
731+
732+
-spec format_key_value_list_checked([{term(), term()}], Encoder::formatter(), State::map()) -> iodata().
733+
format_key_value_list_checked(KVList, UserEnc, State) when is_function(UserEnc, 3) ->
734+
{_,Indent} = indent(State),
735+
format_object(do_format_checked(KVList, UserEnc, State), Indent).
736+
737+
do_format_checked([], _, _) ->
738+
[];
739+
740+
do_format_checked(KVList, UserEnc, #{level := Level} = State) ->
741+
NextState = State#{level := Level + 1},
742+
{KISize, KeyIndent} = indent(NextState),
743+
EncKeyFun = fun(KeyVal, _Fun) -> UserEnc(KeyVal, UserEnc, NextState) end,
744+
EncListFun =
745+
fun({Key, Value}, {Acc, Visited0}) ->
746+
EncKey = iolist_to_binary(key(Key, EncKeyFun)),
747+
case is_map_key(EncKey, Visited0) of
748+
true ->
749+
error({duplicate_key, Key});
750+
false ->
751+
Visited1 = Visited0#{EncKey => true},
752+
ValState = NextState#{col := KISize + 2 + erlang:iolist_size(EncKey)},
753+
EncEntry = [$, , KeyIndent, EncKey, ": "
754+
| UserEnc(Value, UserEnc, ValState)],
755+
{[EncEntry | Acc], Visited1}
756+
end
757+
end,
758+
{EncKVList, _} = lists:foldl(EncListFun, {[], #{}}, KVList),
759+
lists:reverse(EncKVList).
708760

709761
format_object([], _) -> <<"{}">>;
710762
format_object([[_Comma,KeyIndent|Entry]], Indent) ->

lib/stdlib/test/json_SUITE.erl

Lines changed: 182 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -39,6 +39,7 @@
3939
test_encode_proplist/1,
4040
test_encode_escape_all/1,
4141
test_format_list/1,
42+
test_format_proplist/1,
4243
test_format_map/1,
4344
test_format_fun/1,
4445
test_decode_atoms/1,
@@ -91,6 +92,7 @@ groups() ->
9192
]},
9293
{format, [parallel], [
9394
test_format_list,
95+
test_format_proplist,
9496
test_format_map,
9597
test_format_fun
9698
]},
@@ -367,6 +369,186 @@ test_format_list(_Config) ->
367369
?assertEqual(ListString, format([~"foo", ~"bar", ~"baz"], #{indent => 3})),
368370
ok.
369371

372+
test_format_proplist(_Config) ->
373+
Formatter = fun({kvlist, KVList}, Fun, State) ->
374+
json:format_key_value_list(KVList, Fun, State);
375+
({kvlist_checked, KVList}, Fun, State) ->
376+
json:format_key_value_list_checked(KVList, Fun, State);
377+
(Other, Fun, State) ->
378+
json:format_value(Other, Fun, State)
379+
end,
380+
381+
?assertEqual(~"""
382+
{
383+
"a": 1,
384+
"b": "str"
385+
}
386+
387+
""", format({kvlist, [{a, 1}, {b, ~"str"}]}, Formatter)),
388+
389+
?assertEqual(~"""
390+
{
391+
"a": 1,
392+
"b": "str"
393+
}
394+
395+
""", format({kvlist_checked, [{a, 1}, {b, ~"str"}]}, Formatter)),
396+
397+
?assertEqual(~"""
398+
{
399+
"10": 1.0,
400+
"1.0": 10,
401+
"a": "αβ",
402+
"αβ": "a"
403+
}
404+
405+
""", format({kvlist, [{10, 1.0},
406+
{1.0, 10},
407+
{a, ~"αβ"},
408+
{~"αβ", a}
409+
]}, Formatter)),
410+
411+
?assertEqual(~"""
412+
{
413+
"10": 1.0,
414+
"1.0": 10,
415+
"a": "αβ",
416+
"αβ": "a"
417+
}
418+
419+
""", format({kvlist_checked, [{10, 1.0},
420+
{1.0, 10},
421+
{a, ~"αβ"},
422+
{~"αβ", a}
423+
]}, Formatter)),
424+
425+
?assertEqual(~"""
426+
{
427+
"a": 1,
428+
"b": {
429+
"aa": 10,
430+
"bb": 20
431+
},
432+
"c": "str"
433+
}
434+
435+
""", format({kvlist, [{a, 1},
436+
{b, {kvlist, [{aa, 10}, {bb, 20}]}},
437+
{c, ~"str"}
438+
]}, Formatter)),
439+
440+
?assertEqual(~"""
441+
[{
442+
"a1": 1,
443+
"b1": [{
444+
"a11": 1,
445+
"b11": 2
446+
},{
447+
"a12": 3,
448+
"b12": 4
449+
}],
450+
"c1": "str1"
451+
},
452+
{
453+
"a2": 2,
454+
"b2": [{
455+
"a21": 5,
456+
"b21": 6
457+
},{
458+
"a22": 7,
459+
"b22": 8
460+
}],
461+
"c2": "str2"
462+
}]
463+
464+
""", format([{kvlist, [{a1, 1},
465+
{b1, [{kvlist, [{a11, 1}, {b11, 2}]},
466+
{kvlist, [{a12, 3}, {b12, 4}]}
467+
]},
468+
{c1, ~"str1"}
469+
]},
470+
{kvlist, [{a2, 2},
471+
{b2, [{kvlist, [{a21, 5}, {b21, 6}]}
472+
,{kvlist, [{a22, 7}, {b22, 8}]}
473+
]},
474+
{c2, ~"str2"}
475+
]}
476+
], Formatter)),
477+
478+
?assertEqual(~"""
479+
{
480+
"a": 1,
481+
"b": {
482+
"aa": 10,
483+
"bb": 20
484+
},
485+
"c": "str"
486+
}
487+
488+
""", format({kvlist_checked, [{a, 1},
489+
{b, {kvlist_checked, [{aa, 10}, {bb,20}]}},
490+
{c, ~"str"}
491+
]}, Formatter)),
492+
493+
?assertEqual(~"""
494+
[{
495+
"a1": 1,
496+
"b1": [{
497+
"a11": 1,
498+
"b11": 2
499+
},{
500+
"a12": 3,
501+
"b12": 4
502+
}],
503+
"c1": "str1"
504+
},
505+
{
506+
"a2": 2,
507+
"b2": [{
508+
"a21": 5,
509+
"b21": 6
510+
},{
511+
"a22": 7,
512+
"b22": 8
513+
}],
514+
"c2": "str2"
515+
}]
516+
517+
""", format([{kvlist_checked,
518+
[{a1, 1},
519+
{b1, [{kvlist_checked, [{a11, 1}, {b11, 2}]},
520+
{kvlist_checked, [{a12, 3}, {b12, 4}]}
521+
]},
522+
{c1, ~"str1"}
523+
]},
524+
{kvlist_checked,
525+
[{a2, 2},
526+
{b2, [{kvlist_checked, [{a21, 5}, {b21, 6}]}
527+
,{kvlist_checked, [{a22, 7}, {b22, 8}]}
528+
]},
529+
{c2, ~"str2"}
530+
]}
531+
], Formatter)),
532+
533+
534+
?assertError({duplicate_key, a},
535+
format({kvlist_checked, [{a, 1}, {b, ~"str"}, {a, 2}]}, Formatter)),
536+
537+
%% on invalid input exact error is not specified
538+
?assertError(_, format({kvlist, [{a, 1}, b]}, Formatter)),
539+
540+
?assertError(_, format({kvlist, x}, Formatter)),
541+
542+
?assertError(_, format({kvlist, [{#{}, 1}]}, Formatter)),
543+
544+
?assertError(_, format({kvlist_checked, [{a, 1}, b]}, Formatter)),
545+
546+
?assertError(_, format({kvlist_checked, x}, Formatter)),
547+
548+
?assertError(_, format({kvlist_checked, [{#{}, 1}]}, Formatter)),
549+
550+
ok.
551+
370552
test_format_map(_Config) ->
371553
?assertEqual(~'{}\n', format(#{})),
372554
?assertEqual(~'{ "key": "val" }\n', format(#{key => val})),

0 commit comments

Comments
 (0)