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

« back to all changes in this revision

Viewing changes to lib/mnesia/test/mnesia_registry_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 1998-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_registry_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
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
33
all() -> 
 
34
    [good_dump, bad_dump].
 
35
 
 
36
groups() -> 
 
37
    [].
 
38
 
 
39
init_per_group(_GroupName, Config) ->
 
40
    Config.
 
41
 
 
42
end_per_group(_GroupName, Config) ->
 
43
    Config.
 
44
 
 
45
 
 
46
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
47
good_dump(doc) ->
 
48
    ["Dump a faked C-node registry"];
 
49
good_dump(suite) -> [];
 
50
good_dump(Config) when is_list(Config) ->
 
51
    [Node] = Nodes = ?acquire_nodes(1, Config),
 
52
    T1 = gordon,
 
53
    ?match(ok, mnesia_registry:create_table(T1)),
 
54
    One = {T1, 1, 0, integer, 0, 10},
 
55
    Two = {T1, "two", 3, integer, 0, 20},
 
56
    Three = {T1, 3, 0, string, 6, "thirty"},
 
57
    ?match(ok, mnesia:dirty_write(One)),
 
58
    ?match(ok, mnesia:dirty_write(Two)),
 
59
    ?match(ok, mnesia:dirty_write(Three)),
 
60
    ?match([One], mnesia:dirty_read({T1, 1})),
 
61
    ?match([_ | _], dump_registry(Node, T1)),
 
62
 
 
63
    NewOne = {T1, 1, 0, integer, 0, 1},
 
64
    NewFour = {T1, "4", 1, string, 4, "four"},
 
65
 
 
66
    ?match([NewOne], mnesia:dirty_read({T1, 1})),
 
67
    ?match([Two], mnesia:dirty_read({T1, "two"})),
 
68
    ?match([], mnesia:dirty_read({T1, 3})),
 
69
    ?match([NewFour], mnesia:dirty_read({T1, "4"})),
 
70
 
 
71
    T2 = blixt,
 
72
    ?match({'EXIT', {aborted, {no_exists, _}}},
 
73
           mnesia:dirty_read({T2, 1})),
 
74
    ?match([_ |_], dump_registry(Node, T2)),
 
75
 
 
76
    NewOne2 = setelement(1, NewOne, T2),
 
77
    NewFour2 = setelement(1, NewFour, T2),
 
78
 
 
79
    ?match([NewOne2], mnesia:dirty_read({T2, 1})),
 
80
    ?match([], mnesia:dirty_read({T2, "two"})),
 
81
    ?match([], mnesia:dirty_read({T2, 3})),
 
82
    ?match([NewFour2], mnesia:dirty_read({T2, "4"})),
 
83
    ?match([_One2, NewFour2], lists:sort(restore_registry(Node, T2))),
 
84
    
 
85
    ?verify_mnesia(Nodes, []).
 
86
 
 
87
dump_registry(Node, Tab) ->
 
88
    case rpc:call(Node, mnesia_registry, start_dump, [Tab, self()]) of
 
89
        Pid when is_pid(Pid) ->
 
90
            Pid ! {write, 1, 0, integer, 0, 1},
 
91
            Pid ! {delete, 3},
 
92
            Pid ! {write, "4", 1, string, 4, "four"},
 
93
            Pid ! {commit, self()},
 
94
            receive
 
95
                {ok, Pid} ->
 
96
                    [{Tab, "4", 1, string, 4, "four"},
 
97
                     {Tab, 1, 0, integer, 0, 1}];
 
98
                {'EXIT', Pid, Reason} ->
 
99
                    exit(Reason)
 
100
            end;
 
101
        {badrpc, Reason} ->
 
102
            exit(Reason)
 
103
    end.
 
104
 
 
105
restore_registry(Node, Tab) ->
 
106
    case rpc:call(Node, mnesia_registry, start_restore, [Tab, self()]) of
 
107
        {size, Pid, N, _LargestKeySize, _LargestValSize} ->
 
108
            Pid ! {send_records, self()},
 
109
            receive_records(Tab, N);
 
110
        {badrpc, Reason} ->
 
111
            exit(Reason)
 
112
    end.
 
113
 
 
114
receive_records(Tab, N) when N > 0 ->
 
115
    receive
 
116
        {restore, KeySize, ValSize, ValType, Key, Val} -> 
 
117
            [{Tab, Key, KeySize, ValType, ValSize, Val} | receive_records(Tab, N -1)];
 
118
        {'EXIT', _Pid, Reason} ->
 
119
            exit(Reason)
 
120
    end;
 
121
receive_records(_Tab, 0) ->
 
122
    [].
 
123
 
 
124
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
125
bad_dump(doc) ->
 
126
    ["Intentionally fail with the dump of a faked C-node registry"];
 
127
bad_dump(suite) -> [];
 
128
bad_dump(Config) when is_list(Config) ->
 
129
    [Node] = Nodes = ?acquire_nodes(1, Config),
 
130
    
 
131
    OldTab = ming,
 
132
    ?match({'EXIT', {aborted, _}}, mnesia_registry:start_restore(no_tab, self())),
 
133
    ?match({atomic, ok}, mnesia:create_table(OldTab, [{attributes, [a,b,c,d,e,f,g,h,i,j,k,l,m,n,o,p,q]}])),
 
134
    ?match({'EXIT',{aborted,{bad_type,_}}}, dump_registry(Node, OldTab)),
 
135
    ?match(stopped, mnesia:stop()),
 
136
 
 
137
    ?match({'EXIT', {aborted, _}}, mnesia_registry:create_table(down_table)),
 
138
    ?match({'EXIT', {aborted, _}}, mnesia_registry:start_restore(no_tab, self())),
 
139
    ?match({'EXIT', {aborted, _}}, dump_registry(Node, down_dump)),
 
140
 
 
141
    ?verify_mnesia([], Nodes).
 
142