~ubuntu-branches/debian/squeeze/erlang/squeeze

« back to all changes in this revision

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

  • Committer: Bazaar Package Importer
  • Author(s): Erlang Packagers, Sergei Golovan
  • Date: 2006-12-03 17:07:44 UTC
  • mfrom: (2.1.11 feisty)
  • Revision ID: james.westby@ubuntu.com-20061203170744-rghjwupacqlzs6kv
Tags: 1:11.b.2-4
[ Sergei Golovan ]
Fixed erlang-base and erlang-base-hipe prerm scripts.

Show diffs side-by-side

added added

removed removed

Lines of Context:
46
46
         %% Access within an activity - Reads
47
47
         read/1, wread/1, read/3, read/5,
48
48
         match_object/1, match_object/3, match_object/5,
49
 
         select/2, select/3, select/5,
 
49
         select/1,select/2,select/3,select/4,select/5,select/6,
50
50
         all_keys/1, all_keys/4,
51
51
         index_match_object/2, index_match_object/4, index_match_object/6,
52
52
         index_read/3, index_read/6,
 
53
         first/1, next/2, last/1, prev/2,
53
54
 
54
55
         %% Iterators within an activity 
55
56
         foldl/3, foldl/4, foldr/3, foldr/4,
106
107
         %% Textfile access
107
108
         load_textfile/1, dump_to_textfile/1,
108
109
         
 
110
         %% QLC functions
 
111
         table/1, table/2,
 
112
 
109
113
         %% Mnemosyne exclusive
110
114
         get_activity_id/0, put_activity_id/1, % Not for public use
111
115
 
112
116
         %% Mnesia internal functions
113
117
         dirty_rpc/4,                          % Not for public use
114
 
         has_var/1, fun_select/7,
 
118
         has_var/1, fun_select/7, fun_select/10, select_cont/3, dirty_sel_init/5,
115
119
         foldl/6, foldr/6,
116
120
 
117
121
         %% Module internal callback functions
 
122
         raw_table_info/2,                      % Not for public use
118
123
         remote_dirty_match_object/2,           % Not for public use
119
124
         remote_dirty_select/2                  % Not for public use
120
125
        ]).
693
698
              ok;
694
699
        Protocol ->
695
700
              do_dirty_delete_object(Protocol, Tab, Val)
696
 
    end; 
 
701
    end;
697
702
delete_object(_Tid, _Ts, Tab, _Key, _LockKind) ->
698
703
    abort({bad_type, Tab}).
699
704
 
722
727
 
723
728
read(Tid, Ts, Tab, Key, LockKind)
724
729
  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)
 
730
    case element(1, Tid) of
 
731
        ets ->
 
732
            ?ets_lookup(Tab, Key);
 
733
        tid ->
 
734
            Store = Ts#tidstore.store,
 
735
            Oid = {Tab, Key},
 
736
            Objs =
 
737
                case LockKind of
 
738
                    read ->
 
739
                        mnesia_locker:rlock(Tid, Store, Oid);
 
740
                    write ->
 
741
                        mnesia_locker:rwlock(Tid, Store, Oid);
 
742
                    sticky_write ->
 
743
                        mnesia_locker:sticky_rwlock(Tid, Store, Oid);
 
744
                    _ ->
 
745
                        abort({bad_type, Tab, LockKind})
 
746
                end,
 
747
            add_written(?ets_lookup(Store, Oid), Tab, Objs);
 
748
        _Protocol ->
 
749
            dirty_read(Tab, Key)
745
750
    end; 
746
751
read(_Tid, _Ts, Tab, _Key, _LockKind) ->
747
752
    abort({bad_type, Tab}).
748
753
 
 
754
first(Tab) ->
 
755
    case get(mnesia_activity_state) of
 
756
        {?DEFAULT_ACCESS, Tid, Ts} ->
 
757
            first(Tid, Ts, Tab);
 
758
        {Mod, Tid, Ts} ->
 
759
            Mod:first(Tid, Ts, Tab);
 
760
        _ ->
 
761
            abort(no_transaction)
 
762
    end.
 
763
    
 
764
first(Tid, Ts, Tab)
 
765
  when atom(Tab), Tab /= schema ->
 
766
    case element(1, Tid) of
 
767
        ets ->
 
768
            ?ets_first(Tab);
 
769
        tid ->
 
770
            lock_table(Tid, Ts, Tab, read),
 
771
            do_fixtable(Tab,Ts),
 
772
            Key = dirty_first(Tab),
 
773
            stored_keys(Tab,Key,'$end_of_table',Ts,next,
 
774
                        val({Tab, setorbag}));
 
775
        _Protocol ->
 
776
            dirty_first(Tab)
 
777
    end;
 
778
first(_Tid, _Ts,Tab) ->
 
779
    abort({bad_type, Tab}).
 
780
 
 
781
last(Tab) ->
 
782
    case get(mnesia_activity_state) of
 
783
        {?DEFAULT_ACCESS, Tid, Ts} ->
 
784
            last(Tid, Ts, Tab);
 
785
        {Mod, Tid, Ts} ->
 
786
            Mod:last(Tid, Ts, Tab);
 
787
        _ ->
 
788
            abort(no_transaction)
 
789
    end.
 
790
 
 
791
last(Tid, Ts, Tab)
 
792
  when atom(Tab), Tab /= schema ->
 
793
    case element(1, Tid) of
 
794
        ets ->
 
795
            ?ets_last(Tab);
 
796
        tid ->
 
