37
38:- module('$autoload',
39 [ '$find_library'/5,
40 '$in_library'/3,
41 '$define_predicate'/1,
42 '$update_library_index'/1, 43 '$autoload'/1,
44
45 make_library_index/1,
46 make_library_index/2,
47 reload_library_index/0,
48 autoload_path/1,
49
50 autoload/1, 51 autoload/2, 52
53 require/1 54 ]). 55
56:- meta_predicate
57 '$autoload'(:),
58 autoload(:),
59 autoload(:, +),
60 require(:). 61
62:- dynamic
63 library_index/3, 64 autoload_directories/1, 65 index_checked_at/1. 66:- volatile
67 library_index/3,
68 autoload_directories/1,
69 index_checked_at/1. 70
71user:file_search_path(autoload, swi(library)).
72user:file_search_path(autoload, pce(prolog/lib)).
73user:file_search_path(autoload, app_config(lib)).
74user:file_search_path(autoload, Dir) :-
75 '$ext_library_directory'(Dir).
76
77:- create_prolog_flag(warn_autoload, false, []). 78
86
87'$find_library'(Module, Name, Arity, LoadModule, Library) :-
88 load_library_index(Name, Arity),
89 functor(Head, Name, Arity),
90 ( library_index(Head, Module, Library),
91 LoadModule = Module
92 ; library_index(Head, LoadModule, Library)
93 ),
94 !.
95
100
101'$in_library'(Name, Arity, Path) :-
102 atom(Name), integer(Arity),
103 !,
104 load_library_index(Name, Arity),
105 functor(Head, Name, Arity),
106 library_index(Head, _, Path).
107'$in_library'(Name, Arity, Path) :-
108 load_library_index(Name, Arity),
109 library_index(Head, _, Path),
110 functor(Head, Name, Arity).
111
116
117:- meta_predicate
118 '$define_predicate'(:). 119
120'$define_predicate'(Head) :-
121 '$defined_predicate'(Head),
122 !.
123'$define_predicate'(Term) :-
124 Term = Module:Head,
125 ( compound(Head)
126 -> compound_name_arity(Head, Name, Arity)
127 ; Name = Head, Arity = 0
128 ),
129 '$undefined_procedure'(Module, Name, Arity, retry).
130
131
132 135
136:- thread_local
137 silent/0. 138
150
151'$update_library_index'(Options) :-
152 setof(Dir, writable_indexed_directory(Dir, Options), Dirs),
153 !,
154 setup_call_cleanup(
155 asserta(silent, Ref),
156 guarded_make_library_index(Dirs),
157 erase(Ref)),
158 ( flag('$modified_index', true, false)
159 -> reload_library_index
160 ; true
161 ).
162'$update_library_index'(_).
163
164guarded_make_library_index([]).
165guarded_make_library_index([Dir|Dirs]) :-
166 ( catch(make_library_index(Dir), E,
167 print_message(error, E))
168 -> true
169 ; print_message(warning, goal_failed(make_library_index(Dir)))
170 ),
171 guarded_make_library_index(Dirs).
172
177
178writable_indexed_directory(Dir, Options) :-
179 current_prolog_flag(home, Home),
180 writable_indexed_directory(Dir),
181 ( sub_atom(Dir, 0, _, _, Home)
182 -> '$option'(system(true), Options, false)
183 ; '$option'(user(true), Options, true)
184 ).
185
186writable_indexed_directory(Dir) :-
187 index_file_name(IndexFile, autoload('INDEX'), [access([read,write])]),
188 file_directory_name(IndexFile, Dir).
189writable_indexed_directory(Dir) :-
190 absolute_file_name(library('MKINDEX'),
191 [ file_type(prolog),
192 access(read),
193 solutions(all),
194 file_errors(fail)
195 ], MkIndexFile),
196 file_directory_name(MkIndexFile, Dir),
197 plfile_in_dir(Dir, 'INDEX', _, IndexFile),
198 access_file(IndexFile, write).
199
200
201 204
208
209reload_library_index :-
210 context_module(M),
211 reload_library_index(M).
212
213reload_library_index(M) :-
214 with_mutex('$autoload', clear_library_index(M)).
215
216clear_library_index(M) :-
217 retractall(M:library_index(_, _, _)),
218 retractall(M:autoload_directories(_)),
219 retractall(M:index_checked_at(_)).
220
221
228
229:- meta_predicate load_library_index(?, ?, :). 230:- public load_library_index/3. 231
232load_library_index(Name, Arity) :-
233 load_library_index(Name, Arity, autoload('INDEX')).
234
235load_library_index(Name, Arity, M:_Spec) :-
236 atom(Name), integer(Arity),
237 functor(Head, Name, Arity),
238 M:library_index(Head, _, _),
239 !.
240load_library_index(_, _, Spec) :-
241 notrace(with_mutex('$autoload', load_library_index_p(Spec))).
242
243load_library_index_p(M:_) :-
244 M:index_checked_at(Time),
245 get_time(Now),
246 Now-Time < 60,
247 !.
248load_library_index_p(M:Spec) :-
249 findall(Index, index_file_name(Index, Spec, [access(read)]), List0),
250 '$list_to_set'(List0, List),
251 retractall(M:index_checked_at(_)),
252 get_time(Now),
253 assert(M:index_checked_at(Now)),
254 ( M:autoload_directories(List)
255 -> true
256 ; retractall(M:library_index(_, _, _)),
257 retractall(M:autoload_directories(_)),
258 read_index(List, M),
259 assert(M:autoload_directories(List))
260 ).
261
269
270index_file_name(IndexFile, FileSpec, Options) :-
271 absolute_file_name(FileSpec,
272 IndexFile,
273 [ file_type(prolog),
274 solutions(all),
275 file_errors(fail)
276 | Options
277 ]).
278
279read_index([], _) :- !.
280read_index([H|T], M) :-
281 !,
282 read_index(H, M),
283 read_index(T, M).
284read_index(Index, M) :-
285 print_message(silent, autoload(read_index(Dir))),
286 file_directory_name(Index, Dir),
287 setup_call_cleanup(
288 '$push_input_context'(autoload_index),
289 setup_call_cleanup(
290 open(Index, read, In),
291 read_index_from_stream(Dir, In, M),
292 close(In)),
293 '$pop_input_context').
294
295read_index_from_stream(Dir, In, M) :-
296 repeat,
297 read(In, Term),
298 assert_index(Term, Dir, M),
299 !.
300
301assert_index(end_of_file, _, _) :- !.
302assert_index(index(Name, Arity, Module, File), Dir, M) :-
303 !,
304 functor(Head, Name, Arity),
305 atomic_list_concat([Dir, '/', File], Path),
306 assertz(M:library_index(Head, Module, Path)),
307 fail.
308assert_index(Term, Dir, _) :-
309 print_message(error, illegal_autoload_index(Dir, Term)),
310 fail.
311
312
313 316
327
328make_library_index(Dir0) :-
329 forall(absolute_file_name(Dir0, Dir,
330 [ expand(true),
331 file_type(directory),
332 file_errors(fail),
333 solutions(all)
334 ]),
335 make_library_index2(Dir)).
336
337make_library_index2(Dir) :-
338 plfile_in_dir(Dir, 'MKINDEX', _MkIndex, AbsMkIndex),
339 access_file(AbsMkIndex, read),
340 !,
341 load_files(user:AbsMkIndex, [silent(true)]).
342make_library_index2(Dir) :-
343 findall(Pattern, source_file_pattern(Pattern), PatternList),
344 make_library_index2(Dir, PatternList).
345
358
359make_library_index(Dir0, Patterns) :-
360 forall(absolute_file_name(Dir0, Dir,
361 [ expand(true),
362 file_type(directory),
363 file_errors(fail),
364 solutions(all)
365 ]),
366 make_library_index2(Dir, Patterns)).
367
368make_library_index2(Dir, Patterns) :-
369 plfile_in_dir(Dir, 'INDEX', _Index, AbsIndex),
370 ensure_slash(Dir, DirS),
371 pattern_files(Patterns, DirS, Files),
372 ( library_index_out_of_date(Dir, AbsIndex, Files)
373 -> do_make_library_index(AbsIndex, DirS, Files),
374 set_flag('$modified_index', true)
375 ; true
376 ).
377
378ensure_slash(Dir, DirS) :-
379 ( sub_atom(Dir, _, _, 0, /)
380 -> DirS = Dir
381 ; atom_concat(Dir, /, DirS)
382 ).
383
384source_file_pattern(Pattern) :-
385 user:prolog_file_type(PlExt, prolog),
386 PlExt \== qlf,
387 atom_concat('*.', PlExt, Pattern).
388
389plfile_in_dir(Dir, Base, PlBase, File) :-
390 file_name_extension(Base, pl, PlBase),
391 atomic_list_concat([Dir, '/', PlBase], File).
392
393pattern_files([], _, []).
394pattern_files([H|T], DirS, Files) :-
395 atom_concat(DirS, H, P0),
396 expand_file_name(P0, Files0),
397 '$append'(Files0, Rest, Files),
398 pattern_files(T, DirS, Rest).
399
400library_index_out_of_date(_Dir, Index, _Files) :-
401 \+ exists_file(Index),
402 !.
403library_index_out_of_date(Dir, Index, Files) :-
404 time_file(Index, IndexTime),
405 ( time_file(Dir, DotTime),
406 DotTime - IndexTime > 0.001 407 ; '$member'(File, Files), 408 time_file(File, FileTime),
409 FileTime - IndexTime > 0.001
410 ),
411 !.
412
413
414do_make_library_index(Index, Dir, Files) :-
415 ensure_slash(Dir, DirS),
416 '$stage_file'(Index, StagedIndex),
417 setup_call_catcher_cleanup(
418 open(StagedIndex, write, Out),
419 ( print_message(informational, make(library_index(Dir))),
420 index_header(Out),
421 index_files(Files, DirS, Out)
422 ),
423 Catcher,
424 install_index(Out, Catcher, StagedIndex, Index)).
425
426install_index(Out, Catcher, StagedIndex, Index) :-
427 catch(close(Out), Error, true),
428 ( silent
429 -> OnError = silent
430 ; OnError = error
431 ),
432 ( var(Error)
433 -> TheCatcher = Catcher
434 ; TheCatcher = exception(Error)
435 ),
436 '$install_staged_file'(TheCatcher, StagedIndex, Index, OnError).
437
441
442index_files([], _, _).
443index_files([File|Files], DirS, Fd) :-
444 ( catch(exports(File, Module, Public), E,
445 print_message(warning, E)),
446 nonvar(Module)
447 -> atom_concat(DirS, Local, File),
448 file_name_extension(Base, _, Local),
449 forall(public_predicate(Public, Name/Arity),
450 format(Fd, 'index((~k), ~k, ~k, ~k).~n',
451 [Name, Arity, Module, Base]))
452 ; true
453 ),
454 index_files(Files, DirS, Fd).
455
456public_predicate(Public, PI) :-
457 '$member'(PI0, Public),
458 canonical_pi(PI0, PI).
459
460canonical_pi(Var, _) :-
461 var(Var), !, fail.
462canonical_pi(Name/Arity, Name/Arity).
463canonical_pi(Name//A0, Name/Arity) :-
464 Arity is A0 + 2.
465
466
(Fd):-
468 format(Fd, '/* Creator: make/0~n~n', []),
469 format(Fd, ' Purpose: Provide index for autoload~n', []),
470 format(Fd, '*/~n~n', []).
471
475
476:- public exports/3. 477exports(File, Module, Exports) :-
478 ( current_prolog_flag(xref, Old)
479 -> true
480 ; Old = false
481 ),
482 setup_call_cleanup(
483 set_prolog_flag(xref, true),
484 snapshot(exports_(File, Module, Exports)),
485 set_prolog_flag(xref, Old)).
486
487exports_(File, Module, Exports) :-
488 State = state(true, _, []),
489 ( '$source_term'(File,
490 _Read,_RLayout,
491 Term,_TermLayout,
492 _Stream,
493 [ syntax_errors(quiet)
494 ]),
495 ( Term = (:- module(M,Public)),
496 is_list(Public),
497 arg(1, State, true)
498 -> nb_setarg(1, State, false),
499 nb_setarg(2, State, M),
500 nb_setarg(3, State, Public),
501 fail
502 ; nb_setarg(1, State, false),
503 fail
504 ; Term = (:- export(Export))
505 -> phrase(export_pi(Export), PIs),
506 arg(3, State, E0),
507 '$append'(E0, PIs, E1),
508 nb_setarg(3, State, E1),
509 fail
510 ; Term = (:- use_foreign_library(Lib)),
511 nonvar(Lib),
512 arg(2, State, M),
513 atom(M)
514 -> catch('$syspreds':use_foreign_library_noi(M:Lib), error(_,_), true),
515 fail
516 ; Term = (:- Directive),
517 nonvar(Directive)
518 -> fail
519 ; Term == [] 520 -> fail
521 ; !
522 )
523 ; true
524 ),
525 arg(2, State, Module),
526 arg(3, State, Exports).
527
528export_pi(Var) -->
529 { var(Var) },
530 !.
531export_pi((A,B)) -->
532 !,
533 export_pi(A),
534 export_pi(B).
535export_pi(PI) -->
536 { ground(PI) },
537 [PI].
538
539
540 543
558
559autoload_path(Alias) :-
560 ( user:file_search_path(autoload, Alias)
561 -> true
562 ; assertz(user:file_search_path(autoload, Alias)),
563 reload_library_index
564 ).
565
566system:term_expansion((:- autoload_path(Alias)),
567 [ user:file_search_path(autoload, Alias),
568 (:- reload_library_index)
569 ]).
570
571
572 575
583
584'$autoload'(PI) :-
585 source_location(File, _Line),
586 !,
587 setup_call_cleanup(
588 '$start_aux'(File, Context),
589 '$autoload2'(PI),
590 '$end_aux'(File, Context)).
591'$autoload'(PI) :-
592 '$autoload2'(PI).
593
594'$autoload2'(PI) :-
595 setup_call_cleanup(
596 leave_sandbox(Old),
597 '$autoload3'(PI),
598 restore_sandbox(Old)).
599
600leave_sandbox(Sandboxed) :-
601 current_prolog_flag(sandboxed_load, Sandboxed),
602 set_prolog_flag(sandboxed_load, false).
603restore_sandbox(Sandboxed) :-
604 set_prolog_flag(sandboxed_load, Sandboxed).
605
606'$autoload3'(PI) :-
607 autoload_from(PI, LoadModule, FullFile),
608 do_autoload(FullFile, PI, LoadModule).
609
614
615autoload_from(Module:PI, LoadModule, FullFile) :-
616 autoload_in(Module, explicit),
617 current_autoload(Module:File, Ctx, import(Imports)),
618 memberchk(PI, Imports),
619 library_info(File, Ctx, FullFile, LoadModule, Exports),
620 ( pi_in_exports(PI, Exports)
621 -> !
622 ; autoload_error(Ctx, not_exported(PI, File, FullFile, Exports)),
623 fail
624 ).
625autoload_from(Module:Name/Arity, LoadModule, FullFile) :-
626 autoload_in(Module, explicit),
627 PI = Name/Arity,
628 current_autoload(Module:File, Ctx, all),
629 library_info(File, Ctx, FullFile, LoadModule, Exports),
630 pi_in_exports(PI, Exports).
631autoload_from(Module:Name/Arity, LoadModule, Library) :-
632 autoload_in(Module, general),
633 '$find_library'(Module, Name, Arity, LoadModule, Library).
634
635:- public autoload_in/2. 636
637autoload_in(Module, How) :-
638 current_prolog_flag(autoload, AutoLoad),
639 autoload_in(AutoLoad, How, Module),
640 !.
641
643
644autoload_in(true, _, _).
645autoload_in(explicit, explicit, _).
646autoload_in(user, _, user).
647autoload_in(user_or_explicit, explicit, _).
648autoload_in(user_or_explicit, _, user).
649
650
666
667do_autoload(Library, Module:Name/Arity, LoadModule) :-
668 functor(Head, Name, Arity),
669 '$update_autoload_level'([autoload(true)], Old),
670 verbose_autoload(Module:Name/Arity, Library),
671 loadable_file(Library, File),
672 '$compilation_mode'(OldComp, database),
673 ( Module == LoadModule
674 -> ensure_loaded(Module:File)
675 ; ( '$c_current_predicate'(_, LoadModule:Head),
676 '$get_predicate_attribute'(LoadModule:Head, defined, 1),
677 \+ '$loading'(Library)
678 -> Module:import(LoadModule:Name/Arity)
679 ; use_module(Module:File, [Name/Arity])
680 ),
681 warn_autoload(Module, LoadModule:Name/Arity)
682 ),
683 '$set_compilation_mode'(OldComp),
684 '$set_autoload_level'(Old),
685 '$c_current_predicate'(_, Module:Head).
686
687loadable_file(PlFile, File) :-
688 exists_file(PlFile), !,
689 File = PlFile.
690loadable_file(PlFile, Base) :-
691 file_name_extension(Base, pl, PlFile),
692 !.
693loadable_file(File, File).
694
695verbose_autoload(PI, Library) :-
696 current_prolog_flag(verbose_autoload, true),
697 !,
698 set_prolog_flag(verbose_autoload, false),
699 print_message(informational, autoload(PI, Library)),
700 set_prolog_flag(verbose_autoload, true).
701verbose_autoload(PI, Library) :-
702 print_message(silent, autoload(PI, Library)).
703
704
710
711:- public 712 autoloadable/2. 713
714autoloadable(M:Head, FullFile) :-
715 atom(M),
716 current_module(M),
717 autoload_in(M, explicit),
718 ( callable(Head)
719 -> goal_name_arity(Head, Name, Arity),
720 autoload_from(M:Name/Arity, _, FullFile)
721 ; findall((M:H)-F, autoloadable_2(M:H, F), Pairs),
722 ( '$member'(M:Head-FullFile, Pairs)
723 ; current_autoload(M:File, Ctx, all),
724 library_info(File, Ctx, FullFile, _, Exports),
725 '$member'(PI, Exports),
726 '$pi_head'(PI, Head),
727 \+ memberchk(M:Head-_, Pairs)
728 )
729 ).
730autoloadable(M:Head, FullFile) :-
731 ( var(M)
732 -> autoload_in(any, general)
733 ; autoload_in(M, general)
734 ),
735 ( callable(Head)
736 -> goal_name_arity(Head, Name, Arity),
737 ( '$find_library'(_, Name, Arity, _, FullFile)
738 -> true
739 )
740 ; '$in_library'(Name, Arity, autoload),
741 functor(Head, Name, Arity)
742 ).
743
744
745autoloadable_2(M:Head, FullFile) :-
746 current_autoload(M:File, Ctx, import(Imports)),
747 library_info(File, Ctx, FullFile, _LoadModule, _Exports),
748 '$member'(PI, Imports),
749 '$pi_head'(PI, Head).
750
751goal_name_arity(Head, Name, Arity) :-
752 compound(Head),
753 !,
754 compound_name_arity(Head, Name, Arity).
755goal_name_arity(Head, Head, 0).
756
767
768library_info(Spec, _, FullFile, Module, Exports) :-
769 '$resolved_source_path'(Spec, FullFile, []),
770 !,
771 ( \+ '$loading_file'(FullFile, _Queue, _LoadThread)
772 -> '$current_module'(Module, FullFile),
773 '$module_property'(Module, exports(Exports))
774 ; library_info_from_file(FullFile, _, Module, Exports)
775 ).
776library_info(Spec, Context, FullFile, Module, Exports) :-
777 ( Context = (Path:_Line)
778 -> Extra = [relative_to(Path)]
779 ; Extra = []
780 ),
781 ( absolute_file_name(Spec, AbsFile,
782 [ file_type(prolog),
783 access(read),
784 file_errors(fail)
785 | Extra
786 ])
787 -> library_info_from_file(AbsFile, FullFile, Module, Exports),
788 '$register_resolved_source_path'(Spec, FullFile)
789 ; absolute_file_name(Spec, FullFile,
790 [ file_type(prolog),
791 solutions(all),
792 file_errors(fail)
793 | Extra
794 ]),
795 source_file(FullFile),
796 '$current_module'(Module, FullFile)
797 -> '$module_property'(Module, exports(Exports))
798 ; autoload_error(Context, no_file(Spec)),
799 fail
800 ).
801
802library_info_from_file(QlfFile, PlFile, Module, Exports) :-
803 file_name_extension(_, qlf, QlfFile),
804 !,
805 '$qlf_module'(QlfFile, Info),
806 _{module:Module, exports:Exports, file:PlFile} :< Info.
807library_info_from_file(PlFile, PlFile, Module, Exports) :-
808 setup_call_cleanup(
809 '$set_source_module'(OldModule, system),
810 setup_call_cleanup(
811 '$open_source'(PlFile, In, State, [], []),
812 '$term_in_file'(In, _Read, _RLayout, Term, _TLayout, _Stream,
813 [PlFile], []),
814 '$close_source'(State, true)),
815 '$set_source_module'(OldModule)),
816 ( Term = (:- module(Module, Exports))
817 -> !
818 ; nonvar(Term),
819 skip_header(Term)
820 -> fail
821 ; '$domain_error'(module_header, Term)
822 ).
823
(begin_of_file).
825
826
827:- dynamic printed/3. 828:- volatile printed/3. 829
830autoload_error(Context, Error) :-
831 suppress(Context, Error),
832 !.
833autoload_error(Context, Error) :-
834 get_time(Now),
835 assertz(printed(Context, Error, Now)),
836 print_message(warning, error(autoload(Error), autoload(Context))).
837
838suppress(Context, Error) :-
839 printed(Context, Error, Printed),
840 get_time(Now),
841 ( Now - Printed < 1
842 -> true
843 ; retractall(printed(Context, Error, _)),
844 fail
845 ).
846
847
848 851
852:- public
853 set_autoload/1. 854
861
862set_autoload(FlagValue) :-
863 current_prolog_flag(autoload, FlagValue),
864 !.
865set_autoload(FlagValue) :-
866 \+ autoload_in(FlagValue, explicit, any),
867 !,
868 setup_call_cleanup(
869 nb_setval('$autoload_disabling', true),
870 materialize_autoload(Count),
871 nb_delete('$autoload_disabling')),
872 print_message(informational, autoload(disabled(Count))).
873set_autoload(_).
874
875materialize_autoload(Count) :-
876 State = state(0),
877 forall(current_predicate(M:'$autoload'/3),
878 materialize_autoload(M, State)),
879 arg(1, State, Count).
880
881materialize_autoload(M, State) :-
882 ( current_autoload(M:File, Context, Import),
883 library_info(File, Context, PlFile, _LoadModule, _Exports),
884 arg(1, State, N0),
885 N is N0+1,
886 nb_setarg(1, State, N),
887 loadable_file(PlFile, LoadFile),
888 ( Import == all
889 -> verbose_autoload(M:all, PlFile),
890 use_module(M:LoadFile)
891 ; Import = import(Preds)
892 -> verbose_autoload(M:Preds, PlFile),
893 use_module(M:LoadFile, Preds)
894 ),
895 fail
896 ; true
897 ),
898 abolish(M:'$autoload'/3).
899
900
901 904
905autoload(M:File) :-
906 ( \+ autoload_in(M, explicit)
907 ; nb_current('$autoload_disabling', true)
908 ),
909 !,
910 use_module(M:File).
911autoload(M:File) :-
912 '$must_be'(filespec, File),
913 source_context(Context),
914 ( current_autoload(M:File, _, import(all))
915 -> true
916 ; assert_autoload(M:'$autoload'(File, Context, all))
917 ).
918
919autoload(M:File, Imports) :-
920 ( \+ autoload_in(M, explicit)
921 ; nb_current('$autoload_disabling', true)
922 ),
923 !,
924 use_module(M:File, Imports).
925autoload(M:File, Imports0) :-
926 '$must_be'(filespec, File),
927 valid_imports(Imports0, Imports),
928 source_context(Context),
929 register_autoloads(Imports, M, File, Context),
930 ( current_autoload(M:File, _, import(Imports))
931 -> true
932 ; assert_autoload(M:'$autoload'(File, Context, import(Imports)))
933 ).
934
935source_context(Path:Line) :-
936 source_location(Path, Line),
937 !.
938source_context(-).
939
940assert_autoload(Clause) :-
941 '$initialization_context'(Source, Ctx),
942 '$store_admin_clause2'(Clause, _Layout, Source, Ctx).
943
944valid_imports(Imports0, Imports) :-
945 '$must_be'(list, Imports0),
946 valid_import_list(Imports0, Imports).
947
948valid_import_list([], []).
949valid_import_list([H0|T0], [H|T]) :-
950 '$pi_head'(H0, Head),
951 '$pi_head'(H, Head),
952 valid_import_list(T0, T).
953
960
961register_autoloads([], _, _, _).
962register_autoloads([PI|T], Module, File, Context) :-
963 PI = Name/Arity,
964 functor(Head, Name, Arity),
965 ( '$get_predicate_attribute'(Module:Head, autoload, 1)
966 -> ( current_autoload(Module:_File0, _Ctx0, import(Imports)),
967 memberchk(PI, Imports)
968 -> '$permission_error'(redefine, imported_procedure, PI),
969 fail
970 ; Done = true
971 )
972 ; '$c_current_predicate'(_, Module:Head), 973 '$get_predicate_attribute'(Module:Head, imported, From)
974 -> ( ( '$resolved_source_path'(File, FullFile)
975 -> true
976 ; '$resolve_source_path'(File, FullFile, [])
977 ),
978 module_property(From, file(FullFile))
979 -> Done = true
980 ; print_message(warning,
981 autoload(already_defined(Module:PI, From))),
982 Done = true
983 )
984 ; true
985 ),
986 ( Done == true
987 -> true
988 ; '$set_predicate_attribute'(Module:Head, autoload, 1)
989 ),
990 register_autoloads(T, Module, File, Context).
991
992pi_in_exports(PI, Exports) :-
993 '$member'(E, Exports),
994 canonical_pi(E, PI),
995 !.
996
997current_autoload(M:File, Context, Term) :-
998 '$get_predicate_attribute'(M:'$autoload'(_,_,_), defined, 1),
999 M:'$autoload'(File, Context, Term).
1000
1001 1004
1008
1009warn_autoload(TargetModule, PI) :-
1010 current_prolog_flag(warn_autoload, true),
1011 \+ current_prolog_flag(xref, true),
1012 \+ nb_current('$autoload_warning', true),
1013 \+ nowarn_autoload(TargetModule, PI),
1014 '$pi_head'(PI, Head),
1015 source_file(Head, File),
1016 expansion_hook(P),
1017 source_file(P, File),
1018 !,
1019 setup_call_cleanup(
1020 b_setval('$autoload_warning', true),
1021 print_message(warning,
1022 deprecated(autoload(TargetModule, File, PI, expansion))),
1023 nb_delete('$autoload_warning')).
1024warn_autoload(_, _).
1025
1026expansion_hook(user:goal_expansion(_,_)).
1027expansion_hook(user:goal_expansion(_,_,_,_)).
1028expansion_hook(system:goal_expansion(_,_)).
1029expansion_hook(system:goal_expansion(_,_,_,_)).
1030
1043
1044nowarn_autoload(TargetModule, LoadModule:PI) :-
1045 NoWarn = LoadModule:'$nowarn_autoload'(PI,TargetModule),
1046 '$c_current_predicate'(_, NoWarn),
1047 \+ '$get_predicate_attribute'(NoWarn, imported, _From),
1048 call(NoWarn).
1049
1050
1051 1054
1059
1060require(M:Spec) :-
1061 ( is_list(Spec)
1062 -> List = Spec
1063 ; phrase(comma_list(Spec), List)
1064 ), !,
1065 require(List, M, FromLib),
1066 keysort(FromLib, Sorted),
1067 by_file(Sorted, Autoload),
1068 forall('$member'(File-Import, Autoload),
1069 autoload(M:File, Import)).
1070require(_:Spec) :-
1071 '$type_error'(list, Spec).
1072
1073require([],_, []).
1074require([H|T], M, Needed) :-
1075 '$pi_head'(H, Head),
1076 ( '$get_predicate_attribute'(system:Head, defined, 1)
1077 -> require(T, M, Needed)
1078 ; '$pi_head'(Module:Name/Arity, M:Head),
1079 ( '$find_library'(Module, Name, Arity, LoadModule, Library)
1080 -> ( current_predicate(LoadModule:Name/Arity)
1081 -> Module:import(LoadModule:Name/Arity),
1082 require(T, M, Needed)
1083 ; Needed = [Library-H|More],
1084 require(T, M, More)
1085 )
1086 ; print_message(error, error(existence_error(procedure, Name/Arity), _)),
1087 require(T, M, Needed)
1088 )
1089 ).
1090
1091by_file([], []).
1092by_file([File-PI|T0], [Spec-[PI|PIs]|T]) :-
1093 on_path(File, Spec),
1094 same_file(T0, File, PIs, T1),
1095 by_file(T1, T).
1096
1097on_path(Library, library(Base)) :-
1098 file_base_name(Library, Base),
1099 findall(Path, plain_source(library(Base), Path), [Library]),
1100 !.
1101on_path(Library, Library).
1102
1103plain_source(Spec, Path) :-
1104 absolute_file_name(Spec, PathExt,
1105 [ file_type(prolog),
1106 access(read),
1107 file_errors(fail),
1108 solutions(all)
1109 ]),
1110 file_name_extension(Path, _, PathExt).
1111
1112same_file([File-PI|T0], File, [PI|PIs], T) :-
1113 !,
1114 same_file(T0, File, PIs, T).
1115same_file(List, _, [], List).
1116
1117comma_list(Var) -->
1118 { var(Var),
1119 !,
1120 '$instantiation_error'(Var)
1121 }.
1122comma_list((A,B)) -->
1123 !,
1124 comma_list(A),
1125 comma_list(B).
1126comma_list(A) -->
1127 [A]