From 229d0d8ca88bc344bed89e46541b325c1d267996 Mon Sep 17 00:00:00 2001 From: Hans Bolinder Date: Fri, 6 May 2011 15:58:09 +0200 Subject: r Use Erlang specs and types for documentation --- lib/stdlib/doc/src/timer.xml | 173 +++++++++++++++++++------------------------ 1 file changed, 75 insertions(+), 98 deletions(-) (limited to 'lib/stdlib/doc/src/timer.xml') diff --git a/lib/stdlib/doc/src/timer.xml b/lib/stdlib/doc/src/timer.xml index cae655f801..b741ab7db1 100644 --- a/lib/stdlib/doc/src/timer.xml +++ b/lib/stdlib/doc/src/timer.xml @@ -49,9 +49,19 @@ as requested.

+ + + +

Time in milliseconds.

+
+ + +

A timer reference.

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

Starts the timer server. Normally, the server does not need @@ -62,214 +72,181 @@ - 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}.

+

Evaluates apply(Module, Function, Arguments) 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}.

+

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).

+

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}.

+

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).

+

Same as exit_after(Time, self(), Reason1).

kill_after/2 -

Same as exit_after(Time, Pid, kill).

+

Same as exit_after(Time, Pid, kill).

kill_after/1 -

Same as exit_after(Time, self(), kill).

+

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}.

+

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}.

+

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).

+

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 +

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 + {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 +

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 + forever if Time is the atom infinity. Naturally, this function does not return immediately.

- tc(Module, Function, Arguments) -> {Time, Value} - tc(Fun, Arguments) -> {Time, Value} + + + Measure the real time it takes to evaluate apply(Module, Function, Arguments) or apply(Fun, Arguments) - - Module = Function = atom() - Fun = fun() - Arguments = [term()] - Time = integer() in microseconds - Value = term() - + In microseconds

tc/3 -

Evaluates apply(Module, Function, Arguments) and measures - the elapsed real time as reported by now/0. - Returns {Time, Value}, where - Time is the elapsed real time in microseconds, - and Value is what is returned from the apply.

+

Evaluates apply(Module, Function, Arguments) and measures + the elapsed real time as reported by os:timestamp/0. + Returns {Time, Value}, where + Time is the elapsed real time in microseconds, + and Value is what is returned from the apply.

tc/2 -

Evaluates apply(Fun, Arguments). Otherwise works +

Evaluates apply(Fun, Arguments). Otherwise works like tc/3.

+ tc/1 + +

Evaluates Fun(). Otherwise works like tc/2.

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

Calculates the time difference Tdiff = T2 - T1 in - microseconds, where T1 and T2 probably +

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.

+

Returns the number of milliseconds in Seconds.

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

Return the number of milliseconds in Minutes.

+

Return the number of milliseconds in Minutes.

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

Returns the number of milliseconds in Hours.

+

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.

+

Returns the number of milliseconds in Hours + Minutes + Seconds.

-- cgit v1.2.3