~clint-fewbar/ubuntu/precise/erlang/merge-15b

« back to all changes in this revision

Viewing changes to lib/wx/test/wx_class_SUITE.erl

  • Committer: Package Import Robot
  • Author(s): Sergei Golovan
  • Date: 2011-12-15 19:20:10 UTC
  • mfrom: (1.1.18) (3.5.15 sid)
  • mto: (3.5.16 sid)
  • mto: This revision was merged to the branch mainline in revision 33.
  • Revision ID: package-import@ubuntu.com-20111215192010-jnxcfe3tbrpp0big
Tags: 1:15.b-dfsg-1
* New upstream release.
* Upload to experimental because this release breaks external drivers
  API along with ABI, so several applications are to be fixed.
* Removed SSL patch because the old SSL implementation is removed from
  the upstream distribution.
* Removed never used patch which added native code to erlang beam files.
* Removed the erlang-docbuilder binary package because the docbuilder
  application was dropped by upstream.
* Documented dropping ${erlang-docbuilder:Depends} substvar in
  erlang-depends(1) manpage.
* Made erlang-base and erlang-base-hipe provide virtual package
  erlang-abi-15.b (the number means the first erlang version, which
  provides current ABI).

Show diffs side-by-side

added added

removed removed

Lines of Context:
1
1
%%
2
2
%% %CopyrightBegin%
3
3
%%
4
 
%% Copyright Ericsson AB 2008-2010. All Rights Reserved.
 
4
%% Copyright Ericsson AB 2008-2011. All Rights Reserved.
5
5
%%
6
6
%% The contents of this file are subject to the Erlang Public License,
7
7
%% Version 1.1, (the "License"); you may not use this file except in
18
18
%%%-------------------------------------------------------------------
19
19
%%% File    : wx_class_SUITE.erl
20
20
%%% Author  : Dan Gudmundsson <dan.gudmundsson@ericsson.com>
21
 
%%% Description : 
 
21
%%% Description :
22
22
%%%
23
23
%%% Created : 13 Nov 2008 by Dan Gudmundsson <dan.gudmundsson@ericsson.com>
24
24
%%%-------------------------------------------------------------------
25
25
-module(wx_class_SUITE).
26
26
 
27
 
-export([all/0, init_per_suite/1, end_per_suite/1, 
28
 
         init_per_testcase/2, fin_per_testcase/2, end_per_testcase/2]).
 
27
-export([all/0, suite/0,groups/0,init_per_group/2,end_per_group/2,
 
28
         init_per_suite/1, end_per_suite/1,
 
29
         init_per_testcase/2, end_per_testcase/2]).
29
30
 
30
31
-compile(export_all).
31
32
 
40
41
 
41
42
init_per_testcase(Func,Config) ->
42
43
    wx_test_lib:init_per_testcase(Func,Config).
43
 
end_per_testcase(Func,Config) -> 
44
 
    wx_test_lib:end_per_testcase(Func,Config).
45
 
fin_per_testcase(Func,Config) -> %% For test_server
 
44
end_per_testcase(Func,Config) ->
46
45
    wx_test_lib:end_per_testcase(Func,Config).
47
46
 
48
47
%% SUITE specification
 
48
suite() -> [{ct_hooks,[ts_install_cth]}].
 
49
 
49
50
all() ->
50
 
    all(suite).
51
 
all(suite) ->
52
 
    [
53
 
     calendarCtrl, 
54
 
     treeCtrl,
55
 
     notebook,
56
 
     staticBoxSizer,
57
 
     clipboard,
58
 
     helpFrame,
59
 
     htmlWindow,
60
 
     listCtrlSort,
61
 
     radioBox,
62
 
     systemSettings
63
 
    ].
 
51
    [calendarCtrl, treeCtrl, notebook, staticBoxSizer,
 
52
     clipboard, helpFrame, htmlWindow, listCtrlSort, listCtrlVirtual,
 
53
     radioBox, systemSettings].
 
54
 
 
55
groups() ->
 
56
    [].
 
57
 
 
58
init_per_group(_GroupName, Config) ->
 
