File 2032-ssl-public_key-Add-functionality-for-generating-X509.patch of Package erlang

From 9f4c3f973e44ee5784d1d7eddf225ca0458f4525 Mon Sep 17 00:00:00 2001
From: Ingela Anderton Andin <ingela@erlang.org>
Date: Fri, 24 Feb 2017 10:32:37 +0100
Subject: [PATCH] ssl, public_key: Add functionality for generating X509 cert
 test data

For now this functionality is located in ssl. And existing
public_key function is extended. However some of the functionality may
be moved to public_key in a later stage.
---
 lib/public_key/src/public_key.erl |   2 +-
 lib/ssl/test/Makefile             |   3 +-
 lib/ssl/test/erl_make_certs.erl   |   2 +-
 lib/ssl/test/ssl_test_lib.erl     |  41 +++--
 lib/ssl/test/x509_test.erl        | 310 ++++++++++++++++++++++++++++++++++++++
 5 files changed, 339 insertions(+), 19 deletions(-)
 create mode 100644 lib/ssl/test/x509_test.erl

diff --git a/lib/public_key/src/public_key.erl b/lib/public_key/src/public_key.erl
index 8f185bbbd..965606045 100644
--- a/lib/public_key/src/public_key.erl
+++ b/lib/public_key/src/public_key.erl
@@ -610,7 +610,7 @@ pkix_match_dist_point(#'CertificateList'{
 
 %%--------------------------------------------------------------------
 -spec pkix_sign(#'OTPTBSCertificate'{},
-		rsa_private_key() | dsa_private_key()) -> Der::binary().
+		rsa_private_key() | dsa_private_key() | ec_private_key()) -> Der::binary().
 %%
 %% Description: Sign a pkix x.509 certificate. Returns the corresponding
 %% der encoded 'Certificate'{}
diff --git a/lib/ssl/test/Makefile b/lib/ssl/test/Makefile
index a2eb4ce44..55d45c98f 100644
--- a/lib/ssl/test/Makefile
+++ b/lib/ssl/test/Makefile
@@ -56,7 +56,8 @@ MODULES = \
 	ssl_upgrade_SUITE\
 	ssl_sni_SUITE \
 	make_certs\
-	erl_make_certs
+	erl_make_certs\
+        x509_test
 
 
 ERL_FILES = $(MODULES:%=%.erl)
diff --git a/lib/ssl/test/erl_make_certs.erl b/lib/ssl/test/erl_make_certs.erl
index a6657be99..af217efc1 100644
--- a/lib/ssl/test/erl_make_certs.erl
+++ b/lib/ssl/test/erl_make_certs.erl
@@ -179,7 +179,7 @@ make_tbs(SubjectKey, Opts) ->
 		      subject(proplists:get_value(subject, Opts),false)
 	      end,
 
