File 4761-Add-apply_-functions-to-the-timer-module-that-accept.patch of Package erlang

From 4e97963da88fce3e00de85f49ceea396e8bc0634 Mon Sep 17 00:00:00 2001
From: Jan Uhlig <juhlig@hnc-agency.org>
Date: Mon, 16 Oct 2023 14:37:01 +0200
Subject: [PATCH] Add apply_* functions to the timer module that accept
 functions

---
 lib/stdlib/doc/src/timer.xml           | 147 ++++++++++++++++++++++++-
 lib/stdlib/src/timer.erl               |  92 ++++++++++++++--
 lib/stdlib/test/timer_simple_SUITE.erl | 123 ++++++++++++++++-----
 3 files changed, 319 insertions(+), 43 deletions(-)

diff --git a/lib/stdlib/doc/src/timer.xml b/lib/stdlib/doc/src/timer.xml
index 75706f7b2d..90542bc6b9 100644
--- a/lib/stdlib/doc/src/timer.xml
+++ b/lib/stdlib/doc/src/timer.xml
@@ -69,6 +69,31 @@
   </datatypes>
 
   <funcs>
+    <func>
+      <name name="apply_after" arity="2" since="OTP 27.0"/>
+      <fsummary>Spawn a process evaluating <c>erlang:apply(Function, [])</c>
+        after a specified <c>Time</c>.</fsummary>
+      <desc>
+        <p>Evaluates <c>spawn(erlang, apply, [<anno>Function</anno>,
+          []])</c> after <c><anno>Time</anno></c> milliseconds.</p>
+        <p>Returns <c>{ok, <anno>TRef</anno>}</c> or
+          <c>{error, <anno>Reason</anno>}</c>.</p>
+      </desc>
+    </func>
+
+    <func>
+      <name name="apply_after" arity="3" since="OTP 27.0"/>
+      <fsummary>Spawn a process evaluating <c>erlang:apply(Function, Arguments)</c>
+        after a specified <c>Time</c>.</fsummary>
+      <desc>
+        <p>Evaluates <c>spawn(erlang, apply, [<anno>Function</anno>,
+          <anno>Arguments</anno>])</c> after <c><anno>Time</anno></c>
+          milliseconds.</p>
+        <p>Returns <c>{ok, <anno>TRef</anno>}</c> or
+          <c>{error, <anno>Reason</anno>}</c>.</p>
+      </desc>
+    </func>
+
     <func>
       <name name="apply_after" arity="4" since=""/>
       <fsummary>Spawn a process evaluating <c>Module:Function(Arguments)</c>
@@ -82,6 +107,34 @@
       </desc>
     </func>
 
+    <func>
+      <name name="apply_interval" arity="2" since="OTP 27.0"/>
+      <fsummary>Spawn a process evaluating <c>erlang:apply(Function, [])</c>
+        repeatedly at intervals of <c>Time</c>.</fsummary>
+      <desc>
+        <p>Evaluates <c>spawn(erlang, apply, [<anno>Function</anno>,
+          []])</c> repeatedly at intervals of
+          <c><anno>Time</anno></c>, irrespective of whether a previously
+          spawned process has finished or not.</p>
+        <p>Returns <c>{ok, <anno>TRef</anno>}</c> or
+          <c>{error, <anno>Reason</anno>}</c>.</p>
+      </desc>
+    </func>
+
+    <func>
+      <name name="apply_interval" arity="3" since="OTP 27.0"/>
+      <fsummary>Spawn a process evaluating <c>erlang:apply(Function, Arguments)</c>
+        repeatedly at intervals of <c>Time</c>.</fsummary>
+      <desc>
+        <p>Evaluates <c>spawn(erlang, apply, [<anno>Function</anno>,
+	  <anno>Arguments</anno>])</c> repeatedly at intervals of
+          <c><anno>Time</anno></c>, irrespective of whether a previously
+          spawned process has finished or not.</p>
+        <p>Returns <c>{ok, <anno>TRef</anno>}</c> or
+          <c>{error, <anno>Reason</anno>}</c>.</p>
+      </desc>
+    </func>
+
     <func>
       <name name="apply_interval" arity="4" since=""/>
       <fsummary>Spawn a process evaluating <c>Module:Function(Arguments)</c>
