[not loaded]autoload.pl
- $find_library(+Module, +Name, +Arity, -LoadModule, -Library) is semidet
- Locate a predicate in the library. Name and arity are the name and arity of the predicate searched for. `Module' is the preferred target module. The return values are the full path name (excluding extension) of the library and module declared in that file.
- $in_library(+Name, +Arity, -Path) is semidet
- $in_library(-Name, -Arity, -Path) is nondet
- Is true if Name/Arity is in the autoload libraries.
- $define_predicate(:Head)
- Make sure PredInd can be called. First test if the predicate is defined. If not, invoke the autoloader.
- $update_library_index
- Called from make/0 to update the index of the library for each library directory that has a writable index. Note that in the Windows version access_file/2 is mostly bogus. We assert silent/0 to suppress error messages.
- reload_library_index
- Reload the index on the next call
- make_library_index(+Dir) is det
- Create an index for autoloading from the directory Dir. The
index file is called
INDEX.pl
. In Dir contains a fileMKINDEX.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 det
- Create an autoload index
INDEX.pl
for Dir by scanning all files that match any of the file-patterns in Patterns. Typically, this appears as a directive inMKINDEX.pl
. For example::- prolog_load_context(directory, Dir), make_library_index(Dir, ['*.pl']).
- exports(+File, -Module, -Exports) is det
- Get the exports from a library as a list of PIs.
- autoload_path(+Path) is det
- Add Path to the libraries that are used by the autoloader. This
extends the search path
autoload
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.
- autoloadable(:Head, -File) is nondet
- True when Head can be autoloaded from File. This implements the
predicate_property/2 property
autoload(File)
. The module must be instantiated. - set_autoload(+Value) is det
- Hook called from set_prolog_flag/2 when autoloading is switched. If
the desired value is
false
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
- Register the predicates in ListOfPredIndicators for autoloading using autoload/2 if they are not system predicates.
- load_library_index(?Name, ?Arity) is det
- load_library_index(?Name, ?Arity, :IndexSpec) is det
- Try to find Name/Arity in the library. If the predicate is there, we are happy. If not, we check whether the set of loaded libraries has changed and if so we reload the index.
Undocumented predicates
The following predicates are exported, but not or incorrectly documented.