~statik/ubuntu/maverick/erlang/erlang-merge-testing

« back to all changes in this revision

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

  • Committer: Bazaar Package Importer
  • Author(s): Sergei Golovan
  • Date: 2009-05-01 10:14:38 UTC
  • mfrom: (3.1.4 sid)
  • Revision ID: james.westby@ubuntu.com-20090501101438-6qlr6rsdxgyzrg2z
Tags: 1:13.b-dfsg-2
* Cleaned up patches: removed unneeded patch which helped to support
  different SCTP library versions, made sure that changes for m68k
  architecture applied only when building on this architecture.
* Removed duplicated information from binary packages descriptions.
* Don't require libsctp-dev build-dependency on solaris-i386 architecture
  which allows to build Erlang on Nexenta (thanks to Tim Spriggs for
  the suggestion).

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_win).
 
22
 
 
23
%% External exports
 
24
-export([init/0]).
 
25
-export([create_win/3, get_window/1,
 
26
         show_option/3,
 
27
         enable/2, is_enabled/1, select/2,
 
28
         add_module/3, delete_module/2,
 
29
         add_process/6, update_process/4, clear_processes/1,
 
30
         add_break/3, update_break/2, delete_break/2,
 
31
         clear_breaks/1, clear_breaks/2,
 
32
         handle_event/2
 
33
        ]).
 
34
 
 
35
-import(dbg_wx_win, [to_string/1, to_string/2]).
 
36
 
 
37
-include_lib("wx/include/wx.hrl").
 
38
 
 
39
-define(default_rows,10).
 
40
 
 
41
-record(moduleInfo, {module, menubtn}).
 
42
-record(procInfo, {pid, row}).
 
43
-record(breakInfo, {point, status, break}).
 
44
-record(break, {mb, smi, emi, dimi, demi}).  %% BUGBUG defined in dbg_ui_win
 
