Skip to content

Commit

Permalink
ssl: Add option customize_hostname_check
Browse files Browse the repository at this point in the history
  • Loading branch information
IngelaAndin committed Jun 8, 2018
1 parent 0387fa9 commit f821c91
Show file tree
Hide file tree
Showing 6 changed files with 85 additions and 17 deletions.
9 changes: 9 additions & 0 deletions lib/ssl/doc/src/ssl.xml
Original file line number Diff line number Diff line change
Expand Up @@ -89,6 +89,7 @@
[binary()]} | {client | server, [binary()], binary()}}</c></p>
<p><c>| {log_alert, boolean()}</c></p>
<p><c>| {server_name_indication, hostname() | disable}</c></p>
<p><c>| {customize_hostname_check, list()}</c></p>
<p><c>| {sni_hosts, [{hostname(), [ssl_option()]}]}</c></p>
<p><c>| {sni_fun, SNIfun::fun()}</c></p>
</item>
Expand Down Expand Up @@ -649,6 +650,14 @@ fun(srp, Username :: string(), UserState :: term()) ->
disables the hostname verification check
<seealso marker="public_key:public_key#pkix_verify_hostname-2">public_key:pkix_verify_hostname/2</seealso> </p>
</item>

<tag><c>{customize_hostname_check, Options::list()}</c></tag>
<item>
<p> Customizes the hostname verification of the peer certificate, as different protocols that use
TLS such as HTTP or LDAP may want to do it differently, for possible options see
<seealso marker="public_key:public_key#pkix_verify_hostname-3">public_key:pkix_verify_hostname/3</seealso> </p>
</item>

<tag><c>{fallback, boolean()}</c></tag>
<item>
<p> Send special cipher suite TLS_FALLBACK_SCSV to avoid undesired TLS version downgrade.
Expand Down
7 changes: 5 additions & 2 deletions lib/ssl/src/ssl.erl
Original file line number Diff line number Diff line change
Expand Up @@ -938,7 +938,8 @@ handle_options(Opts0, Role, Host) ->
crl_check = handle_option(crl_check, Opts, false),
crl_cache = handle_option(crl_cache, Opts, {ssl_crl_cache, {internal, []}}),
max_handshake_size = handle_option(max_handshake_size, Opts, ?DEFAULT_MAX_HANDSHAKE_SIZE),
handshake = handle_option(handshake, Opts, full)
handshake = handle_option(handshake, Opts, full),
customize_hostname_check = handle_option(customize_hostname_check, Opts, [])
},

CbInfo = proplists:get_value(cb_info, Opts, default_cb_info(Protocol)),
Expand All @@ -954,7 +955,7 @@ handle_options(Opts0, Role, Host) ->
client_preferred_next_protocols, log_alert,
server_name_indication, honor_cipher_order, padding_check, crl_check, crl_cache,
fallback, signature_algs, eccs, honor_ecc_order, beast_mitigation,
max_handshake_size, handshake],
max_handshake_size, handshake, customize_hostname_check],
SockOpts = lists:foldl(fun(Key, PropList) ->
proplists:delete(Key, PropList)
end, Opts, SslOptions),
Expand Down Expand Up @@ -1197,6 +1198,8 @@ validate_option(handshake, hello = Value) ->
Value;
validate_option(handshake, full = Value) ->
Value;
validate_option(customize_hostname_check, Value) when is_list(Value) ->
Value;
validate_option(Opt, Value) ->
throw({error, {options, {Opt, Value}}}).

Expand Down
18 changes: 9 additions & 9 deletions lib/ssl/src/ssl_certificate.erl
Original file line number Diff line number Diff line change
Expand Up @@ -138,8 +138,8 @@ validate(_, {bad_cert, _} = Reason, _) ->
{fail, Reason};
validate(_, valid, UserState) ->
{valid, UserState};
validate(Cert, valid_peer, UserState = {client, _,_, Hostname, _, _}) when Hostname =/= disable ->
verify_hostname(Hostname, Cert, UserState);
validate(Cert, valid_peer, UserState = {client, _,_, {Hostname, Customize}, _, _}) when Hostname =/= disable ->
verify_hostname(Hostname, Customize, Cert, UserState);
validate(_, valid_peer, UserState) ->
{valid, UserState}.

