Abstracts

The following abstracts are meant to describe the functionality of each package, not to serve as documentation. Whatever documentation exists is included in comments within each package. Refer to lib-bas-dlp-acc to find out how to locate the source files if you wish to read the code comments. All the files abstracted in the following pages are found in the library directory.


library(aggregate)
defines aggregate/3, an operation similar to bagof/3, which lets you calculate sums. For example, given a table pupil(Name, Class, Age), to calculate the average age of the pupils in each class, one would write
          | ?- aggregate( sum(Age)/sum(1),
                          Name^pupil(Class, Name, Age),
                          Expr),
               call(Average_Age is Expr).
          

library(antiunify)
Anti-unification is the mathematical dual of unification: given two terms T1 and T2 it returns the most specific term that generalizes them, T. T is the most specific term that unifies with both T1 and T2. A common use for this is in learning; the idea of using it that way comes from Gordon Plotkin.

The code here is based on a routine called generalise/5 written by Fernando Pereira. The name was changed because there are other ways of generalizing things, but there is only one dual of unification.


anti_unify(+Term1, +Term2, -Term)
binds Term to a most specific generalization of Term1 and Term2. When you call it, Term should be a variable.
anti_unify(+Term1, +Term2, -Subst1, -Subst2, -Term)
binds Term to a most specific generalization of Term1 and Term2, and Subst1 and Subst2 to substitutions such that
                      Subst1(Term) = Term1
                      Subst2(Term) = Term2
               

Substitutions are represented as lists of Var=Term pairs, where Var is a Prolog variable, and Term is the term to substitute for Var. When you call anti_unify/5, Subst1, Subst2, and Term should be variables.


library(arity)
Provides support for Arity code translated by arity2quintus.
library(aritystring)
provides support for Arity's string operations.
library(aropen)
lets you open a member of a UNIX archive file (see UNIX ar(1)) without having to extract the member. You cannot compile or consult such a file, but you can read from it. This may be useful as an example of defining Prolog streams from C. Not available under Windows.
library(arrays)
provides constant-time access and update to arrays. It involves a fairly unpleasant hack. You would be better off using library(logarr) or library(trees).
library(assoc)
A binary tree implementation of "association lists".
library(avl)
AVL trees in Prolog.
library(bags)
provides support for the data type bag.
library(benchmark)
Users can easily obtain information about the performance of goals: time and memory requirements.
library(between)
provides routines for generating integers on backtracking.
library(big_text)
Defines a big_text data type and several operations on it. The point of this module is that when writing an interactive program you often want to display to (or acquire from) the user large amounts of text. It would be inadvisable (though possible) to store the text in Prolog's database. With this package you can store text in a file, copy text to a stream, acquire new text from a stream, and/or have Emacs edit a big text file. See the file big_text.txt in the library area for more details.
library(bitsets)
Operations on sets of integers (bitsets). Contains analogs for most operations in library(ordsets).
library(break)
Prints an error message and enters a break level (if possible), avoiding the problem of break/0 in QPC.
library(call)
provides a number of predicates that are useful in programs that pass goals as arguments.
library(caseconv)
is mainly intended as an example of the use of library(ctypes). Here you'll find predicates to test whether text is in all lowercase, all uppercase, or mixed-case, and to convert from one case to another.
library(charsio)
lets you open a list of character codes for input as a Prolog stream and, having written to a Prolog stream, collect the output as a list of character codes. There are three things you can do with library(charsio):
  1. You can open an input stream reading from a (ground) list of characters. This is the predicate chars_to_stream.
  2. You can run a particular goal with input coming from a (ground) list of characters. The predicates with_input_from_chars/[2,3] do this.
  3. You can run a particular goal with output going to a list of characters (the unification is done after the goal has finished). The with_output_to_chars/[2,3] predicates do this.

library(clump)
Group adjacent related elements of lists.
library(count)
The purpose is to count predicate calls. Instead of loading a program by calling compile/1, use count/1. The program will do what it always used to, except that it may run twice as slowly. The output of library(count) is a file that contains a record of predicate calls, and is suitable for processing by awk(1) or similar utilities.
library(critical)
provides a critical-region facility.
library(crypt)
defines two operations similar to open/3:

