~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_locker.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_locker.erl,v 1.2 2009/07/01 15:45:40 kostis Exp $
 
17
%%
 
18
-module(mnesia_locker).
 
19
 
 
20
-export([
 
21
         get_held_locks/0,
 
22
         get_lock_queue/0,
 
23
         global_lock/5,
 
24
         ixrlock/5,
 
25
         init/1,
 
26
         mnesia_down/2,
 
27
         release_tid/1,
 
28
         async_release_tid/2,
 
29
         send_release_tid/2,
 
30
         receive_release_tid_acc/2,
 
31
         rlock/3,
 
32
         rlock_table/3,
 
33
         rwlock/3,
 
34
         sticky_rwlock/3,
 
35
         start/0,
 
36
         sticky_wlock/3,
 
37
         sticky_wlock_table/3,
 
38
         wlock/3,
 
39
         wlock_no_exist/4,
 
40
         wlock_table/3
 
41
        ]).
 
42
 
 
43
%% sys callback functions
 
44
-export([system_continue/3,
 
45
         system_terminate/4,
 
46
         system_code_change/4
 
47
        ]).
 
48
 
 
49
-include("mnesia.hrl").
 
50
-import(mnesia_lib, [dbg_out/2, error/2, verbose/2]).
 
51
 
 
52
-define(dbg(S,V), ok).
 
53
%-define(dbg(S,V), dbg_out("~p:~p: " ++ S, [?MODULE, ?LINE] ++ V)).
 
54
 
 
55
-define(ALL, '______WHOLETABLE_____').
 
56
-define(STICK, '______STICK_____').
 
57
-define(GLOBAL, '______GLOBAL_____').
 
58
 
 
59
-record(state, {supervisor}).
 
60
 
 
61
-record(queue, {oid, tid, op, pid, lucky}).
 
62
 
 
63
%% mnesia_held_locks: contain       {Oid, Op, Tid} entries  (bag)
 
64
-define(match_oid_held_locks(Oid),  {Oid, '_', '_'}).
 
65
%% mnesia_tid_locks: contain        {Tid, Oid, Op} entries  (bag) 
 
66
-define(match_oid_tid_locks(Tid),   {Tid, '_', '_'}).
 
67
%% mnesia_sticky_locks: contain     {Oid, Node} entries and {Tab, Node} entries (set)
 
68
-define(match_oid_sticky_locks(Oid),{Oid, '_'}).
 
69
%% mnesia_lock_queue: contain       {queue, Oid, Tid, Op, ReplyTo, WaitForTid} entries (ordered_set)
 
