On this page
timer
Module
timer
Module summary
Timer Functions
Description
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 carried out by another process.
Successful evaluations of the timer functions yield return values containing a timer reference, denoted TRef
below. By using cancel/1
, the returned reference can be used to cancel any requested action. A TRef
is an Erlang term, the contents of which must not be altered.
The timeouts are not exact, but should be at least
as long as requested.
Data types
time() = integer() >= 0
Time in milliseconds.
tref()
A timer reference.
Exports
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 should be started explicitly. Use configuration parameters for kernel
for this.
apply_after(Time, Module, Function, Arguments) -> {ok, TRef} | {error, Reason}
Types:
Time = time()
Module = module()
Function = atom()
Arguments = [term()]
TRef = tref()
Reason = term()
Evaluates apply(Module, Function, Arguments)
after Time
amount of time has elapsed. Returns {ok, TRef}
, or {error, Reason}
.
send_after(Time, Message) -> {ok, TRef} | {error, Reason}
send_after(Time, Pid, Message) -> {ok, TRef} | {error, Reason}
Types:
Time = time()
Pid = pid() | (RegName :: atom())
Message = term()
TRef = tref()
Reason = term()
-
send_after/3
-
Evaluates
Pid ! Message
afterTime
amount of time has elapsed. (Pid
can also be an atom of a registered name.) Returns{ok, TRef}
, or{error, Reason}
. -
send_after/2
-
Same as
send_after(Time, self(), Message)
.
kill_after(Time) -> {ok, TRef} | {error, Reason2}
kill_after(Time, Pid) -> {ok, TRef} | {error, Reason2}
exit_after(Time, Reason1) -> {ok, TRef} | {error, Reason2}
exit_after(Time, Pid, Reason1) -> {ok, TRef} | {error, Reason2}
Types:
Time = time()
Pid = pid() | (RegName :: atom())
TRef = tref()
Reason1 = Reason2 = term()
-
exit_after/3
-
Send an exit signal with reason
Reason1
to PidPid
. Returns{ok, TRef}
, or{error, Reason2}
. -
exit_after/2
-
Same as
exit_after(Time, self(), Reason1)
. -
kill_after/2
-
Same as
exit_after(Time, Pid, kill)
. -
kill_after/1
-
Same as
exit_after(Time, self(), kill)
.
apply_interval(Time, Module, Function, Arguments) -> {ok, TRef} | {error, Reason}
Types:
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}
.
send_interval(Time, Message) -> {ok, TRef} | {error, Reason}
send_interval(Time, Pid, Message) -> {ok, TRef} | {error, Reason}
Types:
Time = time()
Pid = pid() | (RegName :: atom())
Message = term()
TRef = tref()
Reason = term()
-
send_interval/3
-
Evaluates
Pid ! Message
repeatedly afterTime
amount of time has elapsed. (Pid
can also be an atom of a registered name.) Returns{ok, TRef}
or{error, Reason}
. -
send_interval/2
-
Same as
send_interval(Time, self(), Message)
.
cancel(TRef) -> {ok, cancel} | {error, Reason}
Types:
TRef = tref()
Reason = term()
Cancels a previously requested timeout. TRef
is a unique timer reference returned by the timer function in question. Returns {ok, cancel}
, or {error, Reason}
when TRef
is not a timer reference.
sleep(Time) -> ok
Types:
Time = timeout()
Suspends the process calling this function for Time
amount of milliseconds and then returns ok
, or suspend the process forever if Time
is the atom infinity
. Naturally, this function does not return immediately.
tc(Fun) -> {Time, Value}
tc(Fun, Arguments) -> {Time, Value}
tc(Module, Function, Arguments) -> {Time, Value}
Types:
Module = module()
Function = atom()
Arguments = [term()]
Time = integer()
In microseconds
Value = term()
-
tc/3
-
Evaluates
apply(Module, Function, Arguments)
and measures the elapsed real time as reported byos:timestamp/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 works liketc/3
. -
tc/1
-
Evaluates
Fun()
. Otherwise works liketc/2
.
now_diff(T2, T1) -> Tdiff
Types:
T1 = T2 = erlang:timestamp()
Tdiff = integer()
In microseconds
Calculates the time difference Tdiff = T2 - T1
in microseconds, where T1
and T2
are timestamp tuples on the same format as returned from erlang:timestamp/0
, or os:timestamp/0
.
seconds(Seconds) -> MilliSeconds
Types:
Seconds = MilliSeconds = integer() >= 0
Returns the number of milliseconds in Seconds
.
minutes(Minutes) -> MilliSeconds
Types:
Minutes = MilliSeconds = integer() >= 0
Return the number of milliseconds in Minutes
.
hours(Hours) -> MilliSeconds
Types:
Hours = MilliSeconds = integer() >= 0
Returns the number of milliseconds in Hours
.
hms(Hours, Minutes, Seconds) -> MilliSeconds
Types:
Hours = Minutes = Seconds = MilliSeconds = integer() >= 0
Returns the number of milliseconds in Hours + Minutes + Seconds
.
Examples
This example illustrates how to print out "Hello World!" in 5 seconds:
1> timer:apply_after(5000, io, format, ["~nHello World!~n", []]).
{ok,TRef}
Hello World!
The following coding example illustrates a process which performs a certain action and if this action is not completed within a certain limit, then 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),
...
Warning
A timer can always be removed by calling cancel/1
.
An interval timer, i.e. a timer created by evaluating any of the functions apply_interval/4
, send_interval/3
, and send_interval/2
, is linked to the process towards which the timer performs its task.
A one-shot timer, i.e. 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 timeout, or if it is explicitly removed by a call to cancel/1
.
© 2010–2017 Ericsson AB
Licensed under the Apache License, Version 2.0.