crypt_open(+FileName[, +Password, +Mode, -Stream)]

If you do not supply a Password, crypt_open/3 will prompt you for it. Note that the password will be echoed. If there is demand, this can be changed. The Stream will be clear text as far as Prolog is concerned, yet encrypted as far as the file system is concerned.

encrypt.c is a stand-alone program (which is designed to have its object code linked to three names: encrypt, decrypt, and recrypt), and can be used to read and write files using this encryption method.

This encryption method was designed, and the code was published, in Edinburgh, so it is available outside the USA.

library(decons)
provides a set of routines for recognizing and building Prolog control structures. The only predicate that is likely to be useful is prolog_clause(Clause, Head, Body).
library(demo)
Defines the demo file_search_path.
library(det)
Aids in determinacy checking by locating places where cuts are really necessary.
library(environ)
provides access to the operating system's environment variables. environ(?Varname, ?Value) is a genuine relation. Note that if you include this file in a saved state, the values of environment variables are those current when the saved state was run, not when it was saved. There is also an argv/1 in this file, which is superseded by unix(argv(_)).
library(environment)
Portability aid for UNIX (BSD, System V), Windows, VMS, VM/SP (CMS), MVS, MS-DOS, Macintosh.
library(expansion)
This library "takes over" term_expansion/2 and provides more powerful hooks that enable multiple, "simultaneously active" and recursive program transformations to be achieved in an effcient manner.
library(fft)
Performs a fast fourier transform in Prolog. This file was written to demonstrate that a FFT could be written in Prolog with the same O(N*log(N)) asymptotic cost as in Fortran. There are several easy things that could be done to make it faster, but you would be better off for numerical calculations like this using library(vectors) to call a Fortran subroutine.
library(filename)
Portable filename manipulation. Documentation on filename.txt.
library(flatten)
provides predicates for flattening binary trees into lists.
library(foreach)
defines two iteration forms.
          forall(Generator, Test)
          foreach(Generator, Test)
          

forall/2 is the standard double-negation "there is no proof of Generator for which Test is not provable", coded as \+ (Generator, \+ Test).

foreach/2 works in three phases: first each provable instance of Generator is found, then each corresponding instance of Test is collected in a conjunction, and finally the conjunction is executed.

If, by the time a Test is called, it is always ground -- apart from explicitly existentially quantified variables -- the two forms of iteration are equivalent, and forall/2 is cheaper. But if you want Test to bind some variables, you must use foreach/2.

library(freevars)
This is an internal support package. Users will probably have no direct use for it.
library(fromonto)
defines some "pretty" operators for input/output redirection. Examples:
          | ?- (repeat, read(X), process(X))
               from_file 'fred.dat'.
          
          | ?- read(X) from_chars "example. ".
          
          X = example
          
          | ?- write(273.4000) onto_chars X.
          
          X = "273.4"
          

library(gauss)
Gaussian elimination.
library(getfile)
defines get_file(+FileName, -ListOfLines), which reads an entire file into memory in one go.
library(graphs)
a collection of utilities for manipulating mathematical graphs. The collection is incomplete. Please let us know which operations in this collection are most useful to you, and which operations that you would find useful have not been included.

The P-representation of a graph is a list of (from-to) vertex pairs, where the pairs can be in an arbitrary order. This form is convenient for input and output.

The S-representation of a graph is a list of (vertex-neighbors) pairs, where the pairs are in standard order (as produced by keysort/2) and the neighbors of each vertex are also in standard order (as produced by sort/2). This form is convenient for many calculations.

See also library(mst) (lib-abs), which is soon to be merged into library(graphs).

library(heaps)
provides support for the data type heap (heaps are also known as priority queues).
library(knuth_b_1)
is a table of constants taken from Appendix B1 of D.E. Knuth's The Art of Computer Programming, Volume 1. The point is not to provide the constants -- you could have calculated them yourselves easily enough -- but to illustrate the recommended way of building such constants into your programs.
library(listparts)
exists to establish a common vocabulary for names of parts of lists among Prolog programmers.
library(lpa)
Compatibility library for LPA Prologs. See also quintus.mac, quintus.dec.
library(logarr)
is an implementation of "arrays" as 4-way trees. See also library(trees).
library(long)
This is a rational arithmetic package.

