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

« back to all changes in this revision

Viewing changes to lib/wx/test/wx_test_lib.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_test_lib.erl
 
20
%%% Author  : Dan Gudmundsson <dan.gudmundsson@ericsson.com>
 
21
%%% Description : Library for testing wxerlang.
 
22
%%%
 
23
%%% Created : 30 Oct 2008 by Dan Gudmundsson <dan.gudmundsson@ericsson.com>
 
24
%%%-------------------------------------------------------------------
 
25
-module(wx_test_lib).
 
26
-compile(export_all).
 
27
 
 
28
-include("wx_test_lib.hrl").
 
29
 
 
30
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
31
init_per_suite(Config) ->
 
32
    try 
 
33
        case os:type() of
 
34
            {unix,darwin} ->
 
35
                exit("Can not test on MacOSX");
 
36
            {unix, _} ->
 
37
                io:format("DISPLAY ~s~n", [os:getenv("DISPLAY")]),
 
38
                case proplists:get_value(xserver, Config, none) of
 
39
                    none -> ignore;
 
40
                    Server -> 
 
41
                        os:putenv("DISPLAY", Server)
 
42
                end;
 
43
            _ -> ignore
 
44
        end,
 
45
        wx:new(),
 
46
        wx:destroy(),
 
47
        Config
 
48
    catch 
 
49
        _:undef ->
 
50
            {skipped, "No wx compiled for this platform"};
 
51
        _:Reason ->
 
52
            {skipped, lists:flatten(io_lib:format("Start wx failed: ~p", [Reason]))}
 
53
    end.
 
54
 
 
55
end_per_suite(_Config) ->
 
56
    ok.
 
57
 
 
58
init_per_testcase(_Func, Config) ->
 
59
    global:register_name(wx_global_logger, group_leader()),
 
60
    Config.
 
61
 
 
62
end_per_testcase(_Func, Config) ->
 
63
    global:unregister_name(wx_global_logger),
 
64
    Config.
 
65
 
 
66
%% Backwards compatible with test_server
 
67
tc_info(suite) -> [];
 
68
tc_info(doc) -> "".
 
69
 
 
70
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
71
 
 
72
%% Use ?log(Format, Args) as wrapper
 
73
log(Format, Args, LongFile, Line) ->
 
74
    File = filename:basename(LongFile),
 
75
    Format2 = lists:concat([File, "(", Line, ")", ": ", Format]),
 
76
    log(Format2, Args).
 
77
 
 
78
log(Format, Args) ->
 
79
    case global:whereis_name(wx_global_logger) of
 
80
        undefined ->
 
81
            io:format(user, Format, Args);
 
82
        Pid ->
 
83
            io:format(Pid, Format, Args)
 
84
    end.
 
85
 
 
86
verbose(Format, Args, File, Line) ->
 
87
    Arg = wx_test_verbose,
 
88
    case get(Arg) of
 
89
        false ->
 
90
            ok;
 
91
        true ->
 
92
            log(Format, Args, File, Line);
 
93
        undefined ->
 
94
            case init:get_argument(Arg) of
 
95
                {ok, List} when list(List) ->
 
96
                    case lists:last(List) of
 
97
                        ["true"] ->
 
98
                            put(Arg, true),
 
99
                            log(Format, Args, File, Line);
 
100
                        _ ->
 
101
                            put(Arg, false),
 
102
                            ok
 
103
                    end;
 
104
                _ ->
 
105
                    put(Arg, false),
 
106
                    ok
 
107
            end
 
108
    end.
 
109
 
 
110
error(Format, Args, File, Line) ->
 
111
    global:send(wx_global_logger, {failed, File, Line}),
 
112
    Fail = {filename:basename(File),Line,Args},
 
113
    case global:whereis_name(wx_test_case_sup) of
 
114
        undefined -> ignore;
 
115
        Pid -> Pid ! Fail
 
116
            %%      global:send(wx_test_case_sup, Fail),
 
117
    end,
 
118
    log("<ERROR>~n" ++ Format, Args, File, Line).
 
119
 
 
120
 
 
121
pick_msg() ->
 
122
    receive
 
123
        Message -> Message
 
124
    after 4000 -> timeout
 
125
    end.
 
126
 
 
127
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
128
%% Utility functions
 
129
 
 
130
user_available(Config) ->
 
131
    false /= proplists:get_value(user, Config, false).
 
132
        
 
133
 
 
134
wx_destroy(Frame, Config) ->
 
135
    case proplists:get_value(user, Config, false) of
 
136
        false ->
 
