~rdoering/ubuntu/karmic/erlang/fix-535090

« back to all changes in this revision

Viewing changes to lib/eunit/include/eunit.hrl

  • Committer: Bazaar Package Importer
  • Author(s): Sergei Golovan
  • Date: 2009-02-15 16:42:52 UTC
  • mfrom: (3.1.2 squeeze)
  • Revision ID: james.westby@ubuntu.com-20090215164252-q5x4rcf8a5pbesb1
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
%% Copyright (C) 2004-2006 Micka�l R�mond, Richard Carlsson
 
19
 
 
20
%% Including this file turns on testing and defines TEST, unless NOTEST
 
21
%% is defined before the file is included. If both NOTEST and TEST are
 
22
%% already defined, then TEST takes precedence, and NOTEST will become
 
23
%% undefined.
 
24
%%
 
25
%% If including this file causes TEST to be defined, then NOASSERT will
 
26
%% be undefined, even if it was previously defined. If both ASSERT and
 
27
%% NOASSERT are defined before the file is included, then ASSERT takes
 
28
%% precedence, and NOASSERT will become undefined regardless of TEST.
 
29
%% 
 
30
%% After including this file, EUNIT will be defined if and only if TEST
 
31
%% is defined.
 
32
 
 
33
-ifndef(EUNIT_HRL).
 
34
-define(EUNIT_HRL, true).
 
35
 
 
36
%% allow defining TEST to override NOTEST
 
37
-ifdef(TEST).
 
38
-undef(NOTEST).
 
39
-endif.
 
40
 
 
41
%% allow NODEBUG to imply NOASSERT, unless overridden below
 
42
-ifdef(NODEBUG).
 
43
-ifndef(NOASSERT).
 
44
-define(NOASSERT, true).
 
45
-endif.
 
46
-endif.
 
47
 
 
48
%% note that the main switch used within this file is NOTEST; however,
 
49
%% both TEST and EUNIT may be used to check whether testing is enabled
 
50
-ifndef(NOTEST).
 
51
-undef(NOASSERT).    % testing requires that assertions are enabled
 
52
-ifndef(TEST).
 
53
-define(TEST, true).
 
54
-endif.
 
55
-ifndef(EUNIT).
 
56
-define(EUNIT, true).
 
57
-endif.
 
58
-else.
 
59
-undef(EUNIT).
 
60
-endif.
 
61
 
 
62
%% allow ASSERT to override NOASSERT (regardless of TEST/NOTEST)
 
63
-ifdef(ASSERT).
 
64
-undef(NOASSERT).
 
65
-endif.
 
66
 
 
67
%% Parse transforms for automatic exporting/stripping of test functions.
 
68
%% (Note that although automatic stripping is convenient, it will make
 
69
%% the code dependent on this header file and the eunit_striptests
 
70
%% module for compilation, even when testing is switched off! Using
 
71
%% -ifdef(EUNIT) around all test code makes the program more portable.)
 
72
 
 
73
-ifndef(EUNIT_NOAUTO).
 
74
-ifndef(NOTEST).
 
75
-compile({parse_transform, eunit_autoexport}).
 
76
-else.
 
77
-compile({parse_transform, eunit_striptests}).
 
78
-endif.
 
79
-endif.
 
80
 
 
81
%% All macros should be available even if testing is turned off, and
 
82
%% should preferably not require EUnit to be present at runtime.
 
83
%% 
 
84
%% We must use fun-call wrappers ((fun () -> ... end)()) to avoid
 
85
%% exporting local variables, and furthermore we only use variable names
 
86
%% prefixed with "__", that hopefully will not be bound outside the fun.
 
87
 
 
88
%% A generic let-macro is particularly useful when writing test cases.
 
89
%% It is more compact than 'begin X = Y, Z end', and guarantees that
 
90
%% X gets a new, local binding.
 
91
%% (Note that lowercase 'let' is a reserved word.)
 
92
-ifndef(LET).
 
93
-define(LET(X,Y,Z), ((fun(X)->(Z)end)(Y))).
 
94
-endif.
 
95
 
 
96
%% It is important that testing code is short and readable.
 
97
%% An if-then-else macro can make some code much more compact.
 
98
%% Compare:  case f(X) of true->g(X); false->h(X) end
 
99
%%     and:  ?IF(f(X), g(Y), h(Z))
 
100
-ifndef(IF).
 
101
-define(IF(B,T,F), (case (B) of true->(T); false->(F) end)).
 
102
-endif.
 
103
 
 
104
-ifdef(NOASSERT).
 
105
%% The plain assert macro should be defined to do nothing if this file
 
106
%% is included when debugging/testing is turned off.
 
107
-ifndef(assert).
 
108
-define(assert(BoolExpr),ok).
 
109
-endif.
 
110
-else.
 
111
%% The assert macro is written the way it is so as not to cause warnings
 