rational(N) recognizes arbitrary-precision rational numbers: this includes integers, infinity, neginfinity, & undefined. whole(N) recognizes arbitrary precision integers. eval(Expr, Result) evaluates an expression using arbitrary precision rational arithmetic; it does not accept floats at all. {eq,ge,gt,le,lt,ne}/2 are infix predicates like </2 that compare rationals (or integers, not expressions). succ/2, plus/3, and times/3 are relational forms of arithmetic, which work on rational numbers (not floats). To have rational numbers printed nicely, put the command

          :- assert((portray(X) :- portray_number(X)))
          

in your code. See long.doc and the comments in long.pl.

library(mapand)
provides mapping routines over &-trees. See also maplist.pl.
library(maplist)
is built on top of library(call), and provides a collection of meta-predicates for applying predicates to elements of lists.
library(maps)
implements functions over finite domains, which functions are represented by an explicit data structure.
library(menu)

illustrates how to drive the Emacs interface from Prolog. The sample application involves choosing items from a menu. See also the menu_example.pl program in the demo directory. Not available under Windows.

library(mst)
is a preliminary version of a minimal spanning tree package, that will eventually be merged into library(graphs).

library(mst) currently provides two predicates:


first_mst(+Nodes, +Cost, -Root, -MST)

mst(+Nodes, +Cost, -Root, -MST)
  • Nodes is a list of nodes.
  • Cost is a predicate that takes three extra arguments. A predicate from library(call), call(Cost, X, Y, Dist) calculates the distance Dist between nodes X and Y.
  • Root is the root of a minimal spanning tree and MST is a list of the arcs in that minimal spanning tree.

Please note: mst/4 has been carefully written so that it will find all the minimal spanning trees of a graph. mst/4 finds many trees, especially as it is blind to redundant representations of isomorphic trees. If you will be satisfied with any MST at all, use first_mst/4 instead. first_mst/4 will try to keep the arcs in the same order as the nodes if at all possible.


library(multil)
provides multiple-list routines.
library(newqueues)
provides support for the queue data type. The library(newqueues) package replaces library(queues), and should be used in new programs.
library(nlist)
Interface to the UNIX library function nlist(3). Not available under Windows.
library(note)
The built-in predicates and commands pertaining to the "recorded" (or "internal") database have an argument called the "key". All that matters about this key is its principal functor. That is, fred(a, b) and fred(97, 46) are regarded as the same key.

library(note) defines a complete set of storing, fetching, and deleting commands where the "key" is a ground term all of which is significant, using the existing recorded database. Note that this package is no better indexed than the existing recorded database.

library(order)
The usual convention for Prolog operations is INPUTS before OUTPUTS. The built-in predicate compare/3 violates this. This package provides an additional interface to provide comparison predicates with the usual order. The package contains predicates to compare numbers, terms, sets and ordered lists.
library(ordered)
is a collection of predicates for doing things with a list and an ordering predicate. See also library(ordsets) (lib-lis-ordsets), library(ordprefix) below, and library(samsort) (lib-abs).
library(ordprefix)
is for extracting initial runs from lists, perhaps with a user-supplied ordering predicate. See also library(ordered) above.
quintus.mac
version of lpa.pl to be used on Mac.
quintus.dec
version of lpa.pl to be used on DEC.
library(pipe)
Quintus streams may be connected to pipes using library(pipe), which provides a single predicate:

popen(+Command, +Mode, -Stream)
Mode may be either:

read
Stream will be bound to a new input stream, connected to the standard output of the Command. The standard input stream of the Command is left the same as the standard input stream of Prolog. So we have
                    user_input -> Command -> Stream
                    

write
Stream will be bound to a new output stream, connected to the standard input of the Command. The standard output stream of the Command is left the same as the standard output stream of Prolog. So we have
                    Stream -> Command -> user_output
                    

The behavior of popen/3 is defined by the system function popen(3S). There is no special pclose/1 command: the existing close/1 will call pclose(3S). Commands are executed by sh(1) under UNIX and by the default command interpreter under Windows, e.g. cmd.exe under Windows XP. Under Windows, the underlying popen() C library function, and therefore also popen/3, only works in console applications, e.g. in prolog but not in qpwin.

