~ubuntu-branches/debian/squeeze/erlang/squeeze

« back to all changes in this revision

Viewing changes to erts/preloaded/src/erlang.erl

  • Committer: Bazaar Package Importer
  • Author(s): Sergei Golovan
  • Date: 2010-03-09 17:34:57 UTC
  • mfrom: (10.1.2 sid)
  • Revision ID: james.westby@ubuntu.com-20100309173457-4yd6hlcb2osfhx31
Tags: 1:13.b.4-dfsg-3
Manpages in section 1 are needed even if only arch-dependent packages are
built. So, re-enabled them.

Show diffs side-by-side

added added

removed removed

Lines of Context:
1
1
%%
2
2
%% %CopyrightBegin%
3
 
%% 
4
 
%% Copyright Ericsson AB 1996-2009. All Rights Reserved.
5
 
%% 
 
3
%%
 
4
%% Copyright Ericsson AB 1996-2010. All Rights Reserved.
 
5
%%
6
6
%% The contents of this file are subject to the Erlang Public License,
7
7
%% Version 1.1, (the "License"); you may not use this file except in
8
8
%% compliance with the License. You should have received a copy of the
9
9
%% Erlang Public License along with this software. If not, it can be
10
10
%% retrieved online at http://www.erlang.org/.
11
 
%% 
 
11
%%
12
12
%% Software distributed under the License is distributed on an "AS IS"
13
13
%% basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See
14
14
%% the License for the specific language governing rights and limitations
15
15
%% under the License.
16
 
%% 
 
16
%%
17
17
%% %CopyrightEnd%
18
18
%%
19
19
-module(erlang).
29
29
-export([send_nosuspend/2, send_nosuspend/3]).
30
30
-export([localtime_to_universaltime/1]).
31
31
-export([suspend_process/1]).
32
 
-export([min/2,max/2]).
33
 
 
 
32
-export([min/2, max/2]).
34
33
-export([dlink/1, dunlink/1, dsend/2, dsend/3, dgroup_leader/2,
35
34
         dexit/2, dmonitor_node/3, dmonitor_p/2]).
36
 
 
37
35
-export([delay_trap/2]).
38
 
 
39
36
-export([set_cookie/2, get_cookie/0]).
40
 
 
41
37
-export([nodes/0]).
42
 
 
43
38
-export([concat_binary/1]).
44
 
 
45
39
-export([list_to_integer/2,integer_to_list/2]).
46
 
 
47
40
-export([flush_monitor_message/2]).
48
 
 
49
41
-export([set_cpu_topology/1, format_cpu_topology/1]).
50
 
 
51
42
-export([await_proc_exit/3]).
52
43
 
53
44
-deprecated([hash/2]).
 
45
-deprecated([concat_binary/1]).
54
46
 
55
47
-compile(nowarn_bif_clash).
56
48
 
 
49
%%--------------------------------------------------------------------------
 
50
 
 
51
-type date() :: {pos_integer(), pos_integer(), pos_integer()}.
 
52
-type time() :: {non_neg_integer(), non_neg_integer(), non_neg_integer()}.
 
53
-type date_time() :: {date(), time()}.
 
54
 
 
55
%%--------------------------------------------------------------------------
 
56
 
57
57
apply(Fun, Args) ->
58
58
    apply(Fun, Args).
59
59
 
60
60
apply(Mod, Name, Args) ->
61
61
    apply(Mod, Name, Args).
62
62
 
 
63
%% Spawns with a fun
63
64
 
64
 
% Spawns with a fun
65
65
spawn(F) when is_function(F) ->
66
66
    spawn(erlang, apply, [F, []]);
67
67
spawn({M,F}=MF) when is_atom(M), is_atom(F) ->
124
124
spawn_opt(N, F, O) ->
125
125
    erlang:error(badarg, [N, F, O]).
126
126
 
127
 
% Spawns with MFA
 
127
%% Spawns with MFA
128
128
 
129
129
spawn(N,M,F,A) when N =:= node(), is_atom(M), is_atom(F), is_list(A) ->
130
130
    spawn(M,F,A);
253
253
                             [Mod,Fun,Args,Opts,Node]),
254
254
    exit(Reason).
255
255
 
 
256
-spec yield() -> 'true'.
256
257
yield() ->
257
258
    erlang:yield().
258
259
 
259
 
nodes() -> erlang:nodes(visible).
 
260
-spec nodes() -> [node()].
 
261
nodes() ->
 
262
    erlang:nodes(visible).
260
263
 
261
 
disconnect_node(Node) -> net_kernel:disconnect(Node).
 