Expand Down Expand Up @@ -333,29 +333,29 @@ new_trusteded_chain(DerCert, [_ | Rest]) ->
new_trusteded_chain(_, []) ->
unknown_ca.

verify_hostname({fallback, Hostname}, Cert, UserState) when is_list(Hostname) ->
case public_key:pkix_verify_hostname(Cert, [{dns_id, Hostname}]) of
verify_hostname({fallback, Hostname}, Customize, Cert, UserState) when is_list(Hostname) ->
case public_key:pkix_verify_hostname(Cert, [{dns_id, Hostname}], Customize) of
true ->
{valid, UserState};
false ->
case public_key:pkix_verify_hostname(Cert, [{ip, Hostname}]) of
case public_key:pkix_verify_hostname(Cert, [{ip, Hostname}], Customize) of
true ->
{valid, UserState};
false ->
{fail, {bad_cert, hostname_check_failed}}
end
end;

verify_hostname({fallback, Hostname}, Cert, UserState) ->
case public_key:pkix_verify_hostname(Cert, [{ip, Hostname}]) of
verify_hostname({fallback, Hostname}, Customize, Cert, UserState) ->
case public_key:pkix_verify_hostname(Cert, [{ip, Hostname}], Customize) of
true ->
{valid, UserState};
false ->
{fail, {bad_cert, hostname_check_failed}}
end;

verify_hostname(Hostname, Cert, UserState) ->
case public_key:pkix_verify_hostname(Cert, [{dns_id, Hostname}]) of
verify_hostname(Hostname, Customize, Cert, UserState) ->
case public_key:pkix_verify_hostname(Cert, [{dns_id, Hostname}], Customize) of
true ->
{valid, UserState};
false ->
Expand Down
9 changes: 5 additions & 4 deletions lib/ssl/src/ssl_handshake.erl
Original file line number Diff line number Diff line change
Expand Up @@ -345,6 +345,7 @@ certify(#certificate{asn1_certificates = ASN1Certs}, CertDbHandle, CertDbRef,
Opts#ssl_options.partial_chain),
ValidationFunAndState = validation_fun_and_state(Opts#ssl_options.verify_fun, Role,
CertDbHandle, CertDbRef, ServerName,
Opts#ssl_options.customize_hostname_check,
Opts#ssl_options.crl_check, CRLDbHandle, CertPath),
case public_key:pkix_path_validation(TrustedCert,
CertPath,
Expand Down Expand Up @@ -1243,7 +1244,7 @@ certificate_authorities_from_db(_CertDbHandle, {extracted, CertDbData}) ->

%%-------------Handle handshake messages --------------------------------
validation_fun_and_state({Fun, UserState0}, Role, CertDbHandle, CertDbRef,
ServerNameIndication, CRLCheck, CRLDbHandle, CertPath) ->
ServerNameIndication, CustomizeHostCheck, CRLCheck, CRLDbHandle, CertPath) ->
{fun(OtpCert, {extension, _} = Extension, {SslState, UserState}) ->
case ssl_certificate:validate(OtpCert,
Extension,
Expand All @@ -1260,9 +1261,9 @@ validation_fun_and_state({Fun, UserState0}, Role, CertDbHandle, CertDbRef,
(OtpCert, VerifyResult, {SslState, UserState}) ->
apply_user_fun(Fun, OtpCert, VerifyResult, UserState,
SslState, CertPath)
end, {{Role, CertDbHandle, CertDbRef, ServerNameIndication, CRLCheck, CRLDbHandle}, UserState0}};
end, {{Role, CertDbHandle, CertDbRef, {ServerNameIndication, CustomizeHostCheck}, CRLCheck, CRLDbHandle}, UserState0}};
validation_fun_and_state(undefined, Role, CertDbHandle, CertDbRef,
ServerNameIndication, CRLCheck, CRLDbHandle, CertPath) ->
ServerNameIndication, CustomizeHostCheck, CRLCheck, CRLDbHandle, CertPath) ->
{fun(OtpCert, {extension, _} = Extension, SslState) ->
ssl_certificate:validate(OtpCert,
Extension,
Expand All @@ -1282,7 +1283,7 @@ validation_fun_and_state(undefined, Role, CertDbHandle, CertDbRef,
ssl_certificate:validate(OtpCert,
VerifyResult,
SslState)
end, {Role, CertDbHandle, CertDbRef, ServerNameIndication, CRLCheck, CRLDbHandle}}.
end, {Role, CertDbHandle, CertDbRef, {ServerNameIndication, CustomizeHostCheck}, CRLCheck, CRLDbHandle}}.

apply_user_fun(Fun, OtpCert, VerifyResult, UserState0,
{_, CertDbHandle, CertDbRef, _, CRLCheck, CRLDbHandle} = SslState, CertPath) when
Expand Down
3 changes: 2 additions & 1 deletion lib/ssl/src/ssl_internal.hrl
Original file line number Diff line number Diff line change
Expand Up @@ -145,7 +145,8 @@
eccs,
honor_ecc_order :: boolean(),
max_handshake_size :: integer(),
handshake
handshake,
customize_hostname_check
}).

-record(socket_options,
Expand Down
56 changes: 55 additions & 1 deletion lib/ssl/test/ssl_certificate_verify_SUITE.erl
Original file line number Diff line number Diff line change
Expand Up @@ -87,7 +87,9 @@ tests() ->
extended_key_usage_verify_server,
critical_extension_verify_client,
critical_extension_verify_server,
critical_extension_verify_none].
critical_extension_verify_none,
customize_hostname_check
].

