Skip to content

Commit

Permalink
Merge branch 'maint'
Browse files Browse the repository at this point in the history
* maint:
  Add json format functions for key-value lists
  Allow setting certificates via application config
  • Loading branch information
dgud committed Oct 31, 2024
2 parents 21180d9 + 0f854d9 commit e2740b0
Show file tree
Hide file tree
Showing 5 changed files with 271 additions and 10 deletions.
10 changes: 9 additions & 1 deletion lib/public_key/src/pubkey_os_cacerts.erl
Original file line number Diff line number Diff line change
Expand Up @@ -37,7 +37,15 @@
get() ->
case persistent_term:get(?MODULE, not_loaded) of
not_loaded ->
case load() of
_ = application:load(public_key),

Result =
case application:get_env(public_key, cacerts_path) of
{ok, EnvVar} -> load([EnvVar]);
undefined -> load()
end,

case Result of
ok ->
persistent_term:get(?MODULE);
{error, Reason} ->
Expand Down
15 changes: 14 additions & 1 deletion lib/public_key/src/public_key.erl
Original file line number Diff line number Diff line change
Expand Up @@ -2229,7 +2229,20 @@ cacerts_get() ->
%%--------------------------------------------------------------------
-doc(#{title => <<"Certificate API">>,
since => <<"OTP 25.0">>}).
-doc "Loads the OS supplied trusted CA certificates.".
-doc """
Loads the OS supplied trusted CA certificates.
This can be overridden by setting the `cacerts_path`
environment key of the `public_key` application with
the location of an alternative certificate.
You can set it via the command line as:
erl -public_key cacerts_path '"/path/to/certs.pem"'
Use it with care. It is your responsibility to ensure
that the certificates found in this alternative path
can be trusted by the running system.
""".

-spec cacerts_load() -> ok | {error, Reason::term()}.
%%--------------------------------------------------------------------
Expand Down
8 changes: 7 additions & 1 deletion lib/public_key/test/public_key_SUITE.erl
Original file line number Diff line number Diff line change
Expand Up @@ -1692,6 +1692,12 @@ cacerts_load(Config) ->
ok
end,

%% Load from application environment
application:set_env(public_key, cacerts_path, filename:join(Datadir, "cacerts.pem")),
2 = length(public_key:cacerts_get()),
application:unset_env(public_key, cacerts_path),
true = public_key:cacerts_clear(),

%% Load default OS certs
%% there is no default installed OS certs on netbsd
%% can be installed with 'pkgin install mozilla-rootcerts'
Expand All @@ -1709,7 +1715,7 @@ cacerts_load(Config) ->
ok = public_key:cacerts_load(filename:join(Datadir, "cacerts.pem")),
[_TestCert1, _TestCert2] = public_key:cacerts_get(),

%% Re-Load default OS certs
%% Reload default OS certs
try
process_flag(trap_exit, true),
flush(),
Expand Down
66 changes: 59 additions & 7 deletions lib/stdlib/src/json.erl
Original file line number Diff line number Diff line change
Expand Up @@ -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]).

Expand Down Expand Up @@ -694,17 +696,67 @@ format_tail([Head|Tail], Enc, State, IndentAll, IndentRow) ->
format_tail([], _, _, _, _) ->
[].

-doc """
Format function for lists of key-value pairs as JSON objects.
Accepts lists with atom, binary, integer, or float keys.
""".
-doc(#{since => <<"OTP 27.2">>}).

-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).

-doc """
Format function 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.2">>}).

-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) ->
Expand Down
182 changes: 182 additions & 0 deletions lib/stdlib/test/json_SUITE.erl
Original file line number Diff line number Diff line change
Expand Up @@ -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,
Expand Down Expand Up @@ -91,6 +92,7 @@ groups() ->
]},
{format, [parallel], [
test_format_list,
test_format_proplist,
test_format_map,
test_format_fun
]},
Expand Down Expand Up @@ -367,6 +369,186 @@ 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(~"""
{
"a": 1,
"b": "str"
}
""", format({kvlist, [{a, 1}, {b, ~"str"}]}, Formatter)),

?assertEqual(~"""
{
"a": 1,
"b": "str"
}
""", format({kvlist_checked, [{a, 1}, {b, ~"str"}]}, Formatter)),

?assertEqual(~"""
{
"10": 1.0,
"1.0": 10,
"a": "αβ",
"αβ": "a"
}
""", format({kvlist, [{10, 1.0},
{1.0, 10},
{a, ~"αβ"},
{~"αβ", a}
]}, Formatter)),

?assertEqual(~"""
{
"10": 1.0,
"1.0": 10,
"a": "αβ",
"αβ": "a"
}
""", format({kvlist_checked, [{10, 1.0},
{1.0, 10},
{a, ~"αβ"},
{~"αβ", a}
]}, Formatter)),

?assertEqual(~"""
{
"a": 1,
"b": {
"aa": 10,
"bb": 20
},
"c": "str"
}
""", format({kvlist, [{a, 1},
{b, {kvlist, [{aa, 10}, {bb, 20}]}},
{c, ~"str"}
]}, Formatter)),

?assertEqual(~"""
[{
"a1": 1,
"b1": [{
"a11": 1,
"b11": 2
},{
"a12": 3,
"b12": 4
}],
"c1": "str1"
},
{
"a2": 2,
"b2": [{
"a21": 5,
"b21": 6
},{
"a22": 7,
"b22": 8
}],
"c2": "str2"
}]
""", 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(~"""
{
"a": 1,
"b": {
"aa": 10,
"bb": 20
},
"c": "str"
}
""", format({kvlist_checked, [{a, 1},
{b, {kvlist_checked, [{aa, 10}, {bb,20}]}},
{c, ~"str"}
]}, Formatter)),

?assertEqual(~"""
[{
"a1": 1,
"b1": [{
"a11": 1,
"b11": 2
},{
"a12": 3,
"b12": 4
}],
"c1": "str1"
},
{
"a2": 2,
"b2": [{
"a21": 5,
"b21": 6
},{
"a22": 7,
"b22": 8
}],
"c2": "str2"
}]
""", 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})),
Expand Down

0 comments on commit e2740b0

Please sign in to comment.