Skip to content

Commit

Permalink
ssl, public_key: REVIEW comments
Browse files Browse the repository at this point in the history
  • Loading branch information
u3s committed Aug 21, 2023
1 parent 2d3326c commit 4b2e6c9
Show file tree
Hide file tree
Showing 3 changed files with 8 additions and 8 deletions.
4 changes: 2 additions & 2 deletions lib/public_key/src/pubkey_ocsp.erl
Original file line number Diff line number Diff line change
Expand Up @@ -80,7 +80,7 @@ find_single_response(Cert, IssuerCert, SingleResponseList) ->
SerialNum = get_serial_num(Cert),
match_single_response(IssuerName, IssuerKey, SerialNum, SingleResponseList).

-spec status({atom(), term()}) -> atom() | {atom(), {atom(), term()}}.
-spec status({atom(), term()}) -> ok | {error, {bad_cert, term()}}.
status({good, _}) ->
ok;
status({unknown, Reason}) ->
Expand Down Expand Up @@ -223,7 +223,7 @@ is_authorized_responder(Cert, IssuerCert) ->
case lists:any(fun(E) -> E() end, [Case1, Case2, Case3]) of
true ->
true;
_ ->
false ->
not_authorized_responder
end.

Expand Down
8 changes: 6 additions & 2 deletions lib/public_key/src/public_key.erl
Original file line number Diff line number Diff line change
Expand Up @@ -159,7 +159,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 | {revoked, crl_reason()} | atom().
-type bad_cert_reason() :: cert_expired | invalid_issuer | invalid_signature
| name_not_permitted | missing_basic_constraint
| invalid_key_usage | duplicate_cert_in_path
| {revoked, crl_reason()}
| {revocation_status_undetermined, term()} | atom().

-type combined_cert() :: #cert{}.
-type cert() :: der_cert() | otp_cert().
Expand Down Expand Up @@ -1373,7 +1377,7 @@ pkix_test_root_cert(Name, Opts) ->
IssuerCert:: cert(),
OcspRespDer::der_encoded(),
NonceExt::undefined | binary(),
Reason::term().
Reason::bad_cert_reason().
%% Description: Validate OCSP response
%%--------------------------------------------------------------------
pkix_ocsp_validate(DerCert, IssuerCert, OcspRespDer, NonceExt)
Expand Down
4 changes: 0 additions & 4 deletions lib/ssl/src/ssl.erl
Original file line number Diff line number Diff line change
Expand Up @@ -2511,10 +2511,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;
Expand Down

0 comments on commit 4b2e6c9

Please sign in to comment.