This library collects information on defined and used objects in Prolog source files. Typically these are predicates, but we expect the library to deal with other types of objects in the future. The library is a building block for tools doing dependency tracking in applications. Dependency tracking is useful to reveal the structure of an unknown program or detect missing components at compile time, but also for program transformation or minimising a program saved state by only saving the reachable objects.
The library is exploited by two graphical tools in the SWI-Prolog
environment: the XPCE front-end started by gxref/0,
and
library(prolog_colour)
, which exploits this library for its
syntax highlighting.
For all predicates described below, Source is the source
that is processed. This is normally a filename in any notation
acceptable to the file loading predicates (see load_files/2).
Input handling is done by the library(prolog_source)
, which
may be hooked to process any source that can be translated into a Prolog
stream holding Prolog source text.
Callable is a callable term (see callable/1).
Callables do not carry a module qualifier unless the referred predicate
is not in the module defined by Source.
true
(default false
), emit warning
messages.
all
, non_iso
or non_built_in
.
store
, comments are stored into
the database as if the file was compiled. If collect
,
comments are entered to the xref database and made available through xref_mode/2
and xref_comment/4.
If ignore
, comments are simply ignored. Default is to collect
comments.
true
).
Source | File specification or XPCE buffer |
Called-By
pairs. The xref_called/5
version may return duplicate Called-By
if Called
is called from multiple clauses in
By, but at most one call per clause.
By | is a head term or one of the reserved
terms
'<directive>'(Line) or '<public>'(Line) ,
indicating the call is from an (often initialization/1)
directive or there is a public/1
directive that claims the predicate is called from in some untractable
way. |
Cond | is the (accumulated) condition as
defined by
:- if(Cond) under which the calling code is compiled. |
Line | is the start line of the calling clause. |
:-
include(File)
) directive.
dynamic(Location)
thread_local(Location)
multifile(Location)
public(Location)
local(Location)
foreign(Location)
constraint(Location)
imported(From)
Spec | is a specification for absolute_file_name/3 |
Path | is either an absolute file name of the
target file or the atom <not_found> . |
Op | Term of the form op(Priority, Type, Name) |
Called | is a list of called terms, terms of
the form Term+Extra or terms of the form // (Term). |
Public-
The information collected by this predicate is cached. The cached data is considered valid as long as the modification time of the file does not change.
Source | is the file from which Spec is referenced. |
These predicates fail if File is not a module-file.
Path | is the canonical path to File |
Module | is the module defined in Path |
Export | is a list of predicate indicators. |
Meta | is a list of heads as they appear in meta_predicate/1 declarations. |
Src | is the place from which File is referenced. |