File 4543-ssl-Use-specs-better-in-doc.patch of Package erlang

From 59716e72ff68354719fe80e139c8c5fef1902cd0 Mon Sep 17 00:00:00 2001
From: Ingela Anderton Andin <ingela@erlang.org>
Date: Mon, 27 Sep 2021 16:46:10 +0200
Subject: [PATCH 3/5] ssl: Use specs better in doc

---
 lib/public_key/doc/src/public_key.xml | 230 +++++++++++++-------------
 lib/public_key/src/pubkey_cert.erl    |  28 +---
 lib/public_key/src/public_key.erl     | 158 ++++++++++--------
 lib/ssl/src/ssl_certificate.erl       |   2 +-
 lib/ssl/src/ssl_manager.erl           |   2 +-
 lib/ssl/src/ssl_pkix_db.erl           |   2 +-
 6 files changed, 214 insertions(+), 208 deletions(-)

diff --git a/lib/public_key/doc/src/public_key.xml b/lib/public_key/doc/src/public_key.xml
index f4eb4bdefd..a647b7547e 100644
--- a/lib/public_key/doc/src/public_key.xml
+++ b/lib/public_key/doc/src/public_key.xml
@@ -122,6 +122,7 @@
 
     <datatype>
       <name name="ed_public_key"/>
+      <name name="ed_legacy_pubkey"/>
       <desc>
 	<warning><p>The tagged ed_pub format will not be returned from any public_key
 	functions but can be used as input, should be considered deprecated.</p></warning>
@@ -144,6 +145,7 @@
 
     <datatype>
       <name name="ed_private_key"/>
+      <name name="ed_legacy_privkey"/>
       <desc>
 	<warning><p>The tagged ed_pri format will not be returned from any public_key
 	functions but can be used as input, should be considered deprecated.</p></warning>
@@ -153,7 +155,7 @@
     <datatype>
       <name name="ed_oid_name"/>
       <desc>
-	Macro names for object identifiers for EDDSA curves used by prefixing with ?
+	<p>Macro names for object identifiers for EDDSA curves used by prefixing with ?</p>
       </desc>
     </datatype>
 
@@ -170,18 +172,54 @@
       </desc>
     </datatype>
 
+    <datatype>
+      <name name="issuer_name"/>
+      <desc>
+      </desc>
+    </datatype>
+
+
+    <datatype>
+      <name name="referenceIDs"/>
+      <desc>
+      </desc>
+    </datatype>
+
+    <datatype>
+      <name name="referenceID"/>
+      <desc>
+      </desc>
+    </datatype>
+
     <datatype>
       <name name="cert_id"/>
       <desc>
       </desc>
     </datatype>
 
-     <datatype>
+    <datatype>
       <name name="cert"/>
       <desc>
       </desc>
     </datatype>
 
+     <datatype>
+      <name name="otp_cert"/>
+      <desc>
+      </desc>
+    </datatype>
+
+    <datatype>
+      <name name="der_cert"/>
+      <desc>
+      </desc>
+    </datatype>
+
+    <datatype>
+      <name name="combined_cert"/>
+      <desc>
+      </desc>
+    </datatype>
 
     <datatype>
       <name name="bad_cert_reason"/>
@@ -196,13 +234,43 @@
       </desc>
     </datatype>
 
+    <datatype>
+      <name name="chain_opts"/>
+      <desc>
+      </desc>
+    </datatype>
 
     <datatype>
-      <name name="issuer_name"/>
+      <name name="chain_end"/>
+      <desc>
+      </desc>
+    </datatype>
+
+    <datatype>
+      <name name="cert_opt"/>
       <desc>
       </desc>
     </datatype>
 
+    <datatype>
+      <name name="test_root_cert"/>
+      <desc>
+      </desc>
+    </datatype>
+
+     <datatype>
+      <name name="test_config"/>
+      <desc>
+      </desc>
+     </datatype>
+
+
+     <datatype>
+      <name name="conf_opt"/>
+      <desc>
+      </desc>
+     </datatype>
+
     <datatype>
       <name name="ssh_file"/>
       <desc>
@@ -312,9 +380,9 @@
   
   <func>
     <name name="generate_key" arity="1" since="OTP R16B01"/>
-    <fsummary>Generates a new keypair.</fsummary>
+    <fsummary>Generates a new key pair.</fsummary>
   <desc>
-    <p>Generates a new keypair. Note that except for Diffie-Hellman
+    <p>Generates a new key pair. Note that except for Diffie-Hellman
     the public key is included in the private key structure. See also
     <seemfa marker="crypto:crypto#generate_key/2">crypto:generate_key/2</seemfa>
     </p>
@@ -417,9 +485,9 @@
 
  <func>
    <name name="pkix_issuer_id" arity="2" since="OTP R14B"/>
-   <fsummary>Returns the x509 certificater issuer id.</fsummary>
+   <fsummary>Returns the x509 certificate issuer id.</fsummary>
    <desc> 
-     <p>Returns the x509 certificater issuer id, if it can be determined.</p> 
+     <p>Returns the x509 certificate issuer id, if it can be determined.</p>
    </desc> 
  </func>
  
