File 4741-ssl-adjust-cacertfile-option.patch of Package erlang

From 8c7fa307ed07b89e445ffea1cb3dbdf89fba64c8 Mon Sep 17 00:00:00 2001
From: Jakub Witczak <kuba@erlang.org>
Date: Wed, 27 Jul 2022 14:10:08 +0200
Subject: [PATCH] ssl: adjust cacertfile option

- perform conversions before loading cert data from file
- convert relative path to absolute for avoiding collisions
- convert symlink to actual file path
---
 lib/ssl/src/ssl.erl                  | 15 ++++++++++++---
 lib/ssl/src/ssl_manager.erl          |  2 +-
 lib/ssl/src/ssl_pem_cache.erl        |  1 -
 lib/ssl/src/ssl_pkix_db.erl          |  4 ++--
 lib/ssl/test/ssl_pem_cache_SUITE.erl | 26 +++++++++++++++-----------
 5 files changed, 30 insertions(+), 18 deletions(-)

diff --git a/lib/ssl/src/ssl.erl b/lib/ssl/src/ssl.erl
index 40da543e35..571a00e627 100644
--- a/lib/ssl/src/ssl.erl
+++ b/lib/ssl/src/ssl.erl
@@ -2102,10 +2102,10 @@ validate_option(cacertfile, undefined, _) ->
    <<>>;
 validate_option(cacertfile, Value, _)
   when is_binary(Value) ->
-    Value;
+    unambiguous_path(Value);
 validate_option(cacertfile, Value, _)
   when is_list(Value), Value =/= ""->
-    binary_filename(Value);
+    binary_filename(unambiguous_path(Value));
 validate_option(cacerts, Value, _)
   when Value == undefined;
        is_list(Value) ->
@@ -2579,7 +2579,7 @@ dtls_validate_versions([Version | Rest], Versions) when  Version == 'dtlsv1';
 dtls_validate_versions([Ver| _], Versions) ->
     throw({error, {options, {Ver, {versions, Versions}}}}).
 
-%% The option cacerts overrides cacertsfile
+%% The option cacerts overrides cacertfile
 ca_cert_default(_,_, [_|_]) ->
     undefined;
 ca_cert_default(verify_none, _, _) ->
@@ -2878,3 +2878,12 @@ maybe_client_warn_no_verify(#{verify := verify_none,
     Filters;
 add_filter(Filter, Filters) ->
     [Filter | Filters].
+
+unambiguous_path(Value) ->
+    AbsName = filename:absname(Value),
+    case file:read_link(AbsName) of
+        {ok, PathWithNoLink} ->
+            PathWithNoLink;
+        _ ->
+            AbsName
+    end.
diff --git a/lib/ssl/src/ssl_manager.erl b/lib/ssl/src/ssl_manager.erl
index f4c6dbfc96..2e96624a2b 100644
--- a/lib/ssl/src/ssl_manager.erl
+++ b/lib/ssl/src/ssl_manager.erl
@@ -465,7 +465,7 @@ invalidate_session(Cache, CacheCb, Key, _Session,
 
 clean_cert_db(Ref, CertDb, RefDb, FileMapDb, File) ->
     case ssl_pkix_db:ref_count(Ref, RefDb, 0) of
-	0 ->	  
+	0 ->
 	    ssl_pkix_db:remove(Ref, RefDb),
 	    ssl_pkix_db:remove(File, FileMapDb),
 	    ssl_pkix_db:remove_trusted_certs(Ref, CertDb);
diff --git a/lib/ssl/src/ssl_pem_cache.erl b/lib/ssl/src/ssl_pem_cache.erl
index 1171258b06..9b8505fc3d 100644
--- a/lib/ssl/src/ssl_pem_cache.erl
+++ b/lib/ssl/src/ssl_pem_cache.erl
@@ -52,7 +52,6 @@
 	 }).
 
 -define(CLEAR_PEM_CACHE, 120000).
--define(DEFAULT_MAX_SESSION_CACHE, 1000).
 
 %%====================================================================
 %% API
