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

« back to all changes in this revision

Viewing changes to lib/mnesia/test/mnesia_examples_test.erl

  • 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 1997-2010. 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
-module(mnesia_examples_test).
 
22
-author('hakan@erix.ericsson.se').
 
23
-compile([export_all]).
 
24
-include("mnesia_test_lib.hrl").
 
25
 
 
26
init_per_testcase(Func, Conf) ->
 
27
    mnesia_test_lib:init_per_testcase(Func, Conf).
 
28
 
 
29
end_per_testcase(Func, Conf) ->
 
30
    mnesia_test_lib:end_per_testcase(Func, Conf).
 
31
 
 
32
-define(init(N, Config),
 
33
        mnesia_test_lib:prepare_test_case([{init_test_case, [mnesia]},
 
34
                                           delete_schema],
 
35
                                          N, Config, ?FILE, ?LINE)).
 
36
 
 
37
opt_net_load(ExampleMod) ->
 
38
    opt_net_load([node() | nodes()], ExampleMod, ok).
 
39
 
 
40
opt_net_load([Node | Nodes], ExampleMod, Res) ->
 
41
    case rpc:call(Node, ?MODULE, opt_load, [ExampleMod]) of
 
42
        {module, ExampleMod} ->
 
43
            opt_net_load(Nodes, ExampleMod, Res);
 
44
        {error, Reason} ->
 
45
            Error = {opt_net_load, ExampleMod, Node, Reason},
 
46
            opt_net_load(Nodes, ExampleMod, {error, Error});
 
47
        {badrpc, Reason} ->
 
48
            Error = {opt_net_load, ExampleMod, Node, Reason},
 
49
            opt_net_load(Nodes, ExampleMod, {error, Error})
 
50
    end;
 
51
opt_net_load([], _ExampleMod, Res) ->
 
52
    Res.
 
53
            
 
54
opt_load(Mod) ->
 
55
    case code:is_loaded(Mod) of
 
56
        {file, _} ->
 
57
            {module, Mod};
 
58
        false ->
 
59
            Abs = filename:join([code:lib_dir(mnesia), examples, Mod]),
 
60
            code:load_abs(Abs)
 
61
    end.
 
62
 
 
63
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
64
all() -> 
 
65
    [bup, company, meter, {group, tpcb}].
 
66
 
 
67
groups() -> 
 
68
    [{tpcb, [],
 
69
      [replica_test, sticky_replica_test, dist_test,
 
70
       conflict_test, frag_test, frag2_test, remote_test,
 
71
       remote_frag2_test]}].
 
72
 
 
73
init_per_group(_GroupName, Config) ->
 
74
    Config.
 
75
 
 
76
end_per_group(_GroupName, Config) ->
 
77
    Config.
 
78
 
 
79
 
 
80
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
81
bup(doc) -> ["Run the backup examples in bup.erl"];
 
82
bup(suite) -> [];
 
83
bup(Config) when is_list(Config) ->
 
84
    Nodes = ?init(3, Config),
 
85
    opt_net_load(bup),
 
86
    ?match(ok, bup:test(Nodes)).
 
87
 
 
88
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
89
company(doc) ->
 
90
    ["Run the company examples in company.erl and company_o.erl"].
 
91
 
 
92
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
93
 
 
94
replica_test(suite) -> [];
 
95
replica_test(Config) when is_list(Config) ->
 
96
    ?init(3, Config),
 
97
    opt_net_load(mnesia_tpcb),
 
98
    ?match({ok, _}, mnesia_tpcb:start(mnesia_tpcb:config(replica_test, ram_copies))).
 
99
 
 
100
sticky_replica_test(suite) -> [];
 
101
sticky_replica_test(Config) when is_list(Config) ->
 
102
    ?init(3, Config),
 
103
    opt_net_load(mnesia_tpcb),
 
104
    ?match({ok, _}, mnesia_tpcb:start(mnesia_tpcb:config(sticky_replica_test, ram_copies))).
 
105
 
 
106
dist_test(suite) -> [];
 
107
dist_test(Config) when is_list(Config) ->
 
108
    ?init(3, [{tc_timeout, timer:minutes(10)} | Config]),
 
109
    opt_net_load(mnesia_tpcb),
 
110
    ?match({ok, _}, mnesia_tpcb:start(mnesia_tpcb:config(dist_test, ram_copies))).
 
111
 
 
112
conflict_test(suite) -> [];
 
113
conflict_test(Config) when is_list(Config) ->
 
114
    ?init(3, Config),
 
115
    opt_net_load(mnesia_tpcb),
 
116
    ?match({ok, _}, mnesia_tpcb:start(mnesia_tpcb:config(conflict_test, ram_copies))).
 
117
 
 
118
frag_test(suite) -> [];
 
119
frag_test(Config) when is_list(Config) ->
 
120
    ?init(3, Config),
 
121
    opt_net_load(mnesia_tpcb),
 
122
    ?match({ok, _}, mnesia_tpcb:start(mnesia_tpcb:config(frag_test, ram_copies))).
 
123
 
 
124
frag2_test(suite) -> [];
 
125
frag2_test(Config) when is_list(Config) ->
 
126
    ?init(3, Config),
 
127
    opt_net_load(mnesia_tpcb),
 
128
    ?match({ok, _}, mnesia_tpcb:start(mnesia_tpcb:config(frag2_test, ram_copies))).
 
129
 
 
130
remote_test(suite) -> [];
 
131
remote_test(Config) when is_list(Config) ->
 
132
    ?init(3, Config),
 
133
    opt_net_load(mnesia_tpcb),
 
134
    ?match({ok, _}, mnesia_tpcb:start(mnesia_tpcb:config(remote_test, ram_copies))).
 
135
 
 
136
remote_frag2_test(suite) -> [];
 
137
remote_frag2_test(Config) when is_list(Config) ->
 
138
    ?init(3, Config),
 
139
    opt_net_load(mnesia_tpcb),
 
140
    ?match({ok, _}, mnesia_tpcb:start(mnesia_tpcb:config(remote_frag2_test, ram_copies))).
 
141
 
 
142
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
143
meter(doc) ->
 
144
    ["Run the meter example in mnesia_meter.erl"];
 
145
meter(suite) ->
 
146
    [];
 
147
meter(Config) when is_list(Config) ->
 
148
    [N | _] = ?init(3, Config),
 
149
    opt_net_load(mnesia_meter),
 
150
    ?match(ok, mnesia_meter:go(ram_copies, [N])).
 
151
 
 
152