Skip to content

Commit

Permalink
Merge branch 'maint'
Browse files Browse the repository at this point in the history
* maint:
  ssl: Handle ip-address as string correctly
  • Loading branch information
dgud committed Jan 11, 2024
2 parents 4e359b1 + cf371c9 commit adf0d22
Show file tree
Hide file tree
Showing 5 changed files with 32 additions and 47 deletions.
8 changes: 0 additions & 8 deletions lib/ssl/doc/src/ssl.xml
Original file line number Diff line number Diff line change
Expand Up @@ -124,14 +124,6 @@
<name name="host"/>
</datatype>

<datatype>
<name name="hostname"/>
</datatype>

<datatype>
<name name="ip_address"/>
</datatype>

<datatype>
<name name="protocol_version"/>
</datatype>
Expand Down
10 changes: 4 additions & 6 deletions lib/ssl/src/ssl.erl
Original file line number Diff line number Diff line change
Expand Up @@ -160,9 +160,7 @@
ClosedTag::atom(), ErrTag::atom()}} |
{cb_info, {CallbackModule::atom(), DataTag::atom(),
ClosedTag::atom(), ErrTag::atom(), PassiveTag::atom()}}.
-type host() :: hostname() | ip_address(). % exported
-type hostname() :: string().
-type ip_address() :: inet:ip_address().
-type host() :: inet:hostname() | inet:ip_address(). % exported
-type session_id() :: binary(). % exported
-type protocol_version() :: tls_version() | dtls_version(). % exported
-type tls_version() :: 'tlsv1.2' | 'tlsv1.3' | tls_legacy_version().
Expand Down Expand Up @@ -455,7 +453,7 @@
-type client_psk_identity() :: psk_identity().
-type client_srp_identity() :: srp_identity().
-type customize_hostname_check() :: list().
-type sni() :: HostName :: hostname() | disable.
-type sni() :: inet:hostname() | disable.
-type max_fragment_length() :: undefined | 512 | 1024 | 2048 | 4096.
-type fallback() :: boolean().
-type ssl_imp() :: new | old.
Expand Down Expand Up @@ -500,7 +498,7 @@
-type fail_if_no_peer_cert() :: boolean().
-type server_reuse_session() :: fun().
-type server_reuse_sessions() :: boolean().
-type sni_hosts() :: [{hostname(), [server_option() | common_option()]}].
-type sni_hosts() :: [{inet:hostname(), [server_option() | common_option()]}].
-type sni_fun() :: fun((string()) -> [] | undefined).
-type honor_cipher_order() :: boolean().
-type honor_ecc_order() :: boolean().
Expand All @@ -518,7 +516,7 @@
max_frag_enum => 1..4,
ec_point_formats => [0..2],
elliptic_curves => [public_key:oid()],
sni => hostname()}. % exported
sni => inet:hostname()}. % exported
%% -------------------------------------------------------------------------------------------------------
-type connection_info() :: [common_info() | curve_info() | ssl_options_info() | security_info()].
-type common_info() :: {protocol, protocol_version()} |
Expand Down
34 changes: 10 additions & 24 deletions lib/ssl/src/ssl_certificate.erl
Original file line number Diff line number Diff line change
Expand Up @@ -553,33 +553,19 @@ other_issuer(#cert{otp=OtpCert}=Cert, CertDbHandle, CertDbRef) ->
end
end.

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}], Customize) of
true ->
{valid, UserState};
false ->
{fail, {bad_cert, hostname_check_failed}}
end
end;

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

verify_hostname(Hostname, Customize, Cert, UserState) ->
case public_key:pkix_verify_hostname(Cert, [{dns_id, Hostname}], Customize) of
true ->
{valid, UserState};
false ->
{fail, {bad_cert, hostname_check_failed}}
HostId = case inet:parse_strict_address(Hostname) of
{ok, IP} -> {ip, IP};
_ -> {dns_id, Hostname}
end,
case public_key:pkix_verify_hostname(Cert, [HostId], Customize) of
true -> {valid, UserState};
false -> {fail, {bad_cert, hostname_check_failed}}
end.

