From 2b1a742c651b90f8a7a1fb2ddde73f29915ea376 Mon Sep 17 00:00:00 2001 From: Jakub Witczak Date: Mon, 29 Jan 2024 11:11:53 +0100 Subject: [PATCH 1/2] public_key: OCSP response verification code --- lib/public_key/doc/src/public_key.xml | 25 ++ lib/public_key/src/pubkey_ocsp.erl | 207 ++++++---- lib/public_key/src/public_key.erl | 109 +++-- lib/public_key/test/Makefile | 3 +- lib/public_key/test/pubkey_ocsp_SUITE.erl | 463 +++++++--------------- lib/public_key/test/public_key_SUITE.erl | 101 ++++- 6 files changed, 457 insertions(+), 451 deletions(-) diff --git a/lib/public_key/doc/src/public_key.xml b/lib/public_key/doc/src/public_key.xml index 3e02049bb216..35d0a6e66e70 100644 --- a/lib/public_key/doc/src/public_key.xml +++ b/lib/public_key/doc/src/public_key.xml @@ -771,6 +771,31 @@ fun(#'DistributionPoint'{}, #'CertificateList'{}, + + + Validate OCSP response. + +

Perform OCSP response validation according to RFC + 6960. Returns 'ok' when OCSP response is successfully + validated and {error, {bad_cert, Reason}} otherwise.

+ +

Available options:

+ + {is_trusted_responder_fun, fun()} + +

The fun has the following type specification:

+ fun(#cert{}) -> + boolean() +

The fun returns the true if certificate in the + argument is trusted. If this fun is not specified, Public + Key uses the default implementation: +

+ fun(_) -> false end +
+
+
+
+ Signs certificate. diff --git a/lib/public_key/src/pubkey_ocsp.erl b/lib/public_key/src/pubkey_ocsp.erl index 6bdb9a563f8b..fa4254fd8e80 100644 --- a/lib/public_key/src/pubkey_ocsp.erl +++ b/lib/public_key/src/pubkey_ocsp.erl @@ -19,23 +19,18 @@ %% -module(pubkey_ocsp). +-feature(maybe_expr,enable). -include("public_key.hrl"). -export([find_single_response/3, get_acceptable_response_types_extn/0, get_nonce_extn/1, - get_ocsp_responder_id/1, - ocsp_status/1, - verify_ocsp_response/3, - decode_ocsp_response/1]). + status/1, + verify_response/5, + decode_response/1]). %% Tracing -export([handle_trace/3]). --spec get_ocsp_responder_id(#'Certificate'{}) -> binary(). -get_ocsp_responder_id(#'Certificate'{tbsCertificate = TbsCert}) -> - public_key:der_encode( - 'ResponderID', {byName, TbsCert#'TBSCertificate'.subject}). - -spec get_nonce_extn(undefined | binary()) -> undefined | #'Extension'{}. get_nonce_extn(undefined) -> undefined; @@ -45,10 +40,29 @@ get_nonce_extn(Nonce) when is_binary(Nonce) -> extnValue = Nonce }. --spec verify_ocsp_response(#'BasicOCSPResponse'{}, list(), undefined | binary()) -> +-spec verify_response(#'BasicOCSPResponse'{}, list(), undefined | binary(), + public_key:cert(), fun()) -> {ok, term()} | {error, term()}. -verify_ocsp_response(OCSPResponse, ResponderCerts, Nonce) -> - do_verify_ocsp_response(OCSPResponse, ResponderCerts, Nonce). +verify_response(#'BasicOCSPResponse'{ + tbsResponseData = ResponseData, + signatureAlgorithm = SignatureAlgo, + signature = Signature}, + ResponderCerts, Nonce, IssuerCert, + IsTrustedResponderFun) -> + #'ResponseData'{responderID = ResponderID, + producedAt = ProducedAt} = ResponseData, + maybe + ok ?= verify_past_timestamp(ProducedAt), + ok ?= verify_signature( + public_key:der_encode('ResponseData', ResponseData), + SignatureAlgo#'AlgorithmIdentifier'.algorithm, + Signature, ResponderCerts, + ResponderID, IssuerCert, IsTrustedResponderFun), + verify_nonce(ResponseData, Nonce) + else + {error, Reason} -> + {error, Reason} + end. -spec get_acceptable_response_types_extn() -> #'Extension'{}. get_acceptable_response_types_extn() -> @@ -67,15 +81,15 @@ find_single_response(Cert, IssuerCert, SingleResponseList) -> SerialNum = get_serial_num(Cert), match_single_response(IssuerName, IssuerKey, SerialNum, SingleResponseList). --spec ocsp_status({atom(), term()}) -> atom() | {atom(), {atom(), term()}}. -ocsp_status({good, _}) -> - valid; -ocsp_status({unknown, Reason}) -> - {bad_cert, {revocation_status_undetermined, Reason}}; -ocsp_status({revoked, Reason}) -> - {bad_cert, {revoked, Reason}}. +-spec status({atom(), term()}) -> ok | {error, {bad_cert, term()}}. +status({good, _}) -> + ok; +status({unknown, Reason}) -> + {error, {bad_cert, {revocation_status_undetermined, Reason}}}; +status({revoked, Reason}) -> + {error, {bad_cert, {revoked, Reason}}}. -decode_ocsp_response(ResponseDer) -> +decode_response(ResponseDer) -> Resp = public_key:der_decode('OCSPResponse', ResponseDer), case Resp#'OCSPResponse'.responseStatus of successful -> @@ -92,16 +106,23 @@ match_single_response(_IssuerName, _IssuerKey, _SerialNum, []) -> match_single_response(IssuerName, IssuerKey, SerialNum, [#'SingleResponse'{ certID = #'CertID'{hashAlgorithm = Algo} = CertID} = - Response | Responses]) -> + SingleResponse | Tail]) -> + #'SingleResponse'{thisUpdate = ThisUpdate, + nextUpdate = NextUpdate} = SingleResponse, HashType = public_key:pkix_hash_type(Algo#'AlgorithmIdentifier'.algorithm), case (SerialNum == CertID#'CertID'.serialNumber) andalso (crypto:hash(HashType, IssuerName) == CertID#'CertID'.issuerNameHash) andalso - (crypto:hash(HashType, IssuerKey) == CertID#'CertID'.issuerKeyHash) of + (crypto:hash(HashType, IssuerKey) == CertID#'CertID'.issuerKeyHash) andalso + verify_past_timestamp(ThisUpdate) == ok andalso + verify_next_update(NextUpdate) == ok of true -> - {ok, Response}; + {ok, SingleResponse}; false -> - match_single_response(IssuerName, IssuerKey, SerialNum, Responses) - end. + match_single_response(IssuerName, IssuerKey, SerialNum, Tail) + end; +match_single_response(IssuerName, IssuerKey, SerialNum, + [_BadSingleResponse | Tail]) -> + match_single_response(IssuerName, IssuerKey, SerialNum, Tail). get_serial_num(#'OTPCertificate'{tbsCertificate = TbsCert}) -> TbsCert#'OTPTBSCertificate'.serialNumber. @@ -113,24 +134,7 @@ decode_response_bytes(#'ResponseBytes'{ decode_response_bytes(#'ResponseBytes'{responseType = RespType}) -> {error, {ocsp_response_type_not_supported, RespType}}. -do_verify_ocsp_response(#'BasicOCSPResponse'{ - tbsResponseData = ResponseData, - signatureAlgorithm = SignatureAlgo, - signature = Signature}, - ResponderCerts, Nonce) -> - #'ResponseData'{responderID = ResponderID} = ResponseData, - case verify_ocsp_signature( - public_key:der_encode('ResponseData', ResponseData), - SignatureAlgo#'AlgorithmIdentifier'.algorithm, - Signature, ResponderCerts, - ResponderID) of - ok -> - verify_ocsp_nonce(ResponseData, Nonce); - {error, Reason} -> - {error, Reason} - end. - -verify_ocsp_nonce(ResponseData, Nonce) -> +verify_nonce(ResponseData, Nonce) -> #'ResponseData'{responses = Responses, responseExtensions = ResponseExtns} = ResponseData, case get_nonce_value(ResponseExtns) of @@ -153,31 +157,91 @@ get_nonce_value([#'Extension'{ get_nonce_value([_Extn | Rest]) -> get_nonce_value(Rest). -verify_ocsp_signature(ResponseDataDer, SignatureAlgo, Signature, - Certs, ResponderID) -> - case find_responder_cert(ResponderID, Certs) of - {ok, Cert} -> - do_verify_ocsp_signature( - ResponseDataDer, Signature, SignatureAlgo, Cert); - {error, Reason} -> - {error, Reason} +verify_signature(_, _, _, [], _, _, _) -> + {error, ocsp_responder_cert_not_found}; +verify_signature(ResponseDataDer, SignatureAlgo, Signature, + [ResponderCert | RCs], ResponderID, IssuerCert, + IsTrustedResponderFun) -> + maybe + true ?= is_responder_cert(ResponderID, ResponderCert), + true ?= is_authorized_responder(ResponderCert, IssuerCert, + IsTrustedResponderFun), + ok ?= do_verify_signature(ResponseDataDer, Signature, SignatureAlgo, + ResponderCert) + else + _-> + verify_signature(ResponseDataDer, SignatureAlgo, Signature, + RCs, ResponderID, IssuerCert, + IsTrustedResponderFun) end. -find_responder_cert(_ResponderID, []) -> - {error, ocsp_responder_cert_not_found}; -find_responder_cert(ResponderID, [Cert | TCerts]) -> - case is_responder(ResponderID, Cert) of +verify_past_timestamp(Timestamp) -> + {Now, TimestampSec} = get_time_in_sec(Timestamp), + verify_timestamp(Now, TimestampSec, past_timestamp). + +verify_future_timestamp(Timestamp) -> + {Now, TimestampSec} = get_time_in_sec(Timestamp), + verify_timestamp(Now, TimestampSec, future_timestamp). + +verify_timestamp(Now, Timestamp, past_timestamp) when Timestamp =< Now -> + ok; +verify_timestamp(Now, Timestamp, future_timestamp) when Now =< Timestamp -> + ok; +verify_timestamp(_, _, _) -> + {error, ocsp_stale_response}. + +get_time_in_sec(Timestamp) -> + Now = calendar:datetime_to_gregorian_seconds(calendar:universal_time()), + TimestampSec = pubkey_cert:time_str_2_gregorian_sec( + {generalTime, Timestamp}), + {Now, TimestampSec}. + +verify_next_update(asn1_NOVALUE) -> + ok; +verify_next_update(NextUpdate) -> + verify_future_timestamp(NextUpdate). + +is_responder_cert({byName, Name}, #cert{otp = Cert}) -> + public_key:der_encode('Name', Name) == get_subject_name(Cert); +is_responder_cert({byKey, Key}, #cert{otp = Cert}) -> + Key == crypto:hash(sha, get_public_key(Cert)). + +is_authorized_responder(CombinedResponderCert = #cert{otp = ResponderCert}, + IssuerCert, IsTrustedResponderFun) -> + Case1 = + %% the CA who issued the certificate in question signed the + %% response + fun() -> + ResponderCert == IssuerCert + end, + Case2 = + %% a CA Designated Responder (Authorized Responder, defined in + %% Section 4.2.2.2) who holds a specially marked certificate + %% issued directly by the CA, indicating that the responder may + %% issue OCSP responses for that CA (id-kp-OCSPSigning) + fun() -> + public_key:pkix_is_issuer(ResponderCert, IssuerCert) andalso + designated_for_ocsp_signing(ResponderCert) + end, + Case3 = + %% a Trusted Responder whose public key is trusted by the requestor + fun() -> + IsTrustedResponderFun(CombinedResponderCert) + end, + + case lists:any(fun(E) -> E() end, [Case1, Case2, Case3]) of true -> - {ok, Cert}; + true; false -> - find_responder_cert(ResponderID, TCerts) + not_authorized_responder end. -do_verify_ocsp_signature(ResponseDataDer, Signature, AlgorithmID, Cert) -> +do_verify_signature(ResponseDataDer, Signature, AlgorithmID, + #cert{otp = ResponderCert}) -> {DigestType, _SignatureType} = public_key:pkix_sign_types(AlgorithmID), case public_key:verify( ResponseDataDer, DigestType, Signature, - get_public_key_rec(Cert)) of + get_public_key_rec(ResponderCert)) of true -> ok; false -> @@ -188,11 +252,6 @@ get_public_key_rec(#'OTPCertificate'{tbsCertificate = TbsCert}) -> PKInfo = TbsCert#'OTPTBSCertificate'.subjectPublicKeyInfo, PKInfo#'OTPSubjectPublicKeyInfo'.subjectPublicKey. -is_responder({byName, Name}, Cert) -> - public_key:der_encode('Name', Name) == get_subject_name(Cert); -is_responder({byKey, Key}, Cert) -> - Key == crypto:hash(sha, get_public_key(Cert)). - get_subject_name(#'OTPCertificate'{tbsCertificate = TbsCert}) -> public_key:pkix_encode('Name', TbsCert#'OTPTBSCertificate'.subject, otp). @@ -207,22 +266,26 @@ enc_pub_key({DsaInt, #'Dss-Parms'{}}) when is_integer(DsaInt) -> enc_pub_key({#'ECPoint'{point = Key}, _ECParam}) -> Key. +designated_for_ocsp_signing(OtpCert) -> + TBSCert = OtpCert#'OTPCertificate'.tbsCertificate, + TBSExtensions = TBSCert#'OTPTBSCertificate'.extensions, + Extensions = pubkey_cert:extensions_list(TBSExtensions), + case pubkey_cert:select_extension(?'id-ce-extKeyUsage', Extensions) of + undefined -> + false; + #'Extension'{extnValue = KeyUses} -> + lists:member(?'id-kp-OCSPSigning', KeyUses) + end. + %%%################################################################ %%%# %%%# Tracing %%%# -handle_trace(csp, - {call, {?MODULE, do_verify_ocsp_response, [BasicOcspResponse | _]}}, Stack) -> - #'BasicOCSPResponse'{ - tbsResponseData = - #'ResponseData'{responderID = ResponderID, - producedAt = ProducedAt}} = BasicOcspResponse, - {io_lib:format("ResponderId = ~W producedAt = ~p", [ResponderID, 5, ProducedAt]), Stack}; handle_trace(csp, {call, {?MODULE, match_single_response, [_IssuerName, _IssuerKey, _SerialNum, [#'SingleResponse'{thisUpdate = ThisUpdate, - nextUpdate = NextUpdate}]]}}, Stack) -> + nextUpdate = NextUpdate} | _]]}}, Stack) -> {io_lib:format("ThisUpdate = ~p NextUpdate = ~p", [ThisUpdate, NextUpdate]), Stack}; handle_trace(csp, {call, {?MODULE, is_responder, [Id, Cert]}}, Stack) -> diff --git a/lib/public_key/src/public_key.erl b/lib/public_key/src/public_key.erl index ee27a7b8a487..93d217cb98f3 100644 --- a/lib/public_key/src/public_key.erl +++ b/lib/public_key/src/public_key.erl @@ -21,7 +21,7 @@ %% -module(public_key). - +-feature(maybe_expr,enable). -include("public_key.hrl"). -export([pem_decode/1, pem_encode/1, @@ -62,7 +62,6 @@ pkix_test_data/1, pkix_test_root_cert/2, pkix_ocsp_validate/5, - ocsp_responder_id/1, ocsp_extensions/1, cacerts_get/0, cacerts_load/0, @@ -174,8 +173,11 @@ -type oid() :: tuple(). -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 | duplicate_cert_in_path | - {'policy_requirement_not_met', term()} | {'invalid_policy_mapping', term()} | {revoked, crl_reason()} | invalid_validity_dates | atom(). +-type bad_cert_reason() :: cert_expired | invalid_issuer | invalid_signature | name_not_permitted | + missing_basic_constraint | invalid_key_usage | duplicate_cert_in_path | + {'policy_requirement_not_met', term()} | {'invalid_policy_mapping', term()} | + {revoked, crl_reason()} | invalid_validity_dates | + {revocation_status_undetermined, term()} | atom(). -type combined_cert() :: #cert{}. -type cert() :: der_cert() | otp_cert(). @@ -1387,52 +1389,47 @@ pkix_test_data(#{} = Chain) -> pkix_test_root_cert(Name, Opts) -> pubkey_cert:root_cert(Name, Opts). - + %%-------------------------------------------------------------------- --spec pkix_ocsp_validate(Cert, IssuerCert, OcspRespDer, - ResponderCerts, NonceExt) -> valid | {bad_cert, Reason} - when Cert:: cert(), - IssuerCert:: cert(), +-spec pkix_ocsp_validate(Cert, IssuerCert, OcspRespDer, NonceExt, Options) -> + ok | {error, {bad_cert, Reason}} + when Cert::cert(), + IssuerCert::cert(), OcspRespDer::der_encoded(), - ResponderCerts::[der_cert()], NonceExt::undefined | binary(), - Reason::term(). - -%% Description: Validate OCSP staple response + Options::[{is_trusted_responder_fun, + fun((combined_cert()) -> boolean)}], + Reason::bad_cert_reason(). +%% Description: Validate OCSP response %%-------------------------------------------------------------------- -pkix_ocsp_validate(DerCert, IssuerCert, OcspRespDer, ResponderCerts, NonceExt) +pkix_ocsp_validate(DerCert, IssuerCert, OcspRespDer, NonceExt, Options) when is_binary(DerCert) -> - pkix_ocsp_validate(pkix_decode_cert(DerCert, otp), IssuerCert, OcspRespDer, - ResponderCerts, NonceExt); -pkix_ocsp_validate(Cert, DerIssuerCert, OcspRespDer, ResponderCerts, NonceExt) + pkix_ocsp_validate( + pkix_decode_cert(DerCert, otp), IssuerCert, OcspRespDer, NonceExt, Options); +pkix_ocsp_validate(Cert, DerIssuerCert, OcspRespDer, NonceExt, Options) when is_binary(DerIssuerCert) -> - pkix_ocsp_validate(Cert, pkix_decode_cert(DerIssuerCert, otp), OcspRespDer, - ResponderCerts, NonceExt); -pkix_ocsp_validate(Cert, IssuerCert, OcspRespDer, ResponderCerts, NonceExt) -> - OcspResponse = pubkey_ocsp:decode_ocsp_response(OcspRespDer), - OcspCertResponses = - case OcspResponse of - {ok, BasicOcspResponse = #'BasicOCSPResponse'{certs = Certs}} -> - OcspResponseCerts = [otp_cert(C) || C <- Certs], - UserResponderCerts = - [otp_cert(pkix_decode_cert(C, plain)) || C <- ResponderCerts], - pubkey_ocsp:verify_ocsp_response( - BasicOcspResponse, OcspResponseCerts ++ UserResponderCerts, - NonceExt); - {error, _} = Error -> - Error - end, - case OcspCertResponses of - {ok, Responses} -> - case pubkey_ocsp:find_single_response( - otp_cert(Cert), otp_cert(IssuerCert), Responses) of - {ok, #'SingleResponse'{certStatus = CertStatus}} -> - pubkey_ocsp:ocsp_status(CertStatus); - {error, no_matched_response = Reason} -> - {bad_cert, {revocation_status_undetermined, Reason}} - end; + pkix_ocsp_validate( + Cert, pkix_decode_cert(DerIssuerCert, otp), OcspRespDer, NonceExt, Options); +pkix_ocsp_validate(Cert, IssuerCert, OcspRespDer, NonceExt, Options) + when is_record(Cert, 'OTPCertificate'), + is_record(IssuerCert, 'OTPCertificate') -> + IsTrustedResponderFun = + proplists:get_value(is_trusted_responder_fun, Options, + fun(_) -> false end), + maybe + {ok, BasicOcspResponse = #'BasicOCSPResponse'{certs = Certs}} ?= + pubkey_ocsp:decode_response(OcspRespDer), + OcspResponseCerts = [combined_cert(C) || C <- Certs], + {ok, Responses} ?= + pubkey_ocsp:verify_response( + BasicOcspResponse, OcspResponseCerts, NonceExt, IssuerCert, + IsTrustedResponderFun), + {ok, #'SingleResponse'{certStatus = CertStatus}} ?= + pubkey_ocsp:find_single_response(Cert, IssuerCert, Responses), + pubkey_ocsp:status(CertStatus) + else {error, Reason} -> - {bad_cert, {revocation_status_undetermined, Reason}} + {error, {bad_cert, {revocation_status_undetermined, Reason}}} end. %%-------------------------------------------------------------------- @@ -1444,14 +1441,6 @@ ocsp_extensions(Nonce) -> pubkey_ocsp:get_acceptable_response_types_extn()], erlang:is_record(Extn, 'Extension')]. -%%-------------------------------------------------------------------- --spec ocsp_responder_id(binary()) -> binary(). -%% -%% Description: Get the OCSP responder ID der -%%-------------------------------------------------------------------- -ocsp_responder_id(CertDer) -> - pubkey_ocsp:get_ocsp_responder_id(pkix_decode_cert(CertDer, plain)). - %%-------------------------------------------------------------------- -spec cacerts_get() -> [combined_cert()]. %% @@ -1700,9 +1689,12 @@ otp_cert(Der) when is_binary(Der) -> otp_cert(#'OTPCertificate'{} = Cert) -> Cert; otp_cert(#cert{otp = OtpCert}) -> - OtpCert; -otp_cert(#'Certificate'{} = Cert) -> - pkix_decode_cert(der_encode('Certificate', Cert), otp). + OtpCert. + +combined_cert(#'Certificate'{} = Cert) -> + Der = der_encode('Certificate', Cert), + Otp = pkix_decode_cert(Der, otp), + #cert{der = Der, otp = Otp}. der_cert(#'OTPCertificate'{} = Cert) -> pkix_encode('OTPCertificate', Cert, otp); @@ -2119,15 +2111,6 @@ subject_public_key_info(Alg, PubKey) -> %%%# %%%# Tracing %%%# -handle_trace(csp, - {call, {?MODULE, ocsp_responder_id, [Cert]}}, Stack) -> - {io_lib:format("pkix_decode_cert(Cert, plain) = ~W", [Cert, 5]), - %% {io_lib:format("pkix_decode_cert(Cert, plain) = ~s", [ssl_test_lib:format_cert(Cert)]), - Stack}; -handle_trace(csp, - {return_from, {?MODULE, ocsp_responder_id, 1}, Return}, - Stack) -> - {io_lib:format("OCSP Responder ID = ~P", [Return, 10]), Stack}; handle_trace(crt, {call, {?MODULE, pkix_decode_cert, [Cert, _Type]}}, Stack) -> {io_lib:format("Cert = ~W", [Cert, 5]), Stack}; diff --git a/lib/public_key/test/Makefile b/lib/public_key/test/Makefile index 79dcacb6ce09..c0bbed3af7bc 100644 --- a/lib/public_key/test/Makefile +++ b/lib/public_key/test/Makefile @@ -34,7 +34,8 @@ MODULES= \ pbe_SUITE \ pkits_SUITE \ pubkey_cert_SUITE \ - pubkey_policy_tree_SUITE + pubkey_policy_tree_SUITE \ + pubkey_ocsp_SUITE ERL_FILES= $(MODULES:%=%.erl) diff --git a/lib/public_key/test/pubkey_ocsp_SUITE.erl b/lib/public_key/test/pubkey_ocsp_SUITE.erl index 006741e81a61..b2f42d7c09e0 100644 --- a/lib/public_key/test/pubkey_ocsp_SUITE.erl +++ b/lib/public_key/test/pubkey_ocsp_SUITE.erl @@ -22,17 +22,92 @@ -include_lib("common_test/include/ct.hrl"). -include_lib("public_key/include/public_key.hrl"). - %% Note: This directive should only be used in test suites. --compile(export_all). +-compile([export_all, nowarn_export_all]). + +-define(NONCE, + <<4,8,93,33,1,52,187,3,12,142>>). +-define(OCSP_RESPONSE_DER, + <<48,130,7,36,10,1,0,160,130,7,29,48,130,7,25,6,9,43,6,1,5,5,7,48,1,1,4,130,7,10,48,130,7,6,48,130,1,10,161,129,134,48,129,131,49,14,48,12,6,3,85,4,3,12,5,111,116,112,67,65,49,19,48,17,6,3,85,4,11,12,10,69,114,108,97,110,103,32,79,84,80,49,20,48,18,6,3,85,4,10,12,11,69,114,105,99,115,115,111,110,32,65,66,49,11,48,9,6,3,85,4,6,19,2,83,69,49,18,48,16,6,3,85,4,7,12,9,83,116,111,99,107,104,111,108,109,49,37,48,35,6,9,42,134,72,134,247,13,1,9,1,22,22,112,101,116,101,114,64,101,114,105,120,46,101, + 114,105,99,115,115,111,110,46,115,101,24,15,50,48,50,51,48,55,50,48,49,50,50,57,52,57,90,48,81,48,79,48,58,48,9,6,5,43,14,3,2,26,5,0,4,20,227,147,252,182,155,101,129,45,194,162,22,93,127,46,112,193,196,28,241,232,4,20,34,25,129,87,115,255,155,246,200,97,92,7,51,110,152,61,97,155,164,171,2,1,9,128,0,24,15,50,48,50,51,48,55,50,48,49,50,50,57,52,57,90,161,27,48,25,48,23,6,9,43,6,1,5,5,7,48,1,2,4,10,4,8,93,33,1,52,187,3,12,142,48,13,6,9,42,134,72,134,247,13,1,1,11,5,0,3,130,1,1,0,182,228,165,33, + 173,232,46,125,152,237,37,120,186,223,188,231,181,61,72,89,210,75,38,182,146,218,223,53,38,104,100,89,19,79,48,159,109,70,25,34,143,253,199,92,162,248,245,240,61,82,39,44,243,148,109,21,112,74,206,246,5,146,12,175,235,170,225,206,115,148,109,1,216,194,98,149,105,106,232,83,95,229,196,237,246,6,177,167,177,52,242,63,56,93,74,92,28,246,138,137,99,28,239,68,130,184,182,140,50,206,10,166,243,118,11,153,79,178,220,166,161,45,83,90,58,152,78,229,27,54,147,125,106,199,192,182,242,242,98,69,94,148, + 163,130,154,168,134,24,7,211,176,133,1,156,206,22,197,139,59,66,110,121,187,101,221,16,11,114,106,56,178,21,3,189,89,233,228,8,127,150,247,151,97,145,204,117,80,120,174,191,12,150,148,180,86,16,86,82,170,184,185,10,182,252,210,66,238,144,233,244,94,144,143,200,0,172,179,194,109,137,186,95,180,111,242,81,132,254,70,174,168,9,181,145,154,180,7,78,17,56,24,195,236,80,46,1,241,0,52,172,84,154,43,117,130,153,160,130,4,224,48,130,4,220,48,130,4,216,48,130,3,192,160,3,2,1,2,2,1,1,48,13,6,9,42,134, + 72,134,247,13,1,1,11,5,0,48,129,134,49,17,48,15,6,3,85,4,3,12,8,101,114,108,97,110,103,67,65,49,19,48,17,6,3,85,4,11,12,10,69,114,108,97,110,103,32,79,84,80,49,20,48,18,6,3,85,4,10,12,11,69,114,105,99,115,115,111,110,32,65,66,49,18,48,16,6,3,85,4,7,12,9,83,116,111,99,107,104,111,108,109,49,11,48,9,6,3,85,4,6,19,2,83,69,49,37,48,35,6,9,42,134,72,134,247,13,1,9,1,22,22,112,101,116,101,114,64,101,114,105,120,46,101,114,105,99,115,115,111,110,46,115,101,48,30,23,13,50,51,48,55,50,48,49,50,50,57, + 52,52,90,23,13,51,51,48,53,50,56,49,50,50,57,52,52,90,48,129,131,49,14,48,12,6,3,85,4,3,12,5,111,116,112,67,65,49,19,48,17,6,3,85,4,11,12,10,69,114,108,97,110,103,32,79,84,80,49,20,48,18,6,3,85,4,10,12,11,69,114,105,99,115,115,111,110,32,65,66,49,11,48,9,6,3,85,4,6,19,2,83,69,49,18,48,16,6,3,85,4,7,12,9,83,116,111,99,107,104,111,108,109,49,37,48,35,6,9,42,134,72,134,247,13,1,9,1,22,22,112,101,116,101,114,64,101,114,105,120,46,101,114,105,99,115,115,111,110,46,115,101,48,130,1,34,48,13,6,9,42, + 134,72,134,247,13,1,1,1,5,0,3,130,1,15,0,48,130,1,10,2,130,1,1,0,224,126,14,188,23,118,17,120,117,2,151,131,96,96,81,128,52,8,219,111,48,52,116,100,176,30,58,84,47,206,254,180,60,112,107,216,0,213,16,164,57,110,181,88,62,78,208,125,127,255,36,56,29,37,165,108,64,115,95,46,212,88,172,92,20,177,247,84,13,124,142,41,248,131,77,91,114,228,157,125,20,155,64,70,60,206,180,54,12,80,153,230,208,10,189,163,140,22,146,156,99,21,213,182,98,144,208,94,71,69,249,100,109,104,226,169,55,210,194,244,111,92, + 16,87,6,93,42,174,62,243,175,60,139,134,67,116,107,208,120,214,103,12,182,22,229,195,60,133,235,228,230,17,0,101,185,117,3,52,252,75,173,144,14,30,36,132,251,47,0,161,159,183,230,201,93,76,82,202,66,213,34,44,88,148,92,240,21,152,135,102,160,212,173,100,225,227,143,229,74,120,120,147,179,228,80,127,246,118,213,141,122,209,29,48,47,188,130,179,111,83,234,203,22,0,167,15,53,193,172,80,117,62,98,63,233,161,102,96,21,10,72,179,86,205,96,124,62,133,9,28,197,39,190,23,72,49,2,3,1,0,1,163,130,1,80, + 48,130,1,76,48,15,6,3,85,29,19,1,1,255,4,5,48,3,1,1,255,48,11,6,3,85,29,15,4,4,3,2,1,6,48,29,6,3,85,29,14,4,22,4,20,34,25,129,87,115,255,155,246,200,97,92,7,51,110,152,61,97,155,164,171,48,129,198,6,3,85,29,35,4,129,190,48,129,187,128,20,196,35,212,128,180,55,39,81,140,96,141,212,14,41,206,56,214,196,133,175,161,129,140,164,129,137,48,129,134,49,17,48,15,6,3,85,4,3,12,8,101,114,108,97,110,103,67,65,49,19,48,17,6,3,85,4,11,12,10,69,114,108,97,110,103,32,79,84,80,49,20,48,18,6,3,85,4,10,12,11, + 69,114,105,99,115,115,111,110,32,65,66,49,18,48,16,6,3,85,4,7,12,9,83,116,111,99,107,104,111,108,109,49,11,48,9,6,3,85,4,6,19,2,83,69,49,37,48,35,6,9,42,134,72,134,247,13,1,9,1,22,22,112,101,116,101,114,64,101,114,105,120,46,101,114,105,99,115,115,111,110,46,115,101,130,20,43,178,6,127,40,48,98,119,68,20,137,15,178,249,179,119,3,205,202,41,48,33,6,3,85,29,17,4,26,48,24,129,22,112,101,116,101,114,64,101,114,105,120,46,101,114,105,99,115,115,111,110,46,115,101,48,33,6,3,85,29,18,4,26,48,24,129, + 22,112,101,116,101,114,64,101,114,105,120,46,101,114,105,99,115,115,111,110,46,115,101,48,13,6,9,42,134,72,134,247,13,1,1,11,5,0,3,130,1,1,0,2,39,149,225,217,60,119,245,177,96,137,169,49,169,0,163,164,218,40,228,230,193,142,138,206,47,0,176,80,99,16,226,79,124,237,230,91,57,148,49,250,208,42,193,106,53,86,163,205,254,245,90,45,240,172,107,162,160,59,7,246,245,41,106,44,239,47,78,197,79,123,55,217,87,181,221,73,88,47,122,30,195,225,6,28,237,49,250,105,85,214,69,86,243,73,81,101,192,31,250,31, + 55,111,63,11,1,147,63,144,241,132,32,161,92,168,152,19,29,233,88,234,4,134,144,26,70,162,219,31,125,205,202,94,45,111,3,17,66,62,208,17,188,179,94,222,238,248,79,102,80,138,217,80,233,100,152,240,11,81,36,130,175,152,182,221,2,26,24,33,180,242,63,33,223,18,131,11,52,51,1,193,24,222,91,47,100,131,173,32,69,159,13,94,246,193,182,127,242,164,131,112,92,179,65,79,235,174,161,194,201,255,119,2,251,215,203,135,16,154,55,69,82,33,69,60,223,118,35,56,22,228,106,80,57,180,62,124,121,244,121,197,123, + 242,190,55,26,32,214,176,53,28,117,171,162,76,160>>). +-define(ISSUER_CERT, + {'OTPCertificate',{'OTPTBSCertificate',v3,1, + {'SignatureAlgorithm',{1,2,840,113549,1,1,11},'NULL'}, + {rdnSequence,[[{'AttributeTypeAndValue',{2,5,4,3},{utf8String,<<"erlangCA">>}}],[{'AttributeTypeAndValue',{2,5,4,11},{utf8String,<<"Erlang OTP">>}}],[{'AttributeTypeAndValue',{2,5,4,10},{utf8String,<<"Ericsson AB">>}}],[{'AttributeTypeAndValue',{2,5,4,7},{utf8String,<<"Stockholm">>}}],[{'AttributeTypeAndValue',{2,5,4,6},"SE"}],[{'AttributeTypeAndValue',{1,2,840,113549,1,9,1},"peter@erix.ericsson.se"}]]}, + {'Validity',{utcTime,"230720122944Z"},{utcTime,"330528122944Z"}}, + {rdnSequence,[[{'AttributeTypeAndValue',{2,5,4,3},{utf8String,<<"otpCA">>}}],[{'AttributeTypeAndValue',{2,5,4,11},{utf8String,<<"Erlang OTP">>}}],[{'AttributeTypeAndValue',{2,5,4,10},{utf8String,<<"Ericsson AB">>}}],[{'AttributeTypeAndValue',{2,5,4,6},"SE"}],[{'AttributeTypeAndValue',{2,5,4,7},{utf8String,<<"Stockholm">>}}],[{'AttributeTypeAndValue',{1,2,840,113549,1,9,1},"peter@erix.ericsson.se"}]]}, + {'OTPSubjectPublicKeyInfo',{'PublicKeyAlgorithm',{1,2,840,113549,1,1,1},'NULL'}, + {'RSAPublicKey',28339541610808720697355110173776661351591299627563886520724840524156173758352096851973677497931775737934761046080070714946146799362954032218057107079242015447767834113919294749723734648362271942219510034694564267611067362221363996274084106982740657802072527220370548608128815474010110407985824336936761317435951968068792959040741225688753787656107492053262271328711261658605960823613199135109317800726834363235926476527282638847781232871073244485999722937494811217769991698287040924806827188498324716317026838449695477777978536565396172198805249805405552866638039988130119465502001541293012996469049417900821835106353, + 65537}}, + asn1_NOVALUE,asn1_NOVALUE, + [{'Extension',{2,5,29,19},true,{'BasicConstraints',true,asn1_NOVALUE}}, + {'Extension',{2,5,29,15},false,[keyCertSign,cRLSign]}, + {'Extension',{2,5,29,14},false,<<34,25,129,87,115,255,155,246,200,97,92,7,51,110,152,61,97,155,164,171>>}, + {'Extension',{2,5,29,35}, + false, + {'AuthorityKeyIdentifier',<<196,35,212,128,180,55,39,81,140,96,141,212,14,41,206,56,214,196,133,175>>, + [{directoryName,{rdnSequence,[[{'AttributeTypeAndValue',{2,5,4,3},{utf8String,<<"erlangCA">>}}], + [{'AttributeTypeAndValue',{2,5,4,11},{utf8String,<<"Erlang OTP">>}}], + [{'AttributeTypeAndValue',{2,5,4,10},{utf8String,<<"Ericsson AB">>}}], + [{'AttributeTypeAndValue',{2,5,4,7},{utf8String,<<"Stockholm">>}}], + [{'AttributeTypeAndValue',{2,5,4,6},"SE"}], + [{'AttributeTypeAndValue',{1,2,840,113549,1,9,1},"peter@erix.ericsson.se"}]]}}], + 249456701733760087187851894331345805369320262185}}, + {'Extension',{2,5,29,17},false,[{rfc822Name,"peter@erix.ericsson.se"}]}, + {'Extension',{2,5,29,18},false,[{rfc822Name,"peter@erix.ericsson.se"}]}]}, + {'SignatureAlgorithm',{1,2,840,113549,1,1,11},'NULL'}, + <<2,39,149,225,217,60,119,245,177,96,137,169,49,169,0,163,164,218,40,228,230,193,142,138,206,47,0,176,80,99,16,226,79,124,237,230,91,57,148,49,250,208,42,193,106,53,86,163,205,254,245,90,45,240,172,107,162,160,59,7,246,245,41,106,44,239,47,78,197,79,123,55,217,87,181,221,73,88,47,122,30,195,225,6,28,237,49,250,105,85,214,69,86,243,73,81,101,192,31,250,31,55,111,63,11,1,147,63,144,241,132,32,161,92,168,152,19,29,233,88,234,4,134,144,26,70,162,219,31,125,205,202,94,45,111,3,17, + 66,62,208,17,188,179,94,222,238,248,79,102,80,138,217,80,233,100,152,240,11,81,36,130,175,152,182,221,2,26,24,33,180,242,63,33,223,18,131,11,52,51,1,193,24,222,91,47,100,131,173,32,69,159,13,94,246,193,182,127,242,164,131,112,92,179,65,79,235,174,161,194,201,255,119,2,251,215,203,135,16,154,55,69,82,33,69,60,223,118,35,56,22,228,106,80,57,180,62,124,121,244,121,197,123,242,190,55,26,32,214,176,53,28,117,171,162,76,160>>} + ). +-define(RESPONDER_CERT, #cert{otp = ?ISSUER_CERT}). +-define(A_SERVER_CERT, + {'OTPCertificate',{'OTPTBSCertificate',v3,9, + {'SignatureAlgorithm',{1,2,840,113549,1,1,11},'NULL'}, + {rdnSequence,[[{'AttributeTypeAndValue',{2,5,4,3},{utf8String,<<"otpCA">>}}],[{'AttributeTypeAndValue',{2,5,4,11},{utf8String,<<"Erlang OTP">>}}],[{'AttributeTypeAndValue',{2,5,4,10},{utf8String,<<"Ericsson AB">>}}],[{'AttributeTypeAndValue',{2,5,4,6},"SE"}],[{'AttributeTypeAndValue',{2,5,4,7},{utf8String,<<"Stockholm">>}}],[{'AttributeTypeAndValue',{1,2,840,113549,1,9,1},"peter@erix.ericsson.se"}]]}, + {'Validity',{utcTime,"230720133137Z"},{utcTime,"330528133137Z"}}, + {rdnSequence,[[{'AttributeTypeAndValue',{2,5,4,3},{utf8String,<<"a.server">>}}],[{'AttributeTypeAndValue',{2,5,4,11},{utf8String,<<"Erlang OTP">>}}],[{'AttributeTypeAndValue',{2,5,4,10},{utf8String,<<"Ericsson AB">>}}],[{'AttributeTypeAndValue',{2,5,4,6},"SE"}],[{'AttributeTypeAndValue',{2,5,4,7},{utf8String,<<"Stockholm">>}}],[{'AttributeTypeAndValue',{1,2,840,113549,1,9,1},"peter@erix.ericsson.se"}]]}, + {'OTPSubjectPublicKeyInfo',{'PublicKeyAlgorithm',{1,2,840,113549,1,1,1},'NULL'}, + {'RSAPublicKey',21289228001579879261333836287004823332222603265803194664536540127079242843046558012638236832904402369325784443025964406623777246658832921141960060475804229950419927075126320682148878633948860170628231809668072735203197673472127901696952853229103382707195692260834407944629128675563945194876045436588557031550105450845916227210816469918126215406473272174435113136059751668904728646605321836951857481644376964329827326510385947455341932553729402879301386590388317914766820519616318357183422565964994898098302388155119056040428369731559112404176013041801429296771966314089067058782535413289830323744573459011210321571511, + 65537}}, + asn1_NOVALUE,asn1_NOVALUE, + [{'Extension',{2,5,29,19},false,{'BasicConstraints',false,asn1_NOVALUE}}, + {'Extension',{2,5,29,15},false,[digitalSignature,nonRepudiation,keyEncipherment]}, + {'Extension',{2,5,29,14},false,<<135,115,253,182,154,247,175,77,237,3,215,88,195,15,182,214,248,144,201,202>>}, + {'Extension',{2,5,29,35}, + false, + {'AuthorityKeyIdentifier',<<63,22,3,246,66,83,233,142,103,82,105,230,175,132,130,192,87,79,122,232>>, + [{directoryName,{rdnSequence,[[{'AttributeTypeAndValue',{2,5,4,3},{utf8String,<<"erlangCA">>}}], + [{'AttributeTypeAndValue',{2,5,4,11},{utf8String,<<"Erlang OTP">>}}], + [{'AttributeTypeAndValue',{2,5,4,10},{utf8String,<<"Ericsson AB">>}}], + [{'AttributeTypeAndValue',{2,5,4,7},{utf8String,<<"Stockholm">>}}], + [{'AttributeTypeAndValue',{2,5,4,6},"SE"}], + [{'AttributeTypeAndValue',{1,2,840,113549,1,9,1},"peter@erix.ericsson.se"}]]}}], + 1}}, + {'Extension',{2,5,29,17},false,[{dNSName,"host.example.com"}]}, + {'Extension',{2,5,29,18},false,[{rfc822Name,"peter@erix.ericsson.se"}]}]}, + {'SignatureAlgorithm',{1,2,840,113549,1,1,11},'NULL'}, + <<194,57,242,156,210,120,172,248,208,88,233,168,205,61,179,61,2,85,56,96,136,83,210,119,125,103,192,129,116,221,161,132,108,92,219,163,233,228,179,34,47,164,22,72,45,203,239,245,155,67,137,138,191,142,152,135,233,57,229,36,0,69,149,197,54,204,25,147,4,223,251,99,183,6,158,247,67,220,83,177,77,117,131,196,144,151,105,108,83,227,69,84,143,238,81,189,141,167,155,224,8,199,237,102,62,92,133,120,118,133,41,142,45,9,195,211,95,49,101,226,51,225,78,198,255,142,182,113,179,20,36,214, + 62,56,147,108,248,95,132,193,0,194,102,78,45,7,102,167,183,146,79,108,190,65,108,0,92,40,164,29,81,63,204,59,252,170,33,209,139,181,226,35,136,229,147,190,3,119,238,178,83,203,7,92,103,21,22,171,75,199,87,255,171,219,146,122,207,235,188,254,247,58,64,1,31,190,233,135,232,47,71,117,82,107,254,74,23,178,186,85,110,204,185,51,113,160,41,145,190,52,63,103,210,54,235,206,82,160,188,238,209,99,90,100,138,147,84,20,30,47,253,73,245,168,13,222>>} + ). %%-------------------------------------------------------------------- %% Common Test interface functions ----------------------------------- %%-------------------------------------------------------------------- -all() -> +all() -> [ocsp_test]. -groups() -> +groups() -> []. %%-------------------------------------------------------------------- @@ -63,314 +138,76 @@ end_per_testcase(_TestCase, _Config) -> ocsp_test() -> [{doc, "Test functions in pubkey_ocsp"}]. ocsp_test(Config) when is_list(Config) -> - %% Feeding data - SingleResponseGood = - [#'SingleResponse'{ - certID = {'CertID', - {'AlgorithmIdentifier',{1,3,14,3,2,26},<<5,0>>}, - <<227,147,252,182,155,101,129,45,194,162, - 22,93,127,46,112,193,196,28,241,232>>, - <<99,34,37,88,164,188,98,22,125,252,71,72, - 246,115,141,222,108,19,122,168>>,7}, - certStatus = {good,'NULL'}, - thisUpdate = "20200428083205Z", - nextUpdate = asn1_NOVALUE, - singleExtensions = asn1_NOVALUE}], - - Nonce = <<226,210,104,247,153,233,71,246>>, - - NonceExtension = - #'Extension'{ - extnID = ?'id-pkix-ocsp-nonce', - extnValue = Nonce - }, - - OCSPResponseDer = - <<48,130,7,6,10,1,0,160,130,6,255,48,130,6,251,6,9,43,6,1,5,5,7,48,1,1,4,130,6, - 236,48,130,6,232,48,130,1,11,161,129,137,48,129,134,49,17,48,15,6,3,85,4,3, - 12,8,98,46,115,101,114,118,101,114,49,19,48,17,6,3,85,4,11,12,10,69,114,108, - 97,110,103,32,79,84,80,49,20,48,18,6,3,85,4,10,12,11,69,114,105,99,115,115, - 111,110,32,65,66,49,11,48,9,6,3,85,4,6,19,2,83,69,49,18,48,16,6,3,85,4,7,12, - 9,83,116,111,99,107,104,111,108,109,49,37,48,35,6,9,42,134,72,134,247,13,1,9, - 1,22,22,112,101,116,101,114,64,101,114,105,120,46,101,114,105,99,115,115,111, - 110,46,115,101,24,15,50,48,50,48,48,52,50,56,48,56,51,50,48,53,90,48,81,48, - 79,48,58,48,9,6,5,43,14,3,2,26,5,0,4,20,227,147,252,182,155,101,129,45,194, - 162,22,93,127,46,112,193,196,28,241,232,4,20,99,34,37,88,164,188,98,22,125, - 252,71,72,246,115,141,222,108,19,122,168,2,1,7,128,0,24,15,50,48,50,48,48,52, - 50,56,48,56,51,50,48,53,90,161,25,48,23,48,21,6,9,43,6,1,5,5,7,48,1,2,4,8, - 226,210,104,247,153,233,71,246,48,13,6,9,42,134,72,134,247,13,1,1,11,5,0,3, - 130,1,1,0,85,82,43,226,38,172,139,105,77,248,24,250,244,154,2,174,232,141,52, - 93,102,37,177,31,59,105,104,242,117,238,102,93,61,56,24,47,69,169,184,234, - 109,204,5,64,109,101,23,197,234,6,250,223,95,175,131,138,227,66,123,199,182, - 57,102,47,221,72,112,208,1,4,128,209,235,108,64,209,31,128,37,130,176,132, - 203,119,24,188,187,254,8,167,54,80,28,208,26,118,236,149,184,182,25,236,252, - 158,253,167,143,114,14,184,198,144,51,195,44,16,38,255,112,124,81,201,255, - 132,143,98,119,135,23,232,10,184,54,150,227,131,212,81,101,158,152,82,252, - 156,28,30,163,203,145,11,179,105,230,187,132,119,186,189,67,198,165,48,106, - 114,75,151,128,108,28,44,121,195,162,222,25,45,99,46,84,116,125,51,72,191, - 250,186,71,78,21,222,219,232,143,233,226,56,163,23,51,170,69,152,223,0,63,8, - 236,219,175,18,165,88,166,125,71,31,53,40,12,133,64,250,30,190,113,10,187,38, - 171,17,210,170,126,198,232,195,224,228,1,246,75,140,139,121,229,17,153,115, - 199,68,227,171,176,163,117,171,160,130,4,193,48,130,4,189,48,130,4,185,48, - 130,3,161,160,3,2,1,2,2,1,9,48,13,6,9,42,134,72,134,247,13,1,1,5,5,0,48,129, - 131,49,14,48,12,6,3,85,4,3,12,5,111,116,112,67,65,49,19,48,17,6,3,85,4,11,12, - 10,69,114,108,97,110,103,32,79,84,80,49,20,48,18,6,3,85,4,10,12,11,69,114, - 105,99,115,115,111,110,32,65,66,49,11,48,9,6,3,85,4,6,19,2,83,69,49,18,48,16, - 6,3,85,4,7,12,9,83,116,111,99,107,104,111,108,109,49,37,48,35,6,9,42,134,72, - 134,247,13,1,9,1,22,22,112,101,116,101,114,64,101,114,105,120,46,101,114,105, - 99,115,115,111,110,46,115,101,48,30,23,13,50,48,48,52,50,56,48,56,51,50,48, - 53,90,23,13,51,48,48,51,48,55,48,56,51,50,48,53,90,48,129,134,49,17,48,15,6, - 3,85,4,3,12,8,98,46,115,101,114,118,101,114,49,19,48,17,6,3,85,4,11,12,10,69, - 114,108,97,110,103,32,79,84,80,49,20,48,18,6,3,85,4,10,12,11,69,114,105,99, - 115,115,111,110,32,65,66,49,11,48,9,6,3,85,4,6,19,2,83,69,49,18,48,16,6,3,85, - 4,7,12,9,83,116,111,99,107,104,111,108,109,49,37,48,35,6,9,42,134,72,134,247, - 13,1,9,1,22,22,112,101,116,101,114,64,101,114,105,120,46,101,114,105,99,115, - 115,111,110,46,115,101,48,130,1,34,48,13,6,9,42,134,72,134,247,13,1,1,1,5,0, - 3,130,1,15,0,48,130,1,10,2,130,1,1,0,188,248,42,161,172,252,200,52,180,217, - 145,59,193,72,33,176,213,106,37,81,119,251,205,254,70,196,171,127,79,157,147, - 235,14,61,25,162,207,134,25,239,35,62,57,10,214,115,231,71,203,226,198,73, - 223,222,199,165,82,67,33,78,176,116,241,192,97,169,143,164,219,152,40,115, - 229,242,128,97,98,183,217,199,35,127,146,94,20,115,0,250,200,39,9,255,230, - 216,80,140,6,133,251,39,96,240,176,184,34,1,134,247,126,237,255,130,170,98, - 242,140,104,105,95,48,75,115,135,229,89,191,180,179,123,198,232,228,220,249, - 113,86,186,212,176,194,66,14,164,236,219,138,254,80,57,118,232,163,192,94,78, - 224,100,124,206,199,81,105,54,222,26,245,170,147,184,192,237,77,143,154,180, - 79,42,107,75,77,81,215,19,75,8,160,106,199,196,66,53,16,233,184,175,85,167, - 148,12,232,248,113,61,89,14,156,199,128,83,40,214,228,83,9,36,72,188,25,29, - 47,172,78,114,191,120,240,227,234,255,194,61,132,57,1,141,131,227,64,152,209, - 205,63,24,172,223,194,254,97,133,255,192,133,148,237,178,115,2,3,1,0,1,163, - 130,1,49,48,130,1,45,48,9,6,3,85,29,19,4,2,48,0,48,11,6,3,85,29,15,4,4,3,2,5, - 224,48,29,6,3,85,29,14,4,22,4,20,63,72,140,0,84,13,114,48,50,31,9,241,231, - 177,20,184,8,114,244,29,48,129,179,6,3,85,29,35,4,129,171,48,129,168,128,20, - 99,34,37,88,164,188,98,22,125,252,71,72,246,115,141,222,108,19,122,168,161, - 129,140,164,129,137,48,129,134,49,17,48,15,6,3,85,4,3,12,8,101,114,108,97, - 110,103,67,65,49,19,48,17,6,3,85,4,11,12,10,69,114,108,97,110,103,32,79,84, - 80,49,20,48,18,6,3,85,4,10,12,11,69,114,105,99,115,115,111,110,32,65,66,49, - 18,48,16,6,3,85,4,7,12,9,83,116,111,99,107,104,111,108,109,49,11,48,9,6,3,85, - 4,6,19,2,83,69,49,37,48,35,6,9,42,134,72,134,247,13,1,9,1,22,22,112,101,116, - 101,114,64,101,114,105,120,46,101,114,105,99,115,115,111,110,46,115,101,130, - 1,1,48,27,6,3,85,29,17,4,20,48,18,130,16,104,111,115,116,46,101,120,97,109, - 112,108,101,46,99,111,109,48,33,6,3,85,29,18,4,26,48,24,129,22,112,101,116, - 101,114,64,101,114,105,120,46,101,114,105,99,115,115,111,110,46,115,101,48, - 13,6,9,42,134,72,134,247,13,1,1,5,5,0,3,130,1,1,0,86,112,29,225,102,143,193, - 55,126,115,187,208,118,153,111,177,160,121,55,33,184,60,27,111,40,7,93,241,9, - 226,40,125,181,36,173,116,190,43,187,52,254,50,229,222,56,215,132,67,217,174, - 121,24,94,240,163,56,12,36,212,2,40,94,102,126,206,52,40,32,218,59,86,166, - 238,137,144,90,57,211,141,81,32,102,215,180,59,133,125,208,199,166,81,35,49, - 24,88,100,127,90,145,237,150,249,227,123,120,98,230,12,106,72,201,127,54,94, - 164,204,23,158,3,230,232,181,95,251,98,6,28,115,46,153,241,233,254,152,176, - 114,12,148,24,234,185,204,177,189,70,14,73,181,232,245,63,226,14,138,249,101, - 56,222,188,78,127,191,174,232,182,207,67,162,111,248,192,202,65,96,237,206, - 52,220,63,50,108,82,185,169,29,148,30,75,74,16,156,229,166,96,102,214,145,77, - 225,218,180,54,109,61,62,119,144,231,72,105,61,201,245,219,192,63,160,242, - 247,112,64,199,65,248,252,59,145,150,212,151,166,223,237,121,135,13,122,111, - 22,117,115,166,64,143,10,40,13,5,240,22,38,235,32,107,194,41>>, - - MalOCSPResponseDer = - <<48,130,7,6,10,1,0,160,130,6,255,48,130,6,251,6,9,43,6,1,5,5,7,48,1,1,4,130,6, - 236,48,130,6,232,48,130,1,11,161,129,137,48,129,134,49,17,48,15,6,3,85,4,3, - 12,8,98,46,115,101,114,118,101,114,49,19,48,17,6,3,85,4,11,12,10,69,114,108, - 97,110,103,32,79,84,80,49,20,48,18,6,3,85,4,10,12,11,69,114,105,99,115,115, - 111,110,32,65,66,49,11,48,9,6,3,85,4,6,19,2,83,69,49,18,48,16,6,3,85,4,7,12, - 9,83,116,111,99,107,104,111,108,109,49,37,48,35,6,9,42,134,72,134,247,13,1,9, - 1,22,22,112,101,116,101,114,64,101,114,105,120,46,101,114,105,99,115,115,111, - 110,46,115,101,24,15,50,48,50,48,48,52,50,56,48,56,51,50,48,53,90,48,81,48, - 79,48,58,48,9,6,5,43,14,3,2,26,5,0,4,20,227,147,252,182,155,101,129,45,194, - 162,22,93,127,46,112,193,196,28,241,232,4,20,99,34,37,88,164,188,98,22,125, - 252,71,72,246,115,141,222,108,19,122,168,2,1,7,128,0,24,15,50,48,50,48,48,52, - 50,56,48,56,51,50,48,53,90,161,25,48,23,48,21,6,9,43,6,1,5,5,7,48,1,2,4,8, - 226,210,104,247,153,233,71,246,48,13,6,9,42,134,72,134,247,13,1,1,11,5,0,3, - 130,1,1,0,85,82,43,226,38,172,139,105,77,248,24,250,244,154,2,174,232,141,52, - 93,102,37,177,31,59,105,104,242,117,238,102,93,61,56,24,47,69,169,184,234, - 109,204,5,64,109,101,23,197,234,6,250,223,95,175,131,138,227,66,123,199,182, - 57,102,47,221,72,112,208,1,4,128,209,235,108,64,209,31,128,37,130,176,132, - 203,119,24,188,187,254,8,167,54,80,28,208,26,118,236,149,184,182,25,236,252, - 158,253,167,143,114,14,184,198,168,56,195,44,16,38,255,112,124,81,201,255, - 132,143,98,119,135,23,232,10,184,54,150,227,131,212,81,101,158,152,82,252, - 156,28,30,163,203,145,11,179,105,230,187,132,119,186,189,67,198,165,48,106, - 114,75,151,128,108,28,44,121,195,162,222,25,45,99,46,84,116,125,51,72,191, - 250,186,71,78,21,222,219,232,143,233,226,56,163,23,51,170,69,152,223,0,63,8, - 236,219,175,18,165,88,166,125,71,31,53,40,12,133,64,250,30,190,113,10,187,38, - 171,17,210,170,126,198,232,195,224,228,1,246,75,140,139,121,229,17,153,115, - 199,68,227,171,176,163,117,171,160,130,4,193,48,130,4,189,48,130,4,185,48, - 130,3,161,160,3,2,1,2,2,1,9,48,13,6,9,42,134,72,134,247,13,1,1,5,5,0,48,129, - 131,49,14,48,12,6,3,85,4,3,12,5,111,116,112,67,65,49,19,48,17,6,3,85,4,11,12, - 10,69,114,108,97,110,103,32,79,84,80,49,20,48,18,6,3,85,4,10,12,11,69,114, - 105,99,115,115,111,110,32,65,66,49,11,48,9,6,3,85,4,6,19,2,83,69,49,18,48,16, - 6,3,85,4,7,12,9,83,116,111,99,107,104,111,108,109,49,37,48,35,6,9,42,134,72, - 134,247,13,1,9,1,22,22,112,101,116,101,114,64,101,114,105,120,46,101,114,105, - 99,115,115,111,110,46,115,101,48,30,23,13,50,48,48,52,50,56,48,56,51,50,48, - 53,90,23,13,51,48,48,51,48,55,48,56,51,50,48,53,90,48,129,134,49,17,48,15,6, - 3,85,4,3,12,8,98,46,115,101,114,118,101,114,49,19,48,17,6,3,85,4,11,12,10,69, - 114,108,97,110,103,32,79,84,80,49,20,48,18,6,3,85,4,10,12,11,69,114,105,99, - 115,115,111,110,32,65,66,49,11,48,9,6,3,85,4,6,19,2,83,69,49,18,48,16,6,3,85, - 4,7,12,9,83,116,111,99,107,104,111,108,109,49,37,48,35,6,9,42,134,72,134,247, - 13,1,9,1,22,22,112,101,116,101,114,64,101,114,105,120,46,101,114,105,99,115, - 115,111,110,46,115,101,48,130,1,34,48,13,6,9,42,134,72,134,247,13,1,1,1,5,0, - 3,130,1,15,0,48,130,1,10,2,130,1,1,0,188,248,42,161,172,252,200,52,180,217, - 145,59,193,72,33,176,213,106,37,81,119,251,205,254,70,196,171,127,79,157,147, - 235,14,61,25,162,207,134,25,239,35,62,57,10,214,115,231,71,203,226,198,73, - 223,222,199,165,82,67,33,78,176,116,241,192,97,169,143,164,219,152,40,115, - 229,242,128,97,98,183,217,199,35,127,146,94,20,115,0,250,200,39,9,255,230, - 216,80,140,6,133,251,39,96,240,176,184,34,1,134,247,126,237,255,130,170,98, - 242,140,104,105,95,48,75,115,135,229,89,191,180,179,123,198,232,228,220,249, - 113,86,186,212,176,194,66,14,164,236,219,138,254,80,57,118,232,163,192,94,78, - 224,100,124,206,199,81,105,54,222,26,245,170,147,184,192,237,77,143,154,180, - 79,42,107,75,77,81,215,19,75,8,160,106,199,196,66,53,16,233,184,175,85,167, - 148,12,232,248,113,61,89,14,156,199,128,83,40,214,228,83,9,36,72,188,25,29, - 47,172,78,114,191,120,240,227,234,255,194,61,132,57,1,141,131,227,64,152,209, - 205,63,24,172,223,194,254,97,133,255,192,133,148,237,178,115,2,3,1,0,1,163, - 130,1,49,48,130,1,45,48,9,6,3,85,29,19,4,2,48,0,48,11,6,3,85,29,15,4,4,3,2,5, - 224,48,29,6,3,85,29,14,4,22,4,20,63,72,140,0,84,13,114,48,50,31,9,241,231, - 177,20,184,8,114,244,29,48,129,179,6,3,85,29,35,4,129,171,48,129,168,128,20, - 99,34,37,88,164,188,98,22,125,252,71,72,246,115,141,222,108,19,122,168,161, - 129,140,164,129,137,48,129,134,49,17,48,15,6,3,85,4,3,12,8,101,114,108,97, - 110,103,67,65,49,19,48,17,6,3,85,4,11,12,10,69,114,108,97,110,103,32,79,84, - 80,49,20,48,18,6,3,85,4,10,12,11,69,114,105,99,115,115,111,110,32,65,66,49, - 18,48,16,6,3,85,4,7,12,9,83,116,111,99,107,104,111,108,109,49,11,48,9,6,3,85, - 4,6,19,2,83,69,49,37,48,35,6,9,42,134,72,134,247,13,1,9,1,22,22,112,101,116, - 101,114,64,101,114,105,120,46,101,114,105,99,115,115,111,110,46,115,101,130, - 1,1,48,27,6,3,85,29,17,4,20,48,18,130,16,104,111,115,116,46,101,120,97,109, - 112,108,101,46,99,111,109,48,33,6,3,85,29,18,4,26,48,24,129,22,112,101,116, - 101,114,64,101,114,105,120,46,101,114,105,99,115,115,111,110,46,115,101,48, - 13,6,9,42,134,72,134,247,13,1,1,5,5,0,3,130,1,1,0,86,112,29,225,102,143,193, - 55,126,115,187,208,118,153,111,177,160,121,55,33,184,60,27,111,40,7,93,241,9, - 226,40,125,181,36,173,116,190,43,187,52,254,50,229,222,56,215,132,67,217,174, - 121,24,94,240,163,56,12,36,212,2,40,94,102,126,206,52,40,32,218,59,86,166, - 238,137,144,90,57,211,141,81,32,102,215,180,59,133,125,208,199,166,81,35,49, - 24,88,100,127,90,145,237,150,249,227,123,120,98,230,12,106,72,201,127,54,94, - 164,204,23,158,3,230,232,181,95,251,98,6,28,115,46,153,241,233,254,152,176, - 114,12,148,24,234,185,204,177,189,70,14,73,181,232,245,63,226,14,138,249,101, - 56,222,188,78,127,191,174,232,182,207,67,162,111,248,192,202,65,96,237,206, - 52,220,63,50,108,82,185,169,29,148,30,75,74,16,156,229,166,96,102,214,145,77, - 225,218,180,54,109,61,62,119,144,231,72,105,61,201,245,219,192,63,160,242, - 247,112,64,199,65,248,252,59,145,150,212,151,166,223,237,121,135,13,122,111, - 22,117,115,166,64,143,10,40,13,5,240,22,38,235,32,107,194,41>>, - - ResponderIDer = - <<161,129,135,48,129,132,49,17,48,15,6,3,85,4,3,12,8,98,46, - 115,101,114,118,101,114,49,18,48,16,6,3,85,4,11,12,10,69, - 114,108,97,110,103,79,84,80,49,19,48,17,6,3,85,4,10,12,11, - 69,114,105,99,115,115,111,110,65,66,49,11,48,9,6,3,85,4,6, - 19,2,83,69,49,18,48,16,6,3,85,4,7,12,9,83,116,111,99,107, - 104,111,108,109,49,37,48,35,6,9,42,134,72,134,247,13,1,9,1, - 22,22,112,101,116,101,114,64,101,114,105,120,46,101,114,105, - 99,115,115,111,110,46,115,101>>, + undefined = pubkey_ocsp:get_nonce_extn(undefined), + #'Extension'{extnID = ?'id-pkix-ocsp-nonce', + extnValue = ?NONCE} = pubkey_ocsp:get_nonce_extn(?NONCE), + + {ok, OcspResponse = #'BasicOCSPResponse'{}} = + pubkey_ocsp:decode_response(?OCSP_RESPONSE_DER), + + IsTrustedReponderFun = fun(_) -> true end, + {ok, [SingleResponse]} = + pubkey_ocsp:verify_response(OcspResponse, + [?RESPONDER_CERT], + ?NONCE, + ?ISSUER_CERT, + IsTrustedReponderFun), + {'SingleResponse', + {'CertID', + {'AlgorithmIdentifier', + {1,3,14,3,2,26},<<5,0>>}, + <<227,147,252,182,155,101,129,45,194,162,22,93,127,46,112,193,196,28,241,232>>, + <<34,25,129,87,115,255,155,246,200,97,92,7,51,110,152,61,97,155,164,171>>,9}, + {good,'NULL'},"20230720122949Z",asn1_NOVALUE,asn1_NOVALUE} = + SingleResponse, + + CertId = SingleResponse#'SingleResponse'.certID, + WrongNameHashSingleResponse = + SingleResponse#'SingleResponse'{ + certID = CertId#'CertID'{issuerNameHash = <<"rubbish_hash">>}}, + NextUpdateFromPast = SingleResponse#'SingleResponse'{nextUpdate = "19820720122949Z"}, + ThisUpdateFromFuture = SingleResponse#'SingleResponse'{thisUpdate = "21230720122949Z"}, + {ok, SingleResponse} = + pubkey_ocsp:find_single_response( + ?A_SERVER_CERT, ?ISSUER_CERT, + [rubbish_single_response, + WrongNameHashSingleResponse, + NextUpdateFromPast, + ThisUpdateFromFuture, + SingleResponse, rubbish_single_response]), + + %% invalid responses + IsNotTrustedReponderFun = fun(_) -> false end, + %% passing A_SERVER_CERT to get into Case3 in pubkey_oscp:is_authorized_responder + {error,ocsp_responder_cert_not_found} = + pubkey_ocsp:verify_response(OcspResponse, + [#cert{otp = ?A_SERVER_CERT}], + ?NONCE, + ?ISSUER_CERT, + IsNotTrustedReponderFun), + OcspResponseWrongSignature = + OcspResponse#'BasicOCSPResponse'{signature = <<"rubbish_signature">>}, + {error, ocsp_responder_cert_not_found} = + pubkey_ocsp:verify_response(OcspResponseWrongSignature, + [?RESPONDER_CERT], + ?NONCE, + ?ISSUER_CERT, + IsTrustedReponderFun), - Cert = - #'Certificate'{ - tbsCertificate = #'TBSCertificate'{ - version = v3, - serialNumber = 9, - signature = {'AlgorithmIdentifier',{1,2,840,113549,1,1,5},<<5,0>>}, - issuer = {rdnSequence, - [[{'AttributeTypeAndValue',{2,5,4,3},<<12,5,111,116,112,67,65>>}], - [{'AttributeTypeAndValue',{2,5,4,11},<<"\f\nErlangOTP">>}], - [{'AttributeTypeAndValue',{2,5,4,10},<<"\f\vEricssonAB">>}], - [{'AttributeTypeAndValue',{2,5,4,6},<<19,2,83,69>>}], - [{'AttributeTypeAndValue',{2,5,4,7},<<"\f\tStockholm">>}], - [{'AttributeTypeAndValue', - {1,2,840,113549,1,9,1}, - <<22,22,112,101,116,101,114,64,101,114,105,120,46,101, - 114,105,99,115,115,111,110,46,115,101>>}]]}, - validity = {'Validity',{utcTime,"200428083205Z"},{utcTime,"300307083205Z"}}, - subject = {rdnSequence, - [[{'AttributeTypeAndValue',{2,5,4,3},<<"\f\bb.server">>}], - [{'AttributeTypeAndValue',{2,5,4,11},<<"\f\nErlangOTP">>}], - [{'AttributeTypeAndValue',{2,5,4,10},<<"\f\vEricssonAB">>}], - [{'AttributeTypeAndValue',{2,5,4,6},<<19,2,83,69>>}], - [{'AttributeTypeAndValue',{2,5,4,7},<<"\f\tStockholm">>}], - [{'AttributeTypeAndValue', - {1,2,840,113549,1,9,1}, - <<22,22,112,101,116,101,114,64,101,114,105,120,46,101, - 114,105,99,115,115,111,110,46,115,101>>}]]}, - subjectPublicKeyInfo = {'SubjectPublicKeyInfo', - {'AlgorithmIdentifier',{1,2,840,113549,1,1,1},<<5,0>>}, - <<48,130,1,10,2,130,1,1,0,188,248,42,161,172,252,200,52,180,217, - 145,59,193,72,33,176,213,106,37,81,119,251,205,254,70,196,171, - 127,79,157,147,235,14,61,25,162,207,134,25,239,35,62,57,10,214, - 115,231,71,203,226,198,73,223,222,199,165,82,67,33,78,176,116, - 241,192,97,169,143,164,219,152,40,115,229,242,128,97,98,183,217, - 199,35,127,146,94,20,115,0,250,200,39,9,255,230,216,80,140,6, - 133,251,39,96,240,176,184,34,1,134,247,126,237,255,130,170,98, - 242,140,104,105,95,48,75,115,135,229,89,191,180,179,123,198,232, - 228,220,249,113,86,186,212,176,194,66,14,164,236,219,138,254,80, - 57,118,232,163,192,94,78,224,100,124,206,199,81,105,54,222,26, - 245,170,147,184,192,237,77,143,154,180,79,42,107,75,77,81,215, - 19,75,8,160,106,199,196,66,53,16,233,184,175,85,167,148,12,232, - 248,113,61,89,14,156,199,128,83,40,214,228,83,9,36,72,188,25,29, - 47,172,78,114,191,120,240,227,234,255,194,61,132,57,1,141,131, - 227,64,152,209,205,63,24,172,223,194,254,97,133,255,192,133,148, - 237,178,115,2,3,1,0,1>>}, - issuerUniqueID = asn1_NOVALUE, - subjectUniqueID = asn1_NOVALUE, - extensions = [{'Extension',{2,5,29,19},false,<<48,0>>}, - {'Extension',{2,5,29,15},false,<<3,2,5,224>>}, - {'Extension', - {2,5,29,14}, - false, - <<4,20,63,72,140,0,84,13,114,48,50,31,9,241,231,177,20,184,8,114, - 244,29>>}, - {'Extension', - {2,5,29,35}, - false, - <<48,129,168,128,20,99,34,37,88,164,188,98,22,125,252,71,72,246, - 115,141,222,108,19,122,168,161,129,140,164,129,137,48,129,134, - 49,17,48,15,6,3,85,4,3,12,8,101,114,108,97,110,103,67,65,49,19, - 48,17,6,3,85,4,11,12,10,69,114,108,97,110,103,32,79,84,80,49, - 20,48,18,6,3,85,4,10,12,11,69,114,105,99,115,115,111,110,32,65, - 66,49,18,48,16,6,3,85,4,7,12,9,83,116,111,99,107,104,111,108, - 109,49,11,48,9,6,3,85,4,6,19,2,83,69,49,37,48,35,6,9,42,134,72, - 134,247,13,1,9,1,22,22,112,101,116,101,114,64,101,114,105,120, - 46,101,114,105,99,115,115,111,110,46,115,101,130,1,1>>}, - {'Extension', - {2,5,29,17}, - false, - <<48,18,130,16,104,111,115,116,46,101,120,97,109,112,108,101,46, - 99,111,109>>}, - {'Extension', - {2,5,29,18}, - false, - <<48,24,129,22,112,101,116,101,114,64,101,114,105,120,46,101, - 114,105,99,115,115,111,110,46,115,101>>}]}, - signatureAlgorithm = {'AlgorithmIdentifier',{1,2,840,113549,1,1,5},<<5,0>>}, - signature = <<86,112,29,225,102,143,193,55,126,115,187,208,118,153,111,177,160,121,55, - 33,184,60,27,111,40,7,93,241,9,226,40,125,181,36,173,116,190,43,187,52, - 254,50,229,222,56,215,132,67,217,174,121,24,94,240,163,56,12,36,212,2, - 40,94,102,126,206,52,40,32,218,59,86,166,238,137,144,90,57,211,141,81, - 32,102,215,180,59,133,125,208,199,166,81,35,49,24,88,100,127,90,145,237, - 150,249,227,123,120,98,230,12,106,72,201,127,54,94,164,204,23,158,3,230, - 232,181,95,251,98,6,28,115,46,153,241,233,254,152,176,114,12,148,24,234, - 185,204,177,189,70,14,73,181,232,245,63,226,14,138,249,101,56,222,188, - 78,127,191,174,232,182,207,67,162,111,248,192,202,65,96,237,206,52,220, - 63,50,108,82,185,169,29,148,30,75,74,16,156,229,166,96,102,214,145,77, - 225,218,180,54,109,61,62,119,144,231,72,105,61,201,245,219,192,63,160, - 242,247,112,64,199,65,248,252,59,145,150,212,151,166,223,237,121,135,13, - 122,111,22,117,115,166,64,143,10,40,13,5,240,22,38,235,32,107,194,41>>}, - - %% test of the exported functions - ct:pal("Check pubkey_ocsp:verify_ocsp_response/3~n"), - {ok, SingleResponseGood} = - pubkey_ocsp:verify_ocsp_response(OCSPResponseDer, [Cert], Nonce), - {error, ocsp_response_bad_signature} = - pubkey_ocsp:verify_ocsp_response(MalOCSPResponseDer, [Cert], Nonce), {error, nonce_mismatch} = - pubkey_ocsp:verify_ocsp_response(OCSPResponseDer, [Cert], <<1,2,3>>), - ct:pal("pubkey_ocsp:verify_ocsp_response/3...ok~n"), - - ct:pal("Check pubkey_ocsp:decode_ocsp_response/1~n"), - {ok, #'BasicOCSPResponse'{}} = - pubkey_ocsp:decode_ocsp_response(OCSPResponseDer), - ct:pal("pubkey_ocsp:decode_ocsp_response/1...ok~n"), - - ct:pal("Check pubkey_ocsp:get_ocsp_responder_id/1~n"), - ResponderIDer = - pubkey_ocsp:get_ocsp_responder_id(Cert), - ct:pal("pubkey_ocsp:get_ocsp_responder_id/1...ok~n"), - - ct:pal("Check pubkey_ocsp:get_nonce_extn/1~n"), - undefined = - pubkey_ocsp:get_nonce_extn(undefined), - NonceExtension = - pubkey_ocsp:get_nonce_extn(Nonce), - ct:pal("pubkey_ocsp:get_nonce_extn/1...ok~n"). \ No newline at end of file + pubkey_ocsp:verify_response(OcspResponse, + [?RESPONDER_CERT], + <<"rubbish_nonce">>, + ?ISSUER_CERT, + IsTrustedReponderFun), + + OcspResponseProducedAt22ndCentury = % Year AD 2123 + OcspResponse#'BasicOCSPResponse'{ + tbsResponseData = #'ResponseData'{producedAt = "21230720122949Z"}}, + {error,ocsp_stale_response} = + pubkey_ocsp:verify_response(OcspResponseProducedAt22ndCentury, + [?RESPONDER_CERT], + ?NONCE, + ?ISSUER_CERT, + IsTrustedReponderFun), + ok. diff --git a/lib/public_key/test/public_key_SUITE.erl b/lib/public_key/test/public_key_SUITE.erl index ec14647c2f1b..f2c2fd557abf 100644 --- a/lib/public_key/test/public_key_SUITE.erl +++ b/lib/public_key/test/public_key_SUITE.erl @@ -127,6 +127,7 @@ pkix_test_data/1, pkix_is_issuer/0, pkix_is_issuer/1, + pkix_ocsp_validate/0, pkix_ocsp_validate/1, short_cert_issuer_hash/0, short_cert_issuer_hash/1, short_crl_issuer_hash/0, @@ -135,7 +136,8 @@ gen_ec_param_prime_field/1, gen_ec_param_char_2_field/0, gen_ec_param_char_2_field/1, - cacerts_load/0, cacerts_load/1 + cacerts_load/0, cacerts_load/1, + ocsp_extensions/0, ocsp_extensions/1 ]). -export([list_cacerts/0]). % debug exports @@ -183,7 +185,9 @@ all() -> pkix_is_issuer, short_cert_issuer_hash, short_crl_issuer_hash, - cacerts_load + cacerts_load, + ocsp_extensions, + pkix_ocsp_validate ]. groups() -> @@ -1477,6 +1481,99 @@ gen_ec_param_char_2_field(Config) when is_list(Config) -> Datadir = proplists:get_value(data_dir, Config), do_gen_ec_param(filename:join(Datadir, "ec_key_param1.pem")). +%%-------------------------------------------------------------------- +ocsp_extensions() -> + [{doc, "Check OCSP extensions"}]. +ocsp_extensions(_Config) -> + Nonce = <<4,8,66,243,220,236,16,118,51,215>>, + ExpectedExtentions = + [{'Extension', + ?'id-pkix-ocsp-nonce', + asn1_DEFAULT, + <<4,8,66,243,220,236,16,118,51,215>>}, + {'Extension', + ?'id-pkix-ocsp-response', + asn1_DEFAULT, + <<48,11,6,9,43,6,1,5,5,7,48,1,1>>}], + ExpectedExtentions = public_key:ocsp_extensions(Nonce). + +pkix_ocsp_validate() -> + [{doc, "Check OCSP extensions"}]. +pkix_ocsp_validate(_Config) -> + Cert = + {'OTPCertificate',{'OTPTBSCertificate',v3,9, + {'SignatureAlgorithm',{1,2,840,113549,1,1,11},'NULL'}, + {rdnSequence,[[{'AttributeTypeAndValue',{2,5,4,3},{utf8String,<<"otpCA">>}}],[{'AttributeTypeAndValue',{2,5,4,11},{utf8String,<<"Erlang OTP">>}}],[{'AttributeTypeAndValue',{2,5,4,10},{utf8String,<<"Ericsson AB">>}}],[{'AttributeTypeAndValue',{2,5,4,6},"SE"}],[{'AttributeTypeAndValue',{2,5,4,7},{utf8String,<<"Stockholm">>}}],[{'AttributeTypeAndValue',{1,2,840,113549,1,9,1},"peter@erix.ericsson.se"}]]}, + {'Validity',{utcTime,"230721110721Z"},{utcTime,"330529110721Z"}}, + {rdnSequence,[[{'AttributeTypeAndValue',{2,5,4,3},{utf8String,<<"a.server">>}}],[{'AttributeTypeAndValue',{2,5,4,11},{utf8String,<<"Erlang OTP">>}}],[{'AttributeTypeAndValue',{2,5,4,10},{utf8String,<<"Ericsson AB">>}}],[{'AttributeTypeAndValue',{2,5,4,6},"SE"}],[{'AttributeTypeAndValue',{2,5,4,7},{utf8String,<<"Stockholm">>}}],[{'AttributeTypeAndValue',{1,2,840,113549,1,9,1},"peter@erix.ericsson.se"}]]}, + {'OTPSubjectPublicKeyInfo',{'PublicKeyAlgorithm',{1,2,840,113549,1,1,1},'NULL'}, + {'RSAPublicKey',19254743747256260264207569423711759377779938665145630924415701722071839009286238971264967781043993434178803001083069740412920664146137571550852074547463946025114390093775800702438227109245066854329070921351832849321692114677809046259034306196616912261365770291322044071697789183279204771685063580949070504947864713748039312242300503875879444809664605423001542854874228001872895975468648787616073960661286876663709764410812833966560999459482926236332297043685455899393823175706646393051956438518613689798667608292659880957737510004003274559865311466147775473832468655042097383293967251824412697382839864114388741712057, + 65537}}, + asn1_NOVALUE,asn1_NOVALUE, + [{'Extension',{2,5,29,19},false,{'BasicConstraints',false,asn1_NOVALUE}}, + {'Extension',{2,5,29,15},false,[digitalSignature,nonRepudiation,keyEncipherment]}, + {'Extension',{2,5,29,14},false,<<175,14,85,35,212,170,133,20,114,234,90,223,163,49,255,87,86,93,165,56>>}, + {'Extension',{2,5,29,35}, + false, + {'AuthorityKeyIdentifier',<<123,93,133,100,41,175,227,134,140,47,217,84,132,181,89,186,102,41,30,255>>, + [{directoryName,{rdnSequence,[[{'AttributeTypeAndValue',{2,5,4,3},{utf8String,<<"erlangCA">>}}], + [{'AttributeTypeAndValue',{2,5,4,11},{utf8String,<<"Erlang OTP">>}}], + [{'AttributeTypeAndValue',{2,5,4,10},{utf8String,<<"Ericsson AB">>}}], + [{'AttributeTypeAndValue',{2,5,4,7},{utf8String,<<"Stockholm">>}}], + [{'AttributeTypeAndValue',{2,5,4,6},"SE"}], + [{'AttributeTypeAndValue',{1,2,840,113549,1,9,1},"peter@erix.ericsson.se"}]]}}], + 1}}, + {'Extension',{2,5,29,17},false,[{dNSName,"host.example.com"}]}, + {'Extension',{2,5,29,18},false,[{rfc822Name,"peter@erix.ericsson.se"}]}]}, + {'SignatureAlgorithm',{1,2,840,113549,1,1,11},'NULL'}, + <<23,196,208,23,144,187,135,84,233,168,123,81,115,112,33,52,77,238,239,70,248,131,119,160,178,216,252,166,176,20,252,211,108,160,202,140,96,84,98,209,7,149,30,184,0,196,139,48,122,36,45,10,198,106,98,33,183,254,48,11,88,64,93,232,152,233,133,216,191,128,35,96,183,221,122,87,230,30,191,199,226,203,164,217,236,101,83,158,113,211,177,52,217,39,96,108,242,87,70,44,246,68,124,122,121,88,188,254,22,48,98,121,238,158,4,160,141,249,255,93,147,83,42,86,62,5,118,164,54,75,87,49,111, + 126,197,89,32,226,89,40,154,70,165,118,239,26,249,59,48,52,237,152,240,131,100,187,14,157,201,103,102,27,81,198,226,121,221,68,244,119,130,149,231,179,35,64,96,254,245,5,199,112,145,65,69,80,87,235,140,137,20,220,148,157,94,123,177,186,187,66,99,92,150,213,147,129,36,126,93,4,10,123,70,238,175,247,102,91,42,201,27,123,76,212,45,115,11,31,114,173,124,27,156,248,36,37,195,111,206,236,43,224,157,50,98,109,179,87,223,187,8,204,197,202,155,60>>}, + IssuerCert = + {'OTPCertificate',{'OTPTBSCertificate',v3,1, + {'SignatureAlgorithm',{1,2,840,113549,1,1,11},'NULL'}, + {rdnSequence,[[{'AttributeTypeAndValue',{2,5,4,3},{utf8String,<<"erlangCA">>}}],[{'AttributeTypeAndValue',{2,5,4,11},{utf8String,<<"Erlang OTP">>}}],[{'AttributeTypeAndValue',{2,5,4,10},{utf8String,<<"Ericsson AB">>}}],[{'AttributeTypeAndValue',{2,5,4,7},{utf8String,<<"Stockholm">>}}],[{'AttributeTypeAndValue',{2,5,4,6},"SE"}],[{'AttributeTypeAndValue',{1,2,840,113549,1,9,1},"peter@erix.ericsson.se"}]]}, + {'Validity',{utcTime,"230721110720Z"},{utcTime,"330529110720Z"}}, + {rdnSequence,[[{'AttributeTypeAndValue',{2,5,4,3},{utf8String,<<"otpCA">>}}],[{'AttributeTypeAndValue',{2,5,4,11},{utf8String,<<"Erlang OTP">>}}],[{'AttributeTypeAndValue',{2,5,4,10},{utf8String,<<"Ericsson AB">>}}],[{'AttributeTypeAndValue',{2,5,4,6},"SE"}],[{'AttributeTypeAndValue',{2,5,4,7},{utf8String,<<"Stockholm">>}}],[{'AttributeTypeAndValue',{1,2,840,113549,1,9,1},"peter@erix.ericsson.se"}]]}, + {'OTPSubjectPublicKeyInfo',{'PublicKeyAlgorithm',{1,2,840,113549,1,1,1},'NULL'}, + {'RSAPublicKey',21858379260819365313885475389172639523863567481982302063462584029790343874819317972475546206568963022785252583910194728269078148431804871680312638323851125861707159230343297343111968246731095811513561212201088276841624533346998017512000090901290490304174895932870845288899008429347052837949441312958652271962356020302617279856538736007013593572768976262766464136388094144122584736630529987720049486299302127652434926700165727330943325372510516379103006575448279898129379834740761468401572505064753618409945975591285059206889943804512145915054818226570266582909516966602868100682823910151957272535898084374557112395143, + 65537}}, + asn1_NOVALUE,asn1_NOVALUE, + [{'Extension',{2,5,29,19},true,{'BasicConstraints',true,asn1_NOVALUE}}, + {'Extension',{2,5,29,15},false,[keyCertSign,cRLSign]}, + {'Extension',{2,5,29,14},false,<<123,93,133,100,41,175,227,134,140,47,217,84,132,181,89,186,102,41,30,255>>}, + {'Extension',{2,5,29,35}, + false, + {'AuthorityKeyIdentifier',<<229,159,14,81,153,72,30,27,33,37,234,91,103,205,230,72,95,185,112,95>>, + [{directoryName,{rdnSequence,[[{'AttributeTypeAndValue',{2,5,4,3},{utf8String,<<"erlangCA">>}}], + [{'AttributeTypeAndValue',{2,5,4,11},{utf8String,<<"Erlang OTP">>}}], + [{'AttributeTypeAndValue',{2,5,4,10},{utf8String,<<"Ericsson AB">>}}], + [{'AttributeTypeAndValue',{2,5,4,7},{utf8String,<<"Stockholm">>}}], + [{'AttributeTypeAndValue',{2,5,4,6},"SE"}], + [{'AttributeTypeAndValue',{1,2,840,113549,1,9,1},"peter@erix.ericsson.se"}]]}}], + 674805639123712796695508479052504582494838106155}}, + {'Extension',{2,5,29,17},false,[{rfc822Name,"peter@erix.ericsson.se"}]}, + {'Extension',{2,5,29,18},false,[{rfc822Name,"peter@erix.ericsson.se"}]}]}, + {'SignatureAlgorithm',{1,2,840,113549,1,1,11},'NULL'}, + <<44,128,75,220,253,223,223,77,33,57,30,205,101,103,200,211,254,81,122,195,123,239,98,5,118,58,179,193,24,93,12,243,124,194,160,163,206,243,199,49,143,11,73,192,218,193,154,93,146,232,1,191,99,201,129,94,131,59,107,227,216,17,31,101,67,153,177,189,164,194,224,164,78,160,42,79,131,65,37,78,226,201,200,180,128,38,101,164,193,72,82,196,88,204,145,94,235,84,13,243,0,149,99,175,203,211,108,177,156,17,27,40,87,195,19,56,39,102,103,42,27,60,30,44,204,157,107,121,128,68,93,216,123, + 106,112,105,74,7,142,155,171,1,8,31,123,245,78,142,111,142,178,127,169,202,110,125,35,192,199,23,203,201,103,44,99,100,192,156,214,62,109,71,205,66,32,81,252,124,138,238,225,88,247,85,255,65,141,131,234,184,248,20,51,81,71,19,98,102,114,96,49,77,1,79,27,18,218,79,37,232,194,204,172,54,124,167,188,158,43,54,183,230,40,230,152,216,12,27,56,66,104,238,235,52,176,110,159,88,151,7,228,201,248,195,82,131,220,31,104,44,239,147,61,71,35,245>>}, + OcspRespDer = + <<48,130,7,36,10,1,0,160,130,7,29,48,130,7,25,6,9,43,6,1,5,5,7,48,1,1,4,130,7,10,48,130,7,6,48,130,1,10,161,129,134,48,129,131,49,14,48,12,6,3,85,4,3,12,5,111,116,112,67,65,49,19,48,17,6,3,85,4,11,12,10,69,114,108,97,110,103,32,79,84,80,49,20,48,18,6,3,85,4,10,12,11,69,114,105,99,115,115,111,110,32,65,66,49,11,48,9,6,3,85,4,6,19,2,83,69,49,18,48,16,6,3,85,4,7,12,9,83,116,111,99,107,104,111,108,109,49,37,48,35,6,9,42,134,72,134,247,13,1,9,1,22,22,112,101,116,101,114,64,101,114,105,120,46,101, + 114,105,99,115,115,111,110,46,115,101,24,15,50,48,50,51,48,55,50,49,49,49,48,55,50,53,90,48,81,48,79,48,58,48,9,6,5,43,14,3,2,26,5,0,4,20,227,147,252,182,155,101,129,45,194,162,22,93,127,46,112,193,196,28,241,232,4,20,123,93,133,100,41,175,227,134,140,47,217,84,132,181,89,186,102,41,30,255,2,1,9,128,0,24,15,50,48,50,51,48,55,50,49,49,49,48,55,50,53,90,161,27,48,25,48,23,6,9,43,6,1,5,5,7,48,1,2,4,10,4,8,244,183,192,191,230,8,236,82,48,13,6,9,42,134,72,134,247,13,1,1,11,5,0,3,130,1,1,0,151,99, + 102,238,65,164,80,97,143,115,223,2,201,56,75,220,145,150,17,27,9,169,149,158,40,226,29,109,8,35,234,24,59,113,1,26,123,144,32,68,235,210,36,55,61,215,0,183,49,156,52,153,132,237,180,231,43,45,18,138,126,118,173,130,246,213,225,216,15,85,248,146,35,220,27,100,93,232,234,91,206,224,98,18,48,52,95,213,129,117,11,174,228,48,220,235,82,141,157,179,13,119,17,244,189,21,77,102,114,166,227,25,160,113,148,244,142,33,232,161,77,189,187,72,196,144,82,70,200,250,222,68,154,153,20,33,60,4,252,151,16,64, + 207,109,4,30,49,47,75,150,122,24,90,22,226,156,91,30,83,141,79,29,116,58,13,185,66,215,89,19,64,194,190,72,113,112,136,61,75,5,138,239,108,222,87,212,193,155,108,150,47,180,73,3,110,216,68,189,146,8,179,94,110,147,207,86,2,65,251,193,111,254,43,200,77,72,154,214,13,40,48,209,104,42,105,175,163,52,160,39,92,238,240,174,145,3,33,49,33,231,26,14,5,32,33,220,74,149,25,163,131,65,30,63,134,148,160,130,4,224,48,130,4,220,48,130,4,216,48,130,3,192,160,3,2,1,2,2,1,1,48,13,6,9,42,134,72,134,247,13,1, + 1,11,5,0,48,129,134,49,17,48,15,6,3,85,4,3,12,8,101,114,108,97,110,103,67,65,49,19,48,17,6,3,85,4,11,12,10,69,114,108,97,110,103,32,79,84,80,49,20,48,18,6,3,85,4,10,12,11,69,114,105,99,115,115,111,110,32,65,66,49,18,48,16,6,3,85,4,7,12,9,83,116,111,99,107,104,111,108,109,49,11,48,9,6,3,85,4,6,19,2,83,69,49,37,48,35,6,9,42,134,72,134,247,13,1,9,1,22,22,112,101,116,101,114,64,101,114,105,120,46,101,114,105,99,115,115,111,110,46,115,101,48,30,23,13,50,51,48,55,50,49,49,49,48,55,50,48,90,23,13, + 51,51,48,53,50,57,49,49,48,55,50,48,90,48,129,131,49,14,48,12,6,3,85,4,3,12,5,111,116,112,67,65,49,19,48,17,6,3,85,4,11,12,10,69,114,108,97,110,103,32,79,84,80,49,20,48,18,6,3,85,4,10,12,11,69,114,105,99,115,115,111,110,32,65,66,49,11,48,9,6,3,85,4,6,19,2,83,69,49,18,48,16,6,3,85,4,7,12,9,83,116,111,99,107,104,111,108,109,49,37,48,35,6,9,42,134,72,134,247,13,1,9,1,22,22,112,101,116,101,114,64,101,114,105,120,46,101,114,105,99,115,115,111,110,46,115,101,48,130,1,34,48,13,6,9,42,134,72,134,247, + 13,1,1,1,5,0,3,130,1,15,0,48,130,1,10,2,130,1,1,0,173,38,214,237,131,195,86,49,85,177,225,21,254,222,227,229,5,62,193,131,224,141,51,233,36,68,108,11,164,68,95,160,243,171,55,43,32,228,15,5,179,194,124,9,53,219,33,15,243,77,206,104,255,63,250,231,185,218,111,190,98,34,71,38,139,51,202,112,110,85,248,177,207,156,210,51,28,18,236,236,4,188,58,33,169,250,181,59,114,133,246,82,217,36,166,28,3,70,49,82,68,36,134,32,57,142,168,231,193,73,219,102,49,13,97,199,40,138,118,250,244,41,206,121,115,208, + 19,230,5,243,38,239,1,36,41,13,232,86,191,182,144,86,6,211,57,117,243,216,229,51,99,224,126,39,125,40,127,104,11,72,234,205,113,200,92,92,16,19,136,114,193,132,13,94,240,242,21,211,46,12,85,64,205,36,26,63,69,187,206,233,0,170,217,10,160,20,147,236,233,244,66,234,133,95,84,34,109,40,107,163,119,22,202,156,112,153,240,188,17,145,105,157,23,239,140,106,7,155,196,161,187,21,174,181,169,137,91,242,134,9,35,52,159,36,160,30,169,36,130,60,61,61,245,235,229,135,2,3,1,0,1,163,130,1,80,48,130,1,76,48, + 15,6,3,85,29,19,1,1,255,4,5,48,3,1,1,255,48,11,6,3,85,29,15,4,4,3,2,1,6,48,29,6,3,85,29,14,4,22,4,20,123,93,133,100,41,175,227,134,140,47,217,84,132,181,89,186,102,41,30,255,48,129,198,6,3,85,29,35,4,129,190,48,129,187,128,20,229,159,14,81,153,72,30,27,33,37,234,91,103,205,230,72,95,185,112,95,161,129,140,164,129,137,48,129,134,49,17,48,15,6,3,85,4,3,12,8,101,114,108,97,110,103,67,65,49,19,48,17,6,3,85,4,11,12,10,69,114,108,97,110,103,32,79,84,80,49,20,48,18,6,3,85,4,10,12,11,69,114,105,99, + 115,115,111,110,32,65,66,49,18,48,16,6,3,85,4,7,12,9,83,116,111,99,107,104,111,108,109,49,11,48,9,6,3,85,4,6,19,2,83,69,49,37,48,35,6,9,42,134,72,134,247,13,1,9,1,22,22,112,101,116,101,114,64,101,114,105,120,46,101,114,105,99,115,115,111,110,46,115,101,130,20,118,51,84,213,187,124,136,133,219,84,17,35,72,97,52,24,238,100,168,43,48,33,6,3,85,29,17,4,26,48,24,129,22,112,101,116,101,114,64,101,114,105,120,46,101,114,105,99,115,115,111,110,46,115,101,48,33,6,3,85,29,18,4,26,48,24,129,22,112,101, + 116,101,114,64,101,114,105,120,46,101,114,105,99,115,115,111,110,46,115,101,48,13,6,9,42,134,72,134,247,13,1,1,11,5,0,3,130,1,1,0,44,128,75,220,253,223,223,77,33,57,30,205,101,103,200,211,254,81,122,195,123,239,98,5,118,58,179,193,24,93,12,243,124,194,160,163,206,243,199,49,143,11,73,192,218,193,154,93,146,232,1,191,99,201,129,94,131,59,107,227,216,17,31,101,67,153,177,189,164,194,224,164,78,160,42,79,131,65,37,78,226,201,200,180,128,38,101,164,193,72,82,196,88,204,145,94,235,84,13,243,0,149, + 99,175,203,211,108,177,156,17,27,40,87,195,19,56,39,102,103,42,27,60,30,44,204,157,107,121,128,68,93,216,123,106,112,105,74,7,142,155,171,1,8,31,123,245,78,142,111,142,178,127,169,202,110,125,35,192,199,23,203,201,103,44,99,100,192,156,214,62,109,71,205,66,32,81,252,124,138,238,225,88,247,85,255,65,141,131,234,184,248,20,51,81,71,19,98,102,114,96,49,77,1,79,27,18,218,79,37,232,194,204,172,54,124,167,188,158,43,54,183,230,40,230,152,216,12,27,56,66,104,238,235,52,176,110,159,88,151,7,228,201, + 248,195,82,131,220,31,104,44,239,147,61,71,35,245>>, + NonceExt = <<4,8,244,183,192,191,230,8,236,82>>, + ok = + public_key:pkix_ocsp_validate(Cert, IssuerCert, OcspRespDer, NonceExt, []). + %%-------------------------------------------------------------------- cacerts_load() -> [{doc, "Basic tests of cacerts functionality"}]. From 8e20f461978eb9c103ed2554651adcf56a64f4e0 Mon Sep 17 00:00:00 2001 From: Jakub Witczak Date: Mon, 29 Jan 2024 11:11:53 +0100 Subject: [PATCH 2/2] ssl: stapling and OCSP implementation --- lib/ssl/doc/src/ssl.xml | 35 +-- lib/ssl/doc/src/standards_compliance.xml | 12 +- .../{pem_and_cert_cache.md => ssl_notes.md} | 60 ++++- lib/ssl/src/dtls_connection.erl | 24 +- lib/ssl/src/dtls_handshake.erl | 4 +- lib/ssl/src/ssl.app.src | 2 +- lib/ssl/src/ssl.erl | 69 +++--- lib/ssl/src/ssl_alert.erl | 19 +- lib/ssl/src/ssl_certificate.erl | 59 +++-- lib/ssl/src/ssl_connection.hrl | 4 +- lib/ssl/src/ssl_gen_statem.erl | 10 +- lib/ssl/src/ssl_handshake.erl | 107 ++++---- lib/ssl/src/ssl_internal.hrl | 5 +- lib/ssl/src/ssl_trace.erl | 25 +- lib/ssl/src/tls_client_connection_1_3.erl | 4 +- lib/ssl/src/tls_connection.erl | 36 +-- lib/ssl/src/tls_dtls_connection.erl | 66 ++--- lib/ssl/src/tls_gen_connection.erl | 2 +- lib/ssl/src/tls_gen_connection_1_3.erl | 1 + lib/ssl/src/tls_handshake.erl | 21 +- lib/ssl/src/tls_handshake_1_3.erl | 62 ++--- lib/ssl/test/Makefile | 2 +- lib/ssl/test/make_certs.erl | 42 ++-- ...p_SUITE.erl => openssl_stapling_SUITE.erl} | 234 ++++++++++++------ lib/ssl/test/ssl_api_SUITE.erl | 44 ++-- lib/ssl/test/ssl_gh.spec | 1 - lib/ssl/test/ssl_test_lib.erl | 2 + 27 files changed, 538 insertions(+), 414 deletions(-) rename lib/ssl/internal_doc/{pem_and_cert_cache.md => ssl_notes.md} (50%) rename lib/ssl/test/{openssl_ocsp_SUITE.erl => openssl_stapling_SUITE.erl} (54%) diff --git a/lib/ssl/doc/src/ssl.xml b/lib/ssl/doc/src/ssl.xml index 393399d57a7c..efda94b2d656 100644 --- a/lib/ssl/doc/src/ssl.xml +++ b/lib/ssl/doc/src/ssl.xml @@ -1272,28 +1272,19 @@ fun(srp, Username :: binary(), UserState :: term()) -> - - - - - - - - - - - - - - - - - - - - - - + + +

If staple or a map, OCSP stapling will be enabled, an + extension of type "status_request" will be included in the + client hello to indicate the desire to receive certificate + status information. If no_staple (the default), OCSP stapling will + be disabled.

+ +

When map is used, boolean ocsp_nonce key may indicate if + OCSP nonce should be requested by the client (default is + true).

+
+
diff --git a/lib/ssl/doc/src/standards_compliance.xml b/lib/ssl/doc/src/standards_compliance.xml index ca1803983023..c519b02b4917 100644 --- a/lib/ssl/doc/src/standards_compliance.xml +++ b/lib/ssl/doc/src/standards_compliance.xml @@ -309,8 +309,8 @@ status_request (RFC6066) - NC - + C + 27.0 @@ -1473,8 +1473,8 @@ status_request (RFC6066) - NC - + C + 27.0 @@ -1509,8 +1509,8 @@ Client - NC - + PC + 27.0 diff --git a/lib/ssl/internal_doc/pem_and_cert_cache.md b/lib/ssl/internal_doc/ssl_notes.md similarity index 50% rename from lib/ssl/internal_doc/pem_and_cert_cache.md rename to lib/ssl/internal_doc/ssl_notes.md index 52fac1e6fef9..723aa1594102 100644 --- a/lib/ssl/internal_doc/pem_and_cert_cache.md +++ b/lib/ssl/internal_doc/ssl_notes.md @@ -1,5 +1,53 @@ -# Notes on the PEM and cert caches -## Data relations +# ssl dev notes +## client-side OCSP stapling +1. stapling - is ssl option holding configuration provided by user + - ocsp_nonce :: true|false +2. stapling_state - holds handshake process data + - status :: not_negotiated | negotiated | not_received | received_staple + - ocsp_nonce :: binary() +3. stapling_info - holds date required for verifying the certificate chain + +```mermaid +classDiagram + stapling .. stapling_state + stapling_state ..* stapling_info + + stapling: ocsp_nonce + note for stapling "- stapling option is a boolean or a map\n- map is interpreted as stapling enabled\n- ocsp_nonce is boolean" + stapling_state: configured + stapling_state: ocsp_nonce + note for stapling_state "ocsp_nonce is random binary" + stapling_state: status + stapling_state: response + stapling_info: cert_ext #{SubjectId => Status} +``` +## ssl test certificates +- test certificates are generated by `ssl/test/make_certs.erl/` + +```mermaid +--- +title: Test certs +--- +flowchart RL + localhost["`2:localhost + 3:localhost`"] --> erlangCA[["BIG_RAND_SERIAL:erlangCA"]] + otpCA[[1:otpCA]] --> erlangCA + client["`1:client + 2:client`"] --> otpCA + server["`3:server + 4:server`"] --> otpCA + aserver["`9:a.server + 10:a.server`"] --> otpCA + bserver["`11:b.server + 12:b.server`"] --> otpCA + revoked["`5:revoked + 6:revoked`"] --> otpCA + undetermined["`7:undetermined + 8:undetermined`"] --> otpCA +``` + +## Notes on the PEM and cert caches +### Data relations |---------------| |------------------------| | PemCache | | CertDb | @@ -17,21 +65,21 @@ | Ref (FK) | | Counter | |-----------------| |------------| -### PemCache +#### PemCache 1. stores a copy of file content in memory 2. includes files from cacertfile, certfile, keyfile options 3. content is added unless FileMapDb table contains entry with specified path -### FileMapDb +#### FileMapDb 1. holds relation between specific path (PEM file with CA certificates) and a ref 2. ref is generated when file from path is added for 1st time 3. ref is used as path identifier in CertDb and RefDb tables -### RefDb +#### RefDb 1. holds an active connections counter for a specific ref 2. when counter reaches zero - related data in CertDb, FileMapDb, RefDb is deleted -### CertDb +#### CertDb 1. holds decoded CA ceritificates (only those taken from cacertfile option) 2. used for building certificate chains 3. it is an ETS set table - when iterating in search of Issuer certificate, diff --git a/lib/ssl/src/dtls_connection.erl b/lib/ssl/src/dtls_connection.erl index cedcd334ac43..be26bbb4108e 100644 --- a/lib/ssl/src/dtls_connection.erl +++ b/lib/ssl/src/dtls_connection.erl @@ -88,7 +88,7 @@ %% | Abbrev Flight 1 to Abbrev Flight 2 part 1 %% | %% New session | Resumed session -%% WAIT_OCSP_STAPLING CERTIFY <----------------------------------> ABBREVIATED +%% WAIT_STAPLING CERTIFY <----------------------------------> ABBREVIATED %% %% <- Possibly Receive -- | | %% OCSP Stapel ------> | Send/ Recv Flight 5 | @@ -142,7 +142,7 @@ downgrade/3, hello/3, user_hello/3, - wait_ocsp_stapling/3, + wait_stapling/3, certify/3, wait_cert_verify/3, cipher/3, @@ -304,7 +304,7 @@ hello(internal, #hello_verify_request{cookie = Cookie}, host = Host, port = Port}, handshake_env = #handshake_env{renegotiation = {Renegotiation, _}, - ocsp_stapling_state = OcspState0} = HsEnv, + stapling_state = StaplingState0} = HsEnv, connection_env = CEnv, ssl_options = SslOpts, session = #session{session_id = Id}, @@ -320,7 +320,7 @@ hello(internal, #hello_verify_request{cookie = Cookie}, State0#state{handshake_env = HsEnv#handshake_env{ tls_handshake_history = ssl_handshake:init_handshake_history(), - ocsp_stapling_state = OcspState0#{ocsp_nonce => OcspNonce}}}), + stapling_state = StaplingState0#{ocsp_nonce => OcspNonce}}}), {State2, Actions} = dtls_gen_connection:send_handshake(Hello, State1), State = State2#state{connection_env = CEnv#connection_env{negotiated_version = Version}, % RequestedVersion @@ -365,18 +365,18 @@ hello(internal, #server_hello{} = Hello, static_env = #static_env{role = client}, handshake_env = #handshake_env{ renegotiation = {Renegotiation, _}, - ocsp_stapling_state = OcspState0} = HsEnv, + stapling_state = StaplingState0} = HsEnv, connection_states = ConnectionStates0, session = #session{session_id = OldId}, ssl_options = SslOptions} = State) -> try - {Version, NewId, ConnectionStates, ProtoExt, Protocol, OcspState} = + {Version, NewId, ConnectionStates, ProtoExt, Protocol, StaplingState} = dtls_handshake:hello(Hello, SslOptions, ConnectionStates0, Renegotiation, OldId), tls_dtls_connection:handle_session( Hello, Version, NewId, ConnectionStates, ProtoExt, Protocol, State#state{handshake_env = HsEnv#handshake_env{ - ocsp_stapling_state = maps:merge(OcspState0,OcspState)}}) + stapling_state = maps:merge(StaplingState0,StaplingState)}}) catch throw:#alert{} = Alert -> ssl_gen_statem:handle_own_alert(Alert, ?FUNCTION_NAME, State) end; @@ -430,17 +430,17 @@ abbreviated(Type, Event, State) -> gen_handshake(?FUNCTION_NAME, Type, Event, State). %%-------------------------------------------------------------------- --spec wait_ocsp_stapling(gen_statem:event_type(), term(), #state{}) -> +-spec wait_stapling(gen_statem:event_type(), term(), #state{}) -> gen_statem:state_function_result(). %%-------------------------------------------------------------------- -wait_ocsp_stapling(enter, _Event, State0) -> +wait_stapling(enter, _Event, State0) -> {State, Actions} = handle_flight_timer(State0), {keep_state, State, Actions}; -wait_ocsp_stapling(info, Event, State) -> +wait_stapling(info, Event, State) -> gen_info(Event, ?FUNCTION_NAME, State); -wait_ocsp_stapling(state_timeout, Event, State) -> +wait_stapling(state_timeout, Event, State) -> handle_state_timeout(Event, ?FUNCTION_NAME, State); -wait_ocsp_stapling(Type, Event, State) -> +wait_stapling(Type, Event, State) -> gen_handshake(?FUNCTION_NAME, Type, Event, State). %%-------------------------------------------------------------------- diff --git a/lib/ssl/src/dtls_handshake.erl b/lib/ssl/src/dtls_handshake.erl index 1f85bae2ce1d..30fc4e7f6979 100644 --- a/lib/ssl/src/dtls_handshake.erl +++ b/lib/ssl/src/dtls_handshake.erl @@ -226,12 +226,12 @@ handle_client_hello_extensions(Version, Type, Random, CipherSuites, handle_server_hello_extensions(Version, SessionId, Random, CipherSuite, HelloExt, SslOpt, ConnectionStates0, Renegotiation, IsNew) -> - {ConnectionStates, ProtoExt, Protocol, OcspState} = + {ConnectionStates, ProtoExt, Protocol, StaplingState} = ssl_handshake:handle_server_hello_extensions( dtls_record, Random, CipherSuite, HelloExt, dtls_v1:corresponding_tls_version(Version), SslOpt, ConnectionStates0, Renegotiation, IsNew), - {Version, SessionId, ConnectionStates, ProtoExt, Protocol, OcspState}. + {Version, SessionId, ConnectionStates, ProtoExt, Protocol, StaplingState}. %%-------------------------------------------------------------------- diff --git a/lib/ssl/src/ssl.app.src b/lib/ssl/src/ssl.app.src index 3c86fe874063..0920e8d98d85 100644 --- a/lib/ssl/src/ssl.app.src +++ b/lib/ssl/src/ssl.app.src @@ -88,6 +88,6 @@ {applications, [crypto, public_key, kernel, stdlib]}, {env, []}, {mod, {ssl_app, []}}, - {runtime_dependencies, ["stdlib-4.1","public_key-@OTP-18876@","kernel-9.0", + {runtime_dependencies, ["stdlib-4.1","public_key-@OTP-18876:OTP-18606@","kernel-9.0", "erts-@OTP-18941@","crypto-5.0", "inets-5.10.7", "runtime_tools-1.15.1"]}]}. diff --git a/lib/ssl/src/ssl.erl b/lib/ssl/src/ssl.erl index 80f033b126b0..48eee9967e23 100644 --- a/lib/ssl/src/ssl.erl +++ b/lib/ssl/src/ssl.erl @@ -434,10 +434,8 @@ {session_tickets, client_session_tickets()} | {use_ticket, use_ticket()} | {early_data, client_early_data()} | - {use_srtp, use_srtp()}. -%% {ocsp_stapling, ocsp_stapling()} | -%% {ocsp_responder_certs, ocsp_responder_certs()} | -%% {ocsp_nonce, ocsp_nonce()}. + {use_srtp, use_srtp()} | + {stapling, stapling()}. -type client_verify_type() :: verify_type(). -type client_reuse_session() :: session_id() | {session_id(), SessionData::binary()}. @@ -459,9 +457,7 @@ -type max_fragment_length() :: undefined | 512 | 1024 | 2048 | 4096. -type fallback() :: boolean(). -type ssl_imp() :: new | old. -%% -type ocsp_stapling() :: boolean(). -%% -type ocsp_responder_certs() :: [public_key:der_encoded()]. -%% -type ocsp_nonce() :: boolean(). +-type stapling() :: staple | no_staple | map(). %% ------------------------------------------------------------------------------------------------------- @@ -1645,7 +1641,7 @@ ssl_options() -> middlebox_comp_mode, max_fragment_length, next_protocol_selector, next_protocols_advertised, - ocsp_stapling, ocsp_responder_certs, ocsp_nonce, + stapling, padding_check, partial_chain, password, @@ -1687,7 +1683,7 @@ process_options(UserSslOpts, SslOpts0, Env) -> SslOpts2 = opt_verification(UserSslOptsMap, SslOpts1, Env), SslOpts3 = opt_certs(UserSslOptsMap, SslOpts2, Env), SslOpts4 = opt_tickets(UserSslOptsMap, SslOpts3, Env), - SslOpts5 = opt_ocsp(UserSslOptsMap, SslOpts4, Env), + SslOpts5 = opt_stapling(UserSslOptsMap, SslOpts4, Env), SslOpts6 = opt_sni(UserSslOptsMap, SslOpts5, Env), SslOpts7 = opt_signature_algs(UserSslOptsMap, SslOpts6, Env), SslOpts8 = opt_alpn(UserSslOptsMap, SslOpts7, Env), @@ -2073,33 +2069,30 @@ opt_tickets(UserOpts, #{versions := Versions} = Opts, #{role := server}) -> Opts#{session_tickets => SessionTickets, early_data => EarlyData, anti_replay => AntiReplay, stateless_tickets_seed => STS}. -opt_ocsp(UserOpts, #{versions := _Versions} = Opts, #{role := Role}) -> - {Stapling, SMap} = - case get_opt(ocsp_stapling, ?DEFAULT_OCSP_STAPLING, UserOpts, Opts) of - {old, Map} when is_map(Map) -> {true, Map}; - {_, Bool} when is_boolean(Bool) -> {Bool, #{}}; - {_, Value} -> option_error(ocsp_stapling, Value) +opt_stapling(UserOpts, #{versions := _Versions} = Opts, #{role := client}) -> + {Stapling, Nonce} = + case get_opt(stapling, ?DEFAULT_STAPLING_OPT, UserOpts, Opts) of + {old, StaplingMap} when is_map(StaplingMap) -> + {true, maps:get(ocsp_nonce, StaplingMap, ?DEFAULT_OCSP_NONCE_OPT)}; + {_, staple} -> + {true, ?DEFAULT_OCSP_NONCE_OPT}; + {_, no_staple} -> + {false, ignore}; + {_, Map} when is_map(Map) -> + {true, maps:get(ocsp_nonce, Map, ?DEFAULT_OCSP_NONCE_OPT)}; + {_, Value} -> + option_error(stapling, Value) end, - assert_client_only(Role, Stapling, ocsp_stapling), - {_, Nonce} = get_opt_bool(ocsp_nonce, ?DEFAULT_OCSP_NONCE, UserOpts, SMap), - option_incompatible(Stapling =:= false andalso Nonce =:= false, - [{ocsp_nonce, false}, {ocsp_stapling, false}]), - {_, ORC} = get_opt_list(ocsp_responder_certs, ?DEFAULT_OCSP_RESPONDER_CERTS, - UserOpts, SMap), - CheckBinary = fun(Cert) when is_binary(Cert) -> ok; - (_Cert) -> option_error(ocsp_responder_certs, ORC) - end, - [CheckBinary(C) || C <- ORC], - option_incompatible(Stapling =:= false andalso ORC =/= [], - [ocsp_responder_certs, {ocsp_stapling, false}]), case Stapling of true -> - Opts#{ocsp_stapling => - #{ocsp_nonce => Nonce, - ocsp_responder_certs => ORC}}; + Opts#{stapling => + #{ocsp_nonce => Nonce}}; false -> Opts - end. + end; +opt_stapling(UserOpts, Opts, #{role := server}) -> + assert_client_only(stapling, UserOpts), + Opts. opt_sni(UserOpts, #{versions := _Versions} = Opts, #{role := server}) -> {_, SniHosts} = get_opt_list(sni_hosts, [], UserOpts, Opts), @@ -2609,10 +2602,6 @@ assert_server_only(client, Bool, Option) -> role_error(Bool, server_only, Option); assert_server_only(_, _, _) -> ok. -assert_client_only(server, Bool, Option) -> - role_error(Bool, client_only, Option); -assert_client_only(_, _, _) -> - ok. role_error(false, _ErrorDesc, _Option) -> ok; @@ -3054,9 +3043,9 @@ unambiguous_path(Value) -> %%%# %%%# Tracing %%%# -handle_trace(csp, {call, {?MODULE, opt_ocsp, [UserOpts | _]}}, Stack) -> +handle_trace(csp, {call, {?MODULE, opt_stapling, [UserOpts | _]}}, Stack) -> {format_ocsp_params(UserOpts), Stack}; -handle_trace(csp, {return_from, {?MODULE, opt_ocsp, 3}, Return}, Stack) -> +handle_trace(csp, {return_from, {?MODULE, opt_stapling, 3}, Return}, Stack) -> {format_ocsp_params(Return), Stack}; handle_trace(rle, {call, {?MODULE, listen, Args}}, Stack0) -> Role = server, @@ -3066,8 +3055,6 @@ handle_trace(rle, {call, {?MODULE, connect, Args}}, Stack0) -> {io_lib:format("(*~w) Args = ~W", [Role, Args, 10]), [{role, Role} | Stack0]}. format_ocsp_params(Map) -> - Stapling = maps:get(ocsp_stapling, Map, '?'), + Stapling = maps:get(stapling, Map, '?'), Nonce = maps:get(ocsp_nonce, Map, '?'), - Certs = maps:get(ocsp_responder_certs, Map, '?'), - io_lib:format("Stapling = ~W Nonce = ~W Certs = ~W", - [Stapling, 5, Nonce, 5, Certs, 5]). + io_lib:format("Stapling = ~W Nonce = ~W", [Stapling, 5, Nonce, 5]). diff --git a/lib/ssl/src/ssl_alert.erl b/lib/ssl/src/ssl_alert.erl index e23db08ffbba..ee8cad8d02c6 100644 --- a/lib/ssl/src/ssl_alert.erl +++ b/lib/ssl/src/ssl_alert.erl @@ -27,7 +27,7 @@ %% %%---------------------------------------------------------------------- -module(ssl_alert). - +-feature(maybe_expr, enable). -include("ssl_alert.hrl"). -include("ssl_record.hrl"). -include("ssl_internal.hrl"). @@ -113,9 +113,20 @@ own_alert_format_depth(#alert{reason = Reason} = Alert) -> {" ~s\n ~P", [Txt, Reason, ?DEPTH]} end. -own_alert_txt(#alert{level = Level, description = Description, where = #{line := Line, file := Mod}, role = Role}) -> - "at " ++ Mod ++ ":" ++ integer_to_list(Line) ++ " generated " ++ string:uppercase(atom_to_list(Role)) ++ " ALERT: " ++ - level_txt(Level) ++ description_txt(Description). +own_alert_txt(#alert{level = Level, description = Description, + where = #{line := Line, file := Mod} = Where, + role = Role}) -> + DefaultLeft = "at " ++ Mod ++ ":" ++ integer_to_list(Line), + DefaultRight = " generated " ++ string:uppercase(atom_to_list(Role)) ++ " ALERT: " ++ + level_txt(Level) ++ description_txt(Description), + maybe + debug ?= get(log_level), + {current_stacktrace, Stacktrace} ?= maps:get(st, Where, undefined), + DefaultLeft ++ io_lib:format("~n~p~n", [Stacktrace]) ++ DefaultRight + else + _ -> + DefaultLeft ++ DefaultRight + end. alert_format(Alert) -> Txt = alert_txt(Alert), diff --git a/lib/ssl/src/ssl_certificate.erl b/lib/ssl/src/ssl_certificate.erl index 505eb10f79fa..e3114a3f24ef 100644 --- a/lib/ssl/src/ssl_certificate.erl +++ b/lib/ssl/src/ssl_certificate.erl @@ -78,7 +78,6 @@ select_extension/2, extensions_list/1, public_key_type/1, - foldl_db/3, find_cross_sign_root_paths/4, handle_cert_auths/4, available_cert_key_pairs/1, @@ -571,22 +570,45 @@ verify_hostname(Hostname, Customize, Cert, UserState) -> verify_cert_extensions(Cert, #{cert_ext := CertExts} = UserState) -> Id = public_key:pkix_subject_id(Cert), Extensions = maps:get(Id, CertExts, []), - verify_cert_extensions(Cert, UserState, Extensions, #{}). + verify_cert_extensions(Cert, UserState, Extensions, + #{certificate_valid => false}). +verify_cert_extensions(_Cert, _UserState = #{stapling_state := #{configured := true}, + path_len := 0}, [], + _Context = #{certificate_valid := false}) -> + {fail, missing_certificate_status}; verify_cert_extensions(Cert, UserState, [], _) -> {valid, UserState#{issuer => Cert}}; -verify_cert_extensions(Cert, #{ocsp_responder_certs := ResponderCerts, - ocsp_state := OscpState, - issuer := Issuer} = UserState, - [#certificate_status{response = OcspResponsDer} | Exts], +verify_cert_extensions(_, #{stapling_state := #{configured := false}}, + [#certificate_status{} | _], _) -> + {fail, unexpected_certificate_status}; +verify_cert_extensions(Cert, #{stapling_state := StaplingState, + issuer := Issuer, + certdb := CertDbHandle, + certdb_ref := CertDbRef} = UserState, + [#certificate_status{response = OcspResponseDer} | Exts], Context) -> - #{ocsp_nonce := Nonce} = OscpState, - case public_key:pkix_ocsp_validate(Cert, Issuer, OcspResponsDer, - ResponderCerts, Nonce) of - valid -> - verify_cert_extensions(Cert, UserState, Exts, Context); - {bad_cert, _} = Status -> - {fail, Status} + #{ocsp_nonce := Nonce} = StaplingState, + IsTrustedResponderFun = + fun(#cert{der = DerResponderCert, otp = OtpCert}) -> + OtpTbsCert = OtpCert#'OTPCertificate'.tbsCertificate, + #'OTPTBSCertificate'{ + issuer = IssuerId, serialNumber = SerialNr} = OtpTbsCert, + case ssl_manager:lookup_trusted_cert( + CertDbHandle, CertDbRef, SerialNr, IssuerId) of + {ok, #cert{der = DerResponderCert}} -> + true; + _ -> + false + end + end, + case public_key:pkix_ocsp_validate(Cert, Issuer, OcspResponseDer, Nonce, + [{is_trusted_responder_fun, IsTrustedResponderFun}]) of + ok -> + verify_cert_extensions(Cert, UserState, Exts, + Context#{certificate_valid => true}); + {error, {bad_cert, _} = Reason} -> + {fail, Reason} end; verify_cert_extensions(Cert, UserState, [_|Exts], Context) -> %% Skip unknown extensions! @@ -841,16 +863,15 @@ handle_trace(crt, {call, {?MODULE, verify_cert_extensions, %% {io_lib:format(" no more extensions (~s)", [ssl_test_lib:format_cert(Cert)]), Stack}; handle_trace(crt, {call, {?MODULE, verify_cert_extensions, [Cert, - #{ocsp_responder_certs := _ResponderCerts, - ocsp_state := OcspState, + #{stapling_state := StaplingState, issuer := Issuer} = _UserState, [#certificate_status{response = OcspResponsDer} | _Exts], _Context]}}, Stack) -> - {io_lib:format("#2 OcspState = ~W Issuer = [~W] OcspResponsDer = ~W [~W]", - [OcspState, 10, Issuer, 3, OcspResponsDer, 2, Cert, 3]), + {io_lib:format("#2 StaplingState = ~W Issuer = [~W] OcspResponsDer = ~W [~W]", + [StaplingState, 10, Issuer, 3, OcspResponsDer, 2, Cert, 3]), Stack}; - %% {io_lib:format("#2 OcspState = ~W Issuer = (~s) OcspResponsDer = ~W (~s)", - %% [OcspState, 10, ssl_test_lib:format_cert(Issuer), + %% {io_lib:format("#2 StaplingState = ~W Issuer = (~s) OcspResponsDer = ~W (~s)", + %% [StaplingState, 10, ssl_test_lib:format_cert(Issuer), %% OcspResponsDer, 2, ssl_test_lib:format_cert(Cert)]), handle_trace(crt, {return_from, {ssl_certificate, verify_cert_extensions, 4}, diff --git a/lib/ssl/src/ssl_connection.hrl b/lib/ssl/src/ssl_connection.hrl index 1b8efa0710e2..37006e053528 100644 --- a/lib/ssl/src/ssl_connection.hrl +++ b/lib/ssl/src/ssl_connection.hrl @@ -88,8 +88,8 @@ server_psk_identity :: binary() | 'undefined', % server psk identity hint cookie_iv_shard :: {binary(), binary()} %% IV, Shard | 'undefined', - ocsp_stapling_state = #{ocsp_stapling => false, - ocsp_expect => no_staple} + stapling_state = #{configured => false, + status => not_negotiated} }). -record(connection_env, { diff --git a/lib/ssl/src/ssl_gen_statem.erl b/lib/ssl/src/ssl_gen_statem.erl index 8e90c0a23e29..1d349061984e 100644 --- a/lib/ssl/src/ssl_gen_statem.erl +++ b/lib/ssl/src/ssl_gen_statem.erl @@ -523,7 +523,7 @@ initial_hello({call, From}, {start, Timeout}, cert_db_ref = CertDbRef, protocol_cb = Connection}, handshake_env = #handshake_env{renegotiation = {Renegotiation, _}, - ocsp_stapling_state = OcspState0}, + stapling_state = StaplingState0}, connection_env = CEnv, ssl_options = #{%% Use highest version in initial ClientHello. %% Versions is a descending list of supported versions. @@ -582,16 +582,16 @@ initial_hello({call, From}, {start, Timeout}, {#state{handshake_env = HsEnv1} = State5, _} = Connection:send_handshake_flight(State4), - OcspStaplingKeyPresent = maps:is_key(ocsp_stapling, SslOpts), + StaplingKeyPresent = maps:is_key(stapling, SslOpts), State = State5#state{ connection_env = CEnv#connection_env{ negotiated_version = RequestedVersion}, session = Session, handshake_env = HsEnv1#handshake_env{ - ocsp_stapling_state = - OcspState0#{ocsp_nonce => OcspNonce, - ocsp_stapling => OcspStaplingKeyPresent}}, + stapling_state = + StaplingState0#{ocsp_nonce => OcspNonce, + configured => StaplingKeyPresent}}, start_or_recv_from = From, key_share = KeyShare}, NextState = next_statem_state(Versions, Role), diff --git a/lib/ssl/src/ssl_handshake.erl b/lib/ssl/src/ssl_handshake.erl index 4da3a8fa5c5b..8a0c0b6a7996 100644 --- a/lib/ssl/src/ssl_handshake.erl +++ b/lib/ssl/src/ssl_handshake.erl @@ -337,7 +337,7 @@ next_protocol(SelectedProtocol) -> %%-------------------------------------------------------------------- certify(#certificate{asn1_certificates = ASN1Certs}, CertDbHandle, CertDbRef, #{partial_chain := PartialChain} = SSlOptions, - CRLDbHandle, Role, Host, Version, CertExt) -> + CRLDbHandle, Role, Host, Version, ExtInfo) -> ServerName = server_name(SSlOptions, Host, Role), [PeerCert | _ChainCerts ] = ASN1Certs, try @@ -346,7 +346,7 @@ certify(#certificate{asn1_certificates = ASN1Certs}, CertDbHandle, CertDbRef, PartialChain), case path_validate(PathsAndAnchors, ServerName, Role, CertDbHandle, CertDbRef, CRLDbHandle, - Version, SSlOptions, CertExt) of + Version, SSlOptions, ExtInfo) of {ok, {PublicKeyInfo, _}} -> {PeerCert, PublicKeyInfo}; {error, Reason} -> @@ -1293,13 +1293,10 @@ maybe_add_tls13_extensions(?TLS_1_3, maybe_add_tls13_extensions(_, HelloExtensions, _, _, _, _,_) -> HelloExtensions. -maybe_add_certificate_status_request(_Version, #{ocsp_stapling := OcspStapling}, +maybe_add_certificate_status_request(_Version, #{stapling := _Stapling}, OcspNonce, HelloExtensions) -> - OcspResponderCerts = maps:get(ocsp_responder_certs, OcspStapling), - OcspResponderList = get_ocsp_responder_list(OcspResponderCerts), OcspRequestExtns = public_key:ocsp_extensions(OcspNonce), - Req = #ocsp_status_request{responder_id_list = OcspResponderList, - request_extensions = OcspRequestExtns}, + Req = #ocsp_status_request{request_extensions = OcspRequestExtns}, CertStatusReqExtn = #certificate_status_request{ status_type = ?CERTIFICATE_STATUS_TYPE_OCSP, request = Req @@ -1309,9 +1306,6 @@ maybe_add_certificate_status_request(_Version, _SslOpts, _OcspNonce, HelloExtensions) -> HelloExtensions. -get_ocsp_responder_list(ResponderCerts) -> - lists:map(fun public_key:ocsp_responder_id/1, ResponderCerts). - %% TODO: Add support for PSK key establishment %% RFC 8446 (TLS 1.3) - 4.2.8. Key Share @@ -1523,10 +1517,10 @@ handle_server_hello_extensions(RecordCB, Random, CipherSuite, ok end, - case handle_ocsp_extension(SslOpts, Exts) of + case handle_cert_status_extension(SslOpts, Exts) of #alert{} = Alert -> Alert; - OcspState -> + StaplingState -> %% If we receive an ALPN extension then this is the protocol selected, %% otherwise handle the NPN extension. ALPN = maps:get(alpn, Exts, undefined), @@ -1534,14 +1528,14 @@ handle_server_hello_extensions(RecordCB, Random, CipherSuite, %% ServerHello contains exactly one protocol: the one selected. %% We also ignore the ALPN extension during renegotiation (see encode_alpn/2). [Protocol] when not Renegotiation -> - {ConnectionStates, alpn, Protocol, OcspState}; + {ConnectionStates, alpn, Protocol, StaplingState}; [_] when Renegotiation -> - {ConnectionStates, alpn, undefined, OcspState}; + {ConnectionStates, alpn, undefined, StaplingState}; undefined -> NextProtocolNegotiation = maps:get(next_protocol_negotiation, Exts, undefined), NextProtocolSelector = maps:get(next_protocol_selector, SslOpts, undefined), Protocol = handle_next_protocol(NextProtocolNegotiation, NextProtocolSelector, Renegotiation), - {ConnectionStates, npn, Protocol, OcspState}; + {ConnectionStates, npn, Protocol, StaplingState}; {error, Reason} -> ?ALERT_REC(?FATAL, ?HANDSHAKE_FAILURE, Reason); [] -> @@ -1947,22 +1941,22 @@ extension_value(#psk_key_exchange_modes{ke_modes = Modes}) -> extension_value(#cookie{cookie = Cookie}) -> Cookie. -handle_ocsp_extension(#{ocsp_stapling := _OcspStapling}, Extensions) -> +handle_cert_status_extension(#{stapling := _Stapling}, Extensions) -> case maps:get(status_request, Extensions, false) of - undefined -> %% status_request in server hello is empty - #{ocsp_stapling => true, - ocsp_expect => staple}; - false -> %% status_request is missing (not negotiated) - #{ocsp_stapling => true, - ocsp_expect => no_staple}; + undefined -> %% status_request received in server hello + #{configured => true, + status => negotiated}; + false -> + #{configured => true, + status => not_negotiated}; _Else -> ?ALERT_REC(?FATAL, ?HANDSHAKE_FAILURE, status_request_not_empty) end; -handle_ocsp_extension(_SslOpts, Extensions) -> +handle_cert_status_extension(_SslOpts, Extensions) -> case maps:get(status_request, Extensions, false) of - false -> %% status_request is missing (not negotiated) - #{ocsp_stapling => false, - ocsp_expect => no_staple}; + false -> + #{configured => false, + status => not_negotiated}; _Else -> %% unsolicited status_request ?ALERT_REC(?FATAL, ?HANDSHAKE_FAILURE, unexpected_status_request) end. @@ -2010,11 +2004,11 @@ certificate_authorities_from_db(_CertDbHandle, {extracted, CertDbData}) -> %%-------------Handle handshake messages -------------------------------- path_validate(TrustedAndPath, ServerName, Role, CertDbHandle, CertDbRef, CRLDbHandle, - Version, SslOptions, CertExt) -> + Version, SslOptions, ExtInfo) -> InitialPotentialError = {error, {bad_cert, unknown_ca}}, InitialInvalidated = [], path_validate(TrustedAndPath, ServerName, Role, CertDbHandle, CertDbRef, CRLDbHandle, - Version, SslOptions, CertExt, InitialInvalidated, InitialPotentialError). + Version, SslOptions, ExtInfo, InitialInvalidated, InitialPotentialError). validation_fun_and_state({Fun, UserState0}, VerifyState, CertPath, LogLevel) -> {fun(OtpCert, {extension, _} = Extension, {SslState, UserState}) -> @@ -2199,25 +2193,21 @@ bad_key(#{algorithm := ecdsa}) -> unacceptable_ecdsa_key. cert_status_check(_, - #{ocsp_state := #{ocsp_stapling := true, - ocsp_expect := stapled}}, + #{stapling_state := #{configured := true, + status := received_staple}}, _VerifyResult, _, _) -> - %% OCSP staple will now be checked by + %% OCSP staple(s) will now be checked by %% ssl_certificate:verify_cert_extensions/2 in ssl_certificate:validate valid; cert_status_check(OtpCert, - #{ocsp_state := #{ocsp_stapling := false}} = SslState, + #{stapling_state := #{configured := false}} = SslState, VerifyResult, CertPath, LogLevel) -> maybe_check_crl(OtpCert, SslState, VerifyResult, CertPath, LogLevel); cert_status_check(_OtpCert, - #{ocsp_state := #{ocsp_stapling := true, - ocsp_expect := undetermined}}, - _VerifyResult, _CertPath, _LogLevel) -> - {bad_cert, {revocation_status_undetermined, not_stapled}}; -cert_status_check(_OtpCert, - #{ocsp_state := #{ocsp_stapling := true, - ocsp_expect := no_staple}}, - _VerifyResult, _CertPath, _LogLevel) -> + #{stapling_state := #{configured := true, + status := StaplingStatus}}, + _VerifyResult, _CertPath, _LogLevel) + when StaplingStatus == not_negotiated; StaplingStatus == not_received -> {bad_cert, {revocation_status_undetermined, not_stapled}}. maybe_check_crl(_, #{crl_check := false}, _, _, _) -> @@ -3799,23 +3789,28 @@ path_validate([], _, _, _, _, _, _, _, _, _, {error, {bad_cert, root_cert_expire path_validate([], _, _, _, _, _, _, _, _, _, Error) -> Error; path_validate([{TrustedCert, Path} | Rest], ServerName, Role, CertDbHandle, CertDbRef, CRLDbHandle, - Version, SslOptions, CertExt, InvalidatedList, Error) -> + Version, SslOptions, ExtInfo, InvalidatedList, Error) -> CB = path_validation_cb(Version), case CB:path_validation(trusted_unwrap(TrustedCert), Path, ServerName, Role, CertDbHandle, CertDbRef, CRLDbHandle, - Version, SslOptions, CertExt) of + Version, SslOptions, ExtInfo) of {error, {bad_cert, root_cert_expired}} = NewError -> NewInvalidatedList = [TrustedCert | InvalidatedList], - Alt = ssl_certificate:find_cross_sign_root_paths(Path, CertDbHandle, CertDbRef, NewInvalidatedList), - path_validate(Alt ++ Rest, ServerName, Role, CertDbHandle, CertDbRef, CRLDbHandle, - Version, SslOptions, CertExt, NewInvalidatedList, NewError); + Alt = ssl_certificate:find_cross_sign_root_paths( + Path, CertDbHandle,CertDbRef, NewInvalidatedList), + path_validate(Alt ++ Rest, ServerName, Role, CertDbHandle, + CertDbRef, CRLDbHandle, Version, SslOptions, + ExtInfo, NewInvalidatedList, NewError); {error, {bad_cert, unknown_ca}} = NewError -> - Alt = ssl_certificate:find_cross_sign_root_paths(Path, CertDbHandle, CertDbRef, InvalidatedList), - path_validate(Alt ++ Rest, ServerName, Role, CertDbHandle, CertDbRef, CRLDbHandle, - Version, SslOptions, CertExt, InvalidatedList, error_to_propagate(Error, NewError)); + Alt = ssl_certificate:find_cross_sign_root_paths( + Path, CertDbHandle, CertDbRef, InvalidatedList), + path_validate(Alt ++ Rest, ServerName, Role, CertDbHandle, + CertDbRef, CRLDbHandle, Version, SslOptions, + ExtInfo, InvalidatedList, + error_to_propagate(Error, NewError)); {error, _} when Rest =/= []-> path_validate(Rest, ServerName, Role, CertDbHandle, CertDbRef, CRLDbHandle, - Version, SslOptions, CertExt, InvalidatedList, Error); + Version, SslOptions, ExtInfo, InvalidatedList, Error); Result -> Result end. @@ -3834,11 +3829,10 @@ path_validation(TrustedCert, Path, ServerName, Role, CertDbHandle, CertDbRef, CR crl_check := CrlCheck, log_level := Level} = Opts, #{cert_ext := CertExt, - ocsp_responder_certs := OcspResponderCerts, - ocsp_state := OcspState}) -> + stapling_state := StaplingState}) -> SignAlgos = maps:get(signature_algs, Opts, undefined), SignAlgosCert = maps:get(signature_algs_cert, Opts, undefined), - ValidationFunAndState = + ValidationFunAndState = validation_fun_and_state(VerifyFun, #{role => Role, certdb => CertDbHandle, certdb_ref => CertDbRef, @@ -3852,8 +3846,7 @@ path_validation(TrustedCert, Path, ServerName, Role, CertDbHandle, CertDbRef, CR crl_db => CRLDbHandle, cert_ext => CertExt, issuer => TrustedCert, - ocsp_responder_certs => OcspResponderCerts, - ocsp_state => OcspState, + stapling_state => StaplingState, path_len => length(Path) }, Path, Level), @@ -3880,6 +3873,6 @@ handle_trace(csp, [_Version, SslOpts, _OcspNonce, _HelloExtensions]}}, Stack) -> - OcspStapling = maps:get(ocsp_stapling, SslOpts, false), - {io_lib:format("#1 ADD crt status request / OcspStapling option = ~W", - [OcspStapling, 10]), Stack}. + Stapling = maps:get(stapling, SslOpts, false), + {io_lib:format("#1 ADD crt status request / Stapling option = ~W", + [Stapling, 10]), Stack}. diff --git a/lib/ssl/src/ssl_internal.hrl b/lib/ssl/src/ssl_internal.hrl index cbe497616aa4..091dee3583c1 100644 --- a/lib/ssl/src/ssl_internal.hrl +++ b/lib/ssl/src/ssl_internal.hrl @@ -204,7 +204,6 @@ }). -define(DEFAULT_DEPTH, 10). --define(DEFAULT_OCSP_STAPLING, false). --define(DEFAULT_OCSP_NONCE, true). --define(DEFAULT_OCSP_RESPONDER_CERTS, []). +-define(DEFAULT_STAPLING_OPT, no_staple). +-define(DEFAULT_OCSP_NONCE_OPT, true). -endif. % -ifdef(ssl_internal). diff --git a/lib/ssl/src/ssl_trace.erl b/lib/ssl/src/ssl_trace.erl index 70ac33004c19..068b0c215a06 100644 --- a/lib/ssl/src/ssl_trace.erl +++ b/lib/ssl/src/ssl_trace.erl @@ -430,25 +430,28 @@ trace_profiles() -> fun(M, F, A) -> dbg:ctpl(M, F, A) end, [{ssl_handshake, [{maybe_add_certificate_status_request, 4}, {client_hello_extensions, 10}, {cert_status_check, 5}, - {get_ocsp_responder_list, 1}, {handle_ocsp_extension, 2}, + {handle_cert_status_extension, 2}, {path_validation, 10}, {handle_server_hello_extensions, 9}, {handle_client_hello_extensions, 10}, {cert_status_check, 5}]}, {public_key, [{ocsp_extensions, 1}, {pkix_ocsp_validate, 5}, - {ocsp_responder_id, 1}, {otp_cert, 1}]}, - {pubkey_ocsp, [{find_responder_cert, 2}, {do_verify_ocsp_signature, 4}, - {verify_ocsp_response, 3}, {verify_ocsp_nonce, 2}, - {verify_ocsp_signature, 5}, {do_verify_ocsp_response, 3}, - {is_responder, 2}, {find_single_response, 3}, - {ocsp_status, 1}, {match_single_response, 4}]}, - {ssl, [{opt_ocsp, 3}]}, + {otp_cert, 1}]}, + {pubkey_ocsp, [{do_verify_signature, 4}, + {verify_response, 5}, {verify_nonce, 2}, + {verify_signature, 7}, + {is_responder_cert, 2}, {find_single_response, 3}, + {status, 1}, {match_single_response, 4}, + {designated_for_ocsp_signing, 1}]}, + {ssl, [{opt_stapling, 3}]}, {ssl_certificate, [{verify_cert_extensions, 4}]}, {ssl_test_lib, [{init_openssl_server, 3}, {openssl_server_loop, 3}]}, - {tls_connection, [{wait_ocsp_stapling, 3}]}, + {tls_connection, [{wait_stapling, 3}]}, {dtls_connection, [{initial_hello, 3}, {hello, 3}, {connection, 3}]}, - {tls_dtls_connection, [{wait_ocsp_stapling, 3}, {certify, 3}]}, - {tls_handshake, [{ocsp_nonce, 1}, {ocsp_expect, 1}, {client_hello, 11}]}, + {tls_dtls_connection, [{wait_stapling, 3}, {certify, 3}]}, + {tls_handshake, [{ocsp_nonce, 1}, {client_hello, 11}]}, + {tls_handshake_1_3, [{validate_certificate_chain, 8}, + {process_certificate, 2}]}, {dtls_handshake, [{client_hello, 8}]}]}, {crt, %% certificates fun(M, F, A) -> dbg:tpl(M, F, A, x) end, diff --git a/lib/ssl/src/tls_client_connection_1_3.erl b/lib/ssl/src/tls_client_connection_1_3.erl index b4da35919699..552ca2d2e895 100644 --- a/lib/ssl/src/tls_client_connection_1_3.erl +++ b/lib/ssl/src/tls_client_connection_1_3.erl @@ -521,7 +521,7 @@ do_handle_exlusive_1_3_hello_or_hello_retry_request( transport_cb = Transport, socket = Socket}, handshake_env = #handshake_env{renegotiation = {Renegotiation, _}, - ocsp_stapling_state = OcspState}, + stapling_state = StaplingState}, connection_env = #connection_env{negotiated_version = NegotiatedVersion}, protocol_specific = PS, @@ -565,7 +565,7 @@ do_handle_exlusive_1_3_hello_or_hello_retry_request( ClientKeyShare = ssl_cipher:generate_client_shares([SelectedGroup]), TicketData = tls_handshake_1_3:get_ticket_data(self(), SessionTickets, UseTicket), - OcspNonce = maps:get(ocsp_nonce, OcspState, undefined), + OcspNonce = maps:get(ocsp_nonce, StaplingState, undefined), Hello0 = tls_handshake:client_hello(Host, Port, ConnectionStates0, SslOpts, SessionId, Renegotiation, diff --git a/lib/ssl/src/tls_connection.erl b/lib/ssl/src/tls_connection.erl index 83ebdbd167cc..44d84439d22c 100644 --- a/lib/ssl/src/tls_connection.erl +++ b/lib/ssl/src/tls_connection.erl @@ -71,8 +71,8 @@ %% | Send/Recv Flight 2 or Abbrev Flight 1 - Abbrev Flight 2 part 1 %% | %% New session | Resumed session -%% WAIT_OCSP_STAPLING CERTIFY <----------------------------------> ABBREVIATED -%% WAIT_CERT_VERIFY +%% WAIT_STAPLING CERTIFY <----------------------------------> ABBREVIATED +%% WAIT_CERT_VERIFY %% <- Possibly Receive -- | | %% OCSP Staple/CertVerify -> | Flight 3 part 1 | %% | | @@ -123,7 +123,7 @@ downgrade/3, hello/3, user_hello/3, - wait_ocsp_stapling/3, + wait_stapling/3, certify/3, wait_cert_verify/3, cipher/3, @@ -248,27 +248,27 @@ hello(internal, #server_hello{} = Hello, connection_env = CEnv, static_env = #static_env{role = client}, handshake_env = #handshake_env{ - ocsp_stapling_state = OcspState0, + stapling_state = StaplingState0, renegotiation = {Renegotiation, _}} = HsEnv, session = #session{session_id = OldId}, ssl_options = SslOptions} = State) -> try case tls_handshake:hello(Hello, SslOptions, ConnectionStates0, Renegotiation, OldId) of %% Legacy TLS 1.2 and older - {Version, NewId, ConnectionStates, ProtoExt, Protocol, OcspState} -> + {Version, NewId, ConnectionStates, ProtoExt, Protocol, StaplingState} -> tls_dtls_connection:handle_session( Hello, Version, NewId, ConnectionStates, ProtoExt, Protocol, State#state{ handshake_env = HsEnv#handshake_env{ - ocsp_stapling_state = maps:merge(OcspState0,OcspState)}}); + stapling_state = maps:merge(StaplingState0,StaplingState)}}); %% TLS 1.3 - {next_state, wait_sh, SelectedVersion, OcspState} -> + {next_state, wait_sh, SelectedVersion, StaplingState} -> %% Continue in TLS 1.3 'wait_sh' state {next_state, wait_sh, State#state{handshake_env = - HsEnv#handshake_env{ocsp_stapling_state = - maps:merge(OcspState0, OcspState)}, + HsEnv#handshake_env{stapling_state = + maps:merge(StaplingState0, StaplingState)}, connection_env = CEnv#connection_env{negotiated_version = SelectedVersion}}, [{change_callback_module, tls_client_connection_1_3}, @@ -304,12 +304,12 @@ abbreviated(Type, Event, State) -> end. %%-------------------------------------------------------------------- --spec wait_ocsp_stapling(gen_statem:event_type(), term(), #state{}) -> - gen_statem:state_function_result(). +-spec wait_stapling(gen_statem:event_type(), term(), #state{}) -> + gen_statem:state_function_result(). %%-------------------------------------------------------------------- -wait_ocsp_stapling(info, Event, State) -> +wait_stapling(info, Event, State) -> gen_info(Event, ?FUNCTION_NAME, State); -wait_ocsp_stapling(Type, Event, State) -> +wait_stapling(Type, Event, State) -> try tls_dtls_connection:gen_handshake(?FUNCTION_NAME, Type, Event, State) catch throw:#alert{} = Alert -> ssl_gen_statem:handle_own_alert(Alert, ?FUNCTION_NAME, State) @@ -373,7 +373,7 @@ connection(internal, #hello_request{}, session_cache_cb = CacheCb}, handshake_env = #handshake_env{ renegotiation = {Renegotiation, peer}, - ocsp_stapling_state = OcspState}, + stapling_state = StaplingState}, connection_env = #connection_env{cert_key_alts = CertKeyAlts}, session = Session0, ssl_options = SslOpts, @@ -386,7 +386,7 @@ connection(internal, #hello_request{}, Hello = tls_handshake:client_hello(Host, Port, ConnectionStates, SslOpts, Session#session.session_id, Renegotiation, undefined, - undefined, maps:get(ocsp_nonce, OcspState, undefined), + undefined, maps:get(ocsp_nonce, StaplingState, undefined), CertDbHandle, CertDbRef), {State, Actions} = tls_gen_connection:send_handshake(Hello, State0#state{connection_states = @@ -407,12 +407,12 @@ connection(internal, #hello_request{}, }, handshake_env = #handshake_env{ renegotiation = {Renegotiation, _}, - ocsp_stapling_state = OcspState}, + stapling_state = StaplingState}, ssl_options = SslOpts, connection_states = ConnectionStates} = State0) -> Hello = tls_handshake:client_hello(Host, Port, ConnectionStates, SslOpts, <<>>, Renegotiation, undefined, - undefined, maps:get(ocsp_nonce, OcspState, undefined), + undefined, maps:get(ocsp_nonce, StaplingState, undefined), CertDbHandle, CertDbRef), {State, Actions} = tls_gen_connection:send_handshake(Hello, State0), @@ -610,6 +610,6 @@ choose_tls_fsm(_, _) -> %%%# Tracing %%%# handle_trace(csp, - {call, {?MODULE, wait_ocsp_stapling, + {call, {?MODULE, wait_stapling, [Type, Event|_]}}, Stack) -> {io_lib:format("Type = ~w Event = ~W", [Type, Event, 10]), Stack}. diff --git a/lib/ssl/src/tls_dtls_connection.erl b/lib/ssl/src/tls_dtls_connection.erl index e0869ee7f586..4810d09c6f93 100644 --- a/lib/ssl/src/tls_dtls_connection.erl +++ b/lib/ssl/src/tls_dtls_connection.erl @@ -58,7 +58,7 @@ abbreviated/3, certify/3, wait_cert_verify/3, - wait_ocsp_stapling/3, + wait_stapling/3, cipher/3, connection/3, downgrade/3, @@ -261,30 +261,31 @@ abbreviated(Type, Event, State) -> ssl_gen_statem:handle_common_event(Type, Event, ?FUNCTION_NAME, State). %%-------------------------------------------------------------------- --spec wait_ocsp_stapling(gen_statem:event_type(), - #certificate{} | #certificate_status{} | term(), - #state{}) -> - gen_statem:state_function_result(). +-spec wait_stapling(gen_statem:event_type(), + #certificate{} | #certificate_status{} | term(), + #state{}) -> + gen_statem:state_function_result(). %%-------------------------------------------------------------------- -wait_ocsp_stapling(internal, #certificate{}, +wait_stapling(internal, #certificate{}, #state{static_env = #static_env{protocol_cb = _Connection}} = State) -> %% Postpone message, should be handled in certify after receiving staple message {next_state, ?FUNCTION_NAME, State, [{postpone, true}]}; %% Receive OCSP staple message -wait_ocsp_stapling(internal, #certificate_status{} = CertStatus, +wait_stapling(internal, #certificate_status{} = CertStatus, #state{static_env = #static_env{protocol_cb = _Connection}, handshake_env = - #handshake_env{ocsp_stapling_state = OcspState} = HsEnv} = State) -> + #handshake_env{stapling_state = StaplingState} = HsEnv} = State) -> {next_state, certify, State#state{handshake_env = - HsEnv#handshake_env{ocsp_stapling_state = - OcspState#{ocsp_expect => stapled, - ocsp_response => CertStatus}}}}; + HsEnv#handshake_env{ + stapling_state = + StaplingState#{status => received_staple, + staple => CertStatus}}}}; %% Server did not send OCSP staple message -wait_ocsp_stapling(internal, Msg, +wait_stapling(internal, Msg, #state{static_env = #static_env{protocol_cb = _Connection}, handshake_env = #handshake_env{ - ocsp_stapling_state = OcspState} = HsEnv} = State) + stapling_state = StaplingState} = HsEnv} = State) when is_record(Msg, server_key_exchange) orelse is_record(Msg, hello_request) orelse is_record(Msg, certificate_request) orelse @@ -292,12 +293,12 @@ wait_ocsp_stapling(internal, Msg, is_record(Msg, client_key_exchange) -> {next_state, certify, State#state{handshake_env = - HsEnv#handshake_env{ocsp_stapling_state = - OcspState#{ocsp_expect => undetermined}}}, + HsEnv#handshake_env{stapling_state = + StaplingState#{status => not_received}}}, [{postpone, true}]}; -wait_ocsp_stapling(internal, #hello_request{}, _) -> +wait_stapling(internal, #hello_request{}, _) -> keep_state_and_data; -wait_ocsp_stapling(Type, Event, State) -> +wait_stapling(Type, Event, State) -> ssl_gen_statem:handle_common_event(Type, Event, ?FUNCTION_NAME, State). %%-------------------------------------------------------------------- @@ -329,8 +330,8 @@ certify(internal, #certificate{}, certify(internal, #certificate{}, #state{static_env = #static_env{protocol_cb = Connection}, handshake_env = #handshake_env{ - ocsp_stapling_state = #{ocsp_expect := staple}}} = State) -> - Connection:next_event(wait_ocsp_stapling, no_record, State, [{postpone, true}]); + stapling_state = #{status := negotiated}}} = State) -> + Connection:next_event(wait_stapling, no_record, State, [{postpone, true}]); certify(internal, #certificate{asn1_certificates = [Peer|_]} = Cert, #state{static_env = #static_env{ role = Role, @@ -340,14 +341,18 @@ certify(internal, #certificate{asn1_certificates = [Peer|_]} = Cert, cert_db_ref = CertDbRef, crl_db = CRLDbInfo}, handshake_env = #handshake_env{ - ocsp_stapling_state = #{ocsp_expect := Status} = OcspState}, + stapling_state = #{status := StaplingStatus} = + StaplingState}, connection_env = #connection_env{ negotiated_version = Version}, - ssl_options = Opts} = State0) when Status =/= staple -> - OcspInfo = ocsp_info(OcspState, Opts, Peer), + ssl_options = Opts} = State0) + when StaplingStatus == not_negotiated; StaplingStatus == received_staple -> + %% this clause handles also scenario with stapling disabled, so + %% 'not_negotiated' appears in guard + ExtInfo = ext_info(StaplingState, Peer), case ssl_handshake:certify(Cert, CertDbHandle, CertDbRef, Opts, CRLDbInfo, Role, Host, - ensure_tls(Version), OcspInfo) of + ensure_tls(Version), ExtInfo) of {PeerCert, PublicKeyInfo} -> State = case Role of server -> @@ -1667,16 +1672,13 @@ ensure_tls(Version) when ?DTLS_1_X(Version) -> ensure_tls(Version) -> Version. -ocsp_info(#{ocsp_expect := stapled, ocsp_response := CertStatus} = OcspState, - #{ocsp_stapling := OcspStapling} = _SslOpts, PeerCert) -> - #{ocsp_responder_certs := OcspResponderCerts} = OcspStapling, +ext_info(#{status := received_staple, staple := CertStatus} = StaplingState, + PeerCert) -> #{cert_ext => #{public_key:pkix_subject_id(PeerCert) => [CertStatus]}, - ocsp_responder_certs => OcspResponderCerts, - ocsp_state => OcspState}; -ocsp_info(#{ocsp_expect := no_staple} = OcspState, _, PeerCert) -> + stapling_state => StaplingState}; +ext_info(#{status := not_negotiated} = StaplingState, PeerCert) -> #{cert_ext => #{public_key:pkix_subject_id(PeerCert) => []}, - ocsp_responder_certs => [], - ocsp_state => OcspState}. + stapling_state => StaplingState}. select_client_cert_key_pair(Session0,_, [#{private_key := NoKey, certs := [[]] = NoCerts}], @@ -1727,5 +1729,5 @@ default_cert_key_pair_return(Default, _) -> %%%# Tracing %%%# handle_trace(csp, - {call, {?MODULE, wait_ocsp_stapling, [Type, Msg | _]}}, Stack) -> + {call, {?MODULE, wait_stapling, [Type, Msg | _]}}, Stack) -> {io_lib:format("Type = ~w Msg = ~W", [Type, Msg, 10]), Stack}. diff --git a/lib/ssl/src/tls_gen_connection.erl b/lib/ssl/src/tls_gen_connection.erl index 7a64bc7db3f9..95d4f7687830 100644 --- a/lib/ssl/src/tls_gen_connection.erl +++ b/lib/ssl/src/tls_gen_connection.erl @@ -399,7 +399,7 @@ handle_protocol_record(#ssl_tls{type = ?APPLICATION_DATA}, StateName, StateName == hello; StateName == certify; StateName == wait_cert_verify; - StateName == wait_ocsp_stapling; + StateName == wait_stapling; StateName == abbreviated; StateName == cipher -> diff --git a/lib/ssl/src/tls_gen_connection_1_3.erl b/lib/ssl/src/tls_gen_connection_1_3.erl index 22df97f066cd..c92a35a5aa0a 100644 --- a/lib/ssl/src/tls_gen_connection_1_3.erl +++ b/lib/ssl/src/tls_gen_connection_1_3.erl @@ -54,6 +54,7 @@ initial_state(Role, Sender, Host, Port, Socket, {SSLOptions, SocketOptions, Trackers}, User, {CbModule, DataTag, CloseTag, ErrorTag, PassiveTag}) -> + put(log_level, maps:get(log_level, SSLOptions)), %% Use highest supported version for client/server random nonce generation #{versions := [Version|_]} = SSLOptions, MaxEarlyDataSize = init_max_early_data_size(Role), diff --git a/lib/ssl/src/tls_handshake.erl b/lib/ssl/src/tls_handshake.erl index 76337e3e264f..397ce18c36c5 100644 --- a/lib/ssl/src/tls_handshake.erl +++ b/lib/ssl/src/tls_handshake.erl @@ -161,7 +161,6 @@ hello(#server_hello{server_version = LegacyVersion, selected_version = Version}} = HelloExt}, #{versions := SupportedVersions} = SslOpt, ConnectionStates0, Renegotiation, OldId) -> - Stapling = maps:get(ocsp_stapling, SslOpt, ?DEFAULT_OCSP_STAPLING), %% In TLS 1.3, the TLS server indicates its version using the "supported_versions" extension %% (Section 4.2.1), and the legacy_version field MUST be set to 0x0303, which is the version %% number for TLS 1.2. @@ -181,10 +180,12 @@ hello(#server_hello{server_version = LegacyVersion, HelloExt, SslOpt, ConnectionStates0, Renegotiation, IsNew); SelectedVersion -> - %% TLS 1.3 + %% TLS 1.3 status_request and OCSP + %% responses provided in Certificate + %% messages {next_state, wait_sh, SelectedVersion, - #{ocsp_stapling => Stapling, - ocsp_expect => ocsp_expect(Stapling)}} + #{configured => maps:is_key(stapling, SslOpt), + status => not_negotiated}} end; false -> throw(?ALERT_REC(?FATAL, ?ILLEGAL_PARAMETER)) @@ -310,7 +311,7 @@ get_tls_handshakes(Version, Data, Buffer, Options) -> %% Description: Get an OCSP nonce %%-------------------------------------------------------------------- ocsp_nonce(SslOpts) -> - case maps:get(ocsp_stapling, SslOpts, disabled) of + case maps:get(stapling, SslOpts, disabled) of #{ocsp_nonce := true} -> public_key:der_encode('Nonce', crypto:strong_rand_bytes(8)); _ -> @@ -386,12 +387,12 @@ handle_client_hello_extensions(Version, Type, Random, CipherSuites, handle_server_hello_extensions(Version, SessionId, Random, CipherSuite, HelloExt, SslOpt, ConnectionStates0, Renegotiation, IsNew) -> - {ConnectionStates, ProtoExt, Protocol, OcspState} = + {ConnectionStates, ProtoExt, Protocol, StaplingState} = ssl_handshake:handle_server_hello_extensions(tls_record, Random, CipherSuite, HelloExt, Version, SslOpt, ConnectionStates0, Renegotiation, IsNew), - {Version, SessionId, ConnectionStates, ProtoExt, Protocol, OcspState}. + {Version, SessionId, ConnectionStates, ProtoExt, Protocol, StaplingState}. do_hello(undefined, _Versions, _CipherSuites, _Hello, _SslOpts, _Info, _Renegotiation) -> throw(?ALERT_REC(?FATAL, ?PROTOCOL_VERSION)); @@ -475,12 +476,6 @@ decode_handshake(?TLS_1_3, Tag, Msg) -> decode_handshake(Version, Tag, Msg) -> ssl_handshake:decode_handshake(Version, Tag, Msg). - -ocsp_expect(true) -> - staple; -ocsp_expect(_) -> - no_staple. - get_signature_ext(Ext, HelloExt, ?TLS_1_2) -> case maps:get(Ext, HelloExt, undefined) of %% Signature algorithms was not sent diff --git a/lib/ssl/src/tls_handshake_1_3.erl b/lib/ssl/src/tls_handshake_1_3.erl index 3eb692d5076c..ec98148e0e62 100644 --- a/lib/ssl/src/tls_handshake_1_3.erl +++ b/lib/ssl/src/tls_handshake_1_3.erl @@ -450,9 +450,10 @@ process_certificate(#certificate_1_3{certificate_list = CertEntries}, crl_db = CRLDbHandle}, handshake_env = #handshake_env{ - ocsp_stapling_state = OcspState}} = State0) -> - case validate_certificate_chain(CertEntries, CertDbHandle, CertDbRef, - SslOptions, CRLDbHandle, Role, Host, OcspState) of + stapling_state = StaplingState}} = State0) -> + case validate_certificate_chain( + CertEntries, CertDbHandle, CertDbRef, SslOptions, CRLDbHandle, Role, + Host, StaplingState) of #alert{} = Alert -> State = update_encryption_state(Role, State0), {error, {Alert, State}}; @@ -805,42 +806,35 @@ update_encryption_state(client, State) -> validate_certificate_chain(CertEntries, CertDbHandle, CertDbRef, - SslOptions, CRLDbHandle, Role, Host, OcspState0) -> - {Certs, CertExt, OcspState} = split_cert_entries(CertEntries, OcspState0), - OcspResponderCerts = - case maps:get(ocsp_stapling, SslOptions, disabled) of - #{ocsp_responder_certs := V} -> - V; - disabled -> - ?DEFAULT_OCSP_RESPONDER_CERTS - end, - ssl_handshake:certify(#certificate{asn1_certificates = Certs}, CertDbHandle, CertDbRef, - SslOptions, CRLDbHandle, Role, Host, ?TLS_1_3, - #{cert_ext => CertExt, - ocsp_state => OcspState, - ocsp_responder_certs => OcspResponderCerts}). + SslOptions, CRLDbHandle, Role, Host, StaplingState) -> + {Certs, ExtInfo} = split_cert_entries(CertEntries, StaplingState, [], #{}), + ssl_handshake:certify(#certificate{asn1_certificates = Certs}, CertDbHandle, + CertDbRef, SslOptions, CRLDbHandle, Role, Host, ?TLS_1_3, + ExtInfo). store_peer_cert(#state{session = Session, handshake_env = HsEnv} = State, PeerCert, PublicKeyInfo) -> State#state{session = Session#session{peer_certificate = PeerCert}, handshake_env = HsEnv#handshake_env{public_key_info = PublicKeyInfo}}. -split_cert_entries(CertEntries, OcspState) -> - split_cert_entries(CertEntries, OcspState, [], #{}). - -split_cert_entries([], OcspState, Chain, Ext) -> - {lists:reverse(Chain), Ext, OcspState}; -split_cert_entries([#certificate_entry{data = DerCert, extensions = Extensions0} | CertEntries], - OcspState0, Chain, Ext) -> +split_cert_entries([], StaplingState, Chain, CertExt) -> + {lists:reverse(Chain), #{cert_ext => CertExt, + stapling_state => StaplingState}}; +split_cert_entries([#certificate_entry{data = DerCert, + extensions = Extensions0} | CertEntries], + #{configured := StaplingConfigured} = StaplingState0, Chain, + CertExt) -> Id = public_key:pkix_subject_id(DerCert), Extensions = [ExtValue || {_, ExtValue} <- maps:to_list(Extensions0)], - OcspState = case maps:get(status_request, Extensions0, undefined) of - undefined -> - OcspState0; - _ -> - OcspState0#{ocsp_expect => stapled} - end, - split_cert_entries(CertEntries, OcspState, [DerCert | Chain], Ext#{Id => Extensions}). + StaplingState = case {maps:get(status_request, Extensions0, undefined), + StaplingConfigured} of + {undefined, _} -> + StaplingState0; + {_, true} -> + StaplingState0#{status => received_staple} + end, + split_cert_entries(CertEntries, StaplingState, [DerCert | Chain], + CertExt#{Id => Extensions}). %% 4.4.1. The Transcript Hash %% @@ -1882,8 +1876,7 @@ path_validation(TrustedCert, Path, ServerName, Role, CertDbHandle, CertDbRef, CR signature_algs := SignAlgos, signature_algs_cert := SignAlgosCert} = Opts, #{cert_ext := CertExt, - ocsp_responder_certs := OcspResponderCerts, - ocsp_state := OcspState}) -> + stapling_state := StaplingState}) -> ValidationFunAndState = ssl_handshake:validation_fun_and_state(VerifyFun, #{role => Role, @@ -1900,8 +1893,7 @@ path_validation(TrustedCert, Path, ServerName, Role, CertDbHandle, CertDbRef, CR version => Version, issuer => TrustedCert, cert_ext => CertExt, - ocsp_responder_certs => OcspResponderCerts, - ocsp_state => OcspState, + stapling_state => StaplingState, path_len => length(Path) }, Path, LogLevel), diff --git a/lib/ssl/test/Makefile b/lib/ssl/test/Makefile index d8bb5b5913a8..d1d6f59ba68b 100644 --- a/lib/ssl/test/Makefile +++ b/lib/ssl/test/Makefile @@ -102,7 +102,7 @@ MODULES = \ inet_epmd_dist_cryptcookie_inet \ inet_epmd_dist_cryptcookie_socket \ inet_epmd_cryptcookie_socket_ktls \ - openssl_ocsp_SUITE \ + openssl_stapling_SUITE \ tls_server_session_ticket_SUITE \ tls_client_ticket_store_SUITE diff --git a/lib/ssl/test/make_certs.erl b/lib/ssl/test/make_certs.erl index e786cddeb642..e06ffc9be43b 100644 --- a/lib/ssl/test/make_certs.erl +++ b/lib/ssl/test/make_certs.erl @@ -24,19 +24,20 @@ %-export([all/1, all/2, rootCA/2, intermediateCA/3, endusers/3, enduser/3, revoke/3, gencrl/2, verify/3]). -record(config, {commonName, - organizationalUnitName = "Erlang OTP", - organizationName = "Ericsson AB", - localityName = "Stockholm", - countryName = "SE", - emailAddress = "peter@erix.ericsson.se", - default_bits = 2048, - v2_crls = true, - ecc_certs = false, - issuing_distribution_point = false, - crldp_crlissuer = false, - crl_port = 8000, - openssl_cmd = "openssl", - hostname = "host.example.com"}). + organizationalUnitName = "Erlang OTP", + organizationName = "Ericsson AB", + localityName = "Stockholm", + countryName = "SE", + emailAddress = "peter@erix.ericsson.se", + default_bits = 2048, + v2_crls = true, + ecc_certs = false, + issuing_distribution_point = false, + crldp_crlissuer = false, + crl_port = 8000, + openssl_cmd = "openssl", + hostname = "host.example.com", + cert_profile = "user_cert"}). default_config() -> @@ -88,7 +89,10 @@ all(DataDir, PrivDir, C = #config{}) -> create_rnd(DataDir, PrivDir), % For all requests rootCA(PrivDir, "erlangCA", C), intermediateCA(PrivDir, "otpCA", "erlangCA", C), - endusers(PrivDir, "otpCA", ["client", "server", "revoked", "undetermined", "a.server", "b.server"], C), + endusers(PrivDir, "otpCA", ["client", "server", "revoked", "undetermined", + "a.server"], C), + endusers(PrivDir, "otpCA", ["b.server"], + C#config{cert_profile="user_cert_ocsp_signing"}), endusers(PrivDir, "erlangCA", ["localhost"], C), %% Create keycert files SDir = filename:join([PrivDir, "server"]), @@ -165,7 +169,7 @@ enduser(Root, CA, User, C) -> create_req(Root, CnfFile, KeyFile, ReqFile, C), %create_req(Root, CnfFile, KeyFile, ReqFile), CertFileAllUsage = filename:join([UsrRoot, "cert.pem"]), - sign_req(Root, CA, "user_cert", ReqFile, CertFileAllUsage, C), + sign_req(Root, CA, C#config.cert_profile, ReqFile, CertFileAllUsage, C), CertFileDigitalSigOnly = filename:join([UsrRoot, "digital_signature_only_cert.pem"]), sign_req(Root, CA, "user_cert_digital_signature_only", ReqFile, CertFileDigitalSigOnly, C), CACertsFile = filename:join(UsrRoot, "cacerts.pem"), @@ -651,6 +655,14 @@ ca_cnf( "issuerAltName = issuer:copy\n" %"crlDistributionPoints=@crl_section\n" + "[user_cert_ocsp_signing]\n" + "basicConstraints = CA:false\n" + "keyUsage = nonRepudiation, digitalSignature, keyEncipherment\n" + "extendedKeyUsage = OCSPSigning\n" + "subjectKeyIdentifier = hash\n" + "authorityKeyIdentifier = keyid,issuer:always\n" + "subjectAltName = DNS.1:" ++ Hostname ++ "\n" + "issuerAltName = issuer:copy\n" %%"[crl_section]\n" %% intentionally invalid %%"URI.1=http://localhost/",C#config.commonName,"/crl.pem\n" diff --git a/lib/ssl/test/openssl_ocsp_SUITE.erl b/lib/ssl/test/openssl_stapling_SUITE.erl similarity index 54% rename from lib/ssl/test/openssl_ocsp_SUITE.erl rename to lib/ssl/test/openssl_stapling_SUITE.erl index 045915cc84d3..e4a19aaf8954 100644 --- a/lib/ssl/test/openssl_ocsp_SUITE.erl +++ b/lib/ssl/test/openssl_stapling_SUITE.erl @@ -18,7 +18,7 @@ %% %CopyrightEnd% %% --module(openssl_ocsp_SUITE). +-module(openssl_stapling_SUITE). -include_lib("common_test/include/ct.hrl"). -include_lib("public_key/include/public_key.hrl"). @@ -35,45 +35,57 @@ end_per_testcase/2]). %% Testcases --export([stapling_basic/0, stapling_basic/1, - stapling_with_nonce/0, stapling_with_nonce/1, - stapling_with_responder_cert/0, stapling_with_responder_cert/1, - stapling_revoked/0, stapling_revoked/1, - stapling_undetermined/0, stapling_undetermined/1, - stapling_no_staple/0, stapling_no_staple/1 +-export([staple_by_issuer/0, staple_by_issuer/1, + staple_by_designated/0, staple_by_designated/1, + staple_by_trusted/0, staple_by_trusted/1, + staple_not_designated/0, staple_not_designated/1, + staple_wrong_issuer/0, staple_wrong_issuer/1, + staple_with_nonce/0, staple_with_nonce/1, + cert_status_revoked/0, cert_status_revoked/1, + cert_status_undetermined/0, cert_status_undetermined/1, + staple_missing/0, staple_missing/1 ]). %% spawn export --export([ocsp_responder_init/4]). +-export([ocsp_responder_init/3]). -define(OCSP_RESPONDER_LOG, "ocsp_resp_log.txt"). -define(DEBUG, false). %%-------------------------------------------------------------------- %% Common Test interface functions ----------------------------------- %%-------------------------------------------------------------------- -all() -> +all() -> [{group, 'tlsv1.3'}, + {group, no_next_update}, {group, 'tlsv1.2'}, {group, 'dtlsv1.2'}]. -groups() -> +groups() -> [{'tlsv1.3', [], ocsp_tests()}, + {no_next_update, [], [{group, 'tlsv1.3'}]}, {'tlsv1.2', [], ocsp_tests()}, {'dtlsv1.2', [], ocsp_tests()}]. ocsp_tests() -> - [stapling_basic, - stapling_with_nonce, - stapling_with_responder_cert, - stapling_revoked, - stapling_undetermined, - stapling_no_staple - ]. + positive() ++ negative(). + +positive() -> + [staple_by_issuer, + staple_by_designated, + staple_by_trusted, + staple_with_nonce]. + +negative() -> + [staple_not_designated, + staple_wrong_issuer, + cert_status_revoked, + cert_status_undetermined, + staple_missing]. %%-------------------------------------------------------------------- init_per_suite(Config0) -> - Config = lists:merge([{debug, ?DEBUG}], - ssl_test_lib:init_per_suite(Config0, openssl)), + Config = [{debug, ?DEBUG}] ++ + ssl_test_lib:init_per_suite(Config0, openssl), case ssl_test_lib:openssl_ocsp_support(Config) of true -> do_init_per_suite(Config); @@ -82,72 +94,103 @@ init_per_suite(Config0) -> end. do_init_per_suite(Config) -> - DataDir = proplists:get_value(data_dir, Config), - PrivDir = proplists:get_value(priv_dir, Config), - - %% Prepare certs - {ok, _} = make_certs:all(DataDir, PrivDir), - - ResponderPort = get_free_port(), - Pid = start_ocsp_responder(ResponderPort, PrivDir, ?config(debug, Config)), - - NewConfig = - lists:merge( - [{responder_port, ResponderPort}, - {responder_pid, Pid} - ], Config), - - ssl_test_lib:cert_options(NewConfig). + {ok, _} = make_certs:all(?config(data_dir, Config), + ?config(priv_dir, Config)), + ssl_test_lib:cert_options(Config). end_per_suite(Config) -> - ResponderPid = proplists:get_value(responder_pid, Config), - ssl_test_lib:close(ResponderPid), - [ssl_test_lib:ct_pal_file(?OCSP_RESPONDER_LOG) || ?config(debug, Config)], ssl_test_lib:end_per_suite(Config). %%-------------------------------------------------------------------- +init_per_group(no_next_update, Config) -> + Config; init_per_group(GroupName, Config) -> ssl_test_lib:init_per_group_openssl(GroupName, Config). +end_per_group(no_next_update, Config) -> + Config; end_per_group(GroupName, Config) -> ssl_test_lib:end_per_group(GroupName, Config). %%-------------------------------------------------------------------- -init_per_testcase(_TestCase, Config) -> +init_per_testcase(staple_by_trusted = Testcase, Config) -> + PrivDir = ?config(priv_dir, Config), + ok = public_key:cacerts_load(filename:join(PrivDir, "otpCA/cacerts.pem")), + init_per_testcase_helper(Testcase, Config); +init_per_testcase(Testcase, Config) -> + init_per_testcase_helper(Testcase, Config). + +init_per_testcase_helper(Testcase, Config0) -> ct:timetrap({seconds, 10}), + Default = "otpCA", + TestcaseMapping = #{staple_by_issuer => Default, + staple_by_trusted => "erlangCA", + staple_by_designated => "b.server", + staple_not_designated => "a.server", + staple_wrong_issuer => "localhost"}, + ResponderFolder = maps:get(Testcase, TestcaseMapping, Default), + Config = start_ocsp_responder( + [{responder_folder, ResponderFolder} | Config0]) ++ Config0, ssl_test_lib:ct_log_supported_protocol_versions(Config), Config. -end_per_testcase(_TestCase, Config) -> +end_per_testcase(staple_by_trusted, Config) -> + public_key:cacerts_load(), + end_per_testcase_helper(Config); +end_per_testcase(_Testcase, Config) -> + end_per_testcase_helper(Config). + +end_per_testcase_helper(Config) -> + ResponderPid = ?config(responder_pid, Config), + ssl_test_lib:close(ResponderPid), + [ssl_test_lib:ct_pal_file(?OCSP_RESPONDER_LOG) || ?config(debug, Config)], Config. %%-------------------------------------------------------------------- %% Test Cases -------------------------------------------------------- %%-------------------------------------------------------------------- -stapling_basic() -> - [{doc, "Verify OCSP stapling works without nonce and responder certs."}]. -stapling_basic(Config) +%% Test various certs used for signing OCSP response +%% Assuming Issuer issued a.server certificate used by TLS server +%% 1. otpCA - [OK] Issuer signs response directly +%% 2. b.server - [OK] Responder certificate issued directly by Issuer +%% and designated for OCSP signing +%% 3 localhost - [OK] Certificate not issued by Issuer, but present in trust store +%% 4. a.server - [NOK] Certificate signed directly by Issuer but not designated +%% 5. localhost - [NOK] Certificate not issued by Issuer + +staple_by_issuer() -> + [{doc, "Verify OCSP stapling works without nonce." + "Response signed directly by issuer of server certificate"}]. +staple_by_issuer(Config) when is_list(Config) -> - stapling_helper(Config, [{ocsp_nonce, false}]). - -stapling_with_nonce() -> - [{doc, "Verify OCSP stapling works with nonce."}]. -stapling_with_nonce(Config) + stapling_helper(Config, #{ocsp_nonce => false}). + +staple_by_designated() -> + [{doc,"Verify OCSP stapling works without nonce." + "Response signed with certificate issued directly by issuer of server " + "certificate and is designated for OCSP signing (extKeyUsage allows " + "for OCSP signing)."}]. +staple_by_designated(Config) + when is_list(Config) -> + stapling_helper(Config, #{ocsp_nonce => false}). + +staple_by_trusted() -> + [{doc,"Verify OCSP stapling works without nonce." + "Response signed with certificate issued directly by issuer of server " + "certificate and is designated for OCSP signing (extKeyUsage allows " + "for OCSP signing)."}]. +staple_by_trusted(Config) when is_list(Config) -> - stapling_helper(Config, [{ocsp_nonce, true}]). + stapling_helper(Config, #{ocsp_nonce => false}). -stapling_with_responder_cert() -> - [{doc, "Verify OCSP stapling works with nonce and responder certs."}]. -stapling_with_responder_cert(Config) +staple_with_nonce() -> + [{doc, "Verify OCSP stapling works with nonce."}]. +staple_with_nonce(Config) when is_list(Config) -> - PrivDir = proplists:get_value(priv_dir, Config), - {ok, ResponderCert} = - file:read_file(filename:join(PrivDir, "b.server/cert.pem")), - [{'Certificate', Der, _IsEncrypted}] = - public_key:pem_decode(ResponderCert), - stapling_helper(Config, [{ocsp_nonce, true}, {ocsp_responder_certs, [Der]}]). + stapling_helper(Config, #{ocsp_nonce => true}). -stapling_helper(Config, Opts) -> +stapling_helper(Config, StaplingOpt) -> + %% ok = logger:set_application_level(ssl, debug), PrivDir = proplists:get_value(priv_dir, Config), CACertsFile = filename:join(PrivDir, "a.server/cacerts.pem"), Data = "ping", %% 4 bytes @@ -160,7 +203,7 @@ stapling_helper(Config, Opts) -> ClientOpts = ssl_test_lib:ssl_options([{verify, verify_peer}, {cacertfile, CACertsFile}, {server_name_indication, disable}, - {ocsp_stapling, true}] ++ Opts, + {stapling, StaplingOpt}], Config), Client = ssl_test_lib:start_client(erlang, [{port, Port}, @@ -170,24 +213,44 @@ stapling_helper(Config, Opts) -> Data = ssl_test_lib:check_active_receive(Client, Data), ssl_test_lib:close(Server), ssl_test_lib:close(Client). + %%-------------------------------------------------------------------- -stapling_revoked() -> +staple_not_designated() -> + [{doc,"Verify OCSP stapling works without nonce." + "Response signed with certificate issued directly by issuer of server " + "certificate but not designated for OCSP signing (extKeyUsage missing " + "OCSP signing)."}]. +staple_not_designated(Config) + when is_list(Config) -> + stapling_negative_helper(Config, "a.server/cacerts.pem", + openssl_ocsp, bad_certificate). + +staple_wrong_issuer() -> + [{doc,"Verify OCSP stapling works without nonce." + "Response signed with certificate not related to issuer of server " + "certificate."}]. +staple_wrong_issuer(Config) + when is_list(Config) -> + stapling_negative_helper(Config, "a.server/cacerts.pem", + openssl_ocsp, bad_certificate). + +cert_status_revoked() -> [{doc, "Verify OCSP stapling works with revoked certificate."}]. -stapling_revoked(Config) +cert_status_revoked(Config) when is_list(Config) -> stapling_negative_helper(Config, "revoked/cacerts.pem", openssl_ocsp_revoked, certificate_revoked). -stapling_undetermined() -> +cert_status_undetermined() -> [{doc, "Verify OCSP stapling works with certificate with undetermined status."}]. -stapling_undetermined(Config) +cert_status_undetermined(Config) when is_list(Config) -> stapling_negative_helper(Config, "undetermined/cacerts.pem", openssl_ocsp_undetermined, bad_certificate). -stapling_no_staple() -> +staple_missing() -> [{doc, "Verify OCSP stapling works with a missing OCSP response."}]. -stapling_no_staple(Config) +staple_missing(Config) when is_list(Config) -> %% Start a server that will not include an OCSP response. stapling_negative_helper(Config, "a.server/cacerts.pem", @@ -206,9 +269,8 @@ stapling_negative_helper(Config, CACertsPath, ServerVariant, ExpectedError) -> ClientOpts = ssl_test_lib:ssl_options([{verify, verify_peer}, {server_name_indication, disable}, {cacertfile, CACertsFile}, - {ocsp_stapling, true}, - {ocsp_nonce, true} - ], Config), + {stapling, #{ocsp_nonce => true}}], + Config), Client = ssl_test_lib:start_client_error([{node, ClientNode},{port, Port}, {host, Hostname}, {from, self()}, {options, ClientOpts}]), @@ -218,30 +280,42 @@ stapling_negative_helper(Config, CACertsPath, ServerVariant, ExpectedError) -> %%-------------------------------------------------------------------- %% Internal functions ----------------------------------------------- %%-------------------------------------------------------------------- -start_ocsp_responder(ResponderPort, PrivDir, Debug) -> +start_ocsp_responder(Config) -> + ResponderPort = get_free_port(), Starter = self(), - Pid = erlang:spawn( - ?MODULE, ocsp_responder_init, - [ResponderPort, PrivDir, Starter, Debug]), + process_flag(trap_exit, true), + Pid = erlang:spawn_link(?MODULE, ocsp_responder_init, + [ResponderPort, Starter, Config]), receive {started, Pid} -> - Pid; + [{responder_port, ResponderPort}, {responder_pid, Pid}]; {'EXIT', Pid, Reason} -> throw({unable_to_start_ocsp_service, Reason}) end. -ocsp_responder_init(ResponderPort, PrivDir, Starter, Debug) -> +ocsp_responder_init(ResponderPort, Starter, Config) -> + ResponderFolder = ?config(responder_folder, Config), + PrivDir = ?config(priv_dir, Config), Index = filename:join(PrivDir, "otpCA/index.txt"), - CACerts = filename:join(PrivDir, "b.server/cacerts.pem"), - Cert = filename:join(PrivDir, "b.server/cert.pem"), - Key = filename:join(PrivDir, "b.server/key.pem"), - DebugArgs = case Debug of + CACerts = filename:join(PrivDir, "otpCA/cacerts.pem"), + Cert = filename:join(PrivDir, ResponderFolder ++ "/cert.pem"), + %% search for key.pem file, since generated intermediate CAs + %% "hide" their key.pem inside "private" subfolder + [Key] = filelib:fold_files(filename:join(PrivDir, ResponderFolder), + "key.pem", true, fun(X, Acc) -> [X | Acc] end, []), + Debug = case ?config(debug, Config) of true -> ["-text", "-out", ?OCSP_RESPONDER_LOG]; _ -> [] end, + NextUpdate = case ?config(tc_group_path, Config) of + [[{name,no_next_update}]] -> + []; + _ -> + ["-nmin", "5"] + end, Args = ["ocsp", "-index", Index, "-CA", CACerts, "-rsigner", Cert, "-rkey", Key, "-port", erlang:integer_to_list(ResponderPort)] ++ - DebugArgs, + Debug ++ NextUpdate, process_flag(trap_exit, true), Port = ssl_test_lib:portable_open_port("openssl", Args), ?CT_LOG("OCSP responder: Started Port = ~p", [Port]), diff --git a/lib/ssl/test/ssl_api_SUITE.erl b/lib/ssl/test/ssl_api_SUITE.erl index 79b64cfa5d6a..31b3f9c3e1a0 100644 --- a/lib/ssl/test/ssl_api_SUITE.erl +++ b/lib/ssl/test/ssl_api_SUITE.erl @@ -2386,7 +2386,7 @@ options_whitebox(Config) when is_list(Config) -> options_renegotiate(Config), options_middlebox(Config), options_frag_len(Config), - options_oscp(Config), + options_stapling(Config), options_padding(Config), options_identity(Config), options_reuse_session(Config), @@ -2940,31 +2940,25 @@ options_frag_len(_Config) -> %% max_fragment_length ?ERR({max_fragment_length,2000}, [{max_fragment_length, 2000}], client), ok. -options_oscp(Config) -> - Cert = proplists:get_value( - cert, ssl_test_lib:ssl_options(server_rsa_der_opts, Config)), - NoOcspOption = [ocsp_stapling, ocsp_nonce, ocsp_responder_certs], - - ?OK(#{}, [], client, NoOcspOption), - ?OK(#{}, [{ocsp_stapling, false}], client, NoOcspOption), - ?OK(#{ocsp_stapling := #{ocsp_nonce := true, ocsp_responder_certs := []}}, - [{ocsp_stapling, true}], client, [ocsp_nonce, ocsp_responder_certs]), - ?OK(#{ocsp_stapling := - #{ocsp_nonce := false, ocsp_responder_certs := [_, _]}}, - [{ocsp_stapling, true}, {ocsp_nonce, false}, - {ocsp_responder_certs, [Cert,Cert]}], - client, [ocsp_nonce, ocsp_responder_certs]), +options_stapling(_Config) -> + ?OK(#{}, [], client, [stapling]), + ?OK(#{}, [{stapling, no_staple}], client, [stapling]), + + ?OK(#{stapling := #{ocsp_nonce := true}}, + [{stapling, staple}], client), + ?OK(#{stapling := #{ocsp_nonce := true}}, + [{stapling, #{}}], client), + ?OK(#{stapling := #{ocsp_nonce := true}}, + [{stapling, #{ocsp_nonce => true}}], client), + + ?OK(#{stapling := #{ocsp_nonce := false}}, + [{stapling, #{ocsp_nonce => false}}], client), + %% Errors - ?ERR({ocsp_stapling, foo}, [{ocsp_stapling, 'foo'}], client), - ?ERR({ocsp_nonce, foo}, [{ocsp_nonce, 'foo'}], client), - ?ERR({ocsp_responder_certs, foo}, [{ocsp_responder_certs, 'foo'}], client), - ?ERR({options, incompatible, [{ocsp_nonce, false}, {ocsp_stapling, false}]}, - [{ocsp_nonce, false}], client), - ?ERR({options, incompatible, [ocsp_responder_certs, {ocsp_stapling, false}]}, - [{ocsp_responder_certs, [Cert]}], server), - ?ERR({ocsp_responder_certs, [_]}, - [{ocsp_stapling, true}, {ocsp_responder_certs, ['NOT A BINARY']}], - client), + ?ERR({stapling, foo}, [{stapling, 'foo'}], client), + ?ERR({option, client_only, stapling}, [{stapling, true}], server), + ?ERR({option, client_only, stapling}, [{stapling, false}], server), + ?ERR({option, client_only, stapling}, [{stapling, #{}}], server), ok. options_padding(_Config) -> diff --git a/lib/ssl/test/ssl_gh.spec b/lib/ssl/test/ssl_gh.spec index 6942caa68e73..1df89d2d0182 100644 --- a/lib/ssl/test/ssl_gh.spec +++ b/lib/ssl/test/ssl_gh.spec @@ -2,7 +2,6 @@ {alias,dir,"../ssl_test"}. {suites,dir,all}. -{skip_suites,dir,[openssl_ocsp_SUITE],"Unstable testcases"}. {skip_groups,all_nodes, dir, openssl_session_ticket_SUITE, 'openssl_server', {cases,[openssl_server_hrr]},"Unstable testcases"}. {skip_groups,dir,ssl_bench_SUITE,setup,"Benchmarks run separately"}. diff --git a/lib/ssl/test/ssl_test_lib.erl b/lib/ssl/test/ssl_test_lib.erl index 0cb75719ef9c..608851e0bd75 100644 --- a/lib/ssl/test/ssl_test_lib.erl +++ b/lib/ssl/test/ssl_test_lib.erl @@ -424,6 +424,8 @@ openssl_ocsp_support(Config) -> case proplists:get_value(openssl_version, Config) of "OpenSSL 1.1.1" ++ _Rest -> true; + "OpenSSL 3" ++ _Rest -> + true; _ -> false end.