~ubuntu-branches/ubuntu/karmic/erlang/karmic-security

« back to all changes in this revision

Viewing changes to lib/debugger/src/dbg_wx_break_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_break_win).
 
22
 
 
23
%% External exports
 
24
-export([create_win/5,
 
25
         update_functions/2,
 
26
         handle_event/2]).
 
27
 
 
28
-include_lib("wx/include/wx.hrl").
 
29
 
 
30
-record(winInfo, {type,            % line | conditional | function
 
31
                  win,             % wxobj()
 
32
                  entries,         % [{atom|integer, wxobj()}]
 
33
                  trigger,         % [{wxobj(),enable | disable | delete}]
 
34
                  listbox,         % wxobj()
 
35
                  text,            % wxobj()
 
36
                  ok,              % wxobj()
 
37
                  funcs=[]         % [[Name, Arity]]
 
38
                 }).
 
39
 
 
40
%%====================================================================
 
41
%% External exports
 
42
%%====================================================================
 
43
 
 
44
%%--------------------------------------------------------------------
 
45
%% create_win(Win, Pos, Type, Mod, Line) -> #winInfo{}
 
46
%%   Win = Top level window
 
47
%%   Pos = {X, Y}
 
48
%%     X = Y = integer()
 
49
%%   Type =  line | conditional | function
 
50
%%   Mod = atom() | ""
 
51
%%   Line = integer() | ""
 
52
%%--------------------------------------------------------------------
 
53
 
 
54
create_win(Parent, Pos, function, Mod, _Line) ->
 
55
    Win = wxDialog:new(Parent, ?wxID_ANY, "Function Break",
 
56
                       [{pos, Pos}, 
 
57
                        {style, ?wxDEFAULT_DIALOG_STYLE bor ?wxRESIZE_BORDER}]),
 
58
    MainS = wxBoxSizer:new(?wxVERTICAL),  
 
59
    Label = wxStaticText:new(Win, ?wxID_ANY, "Module:"),
 
60
    Int = int:interpreted(),
 
61
    IntStrs = [atom_to_list(M) || M <- Int],
 
62
    Text  = wxComboBox:new(Win, ?wxID_ANY, 
 
63
                           [{value, dbg_wx_win:to_string(Mod)}, 
 
64
                            {choices, IntStrs}]),
 
65
    
 
66
    Expand = [{border, 5}, {flag,?wxLEFT bor ?wxRIGHT bor ?wxEXPAND}],
 
67
    wxSizer:add(MainS, Label, [{border,5},
 
68
                               {flag,?wxTOP bor ?wxLEFT bor ?wxRIGHT}]),
 
69
    wxSizer:add(MainS, Text, Expand),
 
70
    FunLabel = wxStaticText:new(Win, ?wxID_ANY, "Function:"),
 
71
    LB = wxListBox:new(Win, ?wxID_ANY, [{size,{-1, 100}},{style,?wxLB_MULTIPLE}]),
 
72
    wxSizer:add(MainS, FunLabel, Expand),
 
73
    wxSizer:add(MainS, LB, [{proportion,1}|Expand]),
 
74
    wxSizer:setMinSize(MainS, 300, 400),
 
75
    OK = wxDialog:createStdDialogButtonSizer(Win, ?wxOK bor ?wxCANCEL),
 
76
    wxSizer:add(MainS, OK, [{border,5},{flag,?wxALL}]),
 
77
    wxDialog:setSizer(Win,MainS),
 
78
    wxSizer:fit(MainS, Win),
 
79
    wxSizer:setSizeHints(MainS,Win),
 
80
    wxComboBox:setFocus(Text),
 
81
    wxDialog:connect(Win,    command_button_clicked),
 
82
    wxComboBox:connect(Text, command_text_updated),
 
83
    wxListBox:connect(LB, command_listbox_selected),
 
84
    wxListBox:connect(LB, command_listbox_doubleclicked),
 
85
    OkId   = wxDialog:getAffirmativeId(Win),
 
86
    OKButt = wxWindow:findWindowById(OkId, [{parent, Win}]),
 
87
    wxWindow:disable(OKButt),
 
88
    wxDialog:centreOnParent(Win),
 
89
    wxDialog:show(Win),
 
90
 
 
91
    #winInfo{type=function, win=Win, text=Text, ok=OKButt,
 
92
             entries=[], trigger=enable,
 
93
             listbox=LB, funcs=[]};
 
94
 
 
95
create_win(Parent, Pos, Type, Mod, Line) ->
 
96
    Title = case Type of
 
97
                line -> "Line Break";
 
98
                conditional -> "Conditional Break"
 
99
            end,
 
100
    Style = ?wxDEFAULT_DIALOG_STYLE bor ?wxRESIZE_BORDER,
 
101
    Win = wxDialog:new(Parent, ?wxID_ANY, Title,
 
102
                       [{pos, Pos}, 
 
103
                        {style, Style}]),
 
104
    %% Create Sizers
 