@@ -111,6 +164,34 @@
       </desc>
     </func>
 
+    <func>
+      <name name="apply_repeatedly" arity="2" since="OTP 27.0"/>
+      <fsummary>Spawn a process evaluating <c>erlang:apply(Function, [])</c>
+        repeatedly at intervals of <c>Time</c>.</fsummary>
+      <desc>
+        <p>Evaluates <c>spawn(erlang, apply, [<anno>Function</anno>,
+          []])</c> repeatedly at intervals of
+          <c><anno>Time</anno></c>, waiting for the spawned process to
+          finish before starting the next.</p>
+        <p>Returns <c>{ok, <anno>TRef</anno>}</c> or
+          <c>{error, <anno>Reason</anno>}</c>.</p>
+      </desc>
+    </func>
+
+    <func>
+      <name name="apply_repeatedly" arity="3" since="OTP 27.0"/>
+      <fsummary>Spawn a process evaluating <c>erlang:apply(Function, Arguments)</c>
+        repeatedly at intervals of <c>Time</c>.</fsummary>
+      <desc>
+        <p>Evaluates <c>spawn(erlang, apply, [<anno>Function</anno>,
+          <anno>Arguments</anno>])</c> repeatedly at intervals of
+          <c><anno>Time</anno></c>, waiting for the spawned process to
+          finish before starting the next.</p>
+        <p>Returns <c>{ok, <anno>TRef</anno>}</c> or
+          <c>{error, <anno>Reason</anno>}</c>.</p>
+      </desc>
+    </func>
+
     <func>
       <name name="apply_repeatedly" arity="4" since="OTP 26.0"/>
       <fsummary>Spawn a process evaluating <c>Module:Function(Arguments)</c>
@@ -405,22 +486,76 @@ timer:cancel(R),
 
     <p>An interval timer, that is, a timer created by evaluating any of the
       functions
+      <seemfa marker="#apply_interval/2"><c>apply_interval/2</c></seemfa>,
+      <seemfa marker="#apply_interval/3"><c>apply_interval/3</c></seemfa>,
       <seemfa marker="#apply_interval/4"><c>apply_interval/4</c></seemfa>,
-      <seemfa marker="#send_interval/3"><c>send_interval/3</c></seemfa>, and
-      <seemfa marker="#send_interval/2"><c>send_interval/2</c></seemfa>
+      <seemfa marker="#apply_repeatedly/2"><c>apply_repeatedly/2</c></seemfa>,
+      <seemfa marker="#apply_repeatedly/3"><c>apply_repeatedly/3</c></seemfa>,
+      <seemfa marker="#apply_repeatedly/4"><c>apply_repeatedly/4</c></seemfa>,
+      <seemfa marker="#send_interval/2"><c>send_interval/2</c></seemfa>, and
+      <seemfa marker="#send_interval/3"><c>send_interval/3</c></seemfa>
       is linked to the process to which the timer performs its task.</p>
 
     <p>A one-shot timer, that is, a timer created by evaluating any of the
       functions
+      <seemfa marker="#apply_after/2"><c>apply_after/2</c></seemfa>,
+      <seemfa marker="#apply_after/3"><c>apply_after/3</c></seemfa>,
       <seemfa marker="#apply_after/4"><c>apply_after/4</c></seemfa>,
-      <seemfa marker="#send_after/3"><c>send_after/3</c></seemfa>,
       <seemfa marker="#send_after/2"><c>send_after/2</c></seemfa>,
-      <seemfa marker="#exit_after/3"><c>exit_after/3</c></seemfa>,
+      <seemfa marker="#send_after/3"><c>send_after/3</c></seemfa>,
       <seemfa marker="#exit_after/2"><c>exit_after/2</c></seemfa>,
-      <seemfa marker="#kill_after/2"><c>kill_after/2</c></seemfa>, and
-      <seemfa marker="#kill_after/1"><c>kill_after/1</c></seemfa>
+      <seemfa marker="#exit_after/3"><c>exit_after/3</c></seemfa>,
+      <seemfa marker="#kill_after/1"><c>kill_after/1</c></seemfa>, and
+      <seemfa marker="#kill_after/2"><c>kill_after/2</c></seemfa>
       is not linked to any process. Hence, such a timer is removed only
       when it reaches its time-out, or if it is explicitly removed by a call to
       <seemfa marker="#cancel/1"><c>cancel/1</c></seemfa>.</p>
