Did you know ... Search Documentation:
pce_xref.pl -- Cross-referencer front-end
PublicShow source

XPCE based font-end of the Prolog cross-referencer. Tasks:

  • Cross-reference currently loaded program OK
  • Generate module-dependency graph OK
  • Information on
    • Syntax and other encountered errors
    • Export/Import relation between modules OK
    • Undefined predicates OK
    • Unused predicates OK
  • Summary information
    • Syntax and other encountered errors
    • Exports never used (not for libs!)
    • Undefined predicates
    • Unused predicates
  • Export module import and export header
See also
- library(prolog_xref) holds the actual data-collection.
bug
- Tool produces an error if a file that has been xref'ed is deleted. Paulo Moura.
Source gxref
Start graphical cross-referencer on loaded program. The GUI is started in the XPCE thread.
Source dep_source(?Src)[private]
Generate all sources for the dependecy graph one-by-one.
 append_io_callable(+Popup, -ImportFile, +Callable)[private]
Source export_link(+ExportingFile, -ImportingFile, -Callables) is det[private]
export_link(-ExportingFile, +ImportingFile, -Callables) is det[private]
Callables are exported from ExportingFile to ImportingFile.
Source text_to_regex(+Pattern, -Regex) is semidet[private]
Convert text to a regular expression. Fail if the text does not represent a valid regular expression.
Source exported_to(+ExportFile, +Callable, -ImportFile)[private]
ImportFile imports Callable from ExportFile. The second clause deals with auto-import.

TBD: Make sure the autoload library is loaded before we begin.

Source single_qualify(+Term, -Qualified)[private]
Strip redundant M: from the term, leaving at most one qualifier.
Source used_in(+Source, +QCallable, -CalledBy)[private]
Determine which the callers for QCallable in Source. QCallable is qualified with the module of the exporting file (if any).
Source short_file_name_to_atom(+ShortId, -Atom)[private]
Convert a short filename into an atom
Source library_file(+Path)[private]
True if Path comes from the Prolog tree and must be considered a library.
Source profile_file(+Path)[private]
True if path is a personalisation file. This is a bit hairy.
Source sort_files(+Files, -Sorted)[private]
Sort files, keeping groups comming from the same alias together.
Source available(+File, +Callable, -HowDefined)[private]
True if Callable is available in File.
Source built_in_predicate(+Callable)[private]
True if Callable is a built-in
Source autoload_predicate(+Callable) is semidet[private]
Source autoload_predicate(+Callable, -File) is semidet[private]
True if Callable can be autoloaded. TBD: make sure the autoload index is up-to-date.
Source global_predicate(+Callable)[private]
True if Callable can be auto-imported from the global user module.
Source to_predicate_indicator(+Term, -PI)[private]
Convert to a predicate indicator.
Source is_predicate_indicator(+PI) is semidet[private]
True if PI is a predicate indicator.
Source predicate_indicator(+Callable, -Name)[private]
Generate a human-readable predicate indicator
Source sort_callables(+List, -Sorted)[private]
Sort list of callable terms.
Source ord_list_to_set(+OrdList, -OrdSet)[private]
Removed duplicates (after unification) from an ordered list, creating a set.
Source callable_to_label(+Callable, +File, -Label:atom) is det[private]
Source callable_to_label(+Callable, -Label:atom) is det[private]
Label is a textual label representing Callable in File.
Source edit_callable(+Callable, +File)[private]
Source file_warnings(+File:atom, -Warnings:list(atom))[private]
Unify Warnings with a list of dubious things found in File. Intended to create icons. Fails if the file is totally ok.
Source not_called(+File, -Callable)[private]
Callable is a term defined in File, and for which no callers can be found.
Source xref_called(?Source, ?Callable) is nondet[private]
True if Callable is called in Source, after removing recursive calls and calls made to predicates where the condition says that the predicate should not exist.
Source defined(?File, ?Callable)[private]
True if Callable is defined in File and not imported.
Source undefined(+File, -Callable)[private]
Callable is called in File, but no definition can be found. If File is not a module file we consider other files that are not module files.
Source included_if_defined(+Condition, +Callable) is semidet[private]
 file_imports(+File, -Imports)[private]
Determine which modules must be imported into this one. It considers all called predicates that are not covered by system predicates. Next, we have three sources to resolve the remaining predicates, which are tried in the order below. The latter two is dubious.
  • Already existing imports
  • Imports from other files in the project
  • Imports from the (autoload) library

We first resolve all imports to absolute files. Localizing is done afterwards. Imports is a list of

use_module(FileSpec, Callables)
Source resolve(+Callable, -File)[private]
Try to find files from which to resolve Callable.
Source merge_by_key(+KeyedList, -ListOfKeyValues) is det[private]
Example: [a-x, a-y, b-z] --> [a-[x,y], b-[z]]
Source make_import(+RefFile, +ImportList, -UseModules)[private]
Glues it all together to make a list of directives.
Source xref_file_exports(+File, -Exports)
Produce the export-header for non-module files. Fails if the file is already a module file.

Undocumented predicates

The following predicates are exported, but not or incorrectly documented.

Source xref_file_imports(Arg1, Arg2)