File 0595-Fix-erroneous-aborts-when-using-index-plugins-ERL-55.patch of Package erlang

From fabd7fc883834982417219d4ace57e257e5f9892 Mon Sep 17 00:00:00 2001
From: Ulf Wiger <ulf@feuerlabs.com>
Date: Tue, 30 Jan 2018 08:10:05 +0100
Subject: [PATCH] Fix erroneous aborts when using index plugins (ERL-556)

- first stab at fixing index_[read|match_object] w plugins
- do not include index plugins at match ops
- add index_plugin_test_suite
- Increase ix plugin test coverage + bug fix
---
 lib/mnesia/src/mnesia.erl                    |  74 +++++++-
 lib/mnesia/src/mnesia_index.erl              |  44 +++--
 lib/mnesia/test/Makefile                     |   3 +-
 lib/mnesia/test/mnesia_SUITE.erl             |   3 +-
 lib/mnesia/test/mnesia_index_plugin_test.erl | 261 +++++++++++++++++++++++++++
 lib/mnesia/test/mt.erl                       |   1 +
 6 files changed, 360 insertions(+), 26 deletions(-)
 create mode 100644 lib/mnesia/test/mnesia_index_plugin_test.erl

diff --git a/lib/mnesia/src/mnesia.erl b/lib/mnesia/src/mnesia.erl
index 77afb8250c..02bc884e36 100644
--- a/lib/mnesia/src/mnesia.erl
+++ b/lib/mnesia/src/mnesia.erl
@@ -160,7 +160,7 @@
                     {'sync_transaction', Retries::non_neg_integer()}.
 -type table() :: atom().
 -type storage_type() :: 'ram_copies' | 'disc_copies' | 'disc_only_copies'.
--type index_attr() :: atom() | non_neg_integer().
+-type index_attr() :: atom() | non_neg_integer() | {atom()}.
 -type write_locks() :: 'write' | 'sticky_write'.
 -type read_locks() :: 'read'.
 -type lock_kind() :: write_locks() | read_locks().
@@ -1277,6 +1277,14 @@ match_object(Tid, Ts, Tab, Pat, LockKind)
 match_object(_Tid, _Ts, Tab, Pat, _LockKind) ->
     abort({bad_type, Tab, Pat}).
 
+add_written_index(Store, Pos, Tab, Key, Objs) when is_integer(Pos) ->
+    Pat = setelement(Pos, val({Tab, wild_pattern}), Key),
+    add_written_match(Store, Pat, Tab, Objs);
+add_written_index(Store, Pos, Tab, Key, Objs) when is_tuple(Pos) ->
+    IxF = mnesia_index:index_vals_f(val({Tab, storage_type}), Tab, Pos),
+    Ops = find_ops(Store, Tab, '_'),
+    add_ix_match(Ops, Objs, IxF, Key, val({Tab, setorbag})).
+
 add_written_match(S, Pat, Tab, Objs) ->
     Ops = find_ops(S, Tab, Pat),
     FixedRes = add_match(Ops, Objs, val({Tab, setorbag})),
@@ -1303,6 +1311,46 @@ add_match([{_Oid, Val, write}|R], Objs, bag) ->
 add_match([{Oid, Val, write}|R], Objs, set) ->
     add_match(R, [Val | deloid(Oid,Objs)],set).
 