error_handling_tests()->
[client_with_cert_cipher_suites_handshake,
Expand Down Expand Up @@ -1144,6 +1146,58 @@ unknown_server_ca_accept_backwardscompatibility(Config) when is_list(Config) ->
ssl_test_lib:close(Server),
ssl_test_lib:close(Client).

%%--------------------------------------------------------------------

customize_hostname_check() ->
[{doc,"Test option customize_hostname_check."}].
customize_hostname_check(Config) when is_list(Config) ->
Ext = [#'Extension'{extnID = ?'id-ce-subjectAltName',
extnValue = [{dNSName, "*.example.org"}],
critical = false}
],
{ClientOpts0, ServerOpts0} = ssl_test_lib:make_rsa_cert_chains([{server_chain,
[[],
[],
[{extensions, Ext}]
]}],
Config, "https_hostname_convention"),
ClientOpts = ssl_test_lib:ssl_options(ClientOpts0, Config),
ServerOpts = ssl_test_lib:ssl_options(ServerOpts0, Config),

{ClientNode, ServerNode, Hostname} = ssl_test_lib:run_where(Config),
Server = ssl_test_lib:start_server([{node, ServerNode}, {port, 0},
{from, self()},
{mfa, {ssl_test_lib, send_recv_result_active, []}},
{options, ServerOpts}]),
Port = ssl_test_lib:inet_port(Server),

CustomFun = public_key:pkix_verify_hostname_match_fun(https),

Client = ssl_test_lib:start_client([{node, ClientNode}, {port, Port},
{host, Hostname},
{from, self()},
{mfa, {ssl_test_lib, send_recv_result_active, []}},
{options,
[{server_name_indication, "other.example.org"},
{customize_hostname_check,
[{match_fun, CustomFun}]} | ClientOpts]
}]),
ssl_test_lib:check_result(Server, ok, Client, ok),

Server ! {listen, {mfa, {ssl_test_lib, no_result, []}}},

Client1 = ssl_test_lib:start_client_error([{node, ClientNode}, {port, Port},
{host, Hostname},
{from, self()},
{mfa, {ssl_test_lib, no_result, []}},
{options, ClientOpts}
]),
ssl_test_lib:check_result(Client1, {error, {tls_alert, "handshake failure"}},
Server, {error, {tls_alert, "handshake failure"}}),

ssl_test_lib:close(Server),
ssl_test_lib:close(Client).

%%--------------------------------------------------------------------
%% Internal functions ------------------------------------------------
%%--------------------------------------------------------------------
Expand Down

0 comments on commit f821c91

Please sign in to comment.