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

« back to all changes in this revision

Viewing changes to lib/dialyzer/test/r9c_tests_SUITE_data/src/mnesia/mnesia_registry.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
%% ``The contents of this file are subject to the Erlang Public License,
 
2
%% Version 1.1, (the "License"); you may not use this file except in
 
3
%% compliance with the License. You should have received a copy of the
 
4
%% Erlang Public License along with this software. If not, it can be
 
5
%% retrieved via the world wide web at http://www.erlang.org/.
 
6
%% 
 
7
%% Software distributed under the License is distributed on an "AS IS"
 
8
%% basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See
 
9
%% the License for the specific language governing rights and limitations
 
10
%% under the License.
 
11
%% 
 
12
%% The Initial Developer of the Original Code is Ericsson Utvecklings AB.
 
13
%% Portions created by Ericsson are Copyright 1999, Ericsson Utvecklings
 
14
%% AB. All Rights Reserved.''
 
15
%% 
 
16
%%     $Id: mnesia_registry.erl,v 1.2 2010/03/04 13:54:19 maria Exp $
 
17
%%
 
18
-module(mnesia_registry).
 
19
 
 
20
%%%----------------------------------------------------------------------
 
21
%%% File    : mnesia_registry.erl
 
22
%%% Purpose : Support dump and restore of a registry on a C-node
 
23
%%%           This is an OTP internal module and is not public available.
 
24
%%%
 
25
%%% Example : Dump some hardcoded records into the Mnesia table Tab
 
26
%%%
 
27
%%%       case rpc:call(Node, mnesia_registry, start_dump, [Tab, self()]) of
 
28
%%%          Pid when pid(Pid) ->
 
29
%%%              Pid ! {write, key1, key_size1, val_type1, val_size1, val1},
 
30
%%%              Pid ! {delete, key3},
 
31
%%%              Pid ! {write, key2, key_size2, val_type2, val_size2, val2},
 
32
%%%              Pid ! {write, key4, key_size4, val_type4, val_size4, val4},
 
33
%%%              Pid ! {commit, self()},
 
34
%%%              receive
 
35
%%%                  {ok, Pid} ->
 
36
%%%                      ok;
 
37
%%%                  {'EXIT', Pid, Reason} ->
 
38
%%%                      exit(Reason)
 
39
%%%              end;
 
40
%%%          {badrpc, Reason} ->
 
41
%%%              exit(Reason)
 
42
%%%      end.
 
43
%%%
 
44
%%% Example : Restore the corresponding Mnesia table Tab
 
45
%%%
 
46
%%%       case rpc:call(Node, mnesia_registry, start_restore, [Tab, self()]) of
 
47
%%%          {size, Pid, N, LargestKey, LargestVal} ->
 
48
%%%              Pid ! {send_records, self()},
 
49
%%%              Fun = fun() ->
 
50
%%%                        receive
 
51
%%%                            {restore, KeySize, ValSize, ValType, Key, Val} -> 
 
52
%%%                                {Key, Val};
 
53
%%%                            {'EXIT', Pid, Reason} ->
 
54
%%%                                exit(Reason)
 
55
%%%                        end
 
56
%%%                    end,
 
57
%%%              lists:map(Fun, lists:seq(1, N));
 
58
%%%          {badrpc, Reason} ->
 
59
%%%              exit(Reason)
 
60
%%%      end.
 
61
%%%
 
62
%%%----------------------------------------------------------------------
 
63
 
 
64
%% External exports
 
65
-export([start_dump/2, start_restore/2]).
 
66
-export([create_table/1, create_table/2]).
 
67
 
 
68
%% Internal exports 
 
69
-export([init/4]).
 
70
 
 
71
-record(state, {table, ops = [], link_to}).
 
72
 
 
73
-record(registry_entry, {key, key_size, val_type, val_size, val}).
 
74
 
 
75
-record(size, {pid = self(), n_values = 0, largest_key = 0, largest_val = 0}).
 
76
 
 
77
%%%----------------------------------------------------------------------
 
78
%%% Client
 
79
%%%----------------------------------------------------------------------
 
80
 
 
81
start(Type, Tab, LinkTo) ->
 
82
    Starter = self(),
 
83
    Args = [Type, Starter, LinkTo, Tab],
 
84
    Pid = spawn_link(?MODULE, init, Args),
 
85
    %% The receiver process may unlink the current process
 
86
    receive
 
