Skip to content

Commit

Permalink
Merge branch 'bmk/diameter/20240619/ensure_synchronous_stop_service/O…
Browse files Browse the repository at this point in the history
…TP-19206' into maint-26

* bmk/diameter/20240619/ensure_synchronous_stop_service/OTP-19206:
  [diameter] Dialyzer fixes
  [diameter|test] Event translation
  [diameter|test] Add event transation for 'reconnect'
  [diameter|test] Add 'flooding' event test case
  [diameter] Add utility function for service
  [diameter] Update the mechanism for stopping a service
  [diameter] Explicit unregister when service stop

# Conflicts:
#	lib/diameter/src/base/diameter.erl
  • Loading branch information
Erlang/OTP committed Sep 4, 2024
2 parents 2edc283 + ab73e02 commit d5b27cb
Show file tree
Hide file tree
Showing 8 changed files with 374 additions and 20 deletions.
59 changes: 51 additions & 8 deletions lib/diameter/src/base/diameter.erl
Original file line number Diff line number Diff line change
Expand Up @@ -39,6 +39,7 @@

%% Information.
-export([services/0,
is_service/1,
peer_info/1,
peer_find/1,
service_info/2]).
Expand Down Expand Up @@ -91,12 +92,6 @@
-include_lib("diameter/include/diameter.hrl").
-include("diameter_internal.hrl").

%% Enable debug logging by set(ing) level to debug.
%% For example: logger:set_primary_config(level, debug),
%% -define(DBG(F,A),
%% logger:debug("~w:~w(~w) -> " ++ F ++ "~n",
%% [?MODULE, ?FUNCTION_NAME, ?LINE | A])).


%% ---------------------------------------------------------------------------
%% start/0
Expand Down Expand Up @@ -143,16 +138,63 @@ start_service(SvcName, Opts)
-> ok
| {error, term()}.

%% To handle possible race conditions we check whois and then wait...
%% This should be simple, but just in case the function is called
%% when there is no service actually running...
stop_service(SvcName) ->
diameter_config:stop_service(SvcName).
case diameter_service:whois(SvcName) of
undefined ->
%% Nothing, so we just call stop to perform possible cleanup...
diameter_config:stop_service(SvcName);
_ ->
%% Note that the service may die/be killed just after we checked...
subscribe(SvcName),
Result = do_stop_service(SvcName),
unsubscribe(SvcName),
Result
end.

do_stop_service(SvcName) ->
ok = diameter_config:stop_service(SvcName),
%% Now wait for the stop event
await_service_stop_event(SvcName),
%% And finally wait for the registry to be "flushed" (ugh!)...
diameter_service:await_service_cleanup(SvcName).

await_service_stop_event(SvcName) ->
receive
#diameter_event{service = SvcName,
info = stop} ->
ok
after 1000 ->
case diameter_service:whois(SvcName) of
undefined ->
ok;
_Pid ->
await_service_stop_event(SvcName)
end
end.


%% ---------------------------------------------------------------------------
%% is_service/1
%% ---------------------------------------------------------------------------

%% -doc false.
-spec is_service(service_name())
-> boolean().

is_service(SvcName) ->
(undefined =/= diameter_service:whois(SvcName)).



%% ---------------------------------------------------------------------------
%% services/0
%% ---------------------------------------------------------------------------

-spec services()
-> [service_name()].
-> [service_name()].

services() ->
[Name || {Name, _} <- diameter_service:services()].
Expand Down Expand Up @@ -550,3 +592,4 @@ call(SvcName, App, Message) ->
Mins :: 0..59,
Secs :: 0..59,
MicroSecs :: 0..999999}.

3 changes: 2 additions & 1 deletion lib/diameter/src/base/diameter_config.erl
Original file line number Diff line number Diff line change
Expand Up @@ -147,7 +147,7 @@ start_service(SvcName, Opts)

start_rc({ok = T, _Pid}) ->
T;
start_rc({error, _} = No) ->
start_rc({error, _R} = No) ->
No;
start_rc(timeout) ->
{error, application_not_started}.
Expand Down Expand Up @@ -905,6 +905,7 @@ init_app({application, Opts} = T) ->
M = get_opt(call_mutates_state, Opts, false, [true]),
A = get_opt(answer_errors, Opts, discard, [callback, report]),
P = get_opt(request_errors, Opts, answer_3xxx, [answer, callback]),

#diameter_app{alias = Alias,
dictionary = Dict,
id = cb(Dict, id),
Expand Down
8 changes: 8 additions & 0 deletions lib/diameter/src/base/diameter_internal.hrl
Original file line number Diff line number Diff line change
Expand Up @@ -56,6 +56,14 @@
-define(APP_ID_COMMON, 0).
-define(APP_ID_RELAY, 16#FFFFFFFF).

%% -define(DBG(F, A),
%% io:format("<~s> ~p "
%% "~w:~w[~w] -> " ++ F ++ "~n",
%% [diameter_lib:formated_timestamp(), self(),
%% ?MODULE, ?FUNCTION_NAME, ?LINE | A])).
-define(DBG(F, A), ignore).


%%% ---------------------------------------------------------

%%% RFC 3588, ch 2.6 Peer table
Expand Down
31 changes: 31 additions & 0 deletions lib/diameter/src/base/diameter_lib.erl
Original file line number Diff line number Diff line change
Expand Up @@ -27,6 +27,7 @@
now/0,
timestamp/0,
timestamp/1,
formated_timestamp/0,
now_diff/1,
micro_diff/1,
micro_diff/2,
Expand All @@ -41,6 +42,7 @@
for_n/2,
log/4]).


