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

« back to all changes in this revision

Viewing changes to lib/mnesia/src/mnesia_frag.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 1998-2009. All Rights Reserved.
 
4
%% Copyright Ericsson AB 1998-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
209
209
            end
210
210
    end.
211
211
 
212
 
search_first(ActivityId, Opaque, Tab, N, FH) when N =< FH#frag_state.n_fragments ->
 
212
search_first(ActivityId, Opaque, Tab, N, FH) when N < FH#frag_state.n_fragments ->
213
213
    NextN = N + 1,
214
214
    NextFrag = n_to_frag_name(Tab, NextN),
215
215
    case mnesia:first(ActivityId, Opaque, NextFrag) of
448
448
 
449
449
local_collect(Ref, Pid, Type, LocalMatch, OldSelectFun) ->
450
450
    receive
451
 
        {local_select, Ref, LocalRes} ->
452
 
            remote_collect(Ref, Type, LocalRes, LocalMatch, OldSelectFun);
 
451
        {local_select, Ref, ok} ->
 
452
            remote_collect_ok(Ref, Type, LocalMatch, OldSelectFun);
 
453
        {local_select, Ref, {error, Reason}} ->
 
454
            remote_collect_error(Ref, Type, Reason, OldSelectFun);
453
455
        {'EXIT', Pid, Reason} ->
454
 
            remote_collect(Ref, Type, {error, Reason}, [], OldSelectFun)
 
456
            remote_collect_error(Ref, Type, Reason, OldSelectFun)
455
457
    end.
456
458
    
457
 
remote_collect(Ref, Type, LocalRes = ok, Acc, OldSelectFun) ->
 
459
remote_collect_ok(Ref, Type, Acc, OldSelectFun) ->
458
460
    receive
459
461
        {remote_select, Ref, Node, RemoteRes} ->
460
462
            case RemoteRes of
463
465
                                  ordered_set -> lists:merge(RemoteMatch, Acc);
464
466
                                  _ -> RemoteMatch ++ Acc
465
467
                              end,
466
 
                    remote_collect(Ref, Type, LocalRes, Matches, OldSelectFun);
 
468
                    remote_collect_ok(Ref, Type, Matches, OldSelectFun);
467
469
                _ ->
468
 
                    remote_collect(Ref, Type, {error, {node_not_running, Node}}, [], OldSelectFun)
 
470
                    Reason = {node_not_running, Node},
 
471
                    remote_collect_error(Ref, Type, Reason, OldSelectFun)
469
472
            end
470
473
    after 0 ->
471
474
            Acc
472
 
    end;
473
 
remote_collect(Ref, Type, LocalRes = {error, Reason}, _Acc, OldSelectFun) ->
 
475
    end.
 
476
 
 
477
remote_collect_error(Ref, Type, Reason, OldSelectFun) ->
474
478
    receive
475
479
        {remote_select, Ref, _Node, _RemoteRes} ->
476
 
            remote_collect(Ref, Type, LocalRes, [], OldSelectFun)
 
480
            remote_collect_error(Ref, Type, Reason, OldSelectFun)
477
481
    after 0 ->
478
 
            mnesia:abort(Reason)
 
482
            mnesia:abort({error, Reason})
479
483
    end.
480
484
 
481
485
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
754
758
        [] ->
755
759
            Cs2 = Cs#cstruct{frag_properties = Props},
756
760
            [Cs3] = expand_cstruct(Cs2, activate),
757
 
            TabDef = mnesia_schema:cs2list(Cs3),
 
761
            TabDef = mnesia_schema:vsn_cs2list(Cs3),
758
762
            Op = {op, change_table_frag, activate, TabDef},
759
763
            [[Op]];
760
764
        BadProps ->
779
783
            mnesia:abort({combine_error, Tab, "Too many fragments"});
780
784
        true ->
781
785
            Cs2 = Cs#cstruct{frag_properties = []},
782
 
            TabDef = mnesia_schema:cs2list(Cs2),
 
786
            TabDef = mnesia_schema:vsn_cs2list(Cs2),
783
787
            Op = {op, change_table_frag, deactivate, TabDef},
784
788
            [[Op]]
785
789
    end.
846
850
    SplitOps = split(Tab, FH2, FromIndecies, FragNames, []),
847
851
 
848
852
    Cs2 = replace_frag_hash(Cs, FH2),
849
 
    TabDef = mnesia_schema:cs2list(Cs2),
 
853
    TabDef = mnesia_schema:vsn_cs2list(Cs2),
850
854
    BaseOp = {op, change_table_frag, {add_frag, SortedNs}, TabDef},
851
855
 
852
856
    [BaseOp, NewOp | SplitOps].
958
962
            LastFrag = element(N, FragNames),
959
963
            [LastOp] = mnesia_schema:make_delete_table(LastFrag, single_frag),
960
964
            Cs2 = replace_frag_hash(Cs, FH2),
961
 
            TabDef = mnesia_schema:cs2list(Cs2),
 
965
            TabDef = mnesia_schema:vsn_cs2list(Cs2),
962
966
            BaseOp = {op, change_table_frag, del_frag, TabDef},
963
967
            [BaseOp, LastOp | MergeOps];
964
968
        _ ->
1071
1075
            Props = Cs#cstruct.frag_properties,
1072
1076
            Props2 = lists:keyreplace(node_pool, 1, Props, {node_pool, Pool2}),
1073
1077
            Cs2 = Cs#cstruct{frag_properties = Props2},
1074
 
            TabDef = mnesia_schema:cs2list(Cs2),
 
1078
            TabDef = mnesia_schema:vsn_cs2list(Cs2),
1075
1079
            Op = {op, change_table_frag, {add_node, Node}, TabDef},
1076
1080
            [Op];
1077
1081
        true ->
1100
1104
            Pool2 = Pool -- [Node],
1101
1105
            Props = lists:keyreplace(node_pool, 1, Cs#cstruct.frag_properties, {node_pool, Pool2}),
1102
1106
            Cs2 = Cs#cstruct{frag_properties = Props},
1103
 
            TabDef = mnesia_schema:cs2list(Cs2),
 
1107
            TabDef = mnesia_schema:vsn_cs2list(Cs2),
1104
1108
            Op = {op, change_table_frag, {del_node, Node}, TabDef},
1105
1109
            [Op];
1106
1110
        false ->