87
        {ok, Res} ->
 
88
            Res;
 
89
        {'EXIT', Pid, Reason} when LinkTo == Starter ->
 
90
            exit(Reason)
 
91
    end.
 
92
 
 
93
%% Starts a receiver process and optionally creates a Mnesia table
 
94
%% with suitable default values. Returns the Pid of the receiver process
 
95
%% 
 
96
%% The receiver process accumulates Mnesia operations and performs
 
97
%% all operations or none at commit. The understood messages are:
 
98
%% 
 
99
%%    {write, Key, KeySize, ValType, ValSize, Val} ->
 
100
%%        accumulates mnesia:write({Tab, Key, KeySize, ValType, ValSize, Val})
 
101
%%                                                    (no reply)
 
102
%%    {delete, Key}     ->
 
103
%%        accumulates mnesia:delete({Tab, Key})       (no reply)
 
104
%%    {commit, ReplyTo} ->
 
105
%%        commits all accumulated operations
 
106
%%        and stops the process                       (replies {ok, Pid})
 
107
%%    abort             ->
 
108
%%        stops the process                           (no reply)
 
109
%%    
 
110
%% The receiver process is linked to the process with the process identifier
 
111
%% LinkTo. If some error occurs the receiver process will invoke exit(Reason)
 
112
%% and it is up to he LinkTo process to act properly when it receives an exit
 
113
%% signal.
 
114
 
 
115
start_dump(Tab, LinkTo) ->
 
116
    start(dump, Tab, LinkTo).
 
117
 
 
118
%% Starts a sender process which sends restore messages back to the
 
119
%% LinkTo process. But first are some statistics about the table
 
120
%% determined and returned as a 5-tuple:
 
121
%% 
 
122
%%    {size, SenderPid, N, LargestKeySize, LargestValSize}
 
123
%%
 
124
%% where N is the number of records in the table. Then the sender process
 
125
%% waits for a 2-tuple message:
 
126
%% 
 
127
%%    {send_records, ReplyTo}
 
128
%%
 
129
%% At last N 6-tuple messages is sent to the ReplyTo process:
 
130
%% 
 
131
%%    ReplyTo !  {restore, KeySize, ValSize, ValType, Key, Val}
 
132
%%
 
133
%% If some error occurs the receiver process will invoke exit(Reason)
 
134
%% and it is up to he LinkTo process to act properly when it receives an
 
135
%% exit signal.
 
136
 
 
137
start_restore(Tab, LinkTo) ->
 
138
    start(restore, Tab, LinkTo).
 
139
 
 
140
 
 
141
%% Optionally creates the Mnesia table Tab with suitable default values.
 
142
%% Returns ok or EXIT's
 
143
create_table(Tab) ->
 
144
    Storage = mnesia:table_info(schema, storage_type),
 
145
    create_table(Tab, [{Storage, [node()]}]).
 
146
 
 
147
create_table(Tab, TabDef) ->
 
148
    Attrs = record_info(fields, registry_entry),
 
149
    case mnesia:create_table(Tab, [{attributes, Attrs} | TabDef]) of
 
150
        {'atomic', ok} ->
 
151
            ok;
 
152
        {aborted, {already_exists, Tab}} ->
 
153
            ok;
 
154
        {aborted, Reason} ->
 
155
            exit(Reason)
 
156
    end.
 
157
    
 
158
%%%----------------------------------------------------------------------
 
159
%%% Server
 
160
%%%----------------------------------------------------------------------
 
161
 
 
162
init(Type, Starter, LinkTo, Tab) ->
 
163
    if
 
164
        LinkTo /= Starter ->
 
165
            link(LinkTo),
 
166
            unlink(Starter);
 
167
        true ->
 
168
            ignore
 
169
    end,
 
170
    case Type of
 
171
        dump ->
 
172
            Starter ! {ok, self()},
 
173
            dump_loop(#state{table = Tab, link_to = LinkTo});
 
174
        restore ->
 
175
            restore_table(Tab, Starter, LinkTo)
 
176
    end.
 
177
 
 
178
%%%----------------------------------------------------------------------
 
179
%%% Dump loop    
 
180
%%%----------------------------------------------------------------------
 
181
 
 
182
dump_loop(S) ->
 
183
    Tab = S#state.table,
 
184
    Ops = S#state.ops,
 
185
    receive
 
186
        {write, Key, KeySize, ValType, ValSize, Val} ->
 
187
            RE = #registry_entry{key = Key,
 
188
                                 key_size = KeySize,
 
189
                                 val_type = ValType,
 
190
                                 val_size = ValSize,
 
191
                                 val = Val},
 
