File 0525-Fix-mixing-loading-from-file-or-all-files-in-a-dir.patch of Package erlang
From bc28c906ad632d3ae9fc86f6970c5d418db7844c Mon Sep 17 00:00:00 2001
From: Dan Gudmundsson <dgud@erlang.org>
Date: Fri, 27 Oct 2023 15:06:27 +0200
Subject: [PATCH] Fix mixing loading from file or all files in a dir
Previously it was either one or the other, so the latest commit
with Solaris fixes didn't work.
---
lib/public_key/src/pubkey_os_cacerts.erl | 62 +++++++++++++++++-------
lib/public_key/test/public_key_SUITE.erl | 31 ++++++++++++
2 files changed, 76 insertions(+), 17 deletions(-)
diff --git a/lib/public_key/src/pubkey_os_cacerts.erl b/lib/public_key/src/pubkey_os_cacerts.erl
index ee02e9040e..b2e0002bb2 100644
--- a/lib/public_key/src/pubkey_os_cacerts.erl
+++ b/lib/public_key/src/pubkey_os_cacerts.erl
@@ -23,6 +23,7 @@
-module(pubkey_os_cacerts).
-include("public_key.hrl").
+-include_lib("kernel/include/file.hrl").
-export([load/0, load/1, get/0, clear/0, format_error/2]).
-on_load(on_load/0).
@@ -46,15 +47,15 @@ get() ->
load() ->
case os:type() of
{unix, linux} ->
- load_from_file(linux_paths());
+ load(linux_paths(), undefined);
{unix, openbsd} ->
- load_from_file(bsd_paths());
+ load(bsd_paths(), undefined);
{unix, freebsd} ->
- load_from_file(bsd_paths());
+ load(bsd_paths(), undefined);
{unix, netbsd} ->
- load_from_file(bsd_paths());
+ load(bsd_paths(), undefined);
{unix, sunos} ->
- load_from_files(sunos_paths());
+ load(sunos_paths(), undefined);
{win32, _} ->
load_win32();
{unix, darwin} ->
@@ -68,24 +69,53 @@ load() ->
%% Can be used when load/0 doesn't work for an unsupported os type.
-spec load([file:filename_all()]) -> ok | {error, Reason::term()}.
load(Paths) ->
- load_from_file(Paths).
-
+ load(Paths, {error, enoent}).
%% cleanup persistent_key
-spec clear() -> boolean().
clear() ->
persistent_term:erase(?MODULE).
+load([Path|Paths], Error) ->
+ case dir_or_file(Path) of
+ enoent ->
+ load(Paths, Error);
+ directory ->
+ case load_from_files(Path) of
+ ok -> ok;
+ Err -> load(Paths, Err)
+ end;
+ file ->
+ case load_from_file(Path) of
+ ok -> ok;
+ Err -> load(Paths, Err)
+ end
+ end;
+load([], Error) ->
+ Error.
+
+dir_or_file(Path) ->
+ case file:read_file_info(Path) of
+ {ok, #file_info{type = directory}} ->
+ directory;
+ {ok, #file_info{type = regular}} ->
+ file;
+ {ok, #file_info{}} -> %% Link
+ case filelib:is_dir(Path) of
+ true -> directory;
+ false -> file
+ end;
+ {error, _} -> enoent
+ end.
+
%% Implementation
-load_from_file([Path|Paths]) when is_list(Path); is_binary(Path) ->
+load_from_file(Path) when is_list(Path); is_binary(Path) ->
try
{ok, Binary} = file:read_file(Path),
ok = decode_result(Binary)
catch _:_Reason ->
- load_from_file(Paths)
- end;
-load_from_file([]) ->
- {error, enoent}.
+ {error, enoent}
+ end.
decode_result(Binary) ->
try
@@ -103,7 +133,6 @@ decode_result(Binary) ->
{error, Reason}
end.
-
load_from_files(Path) ->
MakeCert = fun(FileName, Acc) ->
try
@@ -118,7 +147,6 @@ load_from_files(Path) ->
Certs = filelib:fold_files(Path, ".*\.pem", false, MakeCert, []),
store(Certs).
-
load_win32() ->
Dec = fun({_Enc, Der}, Acc) ->
try
@@ -155,10 +183,10 @@ linux_paths() ->
].
bsd_paths() ->
- ["/usr/local/share/certs/ca-root-nss.crt",
- "/etc/ssl/cert.pem",
+ ["/etc/ssl/cert.pem",
"/etc/openssl/certs/cacert.pem", %% netbsd (if installed)
- "/etc/openssl/certs/ca-certificates.crt"
+ "/etc/openssl/certs/ca-certificates.crt",
+ "/usr/local/share/certs/ca-root-nss.crt"
].
sunos_paths() ->
diff --git a/lib/public_key/test/public_key_SUITE.erl b/lib/public_key/test/public_key_SUITE.erl
index 7cb8ceddd4..68b09f38c2 100644
--- a/lib/public_key/test/public_key_SUITE.erl
+++ b/lib/public_key/test/public_key_SUITE.erl
@@ -1369,6 +1369,37 @@ cacerts_load() ->
cacerts_load(Config) ->
Datadir = proplists:get_value(data_dir, Config),
{error, enoent} = public_key:cacerts_load("/dummy.file"),
+
+ %% White box testing of paths loading
+ %% TestDirs
+ ok = pubkey_os_cacerts:load([filename:join(Datadir, "non_existing_dir"),
+ Datadir,
+ filename:join(Datadir, "cacerts.pem")
+ ]),
+ true = 10 < length(public_key:cacerts_get()),
+ %% We currently pick the first found in input order
+ ok = pubkey_os_cacerts:load([filename:join(Datadir, "non_existing_file"),
+ filename:join(Datadir, "ldap_uri_cert.pem"),
+ filename:join(Datadir, "cacerts.pem")]),
+ 1 = length(public_key:cacerts_get()),
+ ok = pubkey_os_cacerts:load([filename:join(Datadir, "non_existing_file"),
+ filename:join(Datadir, "cacerts.pem"),
+ filename:join(Datadir, "ldap_uri_cert.pem")]),
+ 2 = length(public_key:cacerts_get()),
+
+ true = public_key:cacerts_clear(),
+
+ LinkedCaCerts = filename:join(Datadir, "link_to_cacerts.pem"),
+ case file:make_symlink(filename:join(Datadir, "cacerts.pem"), LinkedCaCerts) of
+ ok ->
+ ok = pubkey_os_cacerts:load([LinkedCaCerts]),
+ 2 = length(public_key:cacerts_get()),
+ true = public_key:cacerts_clear(),
+ ok = file:delete(LinkedCaCerts);
+ _ ->
+ ok
+ end,
+
%% Load default OS certs
%% there is no default installed OS certs on netbsd
%% can be installed with 'pkgin install mozilla-rootcerts'
--
2.35.3