+
+    <p>The functions given to 
+      <seemfa marker="#apply_after/2"><c>apply_after/2</c></seemfa>,
+      <seemfa marker="#apply_after/3"><c>apply_after/3</c></seemfa>,
+      <seemfa marker="#apply_interval/2"><c>apply_interval/2</c></seemfa>,
+      <seemfa marker="#apply_interval/3"><c>apply_interval/3</c></seemfa>,
+      <seemfa marker="#apply_repeatedly/2"><c>apply_repeatedly/2</c></seemfa>, and
+      <seemfa marker="#apply_repeatedly/3"><c>apply_repeatedly/3</c></seemfa>,
+      or denoted by <c>Module</c>, <c>Function</c> and <c>Arguments</c> given to
+      <seemfa marker="#apply_after/4"><c>apply_after/4</c></seemfa>,
+      <seemfa marker="#apply_interval/4"><c>apply_interval/4</c></seemfa>, and
+      <seemfa marker="#apply_repeatedly/4"><c>apply_repeatedly/4</c></seemfa>
+      are executed in a freshly-spawned process, and therefore calls to <c>self()</c>
+      in those functions will return the Pid of this process, which is different
+      from the process that called <c>timer:apply_*</c>.</p>
+    <p><em>Example</em></p>
+    <p>In the following example, the intention is to set a timer to execute a
+      function after 1 second, which performs a fictional task, and then wants
+      to inform the process which set the timer about its completion, by sending
+      it a <c>done</c> message.</p>
+    <p>Using <c>self()</c> <em>inside</em> the timed function, the code below does
+      not work as intended. The task gets done, but the <c>done</c> message gets
+      sent to the wrong process and is lost.</p>
+    <pre>
+1> <input>timer:apply_after(1000, fun() -> do_something(), self() ! done end).</input>
+{ok,TRef}
+2> <input>receive done -> done after 5000 -> timeout end.</input>
+%% ... 5s pass...
+timeout</pre>
+    <p>The code below calls <c>self()</c> in the process which sets the timer and
+      assigns it to a variable, which is then used in the function to send the
+      <c>done</c> message to, and so works as intended.</p>
+    <pre>
+1> <input>Target = self()</input>
+&lt;0.82.0&gt;
+2> <input>timer:apply_after(1000, fun() -> do_something(), Target ! done end).</input>
+{ok,TRef}
+3> <input>receive done -> done after 5000 -> timeout end.</input>
+%% ... 1s passes...
+done</pre>
+    <p>Another option is to pass the message target as a parameter to the function.</p>
+    <pre>
+1> <input>timer:apply_after(1000, fun(Target) -> do_something(), Target ! done end, [self()]).</input>
+{ok,TRef}
+2> <input>receive done -> done after 5000 -> timeout end.</input>
+%% ... 1s passes...
+done</pre>
   </section>
 </erlref>
diff --git a/lib/stdlib/src/timer.erl b/lib/stdlib/src/timer.erl
index 5f1d2eb6b7..c02fc18427 100644
--- a/lib/stdlib/src/timer.erl
+++ b/lib/stdlib/src/timer.erl
@@ -19,10 +19,11 @@
 %%
 -module(timer).
 