70
-define(match_oid_lock_queue(Oid),  #queue{oid=Oid, tid='_', op = '_', pid = '_', lucky = '_'}). 
 
71
%% mnesia_lock_counter:             {{write, Tab}, Number} &&
 
72
%%                                  {{read, Tab}, Number} entries  (set)
 
73
 
 
74
start() ->
 
75
    mnesia_monitor:start_proc(?MODULE, ?MODULE, init, [self()]).
 
76
 
 
77
init(Parent) ->
 
78
    register(?MODULE, self()),
 
79
    process_flag(trap_exit, true),
 
80
    proc_lib:init_ack(Parent, {ok, self()}),
 
81
    loop(#state{supervisor = Parent}).
 
82
 
 
83
val(Var) ->
 
84
    case ?catch_val(Var) of
 
85
        {'EXIT', _ReASoN_} -> mnesia_lib:other_val(Var, _ReASoN_); 
 
86
        _VaLuE_ -> _VaLuE_ 
 
87
    end.
 
88
 
 
89
reply(From, R) ->
 
90
    From ! {?MODULE, node(), R}.
 
91
 
 
92
l_request(Node, X, Store) ->
 
93
    {?MODULE, Node} ! {self(), X},
 
94
    l_req_rec(Node, Store).
 
95
 
 
96
l_req_rec(Node, Store) ->
 
97
    ?ets_insert(Store, {nodes, Node}),
 
98
    receive 
 
99
        {?MODULE, Node, {switch, Node2, Req}} ->
 
100
            ?ets_insert(Store, {nodes, Node2}),
 
101
            {?MODULE, Node2} ! Req,
 
102
            {switch, Node2, Req};
 
103
        {?MODULE, Node, Reply} -> 
 
104
            Reply;
 
105
        {mnesia_down, Node} -> 
 
106
            {not_granted, {node_not_running, Node}}
 
107
    end.
 
108
 
 
109
release_tid(Tid) ->
 
110
    ?MODULE ! {release_tid, Tid}.
 
111
 
 
112
async_release_tid(Nodes, Tid) ->
 
113
    rpc:abcast(Nodes, ?MODULE, {release_tid, Tid}).
 
114
 
 
115
send_release_tid(Nodes, Tid) ->
 
116
    rpc:abcast(Nodes, ?MODULE, {self(), {sync_release_tid, Tid}}).
 
117
 
 
118
receive_release_tid_acc([Node | Nodes], Tid) ->
 
119
    receive 
 
120
        {?MODULE, Node, {tid_released, Tid}} -> 
 
121
            receive_release_tid_acc(Nodes, Tid);
 
122
        {mnesia_down, Node} -> 
 
123
            receive_release_tid_acc(Nodes, Tid)
 
124
    end;
 
125
receive_release_tid_acc([], _Tid) ->
 
126
    ok.
 
127
 
 
128
loop(State) ->
 
129
    receive
 
130
        {From, {write, Tid, Oid}} ->
 
131
            try_sticky_lock(Tid, write, From, Oid),
 
132
            loop(State);
 
133
 
 
134
        %% If Key == ?ALL it's a request to lock the entire table
 
135
        %%
 
136
 
 
137
        {From, {read, Tid, Oid}} ->
 
138
            try_sticky_lock(Tid, read, From, Oid),
 
139
            loop(State);
 
140
 
 
141
        %% Really do a  read, but get hold of a write lock
 
142
        %% used by mnesia:wread(Oid).
 
143
        
 
144
        {From, {read_write, Tid, Oid}} ->
 
145
            try_sticky_lock(Tid, read_write, From, Oid),
 
146
            loop(State);
 
147
        
 
148
        %% Tid has somehow terminated, clear up everything
 
149
        %% and pass locks on to queued processes.
 
150
        %% This is the purpose of the mnesia_tid_locks table
 
151
        
 
152
        {release_tid, Tid} ->
 
153
            do_release_tid(Tid),
 
154
            loop(State);
 
155
        
 
156
        %% stick lock, first tries this to the where_to_read Node
 
157
        {From, {test_set_sticky, Tid, {Tab, _} = Oid, Lock}} ->
 
158
            case ?ets_lookup(mnesia_sticky_locks, Tab) of
 
159
                [] -> 
 
160
                    reply(From, not_stuck),
 
161
                    loop(State);
 
162
                [{_,Node}] when Node == node() ->
 
163
                    %% Lock is stuck here, see now if we can just set 
 
164
                    %% a regular write lock
 
165
                    try_lock(Tid, Lock, From, Oid),
 
166
                    loop(State);
 
167
                [{_,Node}] ->
 
168
                    reply(From, {stuck_elsewhere, Node}),
 
169
                    loop(State)
 
170
            end;
 
171
 
 
172
        %% If test_set_sticky fails, we send this to all nodes
 
173
        %% after aquiring a real write lock on Oid
 
174
 
 
175
        {stick, {Tab, _}, N} ->
 
176
            ?ets_insert(mnesia_sticky_locks, {Tab, N}),
 
177
            loop(State);
 
178
 
 
179
        %% The caller which sends this message, must have first 
 
180
        %% aquired a write lock on the entire table
 
181
        {unstick, Tab} ->
 
182
            ?ets_delete(mnesia_sticky_locks, Tab),
 
183
            loop(State);
 
184
 
 
185
        {From, {ix_read, Tid, Tab, IxKey, Pos}} ->
 
186
            case catch mnesia_index:get_index_table(Tab, Pos) of
 
187
                {'EXIT', _} ->
 
188
                    reply(From, {not_granted, {no_exists, Tab, {index, [Pos]}}}),
 
189
                    loop(State);
 
190
                Index ->
 
191
                    Rk = mnesia_lib:elems(2,mnesia_index:db_get(Index, IxKey)),
 
192
                    %% list of real keys
 
193
                    case ?ets_lookup(mnesia_sticky_locks, Tab) of
 
194
                        [] ->
 
195
                            set_read_lock_on_all_keys(Tid, From,Tab,Rk,Rk, 
 
196
                                                      []),
 
197
                            loop(State);
 
198
                        [{_,N}] when N == node() ->
 
199
                            set_read_lock_on_all_keys(Tid, From,Tab,Rk,Rk, 
 
200
                                                      []),
 
201
                            loop(State);
 
202
                        [{_,N}] ->
 
203
                            Req = {From, {ix_read, Tid, Tab, IxKey, Pos}},
 
204
                            From ! {?MODULE, node(), {switch, N, Req}},
 
205
                            loop(State)
 
206
                    end
 
207
            end;
 
208
 
 
209
        {From, {sync_release_tid, Tid}} ->
 
210
            do_release_tid(Tid),
 
211
            reply(From, {tid_released, Tid}),
 
212
            loop(State);
 
213
        
 
214
        {release_remote_non_pending, Node, Pending} ->
 
215
            release_remote_non_pending(Node, Pending),
 
216
            mnesia_monitor:mnesia_down(?MODULE, Node),
 
217
            loop(State);
 
218
 
 
219
        {'EXIT', Pid, _} when Pid == State#state.supervisor ->
 
220
            do_stop();
 
221
 
 
222
        {system, From, Msg} ->
 
223
            verbose("~p got {system, ~p, ~p}~n", [?MODULE, From, Msg]),
 
224
            Parent = State#state.supervisor,
 
225
            sys:handle_system_msg(Msg, From, Parent, ?MODULE, [], State);
 
226
            
 
227
        Msg ->
 
228
            error("~p got unexpected message: ~p~n", [?MODULE, Msg]),
 
229
            loop(State)
 
230
    end.
 
231
 
 
232
set_lock(Tid, Oid, Op) ->
 
233
    ?dbg("Granted ~p ~p ~p~n", [Tid,Oid,Op]),
 
234
    ?ets_insert(mnesia_held_locks, {Oid, Op, Tid}),
 
235
    ?ets_insert(mnesia_tid_locks, {Tid, Oid, Op}).
 
236
 
 
237
%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
238
%% Acquire locks
 
239
 
 
240
try_sticky_lock(Tid, Op, Pid, {Tab, _} = Oid) ->
 
241
    case ?ets_lookup(mnesia_sticky_locks, Tab) of
 
242
        [] ->
 
243
            try_lock(Tid, Op, Pid, Oid);
 
244
        [{_,N}] when N == node() ->
 
245
            try_lock(Tid, Op, Pid, Oid);
 
246
        [{_,N}] ->
 
247
            Req = {Pid, {Op, Tid, Oid}},
 
248
            Pid ! {?MODULE, node(), {switch, N, Req}}
 
249
    end.
 
250
 
 
251
try_lock(Tid, read_write, Pid, Oid) ->
 
252
    try_lock(Tid, read_write, read, write, Pid, Oid);
 
253
try_lock(Tid, Op, Pid, Oid) ->
 
254
    try_lock(Tid, Op, Op, Op, Pid, Oid).
 
255
 
 
256
try_lock(Tid, Op, SimpleOp, Lock, Pid, Oid) ->
 
257
    case can_lock(Tid, Lock, Oid, {no, bad_luck}) of
 
258
        yes ->
 
259
            Reply = grant_lock(Tid, SimpleOp, Lock, Oid),
 
260
            reply(Pid, Reply);
 
261
        {no, Lucky} ->
 
262
            C = #cyclic{op = SimpleOp, lock = Lock, oid = Oid, lucky = Lucky},
 
263
            ?dbg("Rejected ~p ~p ~p ~p ~n", [Tid, Oid, Lock, Lucky]),
 
264
            reply(Pid, {not_granted, C});
 
265
        {queue, Lucky} ->
 
266
            ?dbg("Queued ~p ~p ~p ~p ~n", [Tid, Oid, Lock, Lucky]),
 
267
            %% Append to queue: Nice place for trace output
 
268
            ?ets_insert(mnesia_lock_queue, 
 
269
                        #queue{oid = Oid, tid = Tid, op = Op, 
 
270
                               pid = Pid, lucky = Lucky}),
 
271
            ?ets_insert(mnesia_tid_locks, {Tid, Oid, {queued, Op}})
 
272
    end.
 
273
 
 
274
grant_lock(Tid, read, Lock, {Tab, Key})
 
275
  when Key /= ?ALL, Tab /= ?GLOBAL ->
 
276
    case node(Tid#tid.pid) == node() of
 
277
        true ->
 
278
            set_lock(Tid, {Tab, Key}, Lock),
 
279
            {granted, lookup_in_client};
 
280
        false ->
 
281
            case catch mnesia_lib:db_get(Tab, Key) of %% lookup as well
 
282
                {'EXIT', _Reason} ->
 
283
                    %% Table has been deleted from this node,
 
284
                    %% restart the transaction.
 
285
                    C = #cyclic{op = read, lock = Lock, oid = {Tab, Key},
 
286
                                lucky = nowhere},
 
287
                    {not_granted, C};
 
288
                Val -> 
 
289
                    set_lock(Tid, {Tab, Key}, Lock),
 
290
                    {granted, Val}
 
291
            end
 
292
    end;
 
293
grant_lock(Tid, read, Lock, Oid) ->
 
294
    set_lock(Tid, Oid, Lock),
 
295
    {granted, ok};
 
296
grant_lock(Tid, write, Lock, Oid) ->
 
297
    set_lock(Tid, Oid, Lock),
 
298
    granted.
 
299
 
 
300
%% 1) Impose an ordering on all transactions favour old (low tid) transactions
 
