Skip to content

Commit

Permalink
ssl: Use proc_lib:set_label/1
Browse files Browse the repository at this point in the history
  • Loading branch information
IngelaAndin committed Jan 25, 2024
1 parent 938c87f commit 6535a27
Show file tree
Hide file tree
Showing 7 changed files with 60 additions and 12 deletions.
1 change: 0 additions & 1 deletion lib/ssl/src/dtls_connection.erl
Original file line number Diff line number Diff line change
Expand Up @@ -165,7 +165,6 @@
%% Setup
%%====================================================================
init([Role, Host, Port, Socket, Options, User, CbInfo]) ->
process_flag(trap_exit, true),
State0 = initial_state(Role, Host, Port, Socket, Options, User, CbInfo),
try
State = ssl_gen_statem:init_ssl_config(State0#state.ssl_options,
Expand Down
1 change: 1 addition & 0 deletions lib/ssl/src/dtls_packet_demux.erl
Original file line number Diff line number Diff line change
Expand Up @@ -113,6 +113,7 @@ getstat(PacketSocket, Opts) ->
init([Port0, TransportInfo, EmOpts, DTLSOptions, Socket]) ->
InternalActiveN = get_internal_active_n(),
{ok, SessionIdHandle} = session_id_tracker(Socket, DTLSOptions),
proc_lib:set_label({dtls_server_packet_demultiplexer, Port0}),
{ok, #state{active_n = InternalActiveN,
port = Port0,
first = true,
Expand Down
66 changes: 55 additions & 11 deletions lib/ssl/src/ssl_gen_statem.erl
Original file line number Diff line number Diff line change
Expand Up @@ -135,26 +135,67 @@ start_link(Role, Host, Port, Socket, {SslOpts, _, _} = Options, User, CbInfo) ->
-spec init(list()) -> no_return().
%% Description: Initialization
%%--------------------------------------------------------------------
init([Role, _Sender, _Host, _Port, _Socket, {TLSOpts, _, _}, _User, _CbInfo] = InitArgs) ->
init([Role, _Sender, Host, Port, _Socket, {TLSOpts, _, _}, _User, _CbInfo] = InitArgs) ->
process_flag(trap_exit, true),

case maps:get(erl_dist, TLSOpts, false) of
true ->
process_flag(priority, max);
_ ->
ok
end,
case {Role, TLSOpts} of
{?CLIENT_ROLE, #{versions := [?TLS_1_3]}} ->
tls_client_connection_1_3:init(InitArgs);
{?SERVER_ROLE, #{versions := [?TLS_1_3]}} ->
tls_server_connection_1_3:init(InitArgs);
{_,_} ->
tls_connection:init(InitArgs)
end,

init_label(Role, Host, Port, TLSOpts),

case Role of
?CLIENT_ROLE ->
case TLSOpts of
#{versions := [?TLS_1_3]} ->
tls_client_connection_1_3:init(InitArgs);
_ ->
tls_connection:init(InitArgs)
end;
?SERVER_ROLE ->
case TLSOpts of
#{versions := [?TLS_1_3]} ->
tls_server_connection_1_3:init(InitArgs);
_ ->
tls_connection:init(InitArgs)
end
end;
init([_Role, _Host, _Port, _Socket, _TLSOpts, _User, _CbInfo] = InitArgs) ->
init([Role, Host, Port, _Socket, {DTLSOpts,_,_}, _User, _CbInfo] = InitArgs) ->
process_flag(trap_exit, true),
case Role of
?CLIENT_ROLE ->
init_label(Role, Host, Port, DTLSOpts);
?SERVER_ROLE ->
init_label(Role, Host, Port, DTLSOpts)
end,
dtls_connection:init(InitArgs).

init_label(?CLIENT_ROLE = Role, Host, _, Options) ->
Protocol = maps:get(protocol, Options),
SNIStr =
case maps:get(server_name_indication, Options, undefined) of
undefined ->
host_str(Host);
SNIOpt ->
host_str(SNIOpt)
end,
SNI = erlang:iolist_to_binary(SNIStr),
proc_lib:set_label({Protocol, Role, SNI});
init_label(?SERVER_ROLE = Role, _, Port, Options) ->
Protocol = maps:get(protocol, Options),
proc_lib:set_label({Protocol, Role, Port}).

host_str(Host) when is_list(Host) ->
Host;
host_str(Host) when is_tuple(Host) ->
IPStrs = [erlang:integer_to_list(I) || I <- tuple_to_list(Host)],
lists:join(".", IPStrs);
host_str(Host) when is_atom(Host) ->
atom_to_list(Host).

%%====================================================================
%% TLS connection setup
%%====================================================================
Expand Down Expand Up @@ -454,9 +495,12 @@ dist_handshake_complete(ConnectionPid, DHandle) ->

handle_sni_extension(undefined, State) ->
{ok, State};
handle_sni_extension(#sni{hostname = Hostname}, State0) ->
handle_sni_extension(#sni{hostname = Hostname}, #state{static_env = #static_env{port = Port},
ssl_options = #{protocol := Protocol}} = State0) ->
case check_hostname(Hostname) of
ok ->

proc_lib:set_label({Protocol, ?SERVER_ROLE, erlang:iolist_to_binary(Hostname), Port}),
{ok, handle_sni_hostname(Hostname, State0)};
#alert{} = Alert ->
{error, Alert}
Expand Down
1 change: 1 addition & 0 deletions lib/ssl/src/ssl_server_session_cache.erl
Original file line number Diff line number Diff line change
Expand Up @@ -114,6 +114,7 @@ init([Listener, #{lifetime := Lifetime,
max := Max
}]) ->
process_flag(trap_exit, true),
proc_lib:set_label({pre_tls_13_server_session_cache, Listener}),
Monitor = monitor_listener(Listener),
DbRef = init(Cb, [{role, server} | InitArgs]),
State = #state{store_cb = Cb,
Expand Down
1 change: 1 addition & 0 deletions lib/ssl/src/tls_sender.erl
Original file line number Diff line number Diff line change
Expand Up @@ -251,6 +251,7 @@ init({call, From}, {Pid, #{current_write := WriteState,
bytes_sent = 0,
log_level = LogLevel,
hibernate_after = HibernateAfter}},
proc_lib:set_label({tls_sender, Role, {connection, Pid}}),
{next_state, handshake, StateData, [{reply, From, ok}]};
init(info = Type, Msg, StateData) ->
handle_common(?FUNCTION_NAME, Type, Msg, StateData);
Expand Down
1 change: 1 addition & 0 deletions lib/ssl/src/tls_server_session_ticket.erl
Original file line number Diff line number Diff line change
Expand Up @@ -87,6 +87,7 @@ use(Pid, Identifiers, Prf, HandshakeHist) ->
-spec init(Args :: term()) -> {ok, State :: term()}.
init([Listener | Args]) ->
process_flag(trap_exit, true),
proc_lib:set_label({tls_13_server_session_tickets, Listener}),
Monitor = inet:monitor(Listener),
State = initial_state(Args),
{ok, State#state{listen_monitor = Monitor}}.
Expand Down
1 change: 1 addition & 0 deletions lib/ssl/src/tls_socket.erl
Original file line number Diff line number Diff line change
Expand Up @@ -318,6 +318,7 @@ start_link(Port, SockOpts, SslOpts) ->
%%--------------------------------------------------------------------
init([Listen, Opts, SslOpts]) ->
process_flag(trap_exit, true),
proc_lib:set_label({tls_listen_tracker, Listen}),
Monitor = inet:monitor(Listen),
{ok, #state{emulated_opts = do_set_emulated_opts(Opts, []),
listen_monitor = Monitor,
Expand Down

0 comments on commit 6535a27

Please sign in to comment.