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

« back to all changes in this revision

Viewing changes to lib/wx/test/wx_event_SUITE.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
%%% File    : wx_event_SUITE.erl
 
20
%%% Author  : Dan Gudmundsson <dan.gudmundsson@ericsson.com>
 
21
%%% Description : Test event handling as much as possible
 
22
%%% Created :  3 Nov 2008 by Dan Gudmundsson <dan.gudmundsson@ericsson.com>
 
23
%%%-------------------------------------------------------------------
 
24
-module(wx_event_SUITE).
 
25
-export([all/0, init_per_suite/1, end_per_suite/1, 
 
26
         init_per_testcase/2, fin_per_testcase/2, end_per_testcase/2]).
 
27
 
 
28
-compile(export_all).
 
29
 
 
30
-include("wx_test_lib.hrl").
 
31
 
 
32
%% Initialization functions.
 
33
init_per_suite(Config) ->
 
34
    wx_test_lib:init_per_suite(Config).
 
35
 
 
36
end_per_suite(Config) ->
 
37
    wx_test_lib:end_per_suite(Config).
 
38
 
 
39
init_per_testcase(Func,Config) ->
 
40
    wx_test_lib:init_per_testcase(Func,Config).
 
41
end_per_testcase(Func,Config) -> 
 
42
    wx_test_lib:end_per_testcase(Func,Config).
 
43
fin_per_testcase(Func,Config) -> %% For test_server
 
44
    wx_test_lib:end_per_testcase(Func,Config).
 
45
 
 
46
%% SUITE specification
 
47
all() ->
 
48
    all(suite).
 
49
all(suite) ->
 
50
    [
 
51
     connect,
 
52
     disconnect,
 
53
     connect_msg_20,
 
54
     connect_cb_20,
 
55
     mouse_on_grid,
 
56
     spin_event,
 
57
     connect_in_callback
 
58
    ].
 
59
  
 
60
%% The test cases
 
61
 
 
62
%% Test that the various options to connect work as expected.
 
63
connect(TestInfo) when is_atom(TestInfo) -> wx_test_lib:tc_info(TestInfo);
 
64
connect(Config) ->
 
65
    ?mr(wx_ref, wx:new()),
 
66
    Frame = ?mt(wxFrame, wxFrame:new(wx:null(), 1, "Event Testing")),
 
67
    Panel = ?mt(wxPanel, wxPanel:new(Frame)),
 
68
    Window = wxWindow:new(Panel, -1),
 
69
 
 
70
    Tester = self(),
 
