File 0537-Fix-ERL-1030-SSL-fails-to-handle-cRLIssuer-entry-in-.patch of Package erlang

From 383f0533bf96c6c323d934d3202b9c4e14c67e70 Mon Sep 17 00:00:00 2001
From: Tim Gleeson <tgleeson@cisco.com>
Date: Fri, 6 Sep 2019 10:19:11 +0100
Subject: [PATCH 2/3] Fix ERL-1030: SSL fails to handle 'cRLIssuer' entry in
 CRL DP extension

All ssl_crl_SUITE tests pass, including the new verify_crldp_crlissuer
test.

ssl_dist_SUITE crl_cache_check_pass function still failing.
---
 lib/public_key/src/pubkey_crl.erl |  1 +
 lib/ssl/src/ssl_crl_cache.erl     |  6 ++++++
 lib/ssl/src/ssl_crl_cache_api.erl |  2 +-
 lib/ssl/src/ssl_crl_hash_dir.erl  | 38 ++++++++++++++++++++------------------
 lib/ssl/src/ssl_handshake.erl     |  6 +-----
 5 files changed, 29 insertions(+), 24 deletions(-)

diff --git a/lib/public_key/src/pubkey_crl.erl b/lib/public_key/src/pubkey_crl.erl
index 50abd704de..15aedc0f4d 100644
--- a/lib/public_key/src/pubkey_crl.erl
+++ b/lib/public_key/src/pubkey_crl.erl
@@ -340,6 +340,7 @@ verify_issuer_and_scope(#'OTPCertificate'{tbsCertificate = TBSCert}= Cert,
     end.
 
 dp_crlissuer_to_issuer(DPCRLIssuer) ->
+     %% Assume the cRLIssuer SEQUENCE is of length exactly 1
      [{directoryName, Issuer}] = pubkey_cert_records:transform(DPCRLIssuer, decode),
      Issuer.
 
diff --git a/lib/ssl/src/ssl_crl_cache.erl b/lib/ssl/src/ssl_crl_cache.erl
index 841620ce57..2dc538c251 100644
--- a/lib/ssl/src/ssl_crl_cache.erl
+++ b/lib/ssl/src/ssl_crl_cache.erl
@@ -46,6 +46,12 @@ lookup(#'DistributionPoint'{distributionPoint = {fullName, Names}},
 lookup(_,_,_) ->
     not_available.
 
+select(GenNames, CRLDbHandle) when is_list(GenNames) ->
+    lists:flatmap(fun({directoryName, Issuer}) ->
+                          select(Issuer, CRLDbHandle);
+                     (_) ->
+                          []
+                  end, GenNames);
 select(Issuer, {{_Cache, Mapping},_}) ->
     case ssl_pkix_db:lookup(Issuer, Mapping) of
 	undefined ->
diff --git a/lib/ssl/src/ssl_crl_cache_api.erl b/lib/ssl/src/ssl_crl_cache_api.erl
index 8a750b3929..00e3a641c4 100644
--- a/lib/ssl/src/ssl_crl_cache_api.erl
+++ b/lib/ssl/src/ssl_crl_cache_api.erl
@@ -31,5 +31,5 @@
 
   
 -callback lookup(dist_point(), issuer_name(), crl_cache_ref()) -> not_available | [public_key:der_encoded()].
--callback select(issuer_name(), crl_cache_ref()) ->  [public_key:der_encoded()].
+-callback select(issuer_name() | list(), crl_cache_ref()) ->  [public_key:der_encoded()].
 -callback fresh_crl(dist_point(), public_key:der_encoded()) -> public_key:der_encoded().
diff --git a/lib/ssl/src/ssl_crl_hash_dir.erl b/lib/ssl/src/ssl_crl_hash_dir.erl
index 9478ff9b78..c3972c31ce 100644
--- a/lib/ssl/src/ssl_crl_hash_dir.erl
+++ b/lib/ssl/src/ssl_crl_hash_dir.erl
@@ -27,27 +27,27 @@
 -export([lookup/3, select/2, fresh_crl/2]).
 
 lookup(#'DistributionPoint'{cRLIssuer = CRLIssuer} = DP, CertIssuer, CRLDbInfo) ->
-    Issuer =
-	case CRLIssuer of
-	    asn1_NOVALUE ->
-		%% If the distribution point extension doesn't
-		%% indicate a CRL issuer, use the certificate issuer.
-		CertIssuer;
-	    _ ->
-		CRLIssuer
-	end,
-    %% Find all CRLs for this issuer, and return those that match the
-    %% given distribution point.
-    AllCRLs = select(Issuer, CRLDbInfo),
-    lists:filter(fun(DER) ->
-			 public_key:pkix_match_dist_point(DER, DP)
-		 end, AllCRLs).
+    case CRLIssuer of
+        asn1_NOVALUE ->
+            %% If the distribution point extension doesn't
+            %% indicate a CRL issuer, use the certificate issuer.
+            select(CertIssuer, CRLDbInfo);
+        _ ->
+            CRLs = select(CRLIssuer, CRLDbInfo),
+            lists:filter(fun(DER) ->
+                                 public_key:pkix_match_dist_point(DER, DP)
+                         end, CRLs)
+    end.
 
 fresh_crl(#'DistributionPoint'{}, CurrentCRL) ->
     CurrentCRL.
 
-select(Issuer, {_DbHandle, [{dir, Dir}]}) ->
-    case find_crls(Issuer, Dir) of
+select({rdnSequence, _} = Issuer, DbHandle) ->
+  select([{directoryName, Issuer}], DbHandle);
+select([], _) ->
+    [];
+select([{directoryName, Issuer} | _], {_DbHandle, [{dir, Dir}]}) ->
+    case find_crls(public_key:pkix_normalize_name(Issuer), Dir) of
         [_|_] = DERs ->
 	    DERs;
         [] ->
@@ -62,7 +62,9 @@ select(Issuer, {_DbHandle, [{dir, Dir}]}) ->
                {module, ?MODULE},
                {line, ?LINE}]),
             []
-    end.
+    end;
+select([_ | Rest], CRLDbInfo) ->
+    select(Rest, CRLDbInfo).
 
 find_crls(Issuer, Dir) ->
     case filelib:is_dir(Dir) of
diff --git a/lib/ssl/src/ssl_handshake.erl b/lib/ssl/src/ssl_handshake.erl
index 1c8a2ca452..c0be0fcf3e 100644
--- a/lib/ssl/src/ssl_handshake.erl
+++ b/lib/ssl/src/ssl_handshake.erl
@@ -1792,11 +1792,7 @@ dps_and_crls(OtpCert, Callback, CRLDbHandle, ext) ->
 dps_and_crls(OtpCert, Callback, CRLDbHandle, same_issuer) ->    
     DP = #'DistributionPoint'{distributionPoint = {fullName, GenNames}} = 
 	public_key:pkix_dist_point(OtpCert),
-    CRLs = lists:flatmap(fun({directoryName, Issuer}) -> 
-				 Callback:select(Issuer, CRLDbHandle);
-			    (_) ->
-				 []
-			 end, GenNames),
+    CRLs = Callback:select(GenNames, CRLDbHandle),
     [{DP, {CRL, public_key:der_decode('CertificateList', CRL)}} ||  CRL <- CRLs].
 
 dps_and_crls([], _, Acc) ->
-- 
2.16.4

openSUSE Build Service is sponsored by