+add_ix_match([], Objs, _IxF, _Key, _Type) ->
+    Objs;
+add_ix_match(Written, Objs, IxF, Key, ordered_set) ->
+    %% Must use keysort which is stable
+    add_ordered_match(lists:keysort(1, ix_filter_ops(IxF, Key, Written)), Objs, []);
+add_ix_match([{Oid, _, delete}|R], Objs, IxF, Key, Type) ->
+    add_ix_match(R, deloid(Oid, Objs), IxF, Key, Type);
+add_ix_match([{_Oid, Val, delete_object}|R], Objs, IxF, Key, Type) ->
+    case ix_match(Val, IxF, Key) of
+        true ->
+            add_ix_match(R, lists:delete(Val, Objs), IxF, Key, Type);
+        false ->
+            add_ix_match(R, Objs, IxF, Key, Type)
+    end;
+add_ix_match([{_Oid, Val, write}|R], Objs, IxF, Key, bag) ->
+    case ix_match(Val, IxF, Key) of
+        true ->
+            add_ix_match(R, [Val | lists:delete(Val, Objs)], IxF, Key, bag);
+        false ->
+            add_ix_match(R, Objs, IxF, Key, bag)
+    end;
+add_ix_match([{Oid, Val, write}|R], Objs, IxF, Key, set) ->
+    case ix_match(Val, IxF, Key) of
+        true ->
+            add_ix_match(R, [Val | deloid(Oid,Objs)],IxF,Key,set);
+        false ->
+            add_ix_match(R, Objs, IxF, Key, set)
+    end.
+
+ix_match(Val, IxF, Key) ->
+    lists:member(Key, IxF(Val)).
+
+ix_filter_ops(IxF, Key, Ops) ->
+    lists:filter(
+      fun({_Oid, Obj, write}) ->
+              ix_match(Obj, IxF, Key);
+         (_) ->
+              true
+      end, Ops).
+
 %% For ordered_set only !!
 add_ordered_match(Written = [{{_, Key}, _, _}|_], [Obj|Objs], Acc)
   when Key > element(2, Obj) ->
@@ -1641,6 +1689,16 @@ index_match_object(Tid, Ts, Tab, Pat, Attr, LockKind)
 	    dirty_index_match_object(Tab, Pat, Attr); % Should be optimized?
 	tid ->
 	    case mnesia_schema:attr_tab_to_pos(Tab, Attr) of
+                {_} ->
+                    case LockKind of
+                        read ->
+			    Store = Ts#tidstore.store,
+			    mnesia_locker:rlock_table(Tid, Store, Tab),
+			    Objs = dirty_match_object(Tab, Pat),
+			    add_written_match(Store, Pat, Tab, Objs);
+                        _ ->
+                            abort({bad_type, Tab, LockKind})
+                    end;
 		Pos when Pos =< tuple_size(Pat) ->
 		    case LockKind of
 			read ->
@@ -1688,8 +1746,8 @@ index_read(Tid, Ts, Tab, Key, Attr, LockKind)
 			false ->
 			    Store = Ts#tidstore.store,
 			    Objs = mnesia_index:read(Tid, Store, Tab, Key, Pos),
-			    Pat = setelement(Pos, val({Tab, wild_pattern}), Key),
-			    add_written_match(Store, Pat, Tab, Objs);
+                            add_written_index(
+                              Ts#tidstore.store, Pos, Tab, Key, Objs);
 			true ->
 			    abort({bad_type, Tab, Attr, Key})
 		    end;
@@ -1825,7 +1883,7 @@ remote_dirty_match_object(Tab, Pat) ->
 	false ->
 	    mnesia_lib:db_match_object(Tab, Pat);
 	true ->
-	    PosList = val({Tab, index}),
+            PosList = regular_indexes(Tab),
 	    remote_dirty_match_object(Tab, Pat, PosList)
     end.
 
@@ -1857,7 +1915,7 @@ remote_dirty_select(Tab, Spec) ->
 		false ->
 		    mnesia_lib:db_select(Tab, Spec);
 		true  ->
-		    PosList = val({Tab, index}),
+		    PosList = regular_indexes(Tab),
 		    remote_dirty_select(Tab, Spec, PosList)
 	    end;
 	_ ->
@@ -1924,6 +1982,8 @@ dirty_index_match_object(Pat, _Attr) ->
 dirty_index_match_object(Tab, Pat, Attr)
   when is_atom(Tab), Tab /= schema, is_tuple(Pat), tuple_size(Pat) > 2 ->
     case mnesia_schema:attr_tab_to_pos(Tab, Attr) of
+        {_} ->
+            dirty_match_object(Tab, Pat);
 	Pos when Pos =< tuple_size(Pat) ->
 	    case has_var(element(2, Pat)) of
 		false ->
@@ -3254,3 +3314,7 @@ put_activity_id(Activity) ->
     mnesia_tm:put_activity_id(Activity).
 put_activity_id(Activity,Fun) ->
     mnesia_tm:put_activity_id(Activity,Fun).
+
+regular_indexes(Tab) ->
+    PosList = val({Tab, index}),
+    [P || P <- PosList, is_integer(P)].
diff --git a/lib/mnesia/src/mnesia_index.erl b/lib/mnesia/src/mnesia_index.erl
index 098265d5fc..6f1c21e3b9 100644
--- a/lib/mnesia/src/mnesia_index.erl
+++ b/lib/mnesia/src/mnesia_index.erl
@@ -14,7 +14,7 @@
 %% WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied.
 %% See the License for the specific language governing permissions and
 %% limitations under the License.
-%% 
+%%
 %% %CopyrightEnd%
 %%
 
@@ -37,7 +37,7 @@
 	 db_match_erase/2,
 	 get_index_table/2,
 	 get_index_table/3,
-	 
+
 	 tab2filename/2,
 	 init_index/2,
 	 init_indecies/3,
@@ -45,6 +45,7 @@
 	 del_transient/3,
 	 del_index_table/3,
 
+         index_vals_f/3,
          index_info/2,
 	 ext_index_instances/1]).
 