301
%%    newer (higher tid) transactions may never wait on older ones,
 
302
%% 2) When releasing the tids from the queue always begin with youngest (high tid)
 
303
%%    because of 1) it will avoid the deadlocks.
 
304
%% 3) TabLocks is the problem :-) They should not starve and not deadlock 
 
305
%%    handle tablocks in queue as they had locks on unlocked records.
 
306
 
 
307
can_lock(Tid, read, {Tab, Key}, AlreadyQ) when Key /= ?ALL ->
 
308
    %% The key is bound, no need for the other BIF
 
309
    Oid = {Tab, Key}, 
 
310
    ObjLocks = ?ets_match_object(mnesia_held_locks, {Oid, write, '_'}),
 
311
    TabLocks = ?ets_match_object(mnesia_held_locks, {{Tab, ?ALL}, write, '_'}),
 
312
    check_lock(Tid, Oid, ObjLocks, TabLocks, yes, AlreadyQ, read);
 
313
 
 
314
can_lock(Tid, read, Oid, AlreadyQ) -> % Whole tab
 
315
    Tab = element(1, Oid),
 
316
    ObjLocks = ?ets_match_object(mnesia_held_locks, {{Tab, '_'}, write, '_'}),
 
317
    check_lock(Tid, Oid, ObjLocks, [], yes, AlreadyQ, read);
 
318
 
 
319
can_lock(Tid, write, {Tab, Key}, AlreadyQ) when Key /= ?ALL -> 
 
320
    Oid = {Tab, Key},
 
321
    ObjLocks = ?ets_lookup(mnesia_held_locks, Oid),
 
322
    TabLocks = ?ets_lookup(mnesia_held_locks, {Tab, ?ALL}),
 
323
    check_lock(Tid, Oid, ObjLocks, TabLocks, yes, AlreadyQ, write);
 
324
 
 
325
can_lock(Tid, write, Oid, AlreadyQ) -> % Whole tab
 
326
    Tab = element(1, Oid),
 
327
    ObjLocks = ?ets_match_object(mnesia_held_locks, ?match_oid_held_locks({Tab, '_'})),
 
328
    check_lock(Tid, Oid, ObjLocks, [], yes, AlreadyQ, write).
 
329
 
 
330
%% Check held locks for conflicting locks
 
331
check_lock(Tid, Oid, [Lock | Locks], TabLocks, X, AlreadyQ, Type) ->
 
332
    case element(3, Lock) of
 
333
        Tid ->
 
334
            check_lock(Tid, Oid, Locks, TabLocks, X, AlreadyQ, Type);
 
335
        WaitForTid when WaitForTid > Tid -> % Important order
 
336
            check_lock(Tid, Oid, Locks, TabLocks, {queue, WaitForTid}, AlreadyQ, Type);
 
337
        WaitForTid when Tid#tid.pid == WaitForTid#tid.pid ->
 
338
            dbg_out("Spurious lock conflict ~w ~w: ~w -> ~w~n",
 
339
                    [Oid, Lock, Tid, WaitForTid]),  
 
340
%%          check_lock(Tid, Oid, Locks, TabLocks, {queue, WaitForTid}, AlreadyQ);
 
341
            %% BUGBUG Fix this if possible
 
342
            {no, WaitForTid};
 
343
        WaitForTid ->
 
344
            {no, WaitForTid}
 
345
    end;
 
346
 
 
347
check_lock(_, _, [], [], X, {queue, bad_luck}, _) ->
 
348
    X;  %% The queue should be correct already no need to check it again
 
349
 
 
350
check_lock(_, _, [], [], X = {queue, _Tid}, _AlreadyQ, _) ->
 
351
    X;  
 
352
 
 
353
check_lock(Tid, Oid, [], [], X, AlreadyQ, Type) ->
 
354
    {Tab, Key} = Oid,
 
355
    if
 
356
        Type == write ->
 
357
            check_queue(Tid, Tab, X, AlreadyQ);
 
358
        Key == ?ALL ->
 
359
            %% hmm should be solvable by a clever select expr but not today...
 
360
            check_queue(Tid, Tab, X, AlreadyQ);
 
361
        true ->
 
362
            %% If there is a queue on that object, read_lock shouldn't be granted
 
363
            ObjLocks = ets:lookup(mnesia_lock_queue, Oid),
 
364
            Greatest = max(ObjLocks),
 
365
            case Greatest of
 
366
                empty -> 
 
367
                    check_queue(Tid, Tab, X, AlreadyQ);
 
368
                ObjL when Tid > ObjL -> 
 
369
                    {no, ObjL}; %% Starvation Preemption (write waits for read)
 
370
                ObjL ->
 
371
                    check_queue(Tid, Tab, {queue, ObjL}, AlreadyQ)
 
372
            end
 
373
    end;
 
374
 
 
375
check_lock(Tid, Oid, [], TabLocks, X, AlreadyQ, Type) ->
 
376
    check_lock(Tid, Oid, TabLocks, [], X, AlreadyQ, Type).
 
377
 
 
378
%% Check queue for conflicting locks
 