@@ -647,48 +715,9 @@ fun(#'DistributionPoint'{}, #'CertificateList'{},
   </func>
 
   <func>
-    <name since="OTP 20.1">pkix_test_data(Options) -> Config </name>
-    <name since="OTP 20.1">pkix_test_data([chain_opts()]) -> [conf_opt()]</name>
+    <name  name="pkix_test_data" arity="1" since="OTP 20.1"></name>
     <fsummary>Creates certificate test data.</fsummary>
-    <type>
-      <v>Options = #{chain_type() := chain_opts()} </v>
-      <d>Options for ROOT, Intermediate and Peer certs</d>
-      
-      <v>chain_type() = server_chain | client_chain </v>
-
-      <v>chain_opts() = #{root := [cert_opt()] | root_cert(),
-      peer := [cert_opt()],
-      intermediates => [[cert_opt()]]}</v>
-      <d>
-	A valid chain must have at least a ROOT and a peer cert.
-	The root cert can be given either as a cert pre-generated by
-	<seemfa marker="#pkix_test_root_cert/2">
-	  pkix_test_root_cert/2
-	</seemfa>, or as root cert generation options.
-      </d>
-      <v>root_cert() = #{cert := der_encoded(), key := Key}</v>
-      <d>
-	A root certificate generated by
-	<seemfa marker="#pkix_test_root_cert/2">
-	  pkix_test_root_cert/2
-	</seemfa>.
-      </d>
-      <v>cert_opt() = {Key, Value}</v>
-      <d>For available options see <seeerl marker="#cert_opt"> cert_opt()</seeerl> below.</d>
-
-      <v>Config = #{server_config := [conf_opt()],
-      client_config := [conf_opt()]}</v>
-
-      <v>conf_opt() = {cert, der_encoded()} | {key, PrivateKey} |{cacerts, [der_encoded()]}</v>
-      <d>
-	This is a subset of the type
-	<seetype marker="ssl:ssl#tls_option"> ssl:tls_option()</seetype>.
-	<c>PrivateKey</c> is what
-	<seemfa marker="#generate_key/1">generate_key/1</seemfa>
-	returns.
-      </d>
-    </type>
-    
+
     <desc>
       <p>
 	Creates certificate configuration(s) consisting of certificate