264
-spec disconnect_node(node()) -> boolean().
 
265
disconnect_node(Node) ->
 
266
    net_kernel:disconnect(Node).
262
267
 
263
268
fun_info(Fun) when is_function(Fun) ->
264
269
    Keys = [type,env,arity,name,uniq,index,new_uniq,new_index,module,pid],
284
289
        _  -> false
285
290
    end.
286
291
 
 
292
-spec localtime_to_universaltime(date_time()) -> date_time().
287
293
localtime_to_universaltime(Localtime) ->
288
294
    erlang:localtime_to_universaltime(Localtime, undefined).
289
295
 
 
296
-spec suspend_process(pid()) -> 'true'.
290
297
suspend_process(P) ->
291
298
    case catch erlang:suspend_process(P, []) of
292
299
        {'EXIT', {Reason, _}} -> erlang:error(Reason, [P]);
297
304
%%
298
305
%% If the emulator wants to perform a distributed command and
299
306
%% a connection is not established to the actual node the following 
300
 
%% functions is called in order to set up the connection and then 
 
307
%% functions are called in order to set up the connection and then
301
308
%% reactivate the command.
302
309
%%
303
310
 
 
311
-spec dlink(pid() | port()) -> 'true'.
304
312
dlink(Pid) ->
305
313
    case net_kernel:connect(node(Pid)) of
306
314
        true -> link(Pid);
308
316
    end.
309
317
 
310
318
%% Can this ever happen?
 
319
-spec dunlink(identifier()) -> 'true'.
311
320
dunlink(Pid) ->
312
321
    case net_kernel:connect(node(Pid)) of
313
322
        true -> unlink(Pid);
321
330
    end;
322
331
 
323
332
dmonitor_node(Node, Flag, Opts) ->
324
 
    case lists:member(allow_passive_connect,Opts) of
 
333
    case lists:member(allow_passive_connect, Opts) of
325
334
        true ->
326
335
            case net_kernel:passive_cnct(Node) of
327
336
                true -> erlang:monitor_node(Node, Flag, Opts);
377
386
        ignored -> ok                           % Not distributed.
378
387
    end.
379
388
 
 
389
-spec dmonitor_p('process', pid() | {atom(),atom()}) -> reference().
380
390
dmonitor_p(process, ProcSpec) ->
381
391
    %% ProcSpec = pid() | {atom(),atom()}
382
392
    %% ProcSpec CANNOT be an atom because a locally registered process
383
393
    %% is never handled here.
384
 
 
385
394
    Node = case ProcSpec of
386
395
               {S,N} when is_atom(S), is_atom(N), N =/= node() -> N;
387
396
               _ when is_pid(ProcSpec) -> node(ProcSpec)
399
408
%% Trap function used when modified timing has been enabled.
400
409
%%
401
410
 
 
411
-spec delay_trap(Result, timeout()) -> Result.
402
412
delay_trap(Result, 0) -> erlang:yield(), Result;
403
413
delay_trap(Result, Timeout) -> receive after Timeout -> Result end.
404
414
 
422
432
        error -> exit(badarg);
423
433
        Other -> Other
424
434
    end.
425
 
            
 
435
 
 
436
-spec get_cookie() -> atom().
426
437
get_cookie() ->
427
438
    auth:get_cookie().
428
439
 
429
440
concat_binary(List) ->
430
441
    list_to_binary(List).
431
442
 
 
443
-spec integer_to_list(integer(), 1..255) -> string().
432
444
integer_to_list(I, 10) ->
433
445
    erlang:integer_to_list(I);
434
446
integer_to_list(I, Base) 
456
468
    end.
457
469
 
458
470
 
459
 
 
460
471
list_to_integer(L, 10) ->
461
472
    erlang:list_to_integer(L);
462
473
list_to_integer(L, Base)
661
672
%%       functions in bif.c. Do not make
662
673
%%       any changes to it without reading
663
674
%%       the comment about them in bif.c!
 
675
-spec await_proc_exit(dst(), 'apply' | 'data' | 'reason', term()) -> term().
664
676
await_proc_exit(Proc, Op, Data) ->
665
677
    Mon = erlang:monitor(process, Proc),
666
678
    receive
676
688
            end
677
689
    end.
678
690
 
 
691
-spec min(term(), term()) -> term().
679
692
min(A, B) when A > B -> B;
680
693
min(A, _) -> A.
681
694
 
 
695
-spec max(term(), term()) -> term().
682
696
max(A, B) when A < B -> B;
683
697
max(A, _) -> A.