105
    MainS = wxBoxSizer:new(?wxVERTICAL),      
 
106
    
 
107
    %% Add module
 
108
    Int = int:interpreted(),
 
109
    IntStrs = [atom_to_list(M) || M <- Int],
 
110
    ModT  = wxComboBox:new(Win, ?wxID_ANY, [{choices,IntStrs}]),
 
111
    ModSz = create_label_of_control(Win, "Module:", ModT, Mod),
 
112
    wxSizer:add(MainS,ModSz,[{flag, ?wxEXPAND}]),
 
113
    %% Create rest of text input fields
 
114
    Add = fun({IType, Label, Def}) ->
 
115
                  {Sz, Text} = create_sizer_with_text(Win, Label, Def),
 
116
                  wxSizer:add(MainS, Sz, [{flag, ?wxEXPAND}]),
 
117
                  {Text, IType}
 
118
          end,
 
119
    Inputs = case Type of
 
120
                 line ->
 
121
                     [{integer,"Line:",Line}];
 
122
                 conditional ->
 
123
                     [{integer,"Line:",Line},
 
124
                      {atom,"C-Module:",""}, 
 
125
                      {atom,"C-Function:",""}]
 
126
             end,    
 
127
    %% Add the rest of the entries
 
128
    Entries = wx:map(Add, Inputs),    
 
129
    %% Create and add radio box
 
130
    {TriggerBox,Trigger} = create_trigger_box(Win),
 
131
    wxSizer:add(MainS, TriggerBox, [{border,5},{flag,?wxALL bor ?wxEXPAND}]),
 
132
 
 
133
    wxSizer:addStretchSpacer(MainS),
 
134
    %% Put it together
 
135
    OK = wxDialog:createStdDialogButtonSizer(Win, ?wxOK bor ?wxCANCEL),
 
136
    wxSizer:add(MainS, OK, [{border,5},{flag,?wxALL}]),
 
137
    wxSizer:setMinSize(MainS, 300, -1),
 
138
    wxDialog:setSizer(Win,MainS),
 
139
    wxSizer:fit(MainS, Win),
 
140
    wxSizer:setSizeHints(MainS,Win),
 
141
    wxComboBox:setFocus(ModT),
 
142
    wxDialog:connect(Win, command_button_clicked),
 
143
    wxDialog:connect(Win, command_text_updated),
 
144
    OkId   = wxDialog:getAffirmativeId(Win),
 
145
    OKButt = wxWindow:findWindowById(OkId),
 
146
    wxWindow:disable(OKButt),
 
147
    wxDialog:centreOnParent(Win),
 
148
    wxDialog:show(Win),
 
149
    #winInfo{type=Type, win=Win, text=ModT, 
 
150
             entries=Entries, trigger=Trigger, ok=OKButt}.
 
151
    
 
152
%%--------------------------------------------------------------------
 
153
%% update_functions(WinInfo, Funcs) -> WinInfo
 
154
%%   WinInfo = #winInfo{}
 
155
%%   Funcs = [{Name, Arity}]
 
156
%%     Name = atom()
 
157
%%     Arity = integer()
 
158
%%--------------------------------------------------------------------
 
159
update_functions(WinInfo, Funcs) ->
 
160
    Items = lists:map(fun([N, A]) -> 
 
161
                              lists:flatten(io_lib:format("~p/~p", [N,A]))
 
162
                      end,
 
163
                      Funcs),
 
