~ubuntu-branches/ubuntu/trusty/erlang/trusty

« back to all changes in this revision

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

  • Committer: Bazaar Package Importer
  • Author(s): Clint Byrum
  • Date: 2011-05-05 15:48:43 UTC
  • mfrom: (3.5.13 sid)
  • Revision ID: james.westby@ubuntu.com-20110505154843-0om6ekzg6m7ugj27
Tags: 1:14.b.2-dfsg-3ubuntu1
* Merge from debian unstable.  Remaining changes:
  - Drop libwxgtk2.8-dev build dependency. Wx isn't in main, and not
    supposed to.
  - Drop erlang-wx binary.
  - Drop erlang-wx dependency from -megaco, -common-test, and -reltool, they
    do not really need wx. Also drop it from -debugger; the GUI needs wx,
    but it apparently has CLI bits as well, and is also needed by -megaco,
    so let's keep the package for now.
  - debian/patches/series: Do what I meant, and enable build-options.patch
    instead.
* Additional changes:
  - Drop erlang-wx from -et
* Dropped Changes:
  - patches/pcre-crash.patch: CVE-2008-2371: outer level option with
    alternatives caused crash. (Applied Upstream)
  - fix for ssl certificate verification in newSSL: 
    ssl_cacertfile_fix.patch (Applied Upstream)
  - debian/patches/series: Enable native.patch again, to get stripped beam
    files and reduce the package size again. (build-options is what
    actually accomplished this)
  - Remove build-options.patch on advice from upstream and because it caused
    odd build failures.

Show diffs side-by-side

added added

removed removed

Lines of Context:
1
1
%%
2
2
%% %CopyrightBegin%
3
3
%% 
4
 
%% Copyright Ericsson AB 1998-2009. All Rights Reserved.
 
4
%% Copyright Ericsson AB 1998-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
155
155
 