797
            lock_table(Tid, Ts, Tab, read),
 
798
            do_fixtable(Tab,Ts),
 
799
            Key = dirty_last(Tab),
 
800
            stored_keys(Tab,Key,'$end_of_table',Ts,prev,
 
801
                        val({Tab, setorbag}));
 
802
        _Protocol ->
 
803
            dirty_last(Tab)
 
804
    end;
 
805
last(_Tid, _Ts,Tab) ->
 
806
    abort({bad_type, Tab}).
 
807
 
 
808
next(Tab,Key) ->
 
809
    case get(mnesia_activity_state) of
 
810
        {?DEFAULT_ACCESS,Tid,Ts} ->
 
811
            next(Tid,Ts,Tab,Key);
 
812
        {Mod,Tid,Ts} ->
 
813
            Mod:next(Tid,Ts,Tab,Key);
 
814
        _ ->
 
815
            abort(no_transaction)
 
816
    end.
 
817
next(Tid,Ts,Tab,Key)
 
818
  when atom(Tab), Tab /= schema ->
 
819
    case element(1, Tid) of
 
820
        ets ->
 
821
            ?ets_next(Tab,Key);
 
822
        tid ->
 
823
            lock_table(Tid, Ts, Tab, read),
 
824
            do_fixtable(Tab,Ts),
 
825
            New = (catch dirty_next(Tab,Key)),
 
826
            stored_keys(Tab,New,Key,Ts,next,
 
827
                        val({Tab, setorbag}));
 
828
        _Protocol ->
 
829
            dirty_next(Tab,Key)
 
830
    end;
 
831
next(_Tid, _Ts,Tab,_) ->
 
832
    abort({bad_type, Tab}).
 
833
 
 
834
prev(Tab,Key) ->
 
835
    case get(mnesia_activity_state) of
 
836
        {?DEFAULT_ACCESS,Tid,Ts} ->
 
837
            prev(Tid,Ts,Tab,Key);
 
838
        {Mod,Tid,Ts} ->
 
839
            Mod:prev(Tid,Ts,Tab,Key);
 
840
        _ ->
 
841
            abort(no_transaction)
 
842
    end.
 
843
prev(Tid,Ts,Tab,Key)
 
844
  when atom(Tab), Tab /= schema ->
 
845
    case element(1, Tid) of
 
846
        ets ->
 
847
            ?ets_prev(Tab,Key);
 
848
        tid ->
 
849
            lock_table(Tid, Ts, Tab, read),
 
850
            do_fixtable(Tab,Ts),
 
851
            New = (catch dirty_prev(Tab,Key)),
 
852
            stored_keys(Tab,New,Key,Ts,prev,
 
853
                        val({Tab, setorbag}));
 
854
        _Protocol ->
 
855
            dirty_prev(Tab,Key)
 
856
    end;
 
857
prev(_Tid, _Ts,Tab,_) ->
 
858
    abort({bad_type, Tab}).
 
859
 
 
860
%% Compensate for transaction written and/or deleted records
 
861
stored_keys(Tab,'$end_of_table',Prev,Ts,Op,Type) ->
 