45
-record(winInfo, {window,       % gsobj()
 
46
                  grid,         % gsobj()
 
47
                  row,          % int() Last row in grid
 
48
 
 
49
                  focus,        % int() Selected row in grid
 
50
 
 
51
                  modules=[],   % [#moduleInfo{}] Known modules
 
52
                  processes=[], % [#procInfo{}] Known processes
 
53
                  breaks=[],    % [#breakInfo{}] Known breakpoints
 
54
 
 
55
                  listbox,      % gsobj() Listinng known modules
 
56
 
 
57
                  %% Auto attach buttons
 
58
                  fbutton,      % gsobj()
 
59
                  bbutton,      % gsobj()
 
60
                  ebutton,      % gsobj()
 
61
                  selected=[],  % ['First Call'|'On Break'|'On Exit']
 
62
 
 
63
                  slabel,       % showing Stack Trace option
 
64
                  blabel        % showing Back Trace Size
 
65
                 }).
 
66
 
 
67
%%====================================================================
 
68
%% External exports
 
69
%%====================================================================
 
70
 
 
71
init() ->
 
72
    dbg_wx_win:init().
 
73
 
 
74
%%--------------------------------------------------------------------
 
75
%% create_win(GS, Title, Menus) -> #winInfo{}
 
76
%%   GS = gsobj()
 
77
%%   Title = string()
 
78
%%   Menus = [menu()]  See dbg_ui_win.erl
 
79
%%--------------------------------------------------------------------
 
80
 
 
81
-define(GRID,1000).
 
82
 
 
83
-define(PAD, 5).
 
84
-define(Wf, 150).
 
85
-define(Wg, 770).
 
86
-define(W, 800).
 
87
-define(H, 390).
 
88
 
 
89
create_win(_Wx, Title, Menus) ->
 
90
    wx:batch(fun() -> create_win_batch(Title, Menus) end).
 
91
                      
 
92
create_win_batch(Title, Menus) ->
 
93
    Win = wxFrame:new(wx:null(), ?wxID_ANY, Title, 
 
94
                      [{size, {?W,?H}}]),
 
95
    wxFrame:connect(Win, close_window, [{skip, true}]),
 
96
    MenuBar = wxMenuBar:new(),
 
97
    dbg_wx_win:create_menus(MenuBar, Menus, Win, 1),
 
98
    wxFrame:setMenuBar(Win, MenuBar),
 
99
    
 
100
    MainSz = wxBoxSizer:new(?wxHORIZONTAL),
 
101
    LeftSz = wxBoxSizer:new(?wxVERTICAL),
 
102
 
 
103
    Panel = wxPanel:new(Win),
 
104
    Hlb = 200,
 
105
    Listbox = wxListBox:new(Panel, ?wxID_ANY, [{size,{?Wf,Hlb}},
 
106
                                               {style,?wxLB_SINGLE}]),
 
107
    wxSizer:add(LeftSz,Listbox,[{border, 3}]),
 
108
    wxListBox:connect(Listbox, command_listbox_doubleclicked),
 
109
    wxListBox:connect(Listbox, right_down),
 
110
 
 
111
    SBox = wxStaticBox:new(Panel, ?wxID_ANY, "Auto Attach:"),
 
112
    SBS  = wxStaticBoxSizer:new(SBox, ?wxVERTICAL),
 
113
    Fbtn = wxCheckBox:new(Panel, ?wxID_ANY, "First Call"),
 
114
    wxSizer:add(SBS,Fbtn),
 
115
    Bbtn = wxCheckBox:new(Panel, ?wxID_ANY, "On Break"),
 
116
    wxSizer:add(SBS,Bbtn),
 
117
    Ebtn = wxCheckBox:new(Panel, ?wxID_ANY, "On Exit"),
 
118
    wxSizer:add(SBS,Ebtn),
 
119
    wxFrame:connect(Panel, command_checkbox_clicked), 
 
120
    wxSizer:add(LeftSz,SBS, [{flag,?wxEXPAND}]),
 
121
 
 
122
    SLabel = wxStaticText:new(Panel, ?wxID_ANY, "Stack Trace:\n On (with tail)"), 
 
123
    wxSizer:add(LeftSz,SLabel),
 
124
    BLabel = wxStaticText:new(Panel, ?wxID_ANY, "Back Trace Size:\n 50000"), 
 
125
    wxSizer:add(LeftSz,BLabel),
 
126
    
 
127
    %% Create list_crtl / grid
 
128
    Grid = wxListCtrl:new(Panel, [{winid, ?GRID},
 
129
                                  {style, ?wxLC_REPORT bor ?wxLC_SINGLE_SEL 
 
130
                                   bor ?wxLC_HRULES },
 
131
                                  {size, {600, -1}}]),
 
132
    LI = wxListItem:new(),
 
133
    wxListItem:setText(LI, "Pid"), 
 
134
    wxListItem:setAlign(LI, ?wxLIST_FORMAT_CENTRE),
 
135
    wxListCtrl:insertColumn(Grid, 0, LI),
 
136
    wxListItem:setText(LI, "Initial Call"),
 
137
    wxListItem:setAlign(LI, ?wxLIST_FORMAT_LEFT),
 
138
    wxListCtrl:insertColumn(Grid, 1, LI),
 
139
    wxListItem:setText(LI, "Name"), 
 
140
    wxListCtrl:insertColumn(Grid, 2, LI),
 
141
    wxListItem:setAlign(LI, ?wxLIST_FORMAT_CENTRE),
 
142
    wxListItem:setText(LI, "Status"), 
 
143
    wxListCtrl:insertColumn(Grid, 3, LI),
 
144
    wxListItem:setText(LI, "Information"), 
 
145
    wxListItem:setAlign(LI, ?wxLIST_FORMAT_LEFT),
 
146
    wxListCtrl:insertColumn(Grid, 4, LI),
 
147
    wxListItem:destroy(LI),
 
148
        
 
149
    wxListCtrl:setColumnWidth(Grid, 0, 80),
 
150
    wxListCtrl:setColumnWidth(Grid, 1, 150),
 
151
    wxListCtrl:setColumnWidth(Grid, 2, 100),
 
152
    wxListCtrl:setColumnWidth(Grid, 3, 70),
 
153
    wxListCtrl:setColumnWidth(Grid, 4, 200),
 
154
    wxListCtrl:connect(Grid, command_list_item_activated), 
 
155
    wxListCtrl:connect(Grid, command_list_item_selected), 
 
156
    wxListCtrl:connect(Grid, size, [{skip, true}]),
 
157
    wxListCtrl:connect(Grid, key_up, [{id, ?GRID}, {skip,true}]),
 
158
 
 
159
    wxWindow:connect(Win, enter_window, [{skip,true}]),
 
160
    wxWindow:setFocus(Grid),
 
161
 
 
162
    %% Put it in the window
 
163
    wxSizer:add(MainSz, LeftSz, [{border, 3}, {flag,?wxALL bor ?wxEXPAND}]),
 
164
    wxSizer:add(MainSz, Grid,   [{border, 3}, {flag,?wxALL bor ?wxEXPAND}, 
 
165
                                 {proportion, 1}]),
 
166
 
 
167
    wxWindow:setSizer(Panel,MainSz),
 
168
    wxSizer:fit(MainSz, Win),
 
169
    wxSizer:setSizeHints(MainSz,Win),
 
170
    
 
171
    IconFile = dbg_wx_win:find_icon("erlang_bug.png"),
 
172
    Icon = wxIcon:new(IconFile, [{type,?wxBITMAP_TYPE_PNG}]),
 
173
    wxFrame:setIcon(Win, Icon),
 
174
    wxIcon:destroy(Icon),
 
175
    wxFrame:show(Win),
 
176
    dbg_wx_winman:raise(Win),
 
177
    #winInfo{window=Win, grid=Grid, row=0, focus=0,
 
178
             listbox=Listbox,
 
179
             fbutton=Fbtn, bbutton=Bbtn, ebutton=Ebtn,
 
180
             slabel=SLabel, blabel=BLabel}.
 
181
 
 
182
%%--------------------------------------------------------------------
 
183
%% get_window(WinInfo) -> Window
 
184
%%   WinInfo = #winInfo{}
 
185
%%   Window = wxobj()
 
186
%%--------------------------------------------------------------------
 
187
get_window(WinInfo) ->
 
188
    WinInfo#winInfo.window.
 
189
 
 
190
%%--------------------------------------------------------------------
 
191
%% show_option(WinInfo, Option, Value) -> void()
 
192
%%   WinInfo = #winInfo{}
 
193
%%   Option = auto_attach | stack_trace | back_trace
 
194
%%   Value = [Flag]                          % Option==auto_attach
 
195
%%             Flag = init | break | exit
 
196
%%         | true | all | no_tail | false    % Option==stack_trace
 
197
%%         | int()                           % Option==back_trace
 
198
%%--------------------------------------------------------------------
 
199
show_option(WinInfo, Option, Value) ->
 
200
    case Option of      
 
201
        auto_attach ->
 
202
            wx:foreach(fun(Button) ->
 
203
                                  wxCheckBox:setValue(Button, false)
 
204
                          end,
 
205
                          option_buttons(WinInfo, [init, break, exit])),
 
206
            wx:foreach(fun(Button) ->
 
207
                                  wxCheckBox:setValue(Button, true)
 
208
                          end,
 
209
                          option_buttons(WinInfo, Value));
 
210
 
 
211
        stack_trace ->
 
212
            Text = case Value of
 
213
                       all ->     "Stack Trace:\n On (with tail)";
 
214
                       true ->    "Stack Trace:\n On (with tail)";
 
215
                       no_tail -> "Stack Trace:\n On (no tail)";
 
216
                       false ->   "Stack Trace:\n Off"
 
217
                   end,
 
218
            wxStaticText:setLabel(WinInfo#winInfo.slabel, Text);
 
219
 
 
220
        back_trace ->
 
221
            Text = "Back Trace Size:\n " ++ integer_to_list(Value),
 
222
            wxStaticText:setLabel(WinInfo#winInfo.blabel, Text)
 
223
    end.
 
224
 
 
225
option_buttons(WinInfo, [init|Flags]) ->
 
226
    [WinInfo#winInfo.fbutton|option_buttons(WinInfo, Flags)];
 
227
option_buttons(WinInfo, [break|Flags]) ->
 
228
    [WinInfo#winInfo.bbutton|option_buttons(WinInfo, Flags)];
 
229
option_buttons(WinInfo, [exit|Flags]) ->
 
230
    [WinInfo#winInfo.ebutton|option_buttons(WinInfo, Flags)];
 
231
option_buttons(_WinInfo, []) ->
 
232
    [].
 
233
 
 
234
%%--------------------------------------------------------------------
 
235
%% enable([MenuItem], Bool)
 
236
%% is_enabled(MenuItem) -> Bool
 
237
%%   MenuItem = atom()
 
238
%%   Bool = boolean()
 
239
%%--------------------------------------------------------------------
 
240
enable(MenuItems, Bool) ->
 
241
    lists:foreach(fun(MenuItem) ->
 
242
                          MI = get(MenuItem),
 
243
                          wxMenuItem:enable(MI, [{enable, Bool}])
 
244
                  end,
 
245
                  MenuItems).
 
246
 
 
247
is_enabled(MenuItem) ->
 
248
    MI = get(MenuItem),
 
249
    wxMenuItem:isEnabled(MI).
 
250
 
 
251
%%--------------------------------------------------------------------
 
252
%% select(MenuItem, Bool)
 
253
%%   MenuItem = atom()
 
254
%%   Bool = boolean()
 
255
%%--------------------------------------------------------------------
 
256
select(MenuItem, Bool) ->
 
257
    MI = get(MenuItem),
 
258
    wxMenuItem:check(MI, [{check, Bool}]).
 
259
 
 
260
%%--------------------------------------------------------------------
 
261
%% add_module(WinInfo, Name, Mod) -> WinInfo
 
262
%%   WinInfo = #winInfo{}
 
263
%%   Name = atom()
 
264
%%   Mod = atom()
 
265
%%--------------------------------------------------------------------
 
266
add_module(WinInfo, MenuName, Mod) ->
 
267
    Win = WinInfo#winInfo.window,
 
268
    Modules = WinInfo#winInfo.modules,
 
269
    case lists:keysearch(Mod, #moduleInfo.module, Modules) of
 
270
        {value, _ModInfo} -> WinInfo;
 
271
        false ->
 
272
            %% Create a menu for the module
 
273
            Menu = get(MenuName),
 
274
            Sub = wxMenu:new([]),
 
275
            ViewItem = wxMenu:append(Sub, ?wxID_ANY, "View"), 
 
276
            ViewId = wxMenuItem:getId(ViewItem),
 
277
            wxMenu:connect(Win, command_menu_selected, 
 
278
                           [{id,ViewId}, {userData, {module,Mod,view}}]),
 
279
            DelItem = wxMenu:append(Sub, ?wxID_ANY, "Delete"), 
 
280
            DelId = wxMenuItem:getId(DelItem),
 
281
            wxMenu:connect(Win, command_menu_selected, 
 
282
                           [{id,DelId}, {userData, {module,Mod,delete}}]),
 
283
            MenuBtn = wxMenu:append(Menu, ?wxID_ANY, atom_to_list(Mod), Sub),
 
284
            wxListBox:append(WinInfo#winInfo.listbox, atom_to_list(Mod)),
 
285
            
 
286
            ModInfo = #moduleInfo{module=Mod, menubtn={Menu,MenuBtn}},
 
287
            WinInfo#winInfo{modules=[ModInfo | Modules]}
 
288
    end.
 
289
    
 
290
%%--------------------------------------------------------------------
 
291
%% delete_module(WinInfo, Mod) -> WinInfo
 
292
%%   WinInfo = #winInfo{}
 
293
%%   Mod = atom()
 
294
%%--------------------------------------------------------------------
 
295
delete_module(WinInfo, Mod) ->
 
296
    {value, ModInfo} = lists:keysearch(Mod, #moduleInfo.module,
 
297
                                       WinInfo#winInfo.modules),
 
298
    {Menu, MenuBtn} = ModInfo#moduleInfo.menubtn,
 
299
    wxMenu:'Destroy'(Menu, MenuBtn),
 
300
    ListBox = WinInfo#winInfo.listbox,
 
301
    Id = wxListBox:findString(ListBox, atom_to_list(Mod)),
 
302
    wxListBox:delete(ListBox,Id),
 
303
    WinInfo#winInfo{modules=lists:keydelete(Mod, #moduleInfo.module,
 
304
                                            WinInfo#winInfo.modules)}.
 
305
 
 
306
%%--------------------------------------------------------------------
 
307
%% add_process(WinInfo, Pid, Name, Function, Status, Info) -> WinInfo
 
308
%%   WinInfo = #winInfo{}
 
309
%%   Pid = pid()
 
310
%%   Name = undefined | atom()
 
311
%%   Function = {Mod, Func, Args}
 
312
%%   Status = idle | running | break | exit
 
313
%%   Info = {} | term()
 
314
%%--------------------------------------------------------------------
 
315
add_process(WinInfo, Pid, Name, {Mod,Func,Args}, Status, Info) ->
 
316
    Grid = WinInfo#winInfo.grid,
 
317
    Row = (WinInfo#winInfo.row),
 
318
    
 
319
    Name2 = case Name of undefined -> ""; _ -> to_string(Name) end,
 
320
    FuncS = to_string("~w:~w/~w", [Mod, Func, length(Args)]),
 
321
    Info2 = case Info of {} -> ""; _ -> to_string(Info) end,
 
322
    Pid2  = to_string("~p",[Pid]),
 
323
    
 
324
    Add = fun() ->
 
325
                  _Dbg = wxListCtrl:insertItem(Grid, Row,""),
 
326
                  %%wxListCtrl:setItemData(Grid,Temp,Row),
 
327
                  if (Row rem 2) =:= 0 -> 
 
328
                          wxListCtrl:setItemBackgroundColour(Grid, Row, {240,240,255});
 
329
                     true -> ignore
 
330
                  end,
 
331
 
 
332
                  wxListCtrl:setItem(Grid, Row, 0, Pid2),
 
333
                  wxListCtrl:setItem(Grid, Row, 1, FuncS),
 
334
                  wxListCtrl:setItem(Grid, Row, 2, Name2),
 
335
                  wxListCtrl:setItem(Grid, Row, 3, to_string(Status)),
 
336
                  wxListCtrl:setItem(Grid, Row, 4, Info2),
 
337
                  ok
 
338
          end,
 
339
    wx:batch(Add),
 
340
 
 
341
    ProcInfo = #procInfo{pid=Pid, row=Row},
 
342
    WinInfo#winInfo{processes=[ProcInfo|WinInfo#winInfo.processes],
 
343
                    row=Row+1}.
 
344
 
 
345
%%--------------------------------------------------------------------
 
346
%% update_process(WinInfo, Pid, Status, Info)
 
347
%%   WinInfo = #winInfo{}
 
348
%%   Pid = pid()
 
349
%%   Status = idle | running | break | exit
 
350
%%   Info = {} | term()
 
351
%%--------------------------------------------------------------------
 
352
update_process(WinInfo, Pid, Status, Info) ->
 
353
    {value, ProcInfo} = lists:keysearch(Pid, #procInfo.pid,
 
354
                                        WinInfo#winInfo.processes),
 
355
 
 
356
    Grid = WinInfo#winInfo.grid,
 
357
    Row  = ProcInfo#procInfo.row,    
 
358
    Info2 = case Info of {} -> ""; _ -> Info end,
 
359
    wxListCtrl:setItem(Grid, Row, 3, to_string(Status)),
 
360
    wxListCtrl:setItem(Grid, Row, 4, to_string(Info2)).
 
361
  
 
362
%%--------------------------------------------------------------------
 
363
%% clear_processes(WinInfo) -> WinInfo
 
364
%%   WinInfo = #winInfo{}
 
365
%%--------------------------------------------------------------------
 
366
clear_processes(WinInfo) ->
 
367
    Grid = WinInfo#winInfo.grid,
 
368
    Max = WinInfo#winInfo.row,
 
369
    wx:batch(fun() -> clear_processes(Grid, Max-1) end),
 
370
    WinInfo#winInfo{row=0, focus=0, processes=[]}.
 
371
 
 
372
clear_processes(Grid, Row) when Row >= 0 ->
 
373
    Item = wxListItem:new(),
 
374
    wxListItem:setId(Item,Row),
 
375
    wxListItem:setColumn(Item, 3),
 
376
    case wxListCtrl:getItem(Grid, Item) of
 
377
        true -> 
 
378
            case wxListItem:getText(Item) of
 
379
                "exit" ->
 
380
                    wxListItem:setColumn(Item, 0),
 
381
                    wxListCtrl:getItem(Grid, Item),
 
382
                    Pid = list_to_pid(wxListItem:getText(Item)),
 
383
                    dbg_wx_winman:clear_process(dbg_wx_trace:title(Pid));
 
384
                _ ->
 
385
                    ok
 
386
            end;
 
387
        false ->
 
388
            ignore
 
389
    end,
 
390
    wxListItem:destroy(Item),
 
391
    wxListCtrl:deleteItem(Grid, Row),
 
392
    clear_processes(Grid, Row-1);
 
393
clear_processes(_Grid, _Row) ->
 
394
    done.
 
395
 
 
396
%%--------------------------------------------------------------------
 
397
%% add_break(WinInfo, Name, {Point, Options}) -> WinInfo
 
398
%%   WinInfo = #winInfo{}
 
399
%%   Name = atom()
 
400
%%   Point = {Mod, Line}
 
401
%%   Options = [Status, Action, Mods, Cond]
 
402
%%     Status = active | inactive
 
403
%%     Action = enable | disable | delete
 
404
%%     Mods = null (not used)
 
405
%%     Cond = null | {Mod, Func}
 
406
%%--------------------------------------------------------------------
 
407
add_break(WinInfo, Menu, {Point, Options}) ->
 
408
    Break = dbg_wx_win:add_break(WinInfo#winInfo.window, Menu, Point),
 
409
    dbg_wx_win:update_break(Break, Options),
 
410
    BreakInfo = #breakInfo{point=Point, break=Break},
 
411
    WinInfo#winInfo{breaks=[BreakInfo|WinInfo#winInfo.breaks]}.
 
412
 
 
413
%%--------------------------------------------------------------------
 
414
%% update_break(WinInfo, {Point, Options})
 
415
%%   WinInfo = #winInfo{}
 
416
%%   Point = {Mod, Line}
 
417
%%   Options = [Status, Action, Mods, Cond]
 
418
%%     Status = active | inactive
 
419
%%     Action = enable | disable | delete
 
420
%%     Mods = null (not used)
 
421
%%     Cond = null | {Mod, Func}
 
422
%%--------------------------------------------------------------------
 
423
update_break(WinInfo, {Point, Options}) ->
 
424
    {value, BreakInfo} = lists:keysearch(Point, #breakInfo.point,
 
425
                                         WinInfo#winInfo.breaks),
 
426
    dbg_wx_win:update_break(BreakInfo#breakInfo.break, Options).
 
427
 
 
428
%%--------------------------------------------------------------------
 
429
%% delete_break(WinInfo, Point) -> WinInfo
 
430
%%   WinInfo = #winInfo{}
 
431
%%   Point = {Mod, Line}
 
432
%%--------------------------------------------------------------------
 
433
delete_break(WinInfo, Point) ->
 
434
    {value, BreakInfo} = lists:keysearch(Point, #breakInfo.point,
 
435
                                         WinInfo#winInfo.breaks),
 
436
    dbg_wx_win:delete_break(BreakInfo#breakInfo.break),
 
437
    WinInfo#winInfo{breaks=lists:keydelete(Point, #breakInfo.point,
 
438
                                           WinInfo#winInfo.breaks)}.
 
439
 
 
440
%%--------------------------------------------------------------------
 
441
%% clear_breaks(WinInfo) -> WinInfo
 
442
%% clear_breaks(WinInfo, Mod) -> WinInfo
 
443
%%   WinInfo = #winInfo{}
 
444
%%--------------------------------------------------------------------
 
445
clear_breaks(WinInfo) ->
 
446
    lists:foreach(fun(BreakInfo) ->
 
447
                          dbg_wx_win:delete_break(BreakInfo#breakInfo.break)
 
448
                  end,
 
449
                  WinInfo#winInfo.breaks),
 
450
    WinInfo#winInfo{breaks=[]}.
 
451
clear_breaks(WinInfo, Mod) ->
 
452
    Fun =
 
453
        fun(BreakInfo) ->
 
454
                case BreakInfo#breakInfo.point of
 
455
                    {Mod, _Line} ->
 
456
                        dbg_wx_win:delete_break(BreakInfo#breakInfo.break),
 
457
                        false;
 
458
                    _ -> true
 
459
                end
 
460
        end,
 
461
    Breaks = lists:filter(Fun, WinInfo#winInfo.breaks),
 
462
    WinInfo#winInfo{breaks=Breaks}.
 
463
    
 
464
%%--------------------------------------------------------------------
 
465
%% handle_event(WxEvent, WinInfo) -> Command
 
466
%%   WxEvent = #wx{}
 
467
%%   WinInfo = #winInfo{}
 
468
%%   Command = ignore
 
469
%%           | stopped
 
470
%%           | {coords, {X,Y}}
 
471
%%
 
472
%%           | {shortcut, Key}
 
473
%%           | MenuItem | {Menu, [MenuItem]}
 
474
%%               MenuItem = Menu = atom()
 
475
%%           | {break, Point, What}
 
476
%%               What = delete | {status, Status} | {trigger, Trigger}
 
477
%%           | {module, Mod, What}
 
478
%%               What = view | delete
 
479
%%
 
480
%%           | {focus, Pid, WinInfo}
 
481
%%           | default
 
482
%%--------------------------------------------------------------------
 
483
%% Window events
 
484
handle_event(#wx{event=#wxSize{size={W,_}}}, #winInfo{grid=Grid}) ->
 
485
    wx:batch(fun() ->
 
486
                     Tot = wx:foldl(fun(C,Sum) -> 
 
487
                                            Sum + wxListCtrl:getColumnWidth(Grid, C)
 
488
                                    end, 0, [0,1,2,3]),
 
489
                     wxListCtrl:setColumnWidth(Grid, 4, W-Tot-4)
 
490
             end),
 
491
    ignore;
 
492
handle_event(_Ev=#wx{event=#wxClose{}}, _WinInfo) ->
 
493
%%    io:format("~p Received ~p close ~p~n", [?MODULE, self(), _Ev]),
 
494
    stopped;
 
495
 
 
496
%% Menus and keyboard shortcuts
 
497
handle_event(#wx{userData={dbg_ui_winman, Win},
 
498
                 event=#wxCommand{type=command_menu_selected}}, _Wi) ->
 
499
    dbg_wx_winman:raise(Win),
 
500
    ignore;
 
501
handle_event(_Ev = #wx{event=#wxKey{keyCode=Key, controlDown=true}}, _WinInfo) ->
 
502
    if
 
503
        Key/=?WXK_UP, Key/=?WXK_DOWN, Key /=? WXK_RETURN -> 
 
504
            try  
 
505
                {shortcut, list_to_atom([Key+($a-$A)])}
 
506
            catch _:_ -> ignore
 
507
            end;
 
508
        true -> 
 
509
            ignore
 
510
    end;
 
511
 
 
512
handle_event(#wx{userData={break, Point, status}, 
 
513
                 event=#wxCommand{type=command_menu_selected}},
 
514
             WinInfo) ->
 
515
    {value, BreakInfo} = lists:keysearch(Point, #breakInfo.point,
 
516
                                         WinInfo#winInfo.breaks),
 
517
    %% This is a temporary hack !!
 
518
    #breakInfo{break=#break{smi=Smi}} = BreakInfo,
 
519
 
 
520
    case wxMenuItem:getText(Smi) of
 
521
        "Enable" -> {break, Point, {status, active}};
 
522
        "Disable" -> {break, Point, {status, inactive}}
 
523
    end;
 
524
 
 
525
%% Listbox
 
526
handle_event(#wx{event=#wxCommand{type=command_listbox_doubleclicked, cmdString=ModS}}, 
 
527
             _WinInfo) ->
 
528
    {module, list_to_atom(ModS), view};
 
529
handle_event(#wx{obj=ListBox, event=#wxMouse{type=right_down, x=X,y=Y}}, 
 
530
             #winInfo{listbox=ListBox}) ->
 
531
    case wxListBox:hitTest(ListBox, {X,Y}) of
 
532
        ?wxNOT_FOUND -> ignore;
 
533
        Row ->      
 
534
            ModS = wxListBox:getString(ListBox,Row),
 
535
            io:format("Re-loading/interpreting: ~s~n", [ModS]),
 
536
            int:i(list_to_atom(ModS)),
 
537
            ignore
 
538
    end;
 
539
 
 
540
%% Auto attach buttons
 
541
handle_event(#wx{event=#wxCommand{type=command_checkbox_clicked}}, 
 
542
             WinInfo) ->
 
543
    Check = fun(Button, NamesAcc) ->
 
544
                    case wxCheckBox:isChecked(Button) of
 
545
                        true ->
 
546
                            Name = wxCheckBox:getLabel(Button),
 
547
                            [list_to_atom(Name)|NamesAcc];
 
548
                        false ->
 
549
                            NamesAcc
 
550
                    end
 
551
            end,
 
552
    Names = wx:foldl(Check, [],
 
553
                     [WinInfo#winInfo.ebutton,
 
554
                      WinInfo#winInfo.bbutton,
 
555
                      WinInfo#winInfo.fbutton]),
 
556
    {'Auto Attach', Names};
 
557
 
 
558
%% Process grid
 
559
handle_event(#wx{event=#wxList{type=command_list_item_selected,
 
560
                               itemIndex=Row}}, WinInfo) ->
 
561
    #winInfo{processes=Pids} = WinInfo,
 
562
    {value, #procInfo{pid=Pid}} = 
 
563
        lists:keysearch(Row, #procInfo.row, Pids),
 
564
    {focus, Pid, WinInfo#winInfo{focus=Row}};
 
565
handle_event(#wx{event=#wxList{type=command_list_item_activated}}, 
 
566
             _WinInfo) ->
 
567
    default;
 
568
handle_event(#wx{event=#wxMouse{type=enter_window}}, #winInfo{grid=Grid}) ->
 
569
    %% Keyboard focus
 
570
    wxWindow:setFocus(Grid),
 
571
    ignore;
 
572
 
 
573
%% Menu Events
 
574
handle_event(#wx{userData=Data, 
 
575
                 event=_Cmd=#wxCommand{type=command_menu_selected}},
 
576
             _WinInfo) ->
 
577
    Data;
 
578
handle_event(_Event, _WinInfo) ->
 
579
%%    io:format("Ev: ~p~n",[_Event]),
 
580
    ignore.
 
581
 
 
582
%%====================================================================
 
583
%% Internal functions
 
584
%%====================================================================
 
585
   
 
586