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

« back to all changes in this revision

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

  • Committer: Bazaar Package Importer
  • Author(s): Sergei Golovan
  • Date: 2009-05-07 15:07:37 UTC
  • mfrom: (1.2.1 upstream) (5.1.2 sid)
  • Revision ID: james.westby@ubuntu.com-20090507150737-i4yb5elwinm7r0hc
Tags: 1:13.b-dfsg1-1
* Removed another bunch of non-free RFCs from original tarball
  (closes: #527053).
* Fixed build-dependencies list by adding missing comma. This requires
  libsctp-dev again. Also, added libsctp1 dependency to erlang-base and
  erlang-base-hipe packages because the shared library is loaded via
  dlopen now and cannot be added using dh_slibdeps (closes: #526682).
* Weakened dependency of erlang-webtool on erlang-observer to recommends
  to avoid circular dependencies (closes: #526627).
* Added solaris-i386 to HiPE enabled architectures.
* Made script sources in /usr/lib/erlang/erts-*/bin directory executable,
  which is more convenient if a user wants to create a target Erlang system.
* Shortened extended description line for erlang-dev package to make it
  fit 80x25 terminals.

Show diffs side-by-side

added added

removed removed

Lines of Context:
 
1
%%
 
2
%% %CopyrightBegin%
 
3
%% 
 
4
%% Copyright Ericsson AB 2008-2009. All Rights Reserved.
 
5
%% 
 
6
%% The contents of this file are subject to the Erlang Public License,
 
7
%% Version 1.1, (the "License"); you may not use this file except in
 
8
%% compliance with the License. You should have received a copy of the
 
9
%% Erlang Public License along with this software. If not, it can be
 
10
%% retrieved online at http://www.erlang.org/.
 
11
%% 
 
12
%% Software distributed under the License is distributed on an "AS IS"
 
13
%% basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See
 
14
%% the License for the specific language governing rights and limitations
 
15
%% under the License.
 
16
%% 
 
17
%% %CopyrightEnd%
 
18
%%
 
19
 
 
20
%%
 
21
-module(dbg_wx_mon).
 
22
 
 
23
-include_lib("kernel/include/file.hrl").
 
24
-include_lib("wx/include/wx.hrl").
 
25
 
 
26
%% External exports
 
27
-export([start/2, stop/0]).
 
28
 
 
29
-define(TRACEWIN, ['Search Area', 'Button Area', 'Evaluator Area', 'Bindings Area']).
 
30
-define(BACKTRACE, 100).
 
31
 
 
32
-record(pinfo, {pid,       % pid()
 
33
                status     % break | exit | idle | running | waiting
 
34
               }).
 
35
 
 
36
-record(state, {mode,      % local | global
 
37
                starter,   % bool() 'true' if int was started by me
 
38
 
 
39
                win,       % term() Monitor window data
 
40
                focus,     % undefined | #pinfo{} Process in focus
 
41
                coords,    % {X,Y} Mouse pointer position
 
42
 
 
43
                intdir,    % string() Default dir
 
44
                pinfos,    % [#pinfo{}] Debugged processes
 
45
 
 
46
                tracewin,  % [Area] Areas shown in trace window
 
47
                backtrace, % integer() Number of call frames to fetch
 
48
 
 
49
                attach,    % false | {Flags, Function}
 
50
 
 
51
                sfile,     % default | string() Settings file
 
52
                changed    % boolean() Settings have been changed
 
53
               }). 
 
54
 
 
55
%%====================================================================
 
56
%% External exports
 
57
%%====================================================================
 
58
 
 
59
%%--------------------------------------------------------------------
 
60
%% start(Mode, SFile) -> {ok, Pid} | {error, Reason}
 
61
%%   Mode = local | global
 
62
%%   SFile = string() | default  Settings file
 
63
%%   Pid = pid()
 
64
%%   Reason = {already_started,Pid} | term()
 
65
%%--------------------------------------------------------------------
 
66
start(Mode, SFile) ->
 
67
    case whereis(?MODULE) of
 
68
        undefined ->
 
69
            CallingPid = self(),
 
70
            Pid = spawn(fun () -> init(CallingPid, Mode, SFile) end),
 
71
            receive
 
72
                {initialization_complete, Pid} ->
 
73
                    {ok, Pid};
 
74
                Error ->
 
75
                    Error
 
76
            end;
 
77
 
 
78
        Pid ->
 
79
            {error, {already_started,Pid}}
 
80
    end.
 
81
 
 
82
%%--------------------------------------------------------------------
 
83
%% stop() -> ok
 
84
%%--------------------------------------------------------------------
 
85
stop() ->
 
86
    case whereis(?MODULE) of
 
87
        undefined ->
 
88
            ok;
 
89
        Pid ->
 
90
            Flag = process_flag(trap_exit, true),
 
91
            link(Pid),
 
92
            Pid ! stop,
 
93
            receive
 
94
                {'EXIT', Pid, stop} ->
 
95
                    process_flag(trap_exit, Flag),
 
96
                    ok
 
97
            end
 
98
    end.
 
99
 
 
100
 
 
101
%%====================================================================
 
102
%% Initialization
 
103
%%====================================================================
 
104
 
 
105
init(CallingPid, Mode, SFile) ->
 
106
    register(?MODULE, self()),
 
107
 
 
108
    %% Graphics system
 
109
    case catch dbg_wx_mon_win:init() of
 
110
        {'EXIT', Reason} ->
 
111
            CallingPid ! {error, Reason};
 
112
        GS ->
 
113
            try 
 
114
                init2(CallingPid, Mode, SFile, GS)
 
115
            catch 
 
116
                exit:stop -> stop;
 
117
                Error:Reason ->
 
118
                    io:format("~p: Crashed {~p,~p} in~n  ~p",
 
119
                              [?MODULE, Error, Reason, erlang:get_stacktrace()])
 
120
            end
 
121
    end.
 
122
 
 
123
init2(CallingPid, Mode, SFile, GS) ->
 
124
    %% Start Int if necessary and subscribe to information from it
 
125
    Bool = case int:start() of
 
126
               {ok, _Int} -> true;
 
127
               {error, {already_started, _Int}} -> false
 
128
           end,
 
129
    int:subscribe(),
 
130
 
 
131
    %% Start other necessary stuff
 
132
    dbg_wx_win:init(),     
 
133
    dbg_wx_winman:start(), % Debugger window manager
 
134
 
 
135
    %% Create monitor window
 
136
    Title = "Monitor",
 
137
    Win = dbg_wx_mon_win:create_win(GS, Title, menus()),
 
138
    Window = dbg_wx_mon_win:get_window(Win),
 
139
    dbg_wx_winman:insert(Title, Window),
 
140
 
 
141
    %% Initial process state
 
142
    State1 = #state{mode    = Mode,
 
143
                    starter = Bool,
 
144
 
 
145
                    win     = Win,
 
146
                    focus   = undefined,
 
147
                    coords  = {0,0},
 
148
 
 
149
                    intdir  = element(2, file:get_cwd()),
 
150
                    pinfos  = [],
 
151
 
 
152
                    sfile   = SFile,
 
153
                    changed = false
 
154
                   },
 
155
 
 
156
    State2 = init_options(?TRACEWIN,            % Trace Window
 
157
                          int:auto_attach(),    % Auto Attach
 
158
                          int:stack_trace(),    % Stack Trace
 
159
                          ?BACKTRACE,           % Back Trace Size
 
160
                          State1),
 
161
 
 
162
    State3 = init_contents(int:interpreted(),   % Modules
 
163
                           int:all_breaks(),    % Breakpoints
 
164
                           int:snapshot(),      % Processes
 
165
                           State2),
 
166
 
 
167
    %% Disable/enable functionality according to process in focus (none)
 
168
    gui_enable_functions(State3#state.focus),
 
169
 
 
170
    CallingPid ! {initialization_complete, self()},
 
171
 
 
172
    if
 
173
        SFile==default ->
 
174
            loop(State3);
 
175
        true ->
 
176
            loop(load_settings(SFile, State3))
 
177
    end.
 
178
 
 
179
init_options(TraceWin, AutoAttach, StackTrace, BackTrace, State) ->
 
180
    lists:foreach(fun(Area) ->
 
181
                          dbg_wx_mon_win:select(Area, true)
 
182
                  end,
 
183
                  TraceWin),
 
184
 
 
185
    case AutoAttach of
 
186
        false -> ignore;
 
187
        {Flags, _Function} ->
 
188
            dbg_wx_mon_win:show_option(State#state.win,
 
189
                                       auto_attach, Flags),
 
190
            lists:foreach(fun(Flag) ->
 
191
                                  dbg_wx_mon_win:select(map(Flag), true)
 
192
                          end,
 
193
                          Flags)
 
194
    end,
 
195
 
 
196
    dbg_wx_mon_win:show_option(State#state.win,
 
197
                               stack_trace, StackTrace),
 
198
    dbg_wx_mon_win:select(map(StackTrace), true),
 
199
 
 
200
    dbg_wx_mon_win:show_option(State#state.win, back_trace, BackTrace),
 
201
 
 
202
    State#state{tracewin=TraceWin, backtrace=BackTrace}.
 
203
 
 
204
init_contents(Mods, Breaks, Processes, State) ->
 
205
    Win2 =
 
206
        lists:foldl(fun(Mod, Win) ->
 
207
                            dbg_wx_mon_win:add_module(Win,'Module',Mod)
 
208
                    end,
 
209
                    State#state.win,
 
210
                    Mods),
 
211
 
 
212
    Win3 = 
 
213
        lists:foldl(fun(Break, Win) ->
 
214
                            dbg_wx_mon_win:add_break(Win,'Break',Break)
 
215
                    end,
 
216
                    Win2,
 
217
                    Breaks),
 
218
 
 
219
    lists:foldl(fun(PidTuple, State0) ->
 
220
                        int_cmd({new_process, PidTuple}, State0)
 
221
                end,
 
222
                State#state{win=Win3},
 
223
                Processes).
 
224
 
 
225
 
 
226
%%====================================================================
 
227
%% Main loop and message handling
 
228
%%====================================================================
 
229
 
 
230
loop(State) ->
 
231
    receive
 
232
        stop ->
 
233
            gui_cmd(stopped, State);
 
234
        
 
235
        %% From the wx-GUI
 
236
        #wx{} = GuiEvent ->
 
237
            Cmd = dbg_wx_mon_win:handle_event(GuiEvent,State#state.win),
 
238
            State2 = gui_cmd(Cmd, State),
 
239
            loop(State2);
 
240
 
 
241
        %% From the interpreter process
 
242
        {int, Cmd} ->
 
243
            State2 = int_cmd(Cmd, State),
 
244
            loop(State2);
 
245
 
 
246
        %% From the dbg_ui_interpret process
 
247
        {dbg_ui_interpret, Dir} ->
 
248
            loop(State#state{intdir=Dir});
 
249
        
 
250
        %% From the dbg_wx_winman process (Debugger window manager)
 
251
        {dbg_ui_winman, update_windows_menu, Data} ->
 
252
            Window = dbg_wx_mon_win:get_window(State#state.win),
 
253
            dbg_wx_winman:update_windows_menu(Window,Data),
 
254
            loop(State);
 
255
 
 
256
        %% From the trace window
 
257
        {dbg_wx_trace, From, get_env} -> 
 
258
            From ! {env, self(), wx:get_env(), dbg_wx_mon_win:get_window(State#state.win)},
 
259
            loop(State)
 
260
    end.
 
261
 
 
262
%%--Commands from the GUI---------------------------------------------
 
263
%% Act upon a command from the GUI. In most cases, it is only necessary
 
264
%% to call a relevant int-function. int will then report when the action
 
265
%% has been taken.
 
266
 
 
267
gui_cmd(ignore, State) ->
 
268
    State;
 
269
gui_cmd(stopped, State) ->
 
270
    if
 
271
        State#state.starter==true -> int:stop();
 
272
        true -> int:auto_attach(false)
 
273
    end,
 
274
    exit(stop);
 
275
gui_cmd({coords, Coords}, State) ->
 
276
    State#state{coords=Coords};
 
277
 
 
278
gui_cmd({shortcut, Key}, State) ->
 
279
    case shortcut(Key) of
 
280
        {always, Cmd} -> gui_cmd(Cmd, State);
 
281
        {if_enabled, Cmd} ->
 
282
            case dbg_wx_mon_win:is_enabled(Cmd) of
 
283
                true -> gui_cmd(Cmd, State);
 
284
                false -> State
 
285
            end;
 
286
        false -> State
 
287
    end;
 
288
 
 
289
%% File Menu
 
290
gui_cmd('Load Settings...', State) ->
 
291
    Window = dbg_wx_mon_win:get_window(State#state.win),
 
292
    case dbg_wx_settings:load(Window, State#state.coords,State#state.sfile) of
 
293
        cancel ->     State;
 
294
        {ok, File} -> load_settings(File,State)
 
295
    end;
 
296
gui_cmd('Save Settings...', State) ->
 
297
    Window = dbg_wx_mon_win:get_window(State#state.win),
 
298
    case dbg_wx_settings:save(Window, State#state.coords,State#state.sfile) of
 
299
        cancel ->     State;
 
300
        {ok, File} -> save_settings(File,State)
 
301
    end;
 
302
gui_cmd('Exit', State) ->
 
303
    gui_cmd(stopped, State);
 
304
 
 
305
%% Edit Menu
 
306
gui_cmd('Refresh', State) ->
 
307
    int:clear(),
 
308
    Win = dbg_wx_mon_win:clear_processes(State#state.win),
 
309
    gui_enable_functions(undefined),
 
310
    State2 = State#state{win=Win, focus=undefined, pinfos=[]},
 
311
    lists:foldl(fun(PidTuple, S) ->
 
312
                        int_cmd({new_process,PidTuple}, S)
 
313
                end,
 
314
                State2,
 
315
                int:snapshot());
 
316
gui_cmd('Kill All', State) ->
 
317
    lists:foreach(fun(PInfo) ->
 
318
                          case PInfo#pinfo.status of
 
319
                              exit -> ignore;
 
320
                              _Status -> exit(PInfo#pinfo.pid, kill)
 
321
                          end
 
322
                  end,
 
323
                  State#state.pinfos),
 
324
    State;
 
325
 
 
326
%% Module Menu
 
327
gui_cmd('Interpret...', State) ->
 
328
    Window = dbg_wx_mon_win:get_window(State#state.win),
 
329
    dbg_wx_interpret:start(Window, State#state.coords,
 
330
                           State#state.intdir, State#state.mode),
 
331
    State;
 
332
gui_cmd('Delete All Modules', State) ->
 
333
    lists:foreach(fun(Mod) -> int:nn(Mod) end, int:interpreted()),
 
334
    State;
 
335
gui_cmd({module, Mod, What}, State) ->
 
336
    case What of
 
337
        delete -> int:nn(Mod);
 
338
        view -> 
 
339
            Window = dbg_wx_mon_win:get_window(State#state.win),
 
340
            dbg_wx_view:start(Window, Mod)
 
341
    end,
 
342
    State;
 
343
 
 
344
%% Process Menu
 
345
gui_cmd('Step', State) ->
 
346
    int:step((State#state.focus)#pinfo.pid),
 
347
    State;
 
348
gui_cmd('Next', State) ->
 
349
    int:next((State#state.focus)#pinfo.pid),
 
350
    State;
 
351
gui_cmd('Continue', State) ->
 
352
    int:continue((State#state.focus)#pinfo.pid),
 
353
    State;
 
354
gui_cmd('Finish ', State) ->
 
355
    int:finish((State#state.focus)#pinfo.pid),
 
356
    State;
 
357
gui_cmd('Attach', State) ->
 
358
    Pid = (State#state.focus)#pinfo.pid,
 
359
    case dbg_wx_winman:is_started(dbg_wx_trace:title(Pid)) of
 
360
        true -> ignore;
 
361
        false -> int:attach(Pid, trace_function(State))
 
362
    end,
 
363
    State;
 
364
gui_cmd('Kill', State) ->
 
365
    exit((State#state.focus)#pinfo.pid, kill),
 
366
    State;
 
367
 
 
368
%% Break Menu
 
369
gui_cmd('Line Break...', State) ->
 
370
    Window = dbg_wx_mon_win:get_window(State#state.win),
 
371
    dbg_wx_break:start(Window, State#state.coords, line),
 
372
    State;
 
373
gui_cmd('Conditional Break...', State) ->
 
374
    Window = dbg_wx_mon_win:get_window(State#state.win),
 
375
    dbg_wx_break:start(Window, State#state.coords, conditional),
 
376
    State;
 
377
gui_cmd('Function Break...', State) ->
 
378
    Window = dbg_wx_mon_win:get_window(State#state.win),
 
379
    dbg_wx_break:start(Window, State#state.coords, function),
 
380
    State;
 
381
gui_cmd('Enable All', State) ->
 
382
    Breaks = int:all_breaks(),
 
383
    lists:foreach(fun ({{Mod, Line}, _Options}) ->
 
384
                          int:enable_break(Mod, Line)
 
385
                  end,
 
386
                  Breaks),
 
387
    State;
 
388
gui_cmd('Disable All', State) ->
 
389
    Breaks = int:all_breaks(),
 
390
    lists:foreach(fun ({{Mod, Line}, _Options}) ->
 
391
                          int:disable_break(Mod, Line)
 
392
                  end,
 
393
                  Breaks),
 
394
    State;
 
395
gui_cmd('Delete All', State) ->
 
396
    int:no_break(),
 
397
    State;
 
398
gui_cmd({break, {Mod, Line}, What}, State) ->
 
399
    case What of
 
400
        delete -> int:delete_break(Mod, Line);
 
401
        {status, inactive} -> int:disable_break(Mod, Line);
 
402
        {status, active} -> int:enable_break(Mod, Line);
 
403
        {trigger, Action} -> int:action_at_break(Mod, Line, Action)
 
404
    end,
 
405
    State;
 
406
 
 
407
%% Options Commands
 
408
gui_cmd({'Trace Window', TraceWin}, State) ->
 
409
    State2 = State#state{tracewin=TraceWin},
 
410
    case State#state.attach of
 
411
        false -> ignore;
 
412
        {Flags, {dbg_ui_trace, start, StartFlags}} ->
 
413
            case trace_function(State2) of
 
414
                {_, _, StartFlags} -> ignore;
 
415
                NewFunction -> % {_, _, NewStartFlags}
 
416
                    int:auto_attach(Flags, NewFunction)
 
417
            end;
 
418
        _AutoAttach -> ignore
 
419
    end,
 
420
    State2;
 
421
gui_cmd({'Auto Attach', When}, State) ->
 
422
    if
 
423
        When==[] -> int:auto_attach(false);
 
424
        true ->
 
425
            Flags = lists:map(fun(Name) -> map(Name) end, When),
 
426
            int:auto_attach(Flags, trace_function(State))
 
427
    end,
 
428
    State;
 
429
gui_cmd({'Stack Trace', [Name]}, State) ->
 
430
    int:stack_trace(map(Name)),
 
431
    State;
 
432
gui_cmd('Back Trace Size...', State) ->
 
433
    Window = dbg_wx_mon_win:get_window(State#state.win),
 
434
    What = {integer, State#state.backtrace},
 
435
    case dbg_wx_win:entry(Window, "Backtrace", 'Backtrace:', What) of
 
436
        cancel -> 
 
437
            State;
 
438
        {_,BackTrace} ->
 
439
            dbg_wx_mon_win:show_option(State#state.win,back_trace, BackTrace),
 
440
            State#state{backtrace=BackTrace}
 
441
    end;
 
442
 
 
443
%% Help Menu
 
444
gui_cmd('Debugger', State) ->
 
445
    HelpFile = filename:join([code:lib_dir(debugger),
 
446
                              "doc", "html", "part_frame.html"]),
 
447
    Window = dbg_wx_mon_win:get_window(State#state.win),
 
448
    dbg_wx_win:open_help(Window, HelpFile),
 
449
    State;
 
450
 
 
451
gui_cmd({focus, Pid, Win}, State) ->
 
452
    {value, PInfo} =
 
453
        lists:keysearch(Pid, #pinfo.pid, State#state.pinfos),
 
454
    gui_enable_functions(PInfo),
 
455
    State#state{win=Win, focus=PInfo};
 
456
gui_cmd(default, State) ->
 
457
    case lists:member('Attach', menus(enabled, State#state.focus)) of
 
458
        true -> gui_cmd('Attach', State);
 
459
        false -> State
 
460
    end.
 
461
 
 
462
%%--Commands from the interpreter-------------------------------------
 
463
 
 
464
int_cmd({interpret, Mod}, State) ->
 
465
    Win = dbg_wx_mon_win:add_module(State#state.win, 'Module', Mod),
 
466
    State#state{win=Win};
 
467
int_cmd({no_interpret, Mod}, State) ->
 
468
    Win = dbg_wx_mon_win:delete_module(State#state.win, Mod),
 
469
    State#state{win=Win};
 
470
 
 
471
int_cmd({new_process, {Pid, Function, Status, Info}}, State) ->
 
472
 
 
473
    %% Create record with information about the process
 
474
    Name = registered_name(Pid),
 
475
    PInfo = #pinfo{pid=Pid, status=Status},
 
476
 
 
477
    %% Update window
 
478
    Win = dbg_wx_mon_win:add_process(State#state.win,
 
479
                                     Pid, Name, Function, Status, Info),
 
480
 
 
481
    %% Store process information
 
482
    PInfos = State#state.pinfos ++ [PInfo],
 
483
    State#state{win=Win, pinfos=PInfos};
 
484
int_cmd({new_status, Pid, Status, Info}, State) ->
 
485
 
 
486
    %% Find stored information about the process
 
487
    PInfos = State#state.pinfos,
 
488
    {value, PInfo} = lists:keysearch(Pid, #pinfo.pid, PInfos),
 
489
 
 
490
    %% Update process information
 
491
    PInfo2 = PInfo#pinfo{status=Status},
 
492
    PInfos2 = lists:keyreplace(Pid, #pinfo.pid, PInfos, PInfo2),
 
493
    State2 = State#state{pinfos=PInfos2},
 
494
 
 
495
    %% Update window
 
496
    dbg_wx_mon_win:update_process(State2#state.win, Pid, Status, Info),
 
497
    case State2#state.focus of
 
498
        #pinfo{pid=Pid} ->
 
499
            gui_enable_functions(PInfo2),
 
500
            State2#state{focus=PInfo2};
 
501
        _ ->
 
502
            State2
 
503
    end;
 
504
 
 
505
int_cmd({new_break, Break}, State) ->
 
506
    Win = dbg_wx_mon_win:add_break(State#state.win, 'Break', Break),
 
507
    State#state{win=Win};
 
508
int_cmd({delete_break, Point}, State) ->
 
509
    Win = dbg_wx_mon_win:delete_break(State#state.win, Point),
 
510
    State#state{win=Win};
 
511
int_cmd({break_options, Break}, State) ->
 
512
    dbg_wx_mon_win:update_break(State#state.win, Break),
 
513
    State;
 
514
int_cmd(no_break, State) ->
 
515
    Win = dbg_wx_mon_win:clear_breaks(State#state.win),
 
516
    State#state{win=Win};
 
517
int_cmd({no_break, Mod}, State) ->
 
518
    Win = dbg_wx_mon_win:clear_breaks(State#state.win, Mod),
 
519
    State#state{win=Win};
 
520
 
 
521
int_cmd({auto_attach, AutoAttach}, State) ->
 
522
    OnFlags = case AutoAttach of
 
523
                  false -> [];
 
524
                  {Flags, _Function} -> Flags
 
525
              end,
 
526
    OffFlags = [init, exit, break] -- OnFlags,
 
527
    dbg_wx_mon_win:show_option(State#state.win, auto_attach, OnFlags),
 
528
    lists:foreach(fun(Flag) ->
 
529
                          dbg_wx_mon_win:select(map(Flag), true)
 
530
                  end,
 
531
                  OnFlags),
 
532
    lists:foreach(fun(Flag) ->
 
533
                          dbg_wx_mon_win:select(map(Flag), false)
 
534
                  end,
 
535
                  OffFlags),
 
536
    State#state{attach=AutoAttach};
 
537
int_cmd({stack_trace, Flag}, State) ->
 
538
    dbg_wx_mon_win:show_option(State#state.win, stack_trace, Flag),
 
539
    dbg_wx_mon_win:select(map(Flag), true),
 
540
    State.
 
541
 
 
542
 
 
543
%%====================================================================
 
544
%% GUI auxiliary functions
 
545
%%====================================================================
 
546
 
 
547
menus() ->
 
548
    [{'File', [{'Load Settings...', 0},
 
549
               {'Save Settings...', 2},
 
550
               separator,
 
551
               {'Exit', 0}]},
 
552
     {'Edit', [{'Refresh', no},
 
553
               {'Kill All', no}]},
 
554
     {'Module', [{'Interpret...', 0},
 
555
                 {'Delete All Modules', no},
 
556
                 separator]},
 
557
     {'Process', [{'Step', 0},
 
558
                  {'Next', 0},
 
559
                  {'Continue', 0},
 
560
                  {'Finish ', 0},
 
561
                  separator,
 
562
                  {'Attach', 0},
 
563
                  {'Kill', no}]},
 
564
     {'Break', [{'Line Break...', 5},
 
565
                {'Conditional Break...', no},
 
566
                {'Function Break...', no},
 
567
                separator,
 
568
                {'Enable All', no},
 
569
                {'Disable All', no},
 
570
                {'Delete All', 0},
 
571
                separator]},
 
572
     {'Options', [{'Trace Window', no, cascade,
 
573
                   [{'Search Area', no, check},
 
574
                    {'Button Area', no, check},
 
575
                    {'Evaluator Area', no, check},
 
576
                    {'Bindings Area', no, check},
 
577
                    {'Trace Area', no, check}]},
 
578
                  {'Auto Attach', no, cascade,
 
579
                   [{'First Call', no, check},
 
580
                    {'On Break', no, check},
 
581
                    {'On Exit', no, check}]},
 
582
                  {'Stack Trace', no, cascade,
 
583
                   [{'Stack On, Tail', no, radio},
 
584
                    {'Stack On, No Tail', no, radio},
 
585
                    {'Stack Off', no, radio}]},
 
586
                  {'Back Trace Size...', no}]},
 
587
     {'Windows', []},
 
588
     {'Help', [{'Debugger', no}]}].
 
589
 
 
590
menus(enabled,  undefined) ->
 
591
    [];
 
592
menus(disabled, undefined) ->
 
593
    ['Step','Next','Continue','Finish ','Attach','Kill'];
 
594
menus(enabled,  #pinfo{status=exit}) ->
 
595
    ['Attach'];
 
596
menus(disabled, #pinfo{status=exit}) ->
 
597
    ['Step','Next','Continue','Finish ','Kill'];
 
598
menus(enabled,  #pinfo{status=break}) ->
 
599
    ['Step','Next','Continue','Finish ','Attach','Kill'];
 
600
menus(disabled, #pinfo{status=break}) ->
 
601
    [];
 
602
menus(enabled,  _PInfo) ->
 
603
    ['Attach','Kill'];
 
604
menus(disabled, _PInfo) ->
 
605
    ['Step','Next','Continue','Finish '].
 
606
 
 
607
shortcut(l) -> {always, 'Load Settings...'};
 
608
shortcut(v) -> {always, 'Save Settings...'};
 
609
shortcut(e) -> {always, 'Exit'};
 
610
 
 
611
shortcut(i) -> {always, 'Interpret...'};
 
612
 
 
613
shortcut(s) -> {if_enabled, 'Step'};
 
614
shortcut(n) -> {if_enabled, 'Next'};
 
615
shortcut(c) -> {if_enabled, 'Continue'};
 
616
shortcut(f) -> {if_enabled, 'Finish '};
 
617
shortcut(a) -> {if_enabled, 'Attach'};
 
618
 
 
619
shortcut(b) -> {always, 'Line Break...'};
 
620
shortcut(d) -> {always, 'Delete All'};
 
621
 
 
622
shortcut(_) -> false.
 
623
 
 
624
%% Enable/disable functionality depending on the state of the process
 
625
%% currently in Focus
 
626
gui_enable_functions(PInfo) ->
 
627
    Enabled = menus(enabled, PInfo),
 
628
    Disabled = menus(disabled, PInfo),
 
629
    dbg_wx_mon_win:enable(Enabled, true),
 
630
    dbg_wx_mon_win:enable(Disabled, false).
 
631
 
 
632
%% Map values used by int to/from GUI names
 
633
map('First Call')        -> init;               % Auto attach
 
634
map('On Exit')           -> exit;
 
635
map('On Break')          -> break;
 
636
map(init)                -> 'First Call';
 
637
map(exit)                -> 'On Exit';
 
638
map(break)               -> 'On Break';
 
639
 
 
640
map('Stack On, Tail')    -> all;               % Stack trace
 
641
map('Stack On, No Tail') -> no_tail;
 
642
map('Stack Off')         -> false;
 
643
map(all)                 -> 'Stack On, Tail';
 
644
map(true)                -> 'Stack On, Tail';
 
645
map(no_tail)             -> 'Stack On, No Tail';
 
646
map(false)               -> 'Stack Off'.
 
647
 
 
648
 
 
649
%%====================================================================
 
650
%% Debugger settings
 
651
%%====================================================================
 
652
 
 
653
load_settings(SFile, State) ->
 
654
    case file:read_file(SFile) of
 
655
        {ok, Binary} ->
 
656
            case catch binary_to_term(Binary) of
 
657
                {debugger_settings, Settings} ->
 
658
                    load_settings2(Settings,
 
659
                                   State#state{sfile=SFile,
 
660
                                               changed=false});
 
661
                _Error -> State
 
662
            end;
 
663
        {error, _Reason} -> State
 
664
    end.
 
665
 
 
666
load_settings2(Settings, State) ->
 
667
    {TraceWin, AutoAttach, StackTrace, BackTrace, Files, Breaks} =
 
668
        Settings,
 
669
 
 
670
    TraceWinAll = ['Button Area', 'Evaluator Area', 'Bindings Area',
 
671
                   'Trace Area'],
 
672
    lists:foreach(fun(Area) -> dbg_wx_mon_win:select(Area, true) end,
 
673
                  TraceWin),
 
674
    lists:foreach(fun(Area) -> dbg_wx_mon_win:select(Area, false) end,
 
675
                  TraceWinAll--TraceWin),
 
676
 
 
677
    case AutoAttach of
 
678
        false -> int:auto_attach(false);
 
679
        {Flags, Function} -> int:auto_attach(Flags, Function)
 
680
    end,
 
681
 
 
682
    int:stack_trace(StackTrace),
 
683
 
 
684
    dbg_wx_mon_win:show_option(State#state.win, back_trace, BackTrace),
 
685
 
 
686
    case State#state.mode of
 
687
        local -> lists:foreach(fun(File) -> int:i(File) end, Files);
 
688
        global -> lists:foreach(fun(File) -> int:ni(File) end, Files)
 
689
    end,
 
690
    lists:foreach(fun(Break) ->
 
691
                          {{Mod, Line}, [Status, Action, _, Cond]} =
 
692
                              Break,
 
693
                          int:break(Mod, Line),
 
694
                          if
 
695
                              Status==inactive ->
 
696
                                  int:disable_break(Mod, Line);
 
697
                              true -> ignore
 
698
                          end,
 
699
                          if
 
700
                              Action/=enable ->
 
701
                                  int:action_at_break(Mod,Line,Action);
 
702
                              true -> ignore
 
703
                          end,
 
704
                          case Cond of
 
705
                              CFunction when is_tuple(CFunction) ->
 
706
                                  int:test_at_break(Mod,Line,CFunction);
 
707
                              null -> ignore
 
708
                          end
 
709
                  end,
 
710
                  Breaks),
 
711
 
 
712
    State#state{tracewin=TraceWin, backtrace=BackTrace}.
 
713
 
 
714
save_settings(SFile, State) ->
 
715
    Settings = {State#state.tracewin,
 
716
                int:auto_attach(),
 
717
                int:stack_trace(),
 
718
                State#state.backtrace,
 
719
                lists:map(fun(Mod) ->
 
720
                                  int:file(Mod)
 
721
                          end,
 
722
                          int:interpreted()),
 
723
                int:all_breaks()},
 
724
 
 
725
    Binary = term_to_binary({debugger_settings, Settings}),
 
726
    case file:write_file(SFile, Binary) of
 
727
        ok ->
 
728
            State#state{sfile=SFile, changed=false};
 
729
        {error, _Reason} ->
 
730
            State
 
731
    end.
 
732
 
 
733
 
 
734
%%====================================================================
 
735
%% Other internal functions
 
736
%%====================================================================
 
737
 
 
738
registered_name(Pid) ->
 
739
 
 
740
    %% Yield in order to give Pid more time to register its name
 
741
    timer:sleep(200),
 
742
 
 
743
    Node = node(Pid),
 
744
    if
 
745
        Node==node() ->
 
746
            case erlang:process_info(Pid, registered_name) of
 
747
                {registered_name, Name} -> Name;
 
748
                _ -> undefined
 
749
            end;
 
750
        true ->
 
751
            case rpc:call(Node,erlang,process_info,
 
752
                          [Pid,registered_name]) of
 
753
                {registered_name, Name} -> Name;
 
754
                _ -> undefined
 
755
            end
 
756
    end.
 
757
 
 
758
trace_function(State) ->
 
759
    {dbg_wx_trace, start, [State#state.tracewin, State#state.backtrace]}.