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

« back to all changes in this revision

Viewing changes to lib/wx/test/wx_basic_SUITE.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
%%% File    : wx_basic_SUITE.erl
 
20
%%% Author  : Dan Gudmundsson <dan.gudmundsson@ericsson.com>
 
21
%%% Description : Basic SUITE, some simple tests to show that the basics 
 
22
%%%               are working.
 
23
%%% Created :  3 Nov 2008 by Dan Gudmundsson <dan.gudmundsson@ericsson.com>
 
24
%%%-------------------------------------------------------------------
 
25
-module(wx_basic_SUITE).
 
26
-export([all/0, init_per_suite/1, end_per_suite/1, 
 
27
         init_per_testcase/2, fin_per_testcase/2, end_per_testcase/2]).
 
28
 
 
29
-compile(export_all).
 
30
 
 
31
-include("wx_test_lib.hrl").
 
32
 
 
33
%% Initialization functions.
 
34
init_per_suite(Config) ->
 
35
    wx_test_lib:init_per_suite(Config).
 
36
 
 
37
end_per_suite(Config) ->
 
38
    wx_test_lib:end_per_suite(Config).
 
39
 
 
40
init_per_testcase(Func,Config) ->
 
41
    wx_test_lib:init_per_testcase(Func,Config).
 
42
end_per_testcase(Func,Config) -> 
 
43
    wx_test_lib:end_per_testcase(Func,Config).
 
44
fin_per_testcase(Func,Config) -> %% For test_server
 
45
    wx_test_lib:end_per_testcase(Func,Config).
 
46
 
 
47
%% SUITE specification
 
48
all() ->
 
49
    all(suite).
 
50
all(suite) ->
 
51
    [
 
52
     create_window,
 
53
     several_apps,
 
54
     wx_api,
 
55
     wx_misc,
 
56
     data_types
 
57
    ].
 
58
  
 
59
%% The test cases
 
60
 
 
61
%% create and test creating a window
 
62
create_window(TestInfo) when is_atom(TestInfo) -> wx_test_lib:tc_info(TestInfo);
 
63
create_window(Config) ->
 
64
    Wx = ?mr(wx_ref, wx:new()),
 
65
    Frame = ?mt(wxFrame, wxFrame:new(Wx, 1, "Hello World")),
 
66
    timer:sleep(1000),
 
67
    ?m(true,wxWindow:show(Frame, [])),
 
68
    wx_test_lib:wx_destroy(Frame, Config).
 
69
 
 
70
%% create several windows from independent processes 
 
71
%% to simulate several applications and test creating a window
 
72
several_apps(TestInfo) when is_atom(TestInfo) -> wx_test_lib:tc_info(TestInfo);
 
73
several_apps(Config) -> 
 
74
    Parent = self(),
 
75
    Pids = [spawn_link(fun() -> several_apps(Parent, N, Config) end) 
 
76
            || N <- lists:seq(1,4)],
 
77
    process_flag(trap_exit,true),
 
78
    ?m_multi_receive([{complete,Pid} || Pid <- Pids]),
 
79
    case wx_test_lib:user_available(Config) of
 
80
        true ->
 
81
            receive {'EXIT',_,foo} -> ok end;
 
82
        false ->
 
83
            ok
 
84
    end.
 
85
 
 
86
several_apps(Parent, N, Config) ->
 
87
    Wx = ?mr(wx_ref, wx:new()),
 
88
    Frame = ?mt(wxFrame, wxFrame:new(Wx, 1, "Hello World No:" ++ 
 
89
                                     integer_to_list(N))),
 
90
    create_menus(Frame),
 
91
    wxFrame:connect(Frame,size),
 
92
    ?m(true,wxWindow:show(Frame, [])),
 
93
    receive 
 
94
        #wx{obj=Frame, event=#wxSize{}} ->
 
95
            Parent ! {complete, self()}
 
96
    end,
 
97
    wx_test_lib:wx_destroy(Frame, Config),
 
