Skip to content

Commit

Permalink
Merge pull request #9228 from u3s/kuba/ssl/ssl_codescene_refactor_202…
Browse files Browse the repository at this point in the history
…41220

ssl: refactor related to CodeScene review
  • Loading branch information
u3s authored Dec 23, 2024
2 parents 3ab59bb + da69069 commit f4caf91
Show file tree
Hide file tree
Showing 2 changed files with 53 additions and 70 deletions.
37 changes: 13 additions & 24 deletions lib/ssl/src/ssl.erl
Original file line number Diff line number Diff line change
Expand Up @@ -3171,15 +3171,6 @@ getopts(#sslsocket{}, OptionTags) ->
setopts(#sslsocket{connection_handler = Controller}, [{active, _}] = Active)
when is_pid(Controller) ->
ssl_gen_statem:set_opts(Controller, Active);
setopts(#sslsocket{connection_handler = Controller, connection_cb = tls_gen_connection}, Options0)
when is_pid(Controller), is_list(Options0) ->
try proplists:expand([{binary, [{mode, binary}]}, {list, [{mode, list}]}], Options0) of
Options ->
ssl_gen_statem:set_opts(Controller, Options)
catch
_:_ ->
{error, {options, {not_a_proplist, Options0}}}
end;
setopts(#sslsocket{connection_handler = Controller}, Options0)
when is_pid(Controller), is_list(Options0) ->
try proplists:expand([{binary, [{mode, binary}]}, {list, [{mode, list}]}], Options0) of
Expand Down Expand Up @@ -3466,21 +3457,19 @@ reading and writing keys are updated.
%%
%% Description: Initiate a key update.
%%--------------------------------------------------------------------
update_keys(#sslsocket{connection_handler = Controller,
payload_sender = Sender,
connection_cb = tls_gen_connection}, Type0) when is_pid(Controller) andalso
is_pid(Sender) andalso
(Type0 =:= write orelse
Type0 =:= read_write) ->
Type = case Type0 of
write ->
update_not_requested;
read_write ->
update_requested
end,
tls_gen_connection_1_3:send_key_update(Sender, Type);
update_keys(_, Type) ->
{error, {illegal_parameter, Type}}.
update_keys(#sslsocket{connection_handler = Controller, payload_sender = Sender,
connection_cb = tls_gen_connection}, Type)
when is_pid(Controller) ->
case Type of
write ->
tls_gen_connection_1_3:send_key_update(Sender, update_not_requested);
read_write ->
tls_gen_connection_1_3:send_key_update(Sender, update_requested);
_ ->
{error, {illegal_parameter, Type}}
end;
update_keys(_, _) ->
{error, not_supported}.

%%--------------------------------------------------------------------
-doc(#{equiv => export_key_materials(TLSSocket, Labels, Contexts,
Expand Down
86 changes: 40 additions & 46 deletions lib/ssl/src/ssl_handshake.erl
Original file line number Diff line number Diff line change
Expand Up @@ -1548,53 +1548,34 @@ handle_server_hello_extensions(RecordCB, Random, CipherSuite,
#{secure_renegotiate := SecureRenegotation} =
SslOpts,
ConnectionStates0, Renegotiation, IsNew) ->
ConnectionStates = handle_renegotiation_extension(client, RecordCB, Version,
maps:get(renegotiation_info, Exts, undefined), Random,
ConnectionStates = handle_renegotiation_extension(client, RecordCB, Version,
maps:get(renegotiation_info, Exts, undefined), Random,
CipherSuite, undefined,
ConnectionStates0,
Renegotiation, SecureRenegotation),

%% RFC 6066: handle received/expected maximum fragment length
if IsNew ->
ServerMaxFragEnum = maps:get(max_frag_enum, Exts, undefined),
ConnMaxFragLen = maps:get(max_fragment_length, ConnectionStates0, undefined),
ClientMaxFragEnum = max_frag_enum(ConnMaxFragLen),

if ServerMaxFragEnum == ClientMaxFragEnum ->
ok;
true ->
throw(?ALERT_REC(?FATAL, ?ILLEGAL_PARAMETER))
end;
true ->
ok
end,

case handle_cert_status_extension(SslOpts, Exts) of
#alert{} = Alert ->
Alert;
StaplingState ->
%% If we receive an ALPN extension then this is the protocol selected,
%% otherwise handle the NPN extension.
ALPN = maps:get(alpn, Exts, undefined),
case decode_alpn(ALPN) of
%% ServerHello contains exactly one protocol: the one selected.
%% We also ignore the ALPN extension during renegotiation (see encode_alpn/2).
[Protocol] when not Renegotiation ->
{ConnectionStates, alpn, Protocol, StaplingState};
[_] when Renegotiation ->
{ConnectionStates, alpn, undefined, StaplingState};
undefined ->
NextProtocolNegotiation = maps:get(next_protocol_negotiation, Exts, undefined),
NextProtocolSelector = maps:get(next_protocol_selector, SslOpts, undefined),
Protocol = handle_next_protocol(NextProtocolNegotiation, NextProtocolSelector, Renegotiation),
{ConnectionStates, npn, Protocol, StaplingState};
{error, Reason} ->
?ALERT_REC(?FATAL, ?HANDSHAKE_FAILURE, Reason);
[] ->
?ALERT_REC(?FATAL, ?HANDSHAKE_FAILURE, no_protocols_in_server_hello);
[_|_] ->
?ALERT_REC(?FATAL, ?HANDSHAKE_FAILURE, too_many_protocols_in_server_hello)
end
assert_max_frag_length(IsNew, Exts, ConnectionStates0),
StaplingState = handle_cert_status_extension(SslOpts, Exts),
%% If we receive an ALPN extension then this is the protocol selected,
%% otherwise handle the NPN extension.
ALPN = maps:get(alpn, Exts, undefined),
case decode_alpn(ALPN) of
%% ServerHello contains exactly one protocol: the one selected.
%% We also ignore the ALPN extension during renegotiation (see encode_alpn/2).
[Protocol] when not Renegotiation ->
{ConnectionStates, alpn, Protocol, StaplingState};
[_] when Renegotiation ->
{ConnectionStates, alpn, undefined, StaplingState};
undefined ->
NextProtocolNegotiation = maps:get(next_protocol_negotiation, Exts, undefined),
NextProtocolSelector = maps:get(next_protocol_selector, SslOpts, undefined),
Protocol = handle_next_protocol(NextProtocolNegotiation, NextProtocolSelector, Renegotiation),
{ConnectionStates, npn, Protocol, StaplingState};
{error, Reason} ->
throw(?ALERT_REC(?FATAL, ?HANDSHAKE_FAILURE, Reason));
[] ->
throw(?ALERT_REC(?FATAL, ?HANDSHAKE_FAILURE, no_protocols_in_server_hello));
[_|_] ->
throw(?ALERT_REC(?FATAL, ?HANDSHAKE_FAILURE, too_many_protocols_in_server_hello))
end.

select_curve(Client, Server) ->
Expand Down Expand Up @@ -2019,15 +2000,15 @@ handle_cert_status_extension(#{stapling := _Stapling}, Extensions) ->
#{configured => true,
status => not_negotiated};
_Else ->
?ALERT_REC(?FATAL, ?HANDSHAKE_FAILURE, status_request_not_empty)
throw(?ALERT_REC(?FATAL, ?HANDSHAKE_FAILURE, status_request_not_empty))
end;
handle_cert_status_extension(_SslOpts, Extensions) ->
case maps:get(status_request, Extensions, false) of
false ->
#{configured => false,
status => not_negotiated};
_Else -> %% unsolicited status_request
?ALERT_REC(?FATAL, ?HANDSHAKE_FAILURE, unexpected_status_request)
throw(?ALERT_REC(?FATAL, ?HANDSHAKE_FAILURE, unexpected_status_request))
end.

certificate_authorities(CertDbHandle, CertDbRef) ->
Expand Down Expand Up @@ -3496,6 +3477,19 @@ handle_renegotiation_extension(Role, RecordCB, Version, Info, Random, Negotiated
Random,
ConnectionStates).

assert_max_frag_length(true, Exts, ConnectionStates) ->
%% RFC 6066: handle received/expected maximum fragment length
ServerMaxFragEnum = maps:get(max_frag_enum, Exts, undefined),
ConnMaxFragLen = maps:get(max_fragment_length, ConnectionStates, undefined),
ClientMaxFragEnum = max_frag_enum(ConnMaxFragLen),
if ServerMaxFragEnum == ClientMaxFragEnum ->
ok;
true ->
throw(?ALERT_REC(?FATAL, ?ILLEGAL_PARAMETER))
end;
assert_max_frag_length(_, _, _) ->
ok.

%% Receive protocols, choose one from the list, return it.
handle_alpn_extension(_, {error, Reason}) ->
throw(?ALERT_REC(?FATAL, ?HANDSHAKE_FAILURE, Reason));
Expand Down

0 comments on commit f4caf91

Please sign in to comment.