35
36:- module(prolog_autoload,
37 [ autoload/0,
38 autoload/1 39 ]). 40:- use_module(library(option)). 41:- use_module(library(error)). 42:- use_module(library(aggregate)). 43:- use_module(library(prolog_codewalk)). 44:- use_module(library(check), [ list_undefined/0 ]). 45
46:- predicate_options(autoload/1, 1,
47 [ verbose(boolean),
48 undefined(oneof([ignore,error]))
49 ]).
77:- thread_local
78 autoloaded_count/1.
92autoload :-
93 autoload([]).
94
95autoload(Options) :-
96 must_be(list, Options),
97 statistics(cputime, T0),
98 aggregate_all(count, source_file(_), OldFileCount),
99 call_cleanup(
100 autoload(0, Iterations, Options),
101 check:collect_undef(Undef)),
102 aggregate_all(count, source_file(_), NewFileCount),
103 statistics(cputime, T1),
104 Time is T1-T0,
105 information_level(Level, Options),
106 NewFiles is NewFileCount - OldFileCount,
107 print_message(Level, autoload(completed(Iterations, Time, NewFiles))),
108 report_undefined(Undef).
109
110autoload(Iteration0, Iterations, Options) :-
111 statistics(cputime, T0),
112 autoload_step(NewFiles, NewPreds, Options),
113 statistics(cputime, T1),
114 Time is T1-T0,
115 succ(Iteration0, Iteration),
116 ( NewFiles > 0
117 -> information_level(Level, Options),
118 print_message(Level, autoload(reiterate(Iteration,
119 NewFiles, NewPreds, Time))),
120 autoload(Iteration, Iterations, Options)
121 ; Iterations = Iteration
122 ).
123
124information_level(Level, Options) :-
125 ( option(verbose(true), Options)
126 -> Level = informational
127 ; Level = silent
128 ).
139autoload_step(NewFiles, NewPreds, Options) :-
140 option(verbose(Verbose), Options, false),
141 walk_options(Options, WalkOptions),
142 aggregate_all(count, source_file(_), OldFileCount),
143 setup_call_cleanup(
144 ( current_prolog_flag(autoload, OldAutoLoad),
145 current_prolog_flag(verbose_autoload, OldVerbose),
146 set_prolog_flag(autoload, true),
147 set_prolog_flag(verbose_autoload, Verbose),
148 assert_autoload_hook(Ref),
149 asserta(autoloaded_count(0))
150 ),
151 prolog_walk_code(WalkOptions),
152 ( retract(autoloaded_count(Count)),
153 erase(Ref),
154 set_prolog_flag(autoload, OldAutoLoad),
155 set_prolog_flag(verbose_autoload, OldVerbose)
156 )),
157 aggregate_all(count, source_file(_), NewFileCount),
158 NewPreds = Count,
159 NewFiles is NewFileCount - OldFileCount.
160
161assert_autoload_hook(Ref) :-
162 asserta((user:message_hook(autoload(Module:Name/Arity, Library), _, _) :-
163 autoloaded(Module:Name/Arity, Library)), Ref).
164
165:- public
166 autoloaded/2. 167
168autoloaded(_, _) :-
169 retract(autoloaded_count(N)),
170 succ(N, N2),
171 asserta(autoloaded_count(N2)),
172 fail.
181walk_options([], []).
182walk_options([verbose(V)|T0], [verbose(V)|T]) :-
183 !,
184 walk_options(T0, T).
185walk_options([undefined(error)|T0],
186 [ undefined(trace),
187 on_trace(check:found_undef)
188 | T
189 ]) :-
190 !,
191 walk_options(T0, T).
192walk_options([_|T0], T) :-
193 walk_options(T0, T).
200report_undefined([]) :-
201 !.
202report_undefined(Grouped) :-
203 existence_error(procedures, Grouped).
204
205
206 209
210:- multifile
211 prolog:message//1,
212 prolog:error_message//1. 213
214prolog:message(autoload(reiterate(Iteration, NewFiles, NewPreds, Time))) -->
215 [ 'Autoloader: iteration ~D resolved ~D predicates \c
216 and loaded ~D files in ~3f seconds. Restarting ...'-
217 [Iteration, NewPreds, NewFiles, Time]
218 ].
219prolog:message(autoload(completed(Iterations, Time, NewFiles))) -->
220 [ 'Autoloader: loaded ~D files in ~D iterations in ~3f seconds'-
221 [NewFiles, Iterations, Time] ].
222
223prolog:error_message(existence_error(procedures, Grouped)) -->
224 prolog:message(check(undefined_procedures, Grouped))
Autoload all dependencies
The autoloader is there to smoothen program development. It liberates the programmer from finding the library that defines some particular predicate and including the proper use_module/1,2 directive in the sources. This is even better at the toplevel, where just using maplist/3 is way more comfortable than first having to load
library(apply)
. In addition, it reduces the startup time of applications by only loading the necessary bits.Of course, there is also a price. One is that it becomes less obvious from where some predicate is loaded and thus whether you have the right definition. The second issue is that it is harder to create a stand-alone executable because this executable, without access to the development system, can no longer rely on autoloading. Finally, program analysis becomes harder because the program may be incomplete.
This library provides autoload/0 and autoload/1 to autoload all predicates that are referenced by the program. Now, this is not possible in Prolog because the language allows for constructing arbitrary goals and runtime and calling them (e.g.,
read(X)
,call(X)
).The implementation relies on code analysis of the bodies of all clauses and all initialization goals. */