98
    exit(foo).
 
99
 
 
100
 
 
101
%% Test the wx.erl api functionality.
 
102
wx_api(TestInfo) when is_atom(TestInfo) -> wx_test_lib:tc_info(TestInfo);
 
103
wx_api(Config) ->
 
104
    Wx = ?mr(wx_ref, wx:new()), 
 
105
    ?m(true, wx:is_null(Wx)),
 
106
    Null = ?mr(wx_ref, wx:null()),
 
107
    ?m(true, wx:is_null(Null)),
 
108
    Frame = ?mt(wxFrame, wxFrame:new(Wx, 1, "WX API: " ++ unicode:characters_to_list("������"))),
 
109
    ?m(false, wx:is_null(Frame)),
 
110
    ?m(wxFrame, wx:getObjectType(Frame)),
 
111
    Env = ?mr(wx_env, wx:get_env()),
 
112
    %% Test some error cases 
 
113
    erase(wx_env),
 
114
    ?m({'EXIT', {{wxe,unknown_port},_}},wxWindow:show(Frame, [])),
 
115
    ?m({'EXIT', {{wxe,unknown_port},_}},wx:debug(2)),
 
116
    
 
117
    ?m(ok,wx:set_env(Env)),
 
118
    ?m(ok,wx:debug(1)),
 
119
    ?m(ok,wx:debug(2)),
 
120
    ?m(ok,wx:debug(0)),
 
121
    ?m(ok,wx:debug(none)),
 
122
    ?m(ok,wx:debug(verbose)),
 
123
    ?m(ok,wx:debug(trace)),
 
124
    
 
125
    Mem = ?mr(wx_mem, wx:create_memory(10)),
 
126
    ?m(true, is_binary(wx:get_memory_bin(Mem))),
 
127
    ?mt(foo, wx:typeCast(Frame, foo)),
 
128
 
 
129
    RecBatch = fun() -> 
 
130
                       wx:batch(fun() -> create_menus(Frame) end)
 
131
               end,
 
132
    ?m(batch_ret, wx:batch(fun() -> RecBatch(), batch_ret end)),
 
133
    ?m(ok, wx:foreach(fun(A) -> true = lists:member(A,[1,2,3,4,5]) end, 
 
134
                      lists:seq(1,5))),
 
135
    ?m([2,3,4,5,6], wx:map(fun(A) -> A+1 end, lists:seq(1,5))),
 
136
    ?m({5,15}, wx:foldl(fun(A,{_,Acc}) -> {A,A+Acc} end, {0,0},
 
137
                        lists:seq(1,5))),
 
138
    ?m({1,15}, wx:foldr(fun(A,{_,Acc}) -> {A,A+Acc} end, {0,0},
 
139
                        lists:seq(1,5))),
 
140
    ?m(ok,wx:debug(none)),
 
141
    
 
142
    ?m(ball, wx:batch(fun() -> throw(ball), batch_ret end)),
 
143
    ?m({'EXIT', door}, wx:batch(fun() -> exit(door), batch_ret end)),
 
144
    ?m({'EXIT',{message,_ST}}, 
 
145
       wx:batch(fun() -> erlang:error(message), batch_ret end)),
 
146
    
 
147
 
 
148
    ?m({'EXIT',_},wxWindow:show(wx:null(), [])),
 
149
    ?m(true,wxWindow:show(Frame, [])),
 
150
    Temp = ?mt(wxButton, wxButton:new(Frame, -1)),
 
151
    ?m(ok,wxButton:setLabel(Temp, "Testing")),
 
152
    ?m(ok,wxButton:destroy(Temp)),
 
153
    ?m({'EXIT',_},wxButton:getLabel(Temp)),
 
154
    
 
155
    case wx_test_lib:user_available(Config) of
 
156
        true ->             
 
157
            %% Hmm popup doesn't return until mouse is pressed.
 
158
            Menu = wxMenu:new(),
 
159
            wxMenu:append(Menu, 0, "Press", []),
 
