File 1582-erpc-doc-changes-for-always_spawn.patch of Package erlang

From 717e1491bea36cf910609f1b9e5d146ee38b4b28 Mon Sep 17 00:00:00 2001
From: Jan Uhlig <juhlig@hnc-agency.org>
Date: Mon, 26 Aug 2024 18:58:24 +0200
Subject: [PATCH 2/3] erpc doc changes for always_spawn

---
 lib/kernel/src/erpc.erl | 79 ++++++++++++++++++-----------------------
 1 file changed, 35 insertions(+), 44 deletions(-)

diff --git a/lib/kernel/src/erpc.erl b/lib/kernel/src/erpc.erl
index c674a08d67..c195a74a92 100644
--- a/lib/kernel/src/erpc.erl
+++ b/lib/kernel/src/erpc.erl
@@ -83,7 +83,10 @@ is available on the involved nodes.
          reqids_add/3,
          reqids_to_list/1]).
 
--export_type([request_id/0, request_id_collection/0, timeout_time/0]).
+-export_type([call_options/0,
+	      request_id/0,
+	      request_id_collection/0,
+	      timeout_time/0]).
 
 %% Internal exports (also used by the 'rpc' module)
 
@@ -121,13 +124,25 @@ The value can be:
   a time further into the future than `4294967295` milliseconds. Identifying the
   timeout using an absolute timeout value is especially handy when you have a
   deadline for responses corresponding to a complete collection of requests
-  (`t:request_id_collection/0`) , since you do not have to recalculate the
+  (`t:request_id_collection/0`), since you do not have to recalculate the
   relative time until the deadline over and over again.
 """.
 -type timeout_time() :: 0..?MAX_INT_TIMEOUT | 'infinity' | {abs, integer()}.
 
--type call_options() :: #{'timeout' => timeout_time(),
-			  'always_spawn' => boolean()}.
+-doc """
+Options to be used in [`call/3,5`](`call/5`) and
+[`multicall/3,5`](`multicall/5`) functions.
+
+- **`timeout`** - Upper time limit for call operations to complete, see
+  `t:timeout_time/0`. Default: `infinity`.
+
+- **`always_spawn`** - If `true`, the `apply()` will _always_ be performed
+  in a freshly spawned process. If `false`, the calling process _may_ be
+  used instead, if possible. Default: `false`.
+""".
+-doc(#{since => <<"OTP 28.0">>}).
+-type call_options() :: #{'timeout' => Timeout :: timeout_time(),
+			  'always_spawn' => AlwaysSpawn :: boolean()}.
 
 %%------------------------------------------------------------------------
 %% Exported API
@@ -178,8 +193,10 @@ call(N, M, F, A) ->
 
 -doc """
 Evaluates [`apply(Module, Function, Args)`](`apply/3`) on node `Node` and
-returns the corresponding value `Result`. `Timeout` sets an upper time limit for
-the `call` operation to complete.
+returns the corresponding value `Result`.
+
+`TimeoutOrOptions` can be either a [`timeout time`](`t:timeout_time/0`) or a
+[`call options`](`t:call_options/0`) map (since OTP 28.0).
 
 The `call()` function only returns if the applied function successfully returned
 without raising any uncaught exceptions, the operation did not time out, and no
@@ -242,9 +259,9 @@ communication may, of course, reach the calling process.
 
 > #### Note {: .info }
 >
