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

« back to all changes in this revision

Viewing changes to lib/debugger/src/dbg_iserver.erl

  • Committer: Bazaar Package Importer
  • Author(s): Erlang Packagers, Sergei Golovan
  • Date: 2006-12-03 17:07:44 UTC
  • mfrom: (2.1.11 feisty)
  • Revision ID: james.westby@ubuntu.com-20061203170744-rghjwupacqlzs6kv
Tags: 1:11.b.2-4
[ Sergei Golovan ]
Fixed erlang-base and erlang-base-hipe prerm scripts.

Show diffs side-by-side

added added

removed removed

Lines of Context:
29
29
-record(proc,  {pid,           % pid() Debugged process
30
30
                meta,          % pid() Meta process
31
31
                attpid,        % pid() | undefined  Attached process
32
 
                status,        % running | 
 
32
                status,        % running | exit | idle | waiting
33
33
                info     = {}, % {} | term()
34
34
                exit_info= {}, % {} | {{Mod,Line}, Bs, Stack}
35
35
                function       % {Mod,Func,Args} Initial function call
58
58
    global:whereis_name(?MODULE).
59
59
 
60
60
call(Request) ->
61
 
    gen_server:call(?MODULE, Request).
 
61
    gen_server:call(?MODULE, Request, infinity).
62
62
 
63
63
call(Int, Request) ->
64
 
    gen_server:call(Int, Request).
 
64
    gen_server:call(Int, Request, infinity).
65
65
 
66
66
cast(Request) ->
67
67
    gen_server:cast(?MODULE, Request).
126
126
            case Proc#proc.status of
127
127
                exit ->
128
128
                    Args = [self(),
129
 
                            AttPid,Pid,Proc#proc.info,Proc#proc.exit_info],
130
 
                    Meta = spawn_link(dbg_imeta, exit_info, Args),
 
129
                            AttPid,Pid,Proc#proc.info,
 
130
                            Proc#proc.exit_info],
 
131
                    Meta = spawn_link(dbg_ieval, exit_info, Args),
131
132
                    Proc2 = Proc#proc{meta=Meta, attpid=AttPid},
132
133
                    Procs = lists:keyreplace(Pid, #proc.pid,
133
134
                                             State#state.procs, Proc2),
134
 
                    {reply, {ok, Meta}, State#state{procs=Procs}};
 
135
                    {reply, {ok,Meta}, State#state{procs=Procs}};
135
136
                _Status ->
136
 
                    send(Proc#proc.meta, {attached, AttPid}),
 
137
                    Meta = Proc#proc.meta,
 
138
                    send(Meta, {attached, AttPid}),
137
139
                    Procs = lists:keyreplace(Pid, #proc.pid,
138
140
                                             State#state.procs,
139
141
                                             Proc#proc{attpid=AttPid}),
140
 
                    {reply, {ok, Proc#proc.meta}, State#state{procs=Procs}}
 
142
                    {reply, {ok, Meta}, State#state{procs=Procs}}
141
143
            end;
142
 
        _AttPid ->
 
144
        _AttPid -> % there is already an attached process
143
145
            {reply, error, State}
144
146
    end;
145
147
 
192
194
    link(Meta),
193
195
 
194
196
    %% A new, debugged process has been started. Return its status,
195
 
    %% ie running (running as usual) or init_break (stop)
 
197
    %% ie running (running as usual) or break (stop)
196
198
    %% The status depends on if the process is automatically attached to
197
199
    %% or not.
198
200
    Reply = case auto_attach(init, State#state.auto, Pid) of
199
 
                AttPid when pid(AttPid) -> init_break;
 
201
                AttPid when pid(AttPid) -> break;
200
202
                ignore -> running
201
203
            end,
202
204
 
203
205
    %% Do not add AttPid, it should call attached/2 when started instead
204
206
    Proc = #proc{pid=Pid, meta=Meta, status=running, function=Function},
205
 
    send_all(subscriber, {new_process, {Pid,Function,running,{}}}, State),
 
207
    send_all(subscriber,
 
208
             {new_process, {Pid,Function,running,{}}}, State),
206
209
 
207
210
    {reply, Reply, State#state{procs=State#state.procs++[Proc]}};
208
211
 
309
312
 
310
313
%% Attaching to a process
311
314
handle_cast({attach, Pid, {Mod, Func, Args}}, State) ->
 
315
    %% Simply spawn process, which should call int:attached(Pid)
312
316
    spawn(Mod, Func, [Pid | Args]),
313
317
    {noreply, State};
314
318
 
382
386
    Proc2 = Proc#proc{status=Status, info=Info},
383
387
    {noreply, State#state{procs=lists:keyreplace(Meta, #proc.meta,
384
388
                                                 State#state.procs, Proc2)}};
 
389
handle_cast({set_exit_info, Meta, ExitInfo}, State) ->
 
390
    {true, Proc} = get_proc({meta, Meta}, State#state.procs),
 
391
    Procs = lists:keyreplace(Meta, #proc.meta, State#state.procs,
 
392
                             Proc#proc{exit_info=ExitInfo}),
 
393
    {noreply,State#state{procs=Procs}};
385
394
 
386
395
%% Code loading
387
396
handle_cast({delete, Mod}, State) ->
389
398
    %% Remove the ETS table with information about the module
390
399
    Db = State#state.db,
391
400
    case ets:lookup(Db, {Mod, refs}) of
392
 
        [] -> ignore;
 
401
        [] -> % Mod is not interpreted
 
402
            {noreply, State};
393
403
        [{{Mod, refs}, ModDbs}] ->
394
404
            ets:delete(Db, {Mod, refs}),
395
405
            AllPids = lists:foldl(
410
420
                                      false -> ignore % pid may have exited
411
421
                                  end
412
422
                          end,
413
 
                          AllPids)
414
 
    end,
415
 
 
416
 
    send_all([subscriber, attached], {no_interpret, Mod}, State),
417
 
 
418
 
    %% Remove all breakpoints for Mod
419
 
    handle_cast({no_break, Mod}, State).
 
423
                          AllPids),
 
424
 
 
425
            send_all([subscriber,attached], {no_interpret, Mod}, State),
 
426
 
 
427
            %% Remove all breakpoints for Mod
 
428
            handle_cast({no_break, Mod}, State)
 
429
    end.
420
430
 
421
431
%% Process exits
422
 
handle_info({'EXIT', Who, Why}, State) ->
 
432
handle_info({'EXIT',Who,Why}, State) ->
423
433
    case get_proc({meta, Who}, State#state.procs) of
424
434
 
 
435
        %% Exited process is a meta process for exit_info
 
436
        {true,#proc{status=exit}} ->
 
437
            {noreply,State};
 
438
            
425
439
        %% Exited process is a meta process
426
 
        {true, Proc} when Proc#proc.status/=exit ->
 
440
        {true,Proc} ->
427
441
            Pid = Proc#proc.pid,
428
 
            
429
 
            %% Extract information from the exit reason
430
 
            {Info, ExitInfo} = case Why of
431
 
                                   {Who, Reason} -> {Reason, {}};
432
 
                                   {Who, Reason, Where, Bs, Stack} ->
433
 
                                       {Reason, {Where, Bs, Stack}};
434
 
                                   _Reason -> {Why, {}}
435
 
                               end,
436
 
 
437
 
            %% Check if a new meta process should be started, i.e. if
438
 
            %% someone is attached to the debugged process
 
442
            ExitInfo = Proc#proc.exit_info,
 
443
            %% Check if someone is attached to the debugged process,
 
444
            %% if so a new meta process should be started
439
445
            Meta = case Proc#proc.attpid of
440
446
                       AttPid when pid(AttPid) ->
441
 
                           Args = [self(),
442
 
                                   AttPid, Proc#proc.pid, Info, ExitInfo],
443
 
                           spawn_link(dbg_imeta, exit_info, Args);
 
447
                           spawn_link(dbg_ieval, exit_info, 
 
448
                                      [self(),AttPid,Pid,Why,ExitInfo]);
444
449
                       undefined ->
445
450
                           %% Otherwise, auto attach if necessary
446
451
                           auto_attach(exit, State#state.auto, Pid),
447
452
                           Who
448
453
                   end,
449
 
            
450
 
            send_all(subscriber, {new_status, Pid, exit, Info}, State),
451
 
            
452
 
            Proc2 = Proc#proc{meta=Meta, status=exit, info=Info,
453
 
                              exit_info=ExitInfo},
 
454
            send_all(subscriber, {new_status,Pid,exit,Why}, State),
454
455
            Procs = lists:keyreplace(Who, #proc.meta, State#state.procs,
455
 
                                     Proc2),
456
 
            {noreply, State#state{procs=Procs}};
 
456
                                     Proc#proc{meta=Meta,
 
457
                                               status=exit,
 
458
                                               info=Why}),
 
459
            {noreply,State#state{procs=Procs}};
457
460
 
458
 
        %% Exited process is a simple meta process for a terminated process
459
 
        {true, Proc} when Proc#proc.status==exit ->
460
 
            {noreply, State};
461
 
        
462
461
        false ->
463
462
            case get_proc({attpid, Who}, State#state.procs) of
464
463
                
465
464
                %% Exited process is an attached process
466
465
                {true, Proc} ->
467
 
 
468
466
                    %% If status==exit, then the meta process is a
469
467
                    %% simple meta for a terminated process and can be
470
 
                    %% terminated as well (it is only needed by the attached
471
 
                    %% process)
 
468
                    %% terminated as well (it is only needed by
 
469
                    %% the attached process)
472
470
                    case Proc#proc.status of
473
471
                        exit -> send(Proc#proc.meta, stop);
474
 
                        _Status -> send(Proc#proc.meta, {detached, Who})
 
472
                        _Status -> send(Proc#proc.meta, detached)
475
473
                    end,
476
 
                    
477
474
                    Procs = lists:keyreplace(Proc#proc.pid, #proc.pid,
478
475
                                             State#state.procs,
479
476
                                             Proc#proc{attpid=undefined}),