~clint-fewbar/ubuntu/precise/erlang/merge-15b

« back to all changes in this revision

Viewing changes to lib/mnesia/src/mnesia_tm.erl

  • Committer: Package Import Robot
  • Author(s): Sergei Golovan
  • Date: 2011-12-15 19:20:10 UTC
  • mfrom: (1.1.18) (3.5.15 sid)
  • mto: (3.5.16 sid)
  • mto: This revision was merged to the branch mainline in revision 33.
  • Revision ID: package-import@ubuntu.com-20111215192010-jnxcfe3tbrpp0big
Tags: 1:15.b-dfsg-1
* New upstream release.
* Upload to experimental because this release breaks external drivers
  API along with ABI, so several applications are to be fixed.
* Removed SSL patch because the old SSL implementation is removed from
  the upstream distribution.
* Removed never used patch which added native code to erlang beam files.
* Removed the erlang-docbuilder binary package because the docbuilder
  application was dropped by upstream.
* Documented dropping ${erlang-docbuilder:Depends} substvar in
  erlang-depends(1) manpage.
* Made erlang-base and erlang-base-hipe provide virtual package
  erlang-abi-15.b (the number means the first erlang version, which
  provides current ABI).

Show diffs side-by-side

added added

removed removed

Lines of Context:
1
1
%%
2
2
%% %CopyrightBegin%
3
3
%%
4
 
%% Copyright Ericsson AB 1996-2010. All Rights Reserved.
 
4
%% Copyright Ericsson AB 1996-2011. All Rights Reserved.
5
5
%%
6
6
%% The contents of this file are subject to the Erlang Public License,
7
7
%% Version 1.1, (the "License"); you may not use this file except in
36
36
         prepare_checkpoint/2,
37
37
         prepare_checkpoint/1, % Internal
38
38
         prepare_snmp/3,
39
 
         do_snmp/2,      
 
39
         do_snmp/2,
40
40
         put_activity_id/1,
41
41
         put_activity_id/2,
42
42
         block_tab/1,
64
64
               prev_tab = [], % initiate to a non valid table name
65
65
               prev_types,
66
66
               prev_snmp,
67
 
               types 
 
67
               types,
 
68
               majority = []
68
69
              }).
69
70
 
70
 