862
    case ts_keys(Ts#tidstore.store,Tab,Op,Type,[]) of
 
863
        [] -> '$end_of_table';
 
864
        Keys when Type == ordered_set-> 
 
865
            get_ordered_tskey(Prev,Keys,Op);
 
866
        Keys -> 
 
867
            get_next_tskey(Prev,Keys,Tab)
 
868
    end;
 
869
stored_keys(Tab,{'EXIT',{aborted,R={badarg,[Tab,Key]}}},
 
870
            Key,#tidstore{store=Store},Op,Type) ->
 
871
    %% Had to match on error, ouch..
 
872
    case ?ets_match(Store, {{Tab, Key}, '_', '$1'}) of
 
873
        [] ->  abort(R);
 
874
        Ops ->
 
875
            case lists:last(Ops) of
 
876
                [delete] -> abort(R);
 
877
                _ -> 
 
878
                    case ts_keys(Store,Tab,Op,Type,[]) of
 
879
                        [] -> '$end_of_table';
 
880
                        Keys -> get_next_tskey(Key,Keys,Tab)
 
881
                    end
 
882
            end
 
883
    end;
 
884
stored_keys(_,{'EXIT',{aborted,R}},_,_,_,_) ->
 
885
    abort(R);
 
886
stored_keys(Tab,Key,Prev,#tidstore{store=Store},Op,ordered_set) ->
 
887
    case ?ets_match(Store, {{Tab, Key}, '_', '$1'}) of
 
888
        [] -> 
 
889
            Keys = ts_keys(Store,Tab,Op,ordered_set,[Key]),
 
890
            get_ordered_tskey(Prev,Keys,Op);
 
891
        Ops ->
 
892
            case lists:last(Ops) of
 
893
                [delete] ->
 
894
                    mnesia:Op(Tab,Key);
 
895
                _ -> 
 
896
                    Keys = ts_keys(Store,Tab,Op,ordered_set,[Key]),
 
897
                    get_ordered_tskey(Prev,Keys,Op)
 
898
            end
 
899
    end;
 
900
stored_keys(Tab,Key,_,#tidstore{store=Store},Op,_) ->
 
901
    case ?ets_match(Store, {{Tab, Key}, '_', '$1'}) of
 
902
        [] ->  Key;
 
903
        Ops ->
 
904
            case lists:last(Ops) of
 
905
                [delete] -> mnesia:Op(Tab,Key);
 
906
                _ ->      Key
 
907
            end
 
908
    end.
 
909
 
 
910
get_ordered_tskey('$end_of_table', [First|_],_) ->    First;
 
911
get_ordered_tskey(Prev, [First|_], next) when Prev < First -> First;
 
912
get_ordered_tskey(Prev, [First|_], prev) when Prev > First -> First;
 
913
get_ordered_tskey(Prev, [_|R],Op) ->  get_ordered_tskey(Prev,R,Op);
 
914
get_ordered_tskey(_, [],_) ->    '$end_of_table'.
 
915
 
 
916
get_next_tskey(_, [],_) -> '$end_of_table';
 
917
get_next_tskey(Key,Keys,Tab) ->
 
918
    Next = 
 
919
        if Key == '$end_of_table' -> hd(Keys);
 
920
           true ->
 
921
                case lists:dropwhile(fun(A) -> A /= Key end, Keys) of
 
922
                    [] -> hd(Keys); %% First stored key
 
923
                    [Key] -> '$end_of_table';
 
924
                    [Key,Next2|_] -> Next2
 
925
                end
 
926
        end,
 
927
    case Next of
 
928
        '$end_of_table' -> '$end_of_table';
 
929
        _ -> %% Really slow anybody got another solution??
 
930
            case dirty_read(Tab, Next) of
 
931
                [] -> Next;
 
932
                _ ->  
 
933
                    %% Updated value we already returned this key
 
934
                    get_next_tskey(Next,Keys,Tab)
 
935
            end
 
936
    end.
 
937
 
 
938
ts_keys(Store, Tab, Op, Type, Def) ->
 
939
    All = ?ets_match(Store, {{Tab,'$1'},'_','$2'}),
 
940
    Keys = ts_keys_1(All, Def),
 
941
    if 
 
942
        Type == ordered_set, Op == prev ->
 
943
            lists:reverse(lists:sort(Keys));
 
944
        Type == ordered_set ->
 
945
            lists:sort(Keys);
 
946
        Op == next ->
 
947
            lists:reverse(Keys);
 
948
        true ->
 
949
            Keys
 
950
    end.
 
951
 
 
952
ts_keys_1([[Key, write]|R], []) ->
 
953
    ts_keys_1(R, [Key]);
 
954
ts_keys_1([[Key, write]|R], Acc=[Key|_]) ->
 
955
    ts_keys_1(R, Acc);
 
956
ts_keys_1([[Key, write]|R], Acc) ->
 
957
    ts_keys_1(R, [Key|Acc]);
 
958
ts_keys_1([[Key, delete]|R], [Key|Acc]) ->
 
959
    ts_keys_1(R, Acc);
 
960
ts_keys_1([_|R], Acc) ->
 
961
    ts_keys_1(R, Acc);
 
962
ts_keys_1([], Acc) ->
 
963
    Acc.
 
964
 
 
965
 
749
966
%%%%%%%%%%%%%%%%%%%%%
750
967
%% Iterators 
751
968
 
773
990
                end, RAcc, Stored);
774
991
do_foldl(A, O, Tab, Key, Fun, Acc, ordered_set, [H | Stored]) when H == Key ->
775
992
    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);
 
993
    {_, Tid, Ts} = get(mnesia_activity_state),
 
994
    do_foldl(Tid, Ts, Tab, dirty_next(Tab, Key), Fun, NewAcc, ordered_set, Stored);
777
995
do_foldl(A, O, Tab, Key, Fun, Acc, ordered_set, [H | Stored]) when H < Key ->
778
996
    NewAcc = lists:foldl(Fun, Acc, read(A, O, Tab, H, read)),
779
 
    do_foldl(A, O, Tab, Key, Fun, NewAcc, ordered_set, Stored);
 
997
    {_, Tid, Ts} = get(mnesia_activity_state),
 
998
    do_foldl(Tid, Ts, Tab, Key, Fun, NewAcc, ordered_set, Stored);
780
999
do_foldl(A, O, Tab, Key, Fun, Acc, ordered_set, [H | Stored]) when H > Key ->
781
1000
    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]);
 
1001
    {_, Tid, Ts} = get(mnesia_activity_state),
 
1002
    do_foldl(Tid, Ts, Tab, dirty_next(Tab, Key), Fun, NewAcc, ordered_set, [H |Stored]);
783
1003
do_foldl(A, O, Tab, Key, Fun, Acc, Type, Stored) ->  %% Type is set or bag 
784
1004
    NewAcc = lists:foldl(Fun, Acc, read(A, O, Tab, Key, read)),
785
1005
    NewStored = ordsets:del_element(Key, Stored),
786
 
    do_foldl(A, O, Tab, dirty_next(Tab, Key), Fun, NewAcc, Type, NewStored).
 
1006
    {_, Tid, Ts} = get(mnesia_activity_state),
 
1007
    do_foldl(Tid, Ts, Tab, dirty_next(Tab, Key), Fun, NewAcc, Type, NewStored).
787
1008
 
788
1009
foldr(Fun, Acc, Tab) ->
789
1010
    foldr(Fun, Acc, Tab, read).
815
1036
                end, RAcc, Stored);
816
1037
do_foldr(A, O, Tab, Key, Fun, Acc, ordered_set, [H | Stored]) when H == Key ->
817
1038
    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);
 
1039
    {_, Tid, Ts} = get(mnesia_activity_state),
 
1040
    do_foldr(Tid, Ts, Tab, dirty_prev(Tab, Key), Fun, NewAcc, ordered_set, Stored);
