timer (stdlib v3.15.2)
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/4
, send_interval/3
, and send_interval/2
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/4
, send_after/3
, send_after/2
, exit_after/3
, exit_after/2
, kill_after/2
, and kill_after/1
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
.
Link to this section Summary
Functions
Evaluates apply(Module, Function, Arguments)
after Time
milliseconds.
Evaluates apply(Module, Function, Arguments)
repeatedly at intervals of Time
.
Cancels a previously requested time-out. TRef
is a unique timer reference returned by the related timer function.
exit_after/2
is the same as exit_after(Time, self(), Reason1)
.
Returns the number of milliseconds in Hours + Minutes + Seconds
.
Returns the number of milliseconds in Hours
.
kill_after/1
is the same as exit_after(Time, self(), 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
.
send_after/3
Evaluates
Destination ! Message
afterTime
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.)
send_interval/3
Evaluates
Destination ! Message
repeatedly afterTime
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.)
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. 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.
tc/3
Evaluates
apply(Module, Function, Arguments)
and measures the elapsed real time as reported byerlang:monotonic_time/0
.
Link to this section Types
-type time() :: term().
Specs
time() :: non_neg_integer().
Time in milliseconds.
Specs
tref()
A timer reference.
Link to this section Functions
apply_after/4
Specs
apply_after(Time, Module, Function, Arguments) -> {ok, TRef} | {error, Reason} when Time :: time(), Module :: module(), Function :: atom(), Arguments :: [term()], TRef :: tref(), Reason :: term().
Evaluates apply(Module, Function, Arguments)
after Time
milliseconds.
Returns {ok, TRef}
or {error, Reason}
.
apply_interval/4
Specs
apply_interval(Time, Module, Function, Arguments) -> {ok, TRef} | {error, Reason} when Time :: time(), Module :: module(), Function :: atom(), Arguments :: [term()], TRef :: tref(), Reason :: term().
Evaluates apply(Module, Function, Arguments)
repeatedly at intervals of Time
.
Returns {ok, TRef}
or {error, Reason}
.
cancel/1
Specs
cancel(TRef) -> {ok, cancel} | {error, Reason} when TRef :: tref(), Reason :: term().
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.
exit_after/2
Specs
exit_after(Time, Reason1) -> {ok, TRef} | {error, Reason2} when Time :: time(), TRef :: tref(), Reason1 :: term(), Reason2 :: term().
exit_after/2
is the same as exit_after(Time, self(), Reason1)
.
exit_after/3
sends an exit signal with reason Reason1
to Target
, which can be a local process identifier or an atom of a registered name. Returns {ok, TRef}
or {error, Reason2}
.
exit_after/3
Specs
hms/3
Specs
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
.
hours/1
Specs
hours(Hours) -> MilliSeconds when Hours :: non_neg_integer(), MilliSeconds :: non_neg_integer().
Returns the number of milliseconds in Hours
.
kill_after/1
Specs
kill_after(Time) -> {ok, TRef} | {error, Reason2} when Time :: time(), TRef :: tref(), Reason2 :: term().
kill_after/1
is the same as exit_after(Time, self(), kill)
.
kill_after/2
is the same as exit_after(Time, Target, kill)
.
kill_after/2
Specs
minutes/1
Specs
minutes(Minutes) -> MilliSeconds when Minutes :: non_neg_integer(), MilliSeconds :: non_neg_integer().
Returns the number of milliseconds in Minutes
.
now_diff/2
Specs
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
.
seconds/1
Specs
seconds(Seconds) -> MilliSeconds when Seconds :: non_neg_integer(), MilliSeconds :: non_neg_integer().
Returns the number of milliseconds in Seconds
.
send_after/2
Specs
send_after(Time, Message) -> {ok, TRef} | {error, Reason} when Time :: time(), Message :: term(), TRef :: tref(), Reason :: term().
send_after/3
Evaluates
Destination ! Message
afterTime
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.)Returns
{ok, TRef}
or{error, Reason}
.See also the Timer Module section in the Efficiency Guide.
send_after/2
Same as
send_after(Time, self(), Message)
.
send_after/3
Specs
send_interval/2
Specs
send_interval(Time, Message) -> {ok, TRef} | {error, Reason} when Time :: time(), Message :: term(), TRef :: tref(), Reason :: term().
send_interval/3
Evaluates
Destination ! Message
repeatedly afterTime
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.)Returns
{ok, TRef}
or{error, Reason}
.send_interval/2
Same as
send_interval(Time, self(), Message)
.
send_interval/3
Specs
sleep/1
Specs
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.
Before OTP 25, timer:sleep/1
did not accept integer timeout values greater than 16#ffffffff
, that is, 2^32-1
. Since OTP 25, arbitrarily high integer values are accepted.
start/0
Specs
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.
Specs
tc(Fun) -> {Time, Value} when Fun :: function(), Time :: integer(), Value :: term().
tc/3
Evaluates
apply(Module, Function, Arguments)
and measures the elapsed real time as reported byerlang:monotonic_time/0
.Returns
{Time, Value}
, whereTime
is the elapsed real time in microseconds, andValue
is what is returned from the apply.tc/2
Evaluates
apply(Fun, Arguments)
. Otherwise the same astc/3
.tc/1
Evaluates
Fun()
. Otherwise the same astc/2
.
Specs
tc(Fun, Arguments) -> {Time, Value} when Fun :: function(), Arguments :: [term()], Time :: integer(), Value :: term().
Specs
tc(Module, Function, Arguments) -> {Time, Value} when Module :: module(), Function :: atom(), Arguments :: [term()], Time :: integer(), Value :: term().