112
%% for clauses that cannot match, even if the expression is a constant.
 
113
-undef(assert).
 
114
-define(assert(BoolExpr),
 
115
        ((fun () ->
 
116
            case (BoolExpr) of
 
117
                true -> ok;
 
118
                __V -> .erlang:error({assertion_failed,
 
119
                                      [{module, ?MODULE},
 
120
                                       {line, ?LINE},
 
121
                                       {expression, (??BoolExpr)},
 
122
                                       {expected, true},
 
123
                                       {value, case __V of false -> __V;
 
124
                                                   _ -> {not_a_boolean,__V}
 
125
                                               end}]})
 
126
            end
 
127
          end)())).
 
128
-endif.
 
129
-define(assertNot(BoolExpr), ?assert(not (BoolExpr))).
 
130
 
 
131
-define(_test(Expr), {?LINE, fun () -> (Expr) end}).
 
132
 
 
133
-define(_assert(BoolExpr), ?_test(?assert(BoolExpr))).
 
134
 
 
135
-define(_assertNot(BoolExpr), ?_assert(not (BoolExpr))).
 
136
 
 
137
%% This is mostly a convenience which gives more detailed reports.
 
138
%% Note: Guard is a guarded pattern, and can not be used for value.
 
139
-ifdef(NOASSERT).
 
140
-define(assertMatch(Guard,Expr),ok).
 
141
-else.
 
142
-define(assertMatch(Guard, Expr),
 
143
        ((fun () ->
 
144
            case (Expr) of
 
145
                Guard -> ok;
 
146
                __V -> .erlang:error({assertMatch_failed,
 
147
                                      [{module, ?MODULE},
 
148
                                       {line, ?LINE},
 
149
                                       {expression, (??Expr)},
 
150
                                       {expected, (??Guard)},
 
151
                                       {value, __V}]})
 
152
            end
 
153
          end)())).
 
154
-endif.
 
155
-define(_assertMatch(Guard, Expr), ?_test(?assertMatch(Guard, Expr))).
 
156
 
 
157
%% This is a convenience macro which gives more detailed reports when
 
158
%% the expected LHS value is not a pattern, but a computed value
 
159
-ifdef(NOASSERT).
 
160
-define(assertEqual(Expect,Expr),ok).
 
161
-else.
 
162
-define(assertEqual(Expect, Expr),
 
163
        ((fun (__X) ->
 
164
            case (Expr) of
 
165
                __X -> ok;
 
166
                __V -> .erlang:error({assertEqual_failed,
 
167
                                      [{module, ?MODULE},
 
168
                                       {line, ?LINE},
 
169
                                       {expression, (??Expr)},
 
170
                                       {expected, __X},
 
171
                                       {value, __V}]})
 
172
            end
 
173
          end)(Expect))).
 
174
-endif.
 
175
-define(_assertEqual(Expect, Expr), ?_test(?assertEqual(Expect, Expr))).
 
176
 
 
177
%% Note: Class and Term are patterns, and can not be used for value.
 
178
-ifdef(NOASSERT).
 
179
-define(assertException(Class, Term, Expr),ok).
 
180
-else.
 
181
-define(assertException(Class, Term, Expr),
 
182
        ((fun () ->
 
183
            try (Expr) of
 
184
                __V -> .erlang:error({assertException_failed,
 
185
                                      [{module, ?MODULE},
 
186
                                       {line, ?LINE},
 
187
                                       {expression, (??Expr)},
 
188
                                       {expected,
 
189
                                        "{ "++(??Class)++" , "++(??Term)
 
190
                                        ++" , [...] }"},
 
191
                                       {unexpected_success, __V}]})
 
192
            catch
 
193
                Class:Term -> ok;
 
194
                __C:__T ->
 
195
                    .erlang:error({assertException_failed,
 
196
                                   [{module, ?MODULE},
 
197
                                    {line, ?LINE},
 
198
                                    {expression, (??Expr)},
 
199
                                    {expected,
 
200
                                     "{ "++(??Class)++" , "++(??Term)
 
201
                                     ++" , [...] }"},
 
202
                                    {unexpected_exception,
 
203
                                     {__C, __T, erlang:get_stacktrace()}}]})
 
204
            end
 
205
          end)())).
 
206
-endif.
 
207
 
 
208
-define(assertError(Term, Expr), ?assertException(error, Term, Expr)).
 
209
-define(assertExit(Term, Expr), ?assertException(exit, Term, Expr)).
 
210
-define(assertThrow(Term, Expr), ?assertException(throw, Term, Expr)).
 
211
 
 
212
-define(_assertException(Class, Term, Expr),
 
213
        ?_test(?assertException(Class, Term, Expr))).
 
214
-define(_assertError(Term, Expr), ?_assertException(error, Term, Expr)).
 
