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

« back to all changes in this revision

Viewing changes to lib/eunit/src/eunit_test.erl

  • Committer: Bazaar Package Importer
  • Author(s): Sergei Golovan
  • Date: 2009-02-15 16:42:52 UTC
  • mfrom: (1.1.13 upstream)
  • Revision ID: james.westby@ubuntu.com-20090215164252-dxpjjuq108nz4noa
Tags: 1:12.b.5-dfsg-2
Upload to unstable after lenny is released.

Show diffs side-by-side

added added

removed removed

Lines of Context:
 
1
%% This library is free software; you can redistribute it and/or modify
 
2
%% it under the terms of the GNU Lesser General Public License as
 
3
%% published by the Free Software Foundation; either version 2 of the
 
4
%% License, or (at your option) any later version.
 
5
%%
 
6
%% This library is distributed in the hope that it will be useful, but
 
7
%% WITHOUT ANY WARRANTY; without even the implied warranty of
 
8
%% MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU
 
9
%% Lesser General Public License for more details.
 
10
%%
 
11
%% You should have received a copy of the GNU Lesser General Public
 
12
%% License along with this library; if not, write to the Free Software
 
13
%% Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307
 
14
%% USA
 
15
%%
 
16
%% $Id$ 
 
17
%%
 
18
%% @author Richard Carlsson <richardc@it.uu.se>
 
19
%% @copyright 2006 Richard Carlsson
 
20
%% @private
 
21
%% @see eunit
 
22
%% @doc Test running functionality
 
23
 
 
24
-module(eunit_test).
 
25
 
 
26
-export([run_testfun/1, function_wrapper/2, enter_context/4,
 
27
         browse_context/2, multi_setup/1]).
 
28
 
 
29
 
 
30
-include("eunit.hrl").
 
31
-include("eunit_internal.hrl").
 
32
 
 
33
 
 
34
%% ---------------------------------------------------------------------
 