164
    wxListBox:set(WinInfo#winInfo.listbox, Items),
 
165
    WinInfo#winInfo{funcs=Funcs}.
 
166
 
 
167
%%--------------------------------------------------------------------
 
168
%% handle_event(WxEvent, WinInfo) -> Command
 
169
%% WxEvent = #wx{}
 
170
%% WinInfo = #winInfo{}
 
171
%% Command = ignore
 
172
%%         | stopped
 
173
%%         | {win, WinInfo}
 
174
%%         | {module, Mod}
 
175
%%         | {break, [[Mod, Line]], Action}
 
176
%%         | {break, [[Mod, Line, CMod, CFunc]], Action}
 
177
%%         | {break, [[Mod, Func, Arity]], Action}
 
178
%%--------------------------------------------------------------------
 
179
handle_event(#wx{id=?wxID_CANCEL}, #winInfo{win=Win}) ->
 
180
    wxDialog:destroy(Win),
 
181
    stopped;
 
182
handle_event(#wx{event=#wxCommand{type=command_text_updated}}, 
 
183
             #winInfo{type=function, text=Text, ok=Ok}) ->
 
184
    Module = wxComboBox:getValue(Text),
 
185
    wxWindow:disable(Ok),
 
186
    {module, list_to_atom(Module)};
 
187
handle_event(#wx{event=#wxCommand{type=command_text_updated}}, 
 
188
             #winInfo{text=Text, ok=Ok, entries=Es}) ->
 
189
    Module = wxComboBox:getValue(Text),
 
190
    case check_input(Es) of
 
191
        error -> wxWindow:disable(Ok);
 
192
        _Data when Module =/= "" -> wxWindow:enable(Ok);
 
193
        _ -> wxWindow:disable(Ok)
 
194
    end,
 
195
    ignore;
 
196
handle_event(#wx{event=#wxCommand{type=command_listbox_selected}}, 
 
197
             #winInfo{type=function, listbox=LB, ok=Ok}) ->
 
198
    case wxListBox:getSelections(LB) of
 
199
        {N,_} when N > 0 -> wxWindow:enable(Ok);
 
200
        _ -> wxWindow:disable(Ok)
 
201
    end,
 
202
    ignore;
 
203
handle_event(#wx{id=OKorListBox, event=#wxCommand{type=OkorDoubleClick}},
 
204
             #winInfo{type=function,win=Win,listbox=LB,funcs=Funcs,text=Text})
 
205
  when OKorListBox =:= ?wxID_OK; 
 
206
       OkorDoubleClick =:= command_listbox_doubleclicked ->
 
207
    Mod = wxComboBox:getValue(Text),
 
208
    {_, IndexL} = wxListBox:getSelections(LB),
 
209
    Breaks = lists:map(fun(Index) ->
 
210
                               Func = lists:nth(Index+1, Funcs),
 
211
                               [list_to_atom(Mod) | Func]
 
212
                       end,
 
213
                       IndexL),
 
214
    wxDialog:destroy(Win),
 
215
    {break, Breaks, enable};
 
216
handle_event(#wx{id=?wxID_OK},#winInfo{win=Win,text=Text, entries=Es, trigger=Trigger}) ->
 
217
    %% Non function box
 
218
    Mod = wxComboBox:getValue(Text),
 
219
    Data = check_input(Es),
 
220
    Trigged = get_trigger(Trigger),
 
221
    wxDialog:destroy(Win),    
 
222
    {break, [[list_to_atom(Mod)|Data]], Trigged};
 
223
 
 
224
handle_event(_WxEvent, _WinInfo) ->
 
225
    %% io:format("Ev: ~p ~n", [_WxEvent]),
 
226
    ignore.
 
227
 
 
228
check_input(Entries) ->
 
229
    check_input(Entries, []).
 
230
check_input([{Entry, Type} | Entries], Data) ->
 
231
    Str = wxTextCtrl:getValue(Entry),
 
232
    case erl_scan:string(Str) of
 
233
        {ok, [{Type, _Line, Val}], _EndLine} ->
 
234
            check_input(Entries, [Val|Data]);
 
235
        _Error -> error
 
236
    end;
 
237
check_input([], Data) -> lists:reverse(Data).
 
238
 
 
239
create_sizer_with_text(Parent,Label,Def) ->    
 
240
    Text  = wxTextCtrl:new(Parent, ?wxID_ANY), 
 
241
    Sz = create_label_of_control(Parent, Label, Text, Def),
 
242
    {Sz, Text}.
 
243
 
 
244
create_label_of_control(Parent, Label, Control, Def) ->
 
245
    Sizer = wxBoxSizer:new(?wxHORIZONTAL),
 
246
    Text  = wxStaticText:new(Parent, ?wxID_ANY, Label),
 
247
    Border = {border, 5},
 
248
    Flag   = ?wxRIGHT bor ?wxLEFT bor ?wxALIGN_CENTRE_VERTICAL,
 
249
    wxSizer:add(Sizer, Text, [{proportion,1}, {flag,Flag}, Border]),
 
250
    wxSizer:add(Sizer, Control, [{proportion,3}, {flag,Flag bor ?wxEXPAND}, Border]),
 
251
    wxControl:setLabel(Control, dbg_wx_win:to_string(Def)),
 
252
    Sizer.
 
253
    
 
254
create_trigger_box(Win) ->
 
255
    SBox = wxStaticBox:new(Win, ?wxID_ANY, "Trigger Action:"),
 
256
    SBS  = wxStaticBoxSizer:new(SBox, ?wxVERTICAL),
 
257
    Ebtn = wxRadioButton:new(Win, ?wxID_ANY, "Enable"),
 
258
    wxSizer:add(SBS,Ebtn),
 
259
    Dibtn = wxRadioButton:new(Win, ?wxID_ANY, "Disable"),
 
260
    wxSizer:add(SBS,Dibtn),
 
261
    Debtn = wxRadioButton:new(Win, ?wxID_ANY, "Delete"),
 
262
    wxSizer:add(SBS,Debtn),
 
263
    wxRadioButton:setValue(Ebtn, true),
 
264
    {SBS, [{Ebtn,enable},{Dibtn,disable},{Debtn,delete}]}.
 
265
 
 
266
get_trigger([{Btn,Op}|R]) ->
 
267
    case wxRadioButton:getValue(Btn) of
 
268
        true -> Op;
 
269
        false -> get_trigger(R)
 
270
    end.
 
271
             
 
272