Skip to content

Commit

Permalink
Merge branch 'maint'
Browse files Browse the repository at this point in the history
  • Loading branch information
IngelaAndin committed Aug 10, 2023
2 parents 9d6a376 + 9c299d2 commit ef4cdc8
Show file tree
Hide file tree
Showing 2 changed files with 36 additions and 5 deletions.
9 changes: 6 additions & 3 deletions lib/ssl/src/ssl_gen_statem.erl
Original file line number Diff line number Diff line change
Expand Up @@ -1074,10 +1074,11 @@ handle_normal_shutdown(Alert, StateName, #state{static_env = #static_env{role =
protocol_cb = Connection,
trackers = Trackers},
connection_env = #connection_env{user_application = {_Mon, Pid}},
handshake_env = #handshake_env{renegotiation = Type},
socket_options = Opts,
start_or_recv_from = RecvFrom} = State) ->
Pids = Connection:pids(State),
alert_user(Pids, Transport, Trackers, Socket, StateName, Opts, Pid, RecvFrom, Alert, Role, StateName, Connection).
alert_user(Pids, Transport, Trackers, Socket, Type, Opts, Pid, RecvFrom, Alert, Role, StateName, Connection).

handle_alert(#alert{level = ?FATAL} = Alert, StateName, State) ->
handle_fatal_alert(Alert, StateName, State);
Expand Down Expand Up @@ -1879,9 +1880,11 @@ send_user(Pid, Msg) ->
Pid ! Msg,
ok.

alert_user(Pids, Transport, Trackers, Socket, connection, Opts, Pid, From, Alert, Role, StateName, Connection) ->
alert_user(Pids, Transport, Trackers, Socket, _, Opts, Pid, From, Alert, Role, connection = StateName, Connection) ->
alert_user(Pids, Transport, Trackers, Socket, Opts#socket_options.active, Pid, From, Alert, Role, StateName, Connection);
alert_user(Pids, Transport, Trackers, Socket,_, _, _, From, Alert, Role, StateName, Connection) ->
alert_user(Pids, Transport, Trackers, Socket, {true, internal}, Opts, Pid, From, Alert, Role, StateName, Connection) ->
alert_user(Pids, Transport, Trackers, Socket, Opts#socket_options.active, Pid, From, Alert, Role, StateName, Connection);
alert_user(Pids, Transport, Trackers, Socket, _, _, _, From, Alert, Role, StateName, Connection) ->
alert_user(Pids, Transport, Trackers, Socket, From, Alert, Role, StateName, Connection).

alert_user(Pids, Transport, Trackers, Socket, From, Alert, Role, StateName, Connection) ->
Expand Down
32 changes: 30 additions & 2 deletions lib/ssl/test/ssl_renegotiate_SUITE.erl
Original file line number Diff line number Diff line change
Expand Up @@ -61,7 +61,9 @@
renegotiate_dos_mitigate_passive/0,
renegotiate_dos_mitigate_passive/1,
renegotiate_dos_mitigate_absolute/0,
renegotiate_dos_mitigate_absolute/1
renegotiate_dos_mitigate_absolute/1,
active_error_disallowed_client_renegotiate/0,
active_error_disallowed_client_renegotiate/1
]).

%% Apply export
Expand Down Expand Up @@ -105,7 +107,8 @@ renegotiate_tests() ->
server_no_wrap_sequence_number,
renegotiate_dos_mitigate_active,
renegotiate_dos_mitigate_passive,
renegotiate_dos_mitigate_absolute].
renegotiate_dos_mitigate_absolute,
active_error_disallowed_client_renegotiate].

init_per_suite(Config) ->
catch crypto:stop(),
Expand Down Expand Up @@ -466,6 +469,31 @@ renegotiate_dos_mitigate_absolute(Config) when is_list(Config) ->
ssl_test_lib:close(Server),
ssl_test_lib:close(Client).

%%--------------------------------------------------------------------
active_error_disallowed_client_renegotiate() ->
[{doc,"Test that an active client socket gets an error when server denies client renegotiation."}].
active_error_disallowed_client_renegotiate(Config) when is_list(Config) ->
ServerOpts = ssl_test_lib:ssl_options(server_rsa_verify_opts, Config),
ClientOpts = ssl_test_lib:ssl_options(client_rsa_verify_opts, Config),

{ClientNode, ServerNode, Hostname} = ssl_test_lib:run_where(Config),

Server =
ssl_test_lib:start_server([{node, ServerNode}, {port, 0},
{from, self()},
{mfa, {ssl_test_lib, no_result, []}},
{options, [{client_renegotiation, false} | ServerOpts]}]),
Port = ssl_test_lib:inet_port(Server),

{ok, Client} = ssl:connect(Hostname, Port, [{renegotiate_at, 1}, {active, true} | ClientOpts]),

{error, closed} = ssl:send(Client, crypto:strong_rand_bytes(20)),

receive
{ssl_error, Client, _} ->
ok
end.

%%--------------------------------------------------------------------
%% Internal functions ------------------------------------------------
%%--------------------------------------------------------------------
Expand Down

0 comments on commit ef4cdc8

Please sign in to comment.