@@ -730,8 +759,8 @@ fun(#'DistributionPoint'{}, #'CertificateList'{},
 	but makes the certificate useful for both roles.
       </p>
       <p>
-	The <marker id="cert_opt"/><c>cert_opt()</c>
-	type consists of the following options:
+	Explanation of the options used to customize certificates
+	in the generated chains:
       </p>
       <taglist>
 	<tag> {digest, digest_type()}</tag>
@@ -780,24 +809,8 @@ fun(#'DistributionPoint'{}, #'CertificateList'{},
   </func>
   
   <func>
-    <name since="OTP 20.2">pkix_test_root_cert(Name, Options) -> RootCert</name>
+    <name name="pkix_test_root_cert" arity="2" since="OTP 20.2"/>
     <fsummary>Generates a test data root cert.</fsummary>
-    <type>
-      <v>Name = string()</v>
-      <d>The root certificate name.</d>
-      <v>Options = [cert_opt()]</v>
-      <d>
-	For available options see
-	<seeerl marker="#cert_opt">cert_opt()</seeerl>
-	under
-	<seemfa marker="#pkix_test_data/1">pkix_test_data/1</seemfa>.
-      </d>
-      <v>RootCert = #{cert := der_encoded(), key := Key}</v>
-      <d>
-	A root certificate and key.  The <c>Key</c> is generated by
-	<seemfa marker="#generate_key/1">generate_key/1</seemfa>.
-      </d>
-    </type>
     <desc>
       <p>
 	Generates a root certificate that can be used
@@ -826,23 +839,11 @@ fun(#'DistributionPoint'{}, #'CertificateList'{},
   </func> 
 
   <func>
-    <name since="OTP 19.3">pkix_verify_hostname(Cert, ReferenceIDs) -> boolean()</name>
-    <name since="OTP 19.3">pkix_verify_hostname(Cert, ReferenceIDs, Opts) -> boolean()</name>
+    <name name="pkix_verify_hostname" arity="2"  since="OTP 19.3"/>
+    <name name="pkix_verify_hostname" arity="3"  since="OTP 19.3"/>
     <fsummary>Verifies that a PKIX x.509 certificate <i>presented identifier</i> (e.g hostname) is
     an expected one.</fsummary>
-    <type>
-      <v>Cert = der_encoded() | #'OTPCertificate'{} </v>
-      <v>ReferenceIDs = [ RefID ]</v>
-      <v>RefID = {dns_id,string()} | {srv_id,string()} | {uri_id,string()} | {ip,inet:ip_address()|string()} | {OtherRefID,term()}}</v>
-      <v>OtherRefID = atom()</v>
-      <v>Opts = [ PvhOpt() ]</v>
-      <v>PvhOpt = [MatchOpt | FailCallBackOpt | FqdnExtractOpt]</v>
-      <v>MatchOpt = {match_fun, fun(RefId | FQDN::string(), PresentedID) -> boolean() | default}</v>
-      <v>PresentedID = {dNSName,string()} | {uniformResourceIdentifier,string() | {iPAddress,list(byte())} | {OtherPresId,term()}}</v>
-      <v>OtherPresID = atom()</v>
-      <v>FailCallBackOpt = {fail_callback, fun(#'OTPCertificate'{}) -> boolean()}</v>
-      <v>FqdnExtractOpt = {fqdn_fun, fun(RefID) -> FQDN::string() | default | undefined}</v>
-    </type>
+
     <desc>
       <p>This function checks that the <i>Presented Identifier</i> (e.g hostname) in a peer certificate
       is in agreement with at least one of the <i>Reference Identifier</i> that the client expects to be connected to.
@@ -856,21 +857,21 @@ fun(#'DistributionPoint'{}, #'CertificateList'{},
       <seeguide marker="using_public_key#verify_hostname_examples">code examples</seeguide>
       describes this function more detailed.
       </p>
-      <p>The <c>{OtherRefId,term()}</c> is defined by the user and is passed to the <c>match_fun</c>, if defined.
-      If the term in <c>OtherRefId</c> is a binary, it will be converted to a string.
-      </p>
-      <p>The <c>ip</c> Reference ID takes an
-      <seetype marker="kernel:inet#ip_address">inet:ip_address()</seetype>
-      or an ip address in string format (E.g "10.0.1.1" or "1234::5678:9012") as second element.
-      </p>
-      <p>The options are:</p>
+
+      <p>The option funs are described here:</p>
       <taglist>
 	<tag><c>match_fun</c></tag>
 	<item>
-	  The <c>fun/2</c> in this option replaces the default host name matching rules. The fun should return a
-	  boolean to tell if the Reference ID and Presented ID matches or not. The fun can also return a third 
-	  value, the atom <c>default</c>, if the default matching rules shall apply.
-	  This makes it possible to augment the tests with a special case:
+	  <code>
+fun(ReferenceId::ReferenceId() | FQDN::string(),
+    PresentedId::{dNSName,string()} | {uniformResourceIdentifier,string() |
+                 {iPAddress,list(byte())} | {OtherId::atom()|oid(),term()}})</code>
+          This function replaces the default host name matching rules. The fun should return a
+	  boolean to tell if the Reference ID and Presented ID matches or not.
+
+	   The match fun can also return a third value,
+	   value, the atom <c>default</c>, if the default matching rules shall apply.
+	   This makes it possible to augment the tests with a special case:
 	  <code>
 fun(....) -> true;   % My special case
    (_, _) -> default % all others falls back to the inherit tests
@@ -880,12 +881,17 @@ end
 	  function that takes a protocol name as argument and returns a <c>fun/2</c> suitable for this option and
 	  <seeguide marker="using_public_key#redefining_match_op">Re-defining the match operation</seeguide>
 	  in the User's Guide for an example.
+
+	  <note><p> Reference Id values given as binaries will be converted to strings, and ip
+           references may be given in string format that is "10.0.1.1" or "1234::5678:9012" as
+           well as on the format <seetype marker="kernel:inet#ip_address">inet:ip_address()</seetype></p></note>
+
 	</item>
 
 	<tag><c>fail_callback</c></tag>
 	<item>If a matching fails, there could be circumstances when the certificate should be accepted anyway. Think for
 	example of a web browser where you choose to accept an outdated certificate. This option enables implementation
-	of such a function. This <c>fun/1</c> is called when no <c>ReferenceID</c> matches. The return value of the fun
+	of such an exception but for hostnames. This <c>fun/1</c> is called when no <c>ReferenceID</c> matches. The return value of the fun
 	(a <c>boolean()</c>) decides the outcome. If <c>true</c> the certificate is accepted otherwise
 	it is rejected. See
 	<seeguide marker="using_public_key#-pinning--a-certificate">"Pinning" a Certificate</seeguide>
@@ -911,29 +917,23 @@ end
   </func>
 
   <func>
-    <name since="OTP 21.0">pkix_verify_hostname_match_fun(Protcol) ->  fun(RefId | FQDN::string(), PresentedID) -> boolean() | default</name>
-    <fsummary>Returns a fun that is intendended as argument to the match_fun option in pkix_verify_hostname/3.
+    <name name="pkix_verify_hostname_match_fun" arity="1"  since="OTP 21.0"/>
+    <fsummary>Returns a fun that is intended as argument to the match_fun option in pkix_verify_hostname/3.
     </fsummary>
-    <type>
-      <v>Protocol = https</v>
-      <d>The algorithm for wich the fun should implement the special matching rules</d>
-      <v>RefId</v>
-      <d>See <seemfa marker="#pkix_verify_hostname/3">pkix_verify_hostname/3</seemfa>.</d>
-      <v>FQDN</v>
-      <d>See <seemfa marker="#pkix_verify_hostname/3">pkix_verify_hostname/3</seemfa>.</d>
-      <v>PresentedID</v>
-      <d>See <seemfa marker="#pkix_verify_hostname/3">pkix_verify_hostname/3</seemfa>.</d>
-    </type>
     <desc>
-      <p>The return value of calling this function is intended to be used in the <c>match_fun</c> option in
-      <seemfa marker="#pkix_verify_hostname/3">pkix_verify_hostname/3</seemfa>.
-      </p>
-      <p>The returned fun augments the verify hostname matching according to the specific rules for
-      the protocol in the argument.
-      </p>
-    </desc>
+	<p>The return value of calling this function is intended to be used in the <c>match_fun</c> option in
+	<seemfa marker="#pkix_verify_hostname/3">pkix_verify_hostname/3</seemfa>.</p>
+
+	<p>The returned fun augments the verify hostname matching according to the specific rules for
+	the protocol in the argument.</p>
+
+	<note><p>Currently supported https fun will allow wildcard certificate matching
+	as specified by the HTTP standard. Note that for instance LDAP have a different set of wildcard matching
+	rules. If you do not want to allow wildcard certificates (recommended from a security perspective)
+	or otherwise customize the hostname match the default match function used by ssl application will be sufficient.
+	</p></note>
+   </desc>
   </func>
-  
 
   <func>
     <name name="sign" arity="3" since=""/>
diff --git a/lib/public_key/src/pubkey_cert.erl b/lib/public_key/src/pubkey_cert.erl
index 5310785328..69c879102c 100644
--- a/lib/public_key/src/pubkey_cert.erl
+++ b/lib/public_key/src/pubkey_cert.erl
@@ -51,22 +51,6 @@
 
 -define(NULL, 0).
 
--export_type([cert_opt/0, chain_opts/0, conf_opt/0,
-              test_config/0, test_root_cert/0]).
-
--type cert_opt()  :: {digest, public_key:digest_type()} | 
-                     {key, public_key:key_params() | public_key:private_key()} | 
-                     {validity, {From::erlang:timestamp(), To::erlang:timestamp()}} |
-                     {extensions, [#'Extension'{}]}.
--type chain_end()   :: root | peer.
--type chain_opts()  :: #{chain_end() := [cert_opt()],  intermediates =>  [[cert_opt()]]}.
--type conf_opt()    :: {cert, public_key:der_encoded()} | 
-                       {key,  public_key:private_key()} |
-                       {cacerts, [public_key:der_encoded()]}.
--type test_config() ::
-        #{server_config := [conf_opt()],  client_config :=  [conf_opt()]}.
--type test_root_cert() ::
-        #{cert := binary(), key := public_key:private_key()}.
 %%====================================================================
 %% Internal application APIs
 %%====================================================================
@@ -468,11 +452,11 @@ match_name(Fun, Name, PermittedName, [Head | Tail]) ->
     end.
 
 %%%
--spec gen_test_certs(#{server_chain:= chain_opts(),
-                       client_chain:= chain_opts()} |
-                     chain_opts()) ->
-                            test_config() |
-                            [conf_opt()].
+-spec gen_test_certs(#{server_chain:= public_key:chain_opts(),
+                       client_chain:= public_key:chain_opts()} |
+                     public_key:chain_opts()) ->
+                            public_key:test_config() |
+                            [public_key:conf_opt()].
 %%
 %% Generates server and and client configuration for testing
 %% purposes. All certificate options have default values
@@ -547,7 +531,7 @@ x509_pkix_sign_types(#'SignatureAlgorithm'{algorithm = Alg}) ->
     {Hash, Sign, []}.
 
 %%%
--spec root_cert(string(), [cert_opt()]) -> test_root_cert().
+-spec root_cert(string(), [public_key:cert_opt()]) -> public_key:test_root_cert().
 %%
 %% Generate a self-signed root cert
 root_cert(Name, Opts) ->
diff --git a/lib/public_key/src/public_key.erl b/lib/public_key/src/public_key.erl
index 0371917009..64739aa9b3 100644
--- a/lib/public_key/src/public_key.erl
+++ b/lib/public_key/src/public_key.erl
@@ -95,9 +95,26 @@
          ocsp_extensions/1
 	]).
 
--export_type([public_key/0, private_key/0, pem_entry/0,
-	      pki_asn1_type/0, asn1_type/0, ssh_file/0, der_encoded/0,
-              key_params/0, digest_type/0, issuer_name/0, cert_id/0, oid/0]).
+-export_type([public_key/0,
+              private_key/0,
+              pem_entry/0,
+	      pki_asn1_type/0,
+              asn1_type/0,
+              ssh_file/0,
+              der_encoded/0,
+              key_params/0,
+              digest_type/0,
+              issuer_name/0,
+              cert/0,
+              combined_cert/0,
+              cert_id/0,
+              oid/0,
+              cert_opt/0,
+              chain_opts/0,
+              conf_opt/0,
+              test_config/0,
+              test_root_cert/0]).
+
 
 -type public_key()           ::  rsa_public_key() | rsa_pss_public_key() | dsa_public_key() | ec_public_key() | ed_public_key() .
 -type private_key()          ::  rsa_private_key() | rsa_pss_private_key() | dsa_private_key() | ec_private_key() | ed_private_key() .
@@ -113,9 +130,10 @@
 -type ecpk_parameters_api() :: ecpk_parameters() | #'ECParameters'{} | {namedCurve, Name::crypto:ec_named_curve()}.
 -type ec_public_key()        :: {#'ECPoint'{}, ecpk_parameters_api()}.
 -type ec_private_key()       :: #'ECPrivateKey'{}.
--type ed_public_key()        :: {#'ECPoint'{}, ed_params()} | {ed_pub, ed25519|ed448, Key::binary()}.
--type ed_private_key()       :: #'ECPrivateKey'{parameters :: ed_params()} |
-                                {ed_pri, ed25519|ed448, Pub::binary(), Priv::binary()}.
+-type ed_public_key()        :: {#'ECPoint'{}, ed_params()}.
+-type ed_legacy_pubkey()     ::  {ed_pub, ed25519|ed448, Key::binary()}.
+-type ed_private_key()       :: #'ECPrivateKey'{parameters :: ed_params()}.
+-type ed_legacy_privkey()        :: {ed_pri, ed25519|ed448, Pub::binary(), Priv::binary()}.
 -type ed_oid_name()            ::  'id-Ed25519' | 'id-Ed448'.
 -type ed_params()            ::  {namedCurve, ed_oid_name()}.
 -type key_params()           :: #'DHParameter'{} | {namedCurve, oid()} | #'ECParameters'{} | 
@@ -150,16 +168,29 @@
 -type crl_reason()           ::  unspecified | keyCompromise | cACompromise | affiliationChanged | superseded
 			       | cessationOfOperation | certificateHold | privilegeWithdrawn |  aACompromise.
 -type oid()                  :: tuple().
--type chain_type()           :: server_chain | client_chain.
-
 -type cert_id()              :: {SerialNr::integer(), issuer_name()} .
 -type issuer_name()          :: {rdnSequence,[[#'AttributeTypeAndValue'{}]]} .
--type bad_cert_reason()      :: cert_expired | invalid_issuer | invalid_signature | name_not_permitted | missing_basic_constraint | invalid_key_usage |
-                                {revoked, crl_reason()} | atom().
--type cert()                 :: #cert{} | der_encoded() | #'OTPCertificate'{}.
+-type bad_cert_reason()      :: cert_expired | invalid_issuer | invalid_signature | name_not_permitted | missing_basic_constraint | invalid_key_usage | {revoked, crl_reason()} | atom().
+
+-type combined_cert()        :: #cert{}.
+-type cert()                 :: der_cert() | otp_cert().
+-type der_cert()             :: der_encoded().
+-type otp_cert()             :: #'OTPCertificate'{}.
 -type public_key_info()      :: {key_oid_name(),  rsa_public_key() | #'ECPoint'{} | dss_public_key(),  public_key_params()}.
 -type key_oid_name()              :: 'rsaEncryption' | 'id-RSASSA-PSS' | 'id-ecPublicKey' | 'id-Ed25519' | 'id-Ed448' | 'id-dsa'.
-
+-type cert_opt()  :: {digest, public_key:digest_type()} |
+                     {key, public_key:key_params() | public_key:private_key()} |
+                     {validity, {From::erlang:timestamp(), To::erlang:timestamp()}} |
+                     {extensions, [#'Extension'{}]}.
+-type chain_end()   :: root | peer.
+-type chain_opts()  :: #{chain_end() := [cert_opt()],  intermediates =>  [[cert_opt()]]}.
+-type conf_opt()    :: {cert, public_key:der_encoded()} |
+                       {key,  public_key:private_key()} |
+                       {cacerts, [public_key:der_encoded()]}.
+-type test_config() ::
+        #{server_config := [conf_opt()],  client_config :=  [conf_opt()]}.
+-type test_root_cert() ::
+        #{cert := der_encoded(), key := public_key:private_key()}.
 
 -define(UINT32(X), X:32/unsigned-big-integer).
 -define(DER_NULL, <<5, 0>>).
@@ -303,7 +334,7 @@ pem_entry_encode(Asn1Type, Entity, {{Cipher, Salt} = CipherInfo,
     
 %%--------------------------------------------------------------------
 -spec der_decode(Asn1Type, Der) -> Entity when Asn1Type :: asn1_type(),
-                                               Der :: binary(),
+                                               Der :: der_encoded(),
                                                Entity :: term().
 %%
 %% Description: Decodes a public key asn1 der encoded entity.
@@ -484,9 +515,9 @@ der_encode(Asn1Type, Entity) when is_atom(Asn1Type) ->
 
 %%--------------------------------------------------------------------
 -spec pkix_decode_cert(Cert, Type) ->
-			      #'Certificate'{} | #'OTPCertificate'{} 
-                                  when Cert :: der_encoded(),
-                                       Type :: plain | otp .
+          #'Certificate'{} | otp_cert()
+              when Cert :: der_cert(),
+                   Type :: plain | otp .
 %%
 %% Description: Decodes an asn1 der encoded pkix certificate. The otp
 %% option will use the customized asn1 specification OTP-PKIX.asn1 for
@@ -794,7 +825,7 @@ pkix_hash_type('id-md5') ->
 -spec sign(Msg, DigestType, Key) ->
                   Signature when Msg ::  binary() | {digest,binary()},
                                  DigestType :: digest_type(),
-                                 Key :: private_key(),
+                                 Key :: private_key() | ed_legacy_privkey(),
                                  Signature :: binary() .
 sign(DigestOrPlainText, DigestType, Key) ->
     sign(DigestOrPlainText, DigestType, Key, []).
@@ -802,7 +833,7 @@ sign(DigestOrPlainText, DigestType, Key) ->
 -spec sign(Msg, DigestType, Key, Options) ->
                   Signature when Msg ::  binary() | {digest,binary()},
                                  DigestType :: digest_type(),
-                                 Key :: private_key(),
+                                 Key :: private_key() | ed_legacy_privkey(),
                                  Options :: crypto:pk_sign_verify_opts(),
                                  Signature :: binary() .
 sign(Digest, none, Key = #'DSAPrivateKey'{}, Options) when is_binary(Digest) ->
@@ -823,7 +854,7 @@ sign(DigestOrPlainText, DigestType, Key, Options) ->
                     boolean() when Msg :: binary() | {digest, binary()},
                                    DigestType :: digest_type(),
                                    Signature :: binary(),
-                                   Key :: public_key() .
+                                   Key :: public_key() | ed_legacy_pubkey().
 
 verify(DigestOrPlainText, DigestType, Signature, Key) ->
     verify(DigestOrPlainText, DigestType, Signature, Key, []).
@@ -832,7 +863,7 @@ verify(DigestOrPlainText, DigestType, Signature, Key) ->
                     boolean() when Msg :: binary() | {digest, binary()},
                                    DigestType :: digest_type(),
                                    Signature :: binary(),
-                                   Key :: public_key(),
+                                   Key :: public_key() | ed_legacy_pubkey(),
                                    Options :: crypto:pk_sign_verify_opts().
 
 verify(Digest, none, Signature, Key = {_, #'Dss-Parms'{}}, Options) when is_binary(Digest) ->
@@ -851,7 +882,7 @@ verify(_,_,_,_,_) ->
     false.
 
 %%--------------------------------------------------------------------
--spec pkix_dist_point(Cert) -> DistPoint when Cert :: der_encoded() | #'OTPCertificate'{},
+-spec pkix_dist_point(Cert) -> DistPoint when Cert :: cert(),
                                               DistPoint :: #'DistributionPoint'{}.
 %% Description:  Creates a distribution point for CRLs issued by the same issuer as <c>Cert</c>.
 %%--------------------------------------------------------------------
@@ -875,7 +906,7 @@ pkix_dist_point(OtpCert) ->
 			 reasons = asn1_NOVALUE,
 			 distributionPoint =  Point}.	
 %%--------------------------------------------------------------------
--spec pkix_dist_points(Cert) -> DistPoints when Cert :: der_encoded() | #'OTPCertificate'{},
+-spec pkix_dist_points(Cert) -> DistPoints when Cert :: cert(),
                                                 DistPoints :: [ #'DistributionPoint'{} ].
 %% Description:  Extracts distributionpoints specified in the certificates extensions.
 %%--------------------------------------------------------------------
@@ -944,7 +975,7 @@ pkix_sign(#'OTPTBSCertificate'{signature =
     pkix_encode('OTPCertificate', Cert, otp).
 
 %%--------------------------------------------------------------------
--spec pkix_verify(Cert, Key) -> boolean() when Cert :: der_encoded(),
+-spec pkix_verify(Cert, Key) -> boolean() when Cert :: der_cert(),
                                                Key :: public_key() .
 %%
 %% Description: Verify pkix x.509 certificate signature.
@@ -983,7 +1014,7 @@ pkix_verify(DerCert, Key = {#'ECPoint'{}, _}) when is_binary(DerCert) ->
 %%--------------------------------------------------------------------
 -spec pkix_crl_verify(CRL, Cert) -> boolean()
                                         when CRL  :: der_encoded() | #'CertificateList'{},
-                                             Cert :: der_encoded() | #'OTPCertificate'{} .
+                                             Cert :: cert().
 %%
 %% Description: Verify that Cert is the CRL signer.
 %%--------------------------------------------------------------------
@@ -1002,12 +1033,9 @@ pkix_crl_verify(#'CertificateList'{} = CRL, #'OTPCertificate'{} = Cert) ->
 				    PublicKey, PublicKeyParams).
 
 %%--------------------------------------------------------------------
--spec pkix_is_issuer(Cert, IssuerCert) -> 
-                            boolean() when Cert :: der_encoded()
-                                                 | #'OTPCertificate'{}
-                                                 | #'CertificateList'{},
-                                           IssuerCert :: der_encoded()
-                                                       | #'OTPCertificate'{} .
+-spec pkix_is_issuer(CertorCRL, IssuerCert) ->
+          boolean() when CertorCRL :: cert() | #'CertificateList'{},
+                         IssuerCert :: cert().
 %%
 %% Description: Checks if <IssuerCert> issued <Cert>.
 %%--------------------------------------------------------------------
@@ -1027,7 +1055,7 @@ pkix_is_issuer(#'CertificateList'{tbsCertList = TBSCRL},
 			  pubkey_cert_records:transform(TBSCRL#'TBSCertList'.issuer, decode)).
 
 %%--------------------------------------------------------------------
--spec pkix_is_self_signed(Cert) -> boolean() when Cert::der_encoded()| #'OTPCertificate'{}.
+-spec pkix_is_self_signed(Cert) -> boolean() when Cert::cert().
 %%
 %% Description: Checks if a Certificate is self signed. 
 %%--------------------------------------------------------------------
@@ -1038,7 +1066,7 @@ pkix_is_self_signed(Cert) when is_binary(Cert) ->
     pkix_is_self_signed(OtpCert).
   
 %%--------------------------------------------------------------------
--spec pkix_is_fixed_dh_cert(Cert) -> boolean() when Cert::der_encoded()| #'OTPCertificate'{}.
+-spec pkix_is_fixed_dh_cert(Cert) -> boolean() when Cert::cert().
 %%
 %% Description: Checks if a Certificate is a fixed Diffie-Hellman Cert.
 %%--------------------------------------------------------------------
@@ -1051,7 +1079,7 @@ pkix_is_fixed_dh_cert(Cert) when is_binary(Cert) ->
 %%--------------------------------------------------------------------
 -spec pkix_issuer_id(Cert, IssuedBy) ->
 			    {ok, ID::cert_id()} | {error, Reason}
-                                when Cert::der_encoded()| #'OTPCertificate'{},
+                                when Cert::cert(),
                                      IssuedBy :: self | other,
                                      Reason :: term() .
 
@@ -1066,7 +1094,7 @@ pkix_issuer_id(Cert, Signed) when is_binary(Cert) ->
 
 %%--------------------------------------------------------------------
 -spec pkix_subject_id(Cert) -> ID
-              when Cert::der_encoded()| #'OTPCertificate'{},
+              when Cert::cert(),
                    ID::cert_id() .
 
 %% Description: Returns the subject id.
@@ -1078,10 +1106,9 @@ pkix_subject_id(Cert) when is_binary(Cert) ->
     pkix_subject_id(OtpCert).
 
 %%--------------------------------------------------------------------
--spec pkix_crl_issuer(CRL| #'CertificateList'{}) -> 
-                             Issuer when CRL :: der_encoded(),
-                                         Issuer :: issuer_name() .
-%
+-spec pkix_crl_issuer(CRL) -> Issuer
+               when CRL :: der_encoded() | #'CertificateList'{},
+                    Issuer :: issuer_name() .
 %% Description: Returns the issuer.
 %%--------------------------------------------------------------------
 pkix_crl_issuer(CRL) when is_binary(CRL) ->
@@ -1106,10 +1133,9 @@ pkix_normalize_name(Issuer) ->
           {ok, {PublicKeyInfo, PolicyTree}} |
           {error, {bad_cert, Reason :: bad_cert_reason()}}
               when
-      Cert::binary()| #'OTPCertificate'{} | atom(),
-      CertChain :: [cert()],
-      Options :: [Option],
-      Option  :: {verify_fun, {fun(), term()}} | {max_path_lengh, integer()},
+      Cert :: cert() | atom(),
+      CertChain :: [cert() | combined_cert()],
+      Options  :: [{max_path_length, integer()} | {verify_fun, {fun(), term()}}],
       PublicKeyInfo :: public_key_info(),
       PolicyTree :: list().
 
@@ -1183,29 +1209,22 @@ pkix_crls_validate(OtpCert, DPAndCRLs0, Options) ->
 
 %--------------------------------------------------------------------
 -type referenceIDs() :: [referenceID()] .
--type referenceID() :: {uri_id | dns_id | ip | srv_id | oid(),  string()} 
-                     | {ip, inet:ip_address()} .
-
--type high_level_alg() :: https .
--type match_fun() ::  fun((ReferenceID::referenceID() | string(),
-                           PresentedID::{atom()|oid(),string()}) -> match_fun_result() ) .
--type match_fun_result() :: boolean() | default .
+-type referenceID() :: {uri_id | dns_id | ip | srv_id | atom() | oid(),  string()}
+                     | {ip, inet:ip_address() | string()} .
 
 %% Description: Validates a hostname to RFC 6125
 %%--------------------------------------------------------------------
 -spec pkix_verify_hostname(Cert, ReferenceIDs) -> boolean()
-                                                      when Cert :: der_encoded() 
-                                                                 | #'OTPCertificate'{},
+                                                      when Cert :: cert(),
                                                            ReferenceIDs :: referenceIDs() .
 pkix_verify_hostname(Cert, ReferenceIDs) ->
     pkix_verify_hostname(Cert, ReferenceIDs, []).
 
 -spec pkix_verify_hostname(Cert, ReferenceIDs, Options) ->
                                   boolean()
-                                      when Cert :: der_encoded() 
-                                                 | #'OTPCertificate'{},
+                                      when Cert :: cert(),
                                            ReferenceIDs :: referenceIDs(),
-                                           Options :: [{atom(),term()}] .
+                                           Options :: [{match_fun | fail_callback | fqdn_fun, fun()}] .
 
 pkix_verify_hostname(BinCert, ReferenceIDs, Options)  when is_binary(BinCert) ->
     pkix_verify_hostname(pkix_decode_cert(BinCert,otp), ReferenceIDs, Options);
@@ -1265,8 +1284,10 @@ pkix_verify_hostname(Cert = #'OTPCertificate'{tbsCertificate = TbsCert}, Referen
 	    end
     end.
 
+-spec pkix_verify_hostname_match_fun(Protocol) ->  Result when
+      Protocol :: https,
+      Result :: fun().
 
--spec pkix_verify_hostname_match_fun(high_level_alg()) -> match_fun() .
 
 pkix_verify_hostname_match_fun(https) ->
     fun({dns_id,FQDN=[_|_]}, {dNSName,Name=[_|_]}) -> verify_hostname_match_wildcard(FQDN, Name);
@@ -1282,8 +1303,8 @@ pkix_verify_hostname_match_fun(https) ->
                                  InternalType :: new_openssh,
                                  Decoded :: Decoded_ssh2_pubkey
                                           | Decoded_OtherType,
-                                 Decoded_ssh2_pubkey :: public_key(),
-                                 Decoded_OtherType :: [{public_key(), Attributes}],
+                                 Decoded_ssh2_pubkey :: public_key() | ed_legacy_pubkey(),
+                                 Decoded_OtherType :: [{public_key() | ed_legacy_pubkey(), Attributes}],
                                  Attributes :: [{atom(),term()}] .
 %%
 %% Description: Decodes a ssh file-binary. In the case of know_hosts
@@ -1308,9 +1329,9 @@ ssh_decode(SshBin, Type) when is_binary(SshBin),
                             when Type :: ssh2_pubkey | OtherType,
                                  OtherType :: public_key | ssh_file(),
                                  InData :: InData_ssh2_pubkey | OtherInData,
-                                 InData_ssh2_pubkey :: public_key(),
+                                 InData_ssh2_pubkey :: public_key() | ed_legacy_pubkey(),
                                  OtherInData :: [{Key,Attributes}],
-                                 Key :: public_key(),
+                                 Key :: public_key() | ed_legacy_pubkey(),
                                  Attributes :: [{atom(),term()}] .
 %%
 %% Description: Encodes a list of ssh file entries (public keys and
@@ -1402,10 +1423,11 @@ short_name_hash({rdnSequence, _Attributes} = Name) ->
 
 
 %%--------------------------------------------------------------------
--spec pkix_test_data(#{chain_type() := pubkey_cert:chain_opts()} |
-                     pubkey_cert:chain_opts()) ->
-                            pubkey_cert:test_config() |
-                            [pubkey_cert:conf_opt()].
+-spec pkix_test_data(ChainConf) -> TestConf when
+      ChainConf :: #{server_chain:= chain_opts(),
+                     client_chain:= chain_opts()} |
+                   chain_opts(),
+      TestConf :: test_config() | [conf_opt()].
 
 %% Description: Generates cert(s) and ssl configuration
 %%--------------------------------------------------------------------
@@ -1425,8 +1447,8 @@ pkix_test_data(#{} = Chain) ->
 -spec pkix_test_root_cert(Name, Options) ->
                                  RootCert
                                      when Name :: string(),
-                                          Options :: [{atom(),term()}], %[cert_opt()],
-                                          RootCert :: pubkey_cert:test_root_cert().
+                                          Options :: [cert_opt()],
+                                          RootCert :: test_root_cert().
 %% Description: Generates a root cert suitable for pkix_test_data/1
 %%--------------------------------------------------------------------
 
@@ -1436,10 +1458,10 @@ pkix_test_root_cert(Name, Opts) ->
 %%--------------------------------------------------------------------
 -spec pkix_ocsp_validate(Cert, IssuerCert, OcspRespDer, 
                          ResponderCerts, NonceExt) -> valid | {bad_cert, Reason}
-              when Cert::der_encoded() | #'OTPCertificate'{},
-                   IssuerCert::der_encoded() | #'OTPCertificate'{}, 
+              when Cert:: cert(),
+                   IssuerCert:: cert(),
                    OcspRespDer::der_encoded(),
-                   ResponderCerts::[der_encoded()],
+                   ResponderCerts::[der_cert()],
                    NonceExt::undefined | binary(),
                    Reason::term().
 
diff --git a/lib/ssl/src/ssl_certificate.erl b/lib/ssl/src/ssl_certificate.erl
index acdc85255f..ebaa9a6bec 100644
--- a/lib/ssl/src/ssl_certificate.erl
+++ b/lib/ssl/src/ssl_certificate.erl
@@ -88,7 +88,7 @@
 
 %%--------------------------------------------------------------------
 -spec trusted_cert_and_paths([der_cert()], db_handle(), certdb_ref(), fun()) ->
-          [{#cert{} | unknown_ca | invalid_issuer | selfsigned_peer, [#cert{}]}].
+          [{public_key:combined_cert() | unknown_ca | invalid_issuer | selfsigned_peer, [public_key:combined_cert()]}].
 %%
 %% Description: Construct input to public_key:pkix_path_validation/3,
 %% If the ROOT cert is not found {bad_cert, unknown_ca} will be returned
diff --git a/lib/ssl/src/ssl_manager.erl b/lib/ssl/src/ssl_manager.erl
index 30c4657e52..1f85bebc45 100644
--- a/lib/ssl/src/ssl_manager.erl
+++ b/lib/ssl/src/ssl_manager.erl
@@ -140,7 +140,7 @@ cache_pem_file(File, DbHandle) ->
 %%--------------------------------------------------------------------
 -spec lookup_trusted_cert(term(), reference(), serialnumber(), issuer()) ->
           undefined |
-          {ok, #cert{}}.
+          {ok, public_key:combined_cert()}.
 %%
 %% Description: Lookup the trusted cert with Key = {reference(),
 %% serialnumber(), issuer()}.
diff --git a/lib/ssl/src/ssl_pkix_db.erl b/lib/ssl/src/ssl_pkix_db.erl
index 0747f022c6..4870a62399 100644
--- a/lib/ssl/src/ssl_pkix_db.erl
+++ b/lib/ssl/src/ssl_pkix_db.erl
@@ -96,7 +96,7 @@ remove(Dbs) ->
 
 %%--------------------------------------------------------------------
 -spec lookup_trusted_cert(db_handle(), certdb_ref(), serialnumber(), issuer()) ->
-				 undefined | {ok, #cert{}}.
+				 undefined | {ok, public_key:combined_cert()}.
 
 %%
 %% Description: Retrieves the trusted certificate identified by 
-- 
2.31.1

openSUSE Build Service is sponsored by