~clint-fewbar/ubuntu/precise/erlang/merge-15b

« back to all changes in this revision

Viewing changes to lib/stdlib/src/pool.erl

  • Committer: Package Import Robot
  • Author(s): Sergei Golovan
  • Date: 2011-12-15 19:20:10 UTC
  • mfrom: (1.1.18) (3.5.15 sid)
  • mto: (3.5.16 sid)
  • mto: This revision was merged to the branch mainline in revision 33.
  • Revision ID: package-import@ubuntu.com-20111215192010-jnxcfe3tbrpp0big
Tags: 1:15.b-dfsg-1
* New upstream release.
* Upload to experimental because this release breaks external drivers
  API along with ABI, so several applications are to be fixed.
* Removed SSL patch because the old SSL implementation is removed from
  the upstream distribution.
* Removed never used patch which added native code to erlang beam files.
* Removed the erlang-docbuilder binary package because the docbuilder
  application was dropped by upstream.
* Documented dropping ${erlang-docbuilder:Depends} substvar in
  erlang-depends(1) manpage.
* Made erlang-base and erlang-base-hipe provide virtual package
  erlang-abi-15.b (the number means the first erlang version, which
  provides current ABI).

Show diffs side-by-side

added added

removed removed

Lines of Context:
1
1
%%
2
2
%% %CopyrightBegin%
3
3
%% 
4
 
%% Copyright Ericsson AB 1996-2009. All Rights Reserved.
 
4
%% Copyright Ericsson AB 1996-2011. All Rights Reserved.
5
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
52
52
 
53
53
%% Start up using the .hosts.erlang file
54
54
 
55
 
-spec start(atom()) -> [node()].
 
55
-spec start(Name) -> Nodes when
 
56
      Name :: atom(),
 
57
      Nodes :: [node()].
56
58
start(Name) ->
57
59
    start(Name,[]).
58
60
 
59
 
-spec start(atom(), string()) -> [node()].
 
61
-spec start(Name, Args) -> Nodes when
 
62
      Name :: atom(),
 
63
      Args :: string(),
 
64
      Nodes :: [node()].
60
65
start(Name, Args) when is_atom(Name) ->
61
66
    gen_server:start({global, pool_master}, pool, [], []),
62
67
    Hosts = net_adm:host_file(),
71
76
get_nodes() ->
72
77
    get_elements(2, get_nodes_and_load()).
73
78
 
74
 
-spec attach(node()) -> 'already_attached' | 'attached'.
 
79
-spec attach(Node) -> 'already_attached' | 'attached' when
 
80
      Node :: node().
75
81
attach(Node) ->
76
82
    gen_server:call({global, pool_master}, {attach, Node}).
77
83
 
82
88
get_node() ->
83
89
    gen_server:call({global, pool_master}, get_node).
84
90
 
85
 
-spec pspawn(module(), atom(), [term()]) -> pid().
 
91
-spec pspawn(Mod, Fun, Args) -> pid() when
 
92
      Mod :: module(),
 
93
      Fun :: atom(),
 
94
      Args :: [term()].
86
95
pspawn(M, F, A) ->
87
96
    gen_server:call({global, pool_master}, {spawn, group_leader(), M, F, A}).
88
97
 
89
 
-spec pspawn_link(module(), atom(), [term()]) -> pid().
 
98
-spec pspawn_link(Mod, Fun, Args) -> pid() when
 
99
      Mod :: module(),
 
100
      Fun :: atom(),
 
101
      Args :: [term()].
90
102
pspawn_link(M, F, A) ->
91
103
    P = pspawn(M, F, A),
92
104
    link(P),
95
107
start_nodes([], _, _) -> [];
96
108
start_nodes([Host|Tail], Name, Args) -> 
97
109
    case slave:start(Host, Name, Args) of 
 
110
        {error, {already_running, Node}} ->
 
111
            io:format("Can't start node on host ~w due to ~w~n",[Host, {already_running, Node}]),
 
112
            [Node | start_nodes(Tail, Name, Args)];
98
113
        {error, R} ->
99
114
            io:format("Can't start node on host ~w due to ~w~n",[Host, R]),
100
115
            start_nodes(Tail, Name, Args);