%% ---------------------------------------------------------------------------
%% # stacktrace/1
%% ---------------------------------------------------------------------------
Expand Down Expand Up @@ -129,6 +131,35 @@ timestamp(MonoT) -> %% monotonic time
monotonic_to_microseconds(MonoT) ->
erlang:convert_time_unit(MonoT, native, micro_seconds).
%% ---------------------------------------------------------------------------
%% # formated_timestamp/0
%% ---------------------------------------------------------------------------
-spec formated_timestamp()
-> string().
formated_timestamp() ->
format_timestamp(os:timestamp()).
format_timestamp(Now) ->
N2T = fun(N) -> calendar:now_to_local_time(N) end,
format_timestamp(Now, N2T).
format_timestamp({_N1, _N2, N3} = Now, N2T)
when is_tuple(Now) andalso is_function(N2T) ->
{Date, Time} = N2T(Now),
do_format_timestamp(Date, Time, N3).
do_format_timestamp(Date, Time, N3) ->
{YYYY,MM,DD} = Date,
{Hour,Min,Sec} = Time,
FormatDate =
io_lib:format("~.4w-~.2.0w-~.2.0w ~.2.0w:~.2.0w:~.2.0w.~.3.0w",
[YYYY, MM, DD, Hour, Min, Sec, N3 div 1000]),
lists:flatten(FormatDate).
%% ---------------------------------------------------------------------------
%% # now_diff/1
%% ---------------------------------------------------------------------------
Expand Down
37 changes: 31 additions & 6 deletions lib/diameter/src/base/diameter_service.erl
Original file line number Diff line number Diff line change
Expand Up @@ -33,7 +33,9 @@
unsubscribe/1,
services/0,
peer_info/1,
info/2]).
info/2,

await_service_cleanup/1]).

%% towards diameter_config
-export([start/1,
Expand Down Expand Up @@ -198,6 +200,27 @@ stop(ok, Pid) ->
stop(No, _) ->
No.


%% This one assumes stop/1 has already been called.
%% So, technically, the service is already stopped,
%% but the cleanup may not have completed...
%% This is a simple race, so we should not have to wait long...
await_service_cleanup(SvcName) ->
do_await_service_cleanup(SvcName, 10).

do_await_service_cleanup(_SvcName, N) when (N =< 0) ->
{error, service_cleanup_timeout};
do_await_service_cleanup(SvcName, N) ->
case whois(SvcName) of
undefined ->
%% We are done!
ok;
_Pid ->
receive after 100 -> ok end,
do_await_service_cleanup(SvcName, N-1)
end.


%% ---------------------------------------------------------------------------
%% # start_transport/3
%% ---------------------------------------------------------------------------
Expand Down Expand Up @@ -575,7 +598,7 @@ handle_call(stop, _From, S) ->
{stop, normal, ok, S};
%% The server currently isn't guaranteed to be dead when the caller
%% gets the reply. We deal with this in the call to the server,
%% stating a monitor that waits for DOWN before returning.
%% starting a monitor that waits for DOWN before returning.

handle_call(Req, From, S) ->
unexpected(handle_call, [Req, From], S),
Expand Down Expand Up @@ -692,9 +715,9 @@ transition(Req, S) ->
%% # terminate/2
%% ---------------------------------------------------------------------------

terminate(Reason, #state{service_name = Name, local = {PeerT, _, _}} = S) ->
send_event(Name, stop),
ets:delete(?STATE_TABLE, Name),
terminate(Reason, #state{service_name = SvcName, local = {PeerT, _, _}} = S) ->
send_event(SvcName, stop),
ets:delete(?STATE_TABLE, SvcName),

%% Communicate pending loss of any peers that connection_down/3
%% won't. This is needed when stopping a service since we don't
Expand Down Expand Up @@ -822,7 +845,9 @@ cs(Pid, Req)
try
gen_server:call(Pid, Req, infinity)
catch
E: Reason when E == exit ->
E: {noproc, _} when E =:= exit ->
{error, no_service};
E: Reason when E =:= exit ->
{error, {E, Reason}}
end;

Expand Down
2 changes: 2 additions & 0 deletions lib/diameter/test/Makefile
Original file line number Diff line number Diff line change
Expand Up @@ -67,6 +67,8 @@ ERL_COMPILE_FLAGS := $(filter-out +deterministic,$(ERL_COMPILE_FLAGS))

all $(TYPES): $(TARGET_FILES)

targets: all

strict:
$(MAKE) opt STRICT_FLAGS=-Werror

Expand Down
10 changes: 8 additions & 2 deletions lib/diameter/test/diameter_config_SUITE.erl
Original file line number Diff line number Diff line change
Expand Up @@ -297,9 +297,15 @@ start(Key, Vs)

start(SvcName, Opts) ->
try
diameter:start_service(SvcName, Opts)
Res1 = diameter:start_service(SvcName, Opts),
%% io:format("[started] Is service ~p: ~p~n",
%% [SvcName, diameter:is_service(SvcName)]),
Res1
after
diameter:stop_service(SvcName)
Res2 = diameter:stop_service(SvcName),
%% io:format("[stopped] Is service ~p: ~p~n",
%% [SvcName, diameter:is_service(SvcName)]),
Res2
end.

apps(application) ->
Expand Down
Loading

0 comments on commit d5b27cb

Please sign in to comment.