File 8101-Add-ability-to-always-spawn-for-erpc-call-and-multic.patch of Package erlang
From aa79cb57b4f90b8a702f96290e96e0e92456fafa Mon Sep 17 00:00:00 2001
From: Jan Uhlig <juhlig@hnc-agency.org>
Date: Mon, 26 Aug 2024 09:59:53 +0200
Subject: [PATCH 1/3] Add ability to always spawn for erpc:call and multicall
Co-authored-by: Maria Scott <maria-12648430@hnc-agency.org>
---
lib/kernel/src/erpc.erl | 99 ++++++++++++++++++++++++-----------------
1 file changed, 59 insertions(+), 40 deletions(-)
diff --git a/lib/kernel/src/erpc.erl b/lib/kernel/src/erpc.erl
index db28e54bb2..c674a08d67 100644
--- a/lib/kernel/src/erpc.erl
+++ b/lib/kernel/src/erpc.erl
@@ -75,6 +75,9 @@
-type timeout_time() :: 0..?MAX_INT_TIMEOUT | 'infinity' | {abs, integer()}.
+-type call_options() :: #{'timeout' => timeout_time(),
+ 'always_spawn' => boolean()}.
+
%%------------------------------------------------------------------------
%% Exported API
%%------------------------------------------------------------------------
@@ -85,16 +88,16 @@
Result :: term().
call(N, Fun) ->
- call(N, Fun, infinity).
+ call(N, Fun, #{timeout => infinity}).
--spec call(Node, Fun, Timeout) -> Result when
+-spec call(Node, Fun, TimeoutOrOptions) -> Result when
Node :: node(),
Fun :: function(),
- Timeout :: timeout_time(),
+ TimeoutOrOptions :: timeout_time() | call_options(),
Result :: term().
-call(N, Fun, Timeout) when is_function(Fun, 0) ->
- call(N, erlang, apply, [Fun, []], Timeout);
+call(N, Fun, TimeoutOrOptions) when is_function(Fun, 0) ->
+ call(N, erlang, apply, [Fun, []], TimeoutOrOptions);
call(_N, _Fun, _Timeout) ->
error({?MODULE, badarg}).
@@ -106,22 +109,23 @@ call(_N, _Fun, _Timeout) ->
Result :: term().
call(N, M, F, A) ->
- call(N, M, F, A, infinity).
+ call(N, M, F, A, #{timeout => infinity}).
-dialyzer([{nowarn_function, call/5}, no_return]).
--spec call(Node, Module, Function, Args, Timeout) -> Result when
+-spec call(Node, Module, Function, Args, TimeoutOrOptions) -> Result when
Node :: node(),
Module :: atom(),
Function :: atom(),
Args :: [term()],
- Timeout :: timeout_time(),
+ TimeoutOrOptions :: timeout_time() | call_options(),
Result :: term().
-call(N, M, F, A, infinity) when node() =:= N, %% Optimize local call
- is_atom(M),
- is_atom(F),
- is_list(A) ->
+call(N, M, F, A, #{timeout := infinity,
+ always_spawn := false}) when node() =:= N, %% Optimize local call
+ is_atom(M),
+ is_atom(F),
+ is_list(A) ->
try
{return, Return} = execute_call(M,F,A),
Return
@@ -137,10 +141,12 @@ call(N, M, F, A, infinity) when node() =:= N, %% Optimize local call
error({exception, Reason, ErpcStack})
end
end;
-call(N, M, F, A, T) when is_atom(N),
- is_atom(M),
- is_atom(F),
- is_list(A) ->
+call(N, M, F, A, #{timeout := T,
+ always_spawn := AlwaysSpawn}) when is_atom(N),
+ is_atom(M),
+ is_atom(F),
+ is_list(A),
+ is_boolean(AlwaysSpawn) ->
Timeout = timeout_value(T),
Res = make_ref(),
ReqId = spawn_request(N, ?MODULE, execute_call, [Res, M, F, A],
@@ -153,8 +159,15 @@ call(N, M, F, A, T) when is_atom(N),
after Timeout ->
result(timeout, ReqId, Res, undefined)
end;
-call(_N, _M, _F, _A, _T) ->
- error({?MODULE, badarg}).
+call(_N, _M, _F, _A, #{timeout := _T,
+ always_spawn := _AlwaysSpawn} = _Opts) ->
+ error({?MODULE, badarg});
+call(N, M, F, A, #{} = Opts) ->
+ call(N, M, F, A, maps:merge(#{timeout => infinity,
+ always_spawn => false}, Opts));
+call(N, M, F, A, T) ->
+ call(N, M, F, A, #{timeout => T,
+ always_spawn => false}).
%% Asynchronous call
@@ -479,17 +492,17 @@ reqids_to_list(_) ->
Result :: term().
multicall(Ns, Fun) ->
- multicall(Ns, Fun, infinity).
+ multicall(Ns, Fun, #{timeout => infinity}).
--spec multicall(Nodes, Fun, Timeout) -> Result when
+-spec multicall(Nodes, Fun, TimeoutOrOptions) -> Result when
Nodes :: [atom()],
Fun :: function(),
- Timeout :: timeout_time(),
+ TimeoutOrOptions :: timeout_time() | call_options(),
Result :: term().
-multicall(Ns, Fun, Timeout) when is_function(Fun, 0) ->
- multicall(Ns, erlang, apply, [Fun, []], Timeout);
-multicall(_Ns, _Fun, _Timeout) ->
+multicall(Ns, Fun, TimeoutOrOptions) when is_function(Fun, 0) ->
+ multicall(Ns, erlang, apply, [Fun, []], TimeoutOrOptions);
+multicall(_Ns, _Fun, _TimeoutOrOptions) ->
error({?MODULE, badarg}).
-spec multicall(Nodes, Module, Function, Args) -> Result when
@@ -500,29 +513,35 @@ multicall(_Ns, _Fun, _Timeout) ->
Result :: [{ok, ReturnValue :: term()} | caught_call_exception()].
multicall(Ns, M, F, A) ->
- multicall(Ns, M, F, A, infinity).
+ multicall(Ns, M, F, A, #{timeout => infinity}).
--spec multicall(Nodes, Module, Function, Args, Timeout) -> Result when
+-spec multicall(Nodes, Module, Function, Args, TimeoutOrOptions) -> Result when
Nodes :: [atom()],
Module :: atom(),
Function :: atom(),
Args :: [term()],
- Timeout :: timeout_time(),
+ TimeoutOrOptions :: timeout_time() | call_options(),
Result :: [{ok, ReturnValue :: term()} | caught_call_exception()].
-multicall(Ns, M, F, A, T) ->
+multicall(Ns, M, F, A, #{} = Opts) ->
try
true = is_atom(M),
true = is_atom(F),
true = is_list(A),
Tag = make_ref(),
- Timeout = timeout_value(T),
- SendState = mcall_send_requests(Tag, Ns, M, F, A, Timeout),
+ Timeout = timeout_value(maps:get(timeout, Opts, infinity)),
+ LocalCall = case maps:get(always_spawn, Opts, false) of
+ true -> always_spawn;
+ false -> allow_local_call
+ end,
+ SendState = mcall_send_requests(Tag, Ns, M, F, A, LocalCall, Timeout),
mcall_receive_replies(Tag, SendState)
catch
error:NotIErr when NotIErr /= internal_error ->
error({?MODULE, badarg})
- end.
+ end;
+multicall(Ns, M, F, A, T) ->
+ multicall(Ns, M, F, A, #{timeout => T}).
-spec multicast(Nodes, Fun) -> 'ok' when
Nodes :: [node()],
@@ -849,9 +868,9 @@ mcall_send_request(T, N, M, F, A) when is_reference(T),
{reply_tag, T},
{monitor, [{tag, T}]}]).
-mcall_send_requests(Tag, Ns, M, F, A, Tmo) ->
+mcall_send_requests(Tag, Ns, M, F, A, LC, Tmo) ->
DL = deadline(Tmo),
- mcall_send_requests(Tag, Ns, M, F, A, [], DL, undefined, 0).
+ mcall_send_requests(Tag, Ns, M, F, A, [], DL, LC, 0).
mcall_send_requests(_Tag, [], M, F, A, RIDs, DL, local_call, NRs) ->
%% Timeout infinity and call on local node wanted;
@@ -861,7 +880,7 @@ mcall_send_requests(_Tag, [], M, F, A, RIDs, DL, local_call, NRs) ->
mcall_send_requests(_Tag, [], _M, _F, _A, RIDs, DL, _LC, NRs) ->
{ok, RIDs, #{}, NRs, DL};
mcall_send_requests(Tag, [N|Ns], M, F, A, RIDs,
- infinity, undefined, NRs) when N == node() ->
+ infinity, allow_local_call, NRs) when N == node() ->
mcall_send_requests(Tag, Ns, M, F, A, [local_call|RIDs],
infinity, local_call, NRs);
mcall_send_requests(Tag, [N|Ns], M, F, A, RIDs, DL, LC, NRs) ->
--
2.43.0