156
156
%% Retrieving information
157
157
handle_call(snapshot, _From, State) ->
158
 
    Reply = lists:map(fun(Proc) ->
159
 
                              {Proc#proc.pid, Proc#proc.function,
160
 
                               Proc#proc.status, Proc#proc.info}
161
 
                      end,
162
 
                      State#state.procs),
 
158
    Reply = [{Proc#proc.pid, Proc#proc.function,
 
159
              Proc#proc.status, Proc#proc.info} || Proc <- State#state.procs],
163
160
    {reply, Reply, State};
164
161
handle_call({get_meta, Pid}, _From, State) ->
165
162
    Reply = case get_proc({pid, Pid}, State#state.procs) of
181
178
 
182
179
%% Breakpoint handling
183
180
handle_call({new_break, Point, Options}, _From, State) ->
184
 
    case lists:keysearch(Point, 1, State#state.breaks) of
 
181
    case lists:keymember(Point, 1, State#state.breaks) of
185
182
        false ->
186
183
            Break = {Point, Options},
187
184
            send_all([subscriber, meta, attached],
188
185
                     {new_break, Break}, State),
189
186
            Breaks = keyinsert(Break, 1, State#state.breaks),
190
187
            {reply, ok, State#state{breaks=Breaks}};
191
 
        {value, _Break} ->
 
188
        true ->
192
189
            {reply, {error, break_exists}, State}
193
190
    end;
194
191
handle_call(all_breaks, _From, State) ->
195
192
    {reply, State#state.breaks, State};
196
193
handle_call({all_breaks, Mod}, _From, State) ->
197
194
    Reply = lists:filter(fun({{M,_L}, _Options}) ->
198
 
                                 if M==Mod -> true; true -> false end
 
195
                                 M =/= Mod
199
196
                         end,
200
197
                         State#state.breaks),
201
198
    {reply, Reply, State};
276
273
    Db = State#state.db,
277
274
    [{{Mod, refs}, ModDbs}] = ets:lookup(Db, {Mod, refs}),
278
275
    ModDb = if
279
 
                Pid==any -> hd(ModDbs);
 
276
                Pid =:= any -> hd(ModDbs);
280
277
                true ->
281
278
                    lists:foldl(fun(T, not_found) ->
282
279
                                        [{T, Pids}] = ets:lookup(Db, T),
295
292
    Db = State#state.db,
296
293
    [{{Mod, refs}, ModDbs}] = ets:lookup(Db, {Mod, refs}),
297
294
    ModDb = if
298
 
                Pid==any -> hd(ModDbs);
 
295
                Pid =:= any -> hd(ModDbs);
299
296
                true ->
300
297
                    lists:foldl(fun(T, not_found) ->
301
298
                                        [{T, Pids}] = ets:lookup(Db, T),
360
357
%% Retrieving information
361
358
handle_cast(clear, State) ->
362
359
    Procs = lists:filter(fun(#proc{status=Status}) ->
363
 
                                 if Status==exit -> false; true -> true end
 
360
                                 Status =/= exit
364
361
                         end,
365
362
                         State#state.procs),
366
363
    {noreply, State#state{procs=Procs}};
367
364
 
368
365
%% Breakpoint handling
369
366
handle_cast({delete_break, Point}, State) ->
370
 
    case lists:keysearch(Point, 1, State#state.breaks) of
371
 
        {value, _Break} ->
 
367
    case lists:keymember(Point, 1, State#state.breaks) of
 
368
        true ->
372
369
            send_all([subscriber, meta, attached],
373
370
                     {delete_break, Point}, State),
374
371
            Breaks = lists:keydelete(Point, 1, State#state.breaks),
377
374
            {noreply, State}
378
375
    end;
379
376
handle_cast({break_option, Point, Option, Value}, State) ->
380
 
    case lists:keysearch(Point, 1, State#state.breaks) of
381
 
        {value, {Point, Options}} ->
 
377
    case lists:keyfind(Point, 1, State#state.breaks) of
 
378
        {Point, Options} ->
382
379
            N = case Option of
383
380
                    status -> 1;
384
381
                    action -> 2;
399
396
handle_cast({no_break, Mod}, State) ->
400
397
    send_all([subscriber, meta, attached], {no_break, Mod}, State),
401
398
    Breaks = lists:filter(fun({{M, _L}, _O}) ->
402
 
                                  if M==Mod -> false; true -> true end
 
399
                                  M =/= Mod
403
400
                          end,
404
401
                          State#state.breaks),
405
402
    {noreply, State#state{breaks=Breaks}};
409
406
    {true, Proc} = get_proc({meta, Meta}, State#state.procs),
410
407
    send_all(subscriber, {new_status, Proc#proc.pid, Status, Info}, State),
411
408
    if
412
 
        Status==break ->
 
409
        Status =:= break ->
413
410
            auto_attach(break, State#state.auto, Proc);
414
411
        true -> ignore
415
412
    end,
526
523
%% Internal functions
527
524
%%====================================================================
528
525
 
529
 
auto_attach(Why, Auto, Proc) when is_record(Proc, proc) ->
530
 
    case Proc#proc.attpid of
531
 
        AttPid when is_pid(AttPid) -> ignore;
532
 
        undefined ->
533
 
            auto_attach(Why, Auto, Proc#proc.pid)
 
526
auto_attach(Why, Auto, #proc{attpid = Attpid, pid = Pid}) ->
 
527
    case Attpid of
 
528
        undefined -> auto_attach(Why, Auto, Pid);
 
529
        _ when is_pid(Attpid) -> ignore
534
530
    end;
535
531
auto_attach(Why, Auto, Pid) when is_pid(Pid) ->
536
532
    case Auto of
545
541
 
546
542
keyinsert(Tuple1, N, [Tuple2|Tuples]) ->
547
543
    if
548
 
        element(N, Tuple1)<element(N, Tuple2) ->
 
544
        element(N, Tuple1) < element(N, Tuple2) ->
549
545
            [Tuple1, Tuple2|Tuples];
550
546
        true ->
551
547
            [Tuple2 | keyinsert(Tuple1, N, Tuples)]
576
572
send_all(subscriber, Msg, State) ->
577
573
    send_all(State#state.subs, Msg);
578
574
send_all(meta, Msg, State) ->
579
 
    Metas = lists:map(fun(Proc) -> Proc#proc.meta end, State#state.procs),
 
575
    Metas = [Proc#proc.meta || Proc <- State#state.procs],
580
576
    send_all(Metas, Msg);
581
577
send_all(attached, Msg, State) ->
582
578
    AttPids= mapfilter(fun(Proc) ->
600
596
                meta -> #proc.meta;
601
597
                attpid -> #proc.attpid
602
598
            end,
603
 
    case lists:keysearch(Pid, Index, Procs) of
604
 
        {value, Proc} -> {true, Proc};
605
 
        false -> false
 
599
    case lists:keyfind(Pid, Index, Procs) of
 
600
        false -> false;
 
601
        Proc -> {true, Proc}
606
602
    end.