Skip to content

Commit 51ad60f

Browse files
committed
ssl: Error server options when no certs
When running a ssl server the user must provide cert and key or use an anonymous cipher in tls1.2. Otherwise no connection will succeed. Add an option check so that this is dectected earlier, and gives the user an appropriate error instead of just failing each connection attempt. To keep backwards compatibility the check is only done in handshake, since it is allowed to use an empty (or minimal) option list in ssl:listen and provide the options in handshake later.
1 parent c31eabd commit 51ad60f

File tree

4 files changed

+141
-44
lines changed

4 files changed

+141
-44
lines changed

lib/ssl/src/ssl.erl

Lines changed: 37 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -1621,7 +1621,8 @@ ssl_options() ->
16211621
-spec update_options([any()], client | server, map()) -> map().
16221622
update_options(Opts, Role, InheritedSslOpts) when is_map(InheritedSslOpts) ->
16231623
{UserSslOpts, _} = split_options(Opts, ssl_options()),
1624-
process_options(UserSslOpts, InheritedSslOpts, #{role => Role}).
1624+
Env = #{role => Role, validate_certs_or_anon_ciphers => Role == server},
1625+
process_options(UserSslOpts, InheritedSslOpts, Env).
16251626

16261627
process_options(UserSslOpts, SslOpts0, Env) ->
16271628
%% Reverse option list so we get the last set option if set twice,
@@ -1646,6 +1647,7 @@ process_options(UserSslOpts, SslOpts0, Env) ->
16461647
SslOpts17 = opt_handshake(UserSslOptsMap, SslOpts16, Env),
16471648
SslOpts18 = opt_use_srtp(UserSslOptsMap, SslOpts17, Env),
16481649
SslOpts = opt_process(UserSslOptsMap, SslOpts18, Env),
1650+
validate_server_cert_opts(SslOpts, Env),
16491651
SslOpts.
16501652

16511653
-spec handle_options([any()], client | server, undefined|host()) -> {ok, #config{}}.
@@ -1655,8 +1657,10 @@ handle_options(Opts, Role, Host) ->
16551657
%% Handle all options in listen, connect and handshake
16561658
handle_options(Transport, Socket, Opts0, Role, Host) ->
16571659
{UserSslOptsList, SockOpts0} = split_options(Opts0, ssl_options()),
1658-
1659-
Env = #{role => Role, host => Host},
1660+
NeedValidate = not (Socket == undefined) andalso Role =:= server, %% handshake options
1661+
Env = #{role => Role, host => Host,
1662+
validate_certs_or_anon_ciphers => NeedValidate
1663+
},
16601664
SslOpts = process_options(UserSslOptsList, #{}, Env),
16611665

16621666
%% Handle special options
@@ -2614,6 +2618,36 @@ validate_filename([_|_] = FN, _Option) ->
26142618
validate_filename(FN, Option) ->
26152619
option_error(Option, FN).
26162620

2621+
validate_server_cert_opts(_Opts, #{validate_certs_or_anon_ciphers := false}) ->
2622+
ok;
2623+
validate_server_cert_opts(#{certs_keys := [_|_]=CertsKeys, ciphers := CPHS, versions := Versions}, _) ->
2624+
validate_certs_or_anon_ciphers(CertsKeys, CPHS, Versions);
2625+
validate_server_cert_opts(#{ciphers := CPHS, versions := Versions}, _) ->
2626+
validate_anon_ciphers(CPHS, Versions).
2627+
2628+
validate_certs_or_anon_ciphers(CertsKeys, Ciphers, Versions) ->
2629+
CheckCertsAndKeys =
2630+
fun(Map) ->
2631+
(maps:is_key(cert, Map) orelse maps:is_key(certfile, Map))
2632+
andalso (maps:is_key(key, Map) orelse maps:is_key(keyfile, Map))
2633+
end,
2634+
case lists:any(CheckCertsAndKeys, CertsKeys) of
2635+
true -> ok;
2636+
false -> validate_anon_ciphers(Ciphers, Versions)
2637+
end.
2638+
2639+
validate_anon_ciphers(Ciphers, Versions) ->
2640+
MakeSet = fun(Version, Acc) ->
2641+
Set = sets:from_list(ssl_cipher:anonymous_suites(Version), [{version, 2}]),
2642+
sets:union(Set, Acc)
2643+
end,
2644+
Anonymous = lists:foldl(MakeSet, sets:new([{version, 2}]), Versions),
2645+
CiphersSet = sets:from_list(Ciphers, [{version,2}]),
2646+
case sets:is_disjoint(Anonymous, CiphersSet) of
2647+
false -> ok;
2648+
true -> option_error(certs_keys, no_cert_or_key_given)
2649+
end.
2650+
26172651
%% Do not allow configuration of TLS 1.3 with a gap where TLS 1.2 is not supported
26182652
%% as that configuration can trigger the built in version downgrade protection
26192653
%% mechanism and the handshake can fail with an Illegal Parameter alert.

lib/ssl/src/ssl_cipher.erl

Lines changed: 6 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -344,15 +344,15 @@ tls_legacy_suites(Version) ->
344344
%%--------------------------------------------------------------------
345345

346346
anonymous_suites(Version) when ?TLS_1_X(Version) ->
347-
SuitesToTest = anonymous_suite_to_test(Version),
348-
lists:flatmap(fun tls_v1:exclusive_anonymous_suites/1, SuitesToTest);
347+
Versions = versions_included(Version),
348+
lists:flatmap(fun tls_v1:exclusive_anonymous_suites/1, Versions);
349349
anonymous_suites(Version) when ?DTLS_1_X(Version) ->
350350
dtls_v1:anonymous_suites(Version).
351351

352-
anonymous_suite_to_test(?TLS_1_0) -> [?TLS_1_0];
353-
anonymous_suite_to_test(?TLS_1_1) -> [?TLS_1_1, ?TLS_1_0];
354-
anonymous_suite_to_test(?TLS_1_2) -> [?TLS_1_2, ?TLS_1_1, ?TLS_1_0];
355-
anonymous_suite_to_test(?TLS_1_3) -> [?TLS_1_3].
352+
versions_included(?TLS_1_0) -> [?TLS_1_0];
353+
versions_included(?TLS_1_1) -> [?TLS_1_1, ?TLS_1_0];
354+
versions_included(?TLS_1_2) -> [?TLS_1_2, ?TLS_1_1, ?TLS_1_0];
355+
versions_included(?TLS_1_3) -> [?TLS_1_3].
356356

357357
%%--------------------------------------------------------------------
358358
-spec filter(undefined | binary(), [ssl_cipher_format:cipher_suite()],

lib/ssl/test/ssl_api_SUITE.erl

Lines changed: 74 additions & 16 deletions
Original file line numberDiff line numberDiff line change
@@ -1684,9 +1684,10 @@ close_with_timeout(Config) when is_list(Config) ->
16841684
close_in_error_state() ->
16851685
[{doc,"Special case of closing socket in error state"}].
16861686
close_in_error_state(Config) when is_list(Config) ->
1687-
ServerOpts0 = ssl_test_lib:ssl_options(server_opts, Config),
1687+
ServerOpts0 = ssl_test_lib:ssl_options(server_rsa_opts, Config),
16881688
ServerOpts = [{cacertfile, "foo.pem"} | proplists:delete(cacertfile, ServerOpts0)],
16891689
ClientOpts = ssl_test_lib:ssl_options(client_opts, Config),
1690+
16901691
_ = spawn(?MODULE, run_error_server_close, [[self() | ServerOpts]]),
16911692
receive
16921693
{_Pid, Port} ->
@@ -1703,7 +1704,7 @@ close_in_error_state(Config) when is_list(Config) ->
17031704
call_in_error_state() ->
17041705
[{doc,"Special case of call error handling"}].
17051706
call_in_error_state(Config) when is_list(Config) ->
1706-
ServerOpts0 = ssl_test_lib:ssl_options(server_opts, Config),
1707+
ServerOpts0 = ssl_test_lib:ssl_options(server_rsa_opts, Config),
17071708
ClientOpts = ssl_test_lib:ssl_options(client_opts, Config),
17081709
ServerOpts = [{cacertfile, "foo.pem"} | proplists:delete(cacertfile, ServerOpts0)],
17091710
Pid = spawn(?MODULE, run_error_server, [[self() | ServerOpts]]),
@@ -2187,27 +2188,44 @@ options_whitebox() ->
21872188
customize_defaults(Opts, Role, Host) ->
21882189
%% In many options test scenarios we do not care about verifcation options
21892190
%% but the client now requiers verification options by default.
2190-
ClientIgnorDef = case proplists:get_value(verify, Opts, undefined) of
2191-
undefined when Role == client ->
2192-
[{verify, verify_none}];
2193-
_ ->
2194-
[]
2195-
end,
2191+
DefOpts = case Role of
2192+
client ->
2193+
case proplists:get_value(verify, Opts, undefined) of
2194+
undefined -> [{verify, verify_none}];
2195+
_ -> []
2196+
end;
2197+
server ->
2198+
Ciphers = proplists:get_value(ciphers, Opts, undefined),
2199+
Cert = proplists:get_value(cert, Opts, undefined),
2200+
Key = proplists:get_value(key, Opts, undefined),
2201+
CertsKeys = proplists:get_value(certs_keys, Opts, undefined),
2202+
NoCertOrKeys = Cert == undefined orelse Key == undefined andalso
2203+
CertsKeys == undefined,
2204+
if Ciphers == undefined andalso NoCertOrKeys ->
2205+
[{certs_keys, [#{cert => <<>>, key => {rsa, <<>>}}]}];
2206+
true ->
2207+
[]
2208+
end
2209+
end,
2210+
NoVerify = case Role of
2211+
client -> [{verify, verify_none}|DefOpts];
2212+
server -> DefOpts
2213+
end,
21962214
case proplists:get_value(protocol, Opts, tls) of
21972215
dtls ->
2198-
{ok, #config{ssl=DOpts}} = ssl:handle_options([{verify, verify_none}, {protocol, dtls}], Role, Host),
2199-
{DOpts, ClientIgnorDef ++ Opts};
2216+
{ok, #config{ssl=DOpts}} = ssl:handle_options([{protocol, dtls}|NoVerify], Role, Host),
2217+
{DOpts, DefOpts ++ Opts};
22002218
tls ->
2201-
{ok, #config{ssl=DOpts}} = ssl:handle_options([{verify, verify_none}], Role, Host),
2219+
{ok, #config{ssl=DOpts}} = ssl:handle_options(NoVerify, Role, Host),
22022220
case proplists:get_value(versions, Opts) of
22032221
undefined ->
2204-
{DOpts, ClientIgnorDef ++ [{versions, ['tlsv1.2','tlsv1.3']}|Opts]};
2222+
{DOpts, DefOpts ++ [{versions, ['tlsv1.2','tlsv1.3']}|Opts]};
22052223
_ ->
2206-
{DOpts, ClientIgnorDef ++ Opts}
2224+
{DOpts, DefOpts ++ Opts}
22072225
end;
22082226
_ ->
2209-
{ok, #config{ssl=DOpts}} = ssl:handle_options(ClientIgnorDef, Role, Host),
2210-
{DOpts, ClientIgnorDef ++ Opts}
2227+
{ok, #config{ssl=DOpts}} = ssl:handle_options(NoVerify, Role, Host),
2228+
{DOpts, DefOpts ++ Opts}
22112229
end.
22122230

22132231
-define(OK(EXP, Opts, Role), ?OK(EXP,Opts, Role, [])).
@@ -2279,6 +2297,41 @@ customize_defaults(Opts, Role, Host) ->
22792297
end
22802298
end()).
22812299

2300+
-define(ERR_UPD(EXP, Opts, Role),
2301+
fun() ->
2302+
Host = "dummy.host.org",
2303+
{__DefOpts, __Opts} = customize_defaults(Opts, Role, Host),
2304+
try ssl:handle_options(__Opts, Role, Host) of
2305+
{ok, #config{}} ->
2306+
ok;
2307+
Other ->
2308+
?CT_PAL("ssl:handle_options(~0p,~0p,~0p).",[__Opts,Role,Host]),
2309+
error({unexpected, Other})
2310+
catch
2311+
throw:{error,{options,{insufficient_crypto_support,{'tlsv1.3',_}}}} -> ignored;
2312+
C:Other:ST ->
2313+
?CT_PAL("ssl:handle_options(~0p,~0p,~0p).",[__Opts,Role,Host]),
2314+
error({unexpected, C, Other,ST})
2315+
end,
2316+
try ssl:update_options(__Opts, Role, __DefOpts) of
2317+
Other2 ->
2318+
?CT_PAL("{ok,Cfg} = ssl:handle_options([],~p,~p),"
2319+
"ssl:update_options(~p,~p, element(2,Cfg)).",
2320+
[Role,Host,__Opts,Role]),
2321+
error({unexpected, Other2})
2322+
catch
2323+
throw:{error,{options,{insufficient_crypto_support,{'tlsv1.3',_}}}} -> ignored;
2324+
throw:{error, {options, EXP}} -> ok;
2325+
throw:{error, EXP} -> ok;
2326+
C2:Other2:ST2 ->
2327+
?CT_PAL("{ok,Cfg} = ssl:handle_options([],~p,~p),"
2328+
"ssl:update_options(~p,~p, element(2,Cfg)).",
2329+
[Role,Host,__Opts,Role]),
2330+
error({unexpected, C2, Other2,ST2})
2331+
end
2332+
end()).
2333+
2334+
22822335
options_whitebox(Config) when is_list(Config) ->
22832336
Cert = proplists:get_value(cert, ssl_test_lib:ssl_options(server_rsa_der_opts, Config)),
22842337
true = is_binary(Cert),
@@ -2520,6 +2573,7 @@ options_cert(Config) -> %% cert[file] cert_keys keys password
25202573
?ERR({cert, #{}}, [{cert, #{}}], client),
25212574
?ERR({certfile, cert}, [{certfile, cert}], client),
25222575
?ERR({certs_keys, #{}}, [{certs_keys, #{}}], client),
2576+
?ERR_UPD({certs_keys, no_cert_or_key_given}, [{certs_keys, []}], server),
25232577
?ERR({keyfile, #{}}, [{keyfile, #{}}], client),
25242578
?ERR({key, <<>>}, [{key, <<>>}], client),
25252579
?ERR({password, _}, [{password, fun(Arg) -> Arg end}], client),
@@ -2548,7 +2602,11 @@ options_ciphers(_Config) ->
25482602
?OK(#{ciphers := [_|_]}, [{ciphers, "RC4-SHA:RC4-MD5"}], client),
25492603
?OK(#{ciphers := [_|_]}, [{ciphers, ["RC4-SHA", "RC4-MD5"]}], client),
25502604

2551-
%% FIXME extend this
2605+
?OK(#{ciphers := [_|_]}, [{ciphers, ["TLS_DH_anon_WITH_AES_256_CBC_SHA256"]}], server),
2606+
%% Errors
2607+
?ERR({ciphers, _}, [{ciphers, "foobar:RC4-MD5"}], client),
2608+
?ERR({ciphers, _}, [{ciphers, ["RC4-SHA:RC4-MD5", "RC4-SHA:RC4-MD5"]}], client),
2609+
?ERR_UPD({certs_keys, no_cert_or_key_given}, [{ciphers, "RC4-SHA:RC4-MD5"}], server),
25522610
ok.
25532611

25542612
options_client_renegotiation(_Config) ->

lib/ssl/test/tls_api_SUITE.erl

Lines changed: 24 additions & 19 deletions
Original file line numberDiff line numberDiff line change
@@ -193,8 +193,9 @@ init_per_suite(Config0) ->
193193
try crypto:start() of
194194
ok ->
195195
ssl_test_lib:clean_start(),
196-
ssl_test_lib:make_rsa_cert_with_protected_keyfile(Config0,
197-
?CORRECT_PASSWORD)
196+
Config1 = ssl_test_lib:make_rsa_cert_with_protected_keyfile(Config0,
197+
?CORRECT_PASSWORD),
198+
ssl_test_lib:make_dsa_cert(Config1)
198199
catch _:_ ->
199200
{skip, "Crypto did not start"}
200201
end.
@@ -299,6 +300,7 @@ tls_upgrade_new_opts_with_sni_fun() ->
299300
tls_upgrade_new_opts_with_sni_fun(Config) when is_list(Config) ->
300301
ClientOpts = ssl_test_lib:ssl_options(client_rsa_verify_opts, Config),
301302
ServerOpts = ssl_test_lib:ssl_options(server_rsa_opts, Config),
303+
ServerDsaOpts = ssl_test_lib:ssl_options(server_dsa_opts, Config),
302304
{ClientNode, ServerNode, Hostname} = ssl_test_lib:run_where(Config),
303305
TcpOpts = [binary, {reuseaddr, true}],
304306
Version = ssl_test_lib:protocol_version(Config),
@@ -309,23 +311,26 @@ tls_upgrade_new_opts_with_sni_fun(Config) when is_list(Config) ->
309311
{ciphers, Ciphers},
310312
{verify, verify_peer}],
311313

312-
Server = ssl_test_lib:start_upgrade_server([{node, ServerNode}, {port, 0},
313-
{from, self()},
314-
{mfa, {?MODULE,
315-
upgrade_result, []}},
316-
{tcp_options,
317-
[{active, false} | TcpOpts]},
318-
{ssl_options, [{versions, [Version |NewVersions]}, {sni_fun, fun(_SNI) -> ServerOpts ++ NewOpts end}]}]),
314+
Server = ssl_test_lib:start_upgrade_server(
315+
[{node, ServerNode}, {port, 0},
316+
{from, self()},
317+
{mfa, {?MODULE, upgrade_result, []}},
318+
{tcp_options,
319+
[{active, false} | TcpOpts]},
320+
{ssl_options, [{versions, [Version |NewVersions]},
321+
{sni_fun, fun(_SNI) -> ServerOpts ++ NewOpts end}
322+
| ServerDsaOpts]}]),
319323
Port = ssl_test_lib:inet_port(Server),
320-
Client = ssl_test_lib:start_upgrade_client([{node, ClientNode},
321-
{port, Port},
322-
{host, Hostname},
323-
{from, self()},
324-
{mfa, {?MODULE, upgrade_result, []}},
325-
{tcp_options, [binary]},
326-
{ssl_options, [{versions, [Version |NewVersions]},
327-
{ciphers, Ciphers},
328-
{server_name_indication, Hostname} | ClientOpts]}]),
324+
Client = ssl_test_lib:start_upgrade_client(
325+
[{node, ClientNode},
326+
{port, Port},
327+
{host, Hostname},
328+
{from, self()},
329+
{mfa, {?MODULE, upgrade_result, []}},
330+
{tcp_options, [binary]},
331+
{ssl_options, [{versions, [Version |NewVersions]},
332+
{ciphers, Ciphers},
333+
{server_name_indication, Hostname} | ClientOpts]}]),
329334

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

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

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

0 commit comments

Comments
 (0)