~ubuntu-branches/ubuntu/trusty/erlang/trusty

« back to all changes in this revision

Viewing changes to lib/mnesia/test/mnesia_test_lib.hrl

  • Committer: Bazaar Package Importer
  • Author(s): Clint Byrum
  • Date: 2011-05-05 15:48:43 UTC
  • mfrom: (3.5.13 sid)
  • Revision ID: james.westby@ubuntu.com-20110505154843-0om6ekzg6m7ugj27
Tags: 1:14.b.2-dfsg-3ubuntu1
* Merge from debian unstable.  Remaining changes:
  - Drop libwxgtk2.8-dev build dependency. Wx isn't in main, and not
    supposed to.
  - Drop erlang-wx binary.
  - Drop erlang-wx dependency from -megaco, -common-test, and -reltool, they
    do not really need wx. Also drop it from -debugger; the GUI needs wx,
    but it apparently has CLI bits as well, and is also needed by -megaco,
    so let's keep the package for now.
  - debian/patches/series: Do what I meant, and enable build-options.patch
    instead.
* Additional changes:
  - Drop erlang-wx from -et
* Dropped Changes:
  - patches/pcre-crash.patch: CVE-2008-2371: outer level option with
    alternatives caused crash. (Applied Upstream)
  - fix for ssl certificate verification in newSSL: 
    ssl_cacertfile_fix.patch (Applied Upstream)
  - debian/patches/series: Enable native.patch again, to get stripped beam
    files and reduce the package size again. (build-options is what
    actually accomplished this)
  - Remove build-options.patch on advice from upstream and because it caused
    odd build failures.

Show diffs side-by-side

added added

removed removed

Lines of Context:
 
1
%%
 
2
%% %CopyrightBegin%
 
3
%% 
 
4
%% Copyright Ericsson AB 1996-2011. 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
 
 
20
%%
 
21
-define(log(Format,Args),mnesia_test_lib:log(Format,Args,?FILE,?LINE)).
 
22
-define(warning(Format,Args),?log("<>WARNING<>~n " ++ Format,Args)).
 
23
-define(error(Format,Args),
 
24
        mnesia_test_lib:error(Format,Args,?FILE,?LINE)).
 
25
-define(verbose(Format,Args),mnesia_test_lib:verbose(Format,Args,?FILE,?LINE)).
 
26
 
 
27
-define(fatal(Format,Args),
 
28
        ?error(Format, Args),
 
29
        exit({test_case_fatal, Format, Args, ?FILE, ?LINE})).
 
30
 
 
31
-define(skip(Format,Args),
 
32
        ?warning(Format, Args),
 
33
        exit({skipped, ?flat_format(Format, Args)})).
 
34
 
 
35
-define(flat_format(Format,Args),
 
36
        lists:flatten(io_lib:format(Format, Args))).
 
37
 
 
38
-define(sort(What), mnesia_test_lib:sort(What)).
 
39
 
 
40
-define(ignore(Expr),
 
41
        fun() ->
 
42
                AcTuAlReS = (catch (Expr)),
 
43
                ?verbose("ok, ~n Result as expected:~p~n",[AcTuAlReS]),
 
44
                AcTuAlReS
 
45
        end()).
 
46
 
 
47
-define(match(ExpectedRes,Expr),
 
48
        fun() ->
 
49
                AcTuAlReS = (catch (Expr)),
 
50
                case AcTuAlReS of
 
51
                    ExpectedRes ->
 
52
                        ?verbose("ok, ~n Result as expected:~p~n",[AcTuAlReS]),
 
53
                        {success,AcTuAlReS};
 
54
                    _ ->
 
55
                        ?error("Not Matching Actual result was:~n ~p~n",
 
56
                               [AcTuAlReS]),
 
57
                        {fail,AcTuAlReS}
 
58
                end
 
59
        end()).
 
60
 
 
61
-define(match_inverse(NotExpectedRes,Expr),
 
62
        fun() ->
 
63
                AcTuAlReS = (catch (Expr)),
 
64
                case AcTuAlReS of
 
65
                    NotExpectedRes ->
 
66
                        ?error("Not matching Actual result was:~n ~p~n",
 
67
                               [AcTuAlReS]),
 
68
                        {fail,AcTuAlReS};
 
69
                    _ ->
 
70
                        ?verbose("ok, ~n Result as expected: ~p~n",[AcTuAlReS]),
 
71
                        {success,AcTuAlReS}
 
72
                end
 
73
        end()).
 
74
 
 
75
-define(match_receive(ExpectedMsg),
 
76
        ?match(ExpectedMsg,mnesia_test_lib:pick_msg())).
 
77
 
 
78
%% ExpectedMsgs must be completely bound
 
79
-define(match_multi_receive(ExpectedMsgs),
 
80
        fun() ->
 
81
                TmPeXpCtEdMsGs = lists:sort(ExpectedMsgs),
 
82
                ?match(TmPeXpCtEdMsGs,
 
83
                       lists:sort(lists:map(fun(_) ->
 
84
                                                    mnesia_test_lib:pick_msg()
 
85
                                            end,
 
86
                                            TmPeXpCtEdMsGs)))
 
87
        end()).
 
88
 
 
89
-define(start_activities(Nodes),
 
90
        mnesia_test_lib:start_activities(Nodes)).
 
91
 
 
92
-define(start_transactions(Pids),
 
93
        mnesia_test_lib:start_transactions(Pids)).
 
94
 
 
95
-define(acquire_nodes(N, Config),
 
96
        mnesia_test_lib:prepare_test_case([{init_test_case, [mnesia]},
 
97
                                           delete_schema,
 
98
                                           create_schema,
 
99
                                           {start_appls, [mnesia]}],
 
100
                                          N, Config, ?FILE, ?LINE)).
 
101
 
 
102
-define(activate_debug_fun(I, F, C),
 
103
        mnesia_lib:activate_debug_fun(I, F, C, ?FILE, ?LINE)).
 
104
 
 
105
-define(remote_activate_debug_fun(N, I, F, C),
 
106
        ?match(ok, mnesia_test_lib:remote_activate_debug_fun(N, I, F, C,
 
107
                                                             ?FILE, ?LINE))).
 
108
 
 
109
-define(deactivate_debug_fun(I),
 
110
        mnesia_lib:deactivate_debug_fun(I, ?FILE, ?LINE)).
 
111
 
 
112
-define(remote_deactivate_debug_fun(N, I),
 
113
        rpc:call(N, mnesia_lib, deactivate_debug_fun, [I, ?FILE, ?LINE])).
 
114
 
 
115
-define(is_debug_compiled, 
 
116
        case mnesia_lib:is_debug_compiled() of
 
117
            false ->
 
118
                ?skip("Mnesia is not debug compiled, test case ignored.~n", []);
 
119
            _OhTeR ->
 
120
                ok
 
121
        end).
 
122
 
 
123
-define(needs_disc(Config), 
 
124
        case mnesia_test_lib:diskless(Config) of
 
125
            false ->
 
126
                ok;
 
127
            true ->
 
128
                ?skip("Must have disc, test case ignored.~n", [])
 
129
        end).
 
130
 
 
131
-define(verify_mnesia(Ups, Downs), 
 
132
        mnesia_test_lib:verify_mnesia(Ups, Downs, ?FILE, ?LINE)).