-> You cannot make _any_ assumptions about the process that will perform the
-> `apply()`. It may be the calling process itself, a server, or a freshly
-> spawned process.
+> If the `always_spawn` option is `false` (which is the default), you cannot make
+> _any_ assumptions about the process that will perform the `apply()`. It may be
+> the calling process itself, or a freshly spawned process.
 """.
 -doc(#{since => <<"OTP 23.0">>}).
 -spec call(Node, Module, Function, Args, TimeoutOrOptions) -> Result when
@@ -322,11 +339,6 @@ Fails with an `{erpc, badarg}` `error` exception if:
 
 - `Node` is not an atom.
 - `Fun` is not a fun of zero arity.
-
-> #### Note {: .info }
->
-> You cannot make _any_ assumptions about the process that will perform the
-> `apply()`. It may be a server, or a freshly spawned process.
 """.
 -doc(#{since => <<"OTP 23.0">>}).
 -spec send_request(Node, Fun) -> RequestId when
@@ -377,11 +389,6 @@ Fails with an `{erpc, badarg}` `error` exception if:
 - `Args` is not a list. Note that the list is not verified to be a proper list
   at the client side.
 
-> #### Note {: .info }
->
-> You cannot make _any_ assumptions about the process that will perform the
-> `apply()`. It may be a server, or a freshly spawned process.
-
 Equivalent to
 [`erpc:send_request(Node, erlang, apply, [Fun,[]]), Label, RequestIdCollection)`](`send_request/6`).
 
@@ -390,11 +397,6 @@ Fails with an `{erpc, badarg}` `error` exception if:
 - `Node` is not an atom.
 - `Fun` is not a fun of zero arity.
 - `RequestIdCollection` is detected not to be request identifier collection.
-
-> #### Note {: .info }
->
-> You cannot make _any_ assumptions about the process that will perform the
-> `apply()`. It may be a server, or a freshly spawned process.
 """.
 -doc(#{since => <<"OTP 23.0">>}).
 -spec send_request(Node, Module, Function, Args) -> RequestId when
@@ -446,11 +448,6 @@ Fails with an `{erpc, badarg}` `error` exception if:
 - `Args` is not a list. Note that the list is not verified to be a proper list
   at the client side.
 - `RequestIdCollection` is detected not to be request identifier collection.
-
-> #### Note {: .info }
->
-> You cannot make _any_ assumptions about the process that will perform the
-> `apply()`. It may be a server, or a freshly spawned process.
 """.
 -doc(#{since => <<"OTP 25.0">>}).
 -spec send_request(Node, Module, Function, Args,
@@ -1050,8 +1047,12 @@ multicall(Ns, M, F, A) ->
 Performs multiple `call` operations in parallel on multiple nodes.
 
 That is, evaluates [`apply(Module, Function, Args)`](`apply/3`) on the nodes `Nodes` in
-parallel. `Timeout` sets an upper time limit for all `call` operations to
-complete. The result is returned as a list where the result from each node is
+parallel.
+
+`TimeoutOrOptions` can be either a [`timeout time`](`t:timeout_time/0`) or a
+[`call options`](`t:call_options/0`) map (since OTP 28.0).
+
+The result is returned as a list where the result from each node is
 placed at the same position as the node name is placed in `Nodes`. Each item in
 the resulting list is formatted as either:
 
@@ -1107,9 +1108,9 @@ calling process, such communication may, of course, reach the calling process.
 
 > #### Note {: .info }
 >
-> You cannot make _any_ assumptions about the process that will perform the
-> `apply()`. It may be the calling process itself, a server, or a freshly
-> spawned process.
+> If the `always_spawn` option is `false` (which is the default), you cannot make
+> _any_ assumptions about the processes that will perform the `apply()`s. It may be
+> the calling process itself, or freshly spawned processes, or a mix of both.
 """.
 -doc(#{since => <<"OTP 23.0">>}).
 -spec multicall(Nodes, Module, Function, Args, TimeoutOrOptions) -> Result when
@@ -1174,11 +1175,6 @@ if:
 - `Function` is not an atom.
 - `Args` is not a list. Note that the list is not verified to be a proper list
   at the client side.
-
-> #### Note {: .info }
->
-> You cannot make _any_ assumptions about the process that will perform the
-> `apply()`. It may be a server, or a freshly spawned process.
 """.
 -doc(#{since => <<"OTP 23.0">>}).
 -spec multicast(Nodes, Module, Function, Args) -> 'ok' when
@@ -1234,11 +1230,6 @@ ignored.
 - `Function` is not an atom.
 - `Args` is not a list. Note that the list is not verified to be a proper list
   at the client side.
-
-> #### Note {: .info }
->
-> You cannot make _any_ assumptions about the process that will perform the
-> `apply()`. It may be a server, or a freshly spawned process.
 """.
 -doc(#{since => <<"OTP 23.0">>}).
 -spec cast(Node, Module, Function, Args) -> 'ok' when
-- 
2.43.0

openSUSE Build Service is sponsored by