71
    CB = fun(#wx{event=#wxSize{},userData=UserD}, SizeEvent) ->
 
72
                 ?mt(wxSizeEvent, SizeEvent),
 
73
                 Tester ! {got_size, UserD}
 
74
         end,
 
75
    
 
76
    ?m(ok, wxFrame:connect(Frame,  size)),
 
77
    ?m(ok, wxEvtHandler:connect(Panel, size,[{skip, true},{userData, panel}])),
 
78
    ?m(ok, wxEvtHandler:connect(Panel, size,[{callback,CB},{userData, panel}])),
 
79
 
 
80
    ?m({'EXIT', {{badarg,_},_}}, 
 
81
       wxEvtHandler:connect(Panel, there_is_no_such_event)),
 
82
 
 
83
    ?m({'EXIT', {{badarg,_},_}}, 
 
84
       wxEvtHandler:connect(Panel, there_is_no_such_event, [{callback,CB}])),
 
85
 
 
86
    ?m(ok, wxWindow:connect(Window, size,[{callback,CB},{userData, window}])),
 
87
    ?m(ok, wxWindow:connect(Window, size,[{skip,true},{userData, window}])),
 
88
 
 
89
    ?m(true, wxFrame:show(Frame)),
 
90
 
 
91
    wxWindow:setSize(Panel, {200,100}),
 
92
    wxWindow:setSize(Window, {200,100}),
 
93
 
 
94
    get_size_messages(Frame, [frame, panel_cb, window_cb, window]),
 
95
    
 
96
    wx_test_lib:wx_destroy(Frame, Config).
 
97
 
 
98
get_size_messages(_, []) -> ok;    
 
99
get_size_messages(Frame, Msgs) ->
 
100
    receive 
 
101
        #wx{obj=Frame,event=#wxSize{}} ->  %% ok
 
102
            get_size_messages(Frame, lists:delete(frame, Msgs));
 
103
        #wx{userData=window, event=#wxSize{}} ->
 
104
            ?m(true, lists:member(window_cb, Msgs)),       
 
105
            get_size_messages(Frame, lists:delete(window, Msgs));
 
106
        #wx{userData=panel, event=#wxSize{}} ->
 
107
            ?m(true, lists:member(panel, Msgs)),           
 
108
            get_size_messages(Frame, lists:delete(panel, Msgs));
 
109
        {got_size,window} ->
 
110
            ?m(false, lists:member(window, Msgs)),
 
111
            get_size_messages(Frame, lists:delete(window_cb, Msgs));
 
112
        {got_size,panel} -> 
 
113
            get_size_messages(Frame, lists:delete(panel_cb, Msgs));     
 
114
        Other ->
 
115
            ?error("Got unexpected msg ~p ~p~n", [Other,Msgs])
 
116
    after 1000 ->
 
117
            ?error("Timeout ~p~n", [Msgs])
 
118
    end.
 
119
 
 
120
disconnect(TestInfo) when is_atom(TestInfo) -> wx_test_lib:tc_info(TestInfo);
 
121
disconnect(Config) ->
 
122
    ?mr(wx_ref, wx:new()),
 
123
    Frame = ?mt(wxFrame, wxFrame:new(wx:null(), 1, "Event Testing")),
 
124
    Panel = ?mt(wxPanel, wxPanel:new(Frame)),
 
125
 
 
126
    Tester = self(),
 
127
    CB = fun(#wx{event=#wxSize{},userData=UserD}, SizeEvent) ->
 
128
                 ?mt(wxSizeEvent, SizeEvent),
 
129
                 Tester ! {got_size, UserD}
 
130
         end,
 
131
    ?m(ok, wxFrame:connect(Frame,  close_window)),
 
132
    ?m(ok, wxFrame:connect(Frame,  size)),
 
133
    ?m(ok, wxEvtHandler:connect(Panel, size,[{skip, true},{userData, panel}])),
 
134
    ?m(ok, wxEvtHandler:connect(Panel, size,[{callback,CB},{userData, panel}])),
 
135
 
 
136
    ?m(true, wxFrame:show(Frame)),
 
137
 
 
138
    wxWindow:setSize(Panel, {200,100}),    
 
139
    get_size_messages(Frame, [frame, panel_cb]),
 
140
    wx_test_lib:flush(),
 
141
 
 
142
    ?m(true, wxEvtHandler:disconnect(Panel, size, [{callback,CB}])),
 
143
    ?m(ok, wxWindow:setSize(Panel, {200,101})),
 
144
    get_size_messages(Frame, [panel]),
 
145
    timer:sleep(1000),
 
146
    wx_test_lib:flush(),
 
147
 
 
148
    ?m({'EXIT', {{badarg,_},_}}, wxEvtHandler:disconnect(Panel, non_existing_event_type)),
 
149
    ?m(true, wxEvtHandler:disconnect(Panel, size)),
 
150
    ?m(ok, wxWindow:setSize(Panel, {200,102})),
 
151
    timer:sleep(1000),
 
152
    ?m([], wx_test_lib:flush()),
 
153
 
 
154
    wx_test_lib:wx_destroy(Frame, Config).
 
155
    
 
156
 
 
157
 
 
158
%% Test that the msg events are forwarded as supposed to 
 
159
connect_msg_20(TestInfo) 
 
160
  when is_atom(TestInfo) -> wx_test_lib:tc_info(TestInfo);
 
161
connect_msg_20(Config) ->
 
162
    ?mr(wx_ref, wx:new()),
 
163
    Frame = ?mt(wxFrame, wxFrame:new(wx:null(), 1, "Event 20 Testing")),
 
164
    Tester = self(),
 
165
    Env = wx:get_env(),
 
166
    
 
167
    EvtHandler = fun() ->
 
168
                         wx:set_env(Env),
 
169
                         wxFrame:connect(Frame,size,[{skip,true}]),
 
170
                         Tester ! initiated,
 
171
                         receive #wx{obj=Frame,event=#wxSize{}} ->
 
172
                                 Tester ! got_it
 
173
                         end
 
174
                 end,
 
175
    Msgs = [begin spawn_link(EvtHandler), got_it end|| _ <- lists:seq(1,20)],
 
176
 
 
177
    ?m_multi_receive(lists:duplicate(20, initiated)),    
 
178
    ?m(true, wxFrame:show(Frame)),
 
179
 
 
180
    ?m_multi_receive(Msgs),
 
181
    wx_test_lib:wx_destroy(Frame, Config).
 
182
 
 
183
%% Test that the callbacks works as msgs
 
184
connect_cb_20(TestInfo) 
 
185
  when is_atom(TestInfo) -> wx_test_lib:tc_info(TestInfo);
 
186
connect_cb_20(Config) ->
 
187
    ?mr(wx_ref, wx:new()),
 
188
    Frame = ?mt(wxFrame, wxFrame:new(wx:null(), 1, "Event 20 Testing")),
 
189
    Tester = self(),
 
190
    Env = wx:get_env(),
 
191
    
 
192
    wxFrame:connect(Frame,size,[{callback, 
 
193
                                 fun(#wx{event=#wxSize{}},_SizeEv) -> 
 
194
                                         Tester ! main_got_it
 
195
                                 end}]),
 
196
 
 
197
    EvtHandler = fun() ->
 
198
                         wx:set_env(Env),
 
199
                         Self = self(),
 
200
                         CB = fun(#wx{event=#wxSize{}}, 
 
201
                                  WxSizeEventObj) ->
 
202
                                      wxEvent:skip(WxSizeEventObj),
 
203
                                      Tester ! got_it,
 
204
                                      Self ! quit
 
205
                              end,
 
206
                         wxFrame:connect(Frame,size,[{callback, CB}]),
 
207
                         Tester ! initiated,
 
208
                         receive quit -> ok
 
209
                         end
 
210
                 end,
 
211
    Msgs = [begin spawn_link(EvtHandler), got_it end|| _ <- lists:seq(1,20)],
 
212
    
 
213
    ?m_multi_receive(lists:duplicate(20, initiated)),
 
214
    ?m(true, wxFrame:show(Frame)),
 
215
    
 
216
    ?m_multi_receive(Msgs),
 
217
    ?m_receive(main_got_it),
 
218
 
 
219
    wx_test_lib:wx_destroy(Frame, Config).
 
220
   
 
221
 
 
222
mouse_on_grid(TestInfo) 
 
223
  when is_atom(TestInfo) -> wx_test_lib:tc_info(TestInfo);
 
224
mouse_on_grid(Config) ->
 
225
    Wx = ?mr(wx_ref, wx:new()),
 
226
    
 
227
    Frame = wxFrame:new(Wx, ?wxID_ANY, "Frame"),
 
228
    Panel = wxPanel:new(Frame, []),
 
229
    Sizer = wxBoxSizer:new(?wxVERTICAL),
 
230
    
 
231
    Grid = wxGrid:new(Panel, ?wxID_ANY),
 
232
    wxGrid:createGrid(Grid, 10, 10, []),
 
233
    wxSizer:add(Sizer, Grid, [{proportion, 1}]),
 
234
        
 
235
    wxWindow:connect(Panel, motion),
 
236
    wxWindow:connect(Panel, middle_down), 
 
237
 
 
238
    %% Undocumented function
 
239
    GridWindow = ?mt(wxWindow, wxGrid:getGridWindow(Grid)),
 
240
    wxWindow:connect(GridWindow, motion),
 
241
    wxWindow:connect(GridWindow, middle_down),
 
242
 
 
243
    wxWindow:setSizerAndFit(Panel, Sizer),
 
244
    wxFrame:show(Frame),
 
245
    
 
246
    wx_test_lib:wx_destroy(Frame, Config).
 
247
 
 
248
 
 
249
spin_event(TestInfo) 
 
250
  when is_atom(TestInfo) -> wx_test_lib:tc_info(TestInfo);
 
251
spin_event(Config) ->
 
252
    Wx = ?mr(wx_ref, wx:new()),
 
253
 
 
254
    %% Spin events and scrollEvent share some events id's
 
255
    %% test that they work
 
256
 
 
257
    Frame = wxFrame:new(Wx, ?wxID_ANY, "Spin Events"),
 
258
    Panel = wxPanel:new(Frame, []),
 
259
    Sizer = wxBoxSizer:new(?wxVERTICAL),
 
260
    HSz = wxBoxSizer:new(?wxHORIZONTAL),
 
261
 
 
262
    SB = wxSpinButton:new(Panel, [{id, 100}]),
 
263
    wxSizer:add(HSz, SB, []),
 
264
    wxSpinButton:connect(SB, spin),
 
265
    wxSpinButton:connect(SB, spin_up),
 
266
    wxSpinButton:connect(SB, spin_down),
 
267
 
 
268
    SC = wxSpinCtrl:new(Panel, [{id, 101}, {min, -12}, {max, 12}, 
 
269
                                {value, "-3"}, {initial, 3}, 
 
270
                                {style, ?wxSP_ARROW_KEYS bor ?wxSP_WRAP}]),
 
271
    wxSpinCtrl:connect(SC, command_spinctrl_updated),
 
272
    wxSizer:add(HSz, SC, [{proportion, 1}, {flag, ?wxEXPAND}]),
 
273
    wxSizer:add(Sizer, HSz, [{proportion, 0},{flag, ?wxEXPAND}]),
 
274
    
 
275
    SL = wxSlider:new(Panel, 102, 57, 22, 99),
 
276
    wxSlider:connect(SL, scroll_thumbtrack),
 
277
    wxSlider:connect(SL, scroll_lineup),
 
278
    wxSlider:connect(SL, scroll_linedown),
 
279
    wxSizer:add(Sizer, SL, [{proportion, 0},{flag, ?wxEXPAND}]),
 
280
       
 
281
    wxWindow:setSizerAndFit(Panel, Sizer),
 
282
    wxFrame:show(Frame),
 
283
    wx_test_lib:flush(),
 
284
 
 
285
%% Set value does not generate a spin event...
 
286
%%     wxSpinButton:setValue(SB, 7),
 
287
%%     ?m_receive(#wx{id=100, event=#wxSpin{type=spin}}),
 
288
%%     wxSpinCtrl:setValue(SC, 8),
 
289
%%     ?m_receive(#wx{id=101, event=#wxSpin{type=command_spinctrl_updated}}),
 
290
%%     wxSlider:setValue(SL, 29),
 
291
%%     ?m_receive(#wx{id=102, event=#wxScroll{}}),
 
292
 
 
293
    wx_test_lib:wx_destroy(Frame, Config).
 
294
 
 
295
 
 
296
%% Test that we can connect to events from inside a callback fun
 
297
%% This is needed for example inside a callback that does a wxWindow:popupMenu/2
 
298
connect_in_callback(TestInfo) 
 
299
  when is_atom(TestInfo) -> wx_test_lib:tc_info(TestInfo);
 
300
connect_in_callback(Config) ->
 
301
    Wx = ?mr(wx_ref, wx:new()),
 
302
    Frame = wxFrame:new(Wx, ?wxID_ANY, "Connect in callback"),
 
303
    Panel = wxPanel:new(Frame, []),
 
304
    
 
305
    wxFrame:connect(Frame,size,
 
306
                    [{callback, 
 
307
                      fun(#wx{event=#wxSize{}},_SizeEv) -> 
 
308
                              io:format("Frame got size~n",[]),          
 
309
                              F1 = wxFrame:new(Frame, ?wxID_ANY, "Frame size event"),
 
310
                              CBPid = self(),
 
311
                              wxFrame:connect(F1,size,[{callback,
 
312
                                                        fun(_,_) ->
 
313
                                                                io:format("CB2 got size~n",[]),
 
314
                                                                CBPid ! continue
 
315
                                                        end}]),
 
316
                              wxWindow:show(F1),
 
317
                              receive continue -> wxFrame:destroy(F1) end
 
318
                      end}]),
 
319
    wxPanel:connect(Panel,size,
 
320
                    [{callback, 
 
321
                      fun(#wx{event=#wxSize{}},_SizeEv) -> 
 
322
                              io:format("Panel got size~n",[]),
 
323
                              F1 = wxFrame:new(Frame, ?wxID_ANY, "Panel size event"),
 
324
                              wxFrame:connect(F1,size),
 
325
                              wxWindow:show(F1),
 
326
                              receive #wx{event=#wxSize{}} -> wxFrame:destroy(F1) end
 
327
                      end}]),   
 
328
    wxFrame:show(Frame),
 
329
    wx_test_lib:flush(),
 
330
    
 
331
    wx_test_lib:wx_destroy(Frame, Config).