From 84adefa331c4159d432d22840663c38f155cd4c1 Mon Sep 17 00:00:00 2001 From: Erlang/OTP Date: Fri, 20 Nov 2009 14:54:40 +0000 Subject: The R13B03 release. --- lib/stdlib/doc/src/timer.xml | 300 +++++++++++++++++++++++++++++++++++++++++++ 1 file changed, 300 insertions(+) create mode 100644 lib/stdlib/doc/src/timer.xml (limited to 'lib/stdlib/doc/src/timer.xml') diff --git a/lib/stdlib/doc/src/timer.xml b/lib/stdlib/doc/src/timer.xml new file mode 100644 index 0000000000..0b6807dd6c --- /dev/null +++ b/lib/stdlib/doc/src/timer.xml @@ -0,0 +1,300 @@ + + + + +
+ + 19962009 + Ericsson AB. All Rights Reserved. + + + The contents of this file are subject to the Erlang Public License, + Version 1.1, (the "License"); you may not use this file except in + compliance with the License. You should have received a copy of the + Erlang Public License along with this software. If not, it can be + retrieved online at http://www.erlang.org/. + + Software distributed under the License is distributed on an "AS IS" + basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See + the License for the specific language governing rights and limitations + under the License. + + + + timer + Sebastian Strollo + Bjarne Däcker + 1 + Bjarne Däcker + + 1998-09-09 + D + timer.sgml +
+ timer + 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 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. +

+
+ + + start() -> ok + Start a global timer server (named timer_server). + +

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} + Apply Module:Function(Arguments)after a specified Time. + + Time = integer() in Milliseconds + Module = Function = atom() + Arguments = [term()] + + +

Evaluates apply(M, F, A) after Time amount of time + has elapsed. Returns {ok, TRef}, or {error, Reason}.

+
+
+ + send_after(Time, Pid, Message) -> {ok, TRef} | {error,Reason} + send_after(Time, Message) -> {ok, TRef} | {error,Reason} + Send Messageto Pidafter a specified Time. + + Time = integer() in Milliseconds + Pid = pid() | atom() + Message = term() + Result = {ok, TRef} | {error, Reason} + + +

+ + send_after/3 + +

Evaluates Pid ! Message after Time 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).

+
+
+
+
+ + exit_after(Time, Pid, Reason1) -> {ok, TRef} | {error,Reason2} + exit_after(Time, Reason1) -> {ok, TRef} | {error,Reason2} + kill_after(Time, Pid)-> {ok, TRef} | {error,Reason2} + kill_after(Time) -> {ok, TRef} | {error,Reason2} + Send an exit signal with Reasonafter a specified Time. + + Time = integer() in milliseconds + Pid = pid() | atom() + Reason1 = Reason2 = term() + + +

+ + exit_after/3 + +

Send an exit signal with reason Reason1 to Pid + Pid. 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} + Evaluate Module:Function(Arguments)repeatedly at intervals of Time. + + Time = integer() in milliseconds + Module = Function = atom() + Arguments = [term()] + + +

Evaluates apply(Module, Function, Arguments) repeatedly at + intervals of Time. Returns {ok, TRef}, or + {error, Reason}.

+
+
+ + send_interval(Time, Pid, Message) -> {ok, TRef} | {error, Reason} + send_interval(Time, Message) -> {ok, TRef} | {error, Reason} + Send Messagerepeatedly at intervals of Time. + + Time = integer() in milliseconds + Pid = pid() | atom() + Message = term() + Reason = term() + + +

+ + send_interval/3 + +

Evaluates Pid ! Message repeatedly after Time + 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} + Cancel a previously requested timeout identified by TRef. + +

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 + Suspend the calling process for Timeamount of milliseconds. + + Time = integer() in milliseconds or the atom infinity + + +

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(Module, Function, Arguments) -> {Time, Value} + Measure the real time it takes to evaluate apply(Module, Function, Arguments) + + Module = Function = atom() + Arguments = [term()] + Time = integer() in microseconds + Value = term() + + +

Evaluates apply(Module, Function, Arguments) and measures + the elapsed real time. Returns {Time, Value}, where + Time is the elapsed real time in microseconds, + and Value is what is returned from the apply.

+
+
+ + now_diff(T2, T1) -> Tdiff + Calculate time difference between now/0timestamps + + T1 = T2 = {MegaSecs, Secs, MicroSecs} + Tdiff = MegaSecs = Secs = MicroSecs = integer() + + +

Calculates the time difference Tdiff = T2 - T1 in + microseconds, where T1 and T2 probably + are timestamp tuples returned from erlang:now/0.

+
+
+ + seconds(Seconds) -> Milliseconds + Convert Secondsto Milliseconds. + +

Returns the number of milliseconds in Seconds.

+
+
+ + minutes(Minutes) -> Milliseconds + Converts Minutesto Milliseconds. + +

Return the number of milliseconds in Minutes.

+
+
+ + hours(Hours) -> Milliseconds + Convert Hoursto Milliseconds. + +

Returns the number of milliseconds in Hours.

+
+
+ + hms(Hours, Minutes, Seconds) -> Milliseconds + Convert Hours+Minutes+Secondsto Milliseconds. + +

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.

+
+
+ -- cgit v1.2.3