Skip to content

Commit

Permalink
ssl: Handle defaults on version change
Browse files Browse the repository at this point in the history
  • Loading branch information
IngelaAndin committed Feb 11, 2025
1 parent ecc92ec commit 938a51d
Show file tree
Hide file tree
Showing 2 changed files with 86 additions and 4 deletions.
87 changes: 84 additions & 3 deletions lib/ssl/src/ssl_config.erl
Original file line number Diff line number Diff line change
Expand Up @@ -490,10 +490,36 @@ ssl_options() ->
%% Handle ssl options at handshake, handshake_continue
-doc false.
-spec update_options([any()], client | server, map()) -> map().
update_options(Opts, Role, InheritedSslOpts) when is_map(InheritedSslOpts) ->
{UserSslOpts, _} = split_options(Opts, ssl_options()),
update_options(NewOpts, Role, OriginalSslOpts) when is_map(OriginalSslOpts) ->
{UserSslOpts, _} = split_options(NewOpts, ssl_options()),
Env = #{role => Role, validate_certs_or_anon_ciphers => Role == server},
process_options(UserSslOpts, InheritedSslOpts, Env).
OrigVersionsOpt = maps:get(versions, OriginalSslOpts, []),
NewVersions0 = proplists:get_value(versions, NewOpts, []),
{Record, NewVersions} =
case maps:get(protocol, OriginalSslOpts) of
tls ->
validate_updated_versions(tls, NewVersions0),
{tls_record, NewVersions0};
dtls ->
validate_updated_versions(dtls, NewVersions0),
{dtls_record, NewVersions0}
end,
OrigVersions = [Record:protocol_version(V) || V <- OrigVersionsOpt],
%% Newversions is on atom format that will sort
%% correctly on term format for both tls and dtls.
%% tls_record | dtls_record:is_higher works on {Major:integer(), Minor:integer()}
%% RFC version format.
VersionsOpt = lists:sort(fun(V1, V2) -> V1 > V2 end, NewVersions),
FallBackOptions = handle_possible_version_change(OrigVersions, VersionsOpt,
OriginalSslOpts, Record),
process_options(UserSslOpts, FallBackOptions, Env).

validate_updated_versions(_, []) ->
true;
validate_updated_versions(tls, [_| _] = NewVersions) ->
validate_versions(tls, NewVersions);
validate_updated_versions(dtls, [_|_] = NewVersions) ->
validate_versions(dtls, NewVersions).

process_options(UserSslOpts, SslOpts0, Env) ->
%% Reverse option list so we get the last set option if set twice,
Expand Down Expand Up @@ -1949,6 +1975,61 @@ connection_cb(tls) ->
connection_cb(dtls) ->
dtls_gen_connection.

handle_possible_version_change([Version|_], [Version|_] = VersionOpt, OrigSSLOpts, _) ->
filter_for_versions(VersionOpt, OrigSSLOpts);
handle_possible_version_change(_, [], OrigSSLOpts, _) ->
OrigSSLOpts;
handle_possible_version_change(_, VersionsOpt, #{ciphers := Suites} = OrigSSLOpts, Record) ->
FallbackSuites = ciphers_for_version(VersionsOpt, Suites, Record),
filter_for_versions(VersionsOpt, OrigSSLOpts#{ciphers => FallbackSuites}).

filter_for_versions([], OrigSSLOptions) ->
OrigSSLOptions;
filter_for_versions(['tlsv1.3'], OrigSSLOptions) ->
Opts = ?'PRE_TLS-1_3_ONLY_OPTIONS' ++ ?'TLS-1_0_ONLY_OPTIONS',
maps:without(Opts, OrigSSLOptions);
filter_for_versions(['tlsv1.3', 'tlsv1.2'| Rest], OrigSSLOptions) ->
maybe_exclude_tlsv1(Rest, OrigSSLOptions);
filter_for_versions(['tlsv1.2'], OrigSSLOptions) ->
Opts = ?'TLS-1_3_ONLY_OPTIONS' ++ ?'TLS-1_0_ONLY_OPTIONS',
maps:without(Opts, OrigSSLOptions);
filter_for_versions(['tlsv1.2' | Rest], OrigSSLOptions) ->
Opts = ?'TLS-1_3_ONLY_OPTIONS',
maybe_exclude_tlsv1(Rest, maps:without(Opts, OrigSSLOptions));
filter_for_versions(['tlsv1.1'], OrigSSLOptions) ->
Opts = ?'TLS-1_3_ONLY_OPTIONS' ++ ?'FROM_TLS-1_2_ONLY_OPTIONS'++ ?'TLS-1_0_ONLY_OPTIONS',
maps:without(Opts, OrigSSLOptions);
filter_for_versions(['tlsv1.1'| Rest], OrigSSLOptions) ->
Opts = ?'TLS-1_3_ONLY_OPTIONS' ++ ?'FROM_TLS-1_2_ONLY_OPTIONS',
maybe_exclude_tlsv1(Rest, maps:without(Opts, OrigSSLOptions));
filter_for_versions(['tlsv1'], OrigSSLOptions) ->
OrigSSLOptions;
filter_for_versions(['dtlsv1.2'| _], OrigSSLOptions) ->
OrigSSLOptions; %% dtls1.3 not yet supported
filter_for_versions(['dtlsv1'], OrigSSLOptions) ->
filter_for_versions(['tlsv1.1'], OrigSSLOptions). %% dtlsv1 is equivialent to tlsv1.1


maybe_exclude_tlsv1(Versions, Options) ->
case lists:member('tlsv1', Versions) of
false ->
Opts = ?'TLS-1_0_ONLY_OPTIONS',
maps:without(Opts, Options);
true ->
Options
end.

ciphers_for_version([AtomVersion | _], CurrentSuites, Record) ->
Version = Record:protocol_version_name(AtomVersion),
Suites = ssl_cipher:all_suites(Version),
Intersection = sets:intersection(sets:from_list(Suites),
sets:from_list(CurrentSuites)),
case sets:is_empty(Intersection) of
true ->
tls_v1:default_suites(ssl:tls_version(Version));
false ->
[Suite || Suite <- CurrentSuites, lists:member(Suite, Suites)]
end.
%%%--------------------------------------------------------------
%%% Tracing
%%%--------------------------------------------------------------------
Expand Down
3 changes: 2 additions & 1 deletion lib/ssl/src/tls_v1.erl
Original file line number Diff line number Diff line change
Expand Up @@ -67,7 +67,8 @@
groups/1,
group_to_enum/1,
enum_to_group/1,
default_groups/0]).
default_groups/0,
default_suites/1]).

-export([derive_secret/4,
hkdf_expand_label/5,
Expand Down

0 comments on commit 938a51d

Please sign in to comment.