library(plot)
This package generates UNIX plot(5) files.
library(pptree)
This file defines pretty-printers for (parse) trees represented in the form
          <tree> --> <node label>/[<son>,...<son>]
                  |  <leaf label>         -- anything else
          

Two forms of output are provided: a human-readable form and a Prolog term form for reading back into Prolog.


pp_tree(+Tree)
prints the version intended for human consumption, and
pp_term(+Tree)
prints the Prolog-readable version.

There is a new command ps_tree/1, which prints trees represented in the form

          <tree> --> <node label>(<son>,...,<son>)
                  |  <leaf>               -- constants
          

The output of ps_tree/1 is readable by Prolog and people both. You may find it useful for things other than parse trees.

library(printchars)
extends portray/1 (using library(addportray)) so that lists of character codes are written by print/1, by the top level, and by the debugger, between double quotes.
          
          | ?- X = "fred".
          
          X = [102,114,101,100]
          
          | ?- use_module(library(printchars)),
               X = "fred".
          
          X = "fred"
          

library(printlength)
provides predicates for determining how wide a term would be if written.
library(putfile)
Uses C stream functions to copy the contents of a file to the the current output stream. This is the fastest known method for copying the contents of a file to the current output stream.
library(qerrno)
Defines error codes specific to Quintus Prolog, which do not have any standard errno assignment.
library(qsort)
provides a stable version of quicksort. Note that quicksort is not a good sorting method for a language like Prolog. If you want a good sorting method, see library(samsort) below.
library(queues)
provides support for the queue data type. This library has been made obsolete in release 3 by the introduction of library(newqueues). It is retained for backward compatibility, but should not be used in new programs.
library(random)
provides a random number generator and several handy interface routines. The random number generators supplied by various operating systems are all different. It is useful to have a random number generator that will give the same results in all versions of Quintus Prolog, and this is the one.
library(ranstk)
This is a Prolog implementation of the algorithms in Eugene W. Myers' An Applicative Random-Access Stack.
library(read)
This code was originally written at the University of Edinburgh. David H. D. Warren wrote the first version of the parser. Richard A. O'Keefe extracted it from the Dec-10 Prolog system and made it use only user-visible operations. He also added the feature whereby P(X,Y,Z) is read as call(P,X,Y,Z). Alan Mycroft reorganized the code to regularize the functor modes. This is easier to understand (there are no more ?s), and it also fixes bugs concerning the curious interaction of cut with the state of parameter instantiation. O'Keefe then took it over again and made a number of other changes.

There are three intentional differences between this library and the Dec-10 Prolog parser:


library(retract)
This file adds more predicates for accessing dynamic clauses and the recorded database. The built-in predicate retract/1 will backtrack through a predicate, expunging each matching clause until the caller is satisfied. This is not a bug. That is the way retract/1 is supposed to work. But it is also useful to have a version that does not backtrack.

library(retract) defines, among many other commands, retract_first/1, which is identical to retract/1 except that it expunges only the first matching clause, and fails if asked for another solution.

library(samsort)
provides a stable sorting routine, which exploits existing order, both ascending and descending. (It is a generalization of the natural merge.) samsort(Raw, Sorted) is like sort(Raw, Sorted) except that it does not discard duplicate elements. samsort(Order, Raw, Sorted) lets you specify your own comparison predicate, which the built-in sorting predicates sort/2 and keysort/2 do not. This file also exports two predicates for merging already-sorted lists: merge/3 and merge/4. See also library(ordered) and library(qsort).
library(setof)
provides additional predicates related to the built-in predicate setof/3. Note that the built-in predicates bagof/3 and setof/3 are much more efficient than the predicates in this file. See also library(findall).
library(show)
The built-in command listing/1 displays dynamic predicates. But there is no built-in command for displaying the terms recorded under a given key. library(show) defines two predicates: show(Key) displays all the terms recorded under the given Key, and show/0 displays all the Keys and terms in the recorded database.
library(showmodule)
provides a command for displaying information about a loaded module. show_module(Module) prints a description of the Module, what it exports, and what it imports. The command
          | ?- show_module(_), fail ; true.
          

