% This LaTeX document was generated using the LaTeX backend of PlDoc, % The SWI-Prolog documentation system \section{library(prolog_xref): Prolog cross-referencer data collection} \label{sec:prologxref} \begin{tags} \tag{See also} Where this library analyses \textit{source text}, \file{library(prolog_codewalk)} may be used to analyse \textit{loaded code}. The \file{library(check)} exploits \file{library(prolog_codewalk)} to report on e.g., undefined predicates. \tag{bug} \predref{meta_predicate}{1} declarations take the module into consideration. Predicates that are both available as meta-predicate and normal (in different modules) are handled as meta-predicate in all places. \end{tags} 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 \predref{gxref}{0}, and \file{library(prolog_colour)}, which exploits this library for its syntax highlighting. For all predicates described below, \arg{Source} is the source that is processed. This is normally a filename in any notation acceptable to the file loading predicates (see \predref{load_files}{2}). Input handling is done by the \file{library(prolog_source)}, which may be hooked to process any source that can be translated into a Prolog stream holding Prolog source text. \arg{Callable} is a callable term (see \predref{callable}{1}). Callables do not carry a module qualifier unless the referred predicate is not in the module defined by \arg{Source}.\vspace{0.7cm} \begin{description} \qpredicate[semidet,multifile]{prolog}{called_by}{4}{+Goal, +Module, +Context, -Called}True when \arg{Called} is a list of callable terms called from \arg{Goal}, handled by the predicate \arg{Module}:\arg{Goal} and executed in the context of the module \arg{Context}. Elements of \arg{Called} may be qualified. If not, they are called in the context of the module \arg{Context}. \qpredicate[multifile]{prolog}{called_by}{2}{+Goal, -ListOfCalled}If this succeeds, the cross-referencer assumes \arg{Goal} may call any of the goals in \arg{ListOfCalled}. If this call fails, default meta-goal analysis is used to determine additional called goals. \begin{tags} \tag{deprecated} New code should use \qpredref{prolog}{called_by}{4} \end{tags} \qpredicate[multifile]{prolog}{meta_goal}{2}{+Goal, -Pattern}Define meta-predicates. See the examples in this file for details. \qpredicate[multifile]{prolog}{hook}{1}{Goal}True if \arg{Goal} is a hook that is called spontaneously (e.g., from foreign code). \predicate[det]{xref_source}{1}{+Source} \nodescription \predicate[det]{xref_source}{2}{+Source, +Options} Generate the cross-reference data for \arg{Source} if not already done and the source is not modified. Checking for modifications is only done for files. \arg{Options} processed: \begin{description} \termitem{silent}{+Boolean} If \const{true} (default \const{false}), emit warning messages. \termitem{module}{+Module} Define the initial context module to work in. \termitem{register_called}{+Which} Determines which calls are registerd. \arg{Which} is one of \const{all}, \verb$non_iso$ or \verb$non_built_in$. \termitem{comments}{+CommentHandling} How to handle comments. If \const{store}, comments are stored into the database as if the file was compiled. If \const{collect}, comments are entered to the xref database and made available through \predref{xref_mode}{2} and \predref{xref_comment}{4}. If \const{ignore}, comments are simply ignored. Default is to \const{collect} comments. \termitem{process_include}{+Boolean} Process the content of included files (default is \const{true}). \end{description} \begin{arguments} \arg{Source} & File specification or XPCE buffer \\ \end{arguments} \predicate[det]{xref_clean}{1}{+Source} Reset the database for the given source. \predicate{xref_current_source}{1}{?Source} Check what sources have been analysed. \predicate[det]{xref_done}{2}{+Source, -Time} Cross-reference executed at \arg{Time} \predicate[nondet]{xref_called}{3}{?Source, ?Called, ?By} \nodescription \predicate[nondet]{xref_called}{4}{?Source, ?Called, ?By, ?Cond} \nodescription \predicate[nondet]{xref_called}{5}{?Source, ?Called, ?By, ?Cond, ?Line} True when \arg{By} is called from \arg{Called} in \arg{Source}. Note that \predref{xref_called}{3} and \predref{xref_called}{4} use \predref{distinct}{2} to return only distinct \verb$Called-By$ pairs. The \predref{xref_called}{5} version may return duplicate \verb$Called-By$ if \arg{Called} is called from multiple clauses in \arg{By}, but at most one call per clause. \begin{arguments} \arg{By} & is a head term or one of the reserved terms \verb$''(Line)$ or \verb$''(Line)$, indicating the call is from an (often \predref{initialization}{1}) directive or there is a \predref{public}{1} directive that claims the predicate is called from in some untractable way. \\ \arg{Cond} & is the (accumulated) condition as defined by \verb$:- if(Cond)$ under which the calling code is compiled. \\ \arg{Line} & is the \textit{start line} of the calling clause. \\ \end{arguments} \predicate[nondet]{xref_defined}{3}{?Source, +Goal, ?How} Test if \arg{Goal} is accessible in \arg{Source}. If this is the case, \arg{How} specifies the reason why the predicate is accessible. Note that this predicate does not deal with built-in or global predicates, just locally defined and imported ones. \arg{How} is one of of the terms below. Location is one of Line (an integer) or File:Line if the definition comes from an included (using \Sneck{} \verb$include(File)$) directive. \begin{shortlist} \item \verb$dynamic(Location)$ \item \verb$thread_local(Location)$ \item \verb$multifile(Location)$ \item \verb$public(Location)$ \item \verb$local(Location)$ \item \verb$foreign(Location)$ \item \verb$constraint(Location)$ \item \verb$imported(From)$ \item dcg \end{shortlist} \predicate{xref_definition_line}{2}{+How, -Line} If the 3th argument of xref_defined contains line info, return this in \arg{Line}. \predicate[nondet]{xref_exported}{2}{?Source, ?Head} True when \arg{Source} exports \arg{Head}. \predicate[nondet]{xref_module}{2}{?Source, ?Module} True if \arg{Module} is defined in \arg{Source}. \predicate[nondet]{xref_uses_file}{3}{?Source, ?Spec, ?Path} True when \arg{Source} tries to load a file using \arg{Spec}. \begin{arguments} \arg{Spec} & is a specification for \predref{absolute_file_name}{3} \\ \arg{Path} & is either an absolute file name of the target file or the atom \verb$$. \\ \end{arguments} \predicate[nondet]{xref_op}{2}{?Source, Op} Give the operators active inside the module. This is intended to setup the environment for incremental parsing of a term from the source-file. \begin{arguments} \arg{Op} & Term of the form \verb$op(Priority, Type, Name)$ \\ \end{arguments} \predicate[nondet]{xref_prolog_flag}{4}{?Source, ?Flag, ?Value, ?Line} True when \arg{Flag} is set to \arg{Value} at \arg{Line} in \arg{Source}. This is intended to support incremental parsing of a term from the source-file. \predicate[nondet]{xref_comment}{3}{?Source, ?Title, ?Comment} Is true when \arg{Source} has a section comment with \arg{Title} and \arg{Comment} \predicate[nondet]{xref_comment}{4}{?Source, ?Head, ?Summary, ?Comment} Is true when \arg{Head} in \arg{Source} has the given PlDoc comment. \predicate[nondet]{xref_mode}{3}{?Source, ?Mode, ?Det} Is true when \arg{Source} provides a predicate with \arg{Mode} and determinism. \predicate[nondet]{xref_option}{2}{?Source, ?Option} True when \arg{Source} was processed using \arg{Option}. Options are defined with \predref{xref_source}{2}. \predicate[semidet]{xref_meta}{3}{+Source, +Head, -Called} True when \arg{Head} calls \arg{Called} in \arg{Source}. \begin{arguments} \arg{Called} & is a list of called terms, terms of the form Term+Extra or terms of the form \Sidiv{}(Term). \\ \end{arguments} \predicate[semidet]{xref_meta}{2}{+Head, -Called} \nodescription \predicate[semidet]{xref_meta_src}{3}{+Head, -Called, +Src} True when \arg{Called} is a list of terms called from \arg{Head}. Each element in \arg{Called} can be of the form Term+Int, which means that Term must be extended with Int additional arguments. The variant \predref{xref_meta}{3} first queries the local context. \begin{tags} \tag{deprecated} New code should use \predref{xref_meta}{3}.\mtag{To be done}- Split predifined in several categories. E.g., the ISO predicates cannot be redefined. \\- Rely on the meta_predicate property for many predicates. \end{tags} \predicate{xref_hook}{1}{?Callable} Definition of known hooks. Hooks that can be called in any module are unqualified. Other hooks are qualified with the module where they are called. \predicate[semidet]{xref_public_list}{3}{+Spec, +Source, +Options} Find meta-information about File. This predicate reads all terms upto the first term that is not a directive. It uses the module and meta_predicate directives to assemble the information in \arg{Options}. \arg{Options} processed: \begin{description} \termitem{path}{-Path} \arg{Path} is the full path name of the referenced file. \termitem{module}{-Module} \arg{Module} is the module defines in \arg{Spec}. \termitem{exports}{-Exports} \arg{Exports} is a list of predicate indicators and operators collected from the \predref{module}{2} term and reexport declarations. \prefixtermitem{public}{\prefixterm{\Sminus}{\arg{Public}}} \arg{Public} declarations of the file. \termitem{meta}{-Meta} \arg{Meta} is a list of heads as they appear in \predref{meta_predicate}{1} declarations. \termitem{silent}{+Boolean} Do not print any messages or raise exceptions on errors. \end{description} 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. \begin{arguments} \arg{Source} & is the file from which \arg{Spec} is referenced. \\ \end{arguments} \predicate[semidet]{xref_public_list}{4}{+File, -Path, -Export, +Src} \nodescription \predicate[semidet]{xref_public_list}{6}{+File, -Path, -Module, -Export, -Meta, +Src} \nodescription \predicate[semidet]{xref_public_list}{7}{+File, -Path, -Module, -Export, -Public, -Meta, +Src} Find meta-information about \arg{File}. This predicate reads all terms upto the first term that is not a directive. It uses the module and meta_predicate directives to assemble the information described below. These predicates fail if \arg{File} is not a module-file. \begin{arguments} \arg{Path} & is the canonical path to \arg{File} \\ \arg{Module} & is the module defined in \arg{Path} \\ \arg{Export} & is a list of predicate indicators. \\ \arg{Meta} & is a list of heads as they appear in \predref{meta_predicate}{1} declarations. \\ \arg{Src} & is the place from which \arg{File} is referenced. \\ \end{arguments} \begin{tags} \tag{deprecated} New code should use \predref{xref_public_list}{3}, which unifies all variations using an option list. \end{tags} \predicate[semidet]{xref_source_file}{3}{+Spec, -File, +Src} \nodescription \predicate[semidet]{xref_source_file}{4}{+Spec, -File, +Src, +Options} Find named source file from \arg{Spec}, relative to \arg{Src}. \end{description}