
autoload.pl
$find_library(+Module, +Name, +Arity, -LoadModule, -Library) is semidet
$in_library(+Name, +Arity, -Path) is semidet
$define_predicate(:Head)
$update_library_index(+Options)false.true.
reload_library_index
make_library_index(+Dir) is detINDEX.pl. In Dir contains a file
MKINDEX.pl, this file is loaded and we assume that the index is
created by directives that appearin this file. Otherwise, all
source files are scanned for their module-header and all
exported predicates are added to the autoload index.
make_library_index(+Dir, +Patterns:list(atom)) is detINDEX.pl for Dir by scanning all files
that match any of the file-patterns in Patterns. Typically, this
appears as a directive in MKINDEX.pl. For example:
:- prolog_load_context(directory, Dir), make_library_index(Dir, ['*.pl']).
exports(+File, -Module, -Exports) is det
autoload_path(+Path) is detautoload and reloads the library
index. For example:
:- autoload_path(library(http)).
If this call appears as a directive, it is term-expanded into a clause for file_search_path/2 and a directive calling reload_library_index/0. This keeps source information and allows for removing this directive.
autoload_call(:Goal)
autoloadable(:Head, -File) is nondetautoload(File). The module must be
instantiated.
set_autoload(+Value) is detfalse we should materialize all registered
requests for autoloading. We must do so before disabling autoloading
as loading the files may require autoloading.
require(:ListOfPredIndicators) is det
load_library_index(?Name, ?Arity) is det
load_library_index(?Name, ?Arity, :IndexSpec) is detThe following predicates are exported, but not or incorrectly documented.
autoload(Arg1)
$autoload(Arg1)
autoload(Arg1, Arg2)