160
            wxMenu:append(Menu, 1, "Me", []),
 
161
            ?m(true, wxWindow:popupMenu(Frame, Menu)),
 
162
            %% This didn't work for a while
 
163
            ?m(true, wx:batch(fun() -> 
 
164
                                      wxMenu:append(Menu, 2, "AGAIN", []),
 
165
                                      wxWindow:popupMenu(Frame, Menu) 
 
166
                              end)),
 
167
            ok;
 
168
        _ ->
 
169
            ignore
 
170
    end,
 
171
    
 
172
%%     dbg:tracer(),
 
173
%%     {_, _Port, Server, _Dbg} = wx:get_env(),
 
174
%%     dbg:p(Server, [m, call]),
 
175
%%     dbg:p(new, [m, call]),
 
176
%%     dbg:tpl(wxe_server,'_', [{'_', [], [{return_trace}]}]),
 
177
    wx_test_lib:wx_destroy(Frame,Config).
 
178
                  
 
179
create_menus(Frame) ->
 
180
    MenuBar = ?mt(wxMenuBar, wxMenuBar:new()),
 
181
    File    = ?mt(wxMenu, wxMenu:new([])),
 
182
    Help    = ?mt(wxMenu, wxMenu:new([])),
 
183
    ?mt(wxMenuItem, wxMenu:append(Help, ?wxID_ABOUT, "&About", [])),
 
184
    ?mt(wxMenuItem, wxMenu:append(Help, ?wxID_HELP, "&Help", [])),
 
185
    ?mt(wxMenuItem, wxMenu:append(File, ?wxID_EXIT, "Exit", [])), 
 
186
    ?m(ok,wxFrame:connect(Frame, command_menu_selected)), 
 
187
    ?m(true, wxMenuBar:append(MenuBar, File, "&File")),
 
188
    ?m(true, wxMenuBar:append(MenuBar, Help, "&Help")),
 
189
    ?m(ok, wxFrame:setMenuBar(Frame,MenuBar)).
 
190
 
 
191
 
 
192
%% Test the wx_misc.erl api functionality.
 
193
wx_misc(TestInfo) when is_atom(TestInfo) -> wx_test_lib:tc_info(TestInfo);
 
194
wx_misc(Config) ->    
 
195
    wx:new([{debug, trace}]),
 
196
    put(wx_test_verbose, true),
 
197
    ?m(ok, wx_misc:bell()),
 
198
    ?m(true, length(wx_misc:getUserId()) > 0),
 
199
    ?m(true, is_list(wx_misc:getEmailAddress())),
 
200
    Home = ?m([_|_], wx_misc:getHomeDir()),
 
201
    ?m(true, filelib:is_dir(Home)),
 
202
    ?m(true, length(wx_misc:getOsDescription()) > 0),
 
203
    IsLitte = case <<1:32/native>> of 
 
204
                  <<1:8, 0:24>> -> true;
 
205
                  <<0:24,1:16>> -> false
 
206
              end,
 
207
    ?m(IsLitte, wx_misc:isPlatformLittleEndian()),
 
208
    ?m(true, is_boolean(wx_misc:isPlatform64Bit())),
 
209
    
 
210
    ?mr(wxMouseState, wx_misc:getMouseState()),
 
211
    ?m({_,_}, wx_misc:getMousePosition()),
 
212
    
 
213
    %% Don't hold home down when testing :-)
 
214
    ?m(false, wx_misc:getKeyState(?WXK_HOME)), 
 
215
 
 
216
    
 
217
    %% wx:shutdown()  %% How do you test this?
 
218
 
 
219
    case os:type() of 
 
220
        {win32, _} -> %% These hangs when running automatic tests
 
221
            skip;     %% through ssh on windows. Works otherwise
 
222
        _ -> 
 
223
            wx_misc:shell([{command,"echo TESTING close the popup shell"}])
 
224
    end,
 
225
 
 
226
    case wx_test_lib:user_available(Config) of
 