-    {#'OTPTBSCertificate'{serialNumber = trunc(random:uniform()*100000000)*10000 + 1,
+    {#'OTPTBSCertificate'{serialNumber = trunc(rand:uniform()*100000000)*10000 + 1,
 			  signature    = SignAlgo,
 			  issuer       = Issuer,
 			  validity     = validity(Opts),
diff --git a/lib/ssl/test/ssl_test_lib.erl b/lib/ssl/test/ssl_test_lib.erl
index 4b740c79d..d91f3de79 100644
--- a/lib/ssl/test/ssl_test_lib.erl
+++ b/lib/ssl/test/ssl_test_lib.erl
@@ -488,23 +488,32 @@ make_dsa_cert(Config) ->
 make_ecdsa_cert(Config) ->
     CryptoSupport = crypto:supports(),
     case proplists:get_bool(ecdsa, proplists:get_value(public_keys, CryptoSupport)) of
-	    true ->
-	    {ServerCaCertFile, ServerCertFile, ServerKeyFile} = 
-		make_cert_files("server", Config, ec, ec, "", [{digest, appropriate_sha(CryptoSupport)}]),
-	    {ClientCaCertFile, ClientCertFile, ClientKeyFile} = 
-		make_cert_files("client", Config, ec, ec, "", [{digest, appropriate_sha(CryptoSupport)}]),
-	    [{server_ecdsa_opts, [{ssl_imp, new},{reuseaddr, true},
-				  {cacertfile, ServerCaCertFile},
-				  {certfile, ServerCertFile}, {keyfile, ServerKeyFile}]},
-	     {server_ecdsa_verify_opts, [{ssl_imp, new},{reuseaddr, true},
-					 {cacertfile, ClientCaCertFile},
-					 {certfile, ServerCertFile}, {keyfile, ServerKeyFile},
-					 {verify, verify_peer}]},
-	     {client_ecdsa_opts, [{ssl_imp, new},
-				  {cacertfile, ClientCaCertFile},
-				  {certfile, ClientCertFile}, {keyfile, ClientKeyFile}]}
+        true ->
+	    %% {ServerCaCertFile, ServerCertFile, ServerKeyFile} = 
+	    %%     make_cert_files("server", Config, ec, ec, "", [{digest, appropriate_sha(CryptoSupport)}]),
+	    %% {ClientCaCertFile, ClientCertFile, ClientKeyFile} = 
+	    %%     make_cert_files("client", Config, ec, ec, "", [{digest, appropriate_sha(CryptoSupport)}]),
+            CertFileBase = filename:join([proplists:get_value(priv_dir, Config), "ecdsa_cert.pem"]),
+            KeyFileBase = filename:join([proplists:get_value(priv_dir, Config), "ecdsa_key.pem"]),
+            CaCertFileBase = filename:join([proplists:get_value(priv_dir, Config), "ecdsa_cacerts.pem"]),
+            CurveOid = hd(tls_v1:ecc_curves(0)),
+            GenCertData = x509_test:gen_test_certs([{server_key_gen, {namedCurve, CurveOid}}, 
+                                                    {client_key_gen, {namedCurve, CurveOid}},
+                                                    {server_key_gen_chain, [{namedCurve, CurveOid},
+                                                                            {namedCurve, CurveOid}]},
+                                                    {client_key_gen_chain, [{namedCurve, CurveOid},
+                                                                            {namedCurve, CurveOid}]},
+                                                    {digest, appropriate_sha(CryptoSupport)}]),
+            [{server_config, ServerConf}, 
+             {client_config, ClientConf}] = 
+                x509_test:gen_pem_config_files(GenCertData, CertFileBase, KeyFileBase, CaCertFileBase),
+	    [{server_ecdsa_opts, [{ssl_imp, new},{reuseaddr, true} | ServerConf]},
+             
+	     {server_ecdsa_verify_opts, [{ssl_imp, new}, {reuseaddr, true},
+					 {verify, verify_peer} | ServerConf]},
+	     {client_ecdsa_opts, [{ssl_imp, new}, {reuseaddr, true}  | ClientConf]}
 	     | Config];
-	_ ->
+	false ->
 	    Config
     end.
 
diff --git a/lib/ssl/test/x509_test.erl b/lib/ssl/test/x509_test.erl
new file mode 100644
index 000000000..5cd5c8eca
--- /dev/null
+++ b/lib/ssl/test/x509_test.erl
@@ -0,0 +1,310 @@
+%%
+%% %CopyrightBegin%
+%%
+%% Copyright Ericsson AB 2017-2017. All Rights Reserved.
+%%
+%% Licensed under the Apache License, Version 2.0 (the "License");
+%% you may not use this file except in compliance with the License.
+%% You may obtain a copy of the License at
+%%
+%%     http://www.apache.org/licenses/LICENSE-2.0
+%%
+%% Unless required by applicable law or agreed to in writing, software
+%% distributed under the License is distributed on an "AS IS" BASIS,
+%% WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied.
+%% See the License for the specific language governing permissions and
+%% limitations under the License.
+%%
+%% %CopyrightEnd%
+%%
+
+%%
+
+-module(x509_test).
+
+-include_lib("public_key/include/public_key.hrl").
+
+-export([gen_test_certs/1, gen_pem_config_files/4]).
+
+gen_test_certs(Opts) ->
+    SRootKey = gen_key(proplists:get_value(server_key_gen, Opts)),
+    CRootKey = gen_key(proplists:get_value(client_key_gen, Opts)),
+    ServerRoot = root_cert("server", SRootKey, Opts),
+    ClientRoot = root_cert("client", CRootKey, Opts),
+    [{ServerCert, ServerKey} | ServerCAsKeys] = config(server, ServerRoot, SRootKey, Opts),
+    [{ClientCert, ClientKey} | ClientCAsKeys] = config(client, ClientRoot, CRootKey, Opts),
+    ServerCAs = ca_config(ClientRoot, ServerCAsKeys),
+    ClientCAs = ca_config(ServerRoot, ClientCAsKeys),
+    [{server_config, [{cert, ServerCert}, {key, ServerKey}, {cacerts, ServerCAs}]}, 
+     {client_config, [{cert, ClientCert}, {key, ClientKey}, {cacerts, ClientCAs}]}].
+
+gen_pem_config_files(GenCertData, CertFileBase, KeyFileBase, CAFileBase) ->
+    ServerConf = proplists:get_value(server_config, GenCertData),
+    ClientConf = proplists:get_value(client_config, GenCertData),
+    
+    ServerCaCertFile = filename:join("server_", CAFileBase),
+    ServerCertFile = filename:join("server_", CertFileBase),
+    ServerKeyFile = filename:join("server_", KeyFileBase),
+    
+    ClientCaCertFile = filename:join("client_", CAFileBase),
+    ClientCertFile = filename:join("client_", CertFileBase),
+    ClientKeyFile = filename:join("client_", KeyFileBase),
+    
+    do_gen_pem_config_files(ServerConf,
+                            ServerCertFile,
+                            ServerKeyFile,
+                            ServerCaCertFile),        
+    do_gen_pem_config_files(ClientConf,
+                            ClientCertFile,
+                            ClientKeyFile,
+                            ClientCaCertFile),
+    [{server_config, [{certfile, ServerCertFile}, {keyfile, ServerKeyFile}, {cacertfile, ServerCaCertFile}]}, 
+     {client_config, [{certfile, ClientCertFile}, {keyfile, ClientKeyFile}, {cacertfile, ClientCaCertFile}]}].
+
+    
+do_gen_pem_config_files(Config, CertFile, KeyFile, CAFile) ->
+    CAs = proplists:get_value(cacerts, Config),
+    Cert = proplists:get_value(cert, Config),
+    Key = proplists:get_value(key, Config),
+    der_to_pem(CertFile, [cert_entry(Cert)]),
+    der_to_pem(KeyFile, [key_entry(Key)]),
+    der_to_pem(CAFile, ca_entries(CAs)).
+   
+cert_entry(Cert) ->
+    {'Certificate', Cert, not_encrypted}.
+
+key_entry(Key = #'RSAPrivateKey'{}) ->
+    Der = public_key:der_encode('RSAPrivateKey', Key),
+    {'RSAPrivateKey', Der, not_encrypted};
+key_entry(Key = #'DSAPrivateKey'{}) ->
+    Der =  public_key:der_encode('DSAPrivateKey', Key),
+    {'DSAPrivateKey', Der, not_encrypted};
+key_entry(Key = #'ECPrivateKey'{}) ->
+    Der =  public_key:der_encode('ECPrivateKey', Key),
+    {'ECPrivateKey', Der, not_encrypted}.
+
+ca_entries(CAs) ->
+    [{'Certificate', CACert, not_encrypted} || CACert <- CAs].
+
+gen_key(KeyGen) ->
+    case is_key(KeyGen) of
+        true ->
+            KeyGen;
+        false ->
+            public_key:generate_key(KeyGen)
+    end.
+
+root_cert(Role, PrivKey, Opts) ->
+    TBS = cert_template(),
+    Issuer = issuer("root", Role, " ROOT CA"),
+    OTPTBS = TBS#'OTPTBSCertificate'{
+               signature = sign_algorithm(PrivKey, Opts),
+               issuer = Issuer,
+               validity = validity(Opts),  
+               subject = Issuer,
+               subjectPublicKeyInfo = public_key(PrivKey),
+               extensions = extensions(Opts)
+              },
+    public_key:pkix_sign(OTPTBS, PrivKey).
+
+config(Role, Root, Key, Opts) ->
+    KeyGenOpt = list_to_atom(atom_to_list(Role) ++ "key_gen_chain"),
+    KeyGens = proplists:get_value(KeyGenOpt, Opts, [{namedCurve, hd(tls_v1:ecc_curves(0))}, 
+                                                    {namedCurve, hd(tls_v1:ecc_curves(0))}]),
+    Keys = lists:map(fun gen_key/1, KeyGens),
+    cert_chain(Role, Root, Key, Opts, Keys).
+
+cert_template() ->
+    #'OTPTBSCertificate'{
+       version = v3,              
+       serialNumber = trunc(rand:uniform()*100000000)*10000 + 1,
+       issuerUniqueID = asn1_NOVALUE,       
+       subjectUniqueID = asn1_NOVALUE
+      }.
+
+issuer(Contact, Role, Name) ->
+  subject(Contact, Role ++ Name).
+
+subject(Contact, Name) ->
+    Opts = [{email, Contact ++ "@erlang.org"},
+	    {name,  Name},
+	    {city, "Stockholm"},
+	    {country, "SE"},
+	    {org, "erlang"},
+	    {org_unit, "automated testing"}],
+    subject(Opts).
+
+subject(SubjectOpts) when is_list(SubjectOpts) ->
+    Encode = fun(Opt) ->
+		     {Type,Value} = subject_enc(Opt),
+		     [#'AttributeTypeAndValue'{type=Type, value=Value}]
+	     end,
+    {rdnSequence, [Encode(Opt) || Opt <- SubjectOpts]}.
+
+subject_enc({name,  Name}) ->       
+    {?'id-at-commonName', {printableString, Name}};
+subject_enc({email, Email}) ->      
+    {?'id-emailAddress', Email};
+subject_enc({city,  City}) ->       
+    {?'id-at-localityName', {printableString, City}};
+subject_enc({state, State}) ->      
+    {?'id-at-stateOrProvinceName', {printableString, State}};
+subject_enc({org, Org}) ->          
+    {?'id-at-organizationName', {printableString, Org}};
+subject_enc({org_unit, OrgUnit}) -> 
+    {?'id-at-organizationalUnitName', {printableString, OrgUnit}};
+subject_enc({country, Country}) ->  
+    {?'id-at-countryName', Country};
+subject_enc({serial, Serial}) ->    
+    {?'id-at-serialNumber', Serial};
+subject_enc({title, Title}) ->      
+    {?'id-at-title', {printableString, Title}};
+subject_enc({dnQualifer, DnQ}) ->   
+    {?'id-at-dnQualifier', DnQ};
+subject_enc(Other) -> 
+    Other.
+
+validity(Opts) ->
+    DefFrom0 = calendar:gregorian_days_to_date(calendar:date_to_gregorian_days(date())-1),
+    DefTo0   = calendar:gregorian_days_to_date(calendar:date_to_gregorian_days(date())+7),
+    {DefFrom, DefTo} = proplists:get_value(validity, Opts, {DefFrom0, DefTo0}),
+    Format = fun({Y,M,D}) -> 
+                     lists:flatten(io_lib:format("~w~2..0w~2..0w000000Z",[Y,M,D])) 
+             end,
+    #'Validity'{notBefore={generalTime, Format(DefFrom)},
+		notAfter ={generalTime, Format(DefTo)}}.
+
+extensions(Opts) ->
+    case proplists:get_value(extensions, Opts, []) of
+	false -> 
+	    asn1_NOVALUE;
+	Exts  -> 
+	    lists:flatten([extension(Ext) || Ext <- default_extensions(Exts)])
+    end.
+
+default_extensions(Exts) ->
+    Def = [{key_usage,undefined}, 
+	   {subject_altname, undefined},
+	   {issuer_altname, undefined},
+	   {basic_constraints, default},
+	   {name_constraints, undefined},
+	   {policy_constraints, undefined},
+	   {ext_key_usage, undefined},
+	   {inhibit_any, undefined},
+	   {auth_key_id, undefined},
+	   {subject_key_id, undefined},
+	   {policy_mapping, undefined}],
+    Filter = fun({Key, _}, D) -> 
+                     lists:keydelete(Key, 1, D) 
+             end,
+    Exts ++ lists:foldl(Filter, Def, Exts).
+       	
+extension({_, undefined}) -> 
+    [];
+extension({basic_constraints, Data}) ->
+    case Data of
+	default ->
+	    #'Extension'{extnID = ?'id-ce-basicConstraints',
+			 extnValue = #'BasicConstraints'{cA=true},
+			 critical=true};
+	false -> 
+	    [];
+	Len when is_integer(Len) ->
+	    #'Extension'{extnID = ?'id-ce-basicConstraints',
+			 extnValue = #'BasicConstraints'{cA=true, pathLenConstraint = Len},
+			 critical = true};
+	_ ->
+	    #'Extension'{extnID = ?'id-ce-basicConstraints',
+			 extnValue = Data}
+    end;
+extension({Id, Data, Critical}) ->
+    #'Extension'{extnID = Id, extnValue = Data, critical = Critical}.
+
+public_key(#'RSAPrivateKey'{modulus=N, publicExponent=E}) ->
+    Public = #'RSAPublicKey'{modulus=N, publicExponent=E},
+    Algo = #'PublicKeyAlgorithm'{algorithm= ?rsaEncryption, parameters='NULL'},
+    #'OTPSubjectPublicKeyInfo'{algorithm = Algo,
+			       subjectPublicKey = Public};
+public_key(#'DSAPrivateKey'{p=P, q=Q, g=G, y=Y}) ->
+    Algo = #'PublicKeyAlgorithm'{algorithm= ?'id-dsa', 
+				 parameters={params, #'Dss-Parms'{p=P, q=Q, g=G}}},
+    #'OTPSubjectPublicKeyInfo'{algorithm = Algo, subjectPublicKey = Y};
+public_key(#'ECPrivateKey'{version = _Version,
+			  privateKey = _PrivKey,
+			  parameters = Params,
+			  publicKey = PubKey}) ->
+    Algo = #'PublicKeyAlgorithm'{algorithm= ?'id-ecPublicKey', parameters=Params},
+    #'OTPSubjectPublicKeyInfo'{algorithm = Algo,
+			       subjectPublicKey = #'ECPoint'{point = PubKey}}.
+
+sign_algorithm(#'RSAPrivateKey'{}, Opts) ->
+    Type = rsa_digest_oid(proplists:get_value(digest, Opts, sha1)),
+    #'SignatureAlgorithm'{algorithm  = Type,
+                          parameters = 'NULL'};
+sign_algorithm(#'DSAPrivateKey'{p=P, q=Q, g=G}, _Opts) ->
+    #'SignatureAlgorithm'{algorithm  = ?'id-dsa-with-sha1',
+                          parameters = {params,#'Dss-Parms'{p=P, q=Q, g=G}}};
+sign_algorithm(#'ECPrivateKey'{parameters = Parms}, Opts) ->
+    Type = ecdsa_digest_oid(proplists:get_value(digest, Opts, sha1)),
+    #'SignatureAlgorithm'{algorithm  = Type,
+                          parameters = Parms}.
+
+rsa_digest_oid(sha1) ->
+    ?'sha1WithRSAEncryption';
+rsa_digest_oid(sha512) ->
+    ?'sha512WithRSAEncryption';
+rsa_digest_oid(sha384) ->
+    ?'sha384WithRSAEncryption';
+rsa_digest_oid(sha256) ->
+    ?'sha256WithRSAEncryption';
+rsa_digest_oid(md5) ->
+   ?'md5WithRSAEncryption'.
+
+ecdsa_digest_oid(sha1) ->
+    ?'ecdsa-with-SHA1';
+ecdsa_digest_oid(sha512) ->
+    ?'ecdsa-with-SHA512';
+ecdsa_digest_oid(sha384) ->
+    ?'ecdsa-with-SHA384';
+ecdsa_digest_oid(sha256) ->
+    ?'ecdsa-with-SHA256'.
+
+ca_config(Root, CAsKeys) ->
+    [Root | [CA || {CA, _}  <- CAsKeys]].
+
+cert_chain(Role, Root, RootKey, Opts, Keys) ->
+    cert_chain(Role, Root, RootKey, Opts, Keys, 0, []).
+
+cert_chain(Role, IssuerCert, IssuerKey, Opts, [Key], _, Acc) ->
+    Cert = cert(Role, public_key:pkix_decode_cert(IssuerCert, otp), IssuerKey, Key, "admin", " Peer cert", Opts),
+    [{Cert, Key}, {IssuerCert, IssuerKey} | Acc];
+cert_chain(Role, IssuerCert, IssuerKey, Opts, [Key | Keys], N, Acc) ->
+    Cert = cert(Role, public_key:pkix_decode_cert(IssuerCert, otp), IssuerKey, Key, "webadmin", 
+                " Intermidiate CA " ++ integer_to_list(N), Opts),
+    cert_chain(Role, Cert, Key, Opts, Keys, N+1, [{IssuerCert, IssuerKey} | Acc]).
+        
+cert(Role, #'OTPCertificate'{tbsCertificate = #'OTPTBSCertificate'{subject = Issuer}}, 
+     PrivKey, Key, Contact, Name, Opts) ->
+    TBS = cert_template(),         
+    OTPTBS = TBS#'OTPTBSCertificate'{
+               signature = sign_algorithm(PrivKey, Opts),
+               issuer =  Issuer,
+               validity = validity(Opts),  
+               subject = subject(Contact, atom_to_list(Role) ++ Name),
+               subjectPublicKeyInfo = public_key(Key),
+               extensions = extensions(Opts)
+              },
+    public_key:pkix_sign(OTPTBS, PrivKey).
+
+is_key(#'DSAPrivateKey'{}) ->
+    true;
+is_key(#'RSAPrivateKey'{}) ->
+    true;
+is_key(#'ECPrivateKey'{}) ->
+    true;
+is_key(_) ->
+    false.
+
+der_to_pem(File, Entries) ->
+    PemBin = public_key:pem_encode(Entries),
+    file:write_file(File, PemBin).
-- 
2.12.1

openSUSE Build Service is sponsored by