This section deals with loading Prolog source-files. A Prolog source file is a plain text file containing a Prolog program or part thereof. Prolog source files come in three flavours:
Prolog source-files are located using absolute_file_name/3 with the following options:
locate_prolog_file(Spec, Path) :-
        absolute_file_name(Spec,
                           [ file_type(prolog),
                             access(read)
                           ],
                           Path).
The file_type(prolog) option is used to determine the 
extension of the file using prolog_file_type/2. 
The default extension is
.pl. Spec allows for the path-alias 
construct defined by absolute_file_name/3. 
The most commonly used path-alias is library(LibraryFile). 
The example below loads the library file ordsets.pl 
(containing predicates for manipulating ordered sets).
:- use_module(library(ordsets)).
SWI-Prolog recognises grammar rules (DCG) as defined in Clocksin & Melish, 1987. The user may define additional compilation of the source file by defining the dynamic predicates term_expansion/2 and goal_expansion/2. Transformations by term_expansion/2 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.22It does work for normal loading, but not for qcompile/1.
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 (default false), indicate this load is 
a
demand load. This implies that, depending on the setting of the 
Prolog flag verbose_autoload 
the load-action is printed at level informational or silent. 
See also print_message/2 
and current_prolog_flag/2.true, run the filenames through expand_file_name/2 
and load the returned files. Default is false, except for consult/1 
which is intended for interactive use. Flexible location of files is 
defined by file_search_path/2.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.all and the file is a module file, import all public 
predicates. Otherwise import only the named predicates. Each predicate 
is referred to as <name>/<arity>. This 
option has no effect if the file is not a module file.true, raise an error if the file is not a module file. 
Used by
use_module/[1,2].true, the contents of the argument files 
are included in the .qlf file instead of the loading 
directive.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. This option writes the Prolog flag
verbose_load 
with the negation of Bool.This option is added to allow compiling from non-file locations such as databases, the web, the user (see consult/1) or other servers.
The load_files/2 
predicate can be hooked to load other data or data from other objects 
than files. See prolog_load_file/2 
for a description and
library(http_load) for an example.
 ,  <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 loadorload.pl | 
| ?- [library(quintus)]. | % load Quintus compatibility library | 
| ?- [user]. | 
The predicate consult/1 
is equivalent to load_files(Files, []), except for handling the special 
file user, which reads clauses from the terminal. See also 
the stream(Input) option of load_files/2.
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(not_loaded)]).23On older versions the condition used to be if(changed). Poor time management on some machines or due to copying often caused problems. The make/0 predicate deals with updating the running system after changing the source code.
:- include(File) appears. The include construct is only 
honoured if it appears as a directive in a source-file. Normally
File contains a sequence of directives.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 it 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. The predicate make/0 
is called after
edit/1, 
automatically reloading all modified files. It the user uses an external 
editor (in a separate window), make/0 
is normally used to update the program after editing. In addition, make/0 
updates the autoload indices (see section 
2.13) and runs list_undefined/0 
from the library(check) library to report on undefined 
predicates../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, '/usr/lib/prolog/demo').
the file specification demo(myfile) will be expanded to
/usr/lib/prolog/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) :-
        current_prolog_flag(home, Home).
user:file_search_path(foreign, swi(ArchLib)) :-
        current_prolog_flag(arch, Arch),
        atom_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].
The Prolog flag verbose_file_search 
can be set to true to help debugging Prolog's search for 
files.
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) :-
        current_prolog_flag(associate, Ext),
        Ext \== pl.