@@ -60,9 +61,14 @@ read(Tid, Store, Tab, IxKey, Pos) ->
     ResList = mnesia_locker:ixrlock(Tid, Store, Tab, IxKey, Pos),
     %% Remove all tuples which don't include Ixkey, happens when Tab is a bag
     case val({Tab, setorbag}) of
-	bag -> 
+	bag when is_integer(Pos) ->
 	    mnesia_lib:key_search_all(IxKey, Pos, ResList);
-	_ -> 
+        bag when is_tuple(Pos) ->
+            TabStorage = val({Tab, storage_type}),
+            ValsF = index_vals_f(TabStorage, Tab, Pos),
+            [Obj || Obj <- ResList,
+                    lists:member(IxKey, ValsF(Obj))];
+	_ ->
 	    ResList
     end.
 
@@ -136,7 +142,7 @@ del_object_index2([], _, _Storage, _Tab, _K, _Obj) -> ok;
 del_object_index2([{{Pos, Type}, Ixt} | Tail], SoB, Storage, Tab, K, Obj) ->
     ValsF = index_vals_f(Storage, Tab, Pos),
     case SoB of
-	bag -> 
+	bag ->
 	    del_object_bag(Type, ValsF, Tab, K, Obj, Ixt);
 	_ -> %% If set remove the tuple in index table
 	    del_ixes(Type, Ixt, ValsF, Obj, K)
@@ -197,7 +203,7 @@ merge([], _, _, Ack) ->
 realkeys(Tab, Pos, IxKey) ->
     Index = get_index_table(Tab, Pos),
     db_get(Index, IxKey). % a list on the form [{IxKey, RealKey1} , ....
-    
+
 dirty_select(Tab, Spec, Pos) when is_integer(Pos) ->
     %% Assume that we are on the node where the replica is
     %% Returns the records without applying the match spec
@@ -233,7 +239,7 @@ dirty_read2(Tab, IxKey, Pos) ->
 		  end, Acc, mnesia_lib:db_get(Storage, Tab, K))
 	end, [], Keys)).
 
-pick_index([{{{Pfx,_},IxType}, Ixt}|_], _Tab, {_} = Pfx) ->
+pick_index([{{{Pfx,_,_},IxType}, Ixt}|_], _Tab, {_} = Pfx) ->
     {IxType, Ixt};
 pick_index([{{Pos,IxType}, Ixt}|_], _Tab, Pos) ->
     {IxType, Ixt};
@@ -242,7 +248,7 @@ pick_index([_|T], Tab, Pos) ->
 pick_index([], Tab, Pos) ->
     mnesia:abort({no_exist, Tab, {index, Pos}}).
 
-	    
+
 
 %%%%%%% Creation, Init and deletion routines for index tables
 %% We can have several indexes on the same table
@@ -387,12 +393,12 @@ init_ext_index(Tab, Storage, Alias, Mod, [{Pos,Type} | Tail]) ->
 create_fun(Cont, Tab, Pos) ->
     IxF = index_vals_f(disc_only_copies, Tab, Pos),
     fun(read) ->
-	    Data = 
+	    Data =
 		case Cont of
 		    {start, KeysPerChunk} ->
 			mnesia_lib:db_init_chunk(
 			  disc_only_copies, Tab, KeysPerChunk);
-		    '$end_of_table' -> 
+		    '$end_of_table' ->
 			'$end_of_table';
 		    _Else ->
 			mnesia_lib:db_chunk(disc_only_copies, Cont)