819
1041
do_foldr(A, O, Tab, Key, Fun, Acc, ordered_set, [H | Stored]) when H > Key ->
820
1042
    NewAcc = lists:foldl(Fun, Acc, read(A, O, Tab, H, read)),
821
 
    do_foldr(A, O, Tab, Key, Fun, NewAcc, ordered_set, Stored);
 
1043
    {_, Tid, Ts} = get(mnesia_activity_state),
 
1044
    do_foldr(Tid, Ts, Tab, Key, Fun, NewAcc, ordered_set, Stored);
822
1045
do_foldr(A, O, Tab, Key, Fun, Acc, ordered_set, [H | Stored]) when H < Key ->
823
1046
    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]);
 
1047
    {_, Tid, Ts} = get(mnesia_activity_state),
 
1048
    do_foldr(Tid, Ts, Tab, dirty_prev(Tab, Key), Fun, NewAcc, ordered_set, [H |Stored]);
825
1049
do_foldr(A, O, Tab, Key, Fun, Acc, Type, Stored) ->  %% Type is set or bag 
826
1050
    NewAcc = lists:foldl(Fun, Acc, read(A, O, Tab, Key, read)),
827
1051
    NewStored = ordsets:del_element(Key, Stored),
828
 
    do_foldr(A, O, Tab, dirty_prev(Tab, Key), Fun, NewAcc, Type, NewStored).
 
1052
    {_, Tid, Ts} = get(mnesia_activity_state),
 
1053
    do_foldr(Tid, Ts, Tab, dirty_prev(Tab, Key), Fun, NewAcc, Type, NewStored).
829
1054
 
830
1055
init_iteration(ActivityId, Opaque, Tab, LockKind) ->
831
1056
    lock(ActivityId, Opaque, {table, Tab}, LockKind),
980
1205
add_ordered_match([], Objs, Acc) ->
981
1206
    lists:reverse(Acc, Objs).
982
1207
 
 
1208
%% For select chunk
 
1209
add_sel_match(Sorted, Objs, ordered_set) ->
 
1210
    add_sel_ordered_match(Sorted, Objs, []);
 
1211
add_sel_match(Written, Objs, Type) ->
 
1212
    add_sel_match(Written, Objs, Type, []).
 
1213
 
 
1214
add_sel_match([], Objs, _Type, Acc) ->
 
1215
    {Objs,lists:reverse(Acc)};
 
1216
add_sel_match([Op={Oid, _, delete}|R], Objs, Type, Acc) ->
 
1217
    case deloid(Oid, Objs) of
 
1218
        Objs ->
 
1219
            add_sel_match(R, Objs, Type, [Op|Acc]);
 
1220
        NewObjs when Type == set ->
 
1221
            add_sel_match(R, NewObjs, Type, Acc);
 
1222
        NewObjs ->  %% If bag we may get more in next chunk
 
1223
            add_sel_match(R, NewObjs, Type, [Op|Acc])
 
1224
    end;
 
1225
add_sel_match([Op = {_Oid, Val, delete_object}|R], Objs, Type, Acc) ->
 
1226
    case lists:delete(Val, Objs) of
 
1227
        Objs -> 
 
1228
            add_sel_match(R, Objs, Type, [Op|Acc]);
 
1229
        NewObjs when Type == set ->
 
1230
            add_sel_match(R, NewObjs, Type, Acc);
 
1231
        NewObjs ->
 
1232
            add_sel_match(R, NewObjs, Type, [Op|Acc])
 
1233
    end;
 
1234
add_sel_match([Op={Oid={_,Key}, Val, write}|R], Objs, bag, Acc) ->
 
1235
    case lists:keymember(Key, 2, Objs) of
 
1236
        true ->
 
1237
            add_sel_match(R,[Val|lists:delete(Val,Objs)],bag,
 
1238
                          [{Oid,Val,delete_object}|Acc]);
 
1239
        false ->
 
1240
            add_sel_match(R,Objs,bag,[Op|Acc])
 
1241
    end;
 
1242
add_sel_match([Op={Oid, Val, write}|R], Objs, set, Acc) ->
 
1243
    case deloid(Oid,Objs) of
 
1244
        Objs -> 
 
1245
            add_sel_match(R, Objs,set, [Op|Acc]);
 
1246
        NewObjs ->
 
1247
            add_sel_match(R, [Val | NewObjs],set, Acc)
 
1248
    end.
 
1249
 
 
1250
%% For ordered_set only !!
 
1251
add_sel_ordered_match(Written = [{{_, Key}, _, _}|_], [Obj|Objs],Acc) 
 
1252
  when Key > element(2, Obj) ->
 
1253
    add_sel_ordered_match(Written, Objs, [Obj|Acc]);
 
1254
add_sel_ordered_match([{{_, Key}, Val, write}|Rest], Objs =[Obj|_],Acc) 
 
1255
  when Key < element(2, Obj) ->
 
1256
    add_sel_ordered_match(Rest,[Val|Objs],Acc);
 
1257
add_sel_ordered_match([{{_, Key}, _, _DelOP}|Rest], Objs =[Obj|_], Acc) 
 
1258
  when Key < element(2, Obj) ->
 
1259
    add_sel_ordered_match(Rest,Objs,Acc);
 
1260
%% Greater than last object
 
1261
add_sel_ordered_match(Ops1, [], Acc) ->
 
1262
    {lists:reverse(Acc), Ops1};
 
1263
%% Keys are equal from here 
 
1264
add_sel_ordered_match([{_, Val, write}|Rest], [_Obj|Objs], Acc) ->
 