user:prolog_file_type(qlf,      qlf).
user:prolog_file_type(Ext,      executable) :-
        current_prolog_flag(shared_object_extension, Ext).
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.
| Key | Description | 
| module | Module into which file is loaded | 
| source | File loaded. Returns the 
original Prolog file when loading a .qlffile. Compatible 
to SICStus Prolog. | 
| file | Currently equivalent to file. 
In future versions it may report a different values for files being 
loaded using include/1. | 
| stream | Stream identifier (see current_input/1) | 
| directory | Directory in which File lives. | 
| dialect | Compatibility mode. See expects_dialect/1. | 
| term_position | Position of last term read. Term of the form '$stream_position'(0,<Line>,0,0,0). See also stream_position_data/3. | 
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.ISO Prolog defines no way for program transformation such as macro expansion or conditional compilation. Expansion through term_expansion/2 and expand_term/2 can be seen as part of the de-facto standard. This machanism can do arbitrary translation between valid Prolog terms read from the source file to Prolog terms handed to the compiler. As term_expansion/2 can return a list, the transformation does not need to be term-to-term.
Various Prolog dialects provide the analogous goal_expansion/2 and expand_goal/2, that allow for translation of individual body terms, freeing the user of the task to disassemble each clause.
'$source_location'(<File>, <Line>):<Clause>
When compiling a module (see chapter 
5 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 term_expansion/2 
in module
user. 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. If Goal is of the form Module:Goal 
where Module is instantiated,
goal_expansion/2 
is called on Goal using rules from module
Module followed by user.
Only goals appearing 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, once/1, ignore/1, findall/3, bagof/3, setof/3 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 
standard output of resulting command is loaded. To use the Unix C 
preprocessor one should define:
?- preprocessor(Old, '/lib/cpp -C -P %f'), consult(...). Old = none
Using cpp for Prolog preprocessing is not ideal as the tokenization rules for comment and quoted strings differ between C and Prolog. Another problem is availability and compatibility with regard to option processing of cpp.
Conditional compilation builds on the same principle as term_expansion/2, goal_expansion/2 and the expansion of grammar rules to compile sections of the source-code conditionally. One of the reasons for introducing conditional compilation is to simplify writing portable code. See section C for more information. Here is a simple example:
:- if(\+source_exports(library(lists), suffix/2)).
suffix(Suffix, List) :-
        append(_, Suffix, List).
:- endif.
Note that these directives can only be appear as separate terms in the input. Typical usage scenarios include:
:- if(test1). section_1. :- elif(test2). section_2. :- elif(test3). section_3. :- else. section_else. :- endif.
Traditionally, Prolog environments allow for reloading files holding currently active code. In particular, the following sequence is valid use of the development environment:
Goals running during the reload keep running on the old definition, while new goals use the reloaded definition, which is why the retry must be used after the reload. This implies that clauses of predicates that are active during the reload cannot be reclaimed. Normally a small amount of dead clauses should not be an issue during development. Such clauses can be reclaimed with garbage_collect_clauses/0.
As of version 5.5.30, there is basic thread-safety for reloading source files while other threads are executing code defined in these source files. Reloading a file freezes all threads after marking the active predicates originating from the file being reloaded. The threads are resumed after the file has been loaded. In addition, after completing loading the outermost file the system runs garbage_collect_clauses/0.
What does that mean? Unfortunately it does not mean we can `hot-swap' modules. Consider the case where thread A is executing the recursive predicate P. We `fix' P and reload. The already running goals for P continue to run the old definition, but new recursive calls will use the new definition! Many similar cases can be constructed with dependent predicates.
It provides some basic security for reloading files in multi-threaded applications during development. In the above scenarios the system does not crash uncontrolled, but behaves like any broken program: it may return the wrong bindings, wrong truth value or raise an exception.
Future versions may have an `update now' facility. Such as facility can be implemented on top of the logical update view. It would allow threads to do a controlled update between processing independent jobs.
SWI-Prolog supports compilation of individual or multiple Prolog 
source files into `Quick Load Files'. A `Quick Load Files' (.qlf 
file) stores the contents of the file in a precompiled format.
These files load considerably faster than source files 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 are loaded using
consult/1 
or one of the other file-loading predicates described in
section 4.3. If consult is 
given the explicit .pl file, it will load the Prolog 
source. When given the .qlf file, it will load the file. 
When no extension is specified, it will load the
.qlf file when present and the .pl file 
otherwise.
library(LibFile) and, in 
addition to the normal compilation, 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)', `:- 
[+File]' or :- load_files(+File, 
[qcompile(true), ...]) 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.
Conditional execution or optimisation may test the predicate compiling/0.
Source references (source_file/2) in the Quick Load File refer to the Prolog source file from which the compiled code originates.