227
        true ->
 
228
            wx_misc:shell();
 
229
        false ->
 
230
            %% Don't want to spawn a shell if no user      
 
231
            skip %% is available
 
232
    end,
 
233
 
 
234
    ?m(false, wx_misc:isBusy()),
 
235
    ?m(ok, wx_misc:beginBusyCursor([])),
 
236
    ?m(true, wx_misc:isBusy()),
 
237
    ?m(ok, wx_misc:endBusyCursor()),
 
238
    
 
239
    %%?m(true, is_boolean(wx_misc:setDetectableAutoRepeat(true)),
 
240
    Curr  = wx_misc:getCurrentId(),
 
241
    ?m(true, is_integer(Curr)),
 
242
    NewId = wx_misc:newId(),
 
243
    ?m(ok, wx_misc:registerId(NewId+1)),
 
244
    ?m(true, (NewId+1) /= wx_misc:newId()),
 
245
    
 
246
    wx:destroy().
 
247
 
 
248
 
 
249
%% Check that all the data_types works in communication 
 
250
%% between erlang and c++ thread.
 
251
data_types(TestInfo) when is_atom(TestInfo) -> wx_test_lib:tc_info(TestInfo);
 
252
data_types(_Config) ->
 
253
    Wx = ?mr(wx_ref, wx:new()),
 
254
    
 
255
    Frame = wxFrame:new(Wx, 1, "Data Types"),
 
256
    CDC = wxClientDC:new(Frame),
 
257
 
 
258
    %% From wx.erl
 
259
    %% The following classes are implemented directly as erlang types: <br />
 
260
    %% wxPoint={x,y},wxSize={w,h},wxRect={x,y,w,h},wxColour={r,g,b [,a]},wxString=[integer],
 
261
    %% wxGBPosition={r,c},wxGBSpan={rs,cs},wxGridCellCoords={r,c}.
 
262
 
 
263
    %% Strings
 
264
    ?m("Data Types", wxFrame:getTitle(Frame)),
 
265
 
 
266
    %% Doubles
 
267
    ?m(ok, wxDC:setUserScale(CDC, 123.45, 234.67)),
 
268
    ?m({123.45,234.67}, wxDC:getUserScale(CDC)),
 
269
 
 
270
    %% Colors input is 3 or 4 tuple, returns are 4 tuples
 
271
    ?m(ok, wxDC:setTextForeground(CDC, {100,10,1})),
 
272
    ?m({100,10,1,255}, wxDC:getTextForeground(CDC)),
 
273
    ?m(ok, wxDC:setTextForeground(CDC, {100,10,1,43})),
 
274
    ?m({100,10,1,43}, wxDC:getTextForeground(CDC)),
 
275
 
 
276
    %% Bool 
 
277
    ?m(ok, wxDC:setAxisOrientation(CDC, true, false)),
 
278
    ?m(true, is_boolean(wxDC:isOk(CDC))),
 
279
    
 
280
    %% wxCoord 
 
281
    ?m(true, is_integer(wxDC:maxX(CDC))),
 
282
    
 
283
    %% wxSize
 
284
    ?m({_,_}, wxWindow:getSize(Frame)),
 
285
 
 
286
    %% DateTime 
 
287
    DateTime = calendar:now_to_datetime(erlang:now()),
 
288
    io:format("DateTime ~p ~n",[DateTime]),
 
289
    Cal = ?mt(wxCalendarCtrl, wxCalendarCtrl:new(Frame, ?wxID_ANY, [{date,DateTime}])),
 
290
    ?m(DateTime, wxCalendarCtrl:getDate(Cal)),
 
291
    ?m(true, is_boolean(wxCalendarCtrl:setDate(Cal,DateTime))),
 
292
    ?m(DateTime, wxCalendarCtrl:getDate(Cal)),
 
293
 
 
294
    wxClientDC:destroy(CDC),
 
295
    %%wx_test_lib:wx_destroy(Frame,Config).
 
296
    wx:destroy().