SWI-Prolog source files normally have a suffix `.pl
'.
Specifying the suffix is optional. All predicates that handle source
files first check whether a file with suffix `.pl
' exists.
If not the plain file name is checked for existence. Library files are
specified by embedding the file name using the functor library/1 . Thus
`foo
' refers to `foo.pl
' or `foo
'
in the current directory, `library(foo)
' refers to `foo.pl
'
or `foo
' in one of the library directories specified by the
dynamic predicate library_directory/1.
The user may specify other `aliases' than library
using the
predicate
file_search_path/2.
This is strongly encouraged for managing complex applications. See also absolute_file_name/[2,3].
SWI-Prolog recognises grammar rules as defined in Clocksin & Melish, 1987. The user may define additional compilation of the source file by defining the dynamic predicate term_expansion/2. Transformations by this predicate overrule the systems grammar rule transformations. It is not allowed to use assert/1, retract/1 or any other database predicate in term_expansion/2 other than for local computational purposes. (6)
Directives may be placed anywhere in a source file, invoking any predicate. They are executed when encountered. If the directive fails, a warning is printed. Directives are specified by :-/1 or ?-/1. There is no difference between the two.
SWI-Prolog does not have a separate reconsult/1 predicate. Reconsulting is implied automatically by the fact that a file is consulted which is already loaded.
OptionName(OptionValue)The following options are currently supported:
true
loads the file unconditionally, changed
loads the file if it was not loaded before, or has been modified since
it was loaded the last time, not_loaded
loads the file if
it was not loaded before.
true
, raise an error if the file is not a module file.
Used by
use_module/[1,2].
all
and the file is a module file, import all public
predicates. Otherwise import only the named predicates. Each predicate
is refered to as <name>/<arity>. This
option has no effect if the file is not a module file.
true
, load the file without printing a message. The
specified value is the default for all files loaded as a result of
loading the specified files.
~
, <user>
and
$<var>
. File may also be library(Name)
,
in which case the libraries are searched for a file with the specified
name. See also library_directory/1
and file_search_path/2. consult/1
may be abbreviated by just typing a number of file names in a list.
Examples:
?- consult(load). | % consult load
or load.pl |
?- [library(quintus)] . | % load Quintus compatibility library |
With the semantics, we hope to get as closely possible to the clear semantics without the presence of a module system. Applications using modules should consider using use_module/[1,2].
Equivalent to load_files(Files, [if(changed)]).
The implementation normally first verifies whether the predicate is already defined. If not, it will search the libraries and load the required library.
SWI-Prolog, having autoloading, does not load the library. Instead it creates a procedure header for the predicate if this does not exist. This will flag the predicate as `undefined'. See also check/0 and autoload/0.
pl -c ...
and files loaded
using consult or one of its derivatives. make/0
is normally invoked by the edit/[0,1]
and ed/[0,1] predicates. make/0
can be combined with the compiler to speed up the development of large
packages. In this case compile the package using
sun% pl -g make -o my_program -c file ... |
If `my_program' is started it will first reconsult all source files that have changed since the compilation.
./lib
, ~/lib/prolog
and the system's library
(in this order) are defined. The user may add library directories using assert/1, asserta/1
or remove system defaults using retract/1.
file_search_path(demo, '~/demo'). |
the file specification demo(myfile)
will be expanded to
~/demo/myfile
. The second argument of file_search_path/2
may be another alias.
Below is the initial definition of the file search path. This path
implies swi(<Path>)
refers to a file in
the SWI-Prolog home directory. The alias foreign(<Path>)
is intended for storing shared libraries (.so
or .DLL
files). See also
load_foreign_library/[1,2].
user:file_search_path(library, X) :- library_directory(X). user:file_search_path(swi, Home) :- feature(home, Home). user:file_search_path(foreign, swi(ArchLib)) :- feature(arch, Arch), concat('lib/', Arch, ArchLib). user:file_search_path(foreign, swi(lib)). |
The file_search_path/2 expansion is used by all loading predicates as well as by absolute_file_name/[2,3].
user
determines the extensions considered by file_search_path/2.
Extension is the filename extension without the leading dot,
Type denotes the type as used by the file_type(Type)
option of file_search_path/2.
Here is the initial definition of
prolog_file_type/2:
user:prolog_file_type(pl, prolog). user:prolog_file_type(Ext, prolog) :- feature(associate, Ext), Ext \== pl. user:prolog_file_type(qlf, qlf). user:prolog_file_type(so, executable) :- feature(open_shared_object, true). user:prolog_file_type(dll, executable) :- feature(dll, true). |
Users may wish to change the extension used for Prolog source files
to avoid conflicts (for example with perl) as well as to be
compatible with some specific implementation. The preferred alternative
extension is .pro
.
multifile
(see multifile/1)
cannot be found this way.
Key | Description |
module | Module into which file is loaded |
file | File loaded |
stream | Stream identifier (see current_input/1) |
directory | Directory in which File lives. |
term_position | Position of last term read. Term of the form '$stream_position'(0,<Line>,0,0,0) |
user
or a string), unify File with an
absolute path to the file and Line with the line-number in
the file. New code should use prolog_load_context/2.
'$source_location'(<File>, <Line>):<Clause>When compiling a module (see chapter 4 and the directive module/2), expand_term/2 will first try term_expansion/2 in the module being compiled to allow for term-expansion rules that are local to a module. If there is no local definition, or the local definition fails to translate the term, expand_term/2 will try user:term_expansion/2. For compatibility with SICStus and Quintus Prolog, this feature should not be used. See also expand_term/2, goal_expansion/2 and expand_goal/2.
The predicate goal_expansion/2
is first called in the module that is being compiled, and then on the user
module.
Only goals apearing in the body of clauses when reading a source-file are expanded using mechanism, and only if they appear literally in the clause, or as an argument to the meta-predicates not/1, call/1 or forall/2. A real predicate definition is required to deal with dynamically constructed calls.
%f
' is replaced by the name of the file to be loaded. The
resulting atom is called as a Unix command and the standard output of
this command is loaded. To use the Unix C preprocessor one should
define:
?- preprocessor(Old, '/lib/cpp -C -P %f'), consult(...). Old = none |
The features described in this section should be regarded alpha.
As of version 2.0.0, SWI-Prolog supports compilation of individual or
multiple Prolog sourcefiles into `Quick Load Files'. A `Quick Load
Files' (.qlf
file) stores the contents of the file in a
precompiled format very similar to compiled files created using the -b
and -c flags (see section 2.10).
These files load considerably faster than sourcefiles and are normally more compact. They are machine independent and may thus be loaded on any implementation of SWI-Prolog. Note however that clauses are stored as virtual machine instructions. Changes to the compiler will generally make old compiled files unusable.
Quick Load Files are created using qcompile/1.
They may be loaded explicitly using qload/1
or implicitly using consult/1
or one of the other file-loading predicates described in
section 3.2. If consult is given the explicit
.pl
file, it will load the Prolog source. When given the
.qlf
file, it will call qload/1
to load the file. When no extension is specified, it will load the .qlf
file when present and the fileextpl file otherwise.
library(LibFile)
and creates
a Quick Load File from File. The file-extension of this file
is .qlf
. The base name of the Quick Load File is the same
as the input file.
If the file contains `:- consult(+File)
' or `:-
[+File]
' statements, the referred files are compiled
into the same .qlf
file. Other directives will be stored in
the
.qlf
file and executed in the same fashion as when loading
the
.pl
file.
For term_expansion/2, the same rules as described in section 2.10 apply.
Source references (source_file/2) in the Quick Load File refer to the Prolog source file from which the compiled code originates.
consult(File)
iff File refers to a `Quick Load File'.