192
            dump_loop(S#state{ops = [{write, RE} | Ops]});
 
193
        {delete, Key} ->
 
194
            dump_loop(S#state{ops = [{delete, Key} | Ops]});
 
195
        {commit, ReplyTo} ->
 
196
            create_table(Tab),
 
197
            RecName = mnesia:table_info(Tab, record_name),
 
198
            %% The Ops are in reverse order, but there is no need
 
199
            %% for reversing the list of accumulated operations
 
200
            case mnesia:transaction(fun handle_ops/3, [Tab, RecName, Ops]) of
 
201
                {'atomic', ok} ->
 
202
                    ReplyTo ! {ok, self()},
 
203
                    stop(S#state.link_to);
 
204
                {aborted, Reason} ->
 
205
                    exit({aborted, Reason})
 
206
            end;
 
207
        abort ->
 
208
            stop(S#state.link_to);
 
209
        BadMsg ->
 
210
            exit({bad_message, BadMsg})                                    
 
211
    end.
 
212
 
 
213
stop(LinkTo) ->
 
214
    unlink(LinkTo),
 
215
    exit(normal).
 
216
 
 
217
%% Grab a write lock for the entire table
 
218
%% and iterate over all accumulated operations
 
219
handle_ops(Tab, RecName, Ops) ->
 
220
    mnesia:write_lock_table(Tab),
 
221
    do_handle_ops(Tab, RecName, Ops).
 
222
 
 
223
do_handle_ops(Tab, RecName, [{write, RegEntry} | Ops]) ->
 
224
    Record = setelement(1, RegEntry, RecName),
 
225
    mnesia:write(Tab, Record, write),
 
226
    do_handle_ops(Tab, RecName, Ops);
 
227
do_handle_ops(Tab, RecName, [{delete, Key} | Ops]) ->
 
228
    mnesia:delete(Tab, Key, write),
 
229
    do_handle_ops(Tab, RecName, Ops);
 
230
do_handle_ops(_Tab, _RecName, []) ->
 
231
    ok.
 
232
    
 
233
%%%----------------------------------------------------------------------
 
234
%%% Restore table
 
235
%%%----------------------------------------------------------------------
 
236
 
 
237
restore_table(Tab, Starter, LinkTo) ->
 
238
    Pat = mnesia:table_info(Tab, wild_pattern),
 
239
    Fun = fun() -> mnesia:match_object(Tab, Pat, read) end,
 
240
    case mnesia:transaction(Fun) of
 
241
        {'atomic', AllRecords} ->
 
242
            Size = calc_size(AllRecords, #size{}),
 
243
            Starter ! {ok, Size},
 
244
            receive
 
245
                {send_records, ReplyTo} -> 
 
246
                    send_records(AllRecords, ReplyTo),
 
247
                    unlink(LinkTo),
 
248
                    exit(normal);
 
249
                BadMsg ->
 
250
                    exit({bad_message, BadMsg})
 
251
            end;
 
252
        {aborted, Reason} ->
 
253
            exit(Reason)
 
254
    end.
 
255
 
 
256
calc_size([H | T], S) ->
 
257
    KeySize = max(element(#registry_entry.key_size, H), S#size.largest_key),
 
258
    ValSize = max(element(#registry_entry.val_size, H), S#size.largest_val),
 
259
    N = S#size.n_values + 1,
 
260
    calc_size(T, S#size{n_values = N, largest_key = KeySize, largest_val = ValSize});
 
261
calc_size([], Size) ->
 
262
    Size.
 
263
 
 
264
max(New, Old) when New > Old -> New;
 
265
max(_New, Old) -> Old.
 
266
 
 
267
send_records([H | T], ReplyTo) ->
 
268
    KeySize = element(#registry_entry.key_size, H),
 
269
    ValSize = element(#registry_entry.val_size, H),
 
270
    ValType = element(#registry_entry.val_type, H),
 
271
    Key = element(#registry_entry.key, H),
 
272
    Val = element(#registry_entry.val, H),
 
273
    ReplyTo ! {restore, KeySize, ValSize, ValType, Key, Val},
 
274
    send_records(T, ReplyTo);
 
275
send_records([], _ReplyTo) ->
 
276
    ok.
 
277