View Source timer (stdlib v6.1.2)
Timer functions.
This module provides useful functions related to time. Unless otherwise stated, time is always measured in milliseconds. All timer functions return immediately, regardless of work done by another process.
Successful evaluations of the timer functions give return values containing a
timer reference, denoted TRef
. By using cancel/1
, the returned reference can
be used to cancel any requested action. A TRef
is an Erlang term, which
contents must not be changed.
The time-outs are not exact, but are at least as long as requested.
Creating timers using erlang:send_after/3
and erlang:start_timer/3
is more
efficient than using the timers provided by this module. However, the timer
module has been improved in OTP 25, making it more efficient and less
susceptible to being overloaded. See
the Timer Module section in the Efficiency Guide.
Examples
Example 1
The following example shows how to print "Hello World!" in 5 seconds:
1> timer:apply_after(5000, io, format, ["~nHello World!~n", []]).
{ok,TRef}
Hello World!
Example 2
The following example shows a process performing a certain action, and if this action is not completed within a certain limit, the process is killed:
Pid = spawn(mod, fun, [foo, bar]),
%% If pid is not finished in 10 seconds, kill him
{ok, R} = timer:kill_after(timer:seconds(10), Pid),
...
%% We change our mind...
timer:cancel(R),
...
Notes
A timer can always be removed by calling cancel/1
.
An interval timer, that is, a timer created by evaluating any of the functions
apply_interval/2
, apply_interval/3
, apply_interval/4
,
apply_repeatedly/2
, apply_repeatedly/3
, apply_repeatedly/4
,
send_interval/2
, and send_interval/3
is linked to the process to which the
timer performs its task.
A one-shot timer, that is, a timer created by evaluating any of the functions
apply_after/2
, apply_after/3
, apply_after/4
, send_after/2
,
send_after/3
, exit_after/2
, exit_after/3
, kill_after/1
, and
kill_after/2
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
cancel/1
.
The functions given to apply_after/2
, apply_after/3
, apply_interval/2
,
apply_interval/3
, apply_repeatedly/2
, and apply_repeatedly/3
, or denoted
by Module
, Function
and Arguments
given to apply_after/4
,
apply_interval/4
, and apply_repeatedly/4
are executed in a freshly-spawned
process, and therefore calls to self/0
in those functions will return the Pid
of this process, which is different from the process that called
timer:apply_*
.
Example
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 done
message.
Using self/0
inside the timed function, the code below does not work as
intended. The task gets done, but the done
message gets sent to the wrong
process and is lost.
1> timer:apply_after(1000, fun() -> do_something(), self() ! done end).
{ok,TRef}
2> receive done -> done after 5000 -> timeout end.
%% ... 5s pass...
timeout
The code below calls self/0
in the process which sets the timer and assigns it
to a variable, which is then used in the function to send the done
message to,
and so works as intended.
1> Target = self()
<0.82.0>
2> timer:apply_after(1000, fun() -> do_something(), Target ! done end).
{ok,TRef}
3> receive done -> done after 5000 -> timeout end.
%% ... 1s passes...
done
Another option is to pass the message target as a parameter to the function.
1> timer:apply_after(1000, fun(Target) -> do_something(), Target ! done end, [self()]).
{ok,TRef}
2> receive done -> done after 5000 -> timeout end.
%% ... 1s passes...
done
Summary
Functions
Evaluates spawn(erlang, apply, [Function, []])
after Time
milliseconds.
Evaluates spawn(erlang, apply, [Function, Arguments])
after
Time
milliseconds.
Evaluates spawn(Module, Function, Arguments)
after Time
milliseconds.
Evaluates spawn(erlang, apply, [Function, []])
repeatedly at
intervals of Time
, irrespective of whether a previously spawned process has
finished or not.
Evaluates spawn(erlang, apply, [Function, Arguments])
repeatedly
at intervals of Time
, irrespective of whether a previously spawned process has
finished or not.
Evaluates spawn(Module, Function, Arguments)
repeatedly at
intervals of Time
, irrespective of whether a previously spawned process has
finished or not.
Evaluates spawn(erlang, apply, [Function, []])
repeatedly at
intervals of Time
, waiting for the spawned process to finish before starting
the next.
Evaluates spawn(erlang, apply, [Function, Arguments])
repeatedly
at intervals of Time
, waiting for the spawned process to finish before
starting the next.
Evaluates spawn(Module, Function, Arguments)
repeatedly at
intervals of Time
, waiting for the spawned process to finish before starting
the next.
Cancels a previously requested time-out. TRef
is a unique timer reference
returned by the related timer function.
Equivalent to exit_after(Time, self(), Reason)
.
Sends an exit signal with reason Reason1
to Target
, which can be a local
process identifier or an atom of a registered name.
Returns the number of milliseconds in Hours + Minutes + Seconds
.
Returns the number of milliseconds in Hours
.
Equivalent to exit_after(Time, self(), kill)
.
Equivalent to exit_after(Time, Target, kill)
.
Returns the number of milliseconds in Minutes
.
Calculates the time difference Tdiff = T2 - T1
in microseconds, where T1
and T2
are time-stamp tuples on the same format as returned from
erlang:timestamp/0
or os:timestamp/0
.
Returns the number of milliseconds in Seconds
.
Equivalent to send_after(Time, self(), Message)
.
Evaluates Destination ! Message
after Time
milliseconds.
Equivalent to send_interval(Time, self(), Message)
.
Evaluates Destination ! Message
repeatedly after Time
milliseconds.
Suspends the process calling this function for Time
milliseconds and then
returns ok
, or suspends the process forever if Time
is the atom infinity
.
Naturally, this function does not return immediately.
Starts the timer server.
Equivalent to tc(Fun, microsecond)
.
Measures the execution time of Fun
.
Measures the execution time of Fun
or apply(Module, Function, Arguments)
.
Evaluates apply(Module, Function, Arguments)
and measures the elapsed
real time as reported by erlang:monotonic_time/0
.
Types
-type time() :: non_neg_integer().
Time in milliseconds.
-opaque tref()
A timer reference.
Functions
-spec apply_after(Time, Function) -> {ok, TRef} | {error, Reason} when Time :: time(), Function :: fun(() -> _), TRef :: tref(), Reason :: term().
Evaluates spawn(erlang, apply, [Function, []])
after Time
milliseconds.
-spec apply_after(Time, Function, Arguments) -> {ok, TRef} | {error, Reason} when Time :: time(), Function :: fun((...) -> _), Arguments :: [term()], TRef :: tref(), Reason :: term().
Evaluates spawn(erlang, apply, [Function, Arguments])
after
Time
milliseconds.
-spec apply_after(Time, Module, Function, Arguments) -> {ok, TRef} | {error, Reason} when Time :: time(), Module :: module(), Function :: atom(), Arguments :: [term()], TRef :: tref(), Reason :: term().
Evaluates spawn(Module, Function, Arguments)
after Time
milliseconds.
-spec apply_interval(Time, Function) -> {ok, TRef} | {error, Reason} when Time :: time(), Function :: fun(() -> _), TRef :: tref(), Reason :: term().
Evaluates spawn(erlang, apply, [Function, []])
repeatedly at
intervals of Time
, irrespective of whether a previously spawned process has
finished or not.
-spec apply_interval(Time, Function, Arguments) -> {ok, TRef} | {error, Reason} when Time :: time(), Function :: fun((...) -> _), Arguments :: [term()], TRef :: tref(), Reason :: term().
Evaluates spawn(erlang, apply, [Function, Arguments])
repeatedly
at intervals of Time
, irrespective of whether a previously spawned process has
finished or not.
-spec apply_interval(Time, Module, Function, Arguments) -> {ok, TRef} | {error, Reason} when Time :: time(), Module :: module(), Function :: atom(), Arguments :: [term()], TRef :: tref(), Reason :: term().
Evaluates spawn(Module, Function, Arguments)
repeatedly at
intervals of Time
, irrespective of whether a previously spawned process has
finished or not.
Warning
If the execution time of the spawned process is, on average, greater than the given
Time
, multiple such processes will run at the same time. With long execution times, short intervals, and many interval timers running, this may even lead to exceeding the number of allowed processes. As an extreme example, consider[timer:apply_interval(1, timer, sleep, [1000]) || _ <- lists:seq(1, 1000)]
, that is, 1,000 interval timers executing a process that takes 1s to complete, started in intervals of 1ms, which would result in 1,000,000 processes running at the same time, far more than a node started with default settings allows (see the System Limits section in the Effiency Guide).
-spec apply_repeatedly(Time, Function) -> {ok, TRef} | {error, Reason} when Time :: time(), Function :: fun(() -> _), TRef :: tref(), Reason :: term().
Evaluates spawn(erlang, apply, [Function, []])
repeatedly at
intervals of Time
, waiting for the spawned process to finish before starting
the next.
-spec apply_repeatedly(Time, Function, Arguments) -> {ok, TRef} | {error, Reason} when Time :: time(), Function :: fun((...) -> _), Arguments :: [term()], TRef :: tref(), Reason :: term().
Evaluates spawn(erlang, apply, [Function, Arguments])
repeatedly
at intervals of Time
, waiting for the spawned process to finish before
starting the next.
apply_repeatedly(Time, Module, Function, Arguments)
View Source (since OTP 26.0)-spec apply_repeatedly(Time, Module, Function, Arguments) -> {ok, TRef} | {error, Reason} when Time :: time(), Module :: module(), Function :: atom(), Arguments :: [term()], TRef :: tref(), Reason :: term().
Evaluates spawn(Module, Function, Arguments)
repeatedly at
intervals of Time
, waiting for the spawned process to finish before starting
the next.
If the execution time of the spawned process is greater than the given Time
,
the next process is spawned immediately after the one currently running has
finished. Assuming that execution times of the spawned processes performing the
applies on average are smaller than Time
, the amount of applies made over a
large amount of time will be the same even if some individual execution times
are larger than Time
. The system will try to catch up as soon as possible. For
example, if one apply takes 2.5*Time
, the following two applies will be made
immediately one after the other in sequence.
Cancels a previously requested time-out. TRef
is a unique timer reference
returned by the related timer function.
Returns {ok, cancel}
, or {error, Reason}
when TRef
is not a timer
reference.
-spec exit_after(Time, Reason1) -> {ok, TRef} | {error, Reason2} when Time :: time(), TRef :: tref(), Reason1 :: term(), Reason2 :: term().
Equivalent to exit_after(Time, self(), Reason)
.
-spec exit_after(Time, Target, Reason1) -> {ok, TRef} | {error, Reason2} when Time :: time(), Target :: pid() | (RegName :: atom()), TRef :: tref(), Reason1 :: term(), Reason2 :: term().
Sends an exit signal with reason Reason1
to Target
, which can be a local
process identifier or an atom of a registered name.
-spec hms(Hours, Minutes, Seconds) -> MilliSeconds when Hours :: non_neg_integer(), Minutes :: non_neg_integer(), Seconds :: non_neg_integer(), MilliSeconds :: non_neg_integer().
Returns the number of milliseconds in Hours + Minutes + Seconds
.
-spec hours(Hours) -> MilliSeconds when Hours :: non_neg_integer(), MilliSeconds :: non_neg_integer().
Returns the number of milliseconds in Hours
.
-spec kill_after(Time) -> {ok, TRef} | {error, Reason2} when Time :: time(), TRef :: tref(), Reason2 :: term().
Equivalent to exit_after(Time, self(), kill)
.
-spec kill_after(Time, Target) -> {ok, TRef} | {error, Reason2} when Time :: time(), Target :: pid() | (RegName :: atom()), TRef :: tref(), Reason2 :: term().
Equivalent to exit_after(Time, Target, kill)
.
-spec minutes(Minutes) -> MilliSeconds when Minutes :: non_neg_integer(), MilliSeconds :: non_neg_integer().
Returns the number of milliseconds in Minutes
.
-spec now_diff(T2, T1) -> Tdiff when T1 :: erlang:timestamp(), T2 :: erlang:timestamp(), Tdiff :: integer().
Calculates the time difference Tdiff = T2 - T1
in microseconds, where T1
and T2
are time-stamp tuples on the same format as returned from
erlang:timestamp/0
or os:timestamp/0
.
-spec seconds(Seconds) -> MilliSeconds when Seconds :: non_neg_integer(), MilliSeconds :: non_neg_integer().
Returns the number of milliseconds in Seconds
.
-spec send_after(Time, Message) -> {ok, TRef} | {error, Reason} when Time :: time(), Message :: term(), TRef :: tref(), Reason :: term().
Equivalent to send_after(Time, self(), Message)
.
-spec send_after(Time, Destination, Message) -> {ok, TRef} | {error, Reason} when Time :: time(), Destination :: pid() | (RegName :: atom()) | {RegName :: atom(), Node :: node()}, Message :: term(), TRef :: tref(), Reason :: term().
Evaluates Destination ! Message
after Time
milliseconds.
Destination
can be a remote or local process identifier, an atom of a
registered name or a tuple {RegName, Node}
for a registered name at another node.
-spec send_interval(Time, Message) -> {ok, TRef} | {error, Reason} when Time :: time(), Message :: term(), TRef :: tref(), Reason :: term().
Equivalent to send_interval(Time, self(), Message)
.
-spec send_interval(Time, Destination, Message) -> {ok, TRef} | {error, Reason} when Time :: time(), Destination :: pid() | (RegName :: atom()) | {RegName :: atom(), Node :: node()}, Message :: term(), TRef :: tref(), Reason :: term().
Evaluates Destination ! Message
repeatedly after Time
milliseconds.
Destination
can be a remote or local process identifier, an atom of a registered
name or a tuple {RegName, Node}
for a registered name at another node.
-spec sleep(Time) -> ok when Time :: timeout().
Suspends the process calling this function for Time
milliseconds and then
returns ok
, or suspends the process forever if Time
is the atom infinity
.
Naturally, this function does not return immediately.
Note
Before OTP 25,
timer:sleep/1
did not accept integer timeout values greater than16#ffffffff
, that is,2^32-1
. Since OTP 25, arbitrarily high integer values are accepted.
-spec start() -> ok.
Starts the timer server.
Normally, the server does not need to be started explicitly. It is started dynamically if it is needed. This is useful during development, but in a target system the server is to be started explicitly. Use configuration parameters for Kernel for this.
Equivalent to tc(Fun, microsecond)
.
-spec tc(Fun, Arguments) -> {Time, Value} when Fun :: function(), Arguments :: [term()], Time :: integer(), Value :: term(); (Fun, TimeUnit) -> {Time, Value} when Fun :: function(), TimeUnit :: erlang:time_unit(), Time :: integer(), Value :: term().
Measures the execution time of Fun
.
Equivalent to tc(Fun, Arguments, microsecond)
if called as tc(Fun, Arguments)
.
Measures the execution time of Fun
in TimeUnit
if called as tc(Fun, TimeUnit)
. Added in OTP 26.0.
-spec tc(Module, Function, Arguments) -> {Time, Value} when Module :: module(), Function :: atom(), Arguments :: [term()], Time :: integer(), Value :: term(); (Fun, Arguments, TimeUnit) -> {Time, Value} when Fun :: function(), Arguments :: [term()], TimeUnit :: erlang:time_unit(), Time :: integer(), Value :: term().
Measures the execution time of Fun
or apply(Module, Function, Arguments)
.
Equivalent to tc(Module, Function, Arguments, microsecond)
if called as tc(Module, Function, Arguments)
.
Equivalent to tc(erlang, apply, [Fun, Arguments], TimeUnit)
if called as tc(Fun, Arguments, TimeUnit)
. Added in OTP 26.0
-spec tc(Module, Function, Arguments, TimeUnit) -> {Time, Value} when Module :: module(), Function :: atom(), Arguments :: [term()], TimeUnit :: erlang:time_unit(), Time :: integer(), Value :: term().
Evaluates apply(Module, Function, Arguments)
and measures the elapsed
real time as reported by erlang:monotonic_time/0
.
Returns {Time, Value}
, where Time
is the elapsed real time in the
specified TimeUnit
, and Value
is what is returned from the apply.