diff --git a/lib/ssl/src/ssl_pkix_db.erl b/lib/ssl/src/ssl_pkix_db.erl
index afd6e60c2b..056d772644 100644
--- a/lib/ssl/src/ssl_pkix_db.erl
+++ b/lib/ssl/src/ssl_pkix_db.erl
@@ -132,12 +132,12 @@ lookup_trusted_cert(_DbHandle, {extracted,Certs}, SerialNumber, Issuer) ->
 add_trusted_certs(_Pid, {extracted, _} = Certs, _) ->
     {ok, Certs};
 
-add_trusted_certs(_Pid, {der, DerList}, [CertDb, _,_ | _]) ->
+add_trusted_certs(_Pid, {der, DerList}, [CertDb, _, _ | _]) ->
     NewRef = make_ref(),
     add_certs_from_der(DerList, NewRef, CertDb),
     {ok, NewRef};
 
-add_trusted_certs(_Pid, File, [ _, {RefDb, FileMapDb} | _] = Db) ->
+add_trusted_certs(_Pid, File, [_, {RefDb, FileMapDb} | _] = Db) ->
     case lookup(File, FileMapDb) of
 	[Ref] ->
 	    ref_count(Ref, RefDb, 1),
diff --git a/lib/ssl/test/ssl_pem_cache_SUITE.erl b/lib/ssl/test/ssl_pem_cache_SUITE.erl
index 6647bab898..32515b8fbd 100644
--- a/lib/ssl/test/ssl_pem_cache_SUITE.erl
+++ b/lib/ssl/test/ssl_pem_cache_SUITE.erl
@@ -388,24 +388,28 @@ alternative_path_hardlink(Config) when is_list(Config) ->
     alternative_path_helper(Config, fun make_hardlink/1, Expected).
 
 alternative_path_symlink() ->
-    [{doc,"Test that internal reference table contains expected data for"
-      " absolute and symbolic link. "
-      "This test verifies handling of same file with an alternative reference."}].
-%% see alternative_path_hardlink for specification
+    [{doc,"Test that internal reference table contains only one instance of data "
+      "for absolute path and symbolic link pointing to same file."
+      "This test verifies handling of same file with an alternative reference."
+      "Symlink is expected to be converted to absolute file path - "
+      "as a result establishing 2nd connection should not add new data to tables."}].
+%% see alternative_path_hardlink for detailed specification
 alternative_path_symlink(Config) when is_list(Config) ->
     Expected = #{init => [0, 0, 0, 0], connected1 => [6, 6, 2, 2],
-                 connected2 => [7, 9, 3, 3], connected3 => [8, 12, 4, 4],
-                 disconnected => [8, 0, 0, 0]},
+                 connected2 => [6, 6, 2, 2], connected3 => [7, 9, 3, 3],
+                 disconnected => [7, 0, 0, 0]},
     alternative_path_helper(Config, fun make_symlink/1, Expected).
 
 alternative_path_noabspath() ->
-    [{doc,"Test that internal reference table contains expected data for"
-      " absolute and relative paths. "
-      "This test verifies handling of same file with an alternative reference."}].
-%% see alternative_path_hardlink for specification
+    [{doc,"Test that internal reference table contains only one instance of data "
+      "for absolute and relative paths pointing to same file. "
+      "This test verifies handling of same file with an alternative reference."
+      "Relative file path is expected to be converted to absolute file path  - "
+      "as a result establishing 2nd connection should not add new data to tables."}].
+%% see alternative_path_hardlink for detailed specification
 alternative_path_noabspath(Config) when is_list(Config) ->
     Expected = #{init => [0, 0, 0, 0], connected1 => [6, 6, 2, 2],
-                 connected2 => [7, 9, 3, 3], connected3 => [7, 9, 3, 3],
+                 connected2 => [6, 6, 2, 2], connected3 => [7, 9, 3, 3],
                  disconnected => [7, 0, 0, 0]},
     alternative_path_helper(Config, fun strip_path/1, Expected).
 
-- 
2.35.3

openSUSE Build Service is sponsored by