@@ -462,7 +468,7 @@ add_index_info(Tab, SetOrBag, IxElem) ->
 	    %% Check later if mnesia_tm is sensitive about the order
 	    mnesia_lib:set({Tab, index_info}, IndexInfo),
 	    mnesia_lib:set({Tab, index}, index_positions(IndexInfo)),
-	    mnesia_lib:set({Tab, commit_work}, 
+	    mnesia_lib:set({Tab, commit_work},
 			   mnesia_lib:sort_commit([IndexInfo | Commit]));
 	{value, Old} ->
 	    %% We could check for consistency here
@@ -470,7 +476,7 @@ add_index_info(Tab, SetOrBag, IxElem) ->
 	    mnesia_lib:set({Tab, index_info}, Index),
 	    mnesia_lib:set({Tab, index}, index_positions(Index)),
 	    NewC = lists:keyreplace(index, 1, Commit, Index),
-	    mnesia_lib:set({Tab, commit_work}, 
+	    mnesia_lib:set({Tab, commit_work},
 			   mnesia_lib:sort_commit(NewC))
     end.
 
@@ -488,19 +494,19 @@ del_index_info(Tab, Pos) ->
                                       element(1,P)=/=Pos
                               end,
                               Old#index.pos_list) of
-		[] -> 
+		[] ->
                     IndexInfo = index_info(Old#index.setorbag,[]),
 		    mnesia_lib:set({Tab, index_info}, IndexInfo),
 		    mnesia_lib:set({Tab, index}, index_positions(IndexInfo)),
 		    NewC = lists:keydelete(index, 1, Commit),
-		    mnesia_lib:set({Tab, commit_work}, 
+		    mnesia_lib:set({Tab, commit_work},
 				   mnesia_lib:sort_commit(NewC));
 		New ->
 		    Index = Old#index{pos_list = New},
 		    mnesia_lib:set({Tab, index_info}, Index),
 		    mnesia_lib:set({Tab, index}, index_positions(Index)),
 		    NewC = lists:keyreplace(index, 1, Commit, Index),
-		    mnesia_lib:set({Tab, commit_work}, 
+		    mnesia_lib:set({Tab, commit_work},
 				   mnesia_lib:sort_commit(NewC))
 	    end
     end.
@@ -537,7 +543,7 @@ db_match_erase({{ext,_,_} = Ext, Ixt}, Pat) ->
     mnesia_lib:db_match_erase(Ext, Ixt, Pat);
 db_match_erase({dets, Ixt}, Pat) ->
     ok = dets:match_delete(Ixt, Pat).
-    
+
 db_select({ram, Ixt}, Pat) ->
     ets:select(Ixt, Pat);
 db_select({{ext,_,_} = Ext, Ixt}, Pat) ->
@@ -545,7 +551,7 @@ db_select({{ext,_,_} = Ext, Ixt}, Pat) ->
 db_select({dets, Ixt}, Pat) ->
     dets:select(Ixt, Pat).
 
-    
+
 get_index_table(Tab, Pos) ->
     get_index_table(Tab,  val({Tab, storage_type}), Pos).
 
diff --git a/lib/mnesia/test/Makefile b/lib/mnesia/test/Makefile
index 5b61b1af65..b43bc82801 100644
--- a/lib/mnesia/test/Makefile
+++ b/lib/mnesia/test/Makefile
@@ -53,7 +53,8 @@ MODULES= \
 	mnesia_measure_test \
 	mnesia_cost \
 	mnesia_dbn_meters \
-	ext_test
+	ext_test \
+	mnesia_index_plugin_test
 
 DocExamplesDir := ../doc/src/
 
diff --git a/lib/mnesia/test/mnesia_SUITE.erl b/lib/mnesia/test/mnesia_SUITE.erl
index 24c1def6da..b41bf22efa 100644
--- a/lib/mnesia/test/mnesia_SUITE.erl
+++ b/lib/mnesia/test/mnesia_SUITE.erl
@@ -69,12 +69,13 @@ groups() ->
     %% covered.
     [{light, [],
       [{group, install}, {group, nice}, {group, evil},
-       {group, mnesia_frag_test, light}, {group, qlc},
+       {group, mnesia_frag_test, light}, {group, qlc}, {group, index_plugins},
        {group, registry}, {group, config}, {group, examples}]},
      {install, [], [{mnesia_install_test, all}]},
      {nice, [], [{mnesia_nice_coverage_test, all}]},
      {evil, [], [{mnesia_evil_coverage_test, all}]},
      {qlc, [], [{mnesia_qlc_test, all}]},
+     {index_plugins, [], [{mnesia_index_plugin_test, all}]},
      {registry, [], [{mnesia_registry_test, all}]},
      {config, [], [{mnesia_config_test, all}]},
      {examples, [], [{mnesia_examples_test, all}]},
diff --git a/lib/mnesia/test/mnesia_index_plugin_test.erl b/lib/mnesia/test/mnesia_index_plugin_test.erl
new file mode 100644
index 0000000000..44fe047c50
--- /dev/null
+++ b/lib/mnesia/test/mnesia_index_plugin_test.erl
@@ -0,0 +1,261 @@
+%%
+%% %CopyrightBegin%
+%%
+%% Copyright Ericsson AB 1996-2018. All Rights Reserved.
+%%
+%% Licensed under the Apache License, Version 2.0 (the "License");
+%% you may not use this file except in compliance with the License.
+%% You may obtain a copy of the License at
+%%
+%%     http://www.apache.org/licenses/LICENSE-2.0
+%%
+%% Unless required by applicable law or agreed to in writing, software
+%% distributed under the License is distributed on an "AS IS" BASIS,
+%% WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied.
+%% See the License for the specific language governing permissions and
+%% limitations under the License.
+%%
+%% %CopyrightEnd%
+%%
+
+%%
+-module(mnesia_index_plugin_test).
+-author('ulf@wiger.net').
+
+-export([init_per_testcase/2, end_per_testcase/2,
+         init_per_group/2, end_per_group/2,
+         init_per_suite/1, end_per_suite/1,
+         all/0, groups/0]).
+
+-export([
+         add_rm_plugin/1,
+         tab_with_plugin_index/1,
+         tab_with_multiple_plugin_indexes/1,
+         ix_match_w_plugin/1,
+         ix_match_w_plugin_ordered/1,
+         ix_match_w_plugin_bag/1
+        ]).
+
+-export([ix_prefixes/3,    % test plugin
+         ix_prefixes2/3]). % test plugin 2
+
+-include("mnesia_test_lib.hrl").
+
+init_per_suite(Conf) ->
+    Conf.
+
+end_per_suite(Conf) ->
+    Conf.
+
+init_per_testcase(Func, Conf) ->
+    mnesia_test_lib:init_per_testcase(Func, Conf).
+
+end_per_testcase(Func, Conf) ->
+    mnesia_test_lib:end_per_testcase(Func, Conf).
+
+all() ->
+    [add_rm_plugin,
+     tab_with_plugin_index,
+     tab_with_multiple_plugin_indexes,
+     ix_match_w_plugin,
+     ix_match_w_plugin_ordered,
+     ix_match_w_plugin_bag].
+
+groups() ->
+    [].
+
+init_per_group(_GroupName, Config) ->
+    Config.
+
+end_per_group(_GroupName, Config) ->
+    Config.
+
+
+add_rm_plugin(suite) -> [];
+add_rm_plugin(Config) when is_list(Config) ->
+    [N1, N2] = Nodes = ?acquire_nodes(2, Config),
+    ok = add_plugin(),
+    ok = rpc_check_plugin(N1),
+    ok = rpc_check_plugin(N2),
+    ok = add_plugin2(),
+    ok = del_plugin(),
+    ok = del_plugin2(),
+    ok = add_plugin(),
+    ok = add_plugin2(),
+    ok = del_plugin(),
+    ok = del_plugin2(),
+    ?verify_mnesia(Nodes, []).
+
+-define(PLUGIN1, {{pfx},?MODULE,ix_prefixes}).
+-define(PLUGIN2, {{pfx2},?MODULE,ix_prefixes2}).
+
+add_plugin() ->
+    {atomic, ok} = mnesia_schema:add_index_plugin({pfx}, ?MODULE, ix_prefixes),
+    [?PLUGIN1] = mnesia_schema:index_plugins(),
+    ok.
+
+add_plugin2() ->
+    {atomic, ok} = mnesia_schema:add_index_plugin({pfx2}, ?MODULE, ix_prefixes2),
+    [?PLUGIN1, ?PLUGIN2] = lists:sort(mnesia_schema:index_plugins()),
+    ok.
+
+del_plugin() ->
+    {atomic, ok} = mnesia_schema:delete_index_plugin({pfx}),
+    [?PLUGIN2] = mnesia_schema:index_plugins(),
+    ok.
+
+del_plugin2() ->
+    {atomic, ok} = mnesia_schema:delete_index_plugin({pfx2}),
+    [] = mnesia_schema:index_plugins(),
+    ok.
+
+rpc_check_plugin(N) ->
+    [?PLUGIN1] =
+        rpc:call(N, mnesia_schema, index_plugins, []),
+    ok.
+
+tab_with_plugin_index(suite) -> [];
+tab_with_plugin_index(Config) when is_list(Config) ->
+    [_N1] = Nodes = ?acquire_nodes(1, Config),
+    ok = add_plugin(),
+    {atomic, ok} = mnesia:create_table(t, [{attributes, [k,v1,v2]},
+                                           {index, [{{pfx}, ordered},
+                                                    {v1, ordered},
+                                                    v2]}]),
+    [ok,ok,ok,ok] =
+        [mnesia:dirty_write({t, K, V1, V2})
+         || {K,V1,V2} <- [{1,a,"123"},
+                          {2,b,"12345"},
+                          {3,c,"6789"},
+                          {4,d,nil}]],
+    [{t,1,a,"123"},{t,2,b,"12345"}] =
+        mnesia:dirty_index_read(t,<<"123">>,{pfx}),
+    [{t,3,c,"6789"}] =
+        mnesia:dirty_index_read(t,"6789",v2),
+    [{t,1,a,"123"}] =
+        mnesia:dirty_match_object({t,'_',a,"123"}),
+    [{t,1,a,"123"}] =
+        mnesia:dirty_select(t, [{ {t,'_',a,"123"}, [], ['$_']}]),
+    mnesia:dirty_delete(t,2),
+    [{t,1,a,"123"}] =
+        mnesia:dirty_index_read(t,<<"123">>,{pfx}),
+    ?verify_mnesia(Nodes, []).
+
+tab_with_multiple_plugin_indexes(suite) -> [];
+tab_with_multiple_plugin_indexes(Config) when is_list(Config) ->
+    [_N1] = Nodes = ?acquire_nodes(1, Config),
+    ok = add_plugin(),
+    ok = add_plugin2(),
+    {atomic, ok} =
+        mnesia:create_table(u, [{attributes, [k,v1,v2]},
+                                {index, [{{pfx}, ordered},
+                                         {{pfx2}, ordered}]}]),
+        [ok,ok,ok,ok] =
+        [mnesia:dirty_write({u, K, V1, V2})
+         || {K,V1,V2} <- [{1,a,"123"},
+                          {2,b,"12345"},
+                          {3,c,"6789"},
+                          {4,d,nil}]],
+    [{u,1,a,"123"},{u,2,b,"12345"}] =
+        mnesia:dirty_index_read(u,<<"123">>,{pfx}),
+    [{u,1,a,"123"},{u,2,b,"12345"}] =
+        mnesia:dirty_index_read(u,<<"321">>,{pfx2}),
+    ?verify_mnesia(Nodes, []).
+
+ix_match_w_plugin(suite) -> [];
+ix_match_w_plugin(Config) when is_list(Config) ->
+    [_N1] = Nodes = ?acquire_nodes(1, Config),
+    ok = add_plugin(),
+    {atomic, ok} = mnesia:create_table(im1, [{attributes, [k, v1, v2]},
+                                             {index, [{{pfx}, ordered},
+                                                      {v1, ordered}]}]),
+    fill_and_test_index_match(im1, set),
+    ?verify_mnesia(Nodes, []).
+
+
+ix_match_w_plugin_ordered(suite) -> [];
+ix_match_w_plugin_ordered(Config) when is_list(Config) ->
+    [_N1] = Nodes = ?acquire_nodes(1, Config),
+    ok = add_plugin(),
+    {atomic, ok} = mnesia:create_table(im2, [{attributes, [k, v1, v2]},
+                                             {type, ordered_set},
+                                             {index, [{{pfx}, ordered},
+                                                      {v1, ordered}]}]),
+    fill_and_test_index_match(im2, ordered_set),
+    ?verify_mnesia(Nodes, []).
+
+ix_match_w_plugin_bag(suite) -> [];
+ix_match_w_plugin_bag(Config) when is_list(Config) ->
+    [_N1] = Nodes = ?acquire_nodes(1, Config),
+    ok = add_plugin(),
+    {atomic, ok} = mnesia:create_table(im3, [{attributes, [k, v1, v2]},
+                                             {type, bag},
+                                             {index, [{{pfx}, ordered},
+                                                      {v1, ordered}]}]),
+    fill_and_test_index_match(im3, bag),
+    ?verify_mnesia(Nodes, []).
+
+fill_and_test_index_match(Tab, Type) ->
+    [ok,ok,ok,ok,ok,ok,ok,ok,ok] =
+        [mnesia:dirty_write({Tab, K, V1, V2})
+         || {K,V1,V2} <- [{1,a,"123"},
+                          {2,b,"12345"},
+                          {3,c,"123"},
+                          {4,d,nil},
+                          {5,e,nil},
+                          {6,f,nil},
+                          {7,g,nil},  %% overwritten if not bag
+                          {7,g,"234"},
+                          {8,h,"123"}]],
+    mnesia:activity(
+      transaction,
+      fun() ->
+              ok = mnesia:write({Tab, 1, aa, "1234"}), %% replaces if not bag
+              ok = mnesia:delete({Tab, 2}),
+              ok = mnesia:delete({Tab, 4}),
+              ok = mnesia:write({Tab, 6, ff, nil}),
+              ok = mnesia:write({Tab, 7, gg, "123"}),
+              ok = mnesia:write({Tab, 100, x, nil}),
+              ok = mnesia:delete_object({Tab,3,c,"123"}),
+              ok = mnesia:delete_object({Tab,5,e,nil}),
+              Res = mnesia:index_read(Tab, <<"123">>, {pfx}),
+              SetRes = [{Tab,1,aa,"1234"}, {Tab,7,gg,"123"}, {Tab,8,h,"123"}],
+              case Type of
+                  set ->
+                      SetRes = lists:sort(Res);
+                  ordered_set ->
+                      SetRes = Res;
+                  bag ->
+                      [{Tab,1,a,"123"}, {Tab,1,aa,"1234"},
+                       {Tab,7,gg,"123"}, {Tab,8,h,"123"}] = lists:sort(Res)
+              end
+      end).
+
+%% ============================================================
+%%
+ix_prefixes(_Tab, _Pos, Obj) ->
+    lists:foldl(
+      fun(V, Acc) when is_list(V) ->
+              try Pfxs = prefixes(list_to_binary(V)),
+                   Pfxs ++ Acc
+              catch
+                  error:_ ->
+                      Acc
+              end;
+         (V, Acc) when is_binary(V) ->
+              Pfxs = prefixes(V),
+              Pfxs ++ Acc;
+         (_, Acc) ->
+              Acc
+      end, [], tl(tuple_to_list(Obj))).
+
+ix_prefixes2(Tab, Pos, Obj) ->
+    [rev(P) || P <- ix_prefixes(Tab, Pos, Obj)].
+
+rev(B) when is_binary(B) ->
+    list_to_binary(lists:reverse(binary_to_list(B))).
+
+prefixes(<<P:3/binary, _/binary>>) ->
+    [P];
+prefixes(_) ->
+    [].
diff --git a/lib/mnesia/test/mt.erl b/lib/mnesia/test/mt.erl
index 5a981bf539..037d6adb38 100644
--- a/lib/mnesia/test/mt.erl
+++ b/lib/mnesia/test/mt.erl
@@ -67,6 +67,7 @@ alias(recovery) -> mnesia_recovery_test;
 alias(registry) -> mnesia_registry_test;
 alias(suite) -> mnesia_SUITE;
 alias(trans) -> mnesia_trans_access_test;
+alias(ixp) -> mnesia_index_plugin_test;
 alias(Other) -> Other.
 
 %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
-- 
2.16.4

openSUSE Build Service is sponsored by