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.
Functions
apply_after(Time, Module, Function, Arguments) ->
{ok, TRef} | {error, Reason}
Evaluates apply(
after
milliseconds.
Returns {ok,
or
{error,
.
apply_interval(Time, Module, Function, Arguments) ->
{ok, TRef} | {error, Reason}
Evaluates apply(
repeatedly at intervals of
.
Returns {ok,
or
{error,
.
cancel(TRef) -> {ok, cancel} | {error, Reason}
TRef = tref()
Reason = term()
Cancels a previously requested time-out.
is
a unique
timer reference returned by the related timer function.
Returns {ok, cancel}
, or {error,
when
is not a timer reference.
exit_after(Time, Reason1) -> {ok, TRef} | {error, Reason2}
exit_after(Time, Pid, Reason1) -> {ok, TRef} | {error, Reason2}
exit_after/2
is the same as
exit_after(
.
exit_after/3
sends an exit signal with reason
to
pid
. Returns {ok,
or {error,
.
hms(Hours, Minutes, Seconds) -> MilliSeconds
Hours = Minutes = Seconds = MilliSeconds = integer() >= 0
Returns the number of milliseconds in
.
hours(Hours) -> MilliSeconds
Hours = MilliSeconds = integer() >= 0
Returns the number of milliseconds in
.
kill_after(Time) -> {ok, TRef} | {error, Reason2}
kill_after(Time, Pid) -> {ok, TRef} | {error, Reason2}
kill_after/1
is the same as
exit_after(
.
kill_after/2
is the same as
exit_after(
.
minutes(Minutes) -> MilliSeconds
Minutes = MilliSeconds = integer() >= 0
Returns the number of milliseconds in
.
now_diff(T2, T1) -> Tdiff
T1 = T2 = erlang:timestamp()
Tdiff = integer()
Tdiff = In microseconds
Calculates the time difference
in microseconds,
where
and
are time-stamp tuples on the same format as returned from
erlang:timestamp/0
or
os:timestamp/0
.
seconds(Seconds) -> MilliSeconds
Seconds = MilliSeconds = integer() >= 0
Returns the number of milliseconds in
.
send_after(Time, Message) -> {ok, TRef} | {error, Reason}
send_after(Time, Pid, Message) -> {ok, TRef} | {error, Reason}
send_after/3
Evaluates
after
milliseconds. (
can also be an atom of a registered name.)
Returns {ok,
or
{error,
.
send_after/2
Same as send_after(
.
send_interval(Time, Message) -> {ok, TRef} | {error, Reason}
send_interval(Time, Pid, Message) -> {ok, TRef} | {error, Reason}
send_interval/3
Evaluates
repeatedly after
milliseconds.
(
can also be
an atom of a registered name.)
Returns {ok,
or
{error,
.
send_interval/2
Same as send_interval(
.
sleep(Time) -> ok
Time = timeout()
Suspends the process calling this function for
milliseconds and then returns ok
,
or suspends the process forever if
is the
atom infinity
. Naturally, this
function does not return immediately.
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.
tc(Fun) -> {Time, Value}
Fun = function()
Time = integer()
Value = term()
tc(Fun, Arguments) -> {Time, Value}
Fun = function()
Arguments = [term()]
Time = integer()
Value = term()
tc(Module, Function, Arguments) -> {Time, Value}
Module = module()
Function = atom()
Arguments = [term()]
Time = integer()
Value = term()
Time = In microseconds
tc/3
Evaluates apply(
and measures the elapsed real time as
reported by
erlang:monotonic_time/0
.
Returns {
, where
is the elapsed real time in
microseconds, and
is what is
returned from the apply.
tc/2
Evaluates apply(
.
Otherwise the same as tc/3
.
tc/1
Evaluates
. Otherwise the same as
tc/2
.
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
.