will print a description of every loaded module. To backtrack through all current modules and print information about the predicates they define, import, and export, use

          | ?- ensure_loaded(library(showmodule)),
               show_module(Module).
          

To print information about a particular module m, use

          | ?- show_module(m).
          

library(statistics)
The full_statistics/[0,2] predicates are exactly like the built-in statistics/[0,2] predicates except that
library(stchk)
This package allows local style-check modifications in a file. This module provides an alternative interface to the style check flags. The idea is that a file that uses it will look like
              <usual heading>
          
              :- push_style.
              :- set_style(StyleFlag, Value).
              ...
          
              <clauses>
          
              :- pop_style.
          

Some combination of this with the existing style check interface will be safe: no matter what style check changes are made, the original values will be restored.

The initial state (assumed) is that all checks are ON.

library(terms)
The foreign code interface provides means of passing constants between Prolog and C, FORTRAN, Pascal, etc.

library(terms) lets you pass copies of terms from Prolog to C, and receive copies of terms from C. For example, the new built-in predicate copy_term/2 could have been defined this way:

          'copy term'(Term, Copy) :-
                  prolog_to_c(Term, Pointer_to_C_version),
                  c_to_prolog(Pointer_to_C_version, Temp),
                  erase_c_term(Pointer_to_C_version),
                  Copy = Temp.
          

The C code in terms.c is just as much a part of this package as the Prolog code. In particular, the comments in that file describe the representation used on the C side of the interface and there are routines and macros (see terms.h) for accessing terms-in-C.

library(termdepth)
Many resolution-based theorem provers impose a depth bound on the terms they create -- not least to prevent infinite loops. library(termdepth) provides predicates that find the depth, length and size of a term, which can even be used on cyclic terms.
library(tokens)
This package is a public-domain tokeniser in reasonably standard Prolog. It is meant to complement the library READ routine. It recognizes Dec-10 Prolog with the following exceptions:

BEWARE: this file does not recognize floating-point numbers.

library(trees)
is an implementation of arrays as binary trees.
library(types)
This file is support for the rest of the library, and is not really meant for general use. The type tests it defines are almost certain to remain in the library or to migrate to the system. The error checking and reporting code is certain to change. The library predicates must_be_compound/3, must_be_proper_list/3, must_be_var/3, and proper_list/1 are new in this release.
library(update)
provides utilities for updating "database" relations.
library(vectors)
The Quintus Prolog foreign code interface provides means of passing scalars between Prolog and C, FORTRAN, Pascal, etc.

library(vectors) provides routines you can use to pass one-dimensional numeric arrays between Prolog and C, Pascal, or FORTRAN. See the comments in the code. Briefly,


list_to_vector(+ListOfNumbers, +Type, -Vector)
creates a vector, which you can pass to C. C will declare the argument as Type*, and Prolog will declare the argument as +address(Type). FORTRAN will declare the argument as an array of Type.
make_vector(+Size, +Type, -Vector)
creates a vector, which the foreign routine is to fill in. C will declare the argument as Type*, and Prolog will declare the argument as +address(Type). FORTRAN will declare the argument as an array of Type.
vector_to_list(+Vector, ?List)
extracts the elements of the Vector as a list of numbers; if the Vector contains chars or ints, the List will contain integers, otherwise it will contain floating-point numbers.
kill_vector(+Vector)
frees a vector. Don't forget to do this! You can still call vector_to_list/2 on a dead vector, until the next time memory is allocated. All that you can really rely on is that it is safe to create some vectors, call a C routine, kill all the vectors, and then extract the contents of the interesting ones before doing anything else.

library(writetokens)
This package converts a term to a list of tokens. This is essentially the same as the public-domain write.pl, except that instead of writing characters to the current output stream, it returns a list of tokens. There are three kinds of tokens: punctuation marks, constants, and atoms. There is nothing to indicate spacing; the point of this package is to let the caller do such formatting.
library(xml)
is a package for parsing XML with Prolog, which provides Prolog applications with a simple "Document Value Model" interface to XML documents.