35
%% Getting a cleaned up stack trace. (We don't want it to include
 
36
%% eunit's own internal functions. This complicates self-testing
 
37
%% somewhat, but you can't have everything.) Note that we assume that
 
38
%% this particular module is the boundary between eunit and user code.
 
39
 
 
40
get_stacktrace() ->
 
41
    get_stacktrace([]).
 
42
 
 
43
get_stacktrace(Ts) ->
 
44
    eunit_lib:uniq(prune_trace(erlang:get_stacktrace(), Ts)).
 
45
 
 
46
prune_trace([{?MODULE, _, _} | _Rest], Tail) ->
 
47
    Tail;
 
48
prune_trace([T | Ts], Tail) ->
 
49
    [T | prune_trace(Ts, Tail)];
 
50
prune_trace([], Tail) ->
 
51
    Tail.
 
52
 
 
53
 
 
54
%% ---------------------------------------------------------------------
 
55
%% Test runner
 
56
 
 
57
%% @spec ((any()) -> any()) -> {ok, Value} | {error, eunit_lib:exception()}
 
58
%% @throws wrapperError()
 
59
 
 
60
run_testfun(F) ->
 
61
    try
 
62
        F()
 
63
    of Value ->
 
64
            {ok, Value}
 
65
    catch
 
66
        {eunit_internal, Term} ->
 
67
            %% Internally generated: re-throw Term (lose the trace)
 
68
            throw(Term);
 
69
        Class:Reason ->
 
70
            {error, {Class, Reason, get_stacktrace()}}
 
71
    end.
 
72
 
 
73
 
 
74
-ifdef(TEST).
 
75
macro_test_() ->
 
76
    {"macro definitions",
 
77
     [{?LINE, fun () ->
 
78
                      {?LINE, F} = ?_test(undefined),
 
79
                      {ok, undefined} = run_testfun(F)
 
80
              end},
 
81
      ?_test(begin
 
82
                 {?LINE, F} = ?_assert(true),
 
83
                 {ok, ok} = run_testfun(F)
 
84
             end),
 
85
      ?_test(begin
 
86
                 {?LINE, F} = ?_assert(false),
 
87
                 {error,{error,{assertion_failed,
 
88
                                [{module,_},
 
89
                                 {line,_},
 
90
                                 {expression,_},
 
91
                                 {expected,true},
 
92
                                 {value,false}]},
 
93
                         _}}
 
94
                     = run_testfun(F)
 
95
             end),
 
96
      ?_test(begin
 
97
                 {?LINE, F} = ?_assert([]),
 
98
                 {error,{error,{assertion_failed,
 
99
                                [{module,_},
 
100
                                 {line,_},
 
101
                                 {expression,_},
 
102
                                 {expected,true},
 
103
                                 {value,{not_a_boolean,[]}}]},
 
104
                         _}}
 
105
                     = run_testfun(F)
 
106
             end),
 
107
      ?_test(begin
 
108
                 {?LINE, F} = ?_assertNot(false),
 
109
                 {ok, ok} = run_testfun(F)
 
110
             end),
 
111
      ?_test(begin
 
112
                 {?LINE, F} = ?_assertNot(true),
 
113
                 {error,{error,{assertion_failed,
 
114
                                [{module,_},
 
115
                                 {line,_},
 
116
                                 {expression,_},
 
117
                                 {expected,true},
 
118
                                 {value,false}]},
 
119
                         _}}
 
120
                     = run_testfun(F)
 
121
             end),
 
122
      ?_test(begin
 
123
                 {?LINE, F} = ?_assertMatch(ok, ok),
 
124
                 {ok, ok} = run_testfun(F)
 
125
             end),
 
126
      ?_test(begin
 
127
                 {?LINE, F} = ?_assertMatch([_], []),
 
128
                 {error,{error,{assertMatch_failed,
 
129
                                [{module,_},
 
130
                                 {line,_},
 
131
                                 {expression,_},
 
132
                                 {expected,"[ _ ]"},
 
133
                                 {value,[]}]},
 
134
                         _}}
 
135
                     = run_testfun(F)
 
136
             end),
 
137
      ?_test(begin
 
138
                 {?LINE, F} = ?_assertEqual(ok, ok),
 
139
                 {ok, ok} = run_testfun(F)
 
140
             end),
 
141
      ?_test(begin
 
142
                 {?LINE, F} = ?_assertEqual(3, 1+1),
 
143
                 {error,{error,{assertEqual_failed,
 
144
                                [{module,_},
 
145
                                 {line,_},
 
146
                                 {expression,_},
 
147
                                 {expected,3},
 
148
                                 {value,2}]},
 
149
                         _}}
 
150
                     = run_testfun(F)
 
151
             end),
 
152
      ?_test(begin
 
153
                 {?LINE, F} = ?_assertException(error, badarith,
 
154
                                                erlang:error(badarith)),
 
155
                 {ok, ok} = run_testfun(F)
 
156
             end),
 
157
      ?_test(begin
 
158
                 {?LINE, F} = ?_assertException(error, badarith, ok),
 
159
                 {error,{error,{assertException_failed,
 
160
                                [{module,_},
 
161
                                 {line,_},
 
162
                                 {expression,_},
 
163
                                 {expected,_},
 
164
                                 {unexpected_success,ok}]},
 
165
                         _}}
 
166
                     = run_testfun(F)
 
167
             end),
 
168
      ?_test(begin
 
169
                 {?LINE, F} = ?_assertException(error, badarg,
 
170
                                                erlang:error(badarith)),
 
171
                 {error,{error,{assertException_failed,
 
172
                                [{module,_},
 
173
                                 {line,_},
 
174
                                 {expression,_},
 
175
                                 {expected,_},
 
176
                                 {unexpected_exception,
 
177
                                  {error,badarith,_}}]},
 
178
                         _}}
 
179
                     = run_testfun(F)
 
180
             end)
 
181
     ]}.
 
182
-endif.
 
183
 
 
184
 
 
185
%% ---------------------------------------------------------------------
 
186
%% Wrapper for simple "named function" tests ({M,F}), which provides
 
187
%% better error reporting when the function is missing at test time.
 
188
%%
 
189
%% Note that the wrapper fun is usually called by run_testfun/1, and the
 
190
%% special exceptions thrown here are expected to be handled there.
 
191
%%
 
192
%% @throws {eunit_internal, wrapperError()}
 
193
%%
 
194
%% @type wrapperError() = {no_such_function, mfa()}
 
195
%%                      | {module_not_found, moduleName()}
 
196
 
 
197
function_wrapper(M, F) ->
 
198
    fun () ->
 
199
            try M:F()
 
200
            catch
 
201
                error:undef ->
 
202
                    %% Check if it was M:F/0 that was undefined
 
203
                    case erlang:module_loaded(M) of
 
204
                        false ->
 
205
                            fail({module_not_found, M});
 
206
                        true ->
 
207
                            case erlang:function_exported(M, F, 0) of
 
208
                                false ->
 
209
                                    fail({no_such_function, {M,F,0}});
 
210
                                true ->
 
211
                                    rethrow(error, undef, [{M,F,0}])
 
212
                            end
 
213
                    end
 
214
            end
 
215
    end.
 
216
 
 
217
rethrow(Class, Reason, Trace) ->
 
218
    erlang:raise(Class, Reason, get_stacktrace(Trace)).
 
219
 
 
220
fail(Term) ->
 
221
    throw({eunit_internal, Term}).                                 
 
222
 
 
223
 
 
224
-ifdef(TEST).
 
225
wrapper_test_() ->
 
226
    {"error handling in function wrapper",
 
227
     [?_assertException(throw, {module_not_found, eunit_nonexisting},
 
228
                        run_testfun(function_wrapper(eunit_nonexisting,test))),
 
229
      ?_assertException(throw,
 
230
                        {no_such_function, {?MODULE,nonexisting_test,0}},
 
231
                        run_testfun(function_wrapper(?MODULE,nonexisting_test))),
 
232
      ?_test({error, {error, undef, _T}}
 
233
             = run_testfun(function_wrapper(?MODULE,wrapper_test_exported_)))
 
234
     ]}.
 
235
 
 
236
%% this must be exported (done automatically by the autoexport transform)
 
237
wrapper_test_exported_() ->
 
238
    {ok, ?MODULE:nonexisting_function()}.
 
239
-endif.
 
240
 
 
241
 
 
242
%% ---------------------------------------------------------------------
 
243
%% Entering a setup-context, with guaranteed cleanup.
 
244
 
 
245
%% @spec (Setup, Cleanup, Instantiate, Callback) -> any()
 
246
%%    Setup = () -> any()
 
247
%%    Cleanup = (any()) -> any()
 
248
%%    Instantiate = (any()) -> tests()
 
249
%%    Callback = (tests()) -> any()
 
250
%% @throws {context_error, Error, eunit_lib:exception()}
 
251
%% Error = setup_failed | instantiation_failed | cleanup_failed
 
252
 
 
253
enter_context(Setup, Cleanup, Instantiate, Callback) ->
 
254
    try Setup() of
 
255
        R ->
 
256
            try Instantiate(R) of
 
257
                T ->
 
258
                    try Callback(T)  %% call back to client code
 
259
                    after
 
260
                        %% Always run cleanup; client may be an idiot
 
261
                        try Cleanup(R)
 
262
                        catch
 
263
                            Class:Term ->
 
264
                                context_error(cleanup_failed, Class, Term)
 
265
                        end
 
266
                    end
 
267
            catch
 
268
                Class:Term ->
 
269
                    context_error(instantiation_failed, Class, Term)
 
270
            end
 
271
    catch
 
272
        Class:Term ->
 
273
            context_error(setup_failed, Class, Term)
 
274
    end.
 
275
 
 
276
context_error(Type, Class, Term) ->
 
277
    throw({context_error, Type, {Class, Term, get_stacktrace()}}).
 
278
 
 
279
%% Instantiates a context with dummy values to make browsing possible
 
280
%% @throws {context_error, instantiation_failed, eunit_lib:exception()}
 
281
 
 
282
browse_context(I, F) ->
 
283
    %% Browse: dummy setup/cleanup and a wrapper for the instantiator
 
284
    I1 = fun (_) ->
 
285
                try eunit_lib:browse_fun(I) of
 
286
                    {_, T} -> T
 
287
                catch
 
288
                    Class:Term ->
 
289
                        context_error(instantiation_failed, Class, Term)
 
290
                end
 
291
         end,
 
292
    enter_context(fun ok/0, fun ok/1, I1, F).
 
293
 
 
294
ok() -> ok.
 
295
ok(_) -> ok.
 
296
 
 
297
%% This generates single setup/cleanup functions from a list of tuples
 
298
%% on the form {Tag, Setup, Cleanup}, where the setup function always
 
299
%% backs out correctly from partial completion.
 
300
 
 
301
multi_setup(List) ->
 
302
    {SetupAll, CleanupAll} = multi_setup(List, fun ok/1),
 
303
    %% must reverse back and forth here in order to present the list in
 
304
    %% "natural" order to the test instantiation function
 
305
    {fun () -> lists:reverse(SetupAll([])) end,
 
306
     fun (Rs) -> CleanupAll(lists:reverse(Rs)) end}.
 
307
 
 
308
multi_setup([{Tag, S, C} | Es], CleanupPrev) ->
 
309
    Cleanup = fun ([R | Rs]) ->
 
310
                      try C(R) of
 
311
                          _ -> CleanupPrev(Rs)
 
312
                      catch
 
313
                          Class:Term ->
 
314
                              throw({Tag, {Class, Term, get_stacktrace()}})
 
315
                      end
 
316
              end,
 
317
    {SetupRest, CleanupAll} = multi_setup(Es, Cleanup),
 
318
    {fun (Rs) ->
 
319
             try S() of
 
320
                 R ->
 
321
                     SetupRest([R|Rs])
 
322
             catch
 
323
                 Class:Term ->
 
324
                     CleanupPrev(Rs),
 
325
                     throw({Tag, {Class, Term, get_stacktrace()}})
 
326
             end
 
327
     end,
 
328
     CleanupAll};
 
329
multi_setup([{Tag, S} | Es], CleanupPrev) ->
 
330
    multi_setup([{Tag, S, fun ok/1} | Es], CleanupPrev);
 
331
multi_setup([], CleanupAll) ->
 
332
    {fun (Rs) -> Rs end, CleanupAll}.