1%% ``Licensed under the Apache License, Version 2.0 (the "License");
2%% you may not use this file except in compliance with the License.
3%% You may obtain a copy of the License at
4%%
5%%     http://www.apache.org/licenses/LICENSE-2.0
6%%
7%% Unless required by applicable law or agreed to in writing, software
8%% distributed under the License is distributed on an "AS IS" BASIS,
9%% WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied.
10%% See the License for the specific language governing permissions and
11%% limitations under the License.
12%%
13%% The Initial Developer of the Original Code is Ericsson Utvecklings AB.
14%% Portions created by Ericsson are Copyright 1999, Ericsson Utvecklings
15%% AB. All Rights Reserved.''
16%%
17%%     $Id: mnesia.erl,v 1.2 2010/03/04 13:54:19 maria Exp $
18%% This module exports the public interface of the Mnesia DBMS engine
19
20-module(mnesia).
21%-behaviour(mnesia_access).
22
23-export([
24	 %% Start, stop and debugging
25	 start/0, start/1, stop/0,           % Not for public use
26	 set_debug_level/1, lkill/0, kill/0, % Not for public use
27	 ms/0, nc/0, nc/1, ni/0, ni/1,       % Not for public use
28	 change_config/2,
29
30	 %% Activity mgt
31	 abort/1, transaction/1, transaction/2, transaction/3,
32	 sync_transaction/1, sync_transaction/2, sync_transaction/3,
33	 async_dirty/1, async_dirty/2, sync_dirty/1, sync_dirty/2, ets/1, ets/2,
34	 activity/2, activity/3, activity/4, % Not for public use
35
36	 %% Access within an activity - Lock acquisition
37	 lock/2, lock/4,
38	 read_lock_table/1,
39	 write_lock_table/1,
40
41	 %% Access within an activity - Updates
42	 write/1, s_write/1, write/3, write/5,
43	 delete/1, s_delete/1, delete/3, delete/5,
44	 delete_object/1, s_delete_object/1, delete_object/3, delete_object/5,
45
46	 %% Access within an activity - Reads
47	 read/1, wread/1, read/3, read/5,
48	 match_object/1, match_object/3, match_object/5,
49	 select/2, select/3, select/5,
50	 all_keys/1, all_keys/4,
51	 index_match_object/2, index_match_object/4, index_match_object/6,
52	 index_read/3, index_read/6,
53
54	 %% Iterators within an activity
55	 foldl/3, foldl/4, foldr/3, foldr/4,
56
57	 %% Dirty access regardless of activities - Updates
58	 dirty_write/1, dirty_write/2,
59	 dirty_delete/1, dirty_delete/2,
60	 dirty_delete_object/1, dirty_delete_object/2,
61	 dirty_update_counter/2, dirty_update_counter/3,
62
63	 %% Dirty access regardless of activities - Read
64	 dirty_read/1, dirty_read/2,
65	 dirty_select/2,
66	 dirty_match_object/1, dirty_match_object/2, dirty_all_keys/1,
67	 dirty_index_match_object/2, dirty_index_match_object/3,
68	 dirty_index_read/3, dirty_slot/2,
69	 dirty_first/1, dirty_next/2, dirty_last/1, dirty_prev/2,
70
71	 %% Info
72	 table_info/2, table_info/4, schema/0, schema/1,
73	 error_description/1, info/0, system_info/1,
74	 system_info/0,                      % Not for public use
75
76	 %% Database mgt
77	 create_schema/1, delete_schema/1,
78	 backup/1, backup/2, traverse_backup/4, traverse_backup/6,
79	 install_fallback/1, install_fallback/2,
80	 uninstall_fallback/0, uninstall_fallback/1,
81	 activate_checkpoint/1, deactivate_checkpoint/1,
82	 backup_checkpoint/2, backup_checkpoint/3, restore/2,
83
84	 %% Table mgt
85	 create_table/1, create_table/2, delete_table/1,
86	 add_table_copy/3, del_table_copy/2, move_table_copy/3,
87	 add_table_index/2, del_table_index/2,
88	 transform_table/3, transform_table/4,
89	 change_table_copy_type/3,
90	 read_table_property/2, write_table_property/2, delete_table_property/2,
91	 change_table_frag/2,
92	 clear_table/1,
93
94	 %% Table load
95	 dump_tables/1, wait_for_tables/2, force_load_table/1,
96	 change_table_access_mode/2, change_table_load_order/2,
97	 set_master_nodes/1, set_master_nodes/2,
98
99	 %% Misc admin
100	 dump_log/0, subscribe/1, unsubscribe/1, report_event/1,
101
102	 %% Snmp
103	 snmp_open_table/2, snmp_close_table/1,
104	 snmp_get_row/2, snmp_get_next_index/2, snmp_get_mnesia_key/2,
105
106	 %% Textfile access
107	 load_textfile/1, dump_to_textfile/1,
108
109	 %% Mnemosyne exclusive
110	 get_activity_id/0, put_activity_id/1, % Not for public use
111
112	 %% Mnesia internal functions
113	 dirty_rpc/4,                          % Not for public use
114	 has_var/1, fun_select/7,
115	 foldl/6, foldr/6,
116
117	 %% Module internal callback functions
118	 remote_dirty_match_object/2,           % Not for public use
119	 remote_dirty_select/2                  % Not for public use
120	]).
121
122%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
123
124-include("mnesia.hrl").
125-import(mnesia_lib, [verbose/2]).
126
127-define(DEFAULT_ACCESS, ?MODULE).
128
129%% Select
130-define(PATTERN_TO_OBJECT_MATCH_SPEC(Pat), [{Pat,[],['$_']}]).
131-define(PATTERN_TO_BINDINGS_MATCH_SPEC(Pat), [{Pat,[],['$$']}]).
132
133%% Local function in order to avoid external function call
134val(Var) ->
135    case ?catch_val(Var) of
136	{'EXIT', Reason} -> mnesia_lib:other_val(Var, Reason);
137	Value -> Value
138    end.
139
140is_dollar_digits(Var) ->
141    case atom_to_list(Var) of
142	[$$ | Digs] ->
143	    is_digits(Digs);
144	_ ->
145	    false
146    end.
147
148is_digits([Dig | Tail]) ->
149    if
150	$0 =< Dig, Dig =< $9 ->
151	    is_digits(Tail);
152	true ->
153	    false
154    end;
155is_digits([]) ->
156    true.
157
158has_var(X) when atom(X) ->
159    if
160	X == '_' ->
161	    true;
162	atom(X) ->
163	    is_dollar_digits(X);
164	true  ->
165	    false
166    end;
167has_var(X) when tuple(X) ->
168    e_has_var(X, size(X));
169has_var([H|T]) ->
170    case has_var(H) of
171	false -> has_var(T);
172	Other -> Other
173    end;
174has_var(_) -> false.
175
176e_has_var(_, 0) -> false;
177e_has_var(X, Pos) ->
178    case has_var(element(Pos, X))of
179	false -> e_has_var(X, Pos-1);
180	Other -> Other
181    end.
182
183%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
184%% Start and stop
185
186start() ->
187    {Time , Res} =  timer:tc(application, start, [?APPLICATION, temporary]),
188
189    Secs = Time div 1000000,
190    case Res of
191	ok ->
192	    verbose("Mnesia started, ~p seconds~n",[ Secs]),
193	    ok;
194	{error, {already_started, mnesia}} ->
195	    verbose("Mnesia already started, ~p seconds~n",[ Secs]),
196	    ok;
197	{error, R} ->
198	    verbose("Mnesia failed to start, ~p seconds: ~p~n",[ Secs, R]),
199	    {error, R}
200    end.
201
202start(ExtraEnv) when list(ExtraEnv) ->
203    case mnesia_lib:ensure_loaded(?APPLICATION) of
204	ok ->
205	    patched_start(ExtraEnv);
206	Error ->
207	    Error
208    end;
209start(ExtraEnv) ->
210    {error, {badarg, ExtraEnv}}.
211
212patched_start([{Env, Val} | Tail]) when atom(Env) ->
213    case mnesia_monitor:patch_env(Env, Val) of
214	{error, Reason} ->
215	    {error, Reason};
216	_NewVal ->
217	    patched_start(Tail)
218    end;
219patched_start([Head | _]) ->
220    {error, {bad_type, Head}};
221patched_start([]) ->
222    start().
223
224stop() ->
225    case application:stop(?APPLICATION) of
226	ok -> stopped;
227	{error, {not_started, ?APPLICATION}} -> stopped;
228	Other -> Other
229    end.
230
231change_config(extra_db_nodes, Ns) when list(Ns) ->
232    mnesia_controller:connect_nodes(Ns);
233change_config(BadKey, _BadVal) ->
234    {error, {badarg, BadKey}}.
235
236%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
237%% Debugging
238
239set_debug_level(Level) ->
240    mnesia_subscr:set_debug_level(Level).
241
242lkill() ->
243    mnesia_sup:kill().
244
245kill() ->
246    rpc:multicall(mnesia_sup, kill, []).
247
248ms() ->
249    [
250     mnesia,
251     mnesia_backup,
252     mnesia_bup,
253     mnesia_checkpoint,
254     mnesia_checkpoint_sup,
255     mnesia_controller,
256     mnesia_dumper,
257     mnesia_loader,
258     mnesia_frag,
259     mnesia_frag_hash,
260     mnesia_frag_old_hash,
261     mnesia_index,
262     mnesia_kernel_sup,
263     mnesia_late_loader,
264     mnesia_lib,
265     mnesia_log,
266     mnesia_registry,
267     mnesia_schema,
268     mnesia_snmp_hook,
269     mnesia_snmp_sup,
270     mnesia_subscr,
271     mnesia_sup,
272     mnesia_text,
273     mnesia_tm,
274     mnesia_recover,
275     mnesia_locker,
276
277     %% Keep these last in the list, so
278     %% mnesia_sup kills these last
279     mnesia_monitor,
280     mnesia_event
281    ].
282
283nc() ->
284    Mods = ms(),
285    nc(Mods).
286
287nc(Mods) when list(Mods)->
288    [Mod || Mod <- Mods, ok /= load(Mod, compile)].
289
290ni() ->
291    Mods = ms(),
292    ni(Mods).
293
294ni(Mods) when list(Mods) ->
295    [Mod || Mod <- Mods, ok /= load(Mod, interpret)].
296
297load(Mod, How) when atom(Mod) ->
298    case try_load(Mod, How) of
299	ok ->
300	    ok;
301	_ ->
302	    mnesia_lib:show( "~n RETRY ~p FROM: ", [Mod]),
303	    Abs = mod2abs(Mod),
304	    load(Abs, How)
305    end;
306load(Abs, How) ->
307    case try_load(Abs, How) of
308	ok ->
309	    ok;
310	{error, Reason} ->
311	    mnesia_lib:show( " *** ERROR *** ~p~n", [Reason]),
312	    {error, Reason}
313    end.
314
315try_load(Mod, How) ->
316    mnesia_lib:show( " ~p ", [Mod]),
317    Flags = [{d, debug}],
318    case How of
319	compile ->
320	    case catch c:nc(Mod, Flags) of
321		{ok, _} -> ok;
322		Other -> {error, Other}
323	    end;
324	interpret ->
325	    case catch int:ni(Mod, Flags) of
326		{module, _} -> ok;
327		Other -> {error, Other}
328	    end
329    end.
330
331mod2abs(Mod) ->
332    ModString = atom_to_list(Mod),
333    SubDir =
334	case lists:suffix("test", ModString) of
335	    true -> test;
336	    false -> src
337	end,
338    filename:join([code:lib_dir(?APPLICATION), SubDir, ModString]).
339
340%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
341%% Activity mgt
342
343abort(Reason) ->
344    exit({aborted, Reason}).
345
346transaction(Fun) ->
347    transaction(get(mnesia_activity_state), Fun, [], infinity, ?DEFAULT_ACCESS, async).
348transaction(Fun, Retries) when integer(Retries), Retries >= 0 ->
349    transaction(get(mnesia_activity_state), Fun, [], Retries, ?DEFAULT_ACCESS, async);
350transaction(Fun, Retries) when Retries == infinity ->
351    transaction(get(mnesia_activity_state), Fun, [], Retries, ?DEFAULT_ACCESS, async);
352transaction(Fun, Args) ->
353    transaction(get(mnesia_activity_state), Fun, Args, infinity, ?DEFAULT_ACCESS, async).
354transaction(Fun, Args, Retries) ->
355    transaction(get(mnesia_activity_state), Fun, Args, Retries, ?DEFAULT_ACCESS, async).
356
357sync_transaction(Fun) ->
358    transaction(get(mnesia_activity_state), Fun, [], infinity, ?DEFAULT_ACCESS, sync).
359sync_transaction(Fun, Retries) when integer(Retries), Retries >= 0 ->
360    transaction(get(mnesia_activity_state), Fun, [], Retries, ?DEFAULT_ACCESS, sync);
361sync_transaction(Fun, Retries) when Retries == infinity ->
362    transaction(get(mnesia_activity_state), Fun, [], Retries, ?DEFAULT_ACCESS, sync);
363sync_transaction(Fun, Args) ->
364    transaction(get(mnesia_activity_state), Fun, Args, infinity, ?DEFAULT_ACCESS, sync).
365sync_transaction(Fun, Args, Retries) ->
366    transaction(get(mnesia_activity_state), Fun, Args, Retries, ?DEFAULT_ACCESS, sync).
367
368
369transaction(State, Fun, Args, Retries, Mod, Kind)
370  when function(Fun), list(Args), Retries == infinity, atom(Mod) ->
371    mnesia_tm:transaction(State, Fun, Args, Retries, Mod, Kind);
372transaction(State, Fun, Args, Retries, Mod, Kind)
373  when function(Fun), list(Args), integer(Retries), Retries >= 0, atom(Mod) ->
374    mnesia_tm:transaction(State, Fun, Args, Retries, Mod, Kind);
375transaction(_State, Fun, Args, Retries, Mod, _Kind) ->
376    {aborted, {badarg, Fun, Args, Retries, Mod}}.
377
378non_transaction(State, Fun, Args, ActivityKind, Mod)
379  when function(Fun), list(Args), atom(Mod) ->
380    mnesia_tm:non_transaction(State, Fun, Args, ActivityKind, Mod);
381non_transaction(_State, Fun, Args, _ActivityKind, _Mod) ->
382    {aborted, {badarg, Fun, Args}}.
383
384async_dirty(Fun) ->
385    async_dirty(Fun, []).
386async_dirty(Fun, Args) ->
387    non_transaction(get(mnesia_activity_state), Fun, Args, async_dirty, ?DEFAULT_ACCESS).
388
389sync_dirty(Fun) ->
390    sync_dirty(Fun, []).
391sync_dirty(Fun, Args) ->
392    non_transaction(get(mnesia_activity_state), Fun, Args, sync_dirty, ?DEFAULT_ACCESS).
393
394ets(Fun) ->
395    ets(Fun, []).
396ets(Fun, Args) ->
397    non_transaction(get(mnesia_activity_state), Fun, Args, ets, ?DEFAULT_ACCESS).
398
399activity(Kind, Fun) ->
400    activity(Kind, Fun, []).
401activity(Kind, Fun, Args) when list(Args) ->
402    activity(Kind, Fun, Args, mnesia_monitor:get_env(access_module));
403activity(Kind, Fun, Mod) ->
404    activity(Kind, Fun, [], Mod).
405
406activity(Kind, Fun, Args, Mod) ->
407    State = get(mnesia_activity_state),
408    case Kind of
409	ets ->                    non_transaction(State, Fun, Args, Kind, Mod);
410	async_dirty ->            non_transaction(State, Fun, Args, Kind, Mod);
411	sync_dirty ->             non_transaction(State, Fun, Args, Kind, Mod);
412	transaction ->            wrap_trans(State, Fun, Args, infinity, Mod, async);
413	{transaction, Retries} -> wrap_trans(State, Fun, Args, Retries, Mod, async);
414	sync_transaction ->            wrap_trans(State, Fun, Args, infinity, Mod, sync);
415	{sync_transaction, Retries} -> wrap_trans(State, Fun, Args, Retries, Mod, sync);
416	_ ->                      {aborted, {bad_type, Kind}}
417    end.
418
419wrap_trans(State, Fun, Args, Retries, Mod, Kind) ->
420    case transaction(State, Fun, Args, Retries, Mod, Kind) of
421	{'atomic', GoodRes} -> GoodRes;
422	BadRes -> exit(BadRes)
423    end.
424
425%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
426%% Access within an activity - lock acquisition
427
428%% Grab a lock on an item in the global lock table
429%% Item may be any term. Lock may be write or read.
430%% write lock is set on all the given nodes
431%% read lock is only set on the first node
432%% Nodes may either be a list of nodes or one node as an atom
433%% Mnesia on all Nodes must be connected to each other, but
434%% it is not necessary that they are up and running.
435
436lock(LockItem, LockKind) ->
437    case get(mnesia_activity_state) of
438	{?DEFAULT_ACCESS, Tid, Ts} ->
439	    lock(Tid, Ts, LockItem, LockKind);
440	{Mod, Tid, Ts} ->
441	    Mod:lock(Tid, Ts, LockItem, LockKind);
442	_ ->
443	    abort(no_transaction)
444    end.
445
446lock(Tid, Ts, LockItem, LockKind) ->
447    case element(1, Tid) of
448	tid ->
449	    case LockItem of
450		{record, Tab, Key} ->
451		    lock_record(Tid, Ts, Tab, Key, LockKind);
452		{table, Tab} ->
453		    lock_table(Tid, Ts, Tab, LockKind);
454		{global, GlobalKey, Nodes} ->
455		    global_lock(Tid, Ts, GlobalKey, LockKind, Nodes);
456		_ ->
457		    abort({bad_type, LockItem})
458	    end;
459	_Protocol ->
460	    []
461    end.
462
463%% Grab a read lock on a whole table
464read_lock_table(Tab) ->
465    lock({table, Tab}, read),
466    ok.
467
468%% Grab a write lock on a whole table
469write_lock_table(Tab) ->
470    lock({table, Tab}, write),
471    ok.
472
473lock_record(Tid, Ts, Tab, Key, LockKind) when atom(Tab) ->
474    Store = Ts#tidstore.store,
475    Oid =  {Tab, Key},
476    case LockKind of
477	read ->
478	    mnesia_locker:rlock(Tid, Store, Oid);
479	write ->
480	    mnesia_locker:wlock(Tid, Store, Oid);
481	sticky_write ->
482	    mnesia_locker:sticky_wlock(Tid, Store, Oid);
483	none ->
484	    [];
485	_ ->
486	    abort({bad_type, Tab, LockKind})
487    end;
488lock_record(_Tid, _Ts, Tab, _Key, _LockKind) ->
489    abort({bad_type, Tab}).
490
491lock_table(Tid, Ts, Tab, LockKind) when atom(Tab) ->
492    Store = Ts#tidstore.store,
493    case LockKind of
494	read ->
495	    mnesia_locker:rlock_table(Tid, Store, Tab);
496	write ->
497	    mnesia_locker:wlock_table(Tid, Store, Tab);
498	sticky_write ->
499	    mnesia_locker:sticky_wlock_table(Tid, Store, Tab);
500	none ->
501	    [];
502	_ ->
503	    abort({bad_type, Tab, LockKind})
504    end;
505lock_table(_Tid, _Ts, Tab, _LockKind) ->
506    abort({bad_type, Tab}).
507
508global_lock(Tid, Ts, Item, Kind, Nodes) when list(Nodes) ->
509    case element(1, Tid) of
510	tid ->
511	    Store = Ts#tidstore.store,
512	    GoodNs = good_global_nodes(Nodes),
513	    if
514		Kind /= read, Kind /= write ->
515		    abort({bad_type, Kind});
516		true ->
517		    mnesia_locker:global_lock(Tid, Store, Item, Kind, GoodNs)
518	    end;
519	_Protocol ->
520	    []
521    end;
522global_lock(_Tid, _Ts, _Item, _Kind, Nodes) ->
523    abort({bad_type, Nodes}).
524
525good_global_nodes(Nodes) ->
526    Recover = [node() | val(recover_nodes)],
527    mnesia_lib:intersect(Nodes, Recover).
528
529%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
530%% Access within an activity - updates
531
532write(Val) when tuple(Val), size(Val) > 2 ->
533    Tab = element(1, Val),
534    write(Tab, Val, write);
535write(Val) ->
536    abort({bad_type, Val}).
537
538s_write(Val) when tuple(Val), size(Val) > 2 ->
539    Tab = element(1, Val),
540    write(Tab, Val, sticky_write).
541
542write(Tab, Val, LockKind) ->
543    case get(mnesia_activity_state) of
544	{?DEFAULT_ACCESS, Tid, Ts} ->
545	    write(Tid, Ts, Tab, Val, LockKind);
546	{Mod, Tid, Ts} ->
547	    Mod:write(Tid, Ts, Tab, Val, LockKind);
548	_ ->
549	    abort(no_transaction)
550    end.
551
552write(Tid, Ts, Tab, Val, LockKind)
553  when atom(Tab), Tab /= schema, tuple(Val), size(Val) > 2 ->
554    case element(1, Tid) of
555	ets ->
556	    ?ets_insert(Tab, Val),
557	    ok;
558	tid ->
559	    Store = Ts#tidstore.store,
560	    Oid = {Tab, element(2, Val)},
561	    case LockKind of
562		write ->
563		    mnesia_locker:wlock(Tid, Store, Oid);
564		sticky_write ->
565		    mnesia_locker:sticky_wlock(Tid, Store, Oid);
566		_ ->
567		    abort({bad_type, Tab, LockKind})
568	    end,
569	    write_to_store(Tab, Store, Oid, Val);
570	Protocol ->
571	    do_dirty_write(Protocol, Tab, Val)
572    end;
573write(_Tid, _Ts, Tab, Val, LockKind) ->
574    abort({bad_type, Tab, Val, LockKind}).
575
576write_to_store(Tab, Store, Oid, Val) ->
577    case ?catch_val({Tab, record_validation}) of
578	{RecName, Arity, Type}
579	  when size(Val) == Arity, RecName == element(1, Val) ->
580	    case Type of
581		bag ->
582		    ?ets_insert(Store, {Oid, Val, write});
583		_  ->
584		    ?ets_delete(Store, Oid),
585		    ?ets_insert(Store, {Oid, Val, write})
586	    end,
587	    ok;
588	{'EXIT', _} ->
589	    abort({no_exists, Tab});
590	_ ->
591	    abort({bad_type, Val})
592    end.
593
594delete({Tab, Key}) ->
595    delete(Tab, Key, write);
596delete(Oid) ->
597    abort({bad_type, Oid}).
598
599s_delete({Tab, Key}) ->
600    delete(Tab, Key, sticky_write);
601s_delete(Oid) ->
602    abort({bad_type, Oid}).
603
604delete(Tab, Key, LockKind) ->
605    case get(mnesia_activity_state) of
606	{?DEFAULT_ACCESS, Tid, Ts} ->
607	    delete(Tid, Ts, Tab, Key, LockKind);
608	{Mod, Tid, Ts} ->
609	    Mod:delete(Tid, Ts, Tab, Key, LockKind);
610	_ ->
611	    abort(no_transaction)
612    end.
613
614delete(Tid, Ts, Tab, Key, LockKind)
615  when atom(Tab), Tab /= schema ->
616      case element(1, Tid) of
617	  ets ->
618	      ?ets_delete(Tab, Key),
619	      ok;
620	  tid ->
621	      Store = Ts#tidstore.store,
622	      Oid = {Tab, Key},
623	      case LockKind of
624		  write ->
625		      mnesia_locker:wlock(Tid, Store, Oid);
626		  sticky_write ->
627		      mnesia_locker:sticky_wlock(Tid, Store, Oid);
628		  _ ->
629		      abort({bad_type, Tab, LockKind})
630	      end,
631	      ?ets_delete(Store, Oid),
632	      ?ets_insert(Store, {Oid, Oid, delete}),
633	      ok;
634	Protocol ->
635	      do_dirty_delete(Protocol, Tab, Key)
636    end;
637delete(_Tid, _Ts, Tab, _Key, _LockKind) ->
638    abort({bad_type, Tab}).
639
640delete_object(Val) when tuple(Val), size(Val) > 2 ->
641    Tab = element(1, Val),
642    delete_object(Tab, Val, write);
643delete_object(Val) ->
644    abort({bad_type, Val}).
645
646s_delete_object(Val) when tuple(Val), size(Val) > 2 ->
647    Tab = element(1, Val),
648    delete_object(Tab, Val, sticky_write);
649s_delete_object(Val) ->
650    abort({bad_type, Val}).
651
652delete_object(Tab, Val, LockKind) ->
653    case get(mnesia_activity_state) of
654	{?DEFAULT_ACCESS, Tid, Ts} ->
655	    delete_object(Tid, Ts, Tab, Val, LockKind);
656	{Mod, Tid, Ts} ->
657	    Mod:delete_object(Tid, Ts, Tab, Val, LockKind);
658	_ ->
659	    abort(no_transaction)
660    end.
661
662delete_object(Tid, Ts, Tab, Val, LockKind)
663  when atom(Tab), Tab /= schema, tuple(Val), size(Val) > 2 ->
664      case element(1, Tid) of
665	  ets ->
666	      ?ets_match_delete(Tab, Val),
667	      ok;
668	  tid ->
669	      Store = Ts#tidstore.store,
670	      Oid = {Tab, element(2, Val)},
671	      case LockKind of
672		  write ->
673		      mnesia_locker:wlock(Tid, Store, Oid);
674		  sticky_write ->
675		      mnesia_locker:sticky_wlock(Tid, Store, Oid);
676		  _ ->
677		      abort({bad_type, Tab, LockKind})
678	      end,
679	      case val({Tab, setorbag}) of
680		  bag ->
681		      ?ets_match_delete(Store, {Oid, Val, '_'}),
682		      ?ets_insert(Store, {Oid, Val, delete_object});
683		  _ ->
684		      case ?ets_match_object(Store, {Oid, '_', write}) of
685			  [] ->
686			      ?ets_match_delete(Store, {Oid, Val, '_'}),
687			      ?ets_insert(Store, {Oid, Val, delete_object});
688			  _  ->
689			      ?ets_delete(Store, Oid),
690			      ?ets_insert(Store, {Oid, Oid, delete})
691		      end
692	      end,
693	      ok;
694	Protocol ->
695	      do_dirty_delete_object(Protocol, Tab, Val)
696    end;
697delete_object(_Tid, _Ts, Tab, _Key, _LockKind) ->
698    abort({bad_type, Tab}).
699
700%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
701%% Access within an activity - read
702
703read({Tab, Key}) ->
704    read(Tab, Key, read);
705read(Oid) ->
706    abort({bad_type, Oid}).
707
708wread({Tab, Key}) ->
709    read(Tab, Key, write);
710wread(Oid) ->
711    abort({bad_type, Oid}).
712
713read(Tab, Key, LockKind) ->
714    case get(mnesia_activity_state) of
715	{?DEFAULT_ACCESS, Tid, Ts} ->
716	    read(Tid, Ts, Tab, Key, LockKind);
717	{Mod, Tid, Ts} ->
718	    Mod:read(Tid, Ts, Tab, Key, LockKind);
719	_ ->
720	    abort(no_transaction)
721    end.
722
723read(Tid, Ts, Tab, Key, LockKind)
724  when atom(Tab), Tab /= schema ->
725      case element(1, Tid) of
726	  ets ->
727	      ?ets_lookup(Tab, Key);
728	  tid ->
729	      Store = Ts#tidstore.store,
730	      Oid = {Tab, Key},
731	      Objs =
732		  case LockKind of
733		      read ->
734			  mnesia_locker:rlock(Tid, Store, Oid);
735		      write ->
736			  mnesia_locker:rwlock(Tid, Store, Oid);
737		      sticky_write ->
738			  mnesia_locker:sticky_rwlock(Tid, Store, Oid);
739		      _ ->
740			  abort({bad_type, Tab, LockKind})
741		  end,
742	      add_written(?ets_lookup(Store, Oid), Tab, Objs);
743	  _Protocol ->
744	      dirty_read(Tab, Key)
745    end;
746read(_Tid, _Ts, Tab, _Key, _LockKind) ->
747    abort({bad_type, Tab}).
748
749%%%%%%%%%%%%%%%%%%%%%
750%% Iterators
751
752foldl(Fun, Acc, Tab) ->
753    foldl(Fun, Acc, Tab, read).
754
755foldl(Fun, Acc, Tab, LockKind) when function(Fun) ->
756    case get(mnesia_activity_state) of
757	{?DEFAULT_ACCESS, Tid, Ts} ->
758	    foldl(Tid, Ts, Fun, Acc, Tab, LockKind);
759	{Mod, Tid, Ts} ->
760	    Mod:foldl(Tid, Ts, Fun, Acc, Tab, LockKind);
761	_ ->
762	    abort(no_transaction)
763    end.
764
765foldl(ActivityId, Opaque, Fun, Acc, Tab, LockKind) ->
766    {Type, Prev} = init_iteration(ActivityId, Opaque, Tab, LockKind),
767    Res = (catch do_foldl(ActivityId, Opaque, Tab, dirty_first(Tab), Fun, Acc, Type, Prev)),
768    close_iteration(Res, Tab).
769
770do_foldl(A, O, Tab, '$end_of_table', Fun, RAcc, _Type, Stored) ->
771    lists:foldl(fun(Key, Acc) ->
772			lists:foldl(Fun, Acc, read(A, O, Tab, Key, read))
773		end, RAcc, Stored);
774do_foldl(A, O, Tab, Key, Fun, Acc, ordered_set, [H | Stored]) when H == Key ->
775    NewAcc = lists:foldl(Fun, Acc, read(A, O, Tab, Key, read)),
776    do_foldl(A, O, Tab, dirty_next(Tab, Key), Fun, NewAcc, ordered_set, Stored);
777do_foldl(A, O, Tab, Key, Fun, Acc, ordered_set, [H | Stored]) when H < Key ->
778    NewAcc = lists:foldl(Fun, Acc, read(A, O, Tab, H, read)),
779    do_foldl(A, O, Tab, Key, Fun, NewAcc, ordered_set, Stored);
780do_foldl(A, O, Tab, Key, Fun, Acc, ordered_set, [H | Stored]) when H > Key ->
781    NewAcc = lists:foldl(Fun, Acc, read(A, O, Tab, Key, read)),
782    do_foldl(A, O, Tab, dirty_next(Tab, Key), Fun, NewAcc, ordered_set, [H |Stored]);
783do_foldl(A, O, Tab, Key, Fun, Acc, Type, Stored) ->  %% Type is set or bag
784    NewAcc = lists:foldl(Fun, Acc, read(A, O, Tab, Key, read)),
785    NewStored = ordsets:del_element(Key, Stored),
786    do_foldl(A, O, Tab, dirty_next(Tab, Key), Fun, NewAcc, Type, NewStored).
787
788foldr(Fun, Acc, Tab) ->
789    foldr(Fun, Acc, Tab, read).
790foldr(Fun, Acc, Tab, LockKind) when function(Fun) ->
791    case get(mnesia_activity_state) of
792	{?DEFAULT_ACCESS, Tid, Ts} ->
793	    foldr(Tid, Ts, Fun, Acc, Tab, LockKind);
794	{Mod, Tid, Ts} ->
795	    Mod:foldr(Tid, Ts, Fun, Acc, Tab, LockKind);
796	_ ->
797	    abort(no_transaction)
798    end.
799
800foldr(ActivityId, Opaque, Fun, Acc, Tab, LockKind) ->
801    {Type, TempPrev} = init_iteration(ActivityId, Opaque, Tab, LockKind),
802    Prev =
803	if
804	    Type == ordered_set ->
805		lists:reverse(TempPrev);
806	    true ->      %% Order doesn't matter for set and bag
807		TempPrev %% Keep the order so we can use ordsets:del_element
808	end,
809    Res = (catch do_foldr(ActivityId, Opaque, Tab, dirty_last(Tab), Fun, Acc, Type, Prev)),
810    close_iteration(Res, Tab).
811
812do_foldr(A, O, Tab, '$end_of_table', Fun, RAcc, _Type, Stored) ->
813    lists:foldl(fun(Key, Acc) ->
814			lists:foldl(Fun, Acc, read(A, O, Tab, Key, read))
815		end, RAcc, Stored);
816do_foldr(A, O, Tab, Key, Fun, Acc, ordered_set, [H | Stored]) when H == Key ->
817    NewAcc = lists:foldl(Fun, Acc, read(A, O, Tab, Key, read)),
818    do_foldr(A, O, Tab, dirty_prev(Tab, Key), Fun, NewAcc, ordered_set, Stored);
819do_foldr(A, O, Tab, Key, Fun, Acc, ordered_set, [H | Stored]) when H > Key ->
820    NewAcc = lists:foldl(Fun, Acc, read(A, O, Tab, H, read)),
821    do_foldr(A, O, Tab, Key, Fun, NewAcc, ordered_set, Stored);
822do_foldr(A, O, Tab, Key, Fun, Acc, ordered_set, [H | Stored]) when H < Key ->
823    NewAcc = lists:foldl(Fun, Acc, read(A, O, Tab, Key, read)),
824    do_foldr(A, O, Tab, dirty_prev(Tab, Key), Fun, NewAcc, ordered_set, [H |Stored]);
825do_foldr(A, O, Tab, Key, Fun, Acc, Type, Stored) ->  %% Type is set or bag
826    NewAcc = lists:foldl(Fun, Acc, read(A, O, Tab, Key, read)),
827    NewStored = ordsets:del_element(Key, Stored),
828    do_foldr(A, O, Tab, dirty_prev(Tab, Key), Fun, NewAcc, Type, NewStored).
829
830init_iteration(ActivityId, Opaque, Tab, LockKind) ->
831    lock(ActivityId, Opaque, {table, Tab}, LockKind),
832    Type = val({Tab, setorbag}),
833    Previous = add_previous(ActivityId, Opaque, Type, Tab),
834    St = val({Tab, storage_type}),
835    if
836	St == unknown ->
837	    ignore;
838	true ->
839	    mnesia_lib:db_fixtable(St, Tab, true)
840    end,
841    {Type, Previous}.
842
843close_iteration(Res, Tab) ->
844    case val({Tab, storage_type}) of
845	unknown ->
846	    ignore;
847	St ->
848	    mnesia_lib:db_fixtable(St, Tab, false)
849    end,
850    case Res of
851	{'EXIT', {aborted, What}} ->
852	   abort(What);
853	{'EXIT', What} ->
854	    abort(What);
855	_ ->
856	    Res
857    end.
858
859add_previous(_ActivityId, non_transaction, _Type, _Tab) ->
860    [];
861add_previous(_Tid, Ts, _Type, Tab) ->
862    Previous = ?ets_match(Ts#tidstore.store, {{Tab, '$1'}, '_', write}),
863    lists:sort(lists:concat(Previous)).
864
865%% This routine fixes up the return value from read/1 so that
866%% it is correct with respect to what this particular transaction
867%% has already written, deleted .... etc
868
869add_written([], _Tab, Objs) ->
870    Objs;  % standard normal fast case
871add_written(Written, Tab, Objs) ->
872    case val({Tab, setorbag}) of
873	bag ->
874	    add_written_to_bag(Written, Objs, []);
875	_   ->
876	    add_written_to_set(Written)
877    end.
878
879add_written_to_set(Ws) ->
880    case lists:last(Ws) of
881	{_, _, delete} -> [];
882	{_, Val, write} -> [Val];
883	{_, _, delete_object} -> []
884    end.
885
886add_written_to_bag([{_, Val, write} | Tail], Objs, Ack) ->
887    add_written_to_bag(Tail, lists:delete(Val, Objs), [Val | Ack]);
888add_written_to_bag([], Objs, Ack) ->
889    Objs ++ lists:reverse(Ack); %% Oldest write first as in ets
890add_written_to_bag([{_, _ , delete} | Tail], _Objs, _Ack) ->
891    %% This transaction just deleted all objects
892    %% with this key
893    add_written_to_bag(Tail, [], []);
894add_written_to_bag([{_, Val, delete_object} | Tail], Objs, Ack) ->
895    add_written_to_bag(Tail, lists:delete(Val, Objs), lists:delete(Val, Ack)).
896
897match_object(Pat) when tuple(Pat), size(Pat) > 2 ->
898    Tab = element(1, Pat),
899    match_object(Tab, Pat, read);
900match_object(Pat) ->
901    abort({bad_type, Pat}).
902
903match_object(Tab, Pat, LockKind) ->
904    case get(mnesia_activity_state) of
905	{?DEFAULT_ACCESS, Tid, Ts} ->
906	    match_object(Tid, Ts, Tab, Pat, LockKind);
907	{Mod, Tid, Ts} ->
908	    Mod:match_object(Tid, Ts, Tab, Pat, LockKind);
909	_ ->
910	    abort(no_transaction)
911    end.
912
913match_object(Tid, Ts, Tab, Pat, LockKind)
914  when atom(Tab), Tab /= schema, tuple(Pat), size(Pat) > 2 ->
915    case element(1, Tid) of
916	ets ->
917	    mnesia_lib:db_match_object(ram_copies, Tab, Pat);
918	tid ->
919	    Key = element(2, Pat),
920	    case has_var(Key) of
921		false -> lock_record(Tid, Ts, Tab, Key, LockKind);
922		true  -> lock_table(Tid, Ts, Tab, LockKind)
923	    end,
924	    Objs = dirty_match_object(Tab, Pat),
925	    add_written_match(Ts#tidstore.store, Pat, Tab, Objs);
926	_Protocol ->
927	    dirty_match_object(Tab, Pat)
928    end;
929match_object(_Tid, _Ts, Tab, Pat, _LockKind) ->
930    abort({bad_type, Tab, Pat}).
931
932add_written_match(S, Pat, Tab, Objs) ->
933    Ops = find_ops(S, Tab, Pat),
934    add_match(Ops, Objs, val({Tab, setorbag})).
935
936find_ops(S, Tab, Pat) ->
937    GetWritten = [{{{Tab, '_'}, Pat, write}, [], ['$_']},
938		  {{{Tab, '_'}, '_', delete}, [], ['$_']},
939		  {{{Tab, '_'}, Pat, delete_object}, [], ['$_']}],
940    ets:select(S, GetWritten).
941
942add_match([], Objs, _Type) ->
943    Objs;
944add_match(Written, Objs, ordered_set) ->
945    %% Must use keysort which is stable
946    add_ordered_match(lists:keysort(1,Written), Objs, []);
947add_match([{Oid, _, delete}|R], Objs, Type) ->
948    add_match(R, deloid(Oid, Objs), Type);
949add_match([{_Oid, Val, delete_object}|R], Objs, Type) ->
950    add_match(R, lists:delete(Val, Objs), Type);
951add_match([{_Oid, Val, write}|R], Objs, bag) ->
952    add_match(R, [Val | lists:delete(Val, Objs)], bag);
953add_match([{Oid, Val, write}|R], Objs, set) ->
954    add_match(R, [Val | deloid(Oid,Objs)],set).
955
956%% For ordered_set only !!
957add_ordered_match(Written = [{{_, Key}, _, _}|_], [Obj|Objs], Acc)
958  when Key > element(2, Obj) ->
959    add_ordered_match(Written, Objs, [Obj|Acc]);
960add_ordered_match([{{_, Key}, Val, write}|Rest], Objs =[Obj|_], Acc)
961  when Key < element(2, Obj) ->
962    add_ordered_match(Rest, [Val|Objs],Acc);
963add_ordered_match([{{_, Key}, _, _DelOP}|Rest], Objs =[Obj|_], Acc)
964  when Key < element(2, Obj) ->
965    add_ordered_match(Rest,Objs,Acc);
966%% Greater than last object
967add_ordered_match([{_, Val, write}|Rest], [], Acc) ->
968    add_ordered_match(Rest, [Val], Acc);
969add_ordered_match([_|Rest], [], Acc) ->
970    add_ordered_match(Rest, [], Acc);
971%% Keys are equal from here
972add_ordered_match([{_, Val, write}|Rest], [_Obj|Objs], Acc) ->
973    add_ordered_match(Rest, [Val|Objs], Acc);
974add_ordered_match([{_, _Val, delete}|Rest], [_Obj|Objs], Acc) ->
975    add_ordered_match(Rest, Objs, Acc);
976add_ordered_match([{_, Val, delete_object}|Rest], [Val|Objs], Acc) ->
977    add_ordered_match(Rest, Objs, Acc);
978add_ordered_match([{_, _, delete_object}|Rest], Objs, Acc) ->
979    add_ordered_match(Rest, Objs, Acc);
980add_ordered_match([], Objs, Acc) ->
981    lists:reverse(Acc, Objs).
982
983
984%%%%%%%%%%%%%%%%%%
985% select
986
987select(Tab, Pat) ->
988    select(Tab, Pat, read).
989select(Tab, Pat, LockKind)
990  when atom(Tab), Tab /= schema, list(Pat) ->
991    case get(mnesia_activity_state) of
992	{?DEFAULT_ACCESS, Tid, Ts} ->
993	    select(Tid, Ts, Tab, Pat, LockKind);
994	{Mod, Tid, Ts} ->
995	    Mod:select(Tid, Ts, Tab, Pat, LockKind);
996	_ ->
997	    abort(no_transaction)
998    end;
999select(Tab, Pat, _Lock) ->
1000    abort({badarg, Tab, Pat}).
1001
1002select(Tid, Ts, Tab, Spec, LockKind) ->
1003    SelectFun = fun(FixedSpec) -> dirty_select(Tab, FixedSpec) end,
1004    fun_select(Tid, Ts, Tab, Spec, LockKind, Tab, SelectFun).
1005
1006fun_select(Tid, Ts, Tab, Spec, LockKind, TabPat, SelectFun) ->
1007    case element(1, Tid) of
1008	ets ->
1009	    mnesia_lib:db_select(ram_copies, Tab, Spec);
1010	tid ->
1011	    Store = Ts#tidstore.store,
1012	    Written = ?ets_match_object(Store, {{TabPat, '_'}, '_', '_'}),
1013	    %% Avoid table lock if possible
1014	    case Spec of
1015		[{HeadPat,_, _}] when tuple(HeadPat), size(HeadPat) > 2 ->
1016		    Key = element(2, HeadPat),
1017		    case has_var(Key) of
1018			false -> lock_record(Tid, Ts, Tab, Key, LockKind);
1019			true  -> lock_table(Tid, Ts, Tab, LockKind)
1020		    end;
1021		_ ->
1022		    lock_table(Tid, Ts, Tab, LockKind)
1023	    end,
1024	    case Written of
1025		[] ->
1026		    %% Nothing changed in the table during this transaction,
1027		    %% Simple case get results from [d]ets
1028		    SelectFun(Spec);
1029		_ ->
1030		    %% Hard (slow case) records added or deleted earlier
1031		    %% in the transaction, have to cope with that.
1032		    Type = val({Tab, setorbag}),
1033		    FixedSpec = get_record_pattern(Spec),
1034		    TabRecs = SelectFun(FixedSpec),
1035		    FixedRes = add_match(Written, TabRecs, Type),
1036		    CMS = ets:match_spec_compile(Spec),
1037% 		    case Type of
1038% 			ordered_set ->
1039% 			    ets:match_spec_run(lists:sort(FixedRes), CMS);
1040% 			_ ->
1041% 			    ets:match_spec_run(FixedRes, CMS)
1042% 		    end
1043		    ets:match_spec_run(FixedRes, CMS)
1044	    end;
1045	_Protocol ->
1046	    SelectFun(Spec)
1047    end.
1048
1049get_record_pattern([]) ->
1050    [];
1051get_record_pattern([{M,C,_B}|R]) ->
1052    [{M,C,['$_']} | get_record_pattern(R)].
1053
1054deloid(_Oid, []) ->
1055    [];
1056deloid({Tab, Key}, [H | T]) when element(2, H) == Key ->
1057    deloid({Tab, Key}, T);
1058deloid(Oid, [H | T]) ->
1059    [H | deloid(Oid, T)].
1060
1061all_keys(Tab) ->
1062    case get(mnesia_activity_state) of
1063	{?DEFAULT_ACCESS, Tid, Ts} ->
1064	    all_keys(Tid, Ts, Tab, read);
1065	{Mod, Tid, Ts} ->
1066	    Mod:all_keys(Tid, Ts, Tab, read);
1067	_ ->
1068	    abort(no_transaction)
1069    end.
1070
1071all_keys(Tid, Ts, Tab, LockKind)
1072  when atom(Tab), Tab /= schema ->
1073    Pat0 = val({Tab, wild_pattern}),
1074    Pat = setelement(2, Pat0, '$1'),
1075    Keys = select(Tid, Ts, Tab, [{Pat, [], ['$1']}], LockKind),
1076    case val({Tab, setorbag}) of
1077	bag ->
1078	    mnesia_lib:uniq(Keys);
1079	_ ->
1080	    Keys
1081    end;
1082all_keys(_Tid, _Ts, Tab, _LockKind) ->
1083    abort({bad_type, Tab}).
1084
1085index_match_object(Pat, Attr) when tuple(Pat), size(Pat) > 2 ->
1086    Tab = element(1, Pat),
1087    index_match_object(Tab, Pat, Attr, read);
1088index_match_object(Pat, _Attr) ->
1089    abort({bad_type, Pat}).
1090
1091index_match_object(Tab, Pat, Attr, LockKind) ->
1092    case get(mnesia_activity_state) of
1093	{?DEFAULT_ACCESS, Tid, Ts} ->
1094	    index_match_object(Tid, Ts, Tab, Pat, Attr, LockKind);
1095	{Mod, Tid, Ts} ->
1096	    Mod:index_match_object(Tid, Ts, Tab, Pat, Attr, LockKind);
1097	_ ->
1098	    abort(no_transaction)
1099    end.
1100
1101index_match_object(Tid, Ts, Tab, Pat, Attr, LockKind)
1102  when atom(Tab), Tab /= schema, tuple(Pat), size(Pat) > 2 ->
1103    case element(1, Tid) of
1104	ets ->
1105	    dirty_index_match_object(Tab, Pat, Attr); % Should be optimized?
1106	tid ->
1107	    case mnesia_schema:attr_tab_to_pos(Tab, Attr) of
1108		Pos when Pos =< size(Pat) ->
1109		    case LockKind of
1110			read ->
1111			    Store = Ts#tidstore.store,
1112			    mnesia_locker:rlock_table(Tid, Store, Tab),
1113			    Objs = dirty_index_match_object(Tab, Pat, Attr),
1114			    add_written_match(Store, Pat, Tab, Objs);
1115			_ ->
1116			    abort({bad_type, Tab, LockKind})
1117		    end;
1118		BadPos ->
1119		    abort({bad_type, Tab, BadPos})
1120	    end;
1121	_Protocol ->
1122	    dirty_index_match_object(Tab, Pat, Attr)
1123    end;
1124index_match_object(_Tid, _Ts, Tab, Pat, _Attr, _LockKind) ->
1125    abort({bad_type, Tab, Pat}).
1126
1127index_read(Tab, Key, Attr) ->
1128    case get(mnesia_activity_state) of
1129	{?DEFAULT_ACCESS, Tid, Ts} ->
1130	    index_read(Tid, Ts, Tab, Key, Attr, read);
1131	{Mod, Tid, Ts} ->
1132	    Mod:index_read(Tid, Ts, Tab, Key, Attr, read);
1133	_ ->
1134	    abort(no_transaction)
1135    end.
1136
1137index_read(Tid, Ts, Tab, Key, Attr, LockKind)
1138  when atom(Tab), Tab /= schema ->
1139    case element(1, Tid) of
1140	ets ->
1141	    dirty_index_read(Tab, Key, Attr); % Should be optimized?
1142	tid ->
1143	    Pos = mnesia_schema:attr_tab_to_pos(Tab, Attr),
1144	    case LockKind of
1145		read ->
1146		    case has_var(Key) of
1147			false ->
1148			    Store = Ts#tidstore.store,
1149			    Objs = mnesia_index:read(Tid, Store, Tab, Key, Pos),
1150			    Pat = setelement(Pos, val({Tab, wild_pattern}), Key),
1151			    add_written_match(Store, Pat, Tab, Objs);
1152			true ->
1153			    abort({bad_type, Tab, Attr, Key})
1154		    end;
1155		_ ->
1156		    abort({bad_type, Tab, LockKind})
1157	    end;
1158	_Protocol ->
1159	    dirty_index_read(Tab, Key, Attr)
1160    end;
1161index_read(_Tid, _Ts, Tab, _Key, _Attr, _LockKind) ->
1162    abort({bad_type, Tab}).
1163
1164%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
1165%% Dirty access regardless of activities - updates
1166
1167dirty_write(Val) when tuple(Val), size(Val) > 2  ->
1168    Tab = element(1, Val),
1169    dirty_write(Tab, Val);
1170dirty_write(Val) ->
1171    abort({bad_type, Val}).
1172
1173dirty_write(Tab, Val) ->
1174    do_dirty_write(async_dirty, Tab, Val).
1175
1176do_dirty_write(SyncMode, Tab, Val)
1177  when atom(Tab), Tab /= schema, tuple(Val), size(Val) > 2 ->
1178    case ?catch_val({Tab, record_validation}) of
1179	{RecName, Arity, _Type}
1180	when size(Val) == Arity, RecName == element(1, Val) ->
1181	    Oid = {Tab, element(2, Val)},
1182	    mnesia_tm:dirty(SyncMode, {Oid, Val, write});
1183	{'EXIT', _} ->
1184	    abort({no_exists, Tab});
1185	_ ->
1186	    abort({bad_type, Val})
1187    end;
1188do_dirty_write(_SyncMode, Tab, Val) ->
1189    abort({bad_type, Tab, Val}).
1190
1191dirty_delete({Tab, Key}) ->
1192    dirty_delete(Tab, Key);
1193dirty_delete(Oid) ->
1194    abort({bad_type, Oid}).
1195
1196dirty_delete(Tab, Key) ->
1197    do_dirty_delete(async_dirty, Tab, Key).
1198
1199do_dirty_delete(SyncMode, Tab, Key) when atom(Tab), Tab /= schema  ->
1200    Oid = {Tab, Key},
1201    mnesia_tm:dirty(SyncMode, {Oid, Oid, delete});
1202do_dirty_delete(_SyncMode, Tab, _Key) ->
1203    abort({bad_type, Tab}).
1204
1205dirty_delete_object(Val) when tuple(Val), size(Val) > 2 ->
1206    Tab = element(1, Val),
1207    dirty_delete_object(Tab, Val);
1208dirty_delete_object(Val) ->
1209    abort({bad_type, Val}).
1210
1211dirty_delete_object(Tab, Val) ->
1212    do_dirty_delete_object(async_dirty, Tab, Val).
1213
1214do_dirty_delete_object(SyncMode, Tab, Val)
1215    when atom(Tab), Tab /= schema, tuple(Val), size(Val) > 2 ->
1216    Oid = {Tab, element(2, Val)},
1217    mnesia_tm:dirty(SyncMode, {Oid, Val, delete_object});
1218do_dirty_delete_object(_SyncMode, Tab, Val) ->
1219    abort({bad_type, Tab, Val}).
1220
1221%% A Counter is an Oid being {CounterTab, CounterName}
1222
1223dirty_update_counter({Tab, Key}, Incr) ->
1224    dirty_update_counter(Tab, Key, Incr);
1225dirty_update_counter(Counter, _Incr) ->
1226    abort({bad_type, Counter}).
1227
1228dirty_update_counter(Tab, Key, Incr) ->
1229    do_dirty_update_counter(async_dirty, Tab, Key, Incr).
1230
1231do_dirty_update_counter(SyncMode, Tab, Key, Incr)
1232  when atom(Tab), Tab /= schema, integer(Incr) ->
1233    case ?catch_val({Tab, record_validation}) of
1234	{RecName, 3, set} ->
1235	    Oid = {Tab, Key},
1236	    mnesia_tm:dirty(SyncMode, {Oid, {RecName, Incr}, update_counter});
1237	_ ->
1238	    abort({combine_error, Tab, update_counter})
1239    end;
1240do_dirty_update_counter(_SyncMode, Tab, _Key, Incr) ->
1241    abort({bad_type, Tab, Incr}).
1242
1243%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
1244%% Dirty access regardless of activities - read
1245
1246dirty_read({Tab, Key}) ->
1247    dirty_read(Tab, Key);
1248dirty_read(Oid) ->
1249    abort({bad_type, Oid}).
1250
1251dirty_read(Tab, Key)
1252  when atom(Tab), Tab /= schema ->
1253%%    case catch ?ets_lookup(Tab, Key) of
1254%%        {'EXIT', _} ->
1255            %% Bad luck, we have to perform a real lookup
1256            dirty_rpc(Tab, mnesia_lib, db_get, [Tab, Key]);
1257%%        Val ->
1258%%            Val
1259%%    end;
1260dirty_read(Tab, _Key) ->
1261    abort({bad_type, Tab}).
1262
1263dirty_match_object(Pat) when tuple(Pat), size(Pat) > 2 ->
1264    Tab = element(1, Pat),
1265    dirty_match_object(Tab, Pat);
1266dirty_match_object(Pat) ->
1267    abort({bad_type, Pat}).
1268
1269dirty_match_object(Tab, Pat)
1270  when atom(Tab), Tab /= schema, tuple(Pat), size(Pat) > 2 ->
1271    dirty_rpc(Tab, ?MODULE, remote_dirty_match_object, [Tab, Pat]);
1272dirty_match_object(Tab, Pat) ->
1273    abort({bad_type, Tab, Pat}).
1274
1275remote_dirty_match_object(Tab, Pat) ->
1276    Key = element(2, Pat),
1277    case has_var(Key) of
1278	false ->
1279	    mnesia_lib:db_match_object(Tab, Pat);
1280	true ->
1281	    PosList = val({Tab, index}),
1282	    remote_dirty_match_object(Tab, Pat, PosList)
1283    end.
1284
1285remote_dirty_match_object(Tab, Pat, [Pos | Tail]) when Pos =< size(Pat) ->
1286    IxKey = element(Pos, Pat),
1287    case has_var(IxKey) of
1288	false ->
1289	    mnesia_index:dirty_match_object(Tab, Pat, Pos);
1290	true ->
1291	    remote_dirty_match_object(Tab, Pat, Tail)
1292    end;
1293remote_dirty_match_object(Tab, Pat, []) ->
1294    mnesia_lib:db_match_object(Tab, Pat);
1295remote_dirty_match_object(Tab, Pat, _PosList) ->
1296    abort({bad_type, Tab, Pat}).
1297
1298dirty_select(Tab, Spec) when atom(Tab), Tab /= schema, list(Spec) ->
1299    dirty_rpc(Tab, ?MODULE, remote_dirty_select, [Tab, Spec]);
1300dirty_select(Tab, Spec) ->
1301    abort({bad_type, Tab, Spec}).
1302
1303remote_dirty_select(Tab, Spec) ->
1304    case Spec of
1305	[{HeadPat, _, _}] when tuple(HeadPat), size(HeadPat) > 2 ->
1306	    Key = element(2, HeadPat),
1307	    case has_var(Key) of
1308		false ->
1309		    mnesia_lib:db_select(Tab, Spec);
1310		true  ->
1311		    PosList = val({Tab, index}),
1312		    remote_dirty_select(Tab, Spec, PosList)
1313	    end;
1314	_ ->
1315	    mnesia_lib:db_select(Tab, Spec)
1316    end.
1317
1318remote_dirty_select(Tab, [{HeadPat,_, _}] = Spec, [Pos | Tail])
1319  when tuple(HeadPat), size(HeadPat) > 2, Pos =< size(Spec) ->
1320    Key = element(Pos, HeadPat),
1321    case has_var(Key) of
1322	false ->
1323	    Recs = mnesia_index:dirty_select(Tab, Spec, Pos),
1324	    %% Returns the records without applying the match spec
1325	    %% The actual filtering is handled by the caller
1326	    CMS = ets:match_spec_compile(Spec),
1327	    case val({Tab, setorbag}) of
1328		ordered_set ->
1329		    ets:match_spec_run(lists:sort(Recs), CMS);
1330		_ ->
1331		    ets:match_spec_run(Recs, CMS)
1332	    end;
1333	true  ->
1334	    remote_dirty_select(Tab, Spec, Tail)
1335    end;
1336remote_dirty_select(Tab, Spec, _) ->
1337    mnesia_lib:db_select(Tab, Spec).
1338
1339dirty_all_keys(Tab) when atom(Tab), Tab /= schema ->
1340    case ?catch_val({Tab, wild_pattern}) of
1341	{'EXIT', _} ->
1342	    abort({no_exists, Tab});
1343	Pat0 ->
1344	    Pat = setelement(2, Pat0, '$1'),
1345	    Keys = dirty_select(Tab, [{Pat, [], ['$1']}]),
1346	    case val({Tab, setorbag}) of
1347		bag -> mnesia_lib:uniq(Keys);
1348		_ -> Keys
1349	    end
1350    end;
1351dirty_all_keys(Tab) ->
1352    abort({bad_type, Tab}).
1353
1354dirty_index_match_object(Pat, Attr) when tuple(Pat), size(Pat) > 2 ->
1355    Tab = element(1, Pat),
1356    dirty_index_match_object(Tab, Pat, Attr);
1357dirty_index_match_object(Pat, _Attr) ->
1358    abort({bad_type, Pat}).
1359
1360dirty_index_match_object(Tab, Pat, Attr)
1361  when atom(Tab), Tab /= schema, tuple(Pat), size(Pat) > 2 ->
1362    case mnesia_schema:attr_tab_to_pos(Tab, Attr) of
1363	Pos when Pos =< size(Pat) ->
1364	    case has_var(element(2, Pat)) of
1365		false ->
1366		    dirty_match_object(Tab, Pat);
1367		true ->
1368		    Elem = element(Pos, Pat),
1369		    case has_var(Elem) of
1370			false ->
1371			    dirty_rpc(Tab, mnesia_index, dirty_match_object,
1372				      [Tab, Pat, Pos]);
1373			true ->
1374			    abort({bad_type, Tab, Attr, Elem})
1375		    end
1376	    end;
1377	BadPos ->
1378	    abort({bad_type, Tab, BadPos})
1379    end;
1380dirty_index_match_object(Tab, Pat, _Attr) ->
1381    abort({bad_type, Tab, Pat}).
1382
1383dirty_index_read(Tab, Key, Attr) when atom(Tab), Tab /= schema ->
1384    Pos = mnesia_schema:attr_tab_to_pos(Tab, Attr),
1385    case has_var(Key) of
1386	false ->
1387	    mnesia_index:dirty_read(Tab, Key, Pos);
1388	true ->
1389	    abort({bad_type, Tab, Attr, Key})
1390    end;
1391dirty_index_read(Tab, _Key, _Attr) ->
1392    abort({bad_type, Tab}).
1393
1394dirty_slot(Tab, Slot) when atom(Tab), Tab /= schema, integer(Slot)  ->
1395    dirty_rpc(Tab, mnesia_lib, db_slot, [Tab, Slot]);
1396dirty_slot(Tab, Slot) ->
1397    abort({bad_type, Tab, Slot}).
1398
1399dirty_first(Tab) when atom(Tab), Tab /= schema ->
1400    dirty_rpc(Tab, mnesia_lib, db_first, [Tab]);
1401dirty_first(Tab) ->
1402    abort({bad_type, Tab}).
1403
1404dirty_last(Tab) when atom(Tab), Tab /= schema ->
1405    dirty_rpc(Tab, mnesia_lib, db_last, [Tab]);
1406dirty_last(Tab) ->
1407    abort({bad_type, Tab}).
1408
1409dirty_next(Tab, Key) when atom(Tab), Tab /= schema ->
1410    dirty_rpc(Tab, mnesia_lib, db_next_key, [Tab, Key]);
1411dirty_next(Tab, _Key) ->
1412    abort({bad_type, Tab}).
1413
1414dirty_prev(Tab, Key) when atom(Tab), Tab /= schema ->
1415    dirty_rpc(Tab, mnesia_lib, db_prev_key, [Tab, Key]);
1416dirty_prev(Tab, _Key) ->
1417    abort({bad_type, Tab}).
1418
1419
1420dirty_rpc(Tab, M, F, Args) ->
1421    Node = val({Tab, where_to_read}),
1422    do_dirty_rpc(Tab, Node, M, F, Args).
1423
1424do_dirty_rpc(_Tab, nowhere, _, _, Args) ->
1425    mnesia:abort({no_exists, Args});
1426do_dirty_rpc(Tab, Node, M, F, Args) ->
1427    case rpc:call(Node, M, F, Args) of
1428	{badrpc,{'EXIT', {undef, [{ M, F, _} | _]}}}
1429	  when M == ?MODULE, F == remote_dirty_select ->
1430	    %% Oops, the other node has not been upgraded
1431	    %% to 4.0.3 yet. Lets do it the old way.
1432	    %% Remove this in next release.
1433	    do_dirty_rpc(Tab, Node, mnesia_lib, db_select, Args);
1434	{badrpc, Reason} ->
1435	    erlang:yield(), %% Do not be too eager
1436	    case mnesia_controller:call({check_w2r, Node, Tab}) of % Sync
1437		NewNode when NewNode == Node ->
1438		    ErrorTag = mnesia_lib:dirty_rpc_error_tag(Reason),
1439		    mnesia:abort({ErrorTag, Args});
1440		NewNode ->
1441		    case get(mnesia_activity_state) of
1442			{_Mod, Tid, _Ts} when record(Tid, tid) ->
1443			    %% In order to perform a consistent
1444			    %% retry of a transaction we need
1445			    %% to acquire the lock on the NewNode.
1446			    %% In this context we do neither know
1447			    %% the kind or granularity of the lock.
1448			    %% --> Abort the transaction
1449			    mnesia:abort({node_not_running, Node});
1450			_ ->
1451			    %% Splendid! A dirty retry is safe
1452			    %% 'Node' probably went down now
1453			    %% Let mnesia_controller get broken link message first
1454			    do_dirty_rpc(Tab, NewNode, M, F, Args)
1455		    end
1456	    end;
1457	Other ->
1458	    Other
1459    end.
1460
1461%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
1462%% Info
1463
1464%% Info about one table
1465table_info(Tab, Item) ->
1466    case get(mnesia_activity_state) of
1467	undefined ->
1468	    any_table_info(Tab, Item);
1469	{?DEFAULT_ACCESS, _Tid, _Ts} ->
1470	    any_table_info(Tab, Item);
1471	{Mod, Tid, Ts} ->
1472	    Mod:table_info(Tid, Ts, Tab, Item);
1473	_ ->
1474	    abort(no_transaction)
1475    end.
1476
1477table_info(_Tid, _Ts, Tab, Item) ->
1478    any_table_info(Tab, Item).
1479
1480
1481any_table_info(Tab, Item) when atom(Tab) ->
1482    case Item of
1483	master_nodes ->
1484	    mnesia_recover:get_master_nodes(Tab);
1485%	checkpoints ->
1486%	    case ?catch_val({Tab, commit_work}) of
1487%		[{checkpoints, List} | _] -> List;
1488%		No_chk when list(No_chk) ->  [];
1489%		Else -> info_reply(Else, Tab, Item)
1490%	    end;
1491	size ->
1492	    raw_table_info(Tab, Item);
1493	memory ->
1494	    raw_table_info(Tab, Item);
1495	type ->
1496	    case ?catch_val({Tab, setorbag}) of
1497		{'EXIT', _} ->
1498		    bad_info_reply(Tab, Item);
1499		Val ->
1500		    Val
1501	    end;
1502	all ->
1503	    case mnesia_schema:get_table_properties(Tab) of
1504		[] ->
1505		    abort({no_exists, Tab, Item});
1506		Props ->
1507		    lists:map(fun({setorbag, Type}) -> {type, Type};
1508				 (Prop) -> Prop end,
1509			      Props)
1510	    end;
1511	_ ->
1512	    case ?catch_val({Tab, Item}) of
1513		{'EXIT', _} ->
1514		    bad_info_reply(Tab, Item);
1515		Val ->
1516		    Val
1517	    end
1518    end;
1519any_table_info(Tab, _Item) ->
1520    abort({bad_type, Tab}).
1521
1522raw_table_info(Tab, Item) ->
1523    case ?catch_val({Tab, storage_type}) of
1524	ram_copies ->
1525	    info_reply(catch ?ets_info(Tab, Item), Tab, Item);
1526	disc_copies ->
1527	    info_reply(catch ?ets_info(Tab, Item), Tab, Item);
1528	disc_only_copies ->
1529	    info_reply(catch dets:info(Tab, Item), Tab, Item);
1530	unknown ->
1531	    bad_info_reply(Tab, Item);
1532	{'EXIT', _} ->
1533	    bad_info_reply(Tab, Item)
1534    end.
1535
1536info_reply({'EXIT', _Reason}, Tab, Item) ->
1537    bad_info_reply(Tab, Item);
1538info_reply({error, _Reason}, Tab, Item) ->
1539    bad_info_reply(Tab, Item);
1540info_reply(Val, _Tab, _Item) ->
1541    Val.
1542
1543bad_info_reply(_Tab, size) -> 0;
1544bad_info_reply(_Tab, memory) -> 0;
1545bad_info_reply(Tab, Item) -> abort({no_exists, Tab, Item}).
1546
1547%% Raw info about all tables
1548schema() ->
1549    mnesia_schema:info().
1550
1551%% Raw info about one tables
1552schema(Tab) ->
1553    mnesia_schema:info(Tab).
1554
1555error_description(Err) ->
1556    mnesia_lib:error_desc(Err).
1557
1558info() ->
1559    case mnesia_lib:is_running() of
1560	yes ->
1561	    TmInfo = mnesia_tm:get_info(10000),
1562	    Held = system_info(held_locks),
1563	    Queued = system_info(lock_queue),
1564
1565	    io:format("---> Processes holding locks <--- ~n", []),
1566	    lists:foreach(fun(L) -> io:format("Lock: ~p~n", [L]) end,
1567			  Held),
1568
1569	    io:format( "---> Processes waiting for locks <--- ~n", []),
1570	    lists:foreach(fun({Oid, Op, _Pid, Tid, OwnerTid}) ->
1571				  io:format("Tid ~p waits for ~p lock "
1572					    "on oid ~p owned by ~p ~n",
1573					    [Tid, Op, Oid, OwnerTid])
1574		  end, Queued),
1575	    mnesia_tm:display_info(group_leader(), TmInfo),
1576
1577	    Pat = {'_', unclear, '_'},
1578	    Uncertain = ets:match_object(mnesia_decision, Pat),
1579
1580	    io:format( "---> Uncertain transactions <--- ~n", []),
1581	    lists:foreach(fun({Tid, _, Nodes}) ->
1582				  io:format("Tid ~w waits for decision "
1583					    "from ~w~n",
1584					    [Tid, Nodes])
1585		  end, Uncertain),
1586
1587	    mnesia_controller:info(),
1588	    display_system_info(Held, Queued, TmInfo, Uncertain);
1589	_ ->
1590	    mini_info()
1591    end,
1592    ok.
1593
1594mini_info() ->
1595    io:format("===> System info in version ~p, debug level = ~p <===~n",
1596	      [system_info(version), system_info(debug)]),
1597    Not =
1598	case system_info(use_dir) of
1599	    true -> "";
1600	    false  -> "NOT "
1601	end,
1602
1603    io:format("~w. Directory ~p is ~sused.~n",
1604	      [system_info(schema_location), system_info(directory), Not]),
1605    io:format("use fallback at restart = ~w~n",
1606	      [system_info(fallback_activated)]),
1607    Running = system_info(running_db_nodes),
1608    io:format("running db nodes   = ~w~n", [Running]),
1609    All = mnesia_lib:all_nodes(),
1610    io:format("stopped db nodes   = ~w ~n", [All -- Running]).
1611
1612display_system_info(Held, Queued, TmInfo, Uncertain) ->
1613    mini_info(),
1614    display_tab_info(),
1615    S = fun(Items) -> [system_info(I) || I <- Items] end,
1616
1617    io:format("~w transactions committed, ~w aborted, "
1618	      "~w restarted, ~w logged to disc~n",
1619	      S([transaction_commits, transaction_failures,
1620		transaction_restarts, transaction_log_writes])),
1621
1622    {Active, Pending} =
1623	case TmInfo of
1624	    {timeout, _} -> {infinity, infinity};
1625	    {info, P, A} -> {length(A), length(P)}
1626	end,
1627    io:format("~w held locks, ~w in queue; "
1628	      "~w local transactions, ~w remote~n",
1629	      [length(Held), length(Queued), Active, Pending]),
1630
1631    Ufold = fun({_, _, Ns}, {C, Old}) ->
1632		    New = [N || N <- Ns, not lists:member(N, Old)],
1633		    {C + 1, New ++ Old}
1634	    end,
1635    {Ucount, Unodes} = lists:foldl(Ufold, {0, []}, Uncertain),
1636    io:format("~w transactions waits for other nodes: ~p~n",
1637	      [Ucount, Unodes]).
1638
1639display_tab_info() ->
1640    MasterTabs = mnesia_recover:get_master_node_tables(),
1641    io:format("master node tables = ~p~n", [lists:sort(MasterTabs)]),
1642
1643    Tabs = system_info(tables),
1644
1645    {Unknown, Ram, Disc, DiscOnly} =
1646	lists:foldl(fun storage_count/2, {[], [], [], []}, Tabs),
1647
1648    io:format("remote             = ~p~n", [lists:sort(Unknown)]),
1649    io:format("ram_copies         = ~p~n", [lists:sort(Ram)]),
1650    io:format("disc_copies        = ~p~n", [lists:sort(Disc)]),
1651    io:format("disc_only_copies   = ~p~n", [lists:sort(DiscOnly)]),
1652
1653    Rfoldl = fun(T, Acc) ->
1654		     Rpat =
1655			 case val({T, access_mode}) of
1656			     read_only ->
1657				 lists:sort([{A, read_only} || A <- val({T, active_replicas})]);
1658			     read_write ->
1659				 table_info(T, where_to_commit)
1660			 end,
1661		     case lists:keysearch(Rpat, 1, Acc) of
1662			 {value, {_Rpat, Rtabs}} ->
1663			     lists:keyreplace(Rpat, 1, Acc, {Rpat, [T | Rtabs]});
1664			 false ->
1665			     [{Rpat, [T]} | Acc]
1666		     end
1667	     end,
1668    Repl = lists:foldl(Rfoldl, [], Tabs),
1669    Rdisp = fun({Rpat, Rtabs}) -> io:format("~p = ~p~n", [Rpat, Rtabs]) end,
1670    lists:foreach(Rdisp, lists:sort(Repl)).
1671
1672storage_count(T, {U, R, D, DO}) ->
1673    case table_info(T, storage_type) of
1674	unknown -> {[T | U], R, D, DO};
1675	ram_copies -> {U, [T | R], D, DO};
1676	disc_copies -> {U, R, [T | D], DO};
1677	disc_only_copies -> {U, R, D, [T | DO]}
1678    end.
1679
1680system_info(Item) ->
1681    case catch system_info2(Item) of
1682	{'EXIT',Error} -> abort(Error);
1683	Other -> Other
1684    end.
1685
1686system_info2(all) ->
1687    Items = system_info_items(mnesia_lib:is_running()),
1688    [{I, system_info(I)} || I <- Items];
1689
1690system_info2(db_nodes) ->
1691    DiscNs = ?catch_val({schema, disc_copies}),
1692    RamNs = ?catch_val({schema, ram_copies}),
1693    if
1694	list(DiscNs), list(RamNs) ->
1695	    DiscNs ++ RamNs;
1696	true ->
1697	    case mnesia_schema:read_nodes() of
1698		{ok, Nodes} -> Nodes;
1699		{error,Reason} -> exit(Reason)
1700	    end
1701    end;
1702system_info2(running_db_nodes) ->
1703    case ?catch_val({current, db_nodes}) of
1704	{'EXIT',_} ->
1705	    %% Ensure that we access the intended Mnesia
1706	    %% directory. This function may not be called
1707	    %% during startup since it will cause the
1708	    %% application_controller to get into deadlock
1709	    load_mnesia_or_abort(),
1710	    mnesia_lib:running_nodes();
1711	Other ->
1712	    Other
1713    end;
1714
1715system_info2(extra_db_nodes) ->
1716    case ?catch_val(extra_db_nodes) of
1717	{'EXIT',_} ->
1718	    %% Ensure that we access the intended Mnesia
1719	    %% directory. This function may not be called
1720	    %% during startup since it will cause the
1721	    %% application_controller to get into deadlock
1722	    load_mnesia_or_abort(),
1723	    mnesia_monitor:get_env(extra_db_nodes);
1724	Other ->
1725	    Other
1726    end;
1727
1728system_info2(directory) ->
1729    case ?catch_val(directory) of
1730	{'EXIT',_} ->
1731	    %% Ensure that we access the intended Mnesia
1732	    %% directory. This function may not be called
1733	    %% during startup since it will cause the
1734	    %% application_controller to get into deadlock
1735	    load_mnesia_or_abort(),
1736	    mnesia_monitor:get_env(dir);
1737	Other ->
1738	    Other
1739    end;
1740
1741system_info2(use_dir) ->
1742    case ?catch_val(use_dir) of
1743	{'EXIT',_} ->
1744	    %% Ensure that we access the intended Mnesia
1745	    %% directory. This function may not be called
1746	    %% during startup since it will cause the
1747	    %% application_controller to get into deadlock
1748	    load_mnesia_or_abort(),
1749	    mnesia_monitor:use_dir();
1750	Other ->
1751	    Other
1752    end;
1753
1754system_info2(schema_location) ->
1755    case ?catch_val(schema_location) of
1756	{'EXIT',_} ->
1757	    %% Ensure that we access the intended Mnesia
1758	    %% directory. This function may not be called
1759	    %% during startup since it will cause the
1760	    %% application_controller to get into deadlock
1761	    load_mnesia_or_abort(),
1762	    mnesia_monitor:get_env(schema_location);
1763	Other ->
1764	    Other
1765    end;
1766
1767system_info2(fallback_activated) ->
1768    case ?catch_val(fallback_activated) of
1769	{'EXIT',_} ->
1770	    %% Ensure that we access the intended Mnesia
1771	    %% directory. This function may not be called
1772	    %% during startup since it will cause the
1773	    %% application_controller to get into deadlock
1774	    load_mnesia_or_abort(),
1775	    mnesia_bup:fallback_exists();
1776	Other ->
1777	    Other
1778    end;
1779
1780system_info2(version) ->
1781    case ?catch_val(version) of
1782	{'EXIT', _} ->
1783	    Apps = application:loaded_applications(),
1784	    case lists:keysearch(?APPLICATION, 1, Apps) of
1785		{value, {_Name, _Desc, Version}} ->
1786		    Version;
1787		false ->
1788		    %% Ensure that it does not match
1789		    {mnesia_not_loaded, node(), now()}
1790	    end;
1791	Version ->
1792	    Version
1793    end;
1794
1795system_info2(access_module) -> mnesia_monitor:get_env(access_module);
1796system_info2(auto_repair) -> mnesia_monitor:get_env(auto_repair);
1797system_info2(is_running) -> mnesia_lib:is_running();
1798system_info2(backup_module) -> mnesia_monitor:get_env(backup_module);
1799system_info2(event_module) -> mnesia_monitor:get_env(event_module);
1800system_info2(debug) -> mnesia_monitor:get_env(debug);
1801system_info2(dump_log_load_regulation) -> mnesia_monitor:get_env(dump_log_load_regulation);
1802system_info2(dump_log_write_threshold) -> mnesia_monitor:get_env(dump_log_write_threshold);
1803system_info2(dump_log_time_threshold) -> mnesia_monitor:get_env(dump_log_time_threshold);
1804system_info2(dump_log_update_in_place) ->
1805    mnesia_monitor:get_env(dump_log_update_in_place);
1806system_info2(dump_log_update_in_place) ->
1807    mnesia_monitor:get_env(dump_log_update_in_place);
1808system_info2(max_wait_for_decision) -> mnesia_monitor:get_env(max_wait_for_decision);
1809system_info2(ignore_fallback_at_startup) -> mnesia_monitor:get_env(ignore_fallback_at_startup);
1810system_info2(fallback_error_function) ->  mnesia_monitor:get_env(fallback_error_function);
1811system_info2(log_version) -> mnesia_log:version();
1812system_info2(protocol_version) -> mnesia_monitor:protocol_version();
1813system_info2(schema_version) -> mnesia_schema:version(); %backward compatibility
1814system_info2(tables) -> val({schema, tables});
1815system_info2(local_tables) -> val({schema, local_tables});
1816system_info2(master_node_tables) -> mnesia_recover:get_master_node_tables();
1817system_info2(subscribers) -> mnesia_subscr:subscribers();
1818system_info2(checkpoints) -> mnesia_checkpoint:checkpoints();
1819system_info2(held_locks) -> mnesia_locker:get_held_locks();
1820system_info2(lock_queue) -> mnesia_locker:get_lock_queue();
1821system_info2(transactions) -> mnesia_tm:get_transactions();
1822system_info2(transaction_failures) -> mnesia_lib:read_counter(trans_failures);
1823system_info2(transaction_commits) -> mnesia_lib:read_counter(trans_commits);
1824system_info2(transaction_restarts) -> mnesia_lib:read_counter(trans_restarts);
1825system_info2(transaction_log_writes) -> mnesia_dumper:get_log_writes();
1826
1827system_info2(Item) -> exit({badarg, Item}).
1828
1829system_info_items(yes) ->
1830    [
1831     access_module,
1832     auto_repair,
1833     backup_module,
1834     checkpoints,
1835     db_nodes,
1836     debug,
1837     directory,
1838     dump_log_load_regulation,
1839     dump_log_time_threshold,
1840     dump_log_update_in_place,
1841     dump_log_write_threshold,
1842     event_module,
1843     extra_db_nodes,
1844     fallback_activated,
1845     held_locks,
1846     ignore_fallback_at_startup,
1847     fallback_error_function,
1848     is_running,
1849     local_tables,
1850     lock_queue,
1851     log_version,
1852     master_node_tables,
1853     max_wait_for_decision,
1854     protocol_version,
1855     running_db_nodes,
1856     schema_location,
1857     schema_version,
1858     subscribers,
1859     tables,
1860     transaction_commits,
1861     transaction_failures,
1862     transaction_log_writes,
1863     transaction_restarts,
1864     transactions,
1865     use_dir,
1866     version
1867    ];
1868system_info_items(no) ->
1869    [
1870     auto_repair,
1871     backup_module,
1872     db_nodes,
1873     debug,
1874     directory,
1875     dump_log_load_regulation,
1876     dump_log_time_threshold,
1877     dump_log_update_in_place,
1878     dump_log_write_threshold,
1879     event_module,
1880     extra_db_nodes,
1881     ignore_fallback_at_startup,
1882     fallback_error_function,
1883     is_running,
1884     log_version,
1885     max_wait_for_decision,
1886     protocol_version,
1887     running_db_nodes,
1888     schema_location,
1889     schema_version,
1890     use_dir,
1891     version
1892    ].
1893
1894system_info() ->
1895    IsRunning = mnesia_lib:is_running(),
1896    case IsRunning of
1897	yes ->
1898	    TmInfo = mnesia_tm:get_info(10000),
1899	    Held = system_info(held_locks),
1900	    Queued = system_info(lock_queue),
1901	    Pat = {'_', unclear, '_'},
1902	    Uncertain = ets:match_object(mnesia_decision, Pat),
1903	    display_system_info(Held, Queued, TmInfo, Uncertain);
1904	_ ->
1905	    mini_info()
1906    end,
1907    IsRunning.
1908
1909load_mnesia_or_abort() ->
1910    case mnesia_lib:ensure_loaded(?APPLICATION) of
1911	ok ->
1912	    ok;
1913	{error, Reason} ->
1914	    abort(Reason)
1915    end.
1916
1917%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
1918%% Database mgt
1919
1920create_schema(Ns) ->
1921    mnesia_bup:create_schema(Ns).
1922
1923delete_schema(Ns) ->
1924    mnesia_schema:delete_schema(Ns).
1925
1926backup(Opaque) ->
1927    mnesia_log:backup(Opaque).
1928
1929backup(Opaque, Mod) ->
1930    mnesia_log:backup(Opaque, Mod).
1931
1932traverse_backup(S, T, Fun, Acc) ->
1933    mnesia_bup:traverse_backup(S, T, Fun, Acc).
1934
1935traverse_backup(S, SM, T, TM, F, A) ->
1936    mnesia_bup:traverse_backup(S, SM, T, TM, F, A).
1937
1938install_fallback(Opaque) ->
1939    mnesia_bup:install_fallback(Opaque).
1940
1941install_fallback(Opaque, Mod) ->
1942    mnesia_bup:install_fallback(Opaque, Mod).
1943
1944uninstall_fallback() ->
1945    mnesia_bup:uninstall_fallback().
1946
1947uninstall_fallback(Args) ->
1948    mnesia_bup:uninstall_fallback(Args).
1949
1950activate_checkpoint(Args) ->
1951    mnesia_checkpoint:activate(Args).
1952
1953deactivate_checkpoint(Name) ->
1954    mnesia_checkpoint:deactivate(Name).
1955
1956backup_checkpoint(Name, Opaque) ->
1957    mnesia_log:backup_checkpoint(Name, Opaque).
1958
1959backup_checkpoint(Name, Opaque, Mod) ->
1960    mnesia_log:backup_checkpoint(Name, Opaque, Mod).
1961
1962restore(Opaque, Args) ->
1963    mnesia_schema:restore(Opaque, Args).
1964
1965%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
1966%% Table mgt
1967
1968create_table(Arg) ->
1969    mnesia_schema:create_table(Arg).
1970create_table(Name, Arg) when list(Arg) ->
1971    mnesia_schema:create_table([{name, Name}| Arg]);
1972create_table(Name, Arg) ->
1973    {aborted, badarg, Name, Arg}.
1974
1975delete_table(Tab) ->
1976    mnesia_schema:delete_table(Tab).
1977
1978add_table_copy(Tab, N, S) ->
1979    mnesia_schema:add_table_copy(Tab, N, S).
1980del_table_copy(Tab, N) ->
1981    mnesia_schema:del_table_copy(Tab, N).
1982
1983move_table_copy(Tab, From, To) ->
1984    mnesia_schema:move_table(Tab, From, To).
1985
1986add_table_index(Tab, Ix) ->
1987    mnesia_schema:add_table_index(Tab, Ix).
1988del_table_index(Tab, Ix) ->
1989    mnesia_schema:del_table_index(Tab, Ix).
1990
1991transform_table(Tab, Fun, NewA) ->
1992    case catch val({Tab, record_name}) of
1993	{'EXIT', Reason} ->
1994	    mnesia:abort(Reason);
1995	OldRN ->
1996	    mnesia_schema:transform_table(Tab, Fun, NewA, OldRN)
1997    end.
1998
1999transform_table(Tab, Fun, NewA, NewRN) ->
2000    mnesia_schema:transform_table(Tab, Fun, NewA, NewRN).
2001
2002change_table_copy_type(T, N, S) ->
2003    mnesia_schema:change_table_copy_type(T, N, S).
2004
2005clear_table(Tab) ->
2006    mnesia_schema:clear_table(Tab).
2007
2008%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
2009%% Table mgt - user properties
2010
2011read_table_property(Tab, PropKey) ->
2012    val({Tab, user_property, PropKey}).
2013
2014write_table_property(Tab, Prop) ->
2015    mnesia_schema:write_table_property(Tab, Prop).
2016
2017delete_table_property(Tab, PropKey) ->
2018    mnesia_schema:delete_table_property(Tab, PropKey).
2019
2020%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
2021%% Table mgt - user properties
2022
2023change_table_frag(Tab, FragProp) ->
2024    mnesia_schema:change_table_frag(Tab, FragProp).
2025
2026%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
2027%% Table mgt - table load
2028
2029%% Dump a ram table to disc
2030dump_tables(Tabs) ->
2031    mnesia_schema:dump_tables(Tabs).
2032
2033%% allow the user to wait for some tables to be loaded
2034wait_for_tables(Tabs, Timeout) ->
2035    mnesia_controller:wait_for_tables(Tabs, Timeout).
2036
2037force_load_table(Tab) ->
2038    case mnesia_controller:force_load_table(Tab) of
2039	ok -> yes; % Backwards compatibility
2040	Other -> Other
2041    end.
2042
2043change_table_access_mode(T, Access) ->
2044    mnesia_schema:change_table_access_mode(T, Access).
2045
2046change_table_load_order(T, O) ->
2047    mnesia_schema:change_table_load_order(T, O).
2048
2049set_master_nodes(Nodes) when list(Nodes) ->
2050    UseDir = system_info(use_dir),
2051    IsRunning = system_info(is_running),
2052    case IsRunning of
2053	yes ->
2054	    CsPat = {{'_', cstruct}, '_'},
2055	    Cstructs0 = ?ets_match_object(mnesia_gvar, CsPat),
2056	    Cstructs = [Cs || {_, Cs} <- Cstructs0],
2057	    log_valid_master_nodes(Cstructs, Nodes, UseDir, IsRunning);
2058	_NotRunning ->
2059	    case UseDir of
2060		true ->
2061		    mnesia_lib:lock_table(schema),
2062		    Res =
2063			case mnesia_schema:read_cstructs_from_disc() of
2064			    {ok, Cstructs} ->
2065				log_valid_master_nodes(Cstructs, Nodes, UseDir, IsRunning);
2066			    {error, Reason} ->
2067				{error, Reason}
2068			end,
2069			mnesia_lib:unlock_table(schema),
2070		    Res;
2071		false ->
2072		    ok
2073	    end
2074    end;
2075set_master_nodes(Nodes) ->
2076    {error, {bad_type, Nodes}}.
2077
2078log_valid_master_nodes(Cstructs, Nodes, UseDir, IsRunning) ->
2079    Fun = fun(Cs) ->
2080		  Copies = mnesia_lib:copy_holders(Cs),
2081		  Valid = mnesia_lib:intersect(Nodes, Copies),
2082		  {Cs#cstruct.name, Valid}
2083	  end,
2084    Args = lists:map(Fun, Cstructs),
2085    mnesia_recover:log_master_nodes(Args, UseDir, IsRunning).
2086
2087set_master_nodes(Tab, Nodes) when list(Nodes) ->
2088    UseDir = system_info(use_dir),
2089    IsRunning = system_info(is_running),
2090    case IsRunning of
2091	yes ->
2092	    case ?catch_val({Tab, cstruct}) of
2093		{'EXIT', _} ->
2094		    {error, {no_exists, Tab}};
2095		Cs ->
2096		    case Nodes -- mnesia_lib:copy_holders(Cs) of
2097			[] ->
2098			    Args = [{Tab , Nodes}],
2099			    mnesia_recover:log_master_nodes(Args, UseDir, IsRunning);
2100			BadNodes ->
2101			    {error, {no_exists, Tab,  BadNodes}}
2102		    end
2103	    end;
2104	_NotRunning ->
2105	    case UseDir of
2106		true ->
2107		    mnesia_lib:lock_table(schema),
2108		    Res =
2109			case mnesia_schema:read_cstructs_from_disc() of
2110			    {ok, Cstructs} ->
2111				case lists:keysearch(Tab, 2, Cstructs) of
2112				    {value, Cs} ->
2113					case Nodes -- mnesia_lib:copy_holders(Cs) of
2114					    [] ->
2115						Args = [{Tab , Nodes}],
2116						mnesia_recover:log_master_nodes(Args, UseDir, IsRunning);
2117					    BadNodes ->
2118						{error, {no_exists, Tab,  BadNodes}}
2119					end;
2120				    false ->
2121					{error, {no_exists, Tab}}
2122				end;
2123			    {error, Reason} ->
2124				{error, Reason}
2125			end,
2126		    mnesia_lib:unlock_table(schema),
2127		    Res;
2128		false ->
2129		    ok
2130	    end
2131    end;
2132set_master_nodes(Tab, Nodes) ->
2133    {error, {bad_type, Tab, Nodes}}.
2134
2135%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
2136%% Misc admin
2137
2138dump_log() ->
2139    mnesia_controller:sync_dump_log(user).
2140
2141subscribe(What) ->
2142    mnesia_subscr:subscribe(self(), What).
2143
2144unsubscribe(What) ->
2145    mnesia_subscr:unsubscribe(self(), What).
2146
2147report_event(Event) ->
2148    mnesia_lib:report_system_event({mnesia_user, Event}).
2149
2150%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
2151%% Snmp
2152
2153snmp_open_table(Tab, Us) ->
2154    mnesia_schema:add_snmp(Tab, Us).
2155
2156snmp_close_table(Tab) ->
2157    mnesia_schema:del_snmp(Tab).
2158
2159snmp_get_row(Tab, RowIndex) when atom(Tab), Tab /= schema ->
2160    dirty_rpc(Tab, mnesia_snmp_hook, get_row, [Tab, RowIndex]);
2161snmp_get_row(Tab, _RowIndex) ->
2162    abort({bad_type, Tab}).
2163
2164snmp_get_next_index(Tab, RowIndex) when atom(Tab), Tab /= schema ->
2165    dirty_rpc(Tab, mnesia_snmp_hook, get_next_index, [Tab, RowIndex]);
2166snmp_get_next_index(Tab, _RowIndex) ->
2167    abort({bad_type, Tab}).
2168
2169snmp_get_mnesia_key(Tab, RowIndex) when atom(Tab), Tab /= schema ->
2170    dirty_rpc(Tab, mnesia_snmp_hook, get_mnesia_key, [Tab, RowIndex]);
2171snmp_get_mnesia_key(Tab, _RowIndex) ->
2172    abort({bad_type, Tab}).
2173
2174%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
2175%% Textfile access
2176
2177load_textfile(F) ->
2178    mnesia_text:load_textfile(F).
2179dump_to_textfile(F) ->
2180    mnesia_text:dump_to_textfile(F).
2181
2182%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
2183%% Mnemosyne exclusive
2184
2185get_activity_id() ->
2186    get(mnesia_activity_state).
2187
2188put_activity_id(Activity) ->
2189    mnesia_tm:put_activity_id(Activity).
2190