verify_cert_extensions(Cert, #{cert_ext := CertExts} = UserState) ->
Expand Down
13 changes: 8 additions & 5 deletions lib/ssl/src/ssl_handshake.erl
Original file line number Diff line number Diff line change
Expand Up @@ -84,7 +84,6 @@

-export([get_cert_params/1,
select_own_cert/1,
server_name/3,
path_validation/10,
validation_fun_and_state/4,
path_validation_alert/1]).
Expand Down Expand Up @@ -3558,12 +3557,16 @@ server_name(_, _, server) ->
undefined; %% Not interesting to check your own name.
server_name(SSLOpts, Host, client) ->
case maps:get(server_name_indication, SSLOpts, undefined) of
undefined ->
{fallback, Host}; %% Fallback to Host argument to connect
SNI ->
SNI %% If Server Name Indication is available
disable -> disable;
undefined -> convert_hostname(Host); %% Fallback to Host argument to connect
UserSNI -> convert_hostname(UserSNI) %% If Server Name Indication is available
end.

convert_hostname(SNI) when is_atom(SNI) ->
atom_to_list(SNI);
convert_hostname(SNI) ->
SNI.

client_ecc_extensions(SupportedECCs) ->
CryptoSupport = proplists:get_value(public_keys, crypto:supports()),
case proplists:get_bool(ecdh, CryptoSupport) of
Expand Down
14 changes: 10 additions & 4 deletions lib/ssl/test/ssl_sni_SUITE.erl
Original file line number Diff line number Diff line change
Expand Up @@ -226,7 +226,8 @@ dns_name(Config) ->
ip_fallback(Config) ->
Hostname = net_adm:localhost(),
{ok, #hostent{h_addr_list = [IP |_]}} = inet:gethostbyname(net_adm:localhost()),
IPStr = tuple_to_list(IP),
IPList = tuple_to_list(IP),
IPStr = lists:flatten(integer_to_list(hd(IPList)) ++ [io_lib:format(".~w", [I]) || I <- tl(IPList)]),
#{server_config := ServerOpts0,
client_config := ClientOpts0} =
public_key:pkix_test_data(#{server_chain =>
Expand All @@ -235,7 +236,7 @@ ip_fallback(Config) ->
peer => [{extensions, [#'Extension'{extnID =
?'id-ce-subjectAltName',
extnValue = [{dNSName, Hostname},
{iPAddress, IPStr}],
{iPAddress, IPList}],
critical = false}]},
{key, ssl_test_lib:hardcode_rsa_key(3)}]},
client_chain =>
Expand All @@ -246,11 +247,15 @@ ip_fallback(Config) ->
ServerConf = ssl_test_lib:sig_algs(rsa, Version) ++ ServerOpts0,
ClientConf = ssl_test_lib:sig_algs(rsa, Version) ++ ClientOpts0,
successfull_connect(ServerConf, [{verify, verify_peer} | ClientConf], Hostname, Config),
successfull_connect(ServerConf, [{verify, verify_peer} | ClientConf], IP, Config).
successfull_connect(ServerConf, [{verify, verify_peer} | ClientConf], IP, Config),
successfull_connect(ServerConf, [{verify, verify_peer} | ClientConf], IPStr, Config),
successfull_connect(ServerConf, [{verify, verify_peer} | ClientConf], list_to_atom(Hostname), Config).

no_ip_fallback(Config) ->
Hostname = net_adm:localhost(),
{ok, #hostent{h_addr_list = [IP |_]}} = inet:gethostbyname(net_adm:localhost()),
IPList = tuple_to_list(IP),
IPStr = lists:flatten(integer_to_list(hd(IPList)) ++ [io_lib:format(".~w", [I]) || I <- tl(IPList)]),
#{server_config := ServerOpts0,
client_config := ClientOpts0} =
public_key:pkix_test_data(#{server_chain =>
Expand All @@ -270,7 +275,8 @@ no_ip_fallback(Config) ->
ServerConf = ssl_test_lib:sig_algs(rsa, Version) ++ ServerOpts0,
ClientConf = ssl_test_lib:sig_algs(rsa, Version) ++ ClientOpts0,
successfull_connect(ServerConf, [{verify, verify_peer} | ClientConf], Hostname, Config),
unsuccessfull_connect(ServerConf, [{verify, verify_peer} | ClientConf], IP, Config).
unsuccessfull_connect(ServerConf, [{verify, verify_peer} | ClientConf], IP, Config),
unsuccessfull_connect(ServerConf, [{verify, verify_peer} | ClientConf], IPStr, Config).

dns_name_reuse(Config) ->
SNIHostname = "OTP.test.server",
Expand Down

0 comments on commit adf0d22

Please sign in to comment.