379
%% Assume that all queued locks belongs to other tid's
 
380
 
 
381
check_queue(Tid, Tab, X, AlreadyQ) ->
 
382
    TabLocks = ets:lookup(mnesia_lock_queue, {Tab,?ALL}),
 
383
    Greatest = max(TabLocks),
 
384
    case Greatest of
 
385
        empty -> 
 
386
            X;
 
387
        Tid ->
 
388
            X; 
 
389
        WaitForTid when WaitForTid#queue.tid > Tid -> % Important order
 
390
            {queue, WaitForTid};
 
391
        WaitForTid -> 
 
392
            case AlreadyQ of
 
393
                {no, bad_luck} -> {no, WaitForTid};
 
394
                _ ->  
 
395
                    erlang:error({mnesia_locker, assert, AlreadyQ})
 
396
            end
 
397
    end.
 
398
 
 
399
max([]) ->
 
400
    empty;
 
401
max([H|R]) ->
 
402
    max(R, H#queue.tid).
 
403
 
 
404
max([H|R], Tid) when H#queue.tid > Tid ->
 
405
    max(R, H#queue.tid);
 
406
max([_|R], Tid) ->
 
407
    max(R, Tid);
 
408
max([], Tid) ->
 
409
    Tid.
 
410
 
 
411
%% We can't queue the ixlock requests since it
 
412
%% becomes to complivated for little me :-)
 
413
%% If we encounter an object with a wlock we reject the
 
414
%% entire lock request
 
415
%% 
 
416
%% BUGBUG: this is actually a bug since we may starve
 
417
 
 
418
set_read_lock_on_all_keys(Tid, From, Tab, [RealKey | Tail], Orig, Ack) ->
 
419
    Oid = {Tab, RealKey},
 
420
    case can_lock(Tid, read, Oid, {no, bad_luck}) of
 
421
        yes ->
 
422
            {granted, Val} = grant_lock(Tid, read, read, Oid),
 
423
            case opt_lookup_in_client(Val, Oid, read) of  % Ought to be invoked
 
424
                C when record(C, cyclic) ->               % in the client
 
425
                    reply(From, {not_granted, C});
 
426
                Val2 -> 
 
427
                    Ack2 = lists:append(Val2, Ack),
 
428
                    set_read_lock_on_all_keys(Tid, From, Tab, Tail, Orig, Ack2)
 
429
            end;
 
430
        {no, Lucky} ->
 
431
            C = #cyclic{op = read, lock = read, oid = Oid, lucky = Lucky},
 
432
            reply(From, {not_granted, C});
 
433
        {queue, Lucky} ->
 
434
            C = #cyclic{op = read, lock = read, oid = Oid, lucky = Lucky},
 
435
            reply(From, {not_granted, C})
 
436
    end;
 
437
set_read_lock_on_all_keys(_Tid, From, _Tab, [], Orig, Ack) ->
 
438
    reply(From, {granted, Ack, Orig}).
 
439
 
 
440
%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
441
%% Release of locks
 
442
 
 
443
%% Release remote non-pending nodes
 
444
release_remote_non_pending(Node, Pending) ->
 
445
    %% Clear the mnesia_sticky_locks table first, to avoid
 
446
    %% unnecessary requests to the failing node
 
447
    ?ets_match_delete(mnesia_sticky_locks, {'_' , Node}),
 
448
 
 
449
    %% Then we have to release all locks held by processes
 
450
    %% running at the failed node and also simply remove all
 
451
    %% queue'd requests back to the failed node
 
452
 
 
453
    AllTids = ?ets_match(mnesia_tid_locks, {'$1', '_', '_'}),
 
454
    Tids = [T || [T] <- AllTids, Node == node(T#tid.pid), not lists:member(T, Pending)],
 
455
    do_release_tids(Tids).
 
456
 
 
457
do_release_tids([Tid | Tids]) ->
 
458
    do_release_tid(Tid),
 
459
    do_release_tids(Tids);
 
460
do_release_tids([]) ->
 
461
    ok.
 
462
 
 
463
do_release_tid(Tid) ->
 
464
    Locks = ?ets_lookup(mnesia_tid_locks, Tid),
 
465
    ?dbg("Release ~p ~p ~n", [Tid, Locks]),
 
466
    ?ets_delete(mnesia_tid_locks, Tid),
 
467
    release_locks(Locks),
 
468
    %% Removed queued locks which has had locks
 
469
    UniqueLocks = keyunique(lists:sort(Locks),[]),
 
470
    rearrange_queue(UniqueLocks).
 
471
 
 
472
keyunique([{_Tid, Oid, _Op}|R], Acc = [{_, Oid, _}|_]) ->
 
473
    keyunique(R, Acc);
 
474
keyunique([H|R], Acc) ->
 
475
    keyunique(R, [H|Acc]);
 
476
keyunique([], Acc) ->
 
477
    Acc.
 
478
 
 
479
release_locks([Lock | Locks]) ->
 
480
    release_lock(Lock),
 
481
    release_locks(Locks);
 
482
release_locks([]) ->
 
483
    ok.
 
484
 
 
485
release_lock({Tid, Oid, {queued, _}}) ->
 
486
    ?ets_match_delete(mnesia_lock_queue, 
 
487
                      #queue{oid=Oid, tid = Tid, op = '_',
 
488
                             pid = '_', lucky = '_'});
 
489
release_lock({Tid, Oid, Op}) ->
 
490
    if
 
491
        Op == write ->
 
492
            ?ets_delete(mnesia_held_locks, Oid);
 
493
        Op == read ->
 
494
            ?ets_match_delete(mnesia_held_locks, {Oid, Op, Tid})
 
495
    end.
 
496
 
 
497
rearrange_queue([{_Tid, {Tab, Key}, _} | Locks]) ->
 
498
    if
 
499
        Key /= ?ALL->       
 
500
            Queue =  
 
501
                ets:lookup(mnesia_lock_queue, {Tab, ?ALL}) ++ 
 
502
                ets:lookup(mnesia_lock_queue, {Tab, Key}),
 
503
            case Queue of 
 
504
                [] -> 
 
505
                    ok;
 
506
                _ ->
 
507
                    Sorted = lists:reverse(lists:keysort(#queue.tid, Queue)),
 
508
                    try_waiters_obj(Sorted)
 
509
            end;        
 
510
        true -> 
 
511
            Pat = ?match_oid_lock_queue({Tab, '_'}),
 
512
            Queue = ?ets_match_object(mnesia_lock_queue, Pat),      
 
513
            Sorted = lists:reverse(lists:keysort(#queue.tid, Queue)),
 
514
            try_waiters_tab(Sorted)
 
515
    end,
 
516
    ?dbg("RearrQ ~p~n", [Queue]),
 
517
    rearrange_queue(Locks);
 
518
rearrange_queue([]) ->
 
519
    ok.
 
520
 
 
521
try_waiters_obj([W | Waiters]) ->
 
522
    case try_waiter(W) of
 
523
        queued ->
 
524
            no;
 
525
        _ ->        
 
526
            try_waiters_obj(Waiters)
 
527
    end;
 
528
try_waiters_obj([]) ->
 
529
    ok.
 
530
 
 
531
try_waiters_tab([W | Waiters]) ->
 
532
    case W#queue.oid of
 
533
        {_Tab, ?ALL} ->
 
534
            case try_waiter(W) of
 
535
                queued ->
 
536
                    no;
 
537
                _ ->
 
538
                    try_waiters_tab(Waiters)
 
539
            end;
 
540
        Oid ->
 
541
            case try_waiter(W) of
 
542
                queued ->           
 
543
                    Rest = key_delete_all(Oid, #queue.oid, Waiters),
 
544
                    try_waiters_tab(Rest);
 
545
                _ ->                
 
546
                    try_waiters_tab(Waiters)
 
547
            end
 
548
    end;
 
549
try_waiters_tab([]) ->
 
550
    ok.
 
551
 
 
552
try_waiter({queue, Oid, Tid, read_write, ReplyTo, _}) ->
 
553
    try_waiter(Oid, read_write, read, write, ReplyTo, Tid);
 
554
try_waiter({queue, Oid, Tid, Op, ReplyTo, _}) ->
 
555
    try_waiter(Oid, Op, Op, Op, ReplyTo, Tid).
 
556
 
 
557
try_waiter(Oid, Op, SimpleOp, Lock, ReplyTo, Tid) ->
 
558
    case can_lock(Tid, Lock, Oid, {queue, bad_luck}) of
 
559
        yes ->
 
560
            %% Delete from queue: Nice place for trace output
 
561
            ?ets_match_delete(mnesia_lock_queue, 
 
562
                              #queue{oid=Oid, tid = Tid, op = Op,
 
563
                                     pid = ReplyTo, lucky = '_'}),
 
564
            Reply = grant_lock(Tid, SimpleOp, Lock, Oid),           
 
565
            ReplyTo ! {?MODULE, node(), Reply},
 
566
            locked;
 
567
        {queue, _Why} ->
 
568
            ?dbg("Keep ~p ~p ~p ~p~n", [Tid, Oid, Lock, _Why]),
 
569
            queued; % Keep waiter in queue      
 
570
        {no, Lucky} ->
 
571
            C = #cyclic{op = SimpleOp, lock = Lock, oid = Oid, lucky = Lucky},
 
572
            verbose("** WARNING ** Restarted transaction, possible deadlock in lock queue ~w: cyclic = ~w~n",
 
573
                    [Tid, C]),
 
574
            ?ets_match_delete(mnesia_lock_queue, 
 
575
                              #queue{oid=Oid, tid = Tid, op = Op,
 
576
                                     pid = ReplyTo, lucky = '_'}),
 
577
            Reply = {not_granted, C},
 
578
            ReplyTo ! {?MODULE, node(), Reply},
 
579
            removed
 
580
    end.
 
581
 
 
582
key_delete_all(Key, Pos, TupleList) ->
 
583
    key_delete_all(Key, Pos, TupleList, []).
 
584
key_delete_all(Key, Pos, [H|T], Ack) when element(Pos, H) == Key ->
 
585
    key_delete_all(Key, Pos, T, Ack);
 
586
key_delete_all(Key, Pos, [H|T], Ack) ->
 
587
    key_delete_all(Key, Pos, T, [H|Ack]);
 
588
key_delete_all(_, _, [], Ack) ->
 
589
    lists:reverse(Ack).
 
590
 
 
591
 
 
592
%% ********************* end server code ********************
 
593
%% The following code executes at the client side of a transactions
 
594
 
 
595
mnesia_down(N, Pending) ->
 
596
    case whereis(?MODULE) of
 
597
        undefined ->
 
598
            %% Takes care of mnesia_down's in early startup
 
599
            mnesia_monitor:mnesia_down(?MODULE, N);
 
600
        Pid ->
 
601
            %% Syncronously call needed in order to avoid
 
602
            %% race with mnesia_tm's coordinator processes
 
603
            %% that may restart and acquire new locks.
 
604
            %% mnesia_monitor ensures the sync.
 
605
            Pid ! {release_remote_non_pending, N, Pending}
 
606
    end.
 
607
 
 
608
%% Aquire a write lock, but do a read, used by 
 
609
%% mnesia:wread/1
 
610
 
 
611
rwlock(Tid, Store, Oid) ->
 
612
    {Tab, Key} = Oid,
 
613
    case val({Tab, where_to_read}) of
 
614
        nowhere ->
 
615
            mnesia:abort({no_exists, Tab});
 
616
        Node ->
 
617
            Lock = write,
 
618
            case need_lock(Store, Tab, Key, Lock)  of
 
619
                yes ->
 
620
                    Ns = w_nodes(Tab),
 
621
                    Res = get_rwlocks_on_nodes(Ns, Ns, Node, Store, Tid, Oid),
 
622
                    ?ets_insert(Store, {{locks, Tab, Key}, Lock}),
 
623
                    Res;
 
624
                no ->
 
625
                    if
 
626
                        Key == ?ALL ->
 
627
                            w_nodes(Tab);
 
628
                        Tab == ?GLOBAL ->
 
629
                            w_nodes(Tab);
 
630
                        true ->
 
631
                            dirty_rpc(Node, Tab, Key, Lock)
 
632
                    end
 
633
            end
 
634
    end.
 
635
 
 
636
get_rwlocks_on_nodes([Node | Tail], Orig, Node, Store, Tid, Oid) ->
 
637
    Op = {self(), {read_write, Tid, Oid}},
 
638
    {?MODULE, Node} ! Op,
 
639
    ?ets_insert(Store, {nodes, Node}),
 
640
    add_debug(Node),
 
641
    get_rwlocks_on_nodes(Tail, Orig, Node, Store, Tid, Oid);
 
642
get_rwlocks_on_nodes([Node | Tail], Orig, OtherNode, Store, Tid, Oid) ->
 
643
    Op = {self(), {write, Tid, Oid}},
 
644
    {?MODULE, Node} ! Op,
 
645
    add_debug(Node),
 
646
    ?ets_insert(Store, {nodes, Node}),
 
647
    get_rwlocks_on_nodes(Tail, Orig, OtherNode, Store, Tid, Oid);
 
648
get_rwlocks_on_nodes([], Orig, _Node, Store, _Tid, Oid) ->
 
649
    receive_wlocks(Orig, read_write_lock, Store, Oid).
 
650
 
 
651
%% Return a list of nodes or abort transaction
 
652
%% WE also insert any additional where_to_write nodes
 
653
%% in the local store under the key == nodes
 
654
 
 
655
w_nodes(Tab) ->
 
656
    Nodes = ?catch_val({Tab, where_to_write}),
 
657
    case Nodes of
 
658
        [_ | _] -> Nodes;
 
659
        _ ->  mnesia:abort({no_exists, Tab})
 
660
    end.
 
661
 
 
662
%% aquire a sticky wlock, a sticky lock is a lock
 
663
%% which remains at this node after the termination of the
 
664
%% transaction.
 
665
 
 
666
sticky_wlock(Tid, Store, Oid) ->
 
667
    sticky_lock(Tid, Store, Oid, write).
 
668
 
 
669
sticky_rwlock(Tid, Store, Oid) ->
 
670
    sticky_lock(Tid, Store, Oid, read_write).
 
671
 
 
672
sticky_lock(Tid, Store, {Tab, Key} = Oid, Lock) ->
 
673
    N = val({Tab, where_to_read}), 
 
674
    if
 
675
        node() == N ->
 
676
            case need_lock(Store, Tab, Key, write) of
 
677
                yes ->
 
678
                    do_sticky_lock(Tid, Store, Oid, Lock);
 
679
                no ->
 
680
                    dirty_sticky_lock(Tab, Key, [N], Lock)
 
681
            end;
 
682
        true ->
 
683
            mnesia:abort({not_local, Tab})
 
684
    end.
 
685
 
 
686
do_sticky_lock(Tid, Store, {Tab, Key} = Oid, Lock) ->
 
687
    ?MODULE ! {self(), {test_set_sticky, Tid, Oid, Lock}},
 
688
    receive
 
689
        {?MODULE, _N, granted} ->
 
690
            ?ets_insert(Store, {{locks, Tab, Key}, write}),
 
691
            granted;
 
692
        {?MODULE, _N, {granted, Val}} -> %% for rwlocks
 
693
            case opt_lookup_in_client(Val, Oid, write) of
 
694
                C when record(C, cyclic) ->
 
695
                    exit({aborted, C});
 
696
                Val2 ->
 
697
                    ?ets_insert(Store, {{locks, Tab, Key}, write}),
 
698
                    Val2
 
699
            end;
 
700
        {?MODULE, _N, {not_granted, Reason}} ->
 
701
            exit({aborted, Reason});
 
702
        {?MODULE, N, not_stuck} ->
 
703
            not_stuck(Tid, Store, Tab, Key, Oid, Lock, N),
 
704
            dirty_sticky_lock(Tab, Key, [N], Lock);
 
705
        {mnesia_down, N} ->
 
706
            exit({aborted, {node_not_running, N}});
 
707
        {?MODULE, N, {stuck_elsewhere, _N2}} ->
 
708
            stuck_elsewhere(Tid, Store, Tab, Key, Oid, Lock),
 
709
            dirty_sticky_lock(Tab, Key, [N], Lock)
 
710
    end.
 
711
 
 
712
not_stuck(Tid, Store, Tab, _Key, Oid, _Lock, N) ->
 
713
    rlock(Tid, Store, {Tab, ?ALL}),   %% needed?
 
714
    wlock(Tid, Store, Oid),           %% perfect sync
 
715
    wlock(Tid, Store, {Tab, ?STICK}), %% max one sticker/table
 
716
    Ns = val({Tab, where_to_write}),
 
717
    rpc:abcast(Ns, ?MODULE, {stick, Oid, N}).
 
718
 
 
719
stuck_elsewhere(Tid, Store, Tab, _Key, Oid, _Lock) ->
 
720
    rlock(Tid, Store, {Tab, ?ALL}),   %% needed?
 
721
    wlock(Tid, Store, Oid),           %% perfect sync
 
722
    wlock(Tid, Store, {Tab, ?STICK}), %% max one sticker/table
 
723
    Ns = val({Tab, where_to_write}),
 
724
    rpc:abcast(Ns, ?MODULE, {unstick, Tab}).
 
725
 
 
726
dirty_sticky_lock(Tab, Key, Nodes, Lock) ->
 
727
    if
 
728
        Lock == read_write ->
 
729
            mnesia_lib:db_get(Tab, Key);
 
730
        Key == ?ALL ->
 
731
            Nodes;
 
732
        Tab == ?GLOBAL ->
 
733
            Nodes;
 
734
        true ->
 
735
            ok
 
736
    end.           
 
737
 
 
738
sticky_wlock_table(Tid, Store, Tab) ->
 
739
    sticky_lock(Tid, Store, {Tab, ?ALL}, write).
 
740
 
 
741
%% aquire a wlock on Oid
 
742
%% We store a {Tabname, write, Tid} in all locktables
 
743
%% on all nodes containing a copy of Tabname
 
744
%% We also store an item {{locks, Tab, Key}, write} in the 
 
745
%% local store when we have aquired the lock.
 
746
%% 
 
747
wlock(Tid, Store, Oid) ->
 
748
    {Tab, Key} = Oid,
 
749
    case need_lock(Store, Tab, Key, write) of
 
750
        yes ->
 
751
            Ns = w_nodes(Tab),
 
752
            Op = {self(), {write, Tid, Oid}},
 
753
            ?ets_insert(Store, {{locks, Tab, Key}, write}),
 
754
            get_wlocks_on_nodes(Ns, Ns, Store, Op, Oid);
 
755
        no when Key /= ?ALL, Tab /= ?GLOBAL ->
 
756
            [];
 
757
        no ->
 
758
            w_nodes(Tab)
 
759
    end.
 
760
 
 
761
wlock_table(Tid, Store, Tab) ->
 
762
    wlock(Tid, Store, {Tab, ?ALL}).
 
763
 
 
764
%% Write lock even if the table does not exist
 
765
 
 
766
wlock_no_exist(Tid, Store, Tab, Ns) ->
 
767
    Oid = {Tab, ?ALL},
 
768
    Op = {self(), {write, Tid, Oid}},
 
769
    get_wlocks_on_nodes(Ns, Ns, Store, Op, Oid).
 
770
 
 
771
need_lock(Store, Tab, Key, LockPattern) ->
 
772
    TabL = ?ets_match_object(Store, {{locks, Tab, ?ALL}, LockPattern}),
 
773
    if 
 
774
        TabL == [] ->
 
775
            KeyL = ?ets_match_object(Store, {{locks, Tab, Key}, LockPattern}),
 
776
            if 
 
777
                KeyL == [] ->
 
778
                    yes;
 
779
                true  ->
 
780
                    no
 
781
            end;
 
782
        true ->
 
783
            no
 
784
    end.
 
785
 
 
786
add_debug(Node) ->  % Use process dictionary for debug info
 
787
    case get(mnesia_wlock_nodes) of       
 
788
        undefined -> 
 
789
            put(mnesia_wlock_nodes, [Node]);
 
790
        NodeList  ->
 
791
            put(mnesia_wlock_nodes, [Node|NodeList])
 
792
    end.
 
793
 
 
794
del_debug(Node) ->
 
795
    case get(mnesia_wlock_nodes) of
 
796
        undefined ->  % Shouldn't happen
 
797
            ignore;
 
798
        [Node] ->
 
799
            erase(mnesia_wlock_nodes);
 
800
        List -> 
 
801
            put(mnesia_wlock_nodes, lists:delete(Node, List))
 
802
    end.
 
803
 
 
804
%% We first send lock requests to the lockmanagers on all 
 
805
%% nodes holding a copy of the table
 
806
 
 
807
get_wlocks_on_nodes([Node | Tail], Orig, Store, Request, Oid) ->
 
808
    {?MODULE, Node} ! Request,
 
809
    ?ets_insert(Store, {nodes, Node}),
 
810
    add_debug(Node),
 
811
    get_wlocks_on_nodes(Tail, Orig, Store, Request, Oid);
 
812
get_wlocks_on_nodes([], Orig, Store, _Request, Oid) ->
 
813
    receive_wlocks(Orig, Orig, Store, Oid).
 
814
 
 
815
receive_wlocks([Node | Tail], Res, Store, Oid) ->
 
816
    receive
 
817
        {?MODULE, Node, granted} ->
 
818
            del_debug(Node),
 
819
            receive_wlocks(Tail, Res, Store, Oid);
 
820
        {?MODULE, Node, {granted, Val}} -> %% for rwlocks
 
821
            del_debug(Node),
 
822
            case opt_lookup_in_client(Val, Oid, write) of
 
823
                C when record(C, cyclic) ->
 
824
                    flush_remaining(Tail, Node, {aborted, C});
 
825
                Val2 ->
 
826
                    receive_wlocks(Tail, Val2, Store, Oid)
 
827
            end;
 
828
        {?MODULE, Node, {not_granted, Reason}} ->
 
829
            del_debug(Node),
 
830
            Reason1 = {aborted, Reason},
 
831
            flush_remaining(Tail, Node, Reason1);
 
832
        {mnesia_down, Node} ->
 
833
            del_debug(Node),
 
834
            Reason1 = {aborted, {node_not_running, Node}},
 
835
            flush_remaining(Tail, Node, Reason1);
 
836
        {?MODULE, Node, {switch, Node2, Req}} -> %% for rwlocks
 
837
            del_debug(Node),
 
838
            add_debug(Node2),
 
839
            ?ets_insert(Store, {nodes, Node2}),
 
840
            {?MODULE, Node2} ! Req,
 
841
            receive_wlocks([Node2 | Tail], Res, Store, Oid)
 
842
    end;
 
843
 
 
844
receive_wlocks([], Res, _Store, _Oid) ->
 
845
    Res.
 
846
 
 
847
flush_remaining([], _SkipNode, Res) ->
 
848
    exit(Res);
 
849
flush_remaining([SkipNode | Tail ], SkipNode, Res) ->
 
850
    del_debug(SkipNode),
 
851
    flush_remaining(Tail, SkipNode, Res);
 
852
flush_remaining([Node | Tail], SkipNode, Res) ->
 
853
    receive
 
854
        {?MODULE, Node, _} ->
 
855
            del_debug(Node),
 
856
            flush_remaining(Tail, SkipNode, Res);
 
857
        {mnesia_down, Node} ->
 
858
            del_debug(Node),
 
859
            flush_remaining(Tail, SkipNode, {aborted, {node_not_running, Node}})
 
860
    end.
 
861
 
 
862
opt_lookup_in_client(lookup_in_client, Oid, Lock) ->
 
863
    {Tab, Key} = Oid,
 
864
    case catch mnesia_lib:db_get(Tab, Key) of
 
865
        {'EXIT', _} ->
 
866
            %% Table has been deleted from this node,
 
867
            %% restart the transaction.
 
868
            #cyclic{op = read, lock = Lock, oid = Oid, lucky = nowhere};
 
869
        Val -> 
 
870
            Val
 
871
    end;
 
872
opt_lookup_in_client(Val, _Oid, _Lock) ->
 
873
    Val.
 
874
 
 
875
return_granted_or_nodes({_, ?ALL}   , Nodes) -> Nodes;
 
876
return_granted_or_nodes({?GLOBAL, _}, Nodes) -> Nodes;
 
877
return_granted_or_nodes(_           , _Nodes) -> granted.
 
878
    
 
879
%% We store a {Tab, read, From} item in the 
 
880
%% locks table on the node where we actually do pick up the object
 
881
%% and we also store an item {lock, Oid, read} in our local store
 
882
%% so that we can release any locks we hold when we commit.
 
883
%% This function not only aquires a read lock, but also reads the object
 
884
 
 
885
%% Oid's are always {Tab, Key} tuples
 
886
rlock(Tid, Store, Oid) ->
 
887
    {Tab, Key} = Oid,
 
888
    case val({Tab, where_to_read}) of
 
889
        nowhere ->
 
890
            mnesia:abort({no_exists, Tab});
 
891
        Node ->
 
892
            case need_lock(Store, Tab, Key, '_') of
 
893
                yes ->
 
894
                    R = l_request(Node, {read, Tid, Oid}, Store),
 
895
                    rlock_get_reply(Node, Store, Oid, R);
 
896
                no ->
 
897
                    if
 
898
                        Key == ?ALL ->
 
899
                            [Node];
 
900
                        Tab == ?GLOBAL ->
 
901
                            [Node];
 
902
                        true ->
 
903
                            dirty_rpc(Node, Tab, Key, read)
 
904
                    end
 
905
            end
 
906
    end.
 
907
 
 
908
dirty_rpc(nowhere, Tab, Key, _Lock) ->
 
909
    mnesia:abort({no_exists, {Tab, Key}});
 
910
dirty_rpc(Node, _Tab, ?ALL, _Lock) ->
 
911
    [Node];
 
912
dirty_rpc(Node, ?GLOBAL, _Key, _Lock) ->
 
913
    [Node];
 
914
dirty_rpc(Node, Tab, Key, Lock) ->
 
915
    Args = [Tab, Key],
 
916
    case rpc:call(Node, mnesia_lib, db_get, Args) of
 
917
        {badrpc, Reason} ->
 
918
            case val({Tab, where_to_read}) of
 
919
                Node ->
 
920
                    ErrorTag = mnesia_lib:dirty_rpc_error_tag(Reason),
 
921
                    mnesia:abort({ErrorTag, Args});
 
922
                _NewNode ->
 
923
                    %% Table has been deleted from the node,
 
924
                    %% restart the transaction.
 
925
                    C = #cyclic{op = read, lock = Lock, oid = {Tab, Key}, lucky = nowhere},
 
926
                    exit({aborted, C})
 
927
            end;
 
928
        Other ->
 
929
            Other
 
930
    end.
 
931
 
 
932
rlock_get_reply(Node, Store, Oid, {granted, V}) ->
 
933
    {Tab, Key} = Oid,
 
934
    ?ets_insert(Store, {{locks, Tab, Key}, read}),
 
935
    ?ets_insert(Store, {nodes, Node}),
 
936
    case opt_lookup_in_client(V, Oid, read) of
 
937
        C when record(C, cyclic) -> 
 
938
            mnesia:abort(C);
 
939
        Val -> 
 
940
            Val
 
941
    end;
 
942
rlock_get_reply(Node, Store, Oid, granted) ->
 
943
    {Tab, Key} = Oid,
 
944
    ?ets_insert(Store, {{locks, Tab, Key}, read}),
 
945
    ?ets_insert(Store, {nodes, Node}),
 
946
    return_granted_or_nodes(Oid, [Node]);
 
947
rlock_get_reply(Node, Store, Tab, {granted, V, RealKeys}) ->
 
948
    L = fun(K) -> ?ets_insert(Store, {{locks, Tab, K}, read}) end,
 
949
    lists:foreach(L, RealKeys),
 
950
    ?ets_insert(Store, {nodes, Node}),
 
951
    V;
 
952
rlock_get_reply(_Node, _Store, _Oid, {not_granted , Reason}) ->
 
953
    exit({aborted, Reason});
 
954
 
 
955
rlock_get_reply(_Node, Store, Oid, {switch, N2, Req}) ->
 
956
    ?ets_insert(Store, {nodes, N2}),
 
957
    {?MODULE, N2} ! Req,
 
958
    rlock_get_reply(N2, Store, Oid, l_req_rec(N2, Store)).
 
959
 
 
960
 
 
961
rlock_table(Tid, Store, Tab) ->
 
962
    rlock(Tid, Store, {Tab, ?ALL}).
 
963
 
 
964
ixrlock(Tid, Store, Tab, IxKey, Pos) ->
 
965
    case val({Tab, where_to_read}) of
 
966
        nowhere ->
 
967
            mnesia:abort({no_exists, Tab});
 
968
        Node ->
 
969
            R = l_request(Node, {ix_read, Tid, Tab, IxKey, Pos}, Store),
 
970
            rlock_get_reply(Node, Store, Tab, R)
 
971
    end.
 
972
 
 
973
%% Grabs the locks or exits
 
974
global_lock(Tid, Store, Item, write, Ns) ->
 
975
    Oid = {?GLOBAL, Item},
 
976
    Op = {self(), {write, Tid, Oid}},
 
977
    get_wlocks_on_nodes(Ns, Ns, Store, Op, Oid);
 
978
global_lock(Tid, Store, Item, read, Ns) ->
 
979
    Oid = {?GLOBAL, Item},
 
980
    send_requests(Ns, {read, Tid, Oid}),
 
981
    rec_requests(Ns, Oid, Store),
 
982
    Ns.
 
983
 
 
984
send_requests([Node | Nodes], X) ->
 
985
    {?MODULE, Node} ! {self(), X},
 
986
    send_requests(Nodes, X);
 
987
send_requests([], _X) ->
 
988
    ok.
 
989
 
 
990
rec_requests([Node | Nodes], Oid, Store) ->
 
991
    Res = l_req_rec(Node, Store),
 
992
    case catch rlock_get_reply(Node, Store, Oid, Res) of
 
993
        {'EXIT', Reason} ->
 
994
            flush_remaining(Nodes, Node, Reason);
 
995
        _ ->
 
996
            rec_requests(Nodes, Oid, Store)
 
997
    end;
 
998
rec_requests([], _Oid, _Store) ->
 
999
    ok.
 
1000
 
 
1001
get_held_locks() ->
 
1002
    ?ets_match_object(mnesia_held_locks, '_').
 
1003
 
 
1004
get_lock_queue() ->
 
1005
    Q = ?ets_match_object(mnesia_lock_queue, '_'),
 
1006
    [{Oid, Op, Pid, Tid, WFT} || {queue, Oid, Tid, Op, Pid, WFT} <- Q].
 
1007
 
 
1008
do_stop() ->
 
1009
    exit(shutdown).
 
1010
 
 
1011
%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
1012
%% System upgrade
 
1013
 
 
1014
system_continue(_Parent, _Debug, State) ->
 
1015
    loop(State).
 
1016
 
 
1017
system_terminate(_Reason, _Parent, _Debug, _State) ->
 
1018
    do_stop().
 
1019
 
 
1020
system_code_change(State, _Module, _OldVsn, _Extra) ->
 
1021
    {ok, State}.
 
1022