137
            timer:sleep(100),
 
138
            ?m(ok, wxFrame:destroy(Frame)),
 
139
            ?m(ok, wx:destroy());
 
140
        true ->
 
141
            timer:sleep(500),
 
142
            ?m(ok, wxFrame:destroy(Frame)),
 
143
            ?m(ok, wx:destroy());       
 
144
        step -> %% Wait for user to close window
 
145
            ?m(ok, wxEvtHandler:connect(Frame, close_window, [{skip,true}])),
 
146
            wait_for_close()
 
147
    end.
 
148
 
 
149
wait_for_close() ->
 
150
    receive 
 
151
        #wx{event=#wxClose{}} ->
 
152
            ?log("Got close~n",[]),
 
153
            ?m(ok, wx:destroy());
 
154
        #wx{obj=Obj, event=Event} ->
 
155
            try 
 
156
                Name = wxTopLevelWindow:getTitle(Obj),
 
157
                ?log("~p Event: ~p~n", [Name, Event])
 
158
            catch _:_ ->
 
159
                ?log("Event: ~p~n", [Event])
 
160
            end,
 
161
            wait_for_close();
 
162
        Other ->
 
163
            ?log("Unexpected: ~p~n", [Other]),
 
164
            wait_for_close()
 
165
    end.
 
166
 
 
167
 
 
168
 
 
169
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
170
%% A small test server, which can be run standalone in a shell
 
171
 
 
172
run_test(Test = {_,_},Config) ->
 
173
    run_test([Test],Config);
 
174
run_test([{Module, TC}|Rest], Config) ->
 
175
    [run_test(Module, TC, Config) |
 
176
     run_test(Rest, Config)];
 
177
run_test([], _Config) -> [].
 
178
 
 
179
run_test(Module, all, Config) ->
 
180
    All = [{Module, Test} || Test <- Module:all()],
 
181
    run_test(All, Config);
 
182
run_test(Module, TestCase, Config) ->
 
183
    log("Eval test case: ~w~n", [{Module, TestCase}]),
 
184
    Sec = timer:seconds(1) * 1000,
 
185
    {T, Res} =
 
186
        timer:tc(?MODULE, eval_test_case, [Module, TestCase, Config]),
 
187
    log("Tested ~w in ~w sec~n", [TestCase, T div Sec]),
 
188
    {T div Sec, Res}.
 
189
    
 
190
eval_test_case(Mod, Fun, Config) ->
 
191
    flush(),
 
192
    global:register_name(wx_test_case_sup, self()),
 
193
    Flag = process_flag(trap_exit, true),
 
194
    Pid = spawn_link(?MODULE, test_case_evaluator, [Mod, Fun, [Config]]),
 
195
    R = wait_for_evaluator(Pid, Mod, Fun, Config),
 
196
    global:unregister_name(wx_test_case_sup),
 
197
    process_flag(trap_exit, Flag),
 
198
    R.
 
199
 
 
200
test_case_evaluator(Mod, Fun, [Config]) ->
 
201
    NewConfig = Mod:init_per_testcase(Fun, Config),
 
202
    R = apply(Mod, Fun, [NewConfig]),
 
203
    Mod:fin_per_testcase(Fun, NewConfig),
 
204
    exit({test_case_ok, R}).
 
205
 
 
206
wait_for_evaluator(Pid, Mod, Fun, Config) ->
 
207
    receive
 
208
        {'EXIT', Pid, {test_case_ok, _PidRes}} ->
 
209
            Errors = flush(),
 
210
            Res = 
 
211
                case Errors of
 
212
                    [] -> ok;
 
213
                    Errors -> failed
 
214
                end,
 
215
            {Res, {Mod, Fun}, Errors};
 
216
        {'EXIT', Pid, {skipped, Reason}} ->
 
217
            log("<WARNING> Test case ~w skipped, because ~p~n",
 
218
                [{Mod, Fun}, Reason]),
 
219
            Mod:fin_per_testcase(Fun, Config),
 
220
            {skip, {Mod, Fun}, Reason};
 
221
        {'EXIT', Pid, Reason} ->
 
222
            log("<ERROR> Eval process ~w exited, because ~p~n",
 
223
                [{Mod, Fun}, Reason]),
 
224
            Mod:fin_per_testcase(Fun, Config),
 
225
            {crash, {Mod, Fun}, Reason}
 
226
    end.
 
227
 
 
228
flush() ->
 
229
    receive Msg -> [Msg | flush()]
 
230
    after 0 -> []
 
231
    end.
 
232
 
 
233
 
 
234
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%