59
    Config.
 
60
 
 
61
end_per_group(_GroupName, Config) ->
 
62
    Config.
64
63
 
65
64
%% The test cases
66
65
 
71
70
    Frame = ?mt(wxFrame, wxFrame:new(Wx, 1, "Calendar", [])),
72
71
    Panel = wxPanel:new(Frame),
73
72
    Sz = wxBoxSizer:new(?wxVERTICAL),
74
 
    
 
73
 
75
74
    {YMD={_,_,Day},_} = DateTime = calendar:now_to_datetime(erlang:now()),
76
 
    Cal = ?mt(wxCalendarCtrl, wxCalendarCtrl:new(Panel, ?wxID_ANY, 
 
75
    Cal = ?mt(wxCalendarCtrl, wxCalendarCtrl:new(Panel, ?wxID_ANY,
77
76
                                                 [{date,DateTime}
78
77
                                                 ])),
79
78
    wxSizer:add(Sz,Cal),
92
91
    ?m({0,243,0,255}, wxCalendarDateAttr:getBackgroundColour(DateAttr1)),
93
92
 
94
93
    ?m({YMD, _},wxCalendarCtrl:getDate(Cal)),
95
 
    
96
 
    wxCalendarCtrl:connect(Cal, calendar_weekday_clicked), 
97
 
    wxCalendarCtrl:connect(Cal, calendar_day_changed), 
98
 
    wxCalendarCtrl:connect(Cal, calendar_month_changed), 
 
94
 
 
95
    wxCalendarCtrl:connect(Cal, calendar_weekday_clicked),
 
96
    wxCalendarCtrl:connect(Cal, calendar_day_changed),
 
97
    wxCalendarCtrl:connect(Cal, calendar_month_changed),
99
98
    wxCalendarCtrl:connect(Cal, calendar_year_changed),
100
 
    wxCalendarCtrl:connect(Cal, calendar_doubleclicked), 
 
99
    wxCalendarCtrl:connect(Cal, calendar_doubleclicked),
101
100
    wxCalendarCtrl:connect(Cal, calendar_sel_changed),
102
 
    
 
101
 
103
102
    wxWindow:setSizer(Panel,Sz),
104
103
    wxSizer:setSizeHints(Sz,Frame),
105
 
    wxWindow:show(Frame), 
106
 
    
 
104
    wxWindow:show(Frame),
 
105
 
107
106
    wx_test_lib:wx_destroy(Frame,Config).
108
107
 
109
108
 
110
109
treeCtrl(TestInfo) when is_atom(TestInfo) -> wx_test_lib:tc_info(TestInfo);
111
110
treeCtrl(Config) ->
112
111
    Wx = wx:new(),
113
 
    
 
112
 
114
113
    Frame = wxFrame:new(Wx, ?wxID_ANY, "Frame"),
115
114
    Panel = wxPanel:new(Frame, []),
116
115
    Tree = ?mt(wxTreeCtrl,wxTreeCtrl:new(Panel, [{style , ?wxTR_HAS_BUTTONS}])),
123
122
    ?m(ok,  wxTreeCtrl:setItemData(Tree, Item2, {data, item2})),
124
123
    Item3 = wxTreeCtrl:appendItem(Tree, Root, "Item3", []),
125
124
    ?m(ok, wxTreeCtrl:setItemData(Tree, Item3, {data, item3})),
126
 
    
 
125
 
127
126
    Sizer = wxBoxSizer:new(?wxVERTICAL),
128
127
    wxSizer:add(Sizer, Tree, [{flag, ?wxEXPAND}, {proportion, 1}]),
129
128
 
130
129
    wxWindow:setSizerAndFit(Panel, Sizer),
131
130
    wxFrame:show(Frame),
132
 
    
 
131
 
133
132
    ?m([], wxTreeCtrl:getItemData(Tree, Root)),
134
133
    ?m({data,item1}, wxTreeCtrl:getItemData(Tree, Item1)),
135
134
    ?m({data,item2}, wxTreeCtrl:getItemData(Tree, Item2)),
136
135
    ?m({data,item3}, wxTreeCtrl:getItemData(Tree, Item3)),
137
 
    
 
136
 
138
137
    wxFrame:connect(Tree, command_tree_item_expanded),
139
138
    wxFrame:connect(Tree, command_tree_item_collapsed),
140
139
    wxFrame:connect(Frame, close_window),
141
140
 
142
141
    wxTreeCtrl:editLabel(Tree, Root),
143
142
 
144
 
    
 
143
 
145
144
    wx_test_lib:wx_destroy(Frame,Config).
146
145
 
147
146
notebook(TestInfo) when is_atom(TestInfo) -> wx_test_lib:tc_info(TestInfo);
211
210
    Frame = wxFrame:new(Wx, ?wxID_ANY, "Frame"),
212
211
    Panel = wxPanel:new(Frame, []),
213
212
    InclSizer = ?mt(wxStaticBoxSizer,
214
 
                    wxStaticBoxSizer:new(?wxVERTICAL, Panel, 
 
213
                    wxStaticBoxSizer:new(?wxVERTICAL, Panel,
215
214
                                         [{label, "Module inclusion policy"}])),
216
215
    Sizer = wxBoxSizer:new(?wxVERTICAL),
217
216
    wxSizer:add(Sizer, InclSizer,
218
217
                [{border, 2}, {flag, ?wxALL bor ?wxEXPAND}, {proportion, 1}]),
219
 
    wxWindow:setSizerAndFit(Panel, Sizer),    
220
 
    
 
218
    wxWindow:setSizerAndFit(Panel, Sizer),
 
219
 
221
220
    wxWindow:show(Frame),
222
221
    wx_test_lib:wx_destroy(Frame,Config).
223
222
 
264
263
    wxClipboard:flush(CB),
265
264
    ?log("Stopping ~n",[]),
266
265
    ok.
267
 
    
 
266
 
268
267
helpFrame(TestInfo) when is_atom(TestInfo) -> wx_test_lib:tc_info(TestInfo);
269
268
helpFrame(Config) ->
270
269
    Wx = wx:new(),
271
270
    MFrame = wx:batch(fun() ->
272
271
                              MFrame = wxFrame:new(Wx, ?wxID_ANY, "Main Frame"),
273
 
                              wxPanel:new(MFrame, [{size, {600,400}}]),      
 
272
                              wxPanel:new(MFrame, [{size, {600,400}}]),
274
273
                              wxWindow:show(MFrame),
275
274
                              MFrame
276
275
                      end),
280
279
    {X, Y, W,H} = wxWindow:getScreenRect(MFrame),
281
280
    io:format("Pos0: ~p ~p ~p Pos: ~p:~p Size: ~p:~p ~n",
282
281
              [X0,Y0, wxWindow:clientToScreen(MFrame, {0,0}), X,Y,W,H]),
283
 
    
 
282
 
284
283
    Pos = {X+5, Y+(H div 2)},
285
284
    Size = {W-10, (H div 2) - 5},
286
285
 
287
 
    Comp = wxFrame:new(MFrame, ?wxID_ANY, "Completion Window", 
 
286
    Comp = wxFrame:new(MFrame, ?wxID_ANY, "Completion Window",
288
287
                       [{pos, Pos}, {size, Size},
289
288
                        {style, ?wxFRAME_FLOAT_ON_PARENT}]),
290
289
    LB = wxListBox:new(Comp, 42, [{style, ?wxLB_SINGLE},
302
301
    {MFrame,HPanel} =
303
302
        wx:batch(fun() ->
304
303
                         MFrame = wxFrame:new(Wx, ?wxID_ANY, "Main Frame"),
305
 
                         HPanel = wxHtmlWindow:new(MFrame, [{size, {600,400}}]),  
 
304
                         HPanel = wxHtmlWindow:new(MFrame, [{size, {600,400}}]),
306
305
                         wxWindow:show(MFrame),
307
306
                         {MFrame, HPanel}
308
307
                 end),
311
310
    WxMod = code:which(wx),
312
311
    WxDir = filename:split(filename:dirname(WxMod)) -- ["ebin"],
313
312
    Html = filename:join(filename:join(WxDir),filename:join("doc", "html")),
314
 
    
 
313
 
315
314
    Index = filename:join(Html, "wx.html"),
316
315
 
317
316
    ?m(ok, wxHtmlWindow:connect(HPanel, command_html_link_clicked,
319
318
                                  fun(Ev,_) ->
320
319
                                          io:format("Link clicked: ~p~n",[Ev])
321
320
                                  end}])),
322
 
    
 
321
 
323
322
    case filelib:is_file(Index) of
324
323
        true ->
325
324
            ?m(true, wxHtmlWindow:loadFile(HPanel, Index)),
327
326
        false ->
328
327
            ok
329
328
    end,
330
 
    
 
329
 
331
330
    wx_test_lib:wx_destroy(MFrame,Config).
332
331
 
333
332
 
335
334
listCtrlSort(Config) ->
336
335
    Wx = wx:new(),
337
336
    Frame = wxFrame:new(Wx, ?wxID_ANY, "Frame"),
338
 
    
 
337
 
339
338
    LC = wxListCtrl:new(Frame, [{style, ?wxLC_REPORT bor ?wxLC_SORT_ASCENDING}]),
340
339
 
341
340
    %% must be done crashes in wxwidgets otherwise.
342
341
    wxListCtrl:insertColumn(LC, 0, "Column"),
343
 
    
344
 
    Add = fun(Int) ->    
 
342
 
 
343
    Add = fun(Int) ->
345
344
                  wxListCtrl:insertItem(LC, Int, integer_to_list(Int)),
346
345
                  %% ItemData Can only be integers currently
347
346
                  wxListCtrl:setItemData(LC, Int, abs(2500-Int))
348
347
          end,
349
 
    
 
348
 
350
349
    wx:foreach(Add, lists:seq(0,5000)),
351
350
    wxWindow:show(Frame),
352
351
 
361
360
                                                    end
362
361
                                            end)
363
362
           end,
364
 
    
 
363
 
365
364
    Time = timer:tc(erlang, apply, [Sort,[]]),
366
365
    io:format("Sorted ~p ~n",[Time]),
367
 
    
 
366
 
368
367
    Item = wxListItem:new(),
369
368
    _List = wx:map(fun(Int) ->
370
369
                           wxListItem:setId(Item, Int),
375
374
 
376
375
    wx_test_lib:wx_destroy(Frame,Config).
377
376
 
 
377
listCtrlVirtual(TestInfo) when is_atom(TestInfo) -> wx_test_lib:tc_info(TestInfo);
 
378
listCtrlVirtual(Config) ->
 
379
    Wx = wx:new(),
 
380
    Frame = wxFrame:new(Wx, ?wxID_ANY, "Frame"),
 
381
    IA = wxListItemAttr:new(),
 
382
    wxListItemAttr:setTextColour(IA, {190, 25, 25}),
 
383
    LC = wxListCtrl:new(Frame,
 
384
                        [{style, ?wxLC_REPORT bor ?wxLC_VIRTUAL},
 
385
                         {onGetItemText, fun(_This, Item, 0) ->
 
386
                                                 "Row " ++ integer_to_list(Item);
 
387
                                            (_, Item, 1) when Item rem 5 == 0 ->
 
388
                                                 "Column 2";
 
389
                                            (_, _, _) -> ""
 
390
                                         end},
 
391
                         {onGetItemAttr, fun(_This, Item) when Item rem 3 == 0 ->
 
392
                                                 IA;
 
393
                                            (_This, _Item)  ->
 
394
                                                 wx:typeCast(wx:null(), wxListItemAttr)
 
395
                                         end},
 
396
                         {onGetItemColumnImage, fun(_This, Item, 1) ->
 
397
                                                        Item rem 4;
 
398
                                                   (_, _, _) ->
 
399
                                                        -1
 
400
                                                end}
 
401
                        ]),
 
402
 
 
403
    IL = wxImageList:new(16,16),
 
404
    wxImageList:add(IL, wxArtProvider:getBitmap("wxART_COPY", [{size, {16,16}}])),
 
405
    wxImageList:add(IL, wxArtProvider:getBitmap("wxART_MISSING_IMAGE", [{size, {16,16}}])),
 
406
    wxImageList:add(IL, wxArtProvider:getBitmap("wxART_TICK_MARK", [{size, {16,16}}])),
 
407
    wxImageList:add(IL, wxArtProvider:getBitmap("wxART_CROSS_MARK", [{size, {16,16}}])),
 
408
    wxListCtrl:assignImageList(LC, IL, ?wxIMAGE_LIST_SMALL),
 
409
 
 
410
    wxListCtrl:insertColumn(LC, 0, "Column 1"),
 
411
    wxListCtrl:insertColumn(LC, 1, "Column 2"),
 
412
    wxListCtrl:setColumnWidth(LC, 0, 200),
 
413
    wxListCtrl:setColumnWidth(LC, 1, 200),
 
414
    wxListCtrl:setItemCount(LC, 1000000),
 
415
 
 
416
    wxWindow:show(Frame),
 
417
    wx_test_lib:wx_destroy(Frame,Config).
 
418
 
378
419
 
379
420
radioBox(TestInfo) when is_atom(TestInfo) -> wx_test_lib:tc_info(TestInfo);
380
421
radioBox(Config) ->
383
424
 
384
425
    TrSortRadioBox = wxRadioBox:new(Frame, ?wxID_ANY, "Sort by:",
385
426
                                    {100, 100},{100, 100}, ["Timestamp"]),
386
 
    
 
427
 
387
428
    io:format("TrSortRadioBox ~p ~n", [TrSortRadioBox]),
388
429
    %% If I uncomment any of these lines, it will crash
389
430
 
399
440
systemSettings(Config) ->
400
441
    Wx = wx:new(),
401
442
    Frame = wxFrame:new(Wx, ?wxID_ANY, "Frame"),
402
 
    
 
443
 
403
444
    ?m({_,_,_,_}, wxSystemSettings:getColour(?wxSYS_COLOUR_DESKTOP)),
404
445
    ?mt(wxFont, wxSystemSettings:getFont(?wxSYS_SYSTEM_FONT)),
405
446
    ?m(true, is_integer(wxSystemSettings:getMetric(?wxSYS_MOUSE_BUTTONS))),
407
448
 
408
449
    wxWindow:show(Frame),
409
450
    wx_test_lib:wx_destroy(Frame,Config).
 
451
 
 
452
 
 
453
textCtrl(TestInfo) when is_atom(TestInfo) -> wx_test_lib:tc_info(TestInfo);
 
454
textCtrl(Config) ->
 
455
    Wx = wx:new(),
 
456
    Frame = wxFrame:new(Wx, ?wxID_ANY, "Frame"),
 
457
 
 
458
    TC = ?mt(wxTextCtrl, wxTextCtrl:new(Frame, ?wxID_ANY, [{style, ?wxTE_MULTILINE bor ?wxTE_RICH2}])),
 
459
    wxTextCtrl:appendText(TC, "This line is in default color\n"),
 
460
    Attr = ?mt(wxTextAttr, wxTextAttr:new(?wxRED)),
 
461
    wxTextCtrl:setDefaultStyle(TC, Attr),
 
462
    wxTextCtrl:appendText(TC, "This line is in ?wxRED color\n"),
 
463
    wxTextAttr:setTextColour(Attr, ?wxBLACK),
 
464
    wxTextCtrl:setDefaultStyle(TC, Attr),
 
465
    wxTextCtrl:appendText(TC, "This line is in ?wxBLACK color\n"),
 
466
    Default = wxSystemSettings:getColour(?wxSYS_COLOUR_WINDOWTEXT),
 
467
    wxTextAttr:setTextColour(Attr, Default),
 
468
    wxTextCtrl:setDefaultStyle(TC, Attr),
 
469
    wxTextCtrl:appendText(TC, "This line is in default color\n"),
 
470
    wxTextAttr:destroy(Attr),
 
471
    wxWindow:show(Frame),
 
472
    wx_test_lib:wx_destroy(Frame,Config).