1265
    add_sel_ordered_match(Rest, [Val|Objs], Acc);
 
1266
add_sel_ordered_match([{_, _Val, delete}|Rest], [_Obj|Objs], Acc) ->
 
1267
    add_sel_ordered_match(Rest, Objs, Acc);
 
1268
add_sel_ordered_match([{_, Val, delete_object}|Rest], [Val|Objs], Acc) ->
 
1269
    add_sel_ordered_match(Rest, Objs, Acc);
 
1270
add_sel_ordered_match([{_, _, delete_object}|Rest], Objs, Acc) ->
 
1271
    add_sel_ordered_match(Rest, Objs, Acc);
 
1272
add_sel_ordered_match([], Objs, Acc) ->
 
1273
    {lists:reverse(Acc, Objs),[]}.
 
1274
 
 
1275
 
 
1276
deloid(_Oid, []) ->
 
1277
    [];
 
1278
deloid({Tab, Key}, [H | T]) when element(2, H) == Key ->
 
1279
    deloid({Tab, Key}, T);
 
1280
deloid(Oid, [H | T]) ->
 
1281
    [H | deloid(Oid, T)].
983
1282
 
984
1283
%%%%%%%%%%%%%%%%%%
985
1284
% select 
1007
1306
    case element(1, Tid) of
1008
1307
        ets ->
1009
1308
            mnesia_lib:db_select(ram_copies, Tab, Spec);
1010
 
        tid ->    
 
1309
        tid ->
 
1310
            select_lock(Tid,Ts,LockKind,Spec,Tab),
1011
1311
            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,
 
1312
            Written = ?ets_match_object(Store, {{TabPat, '_'}, '_', '_'}),
1024
1313
            case Written of 
1025
1314
                [] ->  
1026
1315
                    %% Nothing changed in the table during this transaction,
1034
1323
                    TabRecs = SelectFun(FixedSpec),
1035
1324
                    FixedRes = add_match(Written, TabRecs, Type),
1036
1325
                    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
1326
                    ets:match_spec_run(FixedRes, CMS)
1044
1327
            end;
1045
1328
        _Protocol ->
1046
1329
            SelectFun(Spec)
1047
 
    end. 
1048
 
 
1049
 
get_record_pattern([]) ->
1050
 
    [];
 
1330
    end.
 
1331
 
 
1332
select_lock(Tid,Ts,LockKind,Spec,Tab) ->
 
1333
    %% Avoid table lock if possible
 
1334
    case Spec of
 
1335
        [{HeadPat,_, _}] when tuple(HeadPat), size(HeadPat) > 2 ->
 
1336
            Key = element(2, HeadPat),
 
1337
            case has_var(Key) of
 
1338
                false -> lock_record(Tid, Ts, Tab, Key, LockKind);
 
1339
                true  -> lock_table(Tid, Ts, Tab, LockKind)
 
1340
            end;
 
1341
        _ ->
 
1342
            lock_table(Tid, Ts, Tab, LockKind)
 
1343
    end.
 
1344
 
 
1345
%% Breakable Select
 
1346
select(Tab, Pat, NObjects, LockKind) 
 
1347
  when atom(Tab), Tab /= schema, list(Pat), number(NObjects) ->
 
1348
    case get(mnesia_activity_state) of
 
1349
        {?DEFAULT_ACCESS, Tid, Ts} ->
 
1350
            select(Tid, Ts, Tab, Pat, NObjects, LockKind);
 
1351
        {Mod, Tid, Ts} ->
 
1352
            Mod:select(Tid, Ts, Tab, Pat, NObjects, LockKind);
 
1353
        _ ->
 
1354
            abort(no_transaction)
 
1355
    end;
 
1356
select(Tab, Pat, NObjects, _Lock) ->
 
1357
    abort({badarg, Tab, Pat, NObjects}).
 
1358
 
 
1359
select(Tid, Ts, Tab, Spec, NObjects, LockKind) ->
 
1360
    Where = val({Tab,where_to_read}),
 
1361
    Type = mnesia_lib:storage_type_at_node(Where,Tab),
 
1362
    InitFun = fun(FixedSpec) -> dirty_sel_init(Where,Tab,FixedSpec,NObjects,Type) end,
 
1363
    fun_select(Tid,Ts,Tab,Spec,LockKind,Tab,InitFun,NObjects,Where,Type).
 
1364
 
 
1365
-record(mnesia_select, {tab,tid,node,storage,cont,written=[],spec,type,orig}).
 
1366
 
 
1367
fun_select(Tid, Ts, Tab, Spec, LockKind, TabPat, Init, NObjects, Node, Storage) ->
 
1368
    Def = #mnesia_select{tid=Tid,node=Node,storage=Storage,tab=Tab,orig=Spec},
 
1369
    case element(1, Tid) of
 
1370
        ets ->
 
1371
            select_state(mnesia_lib:db_select_init(ram_copies,Tab,Spec,NObjects),Def);
 
1372
        tid ->
 
1373
            select_lock(Tid,Ts,LockKind,Spec,Tab),
 
1374
            Store = Ts#tidstore.store,
 
1375
            do_fixtable(Tab, Store),
 
1376
            
 
1377
            Written0 = ?ets_match_object(Store, {{TabPat, '_'}, '_', '_'}),         
 
1378
            case Written0 of 
 
1379
                [] ->  
 
1380
                    %% Nothing changed in the table during this transaction,
 
1381
                    %% Simple case get results from [d]ets
 
