Skip to content
Merged
Show file tree
Hide file tree
Changes from all commits
Commits
File filter

Filter by extension

Filter by extension

Conversations
Failed to load comments.
Loading
Jump to
Jump to file
Failed to load files.
Loading
Diff view
Diff view
40 changes: 37 additions & 3 deletions lib/ssl/src/ssl.erl
Original file line number Diff line number Diff line change
Expand Up @@ -1621,7 +1621,8 @@ ssl_options() ->
-spec update_options([any()], client | server, map()) -> map().
update_options(Opts, Role, InheritedSslOpts) when is_map(InheritedSslOpts) ->
{UserSslOpts, _} = split_options(Opts, ssl_options()),
process_options(UserSslOpts, InheritedSslOpts, #{role => Role}).
Env = #{role => Role, validate_certs_or_anon_ciphers => Role == server},
process_options(UserSslOpts, InheritedSslOpts, Env).

process_options(UserSslOpts, SslOpts0, Env) ->
%% Reverse option list so we get the last set option if set twice,
Expand All @@ -1646,6 +1647,7 @@ process_options(UserSslOpts, SslOpts0, Env) ->
SslOpts17 = opt_handshake(UserSslOptsMap, SslOpts16, Env),
SslOpts18 = opt_use_srtp(UserSslOptsMap, SslOpts17, Env),
SslOpts = opt_process(UserSslOptsMap, SslOpts18, Env),
validate_server_cert_opts(SslOpts, Env),
SslOpts.

-spec handle_options([any()], client | server, undefined|host()) -> {ok, #config{}}.
Expand All @@ -1655,8 +1657,10 @@ handle_options(Opts, Role, Host) ->
%% Handle all options in listen, connect and handshake
handle_options(Transport, Socket, Opts0, Role, Host) ->
{UserSslOptsList, SockOpts0} = split_options(Opts0, ssl_options()),

Env = #{role => Role, host => Host},
NeedValidate = not (Socket == undefined) andalso Role =:= server, %% handshake options
Env = #{role => Role, host => Host,
validate_certs_or_anon_ciphers => NeedValidate
},
SslOpts = process_options(UserSslOptsList, #{}, Env),

%% Handle special options
Expand Down Expand Up @@ -2614,6 +2618,36 @@ validate_filename([_|_] = FN, _Option) ->
validate_filename(FN, Option) ->
option_error(Option, FN).

validate_server_cert_opts(_Opts, #{validate_certs_or_anon_ciphers := false}) ->
ok;
validate_server_cert_opts(#{certs_keys := [_|_]=CertsKeys, ciphers := CPHS, versions := Versions}, _) ->
validate_certs_or_anon_ciphers(CertsKeys, CPHS, Versions);
validate_server_cert_opts(#{ciphers := CPHS, versions := Versions}, _) ->
validate_anon_ciphers(CPHS, Versions).

validate_certs_or_anon_ciphers(CertsKeys, Ciphers, Versions) ->
CheckCertsAndKeys =
fun(Map) ->
(maps:is_key(cert, Map) orelse maps:is_key(certfile, Map))
andalso (maps:is_key(key, Map) orelse maps:is_key(keyfile, Map))
end,
case lists:any(CheckCertsAndKeys, CertsKeys) of
true -> ok;
false -> validate_anon_ciphers(Ciphers, Versions)
end.

validate_anon_ciphers(Ciphers, Versions) ->
MakeSet = fun(Version, Acc) ->
Set = sets:from_list(ssl_cipher:anonymous_suites(Version), [{version, 2}]),
sets:union(Set, Acc)
end,
Anonymous = lists:foldl(MakeSet, sets:new([{version, 2}]), Versions),
CiphersSet = sets:from_list(Ciphers, [{version,2}]),
case sets:is_disjoint(Anonymous, CiphersSet) of
false -> ok;
true -> option_error(certs_keys, cert_and_key_required)
end.

%% Do not allow configuration of TLS 1.3 with a gap where TLS 1.2 is not supported
%% as that configuration can trigger the built in version downgrade protection
%% mechanism and the handshake can fail with an Illegal Parameter alert.
Expand Down
12 changes: 6 additions & 6 deletions lib/ssl/src/ssl_cipher.erl
Original file line number Diff line number Diff line change
Expand Up @@ -344,15 +344,15 @@ tls_legacy_suites(Version) ->
%%--------------------------------------------------------------------

anonymous_suites(Version) when ?TLS_1_X(Version) ->
SuitesToTest = anonymous_suite_to_test(Version),
lists:flatmap(fun tls_v1:exclusive_anonymous_suites/1, SuitesToTest);
Versions = versions_included(Version),
lists:flatmap(fun tls_v1:exclusive_anonymous_suites/1, Versions);
anonymous_suites(Version) when ?DTLS_1_X(Version) ->
dtls_v1:anonymous_suites(Version).

anonymous_suite_to_test(?TLS_1_0) -> [?TLS_1_0];
anonymous_suite_to_test(?TLS_1_1) -> [?TLS_1_1, ?TLS_1_0];
anonymous_suite_to_test(?TLS_1_2) -> [?TLS_1_2, ?TLS_1_1, ?TLS_1_0];
anonymous_suite_to_test(?TLS_1_3) -> [?TLS_1_3].
versions_included(?TLS_1_0) -> [?TLS_1_0];
versions_included(?TLS_1_1) -> [?TLS_1_1, ?TLS_1_0];
versions_included(?TLS_1_2) -> [?TLS_1_2, ?TLS_1_1, ?TLS_1_0];
versions_included(?TLS_1_3) -> [?TLS_1_3].

%%--------------------------------------------------------------------
-spec filter(undefined | binary(), [ssl_cipher_format:cipher_suite()],
Expand Down
90 changes: 74 additions & 16 deletions lib/ssl/test/ssl_api_SUITE.erl
Original file line number Diff line number Diff line change
Expand Up @@ -1684,9 +1684,10 @@ close_with_timeout(Config) when is_list(Config) ->
close_in_error_state() ->
[{doc,"Special case of closing socket in error state"}].
close_in_error_state(Config) when is_list(Config) ->
ServerOpts0 = ssl_test_lib:ssl_options(server_opts, Config),
ServerOpts0 = ssl_test_lib:ssl_options(server_rsa_opts, Config),
ServerOpts = [{cacertfile, "foo.pem"} | proplists:delete(cacertfile, ServerOpts0)],
ClientOpts = ssl_test_lib:ssl_options(client_opts, Config),

_ = spawn(?MODULE, run_error_server_close, [[self() | ServerOpts]]),
receive
{_Pid, Port} ->
Expand All @@ -1703,7 +1704,7 @@ close_in_error_state(Config) when is_list(Config) ->
call_in_error_state() ->
[{doc,"Special case of call error handling"}].
call_in_error_state(Config) when is_list(Config) ->
ServerOpts0 = ssl_test_lib:ssl_options(server_opts, Config),
ServerOpts0 = ssl_test_lib:ssl_options(server_rsa_opts, Config),
ClientOpts = ssl_test_lib:ssl_options(client_opts, Config),
ServerOpts = [{cacertfile, "foo.pem"} | proplists:delete(cacertfile, ServerOpts0)],
Pid = spawn(?MODULE, run_error_server, [[self() | ServerOpts]]),
Expand Down Expand Up @@ -2187,27 +2188,44 @@ options_whitebox() ->
customize_defaults(Opts, Role, Host) ->
%% In many options test scenarios we do not care about verifcation options
%% but the client now requiers verification options by default.
ClientIgnorDef = case proplists:get_value(verify, Opts, undefined) of
undefined when Role == client ->
[{verify, verify_none}];
_ ->
[]
end,
DefOpts = case Role of
client ->
case proplists:get_value(verify, Opts, undefined) of
undefined -> [{verify, verify_none}];
_ -> []
end;
server ->
Ciphers = proplists:get_value(ciphers, Opts, undefined),
Cert = proplists:get_value(cert, Opts, undefined),
Key = proplists:get_value(key, Opts, undefined),
CertsKeys = proplists:get_value(certs_keys, Opts, undefined),
NoCertOrKeys = Cert == undefined orelse Key == undefined andalso
CertsKeys == undefined,
Comment on lines +2202 to +2203
Copy link
Contributor

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

Please do something with clarity here. More parenthesis maybe? IMHO this expects too much knowledge and being awake from the reader ;-)

if Ciphers == undefined andalso NoCertOrKeys ->
[{certs_keys, [#{cert => <<>>, key => {rsa, <<>>}}]}];
true ->
[]
end
end,
NoVerify = case Role of
client -> [{verify, verify_none}|DefOpts];
server -> DefOpts
end,
case proplists:get_value(protocol, Opts, tls) of
dtls ->
{ok, #config{ssl=DOpts}} = ssl:handle_options([{verify, verify_none}, {protocol, dtls}], Role, Host),
{DOpts, ClientIgnorDef ++ Opts};
{ok, #config{ssl=DOpts}} = ssl:handle_options([{protocol, dtls}|NoVerify], Role, Host),
{DOpts, DefOpts ++ Opts};
tls ->
{ok, #config{ssl=DOpts}} = ssl:handle_options([{verify, verify_none}], Role, Host),
{ok, #config{ssl=DOpts}} = ssl:handle_options(NoVerify, Role, Host),
case proplists:get_value(versions, Opts) of
undefined ->
{DOpts, ClientIgnorDef ++ [{versions, ['tlsv1.2','tlsv1.3']}|Opts]};
{DOpts, DefOpts ++ [{versions, ['tlsv1.2','tlsv1.3']}|Opts]};
_ ->
{DOpts, ClientIgnorDef ++ Opts}
{DOpts, DefOpts ++ Opts}
end;
_ ->
{ok, #config{ssl=DOpts}} = ssl:handle_options(ClientIgnorDef, Role, Host),
{DOpts, ClientIgnorDef ++ Opts}
{ok, #config{ssl=DOpts}} = ssl:handle_options(NoVerify, Role, Host),
{DOpts, DefOpts ++ Opts}
end.

-define(OK(EXP, Opts, Role), ?OK(EXP,Opts, Role, [])).
Expand Down Expand Up @@ -2279,6 +2297,41 @@ customize_defaults(Opts, Role, Host) ->
end
end()).

-define(ERR_UPD(EXP, Opts, Role),
fun() ->
Host = "dummy.host.org",
{__DefOpts, __Opts} = customize_defaults(Opts, Role, Host),
try ssl:handle_options(__Opts, Role, Host) of
{ok, #config{}} ->
ok;
Other ->
?CT_PAL("ssl:handle_options(~0p,~0p,~0p).",[__Opts,Role,Host]),
error({unexpected, Other})
catch
throw:{error,{options,{insufficient_crypto_support,{'tlsv1.3',_}}}} -> ignored;
C:Other:ST ->
?CT_PAL("ssl:handle_options(~0p,~0p,~0p).",[__Opts,Role,Host]),
error({unexpected, C, Other,ST})
end,
try ssl:update_options(__Opts, Role, __DefOpts) of
Other2 ->
?CT_PAL("{ok,Cfg} = ssl:handle_options([],~p,~p),"
"ssl:update_options(~p,~p, element(2,Cfg)).",
[Role,Host,__Opts,Role]),
error({unexpected, Other2})
catch
throw:{error,{options,{insufficient_crypto_support,{'tlsv1.3',_}}}} -> ignored;
throw:{error, {options, EXP}} -> ok;
throw:{error, EXP} -> ok;
C2:Other2:ST2 ->
?CT_PAL("{ok,Cfg} = ssl:handle_options([],~p,~p),"
"ssl:update_options(~p,~p, element(2,Cfg)).",
[Role,Host,__Opts,Role]),
error({unexpected, C2, Other2,ST2})
end
end()).


options_whitebox(Config) when is_list(Config) ->
Cert = proplists:get_value(cert, ssl_test_lib:ssl_options(server_rsa_der_opts, Config)),
true = is_binary(Cert),
Expand Down Expand Up @@ -2520,6 +2573,7 @@ options_cert(Config) -> %% cert[file] cert_keys keys password
?ERR({cert, #{}}, [{cert, #{}}], client),
?ERR({certfile, cert}, [{certfile, cert}], client),
?ERR({certs_keys, #{}}, [{certs_keys, #{}}], client),
?ERR_UPD({certs_keys, cert_and_key_required}, [{certs_keys, []}], server),
?ERR({keyfile, #{}}, [{keyfile, #{}}], client),
?ERR({key, <<>>}, [{key, <<>>}], client),
?ERR({password, _}, [{password, fun(Arg) -> Arg end}], client),
Expand Down Expand Up @@ -2548,7 +2602,11 @@ options_ciphers(_Config) ->
?OK(#{ciphers := [_|_]}, [{ciphers, "RC4-SHA:RC4-MD5"}], client),
?OK(#{ciphers := [_|_]}, [{ciphers, ["RC4-SHA", "RC4-MD5"]}], client),

%% FIXME extend this
?OK(#{ciphers := [_|_]}, [{ciphers, ["TLS_DH_anon_WITH_AES_256_CBC_SHA256"]}], server),
%% Errors
?ERR({ciphers, _}, [{ciphers, "foobar:RC4-MD5"}], client),
?ERR({ciphers, _}, [{ciphers, ["RC4-SHA:RC4-MD5", "RC4-SHA:RC4-MD5"]}], client),
?ERR_UPD({certs_keys, cert_and_key_required}, [{ciphers, "RC4-SHA:RC4-MD5"}], server),
ok.

options_client_renegotiation(_Config) ->
Expand Down
43 changes: 24 additions & 19 deletions lib/ssl/test/tls_api_SUITE.erl
Original file line number Diff line number Diff line change
Expand Up @@ -193,8 +193,9 @@ init_per_suite(Config0) ->
try crypto:start() of
ok ->
ssl_test_lib:clean_start(),
ssl_test_lib:make_rsa_cert_with_protected_keyfile(Config0,
?CORRECT_PASSWORD)
Config1 = ssl_test_lib:make_rsa_cert_with_protected_keyfile(Config0,
?CORRECT_PASSWORD),
ssl_test_lib:make_dsa_cert(Config1)
catch _:_ ->
{skip, "Crypto did not start"}
end.
Expand Down Expand Up @@ -299,6 +300,7 @@ tls_upgrade_new_opts_with_sni_fun() ->
tls_upgrade_new_opts_with_sni_fun(Config) when is_list(Config) ->
ClientOpts = ssl_test_lib:ssl_options(client_rsa_verify_opts, Config),
ServerOpts = ssl_test_lib:ssl_options(server_rsa_opts, Config),
ServerDsaOpts = ssl_test_lib:ssl_options(server_dsa_opts, Config),
{ClientNode, ServerNode, Hostname} = ssl_test_lib:run_where(Config),
TcpOpts = [binary, {reuseaddr, true}],
Version = ssl_test_lib:protocol_version(Config),
Expand All @@ -309,23 +311,26 @@ tls_upgrade_new_opts_with_sni_fun(Config) when is_list(Config) ->
{ciphers, Ciphers},
{verify, verify_peer}],

Server = ssl_test_lib:start_upgrade_server([{node, ServerNode}, {port, 0},
{from, self()},
{mfa, {?MODULE,
upgrade_result, []}},
{tcp_options,
[{active, false} | TcpOpts]},
{ssl_options, [{versions, [Version |NewVersions]}, {sni_fun, fun(_SNI) -> ServerOpts ++ NewOpts end}]}]),
Server = ssl_test_lib:start_upgrade_server(
[{node, ServerNode}, {port, 0},
{from, self()},
{mfa, {?MODULE, upgrade_result, []}},
{tcp_options,
[{active, false} | TcpOpts]},
{ssl_options, [{versions, [Version |NewVersions]},
{sni_fun, fun(_SNI) -> ServerOpts ++ NewOpts end}
| ServerDsaOpts]}]),
Port = ssl_test_lib:inet_port(Server),
Client = ssl_test_lib:start_upgrade_client([{node, ClientNode},
{port, Port},
{host, Hostname},
{from, self()},
{mfa, {?MODULE, upgrade_result, []}},
{tcp_options, [binary]},
{ssl_options, [{versions, [Version |NewVersions]},
{ciphers, Ciphers},
{server_name_indication, Hostname} | ClientOpts]}]),
Client = ssl_test_lib:start_upgrade_client(
[{node, ClientNode},
{port, Port},
{host, Hostname},
{from, self()},
{mfa, {?MODULE, upgrade_result, []}},
{tcp_options, [binary]},
{ssl_options, [{versions, [Version |NewVersions]},
{ciphers, Ciphers},
{server_name_indication, Hostname} | ClientOpts]}]),

?CT_LOG("Client ~p Server ~p ~n", [Client, Server]),

Expand Down Expand Up @@ -515,7 +520,7 @@ tls_client_closes_socket() ->
[{doc,"Test what happens when client closes socket before handshake is completed"}].

tls_client_closes_socket(Config) when is_list(Config) ->
ServerOpts = ssl_test_lib:ssl_options(server_opts, Config),
ServerOpts = ssl_test_lib:ssl_options(server_rsa_opts, Config),
{ClientNode, ServerNode, Hostname} = ssl_test_lib:run_where(Config),
TcpOpts = [binary, {reuseaddr, true}],

Expand Down