215
-define(_assertExit(Term, Expr), ?_assertException(exit, Term, Expr)).
 
216
-define(_assertThrow(Term, Expr), ?_assertException(throw, Term, Expr)).
 
217
 
 
218
%% Macros for running operating system commands. (Note that these
 
219
%% require EUnit to be present at runtime, or at least eunit_lib.)
 
220
 
 
221
%% these can be used for simply running commands in a controlled way
 
222
-define(_cmd_(Cmd), (.eunit_lib:command(Cmd))).
 
223
-define(cmdStatus(N, Cmd),
 
224
        ((fun () ->
 
225
            case ?_cmd_(Cmd) of
 
226
                {(N), __Out} -> __Out;
 
227
                {__N, _} -> .erlang:error({command_failed,
 
228
                                           [{module, ?MODULE},
 
229
                                            {line, ?LINE},
 
230
                                            {command, (Cmd)},
 
231
                                            {expected_status,(N)},
 
232
                                            {status,__N}]})
 
233
            end
 
234
          end)())).
 
235
-define(_cmdStatus(N, Cmd), ?_test(?cmdStatus(N, Cmd))).
 
236
-define(cmd(Cmd), ?cmdStatus(0, Cmd)).
 
237
-define(_cmd(Cmd), ?_test(?cmd(Cmd))).
 
238
 
 
239
%% these are only used for testing; they always return 'ok' on success,
 
240
%% and have no effect if debugging/testing is turned off
 
241
-ifdef(NOASSERT).
 
242
-define(assertCmdStatus(N, Cmd),ok).
 
243
-else.
 
244
-define(assertCmdStatus(N, Cmd),
 
245
        ((fun () ->
 
246
            case ?_cmd_(Cmd) of
 
247
                {(N), _} -> ok;
 
248
                {__N, _} -> .erlang:error({assertCmd_failed,
 
249
                                           [{module, ?MODULE},
 
250
                                            {line, ?LINE},
 
251
                                            {command, (Cmd)},
 
252
                                            {expected_status,(N)},
 
253
                                            {status,__N}]})
 
254
            end
 
255
          end)())).
 
256
-endif.
 
257
-define(assertCmd(Cmd), ?assertCmdStatus(0, Cmd)).
 
258
 
 
259
-ifdef(NOASSERT).
 
260
-define(assertCmdOutput(T, Cmd),ok).
 
261
-else.
 
262
-define(assertCmdOutput(T, Cmd),
 
263
        ((fun () ->
 
264
            case ?_cmd_(Cmd) of
 
265
                {_, (T)} -> ok;
 
266
                {_, __T} -> .erlang:error({assertCmdOutput_failed,
 
267
                                           [{module, ?MODULE},
 
268
                                            {line, ?LINE},
 
269
                                            {command,(Cmd)},
 
270
                                            {expected_output,(T)},
 
271
                                            {output,__T}]})
 
272
            end
 
273
          end)())).
 
274
-endif.
 
275
 
 
276
-define(_assertCmdStatus(N, Cmd), ?_test(?assertCmdStatus(N, Cmd))).
 
277
-define(_assertCmd(Cmd), ?_test(?assertCmd(Cmd))).
 
278
-define(_assertCmdOutput(T, Cmd), ?_test(?assertCmdOutput(T, Cmd))).
 
279
 
 
280
%% Macros to simplify debugging (in particular, they work even when the
 
281
%% standard output is being redirected by EUnit while running tests)
 
282
 
 
283
-ifdef(NODEBUG).
 
284
-define(debugMsg(S), ok).
 
285
-define(debugHere, ok).
 
286
-define(debugFmt(S, As), ok).
 
287
-define(debugVal(E), (E)).
 
288
-define(debugTime(S,E), (E)).
 
289
-else.
 
290
-define(debugMsg(S),
 
291
        (begin
 
292
             io:fwrite(user, <<"~s:~w: ~s\n">>,
 
293
                       [?FILE, ?LINE, S]),
 
294
             ok
 
295
         end)).
 
296
-define(debugHere, (?debugMsg("<-"))).
 
297
-define(debugFmt(S, As), (?debugMsg(io_lib:format((S), (As))))).
 
298
-define(debugVal(E),
 
299
        ((fun (__V) ->
 
300
                  ?debugFmt(<<"~s = ~P">>, [(??E), __V, 15]),
 
301
                  __V
 
302
          end)(E))).
 
303
-define(debugTime(S,E),
 
304
        ((fun () ->
 
305
                  {__T0, _} = statistics(wall_clock),
 
306
                  __V = (E),
 
307
                  {__T1, _} = statistics(wall_clock),
 
308
                  ?debugFmt(<<"~s: ~.3f s">>, [(S), (__T1-__T0)/1000]),
 
309
                  __V
 
310
          end)())).
 
311
-endif.
 
312
 
 
313
-endif. % EUNIT_HRL