~ubuntu-branches/ubuntu/lucid/erlang/lucid

« back to all changes in this revision

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

  • Committer: Bazaar Package Importer
  • Author(s): Sergei Golovan
  • Date: 2009-06-11 12:18:07 UTC
  • mfrom: (1.2.2 upstream)
  • Revision ID: james.westby@ubuntu.com-20090611121807-ks7eb4xrt7dsysgx
Tags: 1:13.b.1-dfsg-1
* New upstream release.
* Removed unnecessary dependency of erlang-os-mon on erlang-observer and
  erlang-tools and added missing dependency of erlang-nox on erlang-os-mon
  (closes: #529512).
* Removed a patch to eunit application because the bug was fixed upstream.

Show diffs side-by-side

added added

removed removed

Lines of Context:
34
34
%%-----------------------------------------------------------------
35
35
 
36
36
-type linkage()   :: 'link' | 'nolink'.
37
 
-type emgr_name() :: {'local', atom()} | {'global', atom()}.
38
 
%%-type emgr_ref()  :: atom() | {atom(), atom()} |  {'global', atom()} | pid().
39
 
-type start_ret() :: {'ok', pid()} | {'error', term()}.
 
37
-type emgr_name() :: {'local', atom()} | {'global', term()}.
 
38
 
 
39
-type start_ret() :: {'ok', pid()} | 'ignore' | {'error', term()}.
40
40
 
41
41
-type opts_flag() :: 'trace' | 'log' | 'statistics' | 'debug'
42
42
                   | {'logfile', string()}.
48
48
%% start(GenMod, LinkP, Name, Mod, Args, Options)
49
49
%%    GenMod = atom(), callback module implementing the 'real' fsm
50
50
%%    LinkP = link | nolink
51
 
%%    Name = {local, atom()} | {global, atom()}
 
51
%%    Name = {local, atom()} | {global, term()}
52
52
%%    Args = term(), init arguments (to Mod:init/1)
53
53
%%    Options = [{timeout, Timeout} | {debug, [Flag]}]
54
54
%%      Flag = trace | log | {logfile, File} | statistics | debug
55
55
%%          (debug == log && statistics)
56
 
%% Returns: {ok, Pid} | {error, Reason} |
57
 
%%          {error, {already_started, Pid}}
 
56
%% Returns: {ok, Pid} | ignore |{error, Reason} |
 
57
%%          {error, {already_started, Pid}} |
58
58
%%    The 'already_started' is returned only if Name is given 
59
59
%%-----------------------------------------------------------------
60
60
 
198
198
           end,
199
199
    try erlang:monitor(process, Process) of
200
200
        Mref ->
201
 
            receive
202
 
                {'DOWN', Mref, _, _, noconnection} ->
203
 
                    exit({nodedown, Node});
204
 
                {'DOWN', Mref, _, _, _} ->
205
 
                    exit(noproc)
206
 
            after 0 ->
207
 
                    Process ! {Label, {self(), Mref}, Request},
208
 
                    wait_resp_mon(Node, Mref, Timeout)
209
 
            end
 
201
            %% If the monitor/2 call failed to set up a connection to a
 
202
            %% remote node, we don't want the '!' operator to attempt
 
203
            %% to set up the connection again. (If the monitor/2 call
 
204
            %% failed due to an expired timeout, '!' too would probably
 
205
            %% have to wait for the timeout to expire.) Therefore,
 
206
            %% use erlang:send/3 with the 'noconnect' option so that it
 
207
            %% will fail immediately if there is no connection to the
 
208
            %% remote node.
 
209
 
 
210
            catch erlang:send(Process, {Label, {self(), Mref}, Request},
 
211
                  [noconnect]),
 
212
            wait_resp_mon(Node, Mref, Timeout)
210
213
    catch
211
214
        error:_ ->
212
215
            %% Node (C/Java?) is not supporting the monitor.
230
233
wait_resp_mon(Node, Mref, Timeout) ->
231
234
    receive
232
235
        {Mref, Reply} ->
233
 
            erlang:demonitor(Mref),
234
 
            receive 
235
 
                {'DOWN', Mref, _, _, _} -> 
236
 
                    {ok, Reply}
237
 
            after 0 -> 
238
 
                    {ok, Reply}
239
 
            end;
 
236
            erlang:demonitor(Mref, [flush]),
 
237
            {ok, Reply};
240
238
        {'DOWN', Mref, _, _, noconnection} ->
241
239
            exit({nodedown, Node});
242
240
        {'DOWN', Mref, _, _, Reason} ->