1382
                    select_state(Init(Spec),Def);
 
1383
                _ ->   
 
1384
                    %% Hard (slow case) records added or deleted earlier 
 
1385
                    %% in the transaction, have to cope with that.
 
1386
                    Type = val({Tab, setorbag}),
 
1387
                    Written = 
 
1388
                        if Type == ordered_set -> %% Sort stable
 
1389
                                lists:keysort(1,Written0);
 
1390
                           true -> 
 
1391
                                Written0
 
1392
                        end,
 
1393
                    FixedSpec = get_record_pattern(Spec),
 
1394
                    CMS = ets:match_spec_compile(Spec),
 
1395
                    trans_select(Init(FixedSpec), 
 
1396
                                 Def#mnesia_select{written=Written,spec=CMS,type=Type})
 
1397
            end;
 
1398
        _Protocol ->
 
1399
            select_state(Init(Spec),Def)
 
1400
    end.
 
1401
 
 
1402
select(Cont) ->
 
1403
    case get(mnesia_activity_state) of
 
1404
        {?DEFAULT_ACCESS, Tid, Ts} ->
 
1405
            select_cont(Tid,Ts,Cont);
 
1406
        {Mod, Tid, Ts} ->
 
1407
            Mod:select_cont(Tid,Ts,Cont);
 
1408
        _ ->
 
1409
            abort(no_transaction)
 
1410
    end.
 
1411
 
 
1412
select_cont(_Tid,_Ts,'$end_of_table') ->
 
1413
    '$end_of_table';
 
1414
select_cont(Tid,_Ts,State=#mnesia_select{tid=Tid,cont=Cont, orig=Ms}) 
 
1415
  when element(1,Tid) == ets ->
 
1416
    case Cont of
 
1417
        '$end_of_table' -> '$end_of_table';
 
1418
        _ -> select_state(mnesia_lib:db_select_cont(ram_copies,Cont,Ms),State)
 
1419
    end;
 
1420
select_cont(Tid,_,State=#mnesia_select{tid=Tid,written=[]}) ->
 
1421
    select_state(dirty_sel_cont(State),State);
 
1422
select_cont(Tid,_Ts,State=#mnesia_select{tid=Tid})  ->
 
1423
    trans_select(dirty_sel_cont(State), State);
 
1424
select_cont(_Tid2,_,#mnesia_select{tid=_Tid1}) ->  % Missmatching tids
 
1425
    abort(wrong_transaction);
 
1426
select_cont(_,_,Cont) ->
 
1427
    abort({badarg, Cont}).
 
1428
 
 
1429
trans_select('$end_of_table', #mnesia_select{written=Written0,spec=CMS,type=Type}) ->
 
1430
    Written = add_match(Written0, [], Type),
 
1431
    {ets:match_spec_run(Written, CMS), '$end_of_table'};
 
1432
trans_select({TabRecs,Cont}, State = #mnesia_select{written=Written0,spec=CMS,type=Type}) ->
 
1433
    {FixedRes,Written} = add_sel_match(Written0, TabRecs, Type),
 
1434
    select_state({ets:match_spec_run(FixedRes, CMS),Cont},
 
1435
                 State#mnesia_select{written=Written}). 
 
1436
 
 
1437
select_state({Matches, Cont}, MS) ->
 
1438
    {Matches, MS#mnesia_select{cont=Cont}};
 
1439
select_state('$end_of_table',_) -> '$end_of_table'.
 
1440
 
 
1441
get_record_pattern([]) ->    [];
1051
1442
get_record_pattern([{M,C,_B}|R]) ->
1052
1443
    [{M,C,['$_']} | get_record_pattern(R)].
1053
1444
 
1054
 
deloid(_Oid, []) ->
1055
 
    [];
1056
 
deloid({Tab, Key}, [H | T]) when element(2, H) == Key ->
1057
 
    deloid({Tab, Key}, T);
1058
 
deloid(Oid, [H | T]) ->
1059
 
    [H | deloid(Oid, T)].
1060
 
 
1061
1445
all_keys(Tab) ->
1062
1446
    case get(mnesia_activity_state) of
1063
1447
        {?DEFAULT_ACCESS, Tid, Ts} ->
1132
1516
            Mod:index_read(Tid, Ts, Tab, Key, Attr, read);
1133
1517
        _ ->
1134
1518
            abort(no_transaction)
1135
 
    end.    
 
1519
    end.
1136
1520
 
1137
1521
index_read(Tid, Ts, Tab, Key, Attr, LockKind) 
1138
1522
  when atom(Tab), Tab /= schema ->
1336
1720
remote_dirty_select(Tab, Spec, _) ->
1337
1721
    mnesia_lib:db_select(Tab, Spec).
1338
1722
 
 
1723
dirty_sel_init(Node,Tab,Spec,NObjects,Type) ->
 
1724
    do_dirty_rpc(Tab,Node,mnesia_lib,db_select_init,[Type,Tab,Spec,NObjects]).
 
1725
 
 
1726
dirty_sel_cont(#mnesia_select{cont='$end_of_table'}) -> '$end_of_table';
 
1727
dirty_sel_cont(#mnesia_select{node=Node,tab=Tab,storage=Type,cont=Cont,orig=Ms}) ->
 
1728
    do_dirty_rpc(Tab,Node,mnesia_lib,db_select_cont,[Type,Cont,Ms]).
 
1729
 
1339
1730
dirty_all_keys(Tab) when atom(Tab), Tab /= schema ->
1340
1731
    case ?catch_val({Tab, wild_pattern}) of
1341
1732
        {'EXIT', _} ->
1425
1816
    mnesia:abort({no_exists, Args});
1426
1817
do_dirty_rpc(Tab, Node, M, F, Args) ->
1427
1818
    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
1819
        {badrpc, Reason} ->
1435
 
            erlang:yield(), %% Do not be too eager
 
1820
            timer:sleep(20), %% Do not be too eager, and can't use yield on SMP
1436
1821
            case mnesia_controller:call({check_w2r, Node, Tab}) of % Sync
1437
1822
                NewNode when NewNode == Node -> 
1438
1823
                    ErrorTag = mnesia_lib:dirty_rpc_error_tag(Reason),
1450
1835
                        _ ->
1451
1836
                            %% Splendid! A dirty retry is safe
1452
1837
                            %% 'Node' probably went down now
1453
 
                            %% Let mnesia_controller get broken link message first                          
 
1838
                            %% Let mnesia_controller get broken link message first
1454
1839
                            do_dirty_rpc(Tab, NewNode, M, F, Args)
1455
1840
                    end
1456
1841
            end;
1822
2207
system_info2(transaction_commits) -> mnesia_lib:read_counter(trans_commits);
1823
2208
system_info2(transaction_restarts) -> mnesia_lib:read_counter(trans_restarts);
1824
2209
system_info2(transaction_log_writes) -> mnesia_dumper:get_log_writes();
 
2210
system_info2(core_dir) ->  mnesia_monitor:get_env(core_dir); 
 
2211
system_info2(no_table_loaders) ->  mnesia_monitor:get_env(no_table_loaders); 
1825
2212
 
1826
2213
system_info2(Item) -> exit({badarg, Item}).
1827
2214
 
1863
2250
     transaction_restarts,
1864
2251
     transactions,
1865
2252
     use_dir,
 
2253
     core_dir,
 
2254
     no_table_loaders,
1866
2255
     version
1867
2256
    ];
1868
2257
system_info_items(no) ->
1888
2277
     schema_location,
1889
2278
     schema_version,
1890
2279
     use_dir,
 
2280
     core_dir,
1891
2281
     version
1892
2282
    ].
1893
2283
    
2180
2570
    mnesia_text:dump_to_textfile(F).
2181
2571
 
2182
2572
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
2573
%% QLC Handles
 
2574
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
2575
table(Tab) ->
 
2576
    table(Tab, []).
 
2577
table(Tab,Opts) ->
 
2578
    {[Trav,Lock,NObjects],QlcOptions0} = 
 
2579
        qlc_opts(Opts,[{traverse,select},{lock,read},{n_objects,100}]),
 
2580
    TF = case Trav of
 
2581
             {select,Ms} ->
 
2582
                 fun() -> qlc_select(select(Tab,Ms,NObjects,Lock)) end;
 
2583
             select ->
 
2584
                 fun(Ms) -> qlc_select(select(Tab,Ms,NObjects,Lock)) end;
 
2585
             _ ->
 
2586
                 erlang:fault({badarg, {Trav,[Tab, Opts]}})
 
2587
         end,
 
2588
    Pre  = fun(Arg) -> pre_qlc(Arg, Tab) end,
 
2589
    Post = fun()  -> post_qlc(Tab) end,
 
2590
    Info = fun(Tag) -> qlc_info(Tab, Tag) end,
 
2591
    ParentFun = fun() -> 
 
2592
                        {mnesia_activity, mnesia:get_activity_id()} 
 
2593
                end,
 
2594
    Lookup = 
 
2595
        case Trav of
 
2596
            {select, _} -> [];
 
2597
            _ ->
 
2598
                LFun = fun(2, Keys) ->
 
2599
                               Read = fun(Key) -> read(Tab,Key,Lock) end,
 
2600
                               lists:flatmap(Read, Keys);
 
2601
                          (Index,Keys) ->
 
2602
                               IdxRead = fun(Key) -> index_read(Tab,Key,Index) end,
 
2603
                               lists:flatmap(IdxRead, Keys)
 
2604
                       end,
 
2605
                [{lookup_fun, LFun}]
 
2606
        end,
 
2607
    MFA  = fun(Type) -> qlc_format(Type, Tab, NObjects, Lock, Opts) end,
 
2608
    QlcOptions = [{pre_fun, Pre}, {post_fun, Post}, 
 
2609
                  {info_fun, Info}, {parent_fun, ParentFun}, 
 
2610
                  {format_fun, MFA}|Lookup] ++ QlcOptions0,
 
2611
    qlc:table(TF, QlcOptions).
 
2612
 
 
2613
pre_qlc(Opts, Tab) ->
 
2614
    {_,Tid,_} = 
 
2615
        case get(mnesia_activity_state) of
 
2616
            undefined ->
 
2617
                case lists:keysearch(parent_value, 1, Opts) of
 
2618
                    {value, {parent_value,{mnesia_activity,undefined}}} ->
 
2619
                        abort(no_transaction);
 
2620
                    {value, {parent_value,{mnesia_activity,Aid}}} ->
 
2621
                        {value,{stop_fun,Stop}} = 
 
2622
                            lists:keysearch(stop_fun,1,Opts),
 
2623
                        put_activity_id(Aid,Stop),
 
2624
                        Aid;
 
2625
                    _ ->
 
2626
                        abort(no_transaction)
 
2627
                end;
 
2628
            Else -> 
 
2629
                Else
 
2630
        end,
 
2631
    case element(1,Tid) of
 
2632
        tid -> ok;
 
2633
        _ ->
 
2634
            case ?catch_val({Tab, setorbag}) of
 
2635
                ordered_set ->   ok;
 
2636
                _ -> 
 
2637
                    dirty_rpc(Tab, mnesia_tm, fixtable, [Tab,true,self()]),
 
2638
                    ok      
 
2639
            end
 
2640
    end.
 
2641
 
 
2642
post_qlc(Tab) ->
 
2643
    case catch get(mnesia_activity_state) of
 
2644
        {_,#tid{},_} -> ok;
 
2645
        _ ->
 
2646
            case ?catch_val({Tab, setorbag}) of
 
2647
                ordered_set ->
 
2648
                    ok;
 
2649
                _ ->
 
2650
                    dirty_rpc(Tab, mnesia_tm, fixtable, [Tab,false,self()]),
 
2651
                    ok
 
2652
            end
 
2653
    end.
 
2654
 
 
2655
qlc_select('$end_of_table') ->     [];
 
2656
qlc_select({Objects, Cont}) -> 
 
2657
    Objects ++ fun() -> qlc_select(select(Cont)) end.
 
2658
 
 
2659
qlc_opts(Opts, Keys) when is_list(Opts) ->
 
2660
    qlc_opts(Opts, Keys, []);
 
2661
qlc_opts(Option, Keys) ->
 
2662
    qlc_opts([Option], Keys, []).
 
2663
 
 
2664
qlc_opts(Opts, [{Key,Def}|Keys], Acc) ->
 
2665
    Opt = case lists:keysearch(Key,1, Opts) of
 
2666
              {value, {Key,Value}} ->
 
2667
                  Value;
 
2668
              false ->
 
2669
                  Def
 
2670
          end,
 
2671
    qlc_opts(lists:keydelete(Key,1,Opts),Keys,[Opt|Acc]);
 
2672
qlc_opts(Opts,[],Acc) -> {lists:reverse(Acc),Opts}.
 
2673
 
 
2674
qlc_info(Tab, num_of_objects) ->
 
2675
    dirty_rpc(Tab, ?MODULE, raw_table_info, [Tab, size]);
 
2676
qlc_info(_, keypos) ->    2;         
 
2677
qlc_info(_, is_unique_objects) ->    true;
 
2678
qlc_info(Tab, is_unique_keys) ->
 
2679
    case val({Tab, type}) of
 
2680
        set -> true;
 
2681
        ordered_set -> true;
 
2682
        _ -> false
 
2683
    end;
 
2684
qlc_info(Tab, is_sorted_objects) ->
 
2685
    case val({Tab, type}) of
 
2686
        ordered_set -> 
 
2687
            case ?catch_val({Tab, frag_hash}) of
 
2688
                {'EXIT', _} -> 
 
2689
                    ascending;
 
2690
                _ ->  %% Fragmented tables are not ordered
 
2691
                    no
 
2692
            end;
 
2693
        _ -> no
 
2694
    end;
 
2695
qlc_info(Tab, indices) ->
 
2696
    val({Tab,index});
 
2697
qlc_info(_Tab, _) ->
 
2698
    undefined.
 
2699
 
 
2700
qlc_format(all, Tab, NObjects, Lock, Opts) ->
 
2701
    {?MODULE, table, [Tab,[{n_objects, NObjects}, {lock,Lock}|Opts]]};
 
2702
qlc_format({match_spec, Ms}, Tab, NObjects, Lock, Opts) ->
 
2703
    {?MODULE, table, [Tab,[{traverse,{select,Ms}},{n_objects, NObjects}, {lock,Lock}|Opts]]};
 
2704
qlc_format({lookup, 2, Keys}, Tab, _, Lock, _) ->
 
2705
    io_lib:format("lists:flatmap(fun(V) -> "
 
2706
                  "~w:read(~w, V, ~w) end, ~w)", 
 
2707
                  [?MODULE, Tab, Lock, Keys]);
 
2708
qlc_format({lookup, Index,Keys}, Tab, _, _, _) ->
 
2709
    io_lib:format("lists:flatmap(fun(V) -> "
 
2710
                  "~w:index_read(~w, V, ~w) end, ~w)", 
 
2711
                  [?MODULE, Tab, Index, Keys]).
 
2712
 
 
2713
 
 
2714
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
2715
 
 
2716
do_fixtable(Tab, #tidstore{store=Store}) ->
 
2717
    do_fixtable(Tab,Store);
 
2718
do_fixtable(Tab, Store) ->
 
2719
    case ?catch_val({Tab, setorbag}) of
 
2720
        ordered_set ->
 
2721
            ok;
 
2722
        _ ->
 
2723
            case ?ets_match_object(Store, {fixtable, {Tab, '_'}}) of
 
2724
                [] -> 
 
2725
                    Node = dirty_rpc(Tab, mnesia_tm, fixtable, [Tab,true,self()]),
 
2726
                    ?ets_insert(Store, {fixtable, {Tab, Node}});
 
2727
                _ ->
 
2728
                    ignore
 
2729
            end,
 
2730
            ok
 
2731
    end.
 
2732
 
 
2733
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
2183
2734
%% Mnemosyne exclusive
2184
2735
 
2185
2736
get_activity_id() -> 
2187
2738
 
2188
2739
put_activity_id(Activity) -> 
2189
2740
    mnesia_tm:put_activity_id(Activity).
 
2741
put_activity_id(Activity,Fun) -> 
 
2742
    mnesia_tm:put_activity_id(Activity,Fun).