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

« back to all changes in this revision

Viewing changes to lib/wx/examples/xrc/xrc.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 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
%%% Description : Testing and demo xrc's
 
20
%%%               This mimics the xrc demo from wxwidgets.
 
21
%%% Created :  4 Dec 2007 by Dan Gudmundsson <dgud@erix.ericsson.se>
 
22
%%%-------------------------------------------------------------------
 
23
 
 
24
-module(xrc).
 
25
-compile(export_all).
 
26
 
 
27
-include("../../include/wx.hrl").
 
28
 
 
29
 
 
30
%% I've put all "classes" in the same file,  but you can see the follow
 
31
%% the code in xrcdemo from the samples directory in wxWidgets src package
 
32
 
 
33
start() ->
 
34
    %% Starts wxwidgets
 
35
    WX = wx:new(),
 
36
    %% In erlang wx, all image handlers are initilized already.
 
37
    %% wxImage::AddHandler(new wxXPMHandler);
 
38
    
 
39
    %% Initialize all the XRC handlers. Always required (unless you feel like
 
40
    %% going through and initializing a handler of each control type you will
 
41
    %% be using (ie initialize the spinctrl handler, initialize the textctrl
 
42
    %% handler). However, if you are only using a few control types, it will
 
43
    %% save some space to only initialize the ones you will be using. See
 
44
    %% wxXRC docs for details.
 
45
 
 
46
    Xrc = wxXmlResource:get(),
 
47
    wxXmlResource:initAllHandlers(Xrc),
 
48
    true = wxXmlResource:load(Xrc, rc_dir("menu.xrc")),
 
49
    true = wxXmlResource:load(Xrc, rc_dir("toolbar.xrc")),
 
50
    true = wxXmlResource:load(Xrc, rc_dir("basicdlg.xrc")),
 
51
    true = wxXmlResource:load(Xrc, rc_dir("derivdlg.xrc")),
 
52
    true = wxXmlResource:load(Xrc, rc_dir("controls.xrc")),
 
53
    true = wxXmlResource:load(Xrc, rc_dir("frame.xrc")),
 
54
    true = wxXmlResource:load(Xrc, rc_dir("uncenter.xrc")),
 
55
    true = wxXmlResource:load(Xrc, rc_dir("custclas.xrc")),
 
56
    true = wxXmlResource:load(Xrc, rc_dir("artprov.xrc")),
 
57
    true = wxXmlResource:load(Xrc, rc_dir("platform.xrc")),
 
58
    true = wxXmlResource:load(Xrc, rc_dir("variable.xrc")),
 
59
    Frame = wxFrame:new(),
 
60
    myframe(WX,Frame),
 
61
    wxFrame:show(Frame),
 
62
    loop(Frame),
 
63
    wx:destroy().
 
64
 
 
65
rc_dir(File) ->
 
66
  SelfDir = filename:dirname(code:which(?MODULE)),
 
67
  filename:join([SelfDir,rc,File]).
 
68
 
 
69
loop(Frame) ->
 
70
    receive 
 
71
        #wx{id=Id, event=#wxCommand{}} ->
 
72
            handle_cmd(get(Id), Id, Frame),
 
73
            loop(Frame);
 
74
        #wx{event=#wxClose{}} ->
 
75
            catch wxWindows:'Destroy'(Frame),
 
76
            ok;
 
77
        Ev = #wx{} ->
 
78
            io:format("Got ~p ~n", [Ev]),
 
79
            loop(Frame)
 
80
    end.
 
81
 
 
82
myframe(Parent, Frame) ->
 
83
    Xrc = wxXmlResource:get(),
 
84
    wxXmlResource:loadFrame(Xrc, Frame, Parent, "main_frame"),
 
85
    %% wxTopLevelWindow:setIcon(Frame, wxXmlResource:loadIcon(Xrc,"appicon")),
 
86
    %% Load and setup menubar
 
87
    wxFrame:setMenuBar(Frame, wxXmlResource:loadMenuBar(Xrc, "main_menu")),
 
88
    %% hmm wxSystemOptions::SetOption ( wxT("msw.remap"), 0 );
 
89
    wxFrame:setToolBar(Frame, wxXmlResource:loadToolBar(Xrc, Frame, "main_toolbar")),
 
90
    wxFrame:createStatusBar(Frame, [{number,1}]),
 
91
    ok = wxFrame:connect(Frame, close_window), 
 
92
    connect(Frame).
 
93
  
 
94
connect(Frame) ->    
 
95
    Menues = [unload_resource_menuitem, reload_resource_menuitem,
 
96
              non_derived_dialog_tool_or_menuitem, derived_tool_or_menuitem,
 
97
              controls_tool_or_menuitem, uncentered_tool_or_menuitem,
 
98
              custom_class_tool_or_menuitem, platform_property_tool_or_menuitem,
 
99
              art_provider_tool_or_menuitem, variable_expansion_tool_or_menuitem
 
100
             ],
 
101
    wxFrame:connect(Frame,command_menu_selected, [{id, ?wxID_EXIT}]),
 
102
    wxFrame:connect(Frame,command_menu_selected, [{id, ?wxID_ABOUT}]),
 
103
    [connect_xrcid(Str,Frame) || Str <- Menues],
 
104
    ok.
 
105
 
 
106
connect_xrcid(Name,Frame) ->
 
107
    ID = wxXmlResource:getXRCID(atom_to_list(Name)),
 
108
    put(ID, Name),
 
109
    wxFrame:connect(Frame,command_menu_selected,[{id,ID}]).
 
110
 
 
111
%% Handle commands
 
112
    
 
113
handle_cmd(unload_resource_menuitem, _, _Frame) ->
 
114
    Xrc = wxXmlResource:get(),
 
115
    case wxXmlResource:unload(Xrc, "rc/basicdlg") of
 
116
        true -> 
 
117
            io:format("Basic dialog unloaded~n",[]);
 
118
        false ->
 
119
            io:format("Failed to unload basic dialog~n",[])
 
120
    end;
 
121
 
 
122
handle_cmd(reload_resource_menuitem, _, _Frame) ->
 
123
    Xrc = wxXmlResource:get(),
 
124
    case wxXmlResource:reload(Xrc, "rc/basicdlg") of
 
125
        true -> 
 
126
            io:format("Basic dialog reloaded~n",[]);
 
127
        false ->
 
128
            io:format("Failed to reload basic dialog~n",[])
 
129
    end;
 
130
 
 
131
handle_cmd(_, ?wxID_EXIT, Frame) ->
 
132
    wxFrame:close(Frame);
 
133
 
 
134
handle_cmd(non_derived_dialog_tool_or_menuitem, _, Frame) ->
 
135
    Xrc = wxXmlResource:get(),
 
136
    Dlg = wxDialog:new(),
 
137
    %% "non_derived_dialog" is the name of the wxDialog XRC node that should
 
138
    %% be loaded.
 
139
    case wxXmlResource:loadDialog(Xrc, Dlg, Frame, "non_derived_dialog") of
 
140
        true ->
 
141
            wxDialog:showModal(Dlg);
 
142
        false ->
 
143
            io:format("Failed to load non_derived_dialog~n",[])
 
144
    end,    
 
145
    %% In Erlang you should delete the dialog afterwards
 
146
    wxDialog:destroy(Dlg);
 
147
 
 
148
handle_cmd(derived_tool_or_menuitem, _, Frame) ->
 
149
    Pref = prefDialog(Frame),
 
150
    wxDialog:showModal(Pref);
 
151
 
 
152
handle_cmd(animation_ctrl_play, _, _Frame) ->
 
153
    %% Not yet implemented
 
154
    ok;
 
155
 
 
156
handle_cmd(controls_tool_or_menuitem,_,Frame) ->
 
157
    Xrc = wxXmlResource:get(),
 
158
    Dlg = wxDialog:new(),
 
159
    true = wxXmlResource:loadDialog(Xrc, Dlg, Frame, "controls_dialog"),
 
160
    
 
161
    LCtrl = wxXmlResource:xrcctrl(Dlg, "controls_listctrl", wxListCtrl),
 
162
    wxListCtrl:insertColumn(LCtrl, 0, "Name", [{width, 200}]), 
 
163
    wxListCtrl:insertItem(LCtrl, 0, "Todd Hope"),
 
164
    wxListCtrl:insertItem(LCtrl, 1, "Kim Wynd"),
 
165
    wxListCtrl:insertItem(LCtrl, 2, "Leon Li"),
 
166
 
 
167
    TCtrl = wxXmlResource:xrcctrl(Dlg, "controls_treectrl", wxTreeCtrl),
 
168
    wxTreeCtrl:addRoot(TCtrl, "Godfather"),
 
169
    TRoot = wxTreeCtrl:getRootItem(TCtrl),
 
170
    wxTreeCtrl:appendItem(TCtrl,TRoot, "Evil henchmen 1"), 
 
171
    wxTreeCtrl:appendItem(TCtrl,TRoot, "Evil henchmen 2"), 
 
172
    wxTreeCtrl:appendItem(TCtrl,TRoot, "Evil accountant"), 
 
173
 
 
174
    wxDialog:showModal(Dlg),
 
175
    wxDialog:destroy(Dlg);
 
176
 
 
177
handle_cmd(uncentered_tool_or_menuitem,_,Frame) ->
 
178
    Xrc = wxXmlResource:get(),
 
179
    Dlg = wxDialog:new(),
 
180
    true = wxXmlResource:loadDialog(Xrc, Dlg, Frame, "uncentered_dialog"),
 
181
    wxDialog:showModal(Dlg),
 
182
    wxDialog:destroy(Dlg);
 
183
 
 
184
handle_cmd(custom_class_tool_or_menuitem,_,Frame) ->
 
185
    Xrc = wxXmlResource:get(),
 
186
    Dlg = wxDialog:new(),
 
187
    true = wxXmlResource:loadDialog(Xrc, Dlg, Frame, "custom_class_dialog"),
 
188
 
 
189
    ResizeableLC = myResizeableListCtrl(Dlg, ?wxID_ANY, {-1,-1}, {-1,-1},?wxLC_REPORT),
 
190
    %% "custom_control_placeholder" is the name of the "unknown" tag in the
 
191
    %% custctrl.xrc XRC file.
 
192
    wxXmlResource:attachUnknownControl(Xrc, "custom_control_placeholder", ResizeableLC),
 
193
    wxDialog:showModal(Dlg),
 
194
    wxDialog:destroy(Dlg);
 
195
 
 
196
handle_cmd(platform_property_tool_or_menuitem, _, Frame) ->
 
197
    Xrc = wxXmlResource:get(),
 
198
    Dlg = wxDialog:new(),
 
199
    true = wxXmlResource:loadDialog(Xrc, Dlg, Frame, "platform_property_dialog"),
 
200
    wxDialog:showModal(Dlg),
 
201
    wxDialog:destroy(Dlg);
 
202
 
 
203
handle_cmd(art_provider_tool_or_menuitem, _, Frame) ->
 
204
    Xrc = wxXmlResource:get(),
 
205
    Dlg = wxDialog:new(),
 
206
    true = wxXmlResource:loadDialog(Xrc, Dlg, Frame, "art_provider_dialog"),
 
207
    wxDialog:showModal(Dlg),
 
208
    wxDialog:destroy(Dlg);
 
209
 
 
210
handle_cmd(variable_expansion_tool_or_menuitem, _, Frame) ->
 
211
    Xrc = wxXmlResource:get(),
 
212
    Dlg = wxDialog:new(),
 
213
    true = wxXmlResource:loadDialog(Xrc, Dlg, Frame, "variable_expansion_dialog"),
 
214
    wxDialog:showModal(Dlg),
 
215
    wxDialog:destroy(Dlg);
 
216
handle_cmd(_, ?wxID_ABOUT, Frame) ->
 
217
    Msg = "This is the about dialog of XML resources demo.\n",
 
218
    MD = wxMessageDialog:new(Frame,Msg,
 
219
                             [{style, ?wxOK bor ?wxICON_INFORMATION}, 
 
220
                              {caption, "About"}]),
 
221
    wxDialog:showModal(MD),
 
222
    wxDialog:destroy(MD);
 
223
handle_cmd(Dialog, Id, _) ->
 
224
    io:format("Not implemented yet ~p (~p) ~n",[Dialog, Id]).
 
225
   
 
226
 
 
227
%%%%%%%%%%%%%%%%
 
228
%% Trying to mimic the derived dialog example
 
229
%%%%%%%%%%%%%%%%
 
230
 
 
231
prefDialog(Parent) ->    
 
232
    Xrc = wxXmlResource:get(),
 
233
    Dlg = wxDialog:new(),
 
234
    true = wxXmlResource:loadDialog(Xrc, Dlg, Parent, "derived_dialog"),
 
235
 
 
236
    %% Shows that callbacks can be used it doesn't need to though.
 
237
    OnMyButtonClicked = fun(_EvRec, _wxEvent) ->
 
238
                                MD = wxMessageDialog:new(Dlg, "You clicked on My Button"),
 
239
                                wxMessageDialog:showModal(MD),
 
240
                                wxMessageDialog:destroy(MD)
 
241
                        end,
 
242
    wxDialog:connect(Dlg, command_button_clicked, 
 
243
                     [{id,wxXmlResource:getXRCID("my_button")},
 
244
                      {callback,OnMyButtonClicked}]),
 
245
 
 
246
    OnMyCheckBox = fun(_EvRec, _Event) ->
 
247
                           CheckB = wxXmlResource:xrcctrl(Dlg, "my_checkbox", wxCheckBox),
 
248
                           Text = wxXmlResource:xrcctrl(Dlg, "my_textctrl", wxTextCtrl),
 
249
                           Bool = wxCheckBox:isChecked(CheckB),
 
250
                           wxTextCtrl:enable(Text, [{enable,Bool}])
 
251
                   end,
 
252
    wxDialog:connect(Dlg,update_ui,[{id,wxXmlResource:getXRCID("my_checkbox")},
 
253
                                    {callback,OnMyCheckBox}]),
 
254
    
 
255
    OnOk = fun(_,_) ->
 
256
                   Str = 
 
257
                       "Press Ok to close derived dialog, or Cancel to abort"
 
258
                       "Overriding base class ok button handler",
 
259
                   MD = wxMessageDialog:new(Dlg, Str, [{style, ?wxOK bor ?wxCANCEL bor ?wxCENTER}]),
 
260
                   case wxMessageDialog:showModal(MD) of
 
261
                       ?wxID_OK -> 
 
262
                           wxMessageDialog:endModal(Dlg, ?wxID_OK);
 
263
                       _R ->
 
264
                           ignore
 
265
                   end,
 
266
                   wxMessageDialog:destroy(MD)
 
267
           end,
 
268
    wxDialog:connect(Dlg,command_button_clicked,[{id,?wxID_OK},{callback,OnOk}]),
 
269
    Dlg.
 
270
 
 
271
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
272
 
 
273
-define(RECORD_COLUMN,  0).
 
274
-define(ACTION_COLUMN,  1).
 
275
-define(PRIORITY_COLUMN,2).
 
276
 
 
277
-define(PU_ADD_RECORD,     ?wxID_HIGHEST+1).
 
278
-define(PU_EDIT_RECORD,    ?wxID_HIGHEST+2).
 
279
-define(PU_DELETE_RECORD,  ?wxID_HIGHEST+3).
 
280
 
 
281
myResizeableListCtrl(Parent,Id,Pos,Size,Style) -> 
 
282
    LC = wxListCtrl:new(Parent, [{winid,Id}, {pos,Pos}, {size,Size}, {style,Style}]),
 
283
    wxListCtrl:insertColumn(LC,?RECORD_COLUMN, "Record", [{width, 140}]),
 
284
    wxListCtrl:insertColumn(LC,?ACTION_COLUMN, "Action", [{width, 70}]),
 
285
    wxListCtrl:insertColumn(LC,?PRIORITY_COLUMN, "Priority", [{width, 70}]),
 
286
    wxListCtrl:connect(LC, right_down, [{id,Id}, {callback, fun lc_onRightClick/2}]),
 
287
    wxListCtrl:connect(LC, size, [{id,Id}, {callback, fun lc_onSize/2}]),
 
288
    LC.
 
289
    
 
290
lc_onRightClick(#wx{obj=ListCtrl, event=#wxMouse{x=X,y=Y}},_Ev) ->
 
291
    Menu = wxMenu:new(),
 
292
    wxMenu:append(Menu, ?PU_ADD_RECORD, "Add a new record"),
 
293
    wxMenu:append(Menu, ?PU_EDIT_RECORD,"Edit selected record"),
 
294
    wxMenu:append(Menu, ?PU_DELETE_RECORD, "Delete selected record"),
 
295
    case wxListCtrl:getSelectedItemCount(ListCtrl) of
 
296
        0 ->
 
297
            wxMenu:enable(Menu, ?PU_EDIT_RECORD, false),
 
298
            wxMenu:enable(Menu, ?PU_DELETE_RECORD, false);
 
299
        _ ->
 
300
            ignore
 
301
    end,
 
302
    MenuCB = fun(_,_) -> io:format("Menu selected~n",[]) end,
 
303
    wxWindow:connect(ListCtrl, command_menu_selected, [{callback, MenuCB}]),
 
304
    wxWindow:popupMenu(ListCtrl, Menu, [{pos, {X,Y}}]),
 
305
    wxMenu:destroy(Menu).
 
306
    
 
307
lc_onSize(#wx{obj=ListCtrl},EvObj) ->
 
308
    {LeftMostColW0,_} = wxListCtrl:getSize(ListCtrl),
 
309
    LeftMostColW1 = LeftMostColW0 - wxListCtrl:getColumnWidth(ListCtrl, ?ACTION_COLUMN),
 
310
    LeftMostColW2 = LeftMostColW1 - wxListCtrl:getColumnWidth(ListCtrl, ?PRIORITY_COLUMN),
 
311
    %% Hmm missing wxSystemSettings::GetMetric( wxSYS_VSCROLL_X );
 
312
    LeftMostColW = LeftMostColW2 - 5,  
 
313
    wxListCtrl:setColumnWidth(ListCtrl, ?RECORD_COLUMN, LeftMostColW),
 
314
    %% REQURED event.Skip() call to allow this event to propagate
 
315
    %% upwards so others can do what they need to do in response to
 
316
    %% this size event.
 
317
    wxEvent:skip(EvObj),
 
318
    io:format("Successfully set column width~n").
 
319
 
 
320
%%%%%