36
37:- module(prolog_deps,
38 [ file_autoload_directives/3, 39 file_auto_import/2 40 ]). 41:- use_module(library(apply), [convlist/3, maplist/3, exclude/3]). 42:- use_module(library(filesex), [copy_file/2]). 43:- use_module(library(lists), [select/3, append/3, member/2]). 44:- use_module(library(option), [option/2, option/3]). 45:- use_module(library(pairs), [group_pairs_by_key/2]). 46:- use_module(library(pprint), [print_term/2]). 47:- use_module(library(prolog_code), [pi_head/2]). 48:- use_module(library(prolog_source),
49 [ file_name_on_path/2,
50 path_segments_atom/2,
51 prolog_open_source/2,
52 prolog_read_source_term/4,
53 prolog_close_source/1
54 ]). 55:- use_module(library(prolog_xref),
56 [ xref_source/1,
57 xref_module/2,
58 xref_called/4,
59 xref_defined/3,
60 xref_built_in/1
61 ]). 62:- use_module(library(readutil), [read_file_to_string/3]). 63:- use_module(library(solution_sequences), [distinct/2]). 64
70
71:- multifile user:file_search_path/2. 72
73user:file_search_path(noautoload, library(.)).
74user:file_search_path(noautoload, library(semweb)).
75user:file_search_path(noautoload, library(lynx)).
76user:file_search_path(noautoload, library(tipc)).
77user:file_search_path(noautoload, library(cql)).
78user:file_search_path(noautoload, library(http)).
79user:file_search_path(noautoload, library(dcg)).
80user:file_search_path(noautoload, library(unicode)).
81user:file_search_path(noautoload, library(clp)).
82user:file_search_path(noautoload, library(pce(prolog/lib))).
83
84
117
118file_autoload_directives(File, Directives, Options) :-
119 xref_source(File),
120 findall(Head, distinct(Head, undefined(File, Head, Options)), Missing0),
121 clean_missing(Missing0, Missing),
122 option(update(Old), Options, []),
123 convlist(missing_autoload(File, Old), Missing, Pairs),
124 keysort(Pairs, Pairs1),
125 group_pairs_by_key(Pairs1, Grouped),
126 directives(File, Grouped, Directives, Options).
127
133
134undefined(File, Undef, Options) :-
135 xref_module(File, _),
136 !,
137 xref_called_cond(File, Undef, Cond),
138 \+ ( available(File, Undef, How, Options),
139 How \== plain_file
140 ),
141 included_if_defined(Cond, Undef),
142 Undef \= (_:_).
143undefined(File, Undef, Options) :-
144 xref_called_cond(File, Undef, Cond),
145 \+ available(File, Undef, _, Options),
146 included_if_defined(Cond, Undef),
147 Undef \= (_:_).
148
150
151included_if_defined(true, _) :- !.
152included_if_defined(false, _) :- !, fail.
153included_if_defined(fail, _) :- !, fail.
154included_if_defined(current_predicate(Name/Arity), Callable) :-
155 \+ functor(Callable, Name, Arity),
156 !.
157included_if_defined(\+ Cond, Callable) :-
158 !,
159 \+ included_if_defined(Cond, Callable).
160included_if_defined((A,B), Callable) :-
161 !,
162 included_if_defined(A, Callable),
163 included_if_defined(B, Callable).
164included_if_defined((A;B), Callable) :-
165 !,
166 ( included_if_defined(A, Callable)
167 ; included_if_defined(B, Callable)
168 ).
169
170xref_called_cond(Source, Callable, Cond) :-
171 xref_called(Source, Callable, By, Cond),
172 By \= Callable. 173
177
178available(File, Called, How, Options) :-
179 xref_defined(File, Called, How0),
180 ( How0 = imported(_)
181 -> option(missing(true), Options)
182 ; true
183 ),
184 !,
185 How = How0.
186available(_, Called, How, _) :-
187 built_in_predicate(Called),
188 !,
189 How = builtin.
190available(_, Called, How, _) :-
191 Called = _:_,
192 defined(_, Called),
193 !,
194 How = module_qualified.
195available(_, M:G, How, _) :-
196 defined(ExportFile, G),
197 xref_module(ExportFile, M),
198 !,
199 How = module_overruled.
200available(_, Called, How, _) :-
201 defined(ExportFile, Called),
202 \+ xref_module(ExportFile, _),
203 !,
204 How == plain_file.
205
209
210built_in_predicate(Goal) :-
211 strip_module(Goal, _, Plain),
212 xref_built_in(Plain).
213
217
218defined(File, Callable) :-
219 xref_defined(File, Callable, How),
220 How \= imported(_).
221
227
228clean_missing(Missing0, Missing) :-
229 memberchk(main, Missing0),
230 memberchk(argv_options(_,_,_), Missing0),
231 !,
232 exclude(argv_option_hook, Missing0, Missing).
233clean_missing(Missing, Missing).
234
235argv_option_hook(opt_type(_,_,_)).
236argv_option_hook(opt_help(_,_)).
237argv_option_hook(opt_meta(_,_)).
238
239
240 243
244missing_autoload(Src, _, Head, From-Head) :-
245 xref_defined(Src, Head, imported(From)),
246 !.
247missing_autoload(Src, Directives, Head, File-Head) :-
248 src_file(Src, SrcFile),
249 member(:-(Dir), Directives),
250 directive_file(Dir, FileSpec),
251 absolute_file_name(FileSpec, File,
252 [ file_type(prolog),
253 file_errors(fail),
254 relative_to(SrcFile),
255 access(read)
256 ]),
257 exports(File, Exports),
258 member(PI, Exports),
259 is_pi(PI),
260 pi_head(PI, Head),
261 !.
262missing_autoload(_Src, _, Head, File-Head) :-
263 predicate_property(Head, autoload(File0)),
264 !,
265 ( absolute_file_name(File0, File,
266 [ access(read),
267 file_type(prolog),
268 file_errors(fail)
269 ])
270 -> true
271 ; File = File0
272 ).
273missing_autoload(_Src, _, Head, File-Head) :-
274 noautoload(Head, File),
275 !.
276missing_autoload(_Src, _, Head, _) :-
277 pi_head(PI, Head),
278 print_message(warning,
279 error(existence_error(procedure, PI), _)),
280 fail.
281
282:- if(exists_source(library(pce))). 283:- autoload(library(pce), [get/3]). 284src_file(@(Ref), File) =>
285 get(?(@(Ref), file), absolute_path, File).
286:- endif. 287src_file(File0, File) =>
288 File = File0.
289
293
294directives(File, FileAndHeads, Directives, Options) :-
295 option(update(Old), Options, []),
296 phrase(update_directives(Old, FileAndHeads, RestDeps, File),
297 Directives, Rest),
298 update_style(Old, Options, Options1),
299 maplist(directive(Options1), RestDeps, Rest0),
300 sort(Rest0, Rest).
301
302update_directives([], Deps, Deps, _) -->
303 [].
304update_directives([:-(H)|T], Deps0, Deps, File) -->
305 { update_directive(File, H, Deps0, Deps1, Directive) },
306 !,
307 [ :-(Directive) ],
308 update_directives(T, Deps1, Deps, File).
309update_directives([H|T], Deps0, Deps, File) -->
310 [ H ],
311 update_directives(T, Deps0, Deps, File).
312
313update_directive(Src, Dir0, Deps0, Deps, Dir) :-
314 src_file(Src, SrcFile),
315 directive_file(Dir0, FileSpec),
316 absolute_file_name(FileSpec, File,
317 [ file_type(prolog),
318 file_errors(fail),
319 relative_to(SrcFile),
320 access(read)
321 ]),
322 select(DepFile-Heads, Deps0, Deps),
323 same_dep_file(DepFile, File),
324 !,
325 ( Dir0 =.. [Pred,File0,Imports]
326 -> exports(File, Exports),
327 maplist(head_pi(Exports), Heads, PIs),
328 subtract_pis(PIs, Imports, New),
329 append(Imports, New, NewImports),
330 Dir =.. [Pred,File0,NewImports]
331 ; Dir = Dir0
332 ).
333
334directive_file(use_module(File), File).
335directive_file(use_module(File,_), File).
336directive_file(autoload(File), File).
337directive_file(autoload(File,_), File).
338
339same_dep_file(File, File) :-
340 !.
341same_dep_file(Dep, _File) :-
342 exists_file(Dep),
343 !,
344 fail.
345same_dep_file(Dep, File) :-
346 user:prolog_file_type(Ext, prolog),
347 file_name_extension(Dep, Ext, DepFile),
348 same_file(DepFile, File),
349 !.
350
351exports(File, Public) :-
352 E = error(_,_),
353 catch('$autoload':exports(File, _Module, Public), E,
354 ( print_message(warning, E),
355 Public = []
356 )).
357
358is_pi(Name/Arity), atom(Name), integer(Arity) => true.
359is_pi(Name//Arity), atom(Name), integer(Arity) => true.
360is_pi(_) => fail.
361
363
364head_pi(PIs, Head, PI) :-
365 head_pi(Head, PI),
366 memberchk(PI, PIs),
367 !.
368head_pi(_PIs, Head, PI) :-
369 pi_head(PI, Head).
370
371head_pi(Head, PI) :-
372 pi_head(PI0, Head),
373 ( PI = PI0
374 ; dcg_pi(PI0, PI)
375 ).
376
377dcg_pi(Module:Name/Arity, PI), integer(Arity), Arity >= 2 =>
378 DCGArity is Arity - 2,
379 PI = Module:Name//DCGArity.
380dcg_pi(Name/Arity, PI), integer(Arity), Arity >= 2 =>
381 DCGArity is Arity - 2,
382 PI = Name//DCGArity.
383dcg_pi(_/Arity, _), integer(Arity) =>
384 fail.
385
387
388subtract_pis([], _, R) =>
389 R = [].
390subtract_pis([H|T], D, R) =>
391 ( member(E, D),
392 same_pi(H, E)
393 -> subtract_pis(T, D, R)
394 ; R = [H|R1],
395 subtract_pis(T, D, R1)
396 ).
397
398same_pi(PI, PI) => true.
399same_pi(Name/A1, Name//A2) => A1 =:= A2+2.
400same_pi(Name//A1, Name/A2) => A1 =:= A2-2.
401same_pi(_,_) => fail.
402
403
408
409update_style(_Old, Options, Options) :-
410 option(directive(_), Options),
411 !.
412update_style(Old, Options, [directive(autoload/2)|Options]) :-
413 memberchk((:- autoload(_,_)), Old),
414 !.
415update_style(Old, Options, [directive(autoload/1)|Options]) :-
416 memberchk((:- autoload(_)), Old),
417 !.
418update_style(Old, Options, [directive(use_module/2)|Options]) :-
419 memberchk((:- use_module(_,_)), Old),
420 !.
421update_style(Old, Options, [directive(use_module/1)|Options]) :-
422 memberchk((:- use_module(_)), Old),
423 !.
424update_style(_, Options, Options).
425
426
430
431directive(Options, File-Heads, Directive) :-
432 file_name_extension(File, pl, LibFile),
433 file_name_on_path(LibFile, Lib0),
434 segments(Lib0, Lib),
435 maplist(pi_head, PIs, Heads),
436 make_directive(Lib, PIs, Directive, Options).
437
438segments(Term0, Term) :-
439 Term0 =.. [Alias,Atom],
440 path_segments_atom(Segments, Atom),
441 format(atom(Atom), '~q', [Segments]),
442 !,
443 Term =.. [Alias,Segments].
444segments(FilePL, File) :-
445 atom(FilePL),
446 file_name_extension(File, pl, FilePL),
447 !.
448segments(Term, Term).
449
450:- multifile
451 prolog:no_autoload_module/1. 452
453make_directive(Lib, Import, (:- use_module(Lib, Import)), Options) :-
454 option(directive(use_module/2), Options, use_autoload/2),
455 !.
456make_directive(Lib, _Import, (:- use_module(Lib)), Options) :-
457 option(directive(use_module/1), Options, use_autoload/2),
458 !.
459make_directive(Lib, _Import, (:- use_module(Lib)), Options) :-
460 option(directive(use_autoload/1), Options, use_autoload/2),
461 prolog:no_autoload_module(Lib),
462 !.
463make_directive(Lib, Import, (:- use_module(Lib, Import)), _) :-
464 prolog:no_autoload_module(Lib),
465 !.
466make_directive(Lib, _Import, (:- autoload(Lib)), Options) :-
467 option(directive(use_autoload/1), Options, use_autoload/2),
468 !.
469make_directive(Lib, Import, (:- autoload(Lib, Import)), _).
470
471
472 475
476:- dynamic
477 library_index/3, 478 autoload_directories/1, 479 index_checked_at/1. 480:- volatile
481 library_index/3,
482 autoload_directories/1,
483 index_checked_at/1. 484
485noautoload(Head, File) :-
486 functor(Head, Name, Arity),
487 context_module(Here),
488 '$autoload':load_library_index(Here:Name, Arity, Here:noautoload('INDEX')),
489 library_index(Head, _, File).
490
491
492 495
503
504file_auto_import(File, Options) :-
505 absolute_file_name(File, Path,
506 [ file_type(prolog),
507 access(read)
508 ]),
509 file_autoload_directives(Path, Directives, Options),
510 ( option(backup(Ext), Options)
511 -> file_name_extension(Path, Ext, Old),
512 copy_file(Path, Old)
513 ; true
514 ),
515 Edit = _{import:Directives, done:_},
516 ( has_import(Path)
517 -> edit_file(Old, Path, Edit.put(replace,true))
518 ; edit_file(Old, Path, Edit.put(new,true))
519 ).
520
521has_import(InFile) :-
522 setup_call_cleanup(
523 prolog_open_source(InFile, In),
524 ( repeat,
525 prolog_read_source_term(In, Term, _Expanded, []),
526 ( Term == end_of_file
527 -> !
528 ; true
529 )
530 ),
531 prolog_close_source(In)),
532 nonvar(Term),
533 import_directive(Term),
534 !.
535
536import_directive((:- use_module(_))).
537import_directive((:- use_module(_, _))).
538
540
541rewrite_term(Never,_,_,_) :-
542 never_rewrite(Never),
543 !,
544 fail.
545rewrite_term(Import,false,[],Options) :-
546 Options.done == true,
547 !,
548 import_directive(Import).
549rewrite_term(In,false,Directives,Options) :-
550 import_directive(In),
551 !,
552 append(Options.import, [nl], Directives),
553 Options.done = true.
554rewrite_term(In,true,Directives,Options) :-
555 In = (:- module(_,_)),
556 Options.get(new) == true,
557 !,
558 append(Options.import, [nl], Directives),
559 Options.done = true.
560
561never_rewrite((:- use_module(_, []))).
562
563edit_file(InFile, OutFile, Options) :-
564 read_file_to_string(InFile, String, []),
565 setup_call_cleanup(
566 prolog_open_source(InFile, In),
567 setup_call_cleanup(
568 open(OutFile, write, Out),
569 rewrite(In, Out, String, Options),
570 close(Out)),
571 prolog_close_source(In)).
572
573rewrite(In, Out, String, Options) :-
574 prolog_read_source_term(
575 In, Term, _Expanded,
576 [ term_position(StartPos),
577 subterm_positions(TermPos),
578 comments(Comments)
579 ]),
580 stream_position_data(char_count, StartPos, StartChar),
581 copy_comments(Comments, StartChar, String, Out),
582 ( Term == end_of_file
583 -> true
584 ; ( nonvar(Term),
585 rewrite_term(Term, Keep, List, Options)
586 -> ( Keep == true
587 -> copy_term_string(TermPos, String, Out)
588 ; true
589 ),
590 forall(member(T, List),
591 output_term(Out, T)),
592 ( append(_, [nl], List)
593 -> skip_blanks(In)
594 ; true
595 )
596 ; copy_term_string(TermPos, String, Out)
597 ),
598 rewrite(In, Out, String, Options)
599 ).
600
601output_term(Out, nl) :-
602 !,
603 nl(Out).
604output_term(Out, Term) :-
605 print_term(Term, [output(Out)]),
606 format(Out, '.~n', []).
607
([Pos-H|T], StartChar, String, Out) :-
609 stream_position_data(char_count, Pos, Start),
610 Start < StartChar,
611 !,
612 string_length(H, Len),
613 sub_string(String, Start, Len, _, Comment),
614 End is Start+Len+1,
615 layout_after(End, String, Layout),
616 format(Out, '~s~s', [Comment, Layout]),
617 copy_comments(T, StartChar, String, Out).
618copy_comments(_, _, _, _).
619
620copy_term_string(TermPos, String, Out) :-
621 arg(1, TermPos, Start),
622 arg(2, TermPos, End),
623 Len is End - Start,
624 sub_string(String, Start, Len, _, TermString),
625 End1 is End + 1,
626 full_stop_after(End1, String, Layout),
627 format(Out, '~s~s', [TermString, Layout]).
628
629layout_after(Index, String, [H|T]) :-
630 string_code(Index, String, H),
631 code_type(H, space),
632 !,
633 Index2 is Index+1,
634 layout_after(Index2, String, T).
635layout_after(_, _, []).
636
637full_stop_after(Index, String, [H|T]) :-
638 string_code(Index, String, H),
639 Index2 is Index+1,
640 ( code_type(H, space)
641 -> !, full_stop_after(Index2, String, T)
642 ; H == 0'.
643 -> !, layout_after(Index2, String, T)
644 ).
645full_stop_after(_, _, []).
646
647skip_blanks(In) :-
648 peek_code(In, C),
649 code_type(C, space),
650 !,
651 get_code(In, _),
652 skip_blanks(In).
653skip_blanks(_)