View source with formatted comments or as raw
    1/*  Part of SWI-Prolog
    2
    3    Author:        Jan Wielemaker
    4    E-mail:        J.Wielemaker@vu.nl
    5    WWW:           http://www.swi-prolog.org
    6    Copyright (c)  1985-2020, University of Amsterdam
    7                              VU University Amsterdam
    8                              CWI, Amsterdam
    9    All rights reserved.
   10
   11    Redistribution and use in source and binary forms, with or without
   12    modification, are permitted provided that the following conditions
   13    are met:
   14
   15    1. Redistributions of source code must retain the above copyright
   16       notice, this list of conditions and the following disclaimer.
   17
   18    2. Redistributions in binary form must reproduce the above copyright
   19       notice, this list of conditions and the following disclaimer in
   20       the documentation and/or other materials provided with the
   21       distribution.
   22
   23    THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS
   24    "AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT
   25    LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS
   26    FOR A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE
   27    COPYRIGHT OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT,
   28    INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING,
   29    BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES;
   30    LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER
   31    CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT
   32    LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN
   33    ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE
   34    POSSIBILITY OF SUCH DAMAGE.
   35*/
   36
   37:- module('$autoload',
   38          [ '$find_library'/5,
   39            '$in_library'/3,
   40            '$define_predicate'/1,
   41            '$update_library_index'/0,
   42            '$autoload'/1,
   43
   44            make_library_index/1,
   45            make_library_index/2,
   46            reload_library_index/0,
   47            autoload_path/1,
   48
   49            autoload/1,                         % +File
   50            autoload/2,                         % +File, +Imports
   51
   52            require/1				% +Predicates
   53          ]).   54
   55:- meta_predicate
   56    '$autoload'(:),
   57    autoload(:),
   58    autoload(:, +),
   59    require(:).   60
   61:- dynamic
   62    library_index/3,                % Head x Module x Path
   63    autoload_directories/1,         % List
   64    index_checked_at/1.             % Time
   65:- volatile
   66    library_index/3,
   67    autoload_directories/1,
   68    index_checked_at/1.   69
   70user:file_search_path(autoload, swi(library)).
   71user:file_search_path(autoload, pce(prolog/lib)).
   72user:file_search_path(autoload, app_config(lib)).
   73
   74
   75%!  '$find_library'(+Module, +Name, +Arity, -LoadModule, -Library) is semidet.
   76%
   77%   Locate a predicate in the library. Name   and arity are the name
   78%   and arity of  the  predicate  searched   for.  `Module'  is  the
   79%   preferred target module. The return  values   are  the full path
   80%   name (excluding extension) of the library and module declared in
   81%   that file.
   82
   83'$find_library'(Module, Name, Arity, LoadModule, Library) :-
   84    load_library_index(Name, Arity),
   85    functor(Head, Name, Arity),
   86    (   library_index(Head, Module, Library),
   87        LoadModule = Module
   88    ;   library_index(Head, LoadModule, Library)
   89    ),
   90    !.
   91
   92%!  '$in_library'(+Name, +Arity, -Path) is semidet.
   93%!  '$in_library'(-Name, -Arity, -Path) is nondet.
   94%
   95%   Is true if Name/Arity is in the autoload libraries.
   96
   97'$in_library'(Name, Arity, Path) :-
   98    atom(Name), integer(Arity),
   99    !,
  100    load_library_index(Name, Arity),
  101    functor(Head, Name, Arity),
  102    library_index(Head, _, Path).
  103'$in_library'(Name, Arity, Path) :-
  104    load_library_index(Name, Arity),
  105    library_index(Head, _, Path),
  106    functor(Head, Name, Arity).
  107
  108%!  '$define_predicate'(:Head)
  109%
  110%   Make sure PredInd can be called. First  test if the predicate is
  111%   defined. If not, invoke the autoloader.
  112
  113:- meta_predicate
  114    '$define_predicate'(:).  115
  116'$define_predicate'(Head) :-
  117    '$defined_predicate'(Head),
  118    !.
  119'$define_predicate'(Term) :-
  120    Term = Module:Head,
  121    (   compound(Head)
  122    ->  compound_name_arity(Head, Name, Arity)
  123    ;   Name = Head, Arity = 0
  124    ),
  125    '$undefined_procedure'(Module, Name, Arity, retry).
  126
  127
  128                /********************************
  129                *          UPDATE INDEX         *
  130                ********************************/
  131
  132:- thread_local
  133    silent/0.  134
  135%!  '$update_library_index'
  136%
  137%   Called from make/0 to update the index   of the library for each
  138%   library directory that has a writable   index.  Note that in the
  139%   Windows  version  access_file/2  is  mostly   bogus.  We  assert
  140%   silent/0 to suppress error messages.
  141
  142'$update_library_index' :-
  143    setof(Dir, writable_indexed_directory(Dir), Dirs),
  144    !,
  145    setup_call_cleanup(
  146        asserta(silent, Ref),
  147        guarded_make_library_index(Dirs),
  148        erase(Ref)),
  149    (   flag('$modified_index', true, false)
  150    ->  reload_library_index
  151    ;   true
  152    ).
  153'$update_library_index'.
  154
  155guarded_make_library_index([]).
  156guarded_make_library_index([Dir|Dirs]) :-
  157    (   catch(make_library_index(Dir), E,
  158              print_message(error, E))
  159    ->  true
  160    ;   print_message(warning, goal_failed(make_library_index(Dir)))
  161    ),
  162    guarded_make_library_index(Dirs).
  163
  164%!  writable_indexed_directory(-Dir) is nondet.
  165%
  166%   True when Dir is an indexed   library  directory with a writable
  167%   index, i.e., an index that can be updated.
  168
  169writable_indexed_directory(Dir) :-
  170    index_file_name(IndexFile, autoload('INDEX'), [access([read,write])]),
  171    file_directory_name(IndexFile, Dir).
  172writable_indexed_directory(Dir) :-
  173    absolute_file_name(library('MKINDEX'),
  174                       [ file_type(prolog),
  175                         access(read),
  176                         solutions(all),
  177                         file_errors(fail)
  178                       ], MkIndexFile),
  179    file_directory_name(MkIndexFile, Dir),
  180    plfile_in_dir(Dir, 'INDEX', _, IndexFile),
  181    access_file(IndexFile, write).
  182
  183
  184                /********************************
  185                *           LOAD INDEX          *
  186                ********************************/
  187
  188%!  reload_library_index
  189%
  190%   Reload the index on the next call
  191
  192reload_library_index :-
  193    context_module(M),
  194    reload_library_index(M).
  195
  196reload_library_index(M) :-
  197    with_mutex('$autoload', clear_library_index(M)).
  198
  199clear_library_index(M) :-
  200    retractall(M:library_index(_, _, _)),
  201    retractall(M:autoload_directories(_)),
  202    retractall(M:index_checked_at(_)).
  203
  204
  205%!  load_library_index(?Name, ?Arity) is det.
  206%!  load_library_index(?Name, ?Arity, :IndexSpec) is det.
  207%
  208%   Try to find Name/Arity  in  the   library.  If  the predicate is
  209%   there, we are happy. If not, we  check whether the set of loaded
  210%   libraries has changed and if so we reload the index.
  211
  212:- meta_predicate load_library_index(?, ?, :).  213:- public load_library_index/3.  214
  215load_library_index(Name, Arity) :-
  216    load_library_index(Name, Arity, autoload('INDEX')).
  217
  218load_library_index(Name, Arity, M:_Spec) :-
  219    atom(Name), integer(Arity),
  220    functor(Head, Name, Arity),
  221    M:library_index(Head, _, _),
  222    !.
  223load_library_index(_, _, Spec) :-
  224    notrace(with_mutex('$autoload', load_library_index_p(Spec))).
  225
  226load_library_index_p(M:_) :-
  227    M:index_checked_at(Time),
  228    get_time(Now),
  229    Now-Time < 60,
  230    !.
  231load_library_index_p(M:Spec) :-
  232    findall(Index, index_file_name(Index, Spec, [access(read)]), List0),
  233    '$list_to_set'(List0, List),
  234    retractall(M:index_checked_at(_)),
  235    get_time(Now),
  236    assert(M:index_checked_at(Now)),
  237    (   M:autoload_directories(List)
  238    ->  true
  239    ;   retractall(M:library_index(_, _, _)),
  240        retractall(M:autoload_directories(_)),
  241        read_index(List, M),
  242        assert(M:autoload_directories(List))
  243    ).
  244
  245%!  index_file_name(-IndexFile, +Spec, +Options) is nondet.
  246%
  247%   True if IndexFile is an autoload   index file. Options is passed
  248%   to  absolute_file_name/3.  This  predicate   searches  the  path
  249%   =autoload=.
  250%
  251%   @see file_search_path/2.
  252
  253index_file_name(IndexFile, FileSpec, Options) :-
  254    absolute_file_name(FileSpec,
  255                       IndexFile,
  256                       [ file_type(prolog),
  257                         solutions(all),
  258                         file_errors(fail)
  259                       | Options
  260                       ]).
  261
  262read_index([], _) :- !.
  263read_index([H|T], M) :-
  264    !,
  265    read_index(H, M),
  266    read_index(T, M).
  267read_index(Index, M) :-
  268    print_message(silent, autoload(read_index(Dir))),
  269    file_directory_name(Index, Dir),
  270    setup_call_cleanup(
  271        '$push_input_context'(autoload_index),
  272        setup_call_cleanup(
  273            open(Index, read, In),
  274            read_index_from_stream(Dir, In, M),
  275            close(In)),
  276        '$pop_input_context').
  277
  278read_index_from_stream(Dir, In, M) :-
  279    repeat,
  280        read(In, Term),
  281        assert_index(Term, Dir, M),
  282    !.
  283
  284assert_index(end_of_file, _, _) :- !.
  285assert_index(index(Name, Arity, Module, File), Dir, M) :-
  286    !,
  287    functor(Head, Name, Arity),
  288    atomic_list_concat([Dir, '/', File], Path),
  289    assertz(M:library_index(Head, Module, Path)),
  290    fail.
  291assert_index(Term, Dir, _) :-
  292    print_message(error, illegal_autoload_index(Dir, Term)),
  293    fail.
  294
  295
  296                /********************************
  297                *       CREATE INDEX.pl         *
  298                ********************************/
  299
  300%!  make_library_index(+Dir) is det.
  301%
  302%   Create an index for autoloading  from   the  directory  Dir. The
  303%   index  file  is  called  INDEX.pl.  In    Dir  contains  a  file
  304%   MKINDEX.pl, this file is loaded and we  assume that the index is
  305%   created by directives that appearin   this  file. Otherwise, all
  306%   source  files  are  scanned  for  their  module-header  and  all
  307%   exported predicates are added to the autoload index.
  308%
  309%   @see make_library_index/2
  310
  311make_library_index(Dir0) :-
  312    forall(absolute_file_name(Dir0, Dir,
  313                              [ expand(true),
  314                                file_type(directory),
  315                                file_errors(fail),
  316                                solutions(all)
  317                              ]),
  318           make_library_index2(Dir)).
  319
  320make_library_index2(Dir) :-
  321    plfile_in_dir(Dir, 'MKINDEX', _MkIndex, AbsMkIndex),
  322    access_file(AbsMkIndex, read),
  323    !,
  324    load_files(user:AbsMkIndex, [silent(true)]).
  325make_library_index2(Dir) :-
  326    findall(Pattern, source_file_pattern(Pattern), PatternList),
  327    make_library_index2(Dir, PatternList).
  328
  329%!  make_library_index(+Dir, +Patterns:list(atom)) is det.
  330%
  331%   Create an autoload index INDEX.pl for  Dir by scanning all files
  332%   that match any of the file-patterns in Patterns. Typically, this
  333%   appears as a directive in MKINDEX.pl.  For example:
  334%
  335%   ```
  336%   :- prolog_load_context(directory, Dir),
  337%      make_library_index(Dir, ['*.pl']).
  338%   ```
  339%
  340%   @see make_library_index/1.
  341
  342make_library_index(Dir0, Patterns) :-
  343    forall(absolute_file_name(Dir0, Dir,
  344                              [ expand(true),
  345                                file_type(directory),
  346                                file_errors(fail),
  347                                solutions(all)
  348                              ]),
  349           make_library_index2(Dir, Patterns)).
  350
  351make_library_index2(Dir, Patterns) :-
  352    plfile_in_dir(Dir, 'INDEX', _Index, AbsIndex),
  353    ensure_slash(Dir, DirS),
  354    pattern_files(Patterns, DirS, Files),
  355    (   library_index_out_of_date(Dir, AbsIndex, Files)
  356    ->  do_make_library_index(AbsIndex, DirS, Files),
  357        flag('$modified_index', _, true)
  358    ;   true
  359    ).
  360
  361ensure_slash(Dir, DirS) :-
  362    (   sub_atom(Dir, _, _, 0, /)
  363    ->  DirS = Dir
  364    ;   atom_concat(Dir, /, DirS)
  365    ).
  366
  367source_file_pattern(Pattern) :-
  368    user:prolog_file_type(PlExt, prolog),
  369    PlExt \== qlf,
  370    atom_concat('*.', PlExt, Pattern).
  371
  372plfile_in_dir(Dir, Base, PlBase, File) :-
  373    file_name_extension(Base, pl, PlBase),
  374    atomic_list_concat([Dir, '/', PlBase], File).
  375
  376pattern_files([], _, []).
  377pattern_files([H|T], DirS, Files) :-
  378    atom_concat(DirS, H, P0),
  379    expand_file_name(P0, Files0),
  380    '$append'(Files0, Rest, Files),
  381    pattern_files(T, DirS, Rest).
  382
  383library_index_out_of_date(_Dir, Index, _Files) :-
  384    \+ exists_file(Index),
  385    !.
  386library_index_out_of_date(Dir, Index, Files) :-
  387    time_file(Index, IndexTime),
  388    (   time_file(Dir, DotTime),
  389        DotTime > IndexTime
  390    ;   '$member'(File, Files),
  391        time_file(File, FileTime),
  392        FileTime > IndexTime
  393    ),
  394    !.
  395
  396
  397do_make_library_index(Index, Dir, Files) :-
  398    ensure_slash(Dir, DirS),
  399    '$stage_file'(Index, StagedIndex),
  400    setup_call_catcher_cleanup(
  401        open(StagedIndex, write, Out),
  402        ( print_message(informational, make(library_index(Dir))),
  403          index_header(Out),
  404          index_files(Files, DirS, Out)
  405        ),
  406        Catcher,
  407        install_index(Out, Catcher, StagedIndex, Index)).
  408
  409install_index(Out, Catcher, StagedIndex, Index) :-
  410    catch(close(Out), Error, true),
  411    (   silent
  412    ->  OnError = silent
  413    ;   OnError = error
  414    ),
  415    (   var(Error)
  416    ->  TheCatcher = Catcher
  417    ;   TheCatcher = exception(Error)
  418    ),
  419    '$install_staged_file'(TheCatcher, StagedIndex, Index, OnError).
  420
  421%!  index_files(+Files, +Directory, +Out:stream) is det.
  422%
  423%   Write index for Files in Directory to the stream Out.
  424
  425index_files([], _, _).
  426index_files([File|Files], DirS, Fd) :-
  427    (   catch(exports(File, Module, Public), E,
  428              print_message(warning, E)),
  429        nonvar(Module)
  430    ->  atom_concat(DirS, Local, File),
  431        file_name_extension(Base, _, Local),
  432        forall(public_predicate(Public, Name/Arity),
  433               format(Fd, 'index((~k), ~k, ~k, ~k).~n',
  434                      [Name, Arity, Module, Base]))
  435    ;   true
  436    ),
  437    index_files(Files, DirS, Fd).
  438
  439public_predicate(Public, PI) :-
  440    '$member'(PI0, Public),
  441    canonical_pi(PI0, PI).
  442
  443canonical_pi(Var, _) :-
  444    var(Var), !, fail.
  445canonical_pi(Name/Arity, Name/Arity).
  446canonical_pi(Name//A0,   Name/Arity) :-
  447    Arity is A0 + 2.
  448
  449
  450index_header(Fd):-
  451    format(Fd, '/*  Creator: make/0~n~n', []),
  452    format(Fd, '    Purpose: Provide index for autoload~n', []),
  453    format(Fd, '*/~n~n', []).
  454
  455exports(File, Module, Exports) :-
  456    (   current_prolog_flag(xref, Old)
  457    ->  true
  458    ;   Old = false
  459    ),
  460    setup_call_cleanup(
  461        set_prolog_flag(xref, true),
  462        exports_(File, Module, Exports),
  463        set_prolog_flag(xref, Old)).
  464
  465exports_(File, Module, Exports) :-
  466    State = state(true, _, []),
  467    (   '$source_term'(File, _,_,Term0,_,_,[syntax_errors(quiet)]),
  468        (   is_list(Term0)
  469        ->  '$member'(Term, Term0)
  470        ;   Term = Term0
  471        ),
  472        (   Term = (:- module(M,Public)),
  473            is_list(Public),
  474            arg(1, State, true)
  475        ->  nb_setarg(1, State, false),
  476            nb_setarg(2, State, M),
  477            nb_setarg(3, State, Public),
  478            fail
  479        ;   nb_setarg(1, State, false),
  480            fail
  481        ;   Term = (:- export(PI)),
  482            ground(PI)
  483        ->  arg(3, State, E0),
  484            '$append'(E0, [PI], E1),
  485            nb_setarg(3, State, E1),
  486            fail
  487        ;   Term = (:- use_foreign_library(Lib)),
  488            nonvar(Lib),
  489            arg(2, State, M),
  490            atom(M)
  491        ->  catch('$syspreds':use_foreign_library_noi(M:Lib), error(_,_), true),
  492            fail
  493        ;   Term = (:- Directive),
  494            nonvar(Directive)
  495        ->  fail
  496        ;   !
  497        )
  498    ;   true
  499    ),
  500    arg(2, State, Module),
  501    arg(3, State, Exports).
  502
  503
  504                 /*******************************
  505                 *            EXTENDING         *
  506                 *******************************/
  507
  508%!  autoload_path(+Path) is det.
  509%
  510%   Add Path to the libraries that are  used by the autoloader. This
  511%   extends the search  path  =autoload=   and  reloads  the library
  512%   index.  For example:
  513%
  514%     ==
  515%     :- autoload_path(library(http)).
  516%     ==
  517%
  518%   If this call appears as a directive,  it is term-expanded into a
  519%   clause  for  user:file_search_path/2  and  a  directive  calling
  520%   reload_library_index/0. This keeps source information and allows
  521%   for removing this directive.
  522
  523autoload_path(Alias) :-
  524    (   user:file_search_path(autoload, Alias)
  525    ->  true
  526    ;   assertz(user:file_search_path(autoload, Alias)),
  527        reload_library_index
  528    ).
  529
  530system:term_expansion((:- autoload_path(Alias)),
  531                      [ user:file_search_path(autoload, Alias),
  532                        (:- reload_library_index)
  533                      ]).
  534
  535
  536		 /*******************************
  537		 *      RUNTIME AUTOLOADER	*
  538		 *******************************/
  539
  540%!  $autoload'(:PI) is semidet.
  541%
  542%   Provide PI by autoloading.  This checks:
  543%
  544%     - Explicit autoload/2 declarations
  545%     - Explicit autoload/1 declarations
  546%     - The library if current_prolog_flag(autoload, true) holds.
  547
  548'$autoload'(PI) :-
  549    source_location(File, _Line),
  550    !,
  551    setup_call_cleanup(
  552        '$start_aux'(File, Context),
  553        '$autoload2'(PI),
  554        '$end_aux'(File, Context)).
  555'$autoload'(PI) :-
  556    '$autoload2'(PI).
  557
  558'$autoload2'(PI) :-
  559    setup_call_cleanup(
  560        leave_sandbox(Old),
  561        '$autoload3'(PI),
  562        restore_sandbox(Old)).
  563
  564leave_sandbox(Sandboxed) :-
  565    current_prolog_flag(sandboxed_load, Sandboxed),
  566    set_prolog_flag(sandboxed_load, false).
  567restore_sandbox(Sandboxed) :-
  568    set_prolog_flag(sandboxed_load, Sandboxed).
  569
  570'$autoload3'(PI) :-
  571    autoload_from(PI, LoadModule, FullFile),
  572    do_autoload(FullFile, PI, LoadModule).
  573
  574%!  autoload_from(+PI, -LoadModule, -File) is semidet.
  575%
  576%   True when PI can be defined  by   loading  File which is defined the
  577%   module LoadModule.
  578
  579autoload_from(Module:PI, LoadModule, FullFile) :-
  580    autoload_in(Module, explicit),
  581    current_autoload(Module:File, Ctx, import(Imports)),
  582    memberchk(PI, Imports),
  583    library_info(File, Ctx, FullFile, LoadModule, Exports),
  584    (   pi_in_exports(PI, Exports)
  585    ->  !
  586    ;   autoload_error(Ctx, not_exported(PI, File, FullFile, Exports)),
  587        fail
  588    ).
  589autoload_from(Module:Name/Arity, LoadModule, FullFile) :-
  590    autoload_in(Module, explicit),
  591    PI = Name/Arity,
  592    current_autoload(Module:File, Ctx, all),
  593    library_info(File, Ctx, FullFile, LoadModule, Exports),
  594    pi_in_exports(PI, Exports).
  595autoload_from(Module:Name/Arity, LoadModule, Library) :-
  596    autoload_in(Module, general),
  597    '$find_library'(Module, Name, Arity, LoadModule, Library).
  598
  599:- public autoload_in/2.                        % used in syspred
  600
  601autoload_in(Module, How) :-
  602    current_prolog_flag(autoload, AutoLoad),
  603    autoload_in(AutoLoad, How, Module),
  604    !.
  605
  606%!  autoload_in(+AutoloadFlag, +AutoloadMode, +TargetModule) is semidet.
  607
  608autoload_in(true,             _,        _).
  609autoload_in(explicit,         explicit, _).
  610autoload_in(user,             _,        user).
  611autoload_in(user_or_explicit, explicit, _).
  612autoload_in(user_or_explicit, _,        user).
  613
  614
  615%!  do_autoload(+File, :PI, +LoadModule) is det.
  616%
  617%   Load File, importing PI into the qualified  module. File is known to
  618%   define LoadModule. There are three cases:
  619%
  620%     - The target is the autoload module itself.  Uncommon.
  621%     - We already loaded this module. Note that
  622%       '$get_predicate_attribute'/3 alone is not enough as it will
  623%       consider auto-import from `user`. '$c_current_predicate'/2
  624%       verifies the predicate really exists, but doesn't validate
  625%       that it is defined.
  626%     - We must load the module and import the target predicate.
  627
  628do_autoload(Library, Module:Name/Arity, LoadModule) :-
  629    functor(Head, Name, Arity),
  630    '$update_autoload_level'([autoload(true)], Old),
  631    verbose_autoload(Module:Name/Arity, Library),
  632    '$compilation_mode'(OldComp, database),
  633    (   Module == LoadModule
  634    ->  ensure_loaded(Module:Library)
  635    ;   (   '$c_current_predicate'(_, LoadModule:Head),
  636            '$get_predicate_attribute'(LoadModule:Head, defined, 1),
  637            \+ '$loading'(Library)
  638        ->  Module:import(LoadModule:Name/Arity)
  639        ;   use_module(Module:Library, [Name/Arity])
  640        )
  641    ),
  642    '$set_compilation_mode'(OldComp),
  643    '$set_autoload_level'(Old),
  644    '$c_current_predicate'(_, Module:Head).
  645
  646verbose_autoload(PI, Library) :-
  647    current_prolog_flag(verbose_autoload, true),
  648    !,
  649    set_prolog_flag(verbose_autoload, false),
  650    print_message(informational, autoload(PI, Library)),
  651    set_prolog_flag(verbose_autoload, true).
  652verbose_autoload(PI, Library) :-
  653    print_message(silent, autoload(PI, Library)).
  654
  655
  656%!  autoloadable(:Head, -File) is nondet.
  657%
  658%   True when Head can be  autoloaded   from  File.  This implements the
  659%   predicate_property/2 property autoload(File).  The   module  muse be
  660%   instantiated.
  661
  662:- public                               % used from predicate_property/2
  663    autoloadable/2.  664
  665autoloadable(M:Head, FullFile) :-
  666    atom(M),
  667    current_module(M),
  668    autoload_in(M, explicit),
  669    (   callable(Head)
  670    ->  goal_name_arity(Head, Name, Arity),
  671        autoload_from(M:Name/Arity, _, FullFile)
  672    ;   findall((M:H)-F, autoloadable_2(M:H, F), Pairs),
  673        (   '$member'(M:Head-FullFile, Pairs)
  674        ;   current_autoload(M:File, Ctx, all),
  675            library_info(File, Ctx, FullFile, _, Exports),
  676            '$member'(PI, Exports),
  677            '$pi_head'(PI, Head),
  678            \+ memberchk(M:Head-_, Pairs)
  679        )
  680    ).
  681autoloadable(M:Head, FullFile) :-
  682    (   var(M)
  683    ->  autoload_in(any, general)
  684    ;   autoload_in(M, general)
  685    ),
  686    (   callable(Head)
  687    ->  goal_name_arity(Head, Name, Arity),
  688        (   '$find_library'(_, Name, Arity, _, FullFile)
  689        ->  true
  690        )
  691    ;   '$in_library'(Name, Arity, autoload),
  692        functor(Head, Name, Arity)
  693    ).
  694
  695
  696autoloadable_2(M:Head, FullFile) :-
  697    current_autoload(M:File, Ctx, import(Imports)),
  698    library_info(File, Ctx, FullFile, _LoadModule, _Exports),
  699    '$member'(PI, Imports),
  700    '$pi_head'(PI, Head).
  701
  702goal_name_arity(Head, Name, Arity) :-
  703    compound(Head),
  704    !,
  705    compound_name_arity(Head, Name, Arity).
  706goal_name_arity(Head, Head, 0).
  707
  708%!  library_info(+Spec, +AutoloadContext, -FullFile, -Module, -Exports)
  709%
  710%   Find information about a library.
  711
  712library_info(Spec, _, FullFile, Module, Exports) :-
  713    '$resolved_source_path'(Spec, FullFile, []),
  714    !,
  715    (   \+ '$loading_file'(FullFile, _Queue, _LoadThread)
  716    ->  '$current_module'(Module, FullFile),
  717        '$module_property'(Module, exports(Exports))
  718    ;   library_info_from_file(FullFile, Module, Exports)
  719    ).
  720library_info(Spec, Context, FullFile, Module, Exports) :-
  721    (   Context = (Path:_Line)
  722    ->  Extra = [relative_to(Path)]
  723    ;   Extra = []
  724    ),
  725    (   absolute_file_name(Spec, FullFile,
  726                           [ file_type(prolog),
  727                             access(read),
  728                             file_errors(fail)
  729                           | Extra
  730                           ])
  731    ->  '$register_resolved_source_path'(Spec, FullFile),
  732        library_info_from_file(FullFile, Module, Exports)
  733    ;   autoload_error(Context, no_file(Spec)),
  734        fail
  735    ).
  736
  737library_info_from_file(FullFile, Module, Exports) :-
  738    setup_call_cleanup(
  739        '$set_source_module'(OldModule, system),
  740        setup_call_cleanup(
  741            '$open_source'(FullFile, In, State, [], []),
  742            '$term_in_file'(In, _Read, _RLayout, Term, _TLayout, _Stream,
  743                            [FullFile], []),
  744            '$close_source'(State, true)),
  745        '$set_source_module'(OldModule)),
  746    (   Term = (:- module(Module, Exports))
  747    ->  !
  748    ;   nonvar(Term),
  749        skip_header(Term)
  750    ->  fail
  751    ;   '$domain_error'(module_header, Term)
  752    ).
  753
  754skip_header(begin_of_file).
  755
  756
  757:- dynamic printed/3.  758:- volatile printed/3.  759
  760autoload_error(Context, Error) :-
  761    suppress(Context, Error),
  762    !.
  763autoload_error(Context, Error) :-
  764    get_time(Now),
  765    assertz(printed(Context, Error, Now)),
  766    print_message(warning, error(autoload(Error), autoload(Context))).
  767
  768suppress(Context, Error) :-
  769    printed(Context, Error, Printed),
  770    get_time(Now),
  771    (   Now - Printed < 1
  772    ->  true
  773    ;   retractall(printed(Context, Error, _)),
  774        fail
  775    ).
  776
  777
  778		 /*******************************
  779		 *            CALLBACK		*
  780		 *******************************/
  781
  782:- public
  783    set_autoload/1.  784
  785%!  set_autoload(+Value) is det.
  786%
  787%   Hook called from set_prolog_flag/2 when  autoloading is switched. If
  788%   the desired value is `false` we   should  materialize all registered
  789%   requests for autoloading. We must do so before disabling autoloading
  790%   as loading the files may require autoloading.
  791
  792set_autoload(FlagValue) :-
  793    current_prolog_flag(autoload, FlagValue),
  794    !.
  795set_autoload(FlagValue) :-
  796    \+ autoload_in(FlagValue, explicit, any),
  797    !,
  798    setup_call_cleanup(
  799        nb_setval('$autoload_disabling', true),
  800        materialize_autoload(Count),
  801        nb_delete('$autoload_disabling')),
  802    print_message(informational, autoload(disabled(Count))).
  803set_autoload(_).
  804
  805materialize_autoload(Count) :-
  806    State = state(0),
  807    forall(current_predicate(M:'$autoload'/3),
  808           materialize_autoload(M, State)),
  809    arg(1, State, Count).
  810
  811materialize_autoload(M, State) :-
  812    (   current_autoload(M:File, Context, Import),
  813        library_info(File, Context, FullFile, _LoadModule, _Exports),
  814        arg(1, State, N0),
  815        N is N0+1,
  816        nb_setarg(1, State, N),
  817        (   Import == all
  818        ->  verbose_autoload(M:all, FullFile),
  819            use_module(M:FullFile)
  820        ;   Import = import(Preds)
  821        ->  verbose_autoload(M:Preds, FullFile),
  822            use_module(M:FullFile, Preds)
  823        ),
  824        fail
  825    ;   true
  826    ),
  827    abolish(M:'$autoload'/3).
  828
  829
  830		 /*******************************
  831		 *          AUTOLOAD/2		*
  832		 *******************************/
  833
  834autoload(M:File) :-
  835    (   \+ autoload_in(M, explicit)
  836    ;   nb_current('$autoload_disabling', true)
  837    ),
  838    !,
  839    use_module(M:File).
  840autoload(M:File) :-
  841    '$must_be'(filespec, File),
  842    source_context(Context),
  843    (   current_autoload(M:File, _, import(all))
  844    ->  true
  845    ;   assert_autoload(M:'$autoload'(File, Context, all))
  846    ).
  847
  848autoload(M:File, Imports) :-
  849    (   \+ autoload_in(M, explicit)
  850    ;   nb_current('$autoload_disabling', true)
  851    ),
  852    !,
  853    use_module(M:File, Imports).
  854autoload(M:File, Imports0) :-
  855    '$must_be'(filespec, File),
  856    valid_imports(Imports0, Imports),
  857    source_context(Context),
  858    register_autoloads(Imports, M, File, Context),
  859    (   current_autoload(M:File, _, import(Imports))
  860    ->  true
  861    ;   assert_autoload(M:'$autoload'(File, Context, import(Imports)))
  862    ).
  863
  864source_context(Path:Line) :-
  865    source_location(Path, Line),
  866    !.
  867source_context(-).
  868
  869assert_autoload(Clause) :-
  870    '$initialization_context'(Source, Ctx),
  871    '$store_admin_clause2'(Clause, _Layout, Source, Ctx).
  872
  873valid_imports(Imports0, Imports) :-
  874    '$must_be'(list, Imports0),
  875    valid_import_list(Imports0, Imports).
  876
  877valid_import_list([], []).
  878valid_import_list([H0|T0], [H|T]) :-
  879    '$pi_head'(H0, Head),
  880    '$pi_head'(H, Head),
  881    valid_import_list(T0, T).
  882
  883%!  register_autoloads(+ListOfPI, +Module, +File, +Context)
  884%
  885%   Put an `autoload` flag on all   predicates declared using autoload/2
  886%   to prevent duplicates or the user defining the same predicate.
  887
  888register_autoloads([], _, _, _).
  889register_autoloads([PI|T], Module, File, Context) :-
  890    PI = Name/Arity,
  891    functor(Head, Name, Arity),
  892    (   '$get_predicate_attribute'(Module:Head, autoload, 1)
  893    ->  (   current_autoload(Module:_File0, _Ctx0, import(Imports)),
  894            memberchk(PI, Imports)
  895        ->  '$permission_error'(redefine, imported_procedure, PI),
  896            fail
  897        ;   Done = true
  898        )
  899    ;   '$c_current_predicate'(_, Module:Head), % no auto-import
  900        '$get_predicate_attribute'(Module:Head, imported, From)
  901    ->  (   (   '$resolved_source_path'(File, FullFile)
  902            ->  true
  903            ;   '$resolve_source_path'(File, FullFile, [])
  904            ),
  905            module_property(From, file(FullFile))
  906        ->  Done = true
  907        ;   print_message(warning,
  908                          autoload(already_defined(Module:PI, From))),
  909            Done = true
  910        )
  911    ;   true
  912    ),
  913    (   Done == true
  914    ->  true
  915    ;   '$set_predicate_attribute'(Module:Head, autoload, 1)
  916    ),
  917    register_autoloads(T, Module, File, Context).
  918
  919pi_in_exports(PI, Exports) :-
  920    '$member'(E, Exports),
  921    canonical_pi(E, PI),
  922    !.
  923
  924current_autoload(M:File, Context, Term) :-
  925    '$get_predicate_attribute'(M:'$autoload'(_,_,_), defined, 1),
  926    M:'$autoload'(File, Context, Term).
  927
  928                 /*******************************
  929                 *             REQUIRE          *
  930                 *******************************/
  931
  932%!  require(:ListOfPredIndicators) is det.
  933%
  934%   Register the predicates  in   ListOfPredIndicators  for  autoloading
  935%   using autoload/2 if they are not system predicates.
  936
  937require(M:Spec) :-
  938    (   is_list(Spec)
  939    ->  List = Spec
  940    ;   phrase(comma_list(Spec), List)
  941    ), !,
  942    require(List, M, FromLib),
  943    keysort(FromLib, Sorted),
  944    by_file(Sorted, Autoload),
  945    forall('$member'(File-Import, Autoload),
  946           autoload(M:File, Import)).
  947require(_:Spec) :-
  948    '$type_error'(list, Spec).
  949
  950require([],_, []).
  951require([H|T], M, Needed) :-
  952   '$pi_head'(H, Head),
  953   (   '$get_predicate_attribute'(system:Head, defined, 1)
  954   ->  require(T, M, Needed)
  955   ;   '$pi_head'(Module:Name/Arity, M:Head),
  956       (   '$find_library'(Module, Name, Arity, LoadModule, Library)
  957       ->  (   current_predicate(LoadModule:Name/Arity)
  958           ->  Module:import(LoadModule:Name/Arity),
  959               require(T, M, Needed)
  960           ;   Needed = [Library-H|More],
  961               require(T, M, More)
  962           )
  963       ;   print_message(error, error(existence_error(procedure, Name/Arity), _)),
  964           require(T, M, Needed)
  965       )
  966   ).
  967
  968by_file([], []).
  969by_file([File-PI|T0], [Spec-[PI|PIs]|T]) :-
  970    on_path(File, Spec),
  971    same_file(T0, File, PIs, T1),
  972    by_file(T1, T).
  973
  974on_path(Library, library(Base)) :-
  975    file_base_name(Library, Base),
  976    findall(Path, plain_source(library(Base), Path), [Library]),
  977    !.
  978on_path(Library, Library).
  979
  980plain_source(Spec, Path) :-
  981    absolute_file_name(Spec, PathExt,
  982                       [ file_type(prolog),
  983                         access(read),
  984                         file_errors(fail),
  985                         solutions(all)
  986                       ]),
  987    file_name_extension(Path, _, PathExt).
  988
  989same_file([File-PI|T0], File, [PI|PIs], T) :-
  990    !,
  991    same_file(T0, File, PIs, T).
  992same_file(List, _, [], List).
  993
  994comma_list(Var) -->
  995    { var(Var),
  996      !,
  997      '$instantiation_error'(Var)
  998    }.
  999comma_list((A,B)) -->
 1000    !,
 1001    comma_list(A),
 1002    comma_list(B).
 1003comma_list(A) -->
 1004    [A]