--export([apply_after/4,
+-export([apply_after/2, apply_after/3, apply_after/4,
          send_after/3, send_after/2,
          exit_after/3, exit_after/2, kill_after/2, kill_after/1,
-         apply_interval/4, apply_repeatedly/4,
+         apply_interval/2, apply_interval/3, apply_interval/4,
+	 apply_repeatedly/2, apply_repeatedly/3, apply_repeatedly/4,
          send_interval/3, send_interval/2,
          cancel/1, sleep/1, tc/1, tc/2, tc/3, tc/4, now_diff/2,
          seconds/1, minutes/1, hours/1, hms/3]).
@@ -40,7 +41,9 @@
 
 %% Validations
 -define(valid_time(T), is_integer(T), T >= 0).
--define(valid_mfa(M, F, A), is_atom(M), is_atom(F), is_list(A)).
+-define(valid_apply(F), is_function(F, 0)).
+-define(valid_apply(F, A), is_list(A), is_function(F, length(A))).
+-define(valid_apply(M, F, A), is_atom(M), is_atom(F), is_list(A)).
 
 %%
 %% Time is in milliseconds.
@@ -52,6 +55,31 @@
 %%
 %% Interface functions
 %%
+-spec apply_after(Time, Function) ->
+          {'ok', TRef} | {'error', Reason}
+              when Time :: time(),
+                   Function :: fun(() -> _),
+                   TRef :: tref(),
+                   Reason :: term().
+apply_after(Time, F)
+  when ?valid_apply(F) ->
+    apply_after(Time, erlang, apply, [F, []]);
+apply_after(_Time, _F) ->
+    {error, badarg}.
+
+-spec apply_after(Time, Function, Arguments) ->
+          {'ok', TRef} | {'error', Reason}
+              when Time :: time(),
+                   Function :: fun((...) -> _),
+                   Arguments :: [term()],
+                   TRef :: tref(),
+                   Reason :: term().
+apply_after(Time, F, A)
+  when ?valid_apply(F, A) ->
+    apply_after(Time, erlang, apply, [F, A]);
+apply_after(_Time, _F, _A) ->
+    {error, badarg}.
+
 -spec apply_after(Time, Module, Function, Arguments) ->
           {'ok', TRef} | {'error', Reason}
               when Time :: time(),
@@ -61,12 +89,12 @@
                    TRef :: tref(),
                    Reason :: term().
 apply_after(0, M, F, A)
-  when ?valid_mfa(M, F, A) ->
+  when ?valid_apply(M, F, A) ->
     _ = do_apply({M, F, A}, false),
     {ok, {instant, make_ref()}};
 apply_after(Time, M, F, A)
   when ?valid_time(Time),
-       ?valid_mfa(M, F, A) ->
+       ?valid_apply(M, F, A) ->
     req(apply_once, {system_time(), Time, {M, F, A}});
 apply_after(_Time, _M, _F, _A) ->
     {error, badarg}.
@@ -146,6 +174,31 @@ kill_after(Time, Pid) ->
 kill_after(Time) ->
     exit_after(Time, self(), kill).
 
+-spec apply_interval(Time, Function) ->
+          {'ok', TRef} | {'error', Reason}
+              when Time :: time(),
+                   Function :: fun(() -> _),
+                   TRef :: tref(),
+                   Reason :: term().
+apply_interval(Time, F)
+  when ?valid_apply(F) ->
+    apply_interval(Time, erlang, apply, [F, []]);
+apply_interval(_Time, _F) ->
+    {error, badarg}.
+
+-spec apply_interval(Time, Function, Arguments) ->
+          {'ok', TRef} | {'error', Reason}
+              when Time :: time(),
+                   Function :: fun((...) -> _),
+                   Arguments :: [term()],
+                   TRef :: tref(),
+                   Reason :: term().
+apply_interval(Time, F, A)
+  when ?valid_apply(F, A) ->
+    apply_interval(Time, erlang, apply, [F, A]);
+apply_interval(_Time, _F, _A) ->
+    {error, badarg}.
+
 -spec apply_interval(Time, Module, Function, Arguments) ->
           {'ok', TRef} | {'error', Reason}
               when Time :: time(),
@@ -156,11 +209,36 @@ kill_after(Time) ->
                    Reason :: term().
 apply_interval(Time, M, F, A)
   when ?valid_time(Time),
-       ?valid_mfa(M, F, A) ->
+       ?valid_apply(M, F, A) ->
     req(apply_interval, {system_time(), Time, self(), {M, F, A}});
 apply_interval(_Time, _M, _F, _A) ->
     {error, badarg}.
 
+-spec apply_repeatedly(Time, Function) ->
+          {'ok', TRef} | {'error', Reason}
+              when Time :: time(),
+                   Function :: fun(() -> _),
+                   TRef :: tref(),
+                   Reason :: term().
+apply_repeatedly(Time, F)
+  when ?valid_apply(F) ->
+    apply_repeatedly(Time, erlang, apply, [F, []]);
+apply_repeatedly(_Time, _F) ->
+    {error, badarg}.
+
+-spec apply_repeatedly(Time, Function, Arguments) ->
+          {'ok', TRef} | {'error', Reason}
+              when Time :: time(),
+                   Function :: fun((...) -> _),
+                   Arguments :: [term()],
+                   TRef :: tref(),
+                   Reason :: term().
+apply_repeatedly(Time, F, A)
+  when ?valid_apply(F, A) ->
+    apply_repeatedly(Time, erlang, apply, [F, A]);
+apply_repeatedly(_Time, _F, _A) ->
+    {error, badarg}.
+
 -spec apply_repeatedly(Time, Module, Function, Arguments) ->
           {'ok', TRef} | {'error', Reason}
               when Time :: time(),
@@ -171,7 +249,7 @@ apply_interval(_Time, _M, _F, _A) ->
                    Reason :: term().
 apply_repeatedly(Time, M, F, A)
   when ?valid_time(Time),
-       ?valid_mfa(M, F, A) ->
+       ?valid_apply(M, F, A) ->
     req(apply_repeatedly, {system_time(), Time, self(), {M, F, A}});
 apply_repeatedly(_Time, _M, _F, _A) ->
     {error, badarg}.
diff --git a/lib/stdlib/test/timer_simple_SUITE.erl b/lib/stdlib/test/timer_simple_SUITE.erl
index 761689dc51..339ac7af91 100644
--- a/lib/stdlib/test/timer_simple_SUITE.erl
+++ b/lib/stdlib/test/timer_simple_SUITE.erl
@@ -240,14 +240,20 @@ init_per_testcase(_, Config) when is_list(Config) ->
 %% Test of apply_after with time = 0, with sending of message.
 apply_after1(Config) when is_list(Config) ->
     Msg = make_ref(),
-    {ok, {instant, _}} = timer:apply_after(0, ?MODULE, send, [self(), Msg]),
-    ok = get_mess(1000, Msg).
+    {ok, {instant, _}} = timer:apply_after(0, ?MODULE, send, [self(), {Msg, 1}]),
+    {ok, {instant, _}} = timer:apply_after(0, fun erlang:send/2, [self(), {Msg, 2}]),
+    Self = self(),
+    {ok, {instant, _}} = timer:apply_after(0, fun() -> Self ! {Msg, 3} end),
+    ok = get_messes(1000, Msg, [1, 2, 3]).
 
 %% Test of apply_after with time = 500, with sending of message.
 apply_after2(Config) when is_list(Config) ->
     Msg = make_ref(),
-    {ok, {once, _}} = timer:apply_after(500, ?MODULE, send, [self(), Msg]),
-    ok = get_mess(1000, Msg).
+    {ok, {once, _}} = timer:apply_after(500, ?MODULE, send, [self(), {Msg, 1}]),
+    {ok, {once, _}} = timer:apply_after(500, fun erlang:send/2, [self(), {Msg, 2}]),
+    Self = self(),
+    {ok, {once, _}} = timer:apply_after(500, fun() -> Self ! {Msg, 3} end),
+    ok = get_messes(1000, Msg, [1, 2, 3]).
 
 %% Test that a request starts the timer server if it is not running.
 apply_after3(Config) when is_list(Config) ->
@@ -270,6 +276,14 @@ apply_after4(Config) when is_list(Config) ->
 
 %% Test that apply_after rejects invalid arguments.
 apply_after_invalid_args(Config) when is_list(Config) ->
+    {error, badarg} = timer:apply_after(-1, fun() -> ok end),
+    {error, badarg} = timer:apply_after(0, foo),
+    {error, badarg} = timer:apply_after(0, fun(_X) -> ok end),
+    {error, badarg} = timer:apply_after(-1, fun(_X) -> ok end, [foo]),
+    {error, badarg} = timer:apply_after(0, foo, []),
+    {error, badarg} = timer:apply_after(0, fun(_X) -> ok end, []),
+    {error, badarg} = timer:apply_after(0, fun(_X) -> ok end, [foo, bar]),
+    {error, badarg} = timer:apply_after(0, fun(_X) -> ok end, foo),
     {error, badarg} = timer:apply_after(-1, foo, bar, []),
     {error, badarg} = timer:apply_after(0, "foo", bar, []),
     {error, badarg} = timer:apply_after(0, foo, "bar", []),
@@ -415,11 +429,17 @@ kill_after3(Config) when is_list(Config) ->
 %% not get any more messages.
 apply_interval1(Config) when is_list(Config) ->
     Msg = make_ref(),
-    {ok, Ref} = timer:apply_interval(1000, ?MODULE, send,
-                                     [self(), Msg]),
-    ok = get_mess(1500, Msg, 3),
-    {ok, cancel} = timer:cancel(Ref),
-    nor = get_mess(1000, Msg).
+    {ok, Ref1} = timer:apply_interval(1000, ?MODULE, send,
+                                      [self(), {Msg, 1}]),
+    {ok, Ref2} = timer:apply_interval(1000, fun erlang:send/2,
+				      [self(), {Msg, 2}]),
+    Self = self(),
+    {ok, Ref3} = timer:apply_interval(1000, fun() -> Self ! {Msg, 3} end),
+    ok = get_messes(1500, Msg, [1, 2, 3], 3),
+    {ok, cancel} = timer:cancel(Ref1),
+    {ok, cancel} = timer:cancel(Ref2),
+    {ok, cancel} = timer:cancel(Ref3),
+    nor = get_messes(1000, Msg, [1, 2, 3]).
 
 %% Test apply_interval with the execution time of the action
 %% longer than the timer interval. The timer should not wait for
@@ -427,19 +447,32 @@ apply_interval1(Config) when is_list(Config) ->
 %% previously started action is still running.
 apply_interval2(Config) when is_list(Config) ->
     Msg = make_ref(),
+    Fn = fun(P, Idx) ->
+             P ! {Msg, Idx},
+	    receive after 1000 -> ok end
+         end,
+    {ok, Ref1} = timer:apply_interval(500, erlang, apply,
+                                     [Fn, [self(), 1]]),
+    {ok, Ref2} = timer:apply_interval(500, Fn, [self(), 2]),
     Self = self(),
-    {ok, Ref} = timer:apply_interval(500, erlang, apply,
-                                     [fun() ->
-                                          Self ! Msg,
-                                          receive after 1000 -> ok end
-                                      end, []]),
+    {ok, Ref3} = timer:apply_interval(500, fun() -> Fn(Self, 3) end),
     receive after 1800 -> ok end,
-    {ok, cancel} = timer:cancel(Ref),
-    ok = get_mess(1000, Msg, 3),
-    nor = get_mess(1000, Msg).
+    {ok, cancel} = timer:cancel(Ref1),
+    {ok, cancel} = timer:cancel(Ref2),
+    {ok, cancel} = timer:cancel(Ref3),
+    ok = get_messes(1000, Msg, [1, 2, 3], 3),
+    nor = get_messes(1000, Msg, [1, 2, 3]).
 
 %% Test that apply_interval rejects invalid arguments.
 apply_interval_invalid_args(Config) when is_list(Config) ->
+    {error, badarg} = timer:apply_interval(-1, fun() -> ok end),
+    {error, badarg} = timer:apply_interval(0, foo),
+    {error, badarg} = timer:apply_interval(0, fun(_X) -> ok end),
+    {error, badarg} = timer:apply_interval(-1, fun(_X) -> ok end, [foo]),
+    {error, badarg} = timer:apply_interval(0, foo, []),
+    {error, badarg} = timer:apply_interval(0, fun(_X) -> ok end, []),
+    {error, badarg} = timer:apply_interval(0, fun(_X) -> ok end, [foo, bar]),
+    {error, badarg} = timer:apply_interval(0, fun(_X) -> ok end, foo),
     {error, badarg} = timer:apply_interval(-1, foo, bar, []),
     {error, badarg} = timer:apply_interval(0, "foo", bar, []),
     {error, badarg} = timer:apply_interval(0, foo, "bar", []),
@@ -453,11 +486,17 @@ apply_interval_invalid_args(Config) when is_list(Config) ->
 %% interval, this should behave the same as apply_interval.
 apply_repeatedly1(Config) when is_list(Config) ->
     Msg = make_ref(),
-    {ok, Ref} = timer:apply_repeatedly(1000, ?MODULE, send,
-                                       [self(), Msg]),
-    ok = get_mess(1500, Msg, 3),
-    {ok, cancel} = timer:cancel(Ref),
-    nor = get_mess(1000, Msg).
+    {ok, Ref1} = timer:apply_repeatedly(1000, ?MODULE, send,
+                                        [self(), {Msg, 1}]),
+    {ok, Ref2} = timer:apply_repeatedly(1000, fun erlang:send/2,
+                                        [self(), {Msg, 2}]),
+    Self = self(),
+    {ok, Ref3} = timer:apply_repeatedly(1000, fun() -> Self ! {Msg, 3} end),
+    ok = get_messes(1500, Msg, [1, 2, 3], 3),
+    {ok, cancel} = timer:cancel(Ref1),
+    {ok, cancel} = timer:cancel(Ref2),
+    {ok, cancel} = timer:cancel(Ref3),
+    nor = get_messes(1000, Msg, [1, 2, 3]).
 
 %% Test apply_repeatedly with the execution time of the action
 %% longer than the timer interval. The timer should wait for
@@ -465,19 +504,33 @@ apply_repeatedly1(Config) when is_list(Config) ->
 %% has completed.
 apply_repeatedly2(Config) when is_list(Config) ->
     Msg = make_ref(),
+    Fn = fun(P, I) ->
+             P ! {Msg, I},
+             receive after 1000 -> ok end
+         end,
     Self = self(),
-    {ok, Ref} = timer:apply_repeatedly(1, erlang, apply,
-                                       [fun() ->
-                                            Self ! Msg,
-                                            receive after 1000 -> ok end
-                                        end, []]),
+    {ok, Ref1} = timer:apply_repeatedly(1, erlang, apply,
+                                        [Fn, [self(), 1]]),
+    {ok, Ref2} = timer:apply_repeatedly(1, Fn, [self(), 2]),
+    Self = self(),
+    {ok, Ref3} = timer:apply_repeatedly(1, fun() -> Fn(Self, 3) end),
     receive after 2500 -> ok end,
-    {ok, cancel} = timer:cancel(Ref),
-    ok = get_mess(1000, Msg, 3),
-    nor = get_mess(1000, Msg).
+    {ok, cancel} = timer:cancel(Ref1),
+    {ok, cancel} = timer:cancel(Ref2),
+    {ok, cancel} = timer:cancel(Ref3),
+    ok = get_messes(1000, Msg, [1, 2, 3], 3),
+    nor = get_messes(1000, Msg, [1, 2, 3]).
 
 %% Test that apply_repeatedly rejects invalid arguments.
 apply_repeatedly_invalid_args(Config) when is_list(Config) ->
+    {error, badarg} = timer:apply_repeatedly(-1, fun() -> ok end),
+    {error, badarg} = timer:apply_repeatedly(0, foo),
+    {error, badarg} = timer:apply_repeatedly(0, fun(_X) -> ok end),
+    {error, badarg} = timer:apply_repeatedly(-1, fun(_X) -> ok end, [foo]),
+    {error, badarg} = timer:apply_repeatedly(0, foo, []),
+    {error, badarg} = timer:apply_repeatedly(0, fun(_X) -> ok end, []),
+    {error, badarg} = timer:apply_repeatedly(0, fun(_X) -> ok end, [foo, bar]),
+    {error, badarg} = timer:apply_repeatedly(0, fun(_X) -> ok end, foo),
     {error, badarg} = timer:apply_repeatedly(-1, foo, bar, []),
     {error, badarg} = timer:apply_repeatedly(0, "foo", bar, []),
     {error, badarg} = timer:apply_repeatedly(0, foo, "bar", []),
@@ -781,6 +834,16 @@ get_mess(Time, Mess, N) ->
         nor   % Not Received
     end.
 
+get_messes(Time, Mess, Indexes) -> get_messes(Time, Mess, Indexes, 1).
+get_messes(Time, Mess, Indexes, N) -> get_messes1(Time, Mess, lists:append(lists:duplicate(N, Indexes))).
+get_messes1(_, _, []) -> ok;
+get_messes1(Time, Mess, Indexes) ->
+    receive
+        {Mess, Index} -> get_messes1(Time, Mess, lists:delete(Index, Indexes))
+    after Time ->
+        nor
+    end.
+
 forever() ->
     ok = timer:sleep(1000),
     forever().
-- 
2.35.3

openSUSE Build Service is sponsored by