-record(participant, {tid, pid, commit, disc_nodes = [], 
 
71
-record(participant, {tid, pid, commit, disc_nodes = [],
71
72
                      ram_nodes = [], protocol = sym_trans}).
72
73
 
73
74
start() ->
76
77
init(Parent) ->
77
78
    register(?MODULE, self()),
78
79
    process_flag(trap_exit, true),
79
 
    
 
80
 
80
81
    %% Initialize the schema
81
82
    IgnoreFallback = mnesia_monitor:get_env(ignore_fallback_at_startup),
82
83
    mnesia_bup:tm_fallback_start(IgnoreFallback),
83
84
    mnesia_schema:init(IgnoreFallback),
84
 
    
 
85
 
85
86
    %% Handshake and initialize transaction recovery
86
87
    mnesia_recover:init(),
87
88
    Early = mnesia_monitor:init(),
100
101
        false ->
101
102
            ignore
102
103
    end,
103
 
    
 
104
 
104
105
    mnesia_schema:purge_tmp_files(),
105
106
    mnesia_recover:start_garb(),
106
 
    
107
 
    ?eval_debug_fun({?MODULE, init},  [{nodes, AllOthers}]),               
 
107
 
 
108
    ?eval_debug_fun({?MODULE, init},  [{nodes, AllOthers}]),
108
109
 
109
110
    case val(debug) of
110
111
        Debug when Debug /= debug, Debug /= trace ->
117
118
 
118
119
val(Var) ->
119
120
    case ?catch_val(Var) of
120
 
        {'EXIT', _ReASoN_} -> mnesia_lib:other_val(Var, _ReASoN_); 
121
 
        _VaLuE_ -> _VaLuE_ 
 
121
        {'EXIT', _ReASoN_} -> mnesia_lib:other_val(Var, _ReASoN_);
 
122
        _VaLuE_ -> _VaLuE_
122
123
    end.
123
124
 
124
125
reply({From,Ref}, R) ->
135
136
        undefined ->
136
137
            {error, {node_not_running, node()}};
137
138
        Pid ->
138
 
            Ref = make_ref(), 
 
139
            Ref = make_ref(),
139
140
            Pid ! {{self(), Ref}, R},
140
141
            rec(Pid, Ref)
141
142
    end.
160
161
            Reply;
161
162
        {'EXIT', Pid, _} ->
162
163
            {error, {node_not_running, node()}}
163
 
    end.   
 
164
    end.
164
165
 
165
166
tmlink({From, Ref}) when is_reference(Ref) ->
166
167
    link(From);
208
209
                    State2 = State#state{dirty_queue = [Item | State#state.dirty_queue]},
209
210
                    doit_loop(State2)
210
211
            end;
211
 
        
 
212
 
212
213
        {From, {sync_dirty, Tid, Commit, Tab}} ->
213
214
            case lists:member(Tab, State#state.blocked_tabs) of
214
215
                false ->
219
220
                    State2 = State#state{dirty_queue = [Item | State#state.dirty_queue]},
220
221
                    doit_loop(State2)
221
222
            end;
222
 
        
 
223
 
223
224
        {From, start_outer} -> %% Create and associate ets_tab with Tid
224
225
            case catch ?ets_new_table(mnesia_trans_store, [bag, public]) of
225
226
                {'EXIT', Reason} -> %% system limit
235
236
                    S2 = State#state{coordinators = A2},
236
237
                    reply(From, {new_tid, Tid, Etab}, S2)
237
238
            end;
238
 
        
 
239
 
239
240
        {From, {ask_commit, Protocol, Tid, Commit, DiscNs, RamNs}} ->
240
 
            ?eval_debug_fun({?MODULE, doit_ask_commit}, 
 
241
            ?eval_debug_fun({?MODULE, doit_ask_commit},
241
242
                            [{tid, Tid}, {prot, Protocol}]),
242
243
            mnesia_checkpoint:tm_enter_pending(Tid, DiscNs, RamNs),
243
 
            Pid = 
 
244
            Pid =
244
245
                case Protocol of
245
246
                    asym_trans when node(Tid#tid.pid) /= node() ->
246
247
                        Args = [tmpid(From), Tid, Commit, DiscNs, RamNs],
247
 
                        spawn_link(?MODULE, commit_participant, Args);          
 
248
                        spawn_link(?MODULE, commit_participant, Args);
248
249
                    _ when node(Tid#tid.pid) /= node() -> %% *_sym_trans
249
250
                        reply(From, {vote_yes, Tid}),
250
251
                        nopid
257
258
                             protocol = Protocol},
258
259
            State2 = State#state{participants = gb_trees:insert(Tid,P,Participants)},
259
260
            doit_loop(State2);
260
 
        
 
261
 
261
262
        {Tid, do_commit} ->
262
263
            case gb_trees:lookup(Tid, Participants) of
263
264
                none ->
271
272
                            Member = lists:member(node(), P#participant.disc_nodes),
272
273
                            if Member == false ->
273
274
                                    ignore;
274
 
                               P#participant.protocol == sym_trans -> 
 
275
                               P#participant.protocol == sym_trans ->
275
276
                                    mnesia_log:log(Commit);
276
 
                               P#participant.protocol == sync_sym_trans -> 
 
277
                               P#participant.protocol == sync_sym_trans ->
277
278
                                    mnesia_log:slog(Commit)
278
279
                            end,
279
280
                            mnesia_recover:note_decision(Tid, committed),
280
281
                            do_commit(Tid, Commit),
281
 
                            if 
 
282
                            if
282
283
                                P#participant.protocol == sync_sym_trans ->
283
284
                                    Tid#tid.pid ! {?MODULE, node(), {committed, Tid}};
284
285
                                true ->
295
296
                            doit_loop(State)
296
297
                    end
297
298
            end;
298
 
        
 
299
 
299
300
        {Tid, simple_commit} ->
300
301
            mnesia_recover:note_decision(Tid, committed),
301
302
            mnesia_locker:release_tid(Tid),
302
303
            transaction_terminated(Tid),
303
304
            doit_loop(State);
304
 
        
 
305
 
305
306
        {Tid, {do_abort, Reason}} ->
306
307
            ?eval_debug_fun({?MODULE, do_abort, pre}, [{tid, Tid}]),
307
308
            case gb_trees:lookup(Tid, Participants) of
316
317
                            Commit = P#participant.commit,
317
318
                            mnesia_recover:note_decision(Tid, aborted),
318
319
                            do_abort(Tid, Commit),
319
 
                            if 
 
320
                            if
320
321
                                P#participant.protocol == sync_sym_trans ->
321
322
                                    Tid#tid.pid ! {?MODULE, node(), {aborted, Tid}};
322
323
                                true ->
334
335
                            doit_loop(State)
335
336
                    end
336
337
            end;
337
 
        
 
338
 
338
339
        {From, {add_store, Tid}} -> %% new store for nested  transaction
339
340
            case catch ?ets_new_table(mnesia_trans_store, [bag, public]) of
340
341
                {'EXIT', Reason} -> %% system limit
354
355
 
355
356
        {'EXIT', Pid, Reason} ->
356
357
            handle_exit(Pid, Reason, State);
357
 
        
 
358
 
358
359
        {From, {restart, Tid, Store}} ->
359
360
            A2 = restore_stores(Coordinators, Tid, Store),
360
361
            clear_fixtable([Store]),
361
362
            ?ets_match_delete(Store, '_'),
362
363
            ?ets_insert(Store, {nodes, node()}),
363
364
            reply(From, {restarted, Tid}, State#state{coordinators = A2});
364
 
        
 
365
 
365
366
        {delete_transaction, Tid} ->
366
367
            %% used to clear transactions which are committed
367
368
            %% in coordinator or participant processes
376
377
                            clear_fixtable(Etabs),
377
378
                            erase_ets_tabs(Etabs),
378
379
                            transaction_terminated(Tid),
379
 
                            doit_loop(State#state{coordinators = 
 
380
                            doit_loop(State#state{coordinators =
380
381
                                                  gb_trees:delete(Tid,Coordinators)})
381
382
                    end;
382
383
                true ->
384
385
                    State2 = State#state{participants=gb_trees:delete(Tid,Participants)},
385
386
                    doit_loop(State2)
386
387
            end;
387
 
        
 
388
 
388
389
        {sync_trans_serial, Tid} ->
389
390
            %% Do the Lamport thing here
390
391
            mnesia_recover:sync_trans_tid_serial(Tid),
391
392
            doit_loop(State);
392
 
            
 
393
 
393
394
        {From, info} ->
394
 
            reply(From, {info, gb_trees:values(Participants), 
 
395
            reply(From, {info, gb_trees:values(Participants),
395
396
                         gb_trees:to_list(Coordinators)}, State);
396
 
        
 
397
 
397
398
        {mnesia_down, N} ->
398
399
            verbose("Got mnesia_down from ~p, reconfiguring...~n", [N]),
399
400
            reconfigure_coordinators(N, gb_trees:to_list(Coordinators)),
400
 
            
 
401
 
401
402
            Tids = gb_trees:keys(Participants),
402
403
            reconfigure_participants(N, gb_trees:values(Participants)),
403
404
            NewState = clear_fixtable(N, State),
407
408
        {From, {unblock_me, Tab}} ->
408
409
            case lists:member(Tab, State#state.blocked_tabs) of
409
410
                false ->
410
 
                    verbose("Wrong dirty Op blocked on ~p ~p ~p", 
 
411
                    verbose("Wrong dirty Op blocked on ~p ~p ~p",
411
412
                            [node(), Tab, From]),
412
413
                    reply(From, unblocked),
413
414
                    doit_loop(State);
414
415
                true ->
415
 
                    Item = {Tab, unblock_me, From}, 
 
416
                    Item = {Tab, unblock_me, From},
416
417
                    State2 = State#state{dirty_queue = [Item | State#state.dirty_queue]},
417
418
                    doit_loop(State2)
418
 
            end;            
419
 
        
 
419
            end;
 
420
 
420
421
        {From, {block_tab, Tab}} ->
421
422
            State2 = State#state{blocked_tabs = [Tab | State#state.blocked_tabs]},
422
423
            reply(From, ok, State2);
423
 
        
 
424
 
424
425
        {From, {unblock_tab, Tab}} ->
425
426
            BlockedTabs2 = State#state.blocked_tabs -- [Tab],
426
427
            case lists:member(Tab, BlockedTabs2) of
427
428
                false ->
428
429
                    mnesia_controller:unblock_table(Tab),
429
430
                    Queue = process_dirty_queue(Tab, State#state.dirty_queue),
430
 
                    State2 = State#state{blocked_tabs = BlockedTabs2, 
 
431
                    State2 = State#state{blocked_tabs = BlockedTabs2,
431
432
                                         dirty_queue = Queue},
432
433
                    reply(From, ok, State2);
433
434
                true ->
434
435
                    State2 = State#state{blocked_tabs = BlockedTabs2},
435
436
                    reply(From, ok, State2)
436
437
            end;
437
 
        
 
438
 
438
439
        {From, {prepare_checkpoint, Cp}} ->
439
440
            Res = mnesia_checkpoint:tm_prepare(Cp),
440
441
            case Res of
447
448
            reply(From, Res, State);
448
449
        {From, {fixtable, [Tab,Lock,Requester]}} ->
449
450
            case ?catch_val({Tab, storage_type}) of
450
 
                {'EXIT', _} -> 
 
451
                {'EXIT', _} ->
451
452
                    reply(From, error, State);
452
453
                Storage ->
453
454
                    mnesia_lib:db_fixtable(Storage,Tab,Lock),
454
455
                    NewState = manage_fixtable(Tab,Lock,Requester,State),
455
456
                    reply(From, node(), NewState)
456
457
            end;
457
 
        
 
458
 
458
459
        {system, From, Msg} ->
459
460
            dbg_out("~p got {system, ~p, ~p}~n", [?MODULE, From, Msg]),
460
461
            sys:handle_system_msg(Msg, From, Sup, ?MODULE, [], State);
461
 
        
 
462
 
462
463
        Msg ->
463
464
            verbose("** ERROR ** ~p got unexpected message: ~p~n", [?MODULE, Msg]),
464
465
            doit_loop(State)
507
508
                    ignore
508
509
            end,
509
510
            prepare_pending_coordinators(Coords, IgnoreNew);
510
 
        {'EXIT', _} -> 
 
511
        {'EXIT', _} ->
511
512
            prepare_pending_coordinators(Coords, IgnoreNew)
512
513
    end;
513
514
prepare_pending_coordinators([], _IgnoreNew) ->
537
538
 
538
539
handle_exit(Pid, Reason, State) ->
539
540
    %% Check if it is a coordinator
540
 
    case pid_search_delete(Pid, gb_trees:to_list(State#state.coordinators)) of 
 
541
    case pid_search_delete(Pid, gb_trees:to_list(State#state.coordinators)) of
541
542
        {none, _} ->
542
543
            %% Check if it is a participant
543
544
            Ps = gb_trees:values(State#state.participants),
551
552
                    NewPs = gb_trees:delete(P#participant.tid,State#state.participants),
552
553
                    doit_loop(State#state{participants = NewPs})
553
554
            end;
554
 
        
 
555
 
555
556
        {{Tid, Etabs}, RestC} ->
556
 
            %% A local coordinator has died and 
 
557
            %% A local coordinator has died and
557
558
            %% we must determine the outcome of the
558
559
            %% transaction and tell mnesia_tm on the
559
560
            %% other nodes about it and then recover
577
578
            %% Tell the participants about the outcome
578
579
            Protocol = Prep#prep.protocol,
579
580
            Outcome = tell_outcome(Tid, Protocol, node(), CheckNodes, TellNodes),
580
 
            
 
581
 
581
582
            %% Recover locally
582
583
            CR = Prep#prep.records,
583
584
            {DiscNs, RamNs} = commit_nodes(CR, [], []),
588
589
                    recover_coordinator(Tid, Protocol, Outcome, Local, DiscNs, RamNs),
589
590
                    ?eval_debug_fun({?MODULE, recover_coordinator, post},
590
591
                                    [{tid, Tid}, {outcome, Outcome}, {prot, Protocol}]);
591
 
                false ->  %% When killed before store havn't been copied to 
 
592
                false ->  %% When killed before store havn't been copied to
592
593
                    ok    %% to the new nested trans store.
593
594
            end
594
595
    end,
609
610
 
610
611
recover_coordinator(Tid, asym_trans, committed, Local, DiscNs, RamNs) ->
611
612
    D = #decision{tid = Tid, outcome = committed,
612
 
                  disc_nodes = DiscNs, ram_nodes = RamNs},              
 
613
                  disc_nodes = DiscNs, ram_nodes = RamNs},
613
614
    mnesia_recover:log_decision(D),
614
615
    do_commit(Tid, Local);
615
616
recover_coordinator(Tid, asym_trans, aborted, Local, DiscNs, RamNs) ->
616
617
    D = #decision{tid = Tid, outcome = aborted,
617
 
                  disc_nodes = DiscNs, ram_nodes = RamNs},              
 
618
                  disc_nodes = DiscNs, ram_nodes = RamNs},
618
619
    mnesia_recover:log_decision(D),
619
620
    do_abort(Tid, Local).
620
621
 
630
631
 
631
632
del_coord_store(Coords, Tid, Current, Obsolete) ->
632
633
    Stores = gb_trees:get(Tid, Coords),
633
 
    Rest = 
 
634
    Rest =
634
635
        case Stores of
635
636
            [Obsolete, Current | Tail] -> Tail;
636
637
            [Current, Obsolete | Tail] -> Tail
641
642
erase_ets_tabs([H | T]) ->
642
643
    ?ets_delete_table(H),
643
644
    erase_ets_tabs(T);
644
 
erase_ets_tabs([]) -> 
 
645
erase_ets_tabs([]) ->
645
646
    ok.
646
647
 
647
648
%% Clear one transactions all fixtables
648
649
clear_fixtable([Store|_]) ->
649
650
    Fixed = get_elements(fixtable, Store),
650
651
    lists:foreach(fun({Tab,Node}) ->
651
 
                          rpc:cast(Node, ?MODULE, fixtable, [Tab,false,self()]) 
 
652
                          rpc:cast(Node, ?MODULE, fixtable, [Tab,false,self()])
652
653
                  end, Fixed).
653
654
 
654
655
%% Clear all fixtable Node have done
660
661
            lists:foreach(
661
662
              fun(Tab) ->
662
663
                      case ?catch_val({Tab, storage_type}) of
663
 
                          {'EXIT', _} -> 
 
664
                          {'EXIT', _} ->
664
665
                              ignore;
665
666
                          Storage ->
666
667
                              mnesia_lib:db_fixtable(Storage,Tab,false)
679
680
    end;
680
681
manage_fixtable(Tab,false,Requester,State = #state{fixed_tabs = FT0}) ->
681
682
    Node = node(Requester),
682
 
    case mnesia_lib:key_search_delete(Node, 1, FT0) of 
 
683
    case mnesia_lib:key_search_delete(Node, 1, FT0) of
683
684
        {none,_FT} -> State; % Hmm? Safeguard
684
 
        {{Node, Tabs0},FT} -> 
 
685
        {{Node, Tabs0},FT} ->
685
686
            case lists:delete(Tab, Tabs0) of
686
687
                [] -> State#state{fixed_tabs=FT};
687
688
                Tabs -> State#state{fixed_tabs=[{Node,Tabs}|FT]}
690
691
 
691
692
%% Deletes a pid from a list of participants
692
693
%% or from a gb_trees of coordinators
693
 
%% {none, All} or {Tr, Rest} 
 
694
%% {none, All} or {Tr, Rest}
694
695
pid_search_delete(Pid, Trs) ->
695
696
    pid_search_delete(Pid, Trs, none, []).
696
697
pid_search_delete(Pid, [Tr = {Tid, _Ts} | Trs], _Val, Ack) when Tid#tid.pid == Pid ->
700
701
 
701
702
pid_search_delete(_Pid, [], Val, Ack) ->
702
703
    {Val, gb_trees:from_orddict(lists:reverse(Ack))}.
703
 
 
 
704
 
704
705
transaction_terminated(Tid)  ->
705
706
    mnesia_checkpoint:tm_exit_pending(Tid),
706
707
    Pid = Tid#tid.pid,
712
713
    end.
713
714
 
714
715
%% If there are an surrounding transaction, we inherit it's context
715
 
non_transaction(OldState={_,_,Trans}, Fun, Args, ActivityKind, Mod) 
 
716
non_transaction(OldState={_,_,Trans}, Fun, Args, ActivityKind, Mod)
716
717
  when Trans /= non_transaction ->
717
 
    Kind = case ActivityKind of 
 
718
    Kind = case ActivityKind of
718
719
               sync_dirty -> sync;
719
720
               _ -> async
720
721
           end,
721
722
    case transaction(OldState, Fun, Args, infinity, Mod, Kind) of
722
 
        {atomic, Res} -> 
 
723
        {atomic, Res} ->
723
724
            Res;
724
725
        {aborted,Res} ->
725
726
            exit(Res)
765
766
 
766
767
execute_outer(Mod, Fun, Args, Factor, Retries, Type) ->
767
768
    case req(start_outer) of
768
 
        {error, Reason} -> 
 
769
        {error, Reason} ->
769
770
            {aborted, Reason};
770
771
        {new_tid, Tid, Store} ->
771
772
            Ts = #tidstore{store = Store},
791
792
 
792
793
copy_ets(From, To) ->
793
794
    do_copy_ets(?ets_first(From), From, To).
794
 
do_copy_ets('$end_of_table', _,_) -> 
 
795
do_copy_ets('$end_of_table', _,_) ->
795
796
    ok;
796
797
do_copy_ets(K, From, To) ->
797
798
    Objs = ?ets_lookup(From, K),
812
813
            mnesia_lib:incr_counter(trans_commits),
813
814
            erase(mnesia_activity_state),
814
815
            %% no need to clear locks, already done by commit ...
815
 
            %% Flush any un processed mnesia_down messages we might have 
 
816
            %% Flush any un processed mnesia_down messages we might have
816
817
            flush_downs(),
817
818
            catch unlink(whereis(?MODULE)),
818
819
            {atomic, Value};
845
846
            maybe_restart(Fun, Args, Factor, Retries, Type, {node_not_running, N});
846
847
        {aborted, {bad_commit, N}} ->
847
848
            maybe_restart(Fun, Args, Factor, Retries, Type, {bad_commit, N});
848
 
        _ -> 
 
849
        _ ->
849
850
            return_abort(Fun, Args, Reason)
850
851
    end.
851
852
 
887
888
            SleepTime = mnesia_lib:random_time(Factor, Tid#tid.counter),
888
889
            dbg_out("Restarting transaction ~w: in ~wms ~w~n", [Tid, SleepTime, Why]),
889
890
            timer:sleep(SleepTime),
890
 
            execute_outer(Mod, Fun, Args, Factor, Retries, Type);       
 
891
            execute_outer(Mod, Fun, Args, Factor, Retries, Type);
891
892
        _ ->
892
893
            SleepTime = mnesia_lib:random_time(Factor0, Tid#tid.counter),
893
894
            dbg_out("Restarting transaction ~w: in ~wms ~w~n", [Tid, SleepTime, Why]),
894
 
            
 
895
 
895
896
            if
896
897
                Factor0 /= 10 ->
897
898
                    ignore;
910
911
            mnesia_locker:receive_release_tid_acc(Nodes, Tid),
911
912
            case get_restarted(Tid) of
912
913
                {restarted, Tid} ->
913
 
                    execute_transaction(Fun, Args, Factor0 + 1, 
 
914
                    execute_transaction(Fun, Args, Factor0 + 1,
914
915
                                        Retries, Type);
915
916
                {error, Reason} ->
916
917
                    mnesia:abort(Reason)
933
934
 
934
935
return_abort(Fun, Args, Reason)  ->
935
936
    {_Mod, Tid, Ts} = get(mnesia_activity_state),
936
 
    dbg_out("Transaction ~p calling ~p with ~p failed: ~n ~p~n", 
 
937
    dbg_out("Transaction ~p calling ~p with ~p failed: ~n ~p~n",
937
938
            [Tid, Fun, Args, Reason]),
938
939
    OldStore = Ts#tidstore.store,
939
940
    Nodes = get_elements(nodes, OldStore),
944
945
        Level == 1 ->
945
946
            mnesia_locker:async_release_tid(Nodes, Tid),
946
947
            ?MODULE ! {delete_transaction, Tid},
947
 
            erase(mnesia_activity_state),           
 
948
            erase(mnesia_activity_state),
948
949
            flush_downs(),
949
950
            catch unlink(whereis(?MODULE)),
950
951
            {aborted, mnesia_lib:fix_error(Reason)};
957
958
                              level = Level - 1},
958
959
            NewTidTs = {OldMod, Tid, Ts2},
959
960
            put(mnesia_activity_state, NewTidTs),
960
 
            case Reason of 
 
961
            case Reason of
961
962
                #cyclic{} ->
962
963
                    exit({aborted, Reason});
963
 
                {node_not_running, _N} -> 
964
 
                    exit({aborted, Reason});
965
 
                {bad_commit, _N}-> 
966
 
                    exit({aborted, Reason});
967
 
                _ -> 
 
964
                {node_not_running, _N} ->
 
965
                    exit({aborted, Reason});
 
966
                {bad_commit, _N}->
 
967
                    exit({aborted, Reason});
 
968
                _ ->
968
969
                    {aborted, mnesia_lib:fix_error(Reason)}
969
970
            end
970
971
    end.
981
982
    put_activity_id(MTT, undefined).
982
983
put_activity_id(undefined,_) ->
983
984
    erase_activity_id();
984
 
put_activity_id({Mod, Tid = #tid{}, Ts = #tidstore{}},Fun) ->    
 
985
put_activity_id({Mod, Tid = #tid{}, Ts = #tidstore{}},Fun) ->
985
986
    flush_downs(),
986
987
    Store = Ts#tidstore.store,
987
 
    if 
 
988
    if
988
989
        is_function(Fun) ->
989
990
            ?ets_insert(Store, {friends, {stop,Fun}});
990
991
        true ->
999
1000
    flush_downs(),
1000
1001
    erase(mnesia_activity_state).
1001
1002
 
1002
 
get_elements(Type,Store) ->    
 
1003
get_elements(Type,Store) ->
1003
1004
    case catch ?ets_lookup(Store, Type) of
1004
1005
        [] -> [];
1005
1006
        [{_,Val}] -> [Val];
1006
1007
        {'EXIT', _} -> [];
1007
1008
        Vals -> [Val|| {_,Val} <- Vals]
1008
1009
    end.
1009
 
    
 
1010
 
1010
1011
opt_propagate_store(_Current, _Obsolete, false) ->
1011
1012
    ok;
1012
1013
opt_propagate_store(Current, Obsolete, true) ->
1029
1030
intercept_best_friend([{stop,Fun} | R],Ignore) ->
1030
1031
    catch Fun(),
1031
1032
    intercept_best_friend(R,Ignore);
1032
 
intercept_best_friend([Pid | R],false) ->    
1033
 
    Pid ! {activity_ended, undefined, self()}, 
 
1033
intercept_best_friend([Pid | R],false) ->
 
1034
    Pid ! {activity_ended, undefined, self()},
1034
1035
    wait_for_best_friend(Pid, 0),
1035
1036
    intercept_best_friend(R,true);
1036
1037
intercept_best_friend([_|R],true) ->
1046
1047
                false -> ok
1047
1048
            end
1048
1049
    end.
1049
 
    
 
1050
 
1050
1051
my_process_is_alive(Pid) ->
1051
1052
    case catch erlang:is_process_alive(Pid) of % New BIF in R5
1052
 
        true -> 
 
1053
        true ->
1053
1054
            true;
1054
 
        false -> 
 
1055
        false ->
1055
1056
            false;
1056
 
        {'EXIT', _} -> % Pre R5 backward compatibility 
 
1057
        {'EXIT', _} -> % Pre R5 backward compatibility
1057
1058
            case process_info(Pid, message_queue_len) of
1058
1059
                undefined -> false;
1059
1060
                _ -> true
1060
 
            end 
 
1061
            end
1061
1062
    end.
1062
1063
 
1063
1064
dirty(Protocol, Item) ->
1069
1070
        async_dirty ->
1070
1071
            %% Send commit records to the other involved nodes,
1071
1072
            %% but do only wait for one node to complete.
1072
 
            %% Preferrably, the local node if possible. 
1073
 
                    
 
1073
            %% Preferrably, the local node if possible.
 
1074
 
1074
1075
            ReadNode = val({Tab, where_to_read}),
1075
1076
            {WaitFor, FirstRes} = async_send_dirty(Tid, CR, Tab, ReadNode),
1076
1077
            rec_dirty(WaitFor, FirstRes);
1077
 
                
 
1078
 
1078
1079
        sync_dirty ->
1079
1080
            %% Send commit records to the other involved nodes,
1080
1081
            %% and wait for all nodes to complete
1096
1097
    if
1097
1098
        Ts#tidstore.level == 1 ->
1098
1099
            intercept_friends(Tid, Ts),
1099
 
            %% N is number of updates 
 
1100
            %% N is number of updates
1100
1101
            case arrange(Tid, Store, Type) of
1101
1102
                {N, Prep} when N > 0 ->
1102
1103
                    multi_commit(Prep#prep.protocol,
 
1104
                                 majority_attr(Prep),
1103
1105
                                 Tid, Prep#prep.records, Store);
1104
1106
                {0, Prep} ->
1105
 
                    multi_commit(read_only, Tid, Prep#prep.records, Store)
 
1107
                    multi_commit(read_only,
 
1108
                                 majority_attr(Prep),
 
1109
                                 Tid, Prep#prep.records, Store)
1106
1110
            end;
1107
1111
        true ->
1108
1112
            %% nested commit
1117
1121
            do_commit_nested
1118
1122
    end.
1119
1123
 
 
1124
majority_attr(#prep{majority = M}) ->
 
1125
    M.
 
1126
 
 
1127
 
1120
1128
%% This function arranges for all objects we shall write in S to be
1121
1129
%% in a list of {Node, CommitRecord}
1122
1130
%% Important function for the performance of mnesia.
1127
1135
    Recs = prep_recs(Nodes, []),
1128
1136
    Key = ?ets_first(Store),
1129
1137
    N = 0,
1130
 
    Prep = 
1131
 
        case Type of 
 
1138
    Prep =
 
1139
        case Type of
1132
1140
            async -> #prep{protocol = sym_trans, records = Recs};
1133
1141
            sync -> #prep{protocol = sync_sym_trans, records = Recs}
1134
1142
        end,
1138
1146
            case Reason of
1139
1147
                {aborted, R} ->
1140
1148
                    mnesia:abort(R);
1141
 
                _ -> 
 
1149
                _ ->
1142
1150
                    mnesia:abort(Reason)
1143
1151
            end;
1144
1152
        {New, Prepared} ->
1147
1155
 
1148
1156
reverse([]) ->
1149
1157
    [];
1150
 
reverse([H=#commit{ram_copies=Ram, disc_copies=DC, 
 
1158
reverse([H=#commit{ram_copies=Ram, disc_copies=DC,
1151
1159
                   disc_only_copies=DOC,snmp = Snmp}
1152
1160
         |R]) ->
1153
1161
    [
1156
1164
       disc_copies      =  lists:reverse(DC),
1157
1165
       disc_only_copies =  lists:reverse(DOC),
1158
1166
       snmp             = lists:reverse(Snmp)
1159
 
      }  
 
1167
      }
1160
1168
     | reverse(R)].
1161
1169
 
1162
1170
prep_recs([N | Nodes], Recs) ->
1183
1191
             (BupRec, CommitRecs, RecName, Where, Snmp) ->
1184
1192
                  Tab = element(1, BupRec),
1185
1193
                  Key = element(2, BupRec),
1186
 
                  Item = 
 
1194
                  Item =
1187
1195
                      if
1188
1196
                          Tab == RecName ->
1189
1197
                              [{{Tab, Key}, BupRec, write}];
1192
1200
                              [{{Tab, Key}, BupRec2, write}]
1193
1201
                      end,
1194
1202
                  do_prepare_items(Tid, Tab, Key, Where, Snmp, Item, CommitRecs)
1195
 
          end,    
 
1203
          end,
1196
1204
    Recs2 = mnesia_schema:arrange_restore(R, Fun, Prep#prep.records),
1197
1205
    P2 = Prep#prep{protocol = asym_trans, records = Recs2},
1198
1206
    do_arrange(Tid, Store, ?ets_next(Store, RestoreKey), P2, N + 1);
1214
1222
    Recs = Prep#prep.records,
1215
1223
    Recs2 = do_prepare_items(Tid, Tab, Key, Types, Snmp, Items, Recs),
1216
1224
    Prep#prep{records = Recs2};
1217
 
    
 
1225
 
1218
1226
prepare_items(Tid, Tab, Key, Items, Prep) ->
1219
1227
    Types = val({Tab, where_to_commit}),
1220
1228
    case Types of
1221
1229
        [] -> mnesia:abort({no_exists, Tab});
1222
 
        {blocked, _} -> 
 
1230
        {blocked, _} ->
1223
1231
            unblocked = req({unblock_me, Tab}),
1224
1232
            prepare_items(Tid, Tab, Key, Items, Prep);
1225
 
        _ ->     
 
1233
        _ ->
 
1234
            Majority = needs_majority(Tab, Prep),
1226
1235
            Snmp = val({Tab, snmp}),
1227
 
            Recs2 = do_prepare_items(Tid, Tab, Key, Types, 
 
1236
            Recs2 = do_prepare_items(Tid, Tab, Key, Types,
1228
1237
                                     Snmp, Items, Prep#prep.records),
1229
 
            Prep2 = Prep#prep{records = Recs2, prev_tab = Tab, 
 
1238
            Prep2 = Prep#prep{records = Recs2, prev_tab = Tab,
 
1239
                              majority = Majority,
1230
1240
                              prev_types = Types, prev_snmp = Snmp},
1231
1241
            check_prep(Prep2, Types)
1232
1242
    end.
1235
1245
    Recs2 = prepare_snmp(Tid, Tab, Key, Types, Snmp, Items, Recs), % May exit
1236
1246
    prepare_nodes(Tid, Types, Items, Recs2, normal).
1237
1247
 
 
1248
 
 
1249
needs_majority(Tab, #prep{majority = M}) ->
 
1250
    case lists:keymember(Tab, 1, M) of
 
1251
        true ->
 
1252
            M;
 
1253
        false ->
 
1254
            case ?catch_val({Tab, majority}) of
 
1255
                {'EXIT', _} ->
 
1256
                    M;
 
1257
                false ->
 
1258
                    M;
 
1259
                true ->
 
1260
                    CopyHolders = val({Tab, all_nodes}),
 
1261
                    [{Tab, CopyHolders} | M]
 
1262
            end
 
1263
    end.
 
1264
 
 
1265
have_majority([], _) ->
 
1266
    ok;
 
1267
have_majority([{Tab, AllNodes} | Rest], Nodes) ->
 
1268
    case mnesia_lib:have_majority(Tab, AllNodes, Nodes) of
 
1269
        true ->
 
1270
            have_majority(Rest, Nodes);
 
1271
        false ->
 
1272
            {error, Tab}
 
1273
    end.
 
1274
 
1238
1275
prepare_snmp(Tab, Key, Items) ->
1239
 
    case val({Tab, snmp}) of 
 
1276
    case val({Tab, snmp}) of
1240
1277
        [] ->
1241
1278
            [];
1242
1279
        Ustruct when Key /= '_' ->
1249
1286
            [{clear_table, Tab}]
1250
1287
    end.
1251
1288
 
1252
 
prepare_snmp(_Tid, _Tab, _Key, _Types, [], _Items, Recs) -> 
 
1289
prepare_snmp(_Tid, _Tab, _Key, _Types, [], _Items, Recs) ->
1253
1290
    Recs;
1254
1291
 
1255
 
prepare_snmp(Tid, Tab, Key, Types, Us, Items, Recs) -> 
 
1292
prepare_snmp(Tid, Tab, Key, Types, Us, Items, Recs) ->
1256
1293
    if Key /= '_' ->
1257
1294
            {_Oid, _Val, Op} = hd(Items),
1258
1295
            SnmpOid = mnesia_snmp_hook:key_to_oid(Tab, Key, Us), % May exit
1261
1298
            prepare_nodes(Tid, Types, [{clear_table, Tab}], Recs, snmp)
1262
1299
    end.
1263
1300
 
1264
 
check_prep(Prep, Types) when Prep#prep.types == Types ->
 
1301
check_prep(#prep{majority = [], types = Types} = Prep, Types) ->
1265
1302
    Prep;
1266
 
check_prep(Prep, Types) when Prep#prep.types == undefined ->
1267
 
    Prep#prep{types = Types};
 
1303
check_prep(#prep{majority = M, types = undefined} = Prep, Types) ->
 
1304
    Protocol = if M == [] ->
 
1305
                       Prep#prep.protocol;
 
1306
                  true ->
 
1307
                       asym_trans
 
1308
               end,
 
1309
    Prep#prep{protocol = Protocol, types = Types};
1268
1310
check_prep(Prep, _Types) ->
1269
1311
    Prep#prep{protocol = asym_trans}.
1270
1312
 
1292
1334
    Rec2 = Rec#commit{snmp = [Item | Rec#commit.snmp]},
1293
1335
    prepare_node(Node, Storage, Items, Rec2, Kind);
1294
1336
prepare_node(Node, Storage, [Item | Items], Rec, Kind) when Kind /= schema ->
1295
 
    Rec2 = 
 
1337
    Rec2 =
1296
1338
        case Storage of
1297
1339
            ram_copies ->
1298
1340
                Rec#commit{ram_copies = [Item | Rec#commit.ram_copies]};
1303
1345
                           [Item | Rec#commit.disc_only_copies]}
1304
1346
        end,
1305
1347
    prepare_node(Node, Storage, Items, Rec2, Kind);
1306
 
prepare_node(_Node, _Storage, Items, Rec, Kind) 
 
1348
prepare_node(_Node, _Storage, Items, Rec, Kind)
1307
1349
  when Kind == schema, Rec#commit.schema_ops == []  ->
1308
1350
    Rec#commit{schema_ops = Items};
1309
1351
prepare_node(_Node, _Storage, [], Rec, _Kind) ->
1311
1353
 
1312
1354
%% multi_commit((Protocol, Tid, CommitRecords, Store)
1313
1355
%% Local work is always performed in users process
1314
 
multi_commit(read_only, Tid, CR, _Store) ->
1315
 
    %% This featherweight commit protocol is used when no 
 
1356
multi_commit(read_only, _Maj = [], Tid, CR, _Store) ->
 
1357
    %% This featherweight commit protocol is used when no
1316
1358
    %% updates has been performed in the transaction.
1317
1359
 
1318
1360
    {DiscNs, RamNs} = commit_nodes(CR, [], []),
1324
1366
    ?MODULE ! {delete_transaction, Tid},
1325
1367
    do_commit;
1326
1368
 
1327
 
multi_commit(sym_trans, Tid, CR, Store) ->
 
1369
multi_commit(sym_trans, _Maj = [], Tid, CR, Store) ->
1328
1370
    %% This lightweight commit protocol is used when all
1329
1371
    %% the involved tables are replicated symetrically.
1330
1372
    %% Their storage types must match on each node.
1339
1381
    %%    perform the updates.
1340
1382
    %%
1341
1383
    %%    The outcome is kept 3 minutes in the transient decision table.
1342
 
    %%    
 
1384
    %%
1343
1385
    %% Recovery:
1344
1386
    %%    If somebody dies before the coordinator has
1345
1387
    %%    broadcasted do_commit, the transaction is aborted.
1346
 
    %%    
 
1388
    %%
1347
1389
    %%    If a participant dies, the table load algorithm
1348
1390
    %%    ensures that the contents of the involved tables
1349
1391
    %%    are picked from another node.
1352
1394
    %%    the outcome with all the others. If all are uncertain
1353
1395
    %%    about the outcome, the transaction is aborted. If
1354
1396
    %%    somebody knows the outcome the others will follow.
1355
 
    
 
1397
 
1356
1398
    {DiscNs, RamNs} = commit_nodes(CR, [], []),
1357
1399
    Pending = mnesia_checkpoint:tm_enter_pending(Tid, DiscNs, RamNs),
1358
1400
    ?ets_insert(Store, Pending),
1359
1401
 
1360
1402
    {WaitFor, Local} = ask_commit(sym_trans, Tid, CR, DiscNs, RamNs),
1361
 
    {Outcome, []} = rec_all(WaitFor, Tid, do_commit, []), 
1362
 
    ?eval_debug_fun({?MODULE, multi_commit_sym}, 
1363
 
                    [{tid, Tid}, {outcome, Outcome}]), 
 
1403
    {Outcome, []} = rec_all(WaitFor, Tid, do_commit, []),
 
1404
    ?eval_debug_fun({?MODULE, multi_commit_sym},
 
1405
                    [{tid, Tid}, {outcome, Outcome}]),
1364
1406
    rpc:abcast(DiscNs -- [node()], ?MODULE, {Tid, Outcome}),
1365
1407
    rpc:abcast(RamNs -- [node()], ?MODULE, {Tid, Outcome}),
1366
1408
    case Outcome of
1376
1418
                    [{tid, Tid}, {outcome, Outcome}]),
1377
1419
    Outcome;
1378
1420
 
1379
 
multi_commit(sync_sym_trans, Tid, CR, Store) ->
 
1421
multi_commit(sync_sym_trans, _Maj = [], Tid, CR, Store) ->
1380
1422
    %%   This protocol is the same as sym_trans except that it
1381
1423
    %%   uses syncronized calls to disk_log and syncronized commits
1382
1424
    %%   when several nodes are involved.
1383
 
    
 
1425
 
1384
1426
    {DiscNs, RamNs} = commit_nodes(CR, [], []),
1385
1427
    Pending = mnesia_checkpoint:tm_enter_pending(Tid, DiscNs, RamNs),
1386
1428
    ?ets_insert(Store, Pending),
1387
1429
 
1388
1430
    {WaitFor, Local} = ask_commit(sync_sym_trans, Tid, CR, DiscNs, RamNs),
1389
 
    {Outcome, []} = rec_all(WaitFor, Tid, do_commit, []), 
1390
 
    ?eval_debug_fun({?MODULE, multi_commit_sym_sync}, 
1391
 
                    [{tid, Tid}, {outcome, Outcome}]), 
 
1431
    {Outcome, []} = rec_all(WaitFor, Tid, do_commit, []),
 
1432
    ?eval_debug_fun({?MODULE, multi_commit_sym_sync},
 
1433
                    [{tid, Tid}, {outcome, Outcome}]),
1392
1434
    [?ets_insert(Store, {waiting_for_commit_ack, Node}) || Node <- WaitFor],
1393
1435
    rpc:abcast(DiscNs -- [node()], ?MODULE, {Tid, Outcome}),
1394
1436
    rpc:abcast(RamNs -- [node()], ?MODULE, {Tid, Outcome}),
1408
1450
                    [{tid, Tid}, {outcome, Outcome}]),
1409
1451
    Outcome;
1410
1452
 
1411
 
multi_commit(asym_trans, Tid, CR, Store) ->
1412
 
    %% This more expensive commit protocol is used when 
 
1453
multi_commit(asym_trans, Majority, Tid, CR, Store) ->
 
1454
    %% This more expensive commit protocol is used when
1413
1455
    %% table definitions are changed (schema transactions).
1414
1456
    %% It is also used when the involved tables are
1415
1457
    %% replicated asymetrically. If the storage type differs
1420
1462
    %%   commit record and votes yes or no depending of the
1421
1463
    %%   outcome of the prepare. The preparation is also performed
1422
1464
    %%   by the coordinator.
1423
 
    %%   
 
1465
    %%
1424
1466
    %% 2a Somebody has died or voted no
1425
1467
    %%    Tell all yes voters to do_abort
1426
1468
    %% 2b Everybody has voted yes
1427
1469
    %%    Put a unclear marker in the log.
1428
1470
    %%    Tell the others to pre_commit. I.e. that they should
1429
1471
    %%    put a unclear marker in the log and reply
1430
 
    %%    acc_pre_commit when they are done. 
 
1472
    %%    acc_pre_commit when they are done.
1431
1473
    %%
1432
1474
    %% 3a Somebody died
1433
1475
    %%    Tell the remaining participants to do_abort
1450
1492
    %%    If we have no unclear marker in the log we may
1451
1493
    %%    safely abort, since we know that nobody may have
1452
1494
    %%    decided to commit yet.
1453
 
    %%    
 
1495
    %%
1454
1496
    %%    If we have a committed marker in the log we may
1455
1497
    %%    safely commit since we know that everybody else
1456
1498
    %%    also will come to this conclusion.
1464
1506
    %%    up. When all involved nodes are up and uncertain,
1465
1507
    %%    we decide to commit (first put a committed marker
1466
1508
    %%    in the log, then do the updates).
1467
 
    
 
1509
 
1468
1510
    D = #decision{tid = Tid, outcome = presume_abort},
1469
1511
    {D2, CR2} = commit_decision(D, CR, [], []),
1470
1512
    DiscNs = D2#decision.disc_nodes,
1471
1513
    RamNs = D2#decision.ram_nodes,
 
1514
    case have_majority(Majority, DiscNs ++ RamNs) of
 
1515
        ok  -> ok;
 
1516
        {error, Tab} -> mnesia:abort({no_majority, Tab})
 
1517
    end,
1472
1518
    Pending = mnesia_checkpoint:tm_enter_pending(Tid, DiscNs, RamNs),
1473
1519
    ?ets_insert(Store, Pending),
1474
1520
    {WaitFor, Local} = ask_commit(asym_trans, Tid, CR2, DiscNs, RamNs),
1475
 
    SchemaPrep = (catch mnesia_schema:prepare_commit(Tid, Local, {coord, WaitFor})), 
1476
 
    {Votes, Pids} = rec_all(WaitFor, Tid, do_commit, []), 
1477
 
    
1478
 
    ?eval_debug_fun({?MODULE, multi_commit_asym_got_votes}, 
 
1521
    SchemaPrep = (catch mnesia_schema:prepare_commit(Tid, Local, {coord, WaitFor})),
 
1522
    {Votes, Pids} = rec_all(WaitFor, Tid, do_commit, []),
 
1523
 
 
1524
    ?eval_debug_fun({?MODULE, multi_commit_asym_got_votes},
1479
1525
                    [{tid, Tid}, {votes, Votes}]),
1480
1526
    case Votes of
1481
1527
        do_commit ->
1484
1530
                    mnesia_log:log(C), % C is not a binary
1485
1531
                    ?eval_debug_fun({?MODULE, multi_commit_asym_log_commit_rec},
1486
1532
                                    [{tid, Tid}]),
1487
 
                    
 
1533
 
1488
1534
                    D3 = C#commit.decision,
1489
 
                    D4 = D3#decision{outcome = unclear},                
1490
 
                    mnesia_recover:log_decision(D4),                    
 
1535
                    D4 = D3#decision{outcome = unclear},
 
1536
                    mnesia_recover:log_decision(D4),
1491
1537
                    ?eval_debug_fun({?MODULE, multi_commit_asym_log_commit_dec},
1492
1538
                                    [{tid, Tid}]),
1493
1539
                    tell_participants(Pids, {Tid, pre_commit}),
1494
1540
                    %% Now we are uncertain and we do not know
1495
1541
                    %% if all participants have logged that
1496
1542
                    %% they are uncertain or not
1497
 
                    rec_acc_pre_commit(Pids, Tid, Store, {C,Local}, 
 
1543
                    rec_acc_pre_commit(Pids, Tid, Store, {C,Local},
1498
1544
                                       do_commit, DumperMode, [], []);
1499
1545
                {'EXIT', Reason} ->
1500
 
                    %% The others have logged the commit 
 
1546
                    %% The others have logged the commit
1501
1547
                    %% record but they are not uncertain
1502
1548
                    mnesia_recover:note_decision(Tid, aborted),
1503
1549
                    ?eval_debug_fun({?MODULE, multi_commit_asym_prepare_exit},
1518
1564
    end.
1519
1565
 
1520
1566
%% Returns do_commit or {do_abort, Reason}
1521
 
rec_acc_pre_commit([Pid | Tail], Tid, Store, Commit, Res, DumperMode, 
 
1567
rec_acc_pre_commit([Pid | Tail], Tid, Store, Commit, Res, DumperMode,
1522
1568
                   GoodPids, SchemaAckPids) ->
1523
1569
    receive
1524
1570
        {?MODULE, _, {acc_pre_commit, Tid, Pid, true}} ->
1552
1598
            %% everybody are uncertain.
1553
1599
            prepare_sync_schema_commit(Store, SchemaAckPids),
1554
1600
            tell_participants(GoodPids, {Tid, committed}),
1555
 
            D2 = D#decision{outcome = committed},               
 
1601
            D2 = D#decision{outcome = committed},
1556
1602
            mnesia_recover:log_decision(D2),
1557
1603
            ?eval_debug_fun({?MODULE, rec_acc_pre_commit_log_commit},
1558
1604
                            [{tid, Tid}]),
1565
1611
            sync_schema_commit(Tid, Store, SchemaAckPids),
1566
1612
            mnesia_locker:release_tid(Tid),
1567
1613
            ?MODULE ! {delete_transaction, Tid};
1568
 
        
 
1614
 
1569
1615
        {do_abort, Reason} ->
1570
1616
            tell_participants(GoodPids, {Tid, {do_abort, Reason}}),
1571
 
            D2 = D#decision{outcome = aborted},         
 
1617
            D2 = D#decision{outcome = aborted},
1572
1618
            mnesia_recover:log_decision(D2),
1573
1619
            ?eval_debug_fun({?MODULE, rec_acc_pre_commit_log_abort},
1574
1620
                            [{tid, Tid}]),
1604
1650
tell_participants([], _Msg) ->
1605
1651
    ok.
1606
1652
 
 
1653
-spec commit_participant(_, _, _, _, _) -> no_return().
1607
1654
%% Trap exit because we can get a shutdown from application manager
1608
1655
commit_participant(Coord, Tid, Bin, DiscNs, RamNs) when is_binary(Bin) ->
1609
1656
    process_flag(trap_exit, true),
1655
1702
                            end,
1656
1703
                            ?eval_debug_fun({?MODULE, commit_participant, do_commit},
1657
1704
                                            [{tid, Tid}]);
1658
 
                        
 
1705
 
1659
1706
                        {Tid, {do_abort, _Reason}} ->
1660
1707
                            mnesia_recover:log_decision(D#decision{outcome = aborted}),
1661
1708
                            ?eval_debug_fun({?MODULE, commit_participant, log_abort},
1663
1710
                            mnesia_schema:undo_prepare_commit(Tid, C0),
1664
1711
                            ?eval_debug_fun({?MODULE, commit_participant, undo_prepare},
1665
1712
                                            [{tid, Tid}]);
1666
 
                        
 
1713
 
1667
1714
                        {'EXIT', _, _} ->
1668
1715
                            mnesia_recover:log_decision(D#decision{outcome = aborted}),
1669
1716
                            ?eval_debug_fun({?MODULE, commit_participant, exit_log_abort},
1671
1718
                            mnesia_schema:undo_prepare_commit(Tid, C0),
1672
1719
                            ?eval_debug_fun({?MODULE, commit_participant, exit_undo_prepare},
1673
1720
                                            [{tid, Tid}]);
1674
 
                        
 
1721
 
1675
1722
                        Msg ->
1676
1723
                            verbose("** ERROR ** commit_participant ~p, got unexpected msg: ~p~n",
1677
1724
                                    [Tid, Msg])
1692
1739
                    verbose("** ERROR ** commit_participant ~p, got unexpected msg: ~p~n",
1693
1740
                            [Tid, Msg])
1694
1741
            end;
1695
 
        
 
1742
 
1696
1743
        {'EXIT', Reason} ->
1697
1744
            ?eval_debug_fun({?MODULE, commit_participant, vote_no},
1698
1745
                            [{tid, Tid}]),
1703
1750
    ?MODULE ! {delete_transaction, Tid},
1704
1751
    unlink(whereis(?MODULE)),
1705
1752
    exit(normal).
1706
 
    
 
1753
 
1707
1754
do_abort(Tid, Bin) when is_binary(Bin) ->
1708
1755
    %% Possible optimization:
1709
1756
    %% If we want we could pass arround a flag
1714
1761
    %% mnesia_schema:undo_prepare_commit/1.
1715
1762
    do_abort(Tid, binary_to_term(Bin));
1716
1763
do_abort(Tid, Commit) ->
1717
 
    mnesia_schema:undo_prepare_commit(Tid, Commit), 
 
1764
    mnesia_schema:undo_prepare_commit(Tid, Commit),
1718
1765
    Commit.
1719
1766
 
1720
1767
do_dirty(Tid, Commit) when Commit#commit.schema_ops == [] ->
1752
1799
 
1753
1800
            verbose("do_update in ~w failed: ~p -> {'EXIT', ~p}~n",
1754
1801
                    [Tid, Op, Reason]),
1755
 
            do_update(Tid, Storage, Ops, OldRes); 
 
1802
            do_update(Tid, Storage, Ops, OldRes);
1756
1803
        NewRes ->
1757
1804
            do_update(Tid, Storage, Ops, NewRes)
1758
1805
    end;
1760
1807
    Res.
1761
1808
 
1762
1809
do_update_op(Tid, Storage, {{Tab, K}, Obj, write}) ->
1763
 
    commit_write(?catch_val({Tab, commit_work}), Tid, 
 
1810
    commit_write(?catch_val({Tab, commit_work}), Tid,
1764
1811
                 Tab, K, Obj, undefined),
1765
1812
    mnesia_lib:db_put(Storage, Tab, Obj);
1766
1813
 
1769
1816
    mnesia_lib:db_erase(Storage, Tab, K);
1770
1817
 
1771
1818
do_update_op(Tid, Storage, {{Tab, K}, {RecName, Incr}, update_counter}) ->
1772
 
    {NewObj, OldObjs} = 
 
1819
    {NewObj, OldObjs} =
1773
1820
        case catch mnesia_lib:db_update_counter(Storage, Tab, K, Incr) of
1774
1821
            NewVal when is_integer(NewVal), NewVal >= 0 ->
1775
1822
                {{RecName, K, NewVal}, [{RecName, K, NewVal - Incr}]};
1777
1824
                New = {RecName, K, Incr},
1778
1825
                mnesia_lib:db_put(Storage, Tab, New),
1779
1826
                {New, []};
1780
 
            _ -> 
 
1827
            _ ->
1781
1828
                Zero = {RecName, K, 0},
1782
1829
                mnesia_lib:db_put(Storage, Tab, Zero),
1783
1830
                {Zero, []}
1784
1831
        end,
1785
 
    commit_update(?catch_val({Tab, commit_work}), Tid, Tab, 
 
1832
    commit_update(?catch_val({Tab, commit_work}), Tid, Tab,
1786
1833
                  K, NewObj, OldObjs),
1787
1834
    element(3, NewObj);
1788
1835
 
1789
1836
do_update_op(Tid, Storage, {{Tab, Key}, Obj, delete_object}) ->
1790
 
    commit_del_object(?catch_val({Tab, commit_work}), 
 
1837
    commit_del_object(?catch_val({Tab, commit_work}),
1791
1838
                      Tid, Tab, Key, Obj, undefined),
1792
1839
    mnesia_lib:db_match_erase(Storage, Tab, Obj);
1793
1840
 
1799
1846
commit_write([{checkpoints, CpList}|R], Tid, Tab, K, Obj, Old) ->
1800
1847
    mnesia_checkpoint:tm_retain(Tid, Tab, K, write, CpList),
1801
1848
    commit_write(R, Tid, Tab, K, Obj, Old);
1802
 
commit_write([H|R], Tid, Tab, K, Obj, Old) 
 
1849
commit_write([H|R], Tid, Tab, K, Obj, Old)
1803
1850
  when element(1, H) == subscribers ->
1804
1851
    mnesia_subscr:report_table_event(H, Tab, Tid, Obj, write, Old),
1805
1852
    commit_write(R, Tid, Tab, K, Obj, Old);
1806
 
commit_write([H|R], Tid, Tab, K, Obj, Old) 
 
1853
commit_write([H|R], Tid, Tab, K, Obj, Old)
1807
1854
  when element(1, H) == index ->
1808
1855
    mnesia_index:add_index(H, Tab, K, Obj, Old),
1809
1856
    commit_write(R, Tid, Tab, K, Obj, Old).
1812
1859
commit_update([{checkpoints, CpList}|R], Tid, Tab, K, Obj, _) ->
1813
1860
    Old = mnesia_checkpoint:tm_retain(Tid, Tab, K, write, CpList),
1814
1861
    commit_update(R, Tid, Tab, K, Obj, Old);
1815
 
commit_update([H|R], Tid, Tab, K, Obj, Old) 
 
1862
commit_update([H|R], Tid, Tab, K, Obj, Old)
1816
1863
  when element(1, H) == subscribers ->
1817
1864
    mnesia_subscr:report_table_event(H, Tab, Tid, Obj, write, Old),
1818
1865
    commit_update(R, Tid, Tab, K, Obj, Old);
1819
 
commit_update([H|R], Tid, Tab, K, Obj, Old) 
 
1866
commit_update([H|R], Tid, Tab, K, Obj, Old)
1820
1867
  when element(1, H) == index ->
1821
1868
    mnesia_index:add_index(H, Tab, K, Obj, Old),
1822
1869
    commit_update(R, Tid, Tab, K, Obj, Old).
1825
1872
commit_delete([{checkpoints, CpList}|R], Tid, Tab, K, Obj, _) ->
1826
1873
    Old = mnesia_checkpoint:tm_retain(Tid, Tab, K, delete, CpList),
1827
1874
    commit_delete(R, Tid, Tab, K, Obj, Old);
1828
 
commit_delete([H|R], Tid, Tab, K, Obj, Old) 
 
1875
commit_delete([H|R], Tid, Tab, K, Obj, Old)
1829
1876
  when element(1, H) == subscribers ->
1830
1877
    mnesia_subscr:report_table_event(H, Tab, Tid, Obj, delete, Old),
1831
1878
    commit_delete(R, Tid, Tab, K, Obj, Old);
1832
 
commit_delete([H|R], Tid, Tab, K, Obj, Old) 
 
1879
commit_delete([H|R], Tid, Tab, K, Obj, Old)
1833
1880
  when element(1, H) == index ->
1834
1881
    mnesia_index:delete_index(H, Tab, K),
1835
1882
    commit_delete(R, Tid, Tab, K, Obj, Old).
1838
1885
commit_del_object([{checkpoints, CpList}|R], Tid, Tab, K, Obj, _) ->
1839
1886
    Old = mnesia_checkpoint:tm_retain(Tid, Tab, K, delete_object, CpList),
1840
1887
    commit_del_object(R, Tid, Tab, K, Obj, Old);
1841
 
commit_del_object([H|R], Tid, Tab, K, Obj, Old) 
1842
 
  when element(1, H) == subscribers -> 
 
1888
commit_del_object([H|R], Tid, Tab, K, Obj, Old)
 
1889
  when element(1, H) == subscribers ->
1843
1890
    mnesia_subscr:report_table_event(H, Tab, Tid, Obj, delete_object, Old),
1844
1891
    commit_del_object(R, Tid, Tab, K, Obj, Old);
1845
 
commit_del_object([H|R], Tid, Tab, K, Obj, Old) 
1846
 
  when element(1, H) == index -> 
 
1892
commit_del_object([H|R], Tid, Tab, K, Obj, Old)
 
1893
  when element(1, H) == index ->
1847
1894
    mnesia_index:del_object_index(H, Tab, K, Obj, Old),
1848
1895
    commit_del_object(R, Tid, Tab, K, Obj, Old).
1849
1896
 
1851
1898
commit_clear([{checkpoints, CpList}|R], Tid, Tab, K, Obj) ->
1852
1899
    mnesia_checkpoint:tm_retain(Tid, Tab, K, clear_table, CpList),
1853
1900
    commit_clear(R, Tid, Tab, K, Obj);
1854
 
commit_clear([H|R], Tid, Tab, K, Obj) 
 
1901
commit_clear([H|R], Tid, Tab, K, Obj)
1855
1902
  when element(1, H) == subscribers ->
1856
1903
    mnesia_subscr:report_table_event(H, Tab, Tid, Obj, clear_table, undefined),
1857
1904
    commit_clear(R, Tid, Tab, K, Obj);
1858
 
commit_clear([H|R], Tid, Tab, K, Obj) 
 
1905
commit_clear([H|R], Tid, Tab, K, Obj)
1859
1906
  when element(1, H) == index ->
1860
1907
    mnesia_index:clear_index(H, Tab, K, Obj),
1861
1908
    commit_clear(R, Tid, Tab, K, Obj).
1866
1913
        {'EXIT', Reason} ->
1867
1914
            %% This should only happen when we recently have
1868
1915
            %% deleted our local replica or recently deattached
1869
 
            %% the snmp table 
 
1916
            %% the snmp table
1870
1917
 
1871
1918
            verbose("do_snmp in ~w failed: ~p -> {'EXIT', ~p}~n",
1872
1919
                    [Tid, Head, Reason]);
1875
1922
    end,
1876
1923
    do_snmp(Tid, Tail).
1877
1924
 
1878
 
commit_nodes([C | Tail], AccD, AccR) 
 
1925
commit_nodes([C | Tail], AccD, AccR)
1879
1926
        when C#commit.disc_copies == [],
1880
1927
             C#commit.disc_only_copies  == [],
1881
1928
             C#commit.schema_ops == [] ->
1887
1934
 
1888
1935
commit_decision(D, [C | Tail], AccD, AccR) ->
1889
1936
    N = C#commit.node,
1890
 
    {D2, Tail2} = 
 
1937
    {D2, Tail2} =
1891
1938
        case C#commit.schema_ops of
1892
1939
            [] when C#commit.disc_copies == [],
1893
1940
                    C#commit.disc_only_copies  == [] ->
1907
1954
    {D#decision{disc_nodes = AccD, ram_nodes = AccR}, []}.
1908
1955
 
1909
1956
ram_only_ops(N, [{op, change_table_copy_type, N, _FromS, _ToS, Cs} | _Ops ]) ->
1910
 
    case lists:member({name, schema}, Cs) of 
1911
 
        true -> 
 
1957
    case lists:member({name, schema}, Cs) of
 
1958
        true ->
1912
1959
            %% We always use disk if change type of the schema
1913
1960
            false;
1914
1961
        false ->
1978
2025
            Reply;
1979
2026
        {mnesia_down, Node} ->
1980
2027
            case get(mnesia_activity_state) of
1981
 
                {_, Tid, _Ts} when element(1,Tid) == tid -> 
 
2028
                {_, Tid, _Ts} when element(1,Tid) == tid ->
1982
2029
                    %% Hmm dirty called inside a transaction, to avoid
1983
2030
                    %% hanging transaction we need to restart the transaction
1984
2031
                    mnesia:abort({node_not_running, Node});
1985
2032
                _ ->
1986
 
                    %% It's ok to ignore mnesia_down's since we will make 
 
2033
                    %% It's ok to ignore mnesia_down's since we will make
1987
2034
                    %% the replicas consistent again when Node is started
1988
2035
                    Res
1989
2036
            end
2021
2068
%% to be safe we let erts do the translation (many times maybe and thus
2022
2069
%% slower but it works.
2023
2070
% opt_term_to_binary(asym_trans, Head, Nodes) ->
2024
 
%     opt_term_to_binary(Nodes, Head);    
 
2071
%     opt_term_to_binary(Nodes, Head);
2025
2072
opt_term_to_binary(_Protocol, Head, _Nodes) ->
2026
2073
    Head.
2027
 
            
 
2074
 
2028
2075
rec_all([Node | Tail], Tid, Res, Pids) ->
2029
2076
    receive
2030
2077
        {?MODULE, Node, {vote_yes, Tid}} ->
2038
2085
        {?MODULE, Node, {aborted, Tid}} ->
2039
2086
            rec_all(Tail, Tid, Res, Pids);
2040
2087
 
2041
 
        {mnesia_down, Node} ->  
 
2088
        {mnesia_down, Node} ->
2042
2089
            %% Make sure that mnesia_tm knows it has died
2043
2090
            %% it may have been restarted
2044
2091
            Abort = {do_abort, {bad_commit, Node}},
2048
2095
rec_all([], _Tid, Res, Pids) ->
2049
2096
    {Res, Pids}.
2050
2097
 
2051
 
get_transactions() -> 
 
2098
get_transactions() ->
2052
2099
    {info, Participant, Coordinator} = req(info),
2053
2100
    lists:map(fun({Tid, _Tabs}) ->
2054
2101
                      Status = tr_status(Tid,Participant),
2078
2125
display_info(Stream, {timeout, T}) ->
2079
2126
    io:format(Stream, "---> No info about coordinator and participant transactions, "
2080
2127
              "timeout ~p <--- ~n", [T]);
2081
 
    
 
2128
 
2082
2129
display_info(Stream, {info, Part, Coord}) ->
2083
2130
    io:format(Stream, "---> Participant transactions <--- ~n", []),
2084
2131
    lists:foreach(fun(P) -> pr_participant(Stream, P) end, Part),
2087
2134
 
2088
2135
pr_participant(Stream, P) ->
2089
2136
    Commit0 = P#participant.commit,
2090
 
    Commit = 
 
2137
    Commit =
2091
2138
        if
2092
2139
            is_binary(Commit0) -> binary_to_term(Commit0);
2093
2140
            true -> Commit0
2114
2161
            io:format( "Tid is coordinator, owner == \n", []),
2115
2162
            display_pid_info(Tid#tid.pid),
2116
2163
            search_pr_coordinator(S, Tail);
2117
 
        _ -> 
 
2164
        _ ->
2118
2165
            search_pr_coordinator(S, Tail)
2119
2166
    end.
2120
2167
 
2121
 
search_pr_participant(_S, []) -> 
 
2168
search_pr_participant(_S, []) ->
2122
2169
    false;
2123
2170
search_pr_participant(S, [ P | Tail]) ->
2124
2171
    Tid = P#participant.tid,
2129
2176
            Pid = Tid#tid.pid,
2130
2177
            display_pid_info(Pid),
2131
2178
            io:format( "Tid wants to write objects \n",[]),
2132
 
            Commit = 
 
2179
            Commit =
2133
2180
                if
2134
2181
                    is_binary(Commit0) -> binary_to_term(Commit0);
2135
2182
                    true -> Commit0
2136
2183
                end,
2137
 
            
 
2184
 
2138
2185
            io:format("~p~n", [Commit]),
2139
2186
            search_pr_participant(S,Tail);  %% !!!!!
2140
 
        true -> 
 
2187
        true ->
2141
2188
            search_pr_participant(S, Tail)
2142
2189
    end.
2143
2190
 
2153
2200
                       Other ->
2154
2201
                           Other
2155
2202
                   end,
2156
 
            Reds  = fetch(reductions, Info), 
 
2203
            Reds  = fetch(reductions, Info),
2157
2204
            LM = length(fetch(messages, Info)),
2158
2205
            pformat(io_lib:format("~p", [Pid]),
2159
2206
                    io_lib:format("~p", [Call]),
2207
2254
    send_to_pids(Pids, Msg);
2208
2255
send_to_pids([], _Msg) ->
2209
2256
    ok.
2210
 
    
 
2257
 
2211
2258
reconfigure_participants(N, [P | Tail]) ->
2212
2259
    case lists:member(N, P#participant.disc_nodes) or
2213
2260
         lists:member(N, P#participant.ram_nodes) of
2215
2262
            %% Ignore, since we are not a participant
2216
2263
            %% in the transaction.
2217
2264
            reconfigure_participants(N, Tail);
2218
 
 
 
2265
 
2219
2266
        true ->
2220
2267
            %% We are on a participant node, lets
2221
2268
            %% check if the dead one was a
2222
2269
            %% participant or a coordinator.
2223
2270
            Tid  = P#participant.tid,
2224
 
            if 
 
2271
            if
2225
2272
                node(Tid#tid.pid) /= N ->
2226
2273
                    %% Another participant node died. Ignore.
2227
2274
                    reconfigure_participants(N, Tail);
2228
2275
 
2229
2276
                true ->
2230
 
                    %% The coordinator node has died and 
 
2277
                    %% The coordinator node has died and
2231
2278
                    %% we must determine the outcome of the
2232
2279
                    %% transaction and tell mnesia_tm on all
2233
2280
                    %% nodes (including the local node) about it
2234
2281
                    verbose("Coordinator ~p in transaction ~p died~n",
2235
2282
                            [Tid#tid.pid, Tid]),
2236
 
                            
 
2283
 
2237
2284
                    Nodes = P#participant.disc_nodes ++
2238
2285
                            P#participant.ram_nodes,
2239
2286
                    AliveNodes = Nodes  -- [N],
2279
2326
system_continue(_Parent, _Debug, State) ->
2280
2327
    doit_loop(State).
2281
2328
 
 
2329
-spec system_terminate(_, _, _, _) -> no_return().
2282
2330
system_terminate(_Reason, _Parent, _Debug, State) ->
2283
2331
    do_stop(State).
2284
2332
 
2285
2333
system_code_change(State=#state{coordinators=Cs0,participants=Ps0},_Module,_OldVsn,downgrade) ->
2286
2334
    case is_tuple(Cs0) of
2287
 
        true -> 
2288
 
            Cs = gb_trees:to_list(Cs0),     
 
2335
        true ->
 
2336
            Cs = gb_trees:to_list(Cs0),
2289
2337
            Ps = gb_trees:values(Ps0),
2290
2338
            {ok, State#state{coordinators=Cs,participants=Ps}};
2291
2339
        false ->
2294
2342
 
2295
2343
system_code_change(State=#state{coordinators=Cs0,participants=Ps0},_Module,_OldVsn,_Extra) ->
2296
2344
    case is_list(Cs0) of
2297
 
        true -> 
 
2345
        true ->
2298
2346
            Cs = gb_trees:from_orddict(lists:sort(Cs0)),
2299
2347
            Ps1 = [{P#participant.tid,P}|| P <- Ps0],
2300
2348
            Ps = gb_trees:from_orddict(lists:sort(Ps1)),