1/* -*- Mode: Prolog -*- */ 2 3:- module(index_util,[ 4 materialize_index/1, 5 materialize_index/2, 6 materialize_index_to_path/2, 7 materialize_indexes_to_path/2, 8 materialize_index_to_file/2, 9 materialize_index_to_file/3, 10 materialize_indexes_to_file/2, 11 materialize_indexes_to_file/3, 12 materialize_index_to_stream/2, 13 materialize_goal_to_file/2, 14 materialize_goals_to_file/2 15 ]). 16 17:- module_transparent materialize_index/1. 18:- module_transparent materialize_index/2. 19:- module_transparent materialize_index_to_file/2. 20:- module_transparent materialize_index_to_file/3. 21:- module_transparent materialize_indexes_to_file/2. 22:- module_transparent materialize_indexes_to_file/3. 23:- module_transparent materialize_index_to_path/2. 24:- module_transparent materialize_indexes_to_path/2. 25:- module_transparent materialize_index_to_stream/2. 26:- module_transparent load_factfile/1. 27 28:- dynamic is_indexed/2.
materialize_index(my_fact(1,0,1,1))
assumes that my_fact(?,?,?,?)
can be exhaustively enumerated.
37materialize_index(Mod:Term) :- 38 !, 39 materialize_index(Mod, Term). 40materialize_index(Term) :- 41 context_module(M), 42 !, 43 materialize_index(M, Term). 44materialize_index(M, Term) :- 45 index_util:is_indexed(M,Term), 46 debug(index, ' already indexed ~w:~w', [M, Term]), 47 !. 48materialize_index(M, Term) :- 49 debug(index, 'indexing ~w:~w', [M, Term]), 50 !, 51 Term =.. [Pred | Args], 52 length(Args, Arity), 53 functor(Goal, Pred, Arity), 54 debug(index, 'rewriting ~w', [Goal]), 55 setof(Goal, M:Goal, Facts), 56 M:abolish(Pred/Arity), 57 M:maplist(assert,Facts), 58 M:compile_predicates([Pred/Arity]), 59 assert(index_util:is_indexed(M,Term)), 60 debug(index, 'done indexing ~w:~w', [M, Term]). 61old__materialize_index(M, Term) :- 62 debug(index, 'indexing ~w:~w', [M, Term]), 63 !, 64 Term=..[CalledPred, _|IxArgsRest], 65 IxArgs=[1|IxArgsRest], % always index the first argument - this is the default index 66 length(IxArgs, Arity), 67 predicate_ixname(CalledPred, StoredPred, 1), 68 functor(CalledGoal, CalledPred, Arity), 69 CalledGoal=..[CalledPred|Args], 70 StoredGoal=..[StoredPred|Args], 71 debug(index, 'rewriting ~w', [CalledGoal]), 72 rewrite_goal_with_index_list(M, CalledGoal, 1, IxArgs), 73 DefaultGoal = ( CalledGoal :- StoredGoal ), 74 M:assert(DefaultGoal), 75 M:compile_predicates([CalledPred/Arity]), 76 assert(index_util:is_indexed(M,Term)), 77 debug(index, 'done indexing ~w:~w', [M, Term]). 78 79 80materialize_indexes_to_path(Terms,Dir) :- 81 forall(member(Term,Terms), 82 materialize_index_to_path(Term,Dir)). 83 84materialize_index_to_stream(M:Term,IO) :- 85 !, 86 materialize_index(M:Term), 87 functor(Term,Pred,Arity), 88 functor(Goal,Pred,Arity), 89 forall(M:Goal, 90 format(IO,'~q.~n',[M:Goal])). 91materialize_index_to_stream(Term,IO) :- 92 materialize_index(Term), 93 functor(Term,Pred,Arity), 94 functor(Goal,Pred,Arity), 95 forall(Goal, 96 format(IO,'~q.~n',[Goal])).
Dir is expanded using absolute_file_name/2
103materialize_index_to_path(Term,Dir) :- 104 Term=..[P|_], 105 atom_concat(P,'.pl',FileName), 106 absolute_file_name(Dir,DirAbs), 107 absolute_file_name(DirAbs/FileName,AbsFilePath), 108 materialize_indexes_to_file([Term],AbsFilePath). 109 110materialize_index_to_file(Term,File) :- 111 materialize_indexes_to_file([Term],File). 112 113materialize_index_to_file(Term,File,Opts) :- 114 materialize_indexes_to_file([Term],File,Opts).
if File does exist, consults File loading as extensional facts, and materializes in-memory index
note that this does not write the full index to file; just the main goal. When an index is re-used, the materialization step is still called. Thus there is only a benefit to using this when Terms contains intensional predicates.
132materialize_indexes_to_file(Terms,File) :- 133 materialize_indexes_to_file(Terms,File,[]). 134materialize_indexes_to_file(Terms,File,Opts) :- 135 select(force(true),Opts,Opts2), 136 exists_file(File), 137 !, 138 delete_file(File), 139 materialize_indexes_to_file(Terms,File,Opts2). 140materialize_indexes_to_file(Terms,File,_Opts) :- 141 exists_file(File), 142 !, 143 debug(index, 'using existing index file: ~w', [File]), 144 % clear existing intensional predicate 145 forall(member(Term,Terms), 146 ( functor(Term,Pred,Arity), 147 abolish(Pred/Arity))), 148 % load cached version: 149 load_factfile(File), 150 %load_files([File],[qcompile(auto)]), 151 debug(index, 'loaded: ~w', [File]), 152 forall(member(Term,Terms), 153 materialize_index(Term)). 154 155materialize_indexes_to_file(Terms,File,_Opts) :- 156 open(File,write,IO), 157 forall(member(Term,Terms), 158 materialize_index_to_stream(Term,IO)), 159 close(IO), 160 debug(index,'Compiling: ~w',[File]), 161 qcompile(File). 162 163 164load_factfile(PlFile) :- 165 file_name_extension(Base, _Ext, PlFile), 166 file_name_extension(Base, qlf, QlfFile), 167 debug(index,'checking for: ~w',[QlfFile]), 168 ( exists_file(QlfFile), 169 time_file(QlfFile, QlfTime), 170 time_file(PlFile, PlTime), 171 QlfTime >= PlTime 172 -> load_files([QlfFile]), 173 debug(index, 'Loaded from ~w',[QlfFile]) 174 ; access_file(QlfFile, write) 175 -> qcompile(PlFile) 176 ; debug(index,' cannot write to qlf, loading from: ~w',[PlFile]), 177 load_files(PlFile) 178 ).
185rewrite_goal_with_index_list(_, _, _, []). 186rewrite_goal_with_index_list(M, CalledGoal, Ix, [A|Args]) :- 187 rewrite_goal_with_index(M, CalledGoal, Ix, A), 188 Ix2 is Ix+1, 189 rewrite_goal_with_index_list(M, CalledGoal, Ix2, Args).
192rewrite_goal_with_index(M, CalledGoal, Ix, (+) ) :- 193 rewrite_goal_with_index(M, CalledGoal, Ix, 1). 194rewrite_goal_with_index(M, CalledGoal, Ix, 1) :- 195 debug(index, ' index ~w', [Ix]), 196 !, 197 CalledGoal=..[CalledPred|Args], 198 length(Args,Arity), 199 predicate_storedname(CalledPred, StoredPred, Ix), 200 reorder_args(Ix, IxVar, Args, ReorderedArgs), 201 StoredGoal=..[StoredPred|Args], 202 predicate_ixname(CalledPred, IxPred, Ix), 203 IxGoal=..[IxPred|ReorderedArgs], 204 debug(index, ' using ~w in ~w // ~w', [StoredPred/Arity,M,IxGoal]), 205 M:dynamic(IxPred/Arity), 206 setof(IxGoal,M:StoredGoal,IxFacts), 207 M:maplist(assert,IxFacts), 208 %forall(M:StoredGoal, 209 % assert_unique(M,IxGoal)), 210 M:compile_predicates([IxPred/Arity]), 211 ( Ix=1 212 -> M:abolish(CalledPred/Arity) 213 ; true), 214 RewrittenGoal = ( CalledGoal :- nonvar(IxVar), !, IxGoal), 215 M:assert(RewrittenGoal). 216rewrite_goal_with_index(_, _, _, _). % no index 217 218% DEPRECATED - too slow 219assert_unique(M,T) :- 220 ground(T), 221 M:T, 222 !. 223assert_unique(M,T) :- 224 M:assert(T).
227reorder_args(Ix, IxVar, Args1, Args2) :- 228 append(L1, [IxVar|L2], Args1), 229 length(L1, Len), 230 Len is Ix-1, 231 !, 232 append([IxVar|L1], L2, Args2). 233 234 235predicate_storedname(N, N, 1) :- !. % use original predicate as source for first index 236predicate_storedname(N1, N2, _) :- % use first index as source for subsequent indexes 237 !, 238 predicate_ixname(N1, N2, 1). 239 240predicate_ixname(N1, N2, Ix) :- 241 concat_atom([N1, '_ix__', Ix], N2).
245materialize_goal_to_file(G,F) :-
246 open(F,write,IO,[]),
247 forall(G,format(IO,'~q~n.',[G])),
248 close(IO).
252materialize_goals_to_file(Gs,F) :-
253 open(F,write,IO,[]),
254 forall(member(G,Gs),
255 forall(G,format(IO,'~q~n.',[G]))),
256 close(IO).
materializes indexes that exploit first-argument indexing
Synopsis
Details
This is designed to be a swap-in replacement for index/1. Indexing a fact with M arguments on N of those arguments will generate N sets of facts with arguments reordered to take advantage of first-argument indexing. The original fact will be rewritten.
For example, calling:
will retract all my_fact/3 facts and generate the following clauses in its place:
here my_factix_1 and my_factix_3 contain the same data as the original my_fact/3 clause. In the second case, the arguments have been reordered
Limitations
Single key indexing only. Could be extended for multikeys.
Reindexing is not a good idea. It could be smarter about this.
Should not be used on dynamic databases.
Does not have to be used with fact (unit clauses) - but the clauses should enumerable
*/