Skip to content

Commit

Permalink
ssl: Change client default verify
Browse files Browse the repository at this point in the history
Closes  #5899

Whitebox option tests need to be fixed before OTP-26 (but we want the change in RC2).
  • Loading branch information
IngelaAndin committed Mar 17, 2023
1 parent 6d813a9 commit bb3603d
Show file tree
Hide file tree
Showing 20 changed files with 298 additions and 330 deletions.
14 changes: 7 additions & 7 deletions lib/ssl/src/dtls_connection.erl
Original file line number Diff line number Diff line change
Expand Up @@ -160,15 +160,15 @@

%%====================================================================
%% Internal application API
%%====================================================================
%%====================================================================
%%====================================================================
%% Setup
%%====================================================================
%%====================================================================
init([Role, Host, Port, Socket, Options, User, CbInfo]) ->
process_flag(trap_exit, true),
State0 = initial_state(Role, Host, Port, Socket, Options, User, CbInfo),
try
State = ssl_gen_statem:ssl_config(State0#state.ssl_options,
State = ssl_gen_statem:init_ssl_config(State0#state.ssl_options,
Role, State0),
gen_statem:enter_loop(?MODULE, [], initial_hello, State)
catch
Expand All @@ -178,8 +178,8 @@ init([Role, Host, Port, Socket, Options, User, CbInfo]) ->
gen_statem:enter_loop(?MODULE, [], config_error, EState)
end.
%%====================================================================
%% Handshake
%%====================================================================
%% Handshake
%%====================================================================
renegotiate(#state{static_env = #static_env{role = client}} = State0, Actions) ->
%% Handle same way as if server requested
%% the renegotiation
Expand All @@ -194,15 +194,15 @@ renegotiate(#state{static_env = #static_env{role = server}} = State0, Actions) -
dtls_gen_connection:next_event(hello, no_record, State, Actions ++ MoreActions).

%%--------------------------------------------------------------------
%% State functions
%% State functions
%%--------------------------------------------------------------------
%%--------------------------------------------------------------------
-spec initial_hello(gen_statem:event_type(),
{start, timeout()} | term(), #state{}) ->
gen_statem:state_function_result().
%%--------------------------------------------------------------------
initial_hello(enter, _, State) ->
{keep_state, State};
{keep_state, State};
initial_hello({call, From}, {start, Timeout},
#state{static_env = #static_env{host = Host,
port = Port,
Expand Down
73 changes: 36 additions & 37 deletions lib/ssl/src/ssl.erl
Original file line number Diff line number Diff line change
Expand Up @@ -1599,9 +1599,7 @@ handle_options(Transport, Socket, Opts0, Role, Host) ->
{UserSslOptsList, SockOpts0} = split_options(Opts0, ssl_options()),

Env = #{role => Role, host => Host},
SslOptsPost = process_options(UserSslOptsList, #{}, Env),

SslOpts = maybe_client_warn_no_verify(SslOptsPost, Role),
SslOpts = process_options(UserSslOptsList, #{}, Env),

%% Handle special options
#{protocol := Protocol} = SslOpts,
Expand Down Expand Up @@ -1697,17 +1695,16 @@ validate_versions(dtls, Vsns0) ->

opt_verification(UserOpts, Opts0, #{role := Role} = Env) ->
{Verify, Opts} =
case get_opt_of(verify, [verify_none, verify_peer], verify_none, UserOpts, Opts0) of
{default, verify_none} when Role =:= client ->
{verify_none, Opts0#{warn_verify_none => true, verify => verify_none}};
case get_opt_of(verify, [verify_none, verify_peer], default_verify(Role), UserOpts, Opts0) of
{_, verify_none} ->
{verify_none, Opts0#{verify => verify_none}};
{verify_none, Opts0#{verify => verify_none, verify_fun => {none_verify_fun(), []}}};
{_, verify_peer} ->
%% If 'verify' is changed from verify_none to verify_peer, (via update_options/3)
%% the 'verify_fun' must also be changed to undefined.
%% i.e remove the default verify_none fun
%% i.e remove verify_none fun
{verify_peer, Opts0#{verify => verify_peer, verify_fun => undefined}}
end,
assert_cacerts(Verify, maps:merge(UserOpts, Opts0)),
{_, PartialChain} = get_opt_fun(partial_chain, 1, fun(_) -> unknown_ca end, UserOpts, Opts),

{_, FailNoPeerCert} = get_opt_bool(fail_if_no_peer_cert, false, UserOpts, Opts),
Expand All @@ -1721,9 +1718,16 @@ opt_verification(UserOpts, Opts0, #{role := Role} = Env) ->
fail_if_no_peer_cert => FailNoPeerCert},
Env).

default_verify(client) ->
%% Server authenication is by default requiered
verify_peer;
default_verify(server) ->
%% Client certification is an optional part of the protocol
verify_none.

opt_verify_fun(UserOpts, Opts, _Env) ->
DefVerifyNoneFun = {default_verify_fun(), []},
VerifyFun = case get_opt(verify_fun, DefVerifyNoneFun, UserOpts, Opts) of
%%DefVerifyNoneFun = {default_verify_fun(), []},
VerifyFun = case get_opt(verify_fun, undefined, UserOpts, Opts) of
{_, {F,_} = FA} when is_function(F, 3); is_function(F, 4) ->
FA;
{_, UserFun} when is_function(UserFun, 1) ->
Expand All @@ -1735,22 +1739,22 @@ opt_verify_fun(UserOpts, Opts, _Env) ->
end,
Opts#{verify_fun => VerifyFun}.

default_verify_fun() ->
fun(_, {bad_cert, _}, UserState) ->
none_verify_fun() ->
fun(_, {bad_cert, _}, UserState) ->
{valid, UserState};
(_, {extension, #'Extension'{critical = true}}, UserState) ->
%% This extension is marked as critical, so
%% certificate verification should fail if we don't
%% understand the extension. However, this is
%% `verify_none', so let's accept it anyway.
{valid, UserState};
(_, {extension, _}, UserState) ->
{unknown, UserState};
(_, valid, UserState) ->
{valid, UserState};
(_, {extension, #'Extension'{critical = true}}, UserState) ->
%% This extension is marked as critical, so
%% certificate verification should fail if we don't
%% understand the extension. However, this is
%% `verify_none', so let's accept it anyway.
{valid, UserState};
(_, {extension, _}, UserState) ->
{unknown, UserState};
(_, valid, UserState) ->
{valid, UserState};
(_, valid_peer, UserState) ->
{valid, UserState}
end.
(_, valid_peer, UserState) ->
{valid, UserState}
end.

convert_verify_fun() ->
fun(_,{bad_cert, _} = Reason, OldFun) ->
Expand Down Expand Up @@ -2450,6 +2454,13 @@ role_error(true, ErrorDesc, Option)
when ErrorDesc =:= client_only; ErrorDesc =:= server_only ->
throw_error({option, ErrorDesc, Option}).

assert_cacerts(verify_peer, Options) ->
CaCerts = maps:get(cacerts, Options, undefined),
CaCertsFile = maps:get(cacertfile, Options, undefined),
option_error((CaCerts == undefined) andalso (CaCertsFile == undefined), verify, {missing_dep_cacertfile_or_cacerts});
assert_cacerts(verify_none,_) ->
ok.

option_incompatible(false, _Options) -> ok;
option_incompatible(true, Options) -> option_incompatible(Options).

Expand Down Expand Up @@ -2823,18 +2834,6 @@ add_filter(undefined, Filters) ->
add_filter(Filter, Filters) ->
[Filter | Filters].

maybe_client_warn_no_verify(#{verify := verify_none,
warn_verify_none := true,
log_level := LogLevel} = Opts, client) ->
ssl_logger:log(warning, LogLevel,
#{description => "Server authenticity is not verified since certificate path validation is not enabled",
reason => "The option {verify, verify_peer} and one of the options 'cacertfile' or "
"'cacerts' are required to enable this."}, ?LOCATION),
maps:without([warn_verify_none], Opts);
maybe_client_warn_no_verify(Opts,_) ->
%% Warning not needed. Note client certificate validation is optional in TLS
Opts.

unambiguous_path(Value) ->
AbsName = filename:absname(Value),
UP = case file:read_link(AbsName) of
Expand Down
34 changes: 21 additions & 13 deletions lib/ssl/src/ssl_gen_statem.erl
Original file line number Diff line number Diff line change
Expand Up @@ -38,7 +38,8 @@
init/1]).

%% TLS connection setup
-export([ssl_config/3,
-export([init_ssl_config/3,
ssl_config/3,
connect/8,
handshake/7,
handshake/2,
Expand Down Expand Up @@ -158,11 +159,27 @@ init([_Role, _Host, _Port, _Socket, _TLSOpts, _User, _CbInfo] = InitArgs) ->
%% TLS connection setup
%%====================================================================

%%--------------------------------------------------------------------
-spec init_ssl_config(ssl_options(), client | server, #state{}) -> #state{}.
%%--------------------------------------------------------------------
init_ssl_config(Opts, Role, #state{ssl_options = #{handshake := Handshake},
handshake_env = HsEnv} = State0) ->
ContinueStatus = case Handshake of
hello ->
%% Will pause handshake after hello message to
%% enable user to react to hello extensions
pause;
full ->
Handshake
end,
ssl_config(Opts, Role,
State0#state{handshake_env =
HsEnv#handshake_env{continue_status = ContinueStatus}}).

%%--------------------------------------------------------------------
-spec ssl_config(ssl_options(), client | server, #state{}) -> #state{}.
%%--------------------------------------------------------------------
ssl_config(Opts, Role, #state{static_env = InitStatEnv0,
ssl_options = #{handshake := Handshake},
handshake_env = HsEnv,
connection_env = CEnv} = State0) ->
{ok, #{cert_db_ref := Ref,
Expand All @@ -176,15 +193,6 @@ ssl_config(Opts, Role, #state{static_env = InitStatEnv0,
TimeStamp = erlang:monotonic_time(),
Session = State0#state.session,

ContinueStatus = case Handshake of
hello ->
%% Will pause handshake after hello message to
%% enable user to react to hello extensions
pause;
full ->
Handshake
end,

State0#state{session = Session#session{time_stamp = TimeStamp},
static_env = InitStatEnv0#static_env{
file_ref_db = FileRefHandle,
Expand All @@ -193,8 +201,8 @@ ssl_config(Opts, Role, #state{static_env = InitStatEnv0,
crl_db = CRLDbHandle,
session_cache = CacheHandle
},
handshake_env = HsEnv#handshake_env{diffie_hellman_params = DHParams,
continue_status = ContinueStatus},
handshake_env =
HsEnv#handshake_env{diffie_hellman_params = DHParams},
connection_env = CEnv#connection_env{cert_key_alts = CertKeyAlts},
ssl_options = Opts}.

Expand Down
26 changes: 16 additions & 10 deletions lib/ssl/src/tls_client_connection_1_3.erl
Original file line number Diff line number Diff line change
Expand Up @@ -117,7 +117,7 @@ init([?CLIENT_ROLE, Sender, Host, Port, Socket, Options, User, CbInfo]) ->
Host, Port, Socket,
Options, User, CbInfo),
try
State = ssl_gen_statem:ssl_config(State0#state.ssl_options,
State = ssl_gen_statem:init_ssl_config(State0#state.ssl_options,
?CLIENT_ROLE, State0),
tls_gen_connection:initialize_tls_sender(State),
gen_statem:enter_loop(?MODULE, [], initial_hello, State)
Expand Down Expand Up @@ -178,16 +178,22 @@ user_hello({call, From}, cancel, State) ->
user_canceled),
?FUNCTION_NAME, State);
user_hello({call, From}, {handshake_continue, NewOptions, Timeout},
#state{handshake_env = HSEnv,
#state{handshake_env = #handshake_env{continue_status = pause} = HSEnv,
ssl_options = Options0} = State0) ->
Options = ssl:update_options(NewOptions, ?CLIENT_ROLE, Options0),
State = ssl_gen_statem:ssl_config(Options, ?CLIENT_ROLE, State0),
{next_state, wait_sh, State#state{start_or_recv_from = From,
handshake_env =
HSEnv#handshake_env{continue_status
= continue}
},
[{{timeout, handshake}, Timeout, close}]};
try ssl:update_options(NewOptions, ?CLIENT_ROLE, Options0) of
Options ->
State = ssl_gen_statem:ssl_config(Options, ?CLIENT_ROLE, State0),
{next_state, wait_sh, State#state{start_or_recv_from = From,
handshake_env =
HSEnv#handshake_env{continue_status
= continue}
},
[{{timeout, handshake}, Timeout, close}]}
catch
throw:{error, Reason} ->
gen_statem:reply(From, {error, Reason}),
ssl_gen_statem:handle_own_alert(?ALERT_REC(?FATAL, ?INTERNAL_ERROR, Reason), ?FUNCTION_NAME, State0)
end;
user_hello(Type, Msg, State) ->
tls_gen_connection_1_3:user_hello(Type, Msg, State).

Expand Down
2 changes: 1 addition & 1 deletion lib/ssl/src/tls_connection.erl
Original file line number Diff line number Diff line change
Expand Up @@ -149,7 +149,7 @@ init([Role, Sender, Host, Port, Socket, Options, User, CbInfo]) ->
},
connection_env = #connection_env{cert_key_alts = CertKeyAlts},
ssl_options = SslOptions,
session = Session0} = ssl_gen_statem:ssl_config(State0#state.ssl_options, Role, State0),
session = Session0} = ssl_gen_statem:init_ssl_config(State0#state.ssl_options, Role, State0),
State = case Role of
client ->
CertKeyPairs = ssl_certificate:available_cert_key_pairs(CertKeyAlts),
Expand Down
18 changes: 12 additions & 6 deletions lib/ssl/src/tls_dtls_connection.erl
Original file line number Diff line number Diff line change
Expand Up @@ -174,12 +174,18 @@ user_hello({call, From}, {handshake_continue, NewOptions, Timeout},
#state{static_env = #static_env{role = Role},
handshake_env = HSEnv,
ssl_options = Options0} = State0) ->
Options = ssl:update_options(NewOptions, Role, Options0),
State = ssl_gen_statem:ssl_config(Options, Role, State0),
{next_state, hello, State#state{start_or_recv_from = From,
handshake_env = HSEnv#handshake_env{continue_status = continue}
},
[{{timeout, handshake}, Timeout, close}]};
try ssl:update_options(NewOptions, Role, Options0) of
Options ->
State = ssl_gen_statem:ssl_config(Options, Role, State0),
{next_state, hello, State#state{start_or_recv_from = From,
handshake_env = HSEnv#handshake_env{continue_status = continue}
},
[{{timeout, handshake}, Timeout, close}]}
catch
throw:{error, Reason} ->
gen_statem:reply(From, {error, Reason}),
ssl_gen_statem:handle_own_alert(?ALERT_REC(?FATAL, ?INTERNAL_ERROR, Reason), ?FUNCTION_NAME, State0)
end;
user_hello(info, {'DOWN', _, _, _, _} = Event, State) ->
ssl_gen_statem:handle_info(Event, ?FUNCTION_NAME, State);
user_hello(_, _, _) ->
Expand Down
36 changes: 21 additions & 15 deletions lib/ssl/src/tls_server_connection_1_3.erl
Original file line number Diff line number Diff line change
Expand Up @@ -109,7 +109,7 @@ init([?SERVER_ROLE, Sender, Host, Port, Socket, Options, User, CbInfo]) ->
tls_gen_connection_1_3:initial_state(?SERVER_ROLE, Sender,
Host, Port, Socket, Options, User, CbInfo),
try
State = ssl_gen_statem:ssl_config(State0#state.ssl_options, ?SERVER_ROLE, State0),
State = ssl_gen_statem:init_ssl_config(State0#state.ssl_options, ?SERVER_ROLE, State0),
tls_gen_connection:initialize_tls_sender(State),
gen_statem:enter_loop(?MODULE, [], initial_hello, State)
catch throw:Error ->
Expand Down Expand Up @@ -170,20 +170,26 @@ user_hello({call, From}, cancel, State) ->
user_hello({call, From}, {handshake_continue, NewOptions, Timeout},
#state{handshake_env = #handshake_env{continue_status = {pause, ClientVersions}} = HSEnv,
ssl_options = Options0} = State0) ->
Options = #{versions := Versions} = ssl:update_options(NewOptions, ?SERVER_ROLE, Options0),
State = ssl_gen_statem:ssl_config(Options, ?SERVER_ROLE, State0),
case ssl_handshake:select_supported_version(ClientVersions, Versions) of
{3,4} ->
{next_state, start, State#state{start_or_recv_from = From,
handshake_env = HSEnv#handshake_env{continue_status = continue}},
[{{timeout, handshake}, Timeout, close}]};
undefined ->
ssl_gen_statem:handle_own_alert(?ALERT_REC(?FATAL, ?PROTOCOL_VERSION), ?FUNCTION_NAME, State);
_Else ->
{next_state, hello, State#state{start_or_recv_from = From,
handshake_env = HSEnv#handshake_env{continue_status = continue}},
[{change_callback_module, tls_connection},
{{timeout, handshake}, Timeout, close}]}
try ssl:update_options(NewOptions, ?SERVER_ROLE, Options0) of
Options = #{versions := Versions} ->
State = ssl_gen_statem:ssl_config(Options, ?SERVER_ROLE, State0),
case ssl_handshake:select_supported_version(ClientVersions, Versions) of
{3,4} ->
{next_state, start, State#state{start_or_recv_from = From,
handshake_env = HSEnv#handshake_env{continue_status = continue}},
[{{timeout, handshake}, Timeout, close}]};
undefined ->
ssl_gen_statem:handle_own_alert(?ALERT_REC(?FATAL, ?PROTOCOL_VERSION), ?FUNCTION_NAME, State);
_Else ->
{next_state, hello, State#state{start_or_recv_from = From,
handshake_env = HSEnv#handshake_env{continue_status = continue}},
[{change_callback_module, tls_connection},
{{timeout, handshake}, Timeout, close}]}
end
catch
throw:{error, Reason} ->
gen_statem:reply(From, {error, Reason}),
ssl_gen_statem:handle_own_alert(?ALERT_REC(?FATAL, ?INTERNAL_ERROR, Reason), ?FUNCTION_NAME, State0)
end;
user_hello(Type, Msg, State) ->
tls_gen_connection_1_3:user_hello(Type, Msg, State).
Expand Down
6 changes: 3 additions & 3 deletions lib/ssl/test/dtls_api_SUITE.erl
Original file line number Diff line number Diff line change
Expand Up @@ -191,7 +191,7 @@ dtls_listen_reopen() ->
[{doc, "Test that you close a DTLS 'listner' socket and open a new one for the same port"}].

dtls_listen_reopen(Config) when is_list(Config) ->
ClientOpts = ssl_test_lib:ssl_options(client_rsa_opts, Config),
ClientOpts = ssl_test_lib:ssl_options(client_rsa_verify_opts, Config),
ServerOpts = ssl_test_lib:ssl_options(server_rsa_opts, Config),
{_, ServerNode, Hostname} = ssl_test_lib:run_where(Config),

Expand Down Expand Up @@ -356,7 +356,7 @@ client_restarts() ->
[{doc, "Test re-connection "}].

client_restarts(Config) ->
ClientOpts0 = ssl_test_lib:ssl_options(client_rsa_opts, Config),
ClientOpts0 = ssl_test_lib:ssl_options(client_rsa_verify_opts, Config),
ServerOpts = ssl_test_lib:ssl_options(server_rsa_verify_opts, Config),
{ClientNode, ServerNode, Hostname} = ssl_test_lib:run_where(Config),

Expand Down Expand Up @@ -435,7 +435,7 @@ client_restarts_multiple_acceptors(Config) ->
%% closed.
%% Then do a new openssl connect with the same client port.

ClientOpts0 = ssl_test_lib:ssl_options(client_rsa_opts, Config),
ClientOpts0 = ssl_test_lib:ssl_options(client_rsa_verify_opts, Config),
ServerOpts = ssl_test_lib:ssl_options(server_rsa_verify_opts, Config),
{ClientNode, ServerNode, Hostname} = ssl_test_lib:run_where(Config),

Expand Down
Loading

0 comments on commit bb3603d

Please sign in to comment.