Path: utzoo!utgpu!news-server.csri.toronto.edu!bonnie.concordia.ca!thunder.mcrcim.mcgill.edu!snorkelwacker.mit.edu!apple!agate!ucbvax!vax.oxford.ac.uk!POPX
From: POPX@vax.oxford.ac.uk (Jocelyn Paine)
Newsgroups: comp.lang.prolog
Subject: Library of AI software
Message-ID: <9101152355.AA11097@ucbvax.Berkeley.EDU>
Date: 15 Jan 91 23:50:00 GMT
Sender: daemon@ucbvax.BERKELEY.EDU
Lines: 2373

Newsgroups: comp.lang.prolog
Subject: Library of AI software
Summary:
Expires:
Sender:
Reply-To: popx@vax.ox.ac.uk (Jocelyn Paine)
Followup-To:
Distribution: comp.lang.prolog
Organization: Experimental Psychology, Oxford University, UK.                
Keywords:

I recently announced that I had started a library of Prolog software
(intended to be for AI), and was willing to extend it to cover AI stuff
in other languages too. This is a copy of the current catalogue. So far,
all the entries are still Prolog, but I will take contributions in other
languages.

Please mail to POPX if you want to request or (please!) to contribute.

                                   Jocelyn Paine (POPX @ UK.AC.OX.VAX)
                            Experimental Psychology, Oxford University



0. LIBRARY CATALOGUE - CONTENTS
===============================

0. Contents.

1. Introduction.

2. How to receive entries.

   2.1 - by E-mail.

   2.2 - by floppy disc.

3. Description of entries.

   3.1  Prolog abstract syntax notation translator.
        Written by C.D. Farris and P. Singleton, University of Keele.

   3.2  Prolog transition net interpreter.
        Written by Jocelyn Paine, Oxford University.

   3.3  Prolog predicate auto-tester.
        Written by Jocelyn Paine, Oxford University.

   3.4  Grips/Prolog demonstration mini-compiler.
        Contributed by Jocelyn Paine, Oxford University.

   3.5  Prolog programming consultant.
        Written by Edouard Lagache, Berkeley.

   3.6  Prolog utilities.
        Written by John Cugini, National Bureau of Standards.

   3.7  Prolog definite clause translation grammar translator.
        Contributed by Jocelyn Paine, Oxford University.

   3.8  Prolog doubly-linked list package.
        Contributed by Philip Dart, Melbourne University.

   3.9  Prolog expert system for forestry management.
        Contributed by Steve Jones, Reading University.

   3.10 Prolog grammar-rule translator.
        Contributed by Jocelyn Paine, Oxford University.

   3.11 Prolog graph-handling routines.
        Written by Paul Freedman, CNRS.

   3.12 Grips - a functional language in Prolog.
        Written by Jocelyn Paine, Oxford University.

   3.13 Prolog interval-algebra predicates.
        Written by Jocelyn Paine, Oxford University.

   3.14 Prolog iterative deepening interpreter.                     
        Written be Lee Naish.

   3.15 Prolog list-handling predicates.
        Contributed by J.G. Forero, Reading University.

   3.16 Linger - a natural language corrector and teacher in Prolog.
        Contributed by Paul O'Brien and Masoud Yazdani, Exeter University.

   3.17 Prolog operator tests.
        Written by Chris Moss, Dept. of Computing, Imperial College.

   3.18 Prolog naive reverse benchmark.
        Contributed by Norbert Fuchs.

   3.19 Pereira's Prolog benchmarks.
        Written by Fernando Pereira.

   3.20 Plaisted's theorem prover in Prolog.
        Written by David A. Plaisted.

   3.21 Prolog object-oriented package.
        Written by Ben Staveley-Taylor.

   3.22 Prolog expert system building tool.
        Contributed by Steven Salvini, Heriot-Watt University.

   3.23 Shapiro's Prolog debugger.
        Written by E. Y. Shapiro.

   3.24 Prolog file separator.
        Written by Jocelyn Paine, Oxford University.

   3.25 Prolog static call analyser.
        Contributed by John Cugini, National Bureau of Standards.

   3.26 The Edinburgh Tools.
        Contributed by the AI Applications Institute, Edinburgh.

   3.27 Prolog turtle graphics.
        Contributed by Salleh Mustaffa, University of Manchester.

   3.28 Prolog type-checker.
        Contributed by R.A.O'Keefe.

   3.29 Structures in Prolog.
        Written by Jean G. Vaucher,
        De'partement d' informatique et R.O., Universite' de Montre'al.

   3.30 Prolog cursor-addressing predicates.
        Written by Jocelyn Paine, Oxford University.


1. INTRODUCTION.
================

Each entry in the catalogue is headed by: a title; the name of the
contributor - and author if different; and the dates when I received the
contribution.

There is then a description of the program. Unless I've said otherwise,
these are the author's comments, and not mine; so the style is not at
all uniform between entries.

Finally, I've put the entry's size; what happened when I tried running
it; and an evaluation of its portability and documentation. Entries
which consist of more than one file are noted - see the next section.


2. HOW TO RECEIVE ENTRIES.
==========================

I can send either by E-mail (if you are on a network connected to the UK
academic network Janet), or by IBM PC floppy. The two sections below
describe how to deal with each.

In both cases, each entry includes a file whose extension is .PRE. This
is like the catalogue entries but more detailed. It lists the names of
the files supplied; gives comments on portability and documentation; and
tells how to run the program.


2.1 BY E-MAIL.
==============

If the mail link to a subscriber seems reliable enough, I'll send files
individually, one per message.

Otherwise, to avoid having to re-send lots of separate lost files, I'll
pack files into a composite file. The composite file will consist of two
or more subfiles, each of this form:

    
zero or more times The header line of a subfile is of the form ^START^ ^ where is a sequence of characters which is unlikely to appear in any source text, namely: )(*&%$#@! at the beginning of a line. is the name of the file from which the subfile was made. The tailer line is ^END^ ^ Here is an example containing two subfiles (indented by four spaces): )(*&%$#@!^START^APPEND.TXT^ This entry contains a predicate called 'append' which joins two lists to give a third. )(*&%$#@!^END^APPEND.TXT^ )(*&%$#@!^START^APPEND.PL^ /* APPEND.PL */ append( [], L, L ) :- !. append( [H|T], L, [H|T1] ) :- append( T, L, L1 ), !. )(*&%$#@!^END^APPEND.PL^ It should be simple to separate out subfiles with a text editor. Also, one of the library entries is a program which reads a composite file, and copies each subfile to the file named in its header. 2.2 BY MS-DOS FLOPPY. ===================== There is a small charge to pay for floppies, postage, and packing. Unless otherwise requested, entries will be sent as "archive files", packed by the public domain program ARC. There will be one such archive file for each catalogue entry. To unpack it, run the program PKXARC.EXE, which I have also copied onto your disc. For example, if you have ordered the Edinburgh tools, they will be packed into TOOLS.ARC. Assuming this file, and PKXARC.EXE, are both in your current directory, do: PKXARC TOOLS Note that MS-DOS truncates filenames to eight characters and replaces _ by X; so some names will not be the same as in the .PRE file for that entry. 3. DESCRIPTION OF ENTRIES. ========================== ======================================================================== ABSTRACT SYNTAX NOTATION TRANSLATOR Contributed by C.D. Farris and P. Singleton, University of Keele Received on the 25th of July 1989 Shelved on the 14th of November 1989 Abstract Syntax Notation is a formalism for describing language syntax. Grammars are written as Prolog terms, and compiled into an optimised Definite Clause Grammar. ASN is described in "The compilation of metalanguages into Prolog", by C.D. Farris and P. Singleton, University Computing, vol 11, no 2, pp 62-75. The article includes a listing of the code, which is what makes up this entry. SIZE: 77 kilobytes. CHECKED ON EDINBURGH-COMPATIBLE (POPLOG) PROLOG : yes. The original version used some Quintus-specific predicates, mainly for I/O. I have replaced these by calls to Edinburgh Prolog predicates. PORTABILITY : Source includes % comments. There are also some long character lists (i.e. "..." strings) which have been broken over more than one line. How these are denoted will be system-dependent. INTERNAL DOCUMENTATION : Each predicate comes with a brief description of its purpose. The theory behind ASN is not described in the program, but you can get it from the original article. ======================================================================== PROLOG TRANSITION NET INTERPRETER Contributed by Jocelyn Paine, Oxford University. Shelved on the 11th of January 1991 This is for those occasions when you need to represent a program as a network of labels and gotos, perhaps because you're interpreting a finite-state machine. The entry defines predicates for loading and interpreting such networks. Here is an example network: go :: to count(1). count(10) :: write( 'Done.' ), nl to success. count(N) :: write( 'N = ' ), write( N ), write('.'), nl, Rem is N mod 2 to odd(N) if Rem=1 to even(N). odd(N) :: write( 'That is even.' ), nl to inc(N). even(N) :: write( 'That is odd.' ), nl to inc(N). inc(N) :: Ni is N+1 to count(Ni). To run it, you would load it, and then call ?- do_node( go ). SIZE : 14 kilobytes. CHECKED ON EDINBURGH-COMPATIBLE (POPLOG) PROLOG : yes. PORTABILITY : should be no problems. INTERNAL DOCUMENTATION : as program comments. ======================================================================== PROLOG PREDICATE AUTO-TESTER Jocelyn Paine Shelved on the 21st of December 1987 This program reads a file or files of Prolog goals, where each goal is accompanied by a specification saying whether it should succeed, fail, cause an error, or pass some tests on its bound variables. For each goal/specification pair, the program calls the goal, and compares its effect against the specification. If they differ, then a warning message is displayed. This is useful for automatically testing predicates against their expected outputs - the test files can be kept, and re-run every time a predicate is changed. As an example, a test file for 'functor', and good old 'append' and 'member' might contain these lines: append( [], [1,2,3], [1,2,3] ) :: succeeds. append( [1,2,3], [], [1,2,3] ) :: succeeds. append( [1,2], [3,4,5], [1,2,3,4,5] ) :: succeeds. member( any, [] ) :: fails. member( any, [a,b,c,d,e,any] ) :: succeeds. member( any, [a,b,c,d,e] ) :: fails. functor( f(1,2), F, A ) :: F = f, A = 2. SIZE : 17 kilobytes. CHECKED ON EDINBURGH-COMPATIBLE (POPLOG) PROLOG : yes. PORTABILITY : Easy, except possibly for trapping errors during testing. INTERNAL DOCUMENTATION : Comments for each predicate, sample output. ======================================================================== GRIPS/PROLOG DEMONSTRATION MINI-COMPILER Contributed by Jocelyn Paine, Oxford University. Shelved on the 11th of January 1991 This is a demonstration compiler, written in a functional language (GRIPS) that can be translated into Prolog. The GRIPS translator is available as another library entry. The compiler takes programs in a (very small) subset of Pascal. It lexically analyses them into tokens, parses the token list into a tree, generates code from the tree, fixes up references in the code, and then interprets the code on a stack virtual machine. It displays the output of each stage, and the interpreter displays the machine state as each instruction is obeyed. The compiler is written in a functional style, using functions (sometimes represented as sets of domain->codomain pairs) to represent well-known concepts in programming language semantics, such as the store and the environment. I wrote it to explain in his own idiom, compiling to a mathematician starting a computer science M.Sc. Here is an example program that it can compile and run. program p; label 99, 100; const five = 5; var v : integer; w : integer; begin write('Hello.'); v := 1; w := 1; 99: if v=five then goto 100; v := v + 1; w := w * v; goto 99; 100: write('v = '); write(v); write('v! = '); write(w) end. SIZE : 55 kilobytes. CHECKED ON EDINBURGH-COMPATIBLE (POPLOG) PROLOG : yes. PORTABILITY : should be no problems. INTERNAL DOCUMENTATION : as program comments. ======================================================================== PROLOG PROGRAMMING CONSULTANT Written by Edouard Lagache, Berkeley Received via Prolog Digest V6 #28 Shelved on the 3rd of October 1988 This program is intended to serve as a "intelligent consultant" for PROLOG programs to turn to when encountering some impasse in a programming project. The program is based on the "Eliza" program, but it designed to provide comments that might foster the user to "solve" his or her own problem. (Copyright(C) 1988, The PROLOG Forum). The "assistant" was demonstrated at the March 10 meeting of the PROLOG Forum. The program is the result of 3 late night work, and NO claims of correctness or efficiency are expressed on implied. On the contrary, suggestions for expansion or improvement are most welcome. As stated earlier, it is hoped to turn this program into a group project, so we hope that there is plenty of room for expansion! There are some calls to my imfamous PROLOG libraries. The 'window' and 'set_attribute' calls will only work on a Texas Instruments PC, so I leave it to you to omit, or port these calls to your system. Hack to your hearts delight! [EL]. I've removed calls to non-portable windowing predicates, added the definition of member/2 (which was needed by intersection/3), re-formatted the source, and dropped a non-portable call from get_seed/1. [JNP]. SIZE: 28 kilobytes. CHECKED ON EDINBURGH-COMPATIBLE (POPLOG) PROLOG : Yes. PORTABILITY : irandom and get_seed, in the random-number generator, may need altering. INTERNAL DOCUMENTATION : Each predicate is commented with its purpose. ======================================================================== PROLOG UTILITIES Written by John Cugini, National Bureau of Standards This version sent by John Cugini, and shelved on the 30th of July, 1988 Original version (sent by Bert Shure, The SHURE Group) shelved on the 12th of December 1987 This file contains various utility predicates, some commonly used, some not. They deal with lists, structures, I/O, sets, numeric facilities, and some extensions of logic and control. This library is written in and for the C-Prolog dialect of Prolog. The overall organization of the library is: Basic predicates Lists Structures Input/Output Sets Numeric Control Extended Logic [John Cugini] Predicates include: member; append; maplist; other list-handling predicates; predicates for handling sets represented as lists; type-testing predicates; sorting and merging; readline; a predicate for getting the printable representation of a term; rational number predicates; meta-logical predicates for dealing with true disjunction and negation. I have altered the original library so that %% comments are replaced by /* */ [JNP] SIZE : 68 kilobytes. CHECKED ON EDINBURGH-COMPATIBLE (POPLOG) PROLOG : yes. PORTABILITY : Easy. I've documented possible problems at the head of the source file. DOCUMENTATION : A comment for each main predicate, specifying its declarative reading, and which arguments must be instantiated. ======================================================================== Definite Clause Translation Grammar Translator Contributed by Jocelyn Paine Shelved on the 21st of July 1990 Definite Clause Translation Grammars are described in chapter 9 of "Logic Grammars", by H.Abramson and V.Dahl (Springer 1989). They were devised by Abramson to overcome the defects of Definite Clause Grammars, in which syntax and semantics are often mixed in a non-modular fashion. They avoid also the proliferation of unnamed arguments that aflicts Definite Clause Grammars. In a DCTG, the syntax and semantics are separated. Each rule contains first a syntactic part, and then an optional semantics, written as one or more clauses. See below for an example, and "Logic Grammars" for more details. Most of the code in this entry comes from Appendix II of "Logic Grammars". I have made a few minor changes and added a predicate for loading grammars from file. There follows an example, for parsing binary numbers with binary points (such as 1.1 or 1001.11) when expressed as lists ([1,'.',1] or [1,0,0,1,'.',1,1]). bit ::= [0] <:> bitval( 0, _ ). bit ::= [1] <:> bitval( V,Scale ) ::- V is **(2,Scale). bitstring ::= [] <:> length(0) && value(0,_). bitstring ::= bit^^B, bitstring^^B1 <:> length( Length ) ::- B1 ^^ length(Length1), Length is Length1 + 1 && value( Value, ScaleB ) ::- B ^^ bitval( VB, ScaleB ), S1 is ScaleB - 1, B1 ^^ value( V1, S1 ), Value is VB + V1. number ::= bitstring ^^ B, fraction ^^ F <:> value(V) ::- B ^^ length(Length), S is Length-1, B ^^ value( VB, S ), F ^^ fractional_value( VF ), V is VB + VF. fraction ::= ['.'], bitstring ^^ B <:> fractional_value( V ) ::- S is -1, B ^^ value( V, S ). fraction ::= [] <:> fractional_value(0). test( L, V ) :- write( 'LIST ' ), write( L ), nl, number( Tree, L, [] ), Tree ^^ value( V ), write( 'VALUE ' ), write( V ), nl, nl. ?- test( [1,'.',1], V ). /* Should set V to 1.5. */ SIZE: 9 kilobytes. CHECKED ON EDINBURGH-COMPATIBLE (POPLOG) PROLOG : yes. PORTABILITY : No problems. INTERNAL DOCUMENTATION : Almost none. See "Logic Grammars" for the meaning of the predicates and the theory. ======================================================================== PROLOG DOUBLY-LINKED LIST PACKAGE Contributed by Philip Dart, Melbourne University Received on the 14th of November 1987 Shelved on the 6th of December 1987 This is my revised version of a doubly-linked list-handling package sent to the Prolog Digest Bulletin Board on 14th of November by Philip Dart, Melbourne University I've changed the syntax slightly so it fits Edinburgh Prolog: otherwise, the predicates are the same. [JNP] Following the comments [on the bulletin board] about Fortran as an AI language, Melbourne University Department of Artificial Intelligence has decided to convert all of its Fortran AI programs to NU-Prolog. This package has been written as an aid to this conversion. Doubly-linked list package: Why use boring old single-linked lists when doubly-linked list could make your list processing applications run as never before. P.S. Don't forget to turn off the occur-check in your version of Prolog! Predicates defined: test Demonstrate the predicates dPrev(D, _) Get previous node dNext(D, _) Get next node dHead(D, _) Get head of list dTail(D, _) Get tail of list isD(D) Is this a doubly-linked list? portray(D) Portray doubly-linked list dAppend(X, Y, Z) Append for doubly-linked lists dAdj(L, R) Are these adjacent nodes? [Philip Dart] SIZE : 6 kilobytes. CHECKED ON EDINBURGH-COMPATIBLE (POPLOG) PROLOG : yes. PORTABILITY : The original version was almost Edinburgh standard, but used mode declarations, end-of-line comments, and funny atom names. My revised version should be easily portable. Neither version will work in a Prolog which implements the occurs-check, but very few do. INTERNAL DOCUMENTATION : One-line description of each predicate's specification. ======================================================================== PROLOG EXPERT SYSTEM FOR FORESTRY MANAGEMENT Contributed by Steve Jones, Reading University Received on the 3rd of March 1988 Shelved on the 15th of March 1988 I enclose a small expert system for forestry management which was in another newsgroup. Anybody who missed it there might find it interesting. I was running it under PROLOG2, but it should run under most other dialects, although all the "s may need to be changed to '. [ Steve Jones ] I've modified the code so it runs under Edinburgh Prolog, and reformatted it. The system (which I'll call ESFM) contains about 30 IF-THEN rules about forestry management. These are stored as Prolog clauses, for example: recommendation('scatter cones') :- fact(branch18,yes), fact(silvaculture,clearcut), fact('improved stock',no), fact('good cone supply',yes), recommend( 'You should scatter the serotinous cones over the area.' ). Inference is depth-first, backward-chaining, and is done by having Prolog execute the rules. ESFM does not explain why it asks questions, nor how it comes to a conclusion. Here's a sample consultation: ?- go. Is the stocking of the jack pine stand currently at least minimum ? If you are unsure of how to determine stocking, see page 4 in the Managers Handbook for Jack Pine |: yes. Is the average diameter of the trees less than 5 inches ?|: no. Is the age of the stand mature or immature ?|: mature. Do you want to keep jack pine in this area ?|: no. Based upon your responses, the following is recommended : You should convert the area to some more desirable kind of tree. To see the complete set of derived facts, type "display_kb." ?- display_kb. stocking good is yes avg < 5 is no age is mature pine desired is no advice is You should convert the area to some more desirable kind of tree. [JNP] SIZE: 11 Kilobytes. CHECKED ON EDINBURGH-COMPATIBLE (POPLOG) PROLOG : yes. PORTABILITY : Easy, no known problems. INTERNAL DOCUMENTATION : Very little. ======================================================================== PROLOG GRAMMAR-RULE TRANSLATOR Jocelyn Paine Shelved on the 6th of December 1987 This program defines a predicate, 'grexpand', for expanding Definite Clause Grammar Rules into Prolog clauses. These are the standard form of DCG rules, for which a translator is built-in to many Prologs. The translator is essentially the same as that published in "Programming in Prolog", by Clocksin and Mellish. [JNP] SIZE : 9 kilobytes. CHECKED ON EDINBURGH-COMPATIBLE (POPLOG) PROLOG : yes. PORTABILITY : easy, no known problems. INTERNAL DOCUMENTATION : comments for each predicate, sample output. ======================================================================== PROLOG GRAPH-HANDLING ROUTINES Author: Paul Freedman, LAAS/CNRS Received on 15th December 1990 Shelved on the 12th of January 1991 This entry is two programs: one for decomposing a non-weighted directed graph into strongly connected components; and the other for finding simple and elementary cycles in a strongly connected component. The program is written for SICStus Prolog, which is Quintus compatible and hence uses `standard' Edinburgh syntax. The only non-portabilities are the I/O, which calls some non-standard Phigs stuff. I [JNP] have not yet changed these to make them portable. Although the programs are commented, it would probably help to know something about graph theory. The documentation file gives the most important references for the algorithms behind the programs. (of course, the algorithms as they appear in the programs don't correspond 100% with the references). This file also contains a Unix script describing how the program is used (in SICStus Prolog running on a Sun-4). SIZE : 30 kilobytes. CHECKED ON EDINBURGH-COMPATIBLE (POPLOG) PROLOG : no. PORTABILITY : OK, except that you'll need to change some of the I/O calls. INTERNAL DOCUMENTATION : comments in the program source, plus literature references. ======================================================================== GRIPS - A FUNCTIONAL LANGUAGE IN PROLOG Contributed by Jocelyn Paine, Oxford University. Shelved on the 11th of January 1991 GRIPS is a pre-processor for translating a functional version of Prolog into Prolog. By using it, you can eliminate the tedium of having to think up variables to pass output from one predicate to the input of the next, and of having to flatten arithmetic expressions into a sequence of machine-code-like assignments. Here are two example definitions. factorial(N) <- 1 if N =< 0. factorial(N) <- N * factorial(N-1) if N > 0. count( [] ) <- 0. count( [_|T] ) <- 1 + count(T). You can load these by doing 'grips_consult' or 'grips_reconsult' on the file they're in. You could then run the interpreter: ?- grips. |: do grips_reconsult('test.pl'). Done |: factorial(3). Result = 6. |: factorial(factorial(3)). Result = 720. |: count( [a,b,c,d] ). Result = 4. |: 1 + count([a,b,c,d])/factorial(3). Result = 1.66667. |: pr( factorial(3,F) ). F = 6 More (y/n)? |: y no |: There is a user manual for GRIPS. There's also another library entry, COMPILER, which is a simple compiler written in GRIPS. SIZE : 58 kilobytes. CHECKED ON EDINBURGH-COMPATIBLE (POPLOG) PROLOG : yes. PORTABILITY : should be no problems. See the comments in the code. INTERNAL DOCUMENTATION : as program comments and some sections in the user guide. ======================================================================== PROLOG INTERVAL-ALGEBRA PREDICATES Jocelyn Paine Shelved on the 21st of December 1987 This file defines predicates for manipulating sets of integers, represented as lists of disjoint intervals. This is a compact way of representing large sets, provided that they contain few gaps between intervals. Here are two examples of the representation: Set Representation { -32768 .. 32767 } [ -32768--32767 ] { 1,3,4,5,9,10,11,12,15,16,100,101,102} [ 1--1, 3--5, 9--12, 15--16, 100--102 ] The predicates in this entry include ones for forming the union, intersection, and difference of such sets, and for various operations on single intervals. For efficiency, I keep sets in a canonical form; one in which the intervals are disjoint, and are in ascending order, and form a minimal covering (i.e. there is no other representation of a set, using fewer intervals). There is a predicate for converting a list of arbitrary unordered intervals into a canonical form. I have found the predicates useful when writing programs for syntax-directed translation of character data. For example, some tag field on a line may specify that the line is a record of type R1 if the field lies in the set C1 of characters, or a record of type R2 if the field lies in the set C2 of characters, and so on. Using these predicates, I can check for ambiguous specifications by testing whether C1 and C2 overlap; and I can generate quick tests for whether some character is in C1 or C2 by knowing that the set are represented by as few intervals as possible. SIZE : 26 kilobytes. CHECKED ON EDINBURGH-COMPATIBLE (POPLOG) PROLOG : yes. PORTABILITY : Easy, no known problems. INTERNAL DOCUMENTATION : Comments for each main predicate; the properties of the representation; summary of proofs of correctness. ======================================================================== PROLOG ITERATIVE DEEPENING INTERPRETER Written by Lee Naish Received via Prolog Digest V6 #47 Shelved on the 3rd of October 1988 This program was written in reply to a request for a Prolog meta-evaluator to do breadth first evaluation. Many people use breadth first evaluation when they just need any fair search strategy. As a general rule, a bounded depth first search with iterative deepening is *much* better than breadth first. With breadth first, you tend to have to copy large quantities of data. Typically, for each call, you must copy all matching clauses and for each clause (even those which dont match in a simple implementation), you must copy the current instance of the variables in the top level goal and the entire current goal (not just a single call). This copying takes lots of time and memory. Depth first evaluation does not need to copy goals or variables since it only works on one branch at a time. It also takes more advantage of Prolog operations such as backtracking. There are two potential problems with it. Firstly, the same solution may be returned several times (one for each iteration). Secondly, it will never fail (it keeps trying greater depths indefinitely). This program avoids the first problem and can be modified to solve the second problem (by using a side effect). P.S. I wont claim this does anything sensible with negation or cut - they need a bit more work. [Lee Naish] SIZE: 10 kilobytes. CHECKED ON EDINBURGH-COMPATIBLE (POPLOG) PROLOG : Yes. PORTABILITY : Easy. You will need some way to test whether a goal is a call to one of your system predicates. INTERNAL DOCUMENTATION : Comments at the file's head describe the method. ======================================================================== PROLOG LIST-HANDLING PREDICATES Contributed by J.G. Forero, Reading University Shelved on the 21st of December 1987 This entry contains some list-handling predicates contributed by Jorge Forero. I've amended the syntax slightly so as not to use % comments or -> . The predicates' functions are: test for list-ness; test for sublist; find element at known position, or position of known element; remove duplicates; flatten a list; add element after known element; find that part of a list following a given element. SIZE : 4 kilobytes. CHECKED ON EDINBURGH-COMPATIBLE (POPLOG) PROLOG : yes. PORTABILITY : no known problems. INTERNAL DOCUMENTATION : comments for each predicate. ======================================================================== LINGER - A NATURAL LANGUAGE CORRECTOR IN PROLOG Contributed by Paul O'Brien and Masoud Yazdani, Exeter University Received on the 25th of March, 1988 Shelved on the 20th of April, 1988 LINGER is a language-independent system to analyse natural language sentences and report and correct grammatical errors encountered. An important objective is that the system should be easily configured for a particular natural language by an expert in that language but not in computer science. A sample run is shown below, with three sentences, all of which are slightly incorrect (Linger reports a noun not in its lexicon for the third one). Skip to the end of this run for further comments. ?- [ 'linger_shell.pl' ]. Type "run" to start LINGER linger_shell.pl consulted yes ?- run. LINGER -- Language INdependent Grammatical Error Reporter What language do you want (french/english/spanish/german/italian)? ==> |: french. consulting Grammar consulting Dictionary Type your sentence ==>|: tu est une chat. Pre-parsing sentence Trying for a legal parse Legal parse found Parse tree selected: sentence main_clause subj_phr noun_pron_phr pronoun : [tu, 1] verb_phr pos_or_neg_verb_cons pos_verb_cons rp_pron_list pron_list pron_list2 governing_verb verb_or_aux_verb aux_verb : [est, 2] dir_obj_phr noun_phr determiner : [une, 3] adj_list noun : [chat, 4] adj_list indir_obj_phr Your sentence was: --- tu est une chat . --- I think the correct version of your sentence should read: >>> tu est un chat . <<< **** Comments **** determiner "une" changed to "un" : [gender(m), plurality(s), apostrophe(n)] **** End Comments **** Another go ? ==> |: y. Type your sentence ==>|: vous est un chat. Pre-parsing sentence Trying for a legal parse Legal parse found Parse tree selected: sentence main_clause subj_phr noun_pron_phr pronoun : [vous, 1] verb_phr pos_or_neg_verb_cons pos_verb_cons rp_pron_list pron_list pron_list2 governing_verb verb_or_aux_verb aux_verb : [est, 2] dir_obj_phr noun_phr determiner : [un, 3] adj_list noun : [chat, 4] adj_list indir_obj_phr Your sentence was: --- vous est un chat . --- I think the correct version of your sentence should read: >>> vous e4tes un chat . <<< **** Comments **** aux_verb "est" changed to "e4tes" : [tense(present), transitivity(t), person(2), plurality(p)] **** End Comments **** Another go ? ==> |: y. Type your sentence ==>|: j'ai vu un herisson. Pre-parsing sentence Trying for a legal parse Legal parse found Parse tree selected: sentence main_clause subj_phr noun_pron_phr pronoun : [j', 1] verb_phr pos_or_neg_verb_cons pos_verb_cons rp_pron_list pron_list pron_list2 aux_verb : [ai, 2] governing_verb past_participle : [vu, 3] dir_obj_phr noun_phr determiner : [un, 4] adj_list noun : [herisson, 5] adj_list indir_obj_phr Your sentence was: --- j' ai vu un herisson . --- I think the correct version of your sentence should read: >>> j' ai vu un . <<< **** Comments **** "herisson" is unknown and has been guessed to be of type noun **** End Comments **** Another go ? ==> |: n. CHECKED ON EDINBURGH-COMPATIBLE (POPLOG) PROLOG : yes. PORTABILITY : no known problems. INTERNAL DOCUMENTATION : comments for portability problems. ======================================================================== PROLOG OPERATOR TESTS Written by Chris Moss, Dept. of Computing, Imperial College Contributed by Norbert Fuchs, Department of Computer Science, Zurich University Shelved on the 3rd of October 1988 You may have noticed there are subtle differences between the way different Prologs handle operator definitions. The test file below is designed to explore some of these on the lines of some of my earlier tests. Thanks to Hamish Taylor for some of these tests. Note that some of the answers are definitely WRONG. I leave you to decide which! [Chris Moss] SIZE: 12 kilobytes. CHECKED ON EDINBURGH-COMPATIBLE (POPLOG) PROLOG : Yes. PORTABILITY : That's what it's meant to test! INTERNAL DOCUMENTATION : Each test carries a very brief statement of its purpose. ======================================================================== PROLOG NAIVE REVERSE BENCHMARK Contributed by Norbert Fuchs, Department of Computer Science, Zurich University Shelved on the 3rd of October 1988 This is a benchmark, for reversing lists by the "naive" (2-argument) form of reverse. SIZE: 6 kilobytes. CHECKED ON EDINBURGH-COMPATIBLE (POPLOG) PROLOG : Yes. PORTABILITY : Easy. You will need to change the 'T0 is cputime' inside bench(Count), and the factor of 496 inside calculate_lips. INTERNAL DOCUMENTATION : None. ======================================================================== PEREIRA'S PROLOG BENCHMARKS Written by Fernando Pereira Contributed by Norbert Fuchs, Department of Computer Science, Zurich University Shelved on the 3rd of October 1988 I've received several requests for the benchmarks that were used in the June issue of AI Expert. The purpose of these benchmarks is to try to identify strengths and weaknesses in the basic engine of a Prolog system. In particular, I try to separate costs normaly conflated in other benchmark suites, such as procedure call cost, term matching and term construction costs and the costs of tail calls vs. nontail calls. I'm sure the benchmarks could be improved, but I don't have time to work on them right now. Also, I must say that I have relatively little faith on small benchmark programs. I find that performance (both time and space) on substantial programs, reliability, adherence to de facto standards and ease of use are far more important in practice. I've tried several Prolog systems that performed very well on small benchmarks (including mine), but that failed badly on one or more of these criteria. Some of the benchmarks are inspired on a benchmark suite developed at ICOT for their SIM project, and other benchmark choices were influenced by discussions with ICOT researchers on the relative performance of SIM-I vs. Prolog-20. [Fernando Pereira] SIZE: 50 kilobytes. CHECKED ON EDINBURGH-COMPATIBLE (POPLOG) PROLOG : No. PORTABILITY : Contains several Quintus/Dec-10 Prolog idiosyncrasies. INTERNAL DOCUMENTATION : Brief statement of the purpose of each benchmark. ======================================================================== PLAISTED'S THEOREM PROVER Written by David A. Plaisted Contributed by Norbert Fuchs, Department of Computer Science, Zurich University Shelved on the 3rd of October 1988 This is a C Prolog program: a theorem prover based on the simplified problem reduction format. SIZE: 80 kilobytes. CHECKED ON EDINBURGH-COMPATIBLE (POPLOG) PROLOG : No. PORTABILITY : Contains a number of C-Prolog idiosyncrasies. INTERNAL DOCUMENTATION : A description of how to run the program, plus a number of examples. ======================================================================== PROLOG OBJECT-ORIENTED PACKAGE Author: Ben Staveley-Taylor Received sometime in early 1987 Shelved on the 10th of December 1987 Updated on the 10th of September 1988 with small changes to improve portability suggested by Nick Youd (Cambridge University Engineering Department) This program - called POEM by its author - comes from a Poplog Users' Group tape, received in early 1987. [JNP]. Class Definition ---------------- POEM makes available some of the features found in languages like Simula-67. Classes may be defined, objects (instantiations of classes) created and operated on as high- level entities. An example is often the best way to introduce an idea. Suppose that points are to be represented in 2-dimensional Cartesian co-ordinates, and only the quadrant 0 <= x,y <= 10 is to be considered: class point(X, Y) checks ( X >= 0, X =< 10, Y >= 0, Y =< 10 ) body identical( point(X1, Y1) ) => ( X1 = X, Y1 = Y ) -&- distance2( point(X1, Y1), Dist ) => Dist is (X1-X)*(X1-X)+(Y1-Y)*(Y1-Y). This declaration then sets up a class 'point'. The clauses following 'checks' are executed whenever a new point object is created, and the 'checks' goal must succeed for the object to be successfully instantiated. Two predicates are defined to manipulate the class: identical/1 succeeds if the argument point structure is the same as the point that owns this incarnation of identical/1. distance2/2 instantiates its second argument to the square of the distance between the two points. Subclass Definition ------------------- As in Simula, a hierarchy of classes may be established. This allows subclasses to be defined with all the checks and predicates of their superclasses, and further subclass specific ones. Object Manipulation ------------------- To enter the class definitions into the Prolog database, the top level predicate poem/0 is used. The necessary procedure is: - consult the file 'poem.pl'. This sets up the necessary operator declarations. - consult the user defined file of class definitions. - invoke the predicate poem/0. This translates the class definitions into the internal Prolog representation. Once this is done, the objects can be defined and manipulated. Parting Shot ------------ Wholly wonderful as POEM is, it is only a quickly written program and does not make any claims to robustness. In particular, there is no error detection mechanism - if classes are defined with incorrect syntax, the malformed classes will not be processed. Generally, errors result in logical failure of the associated goal. [ Ben Staveley-Taylor]. SIZE : 26 kilobytes. CHECKED ON EDINBURGH-COMPATIBLE (POPLOG) PROLOG : yes. PORTABILITY : Easy - documented at head of each source file. DOCUMENTATION : (1) A separate description of POEM's class description syntax, main predicates, and how class descriptions are translated into Prolog. (2) Comments in the program for important predicates and methods. ======================================================================== PROLOG EXPERT SYSTEM BUILDING TOOL Contributed by Steven Salvini, Heriot-Watt University Received on the 30th of August 1988 Shelved on the 3rd of October 1988 PROTEST EXPERT SYSTEM This is a cut-down version of the expert system building tool produced by Steven Salvini as part of his M.Sc. dissertation in 1986. [Steven S] PROTEST is a tool for building prototype expert systems. It accepts a knowledge base written in IF-THEN rules whose conditions and conclusions consist of object/attribute/value triples: rule1: if pain/duration/constant and pain/localisation/accurate and pain/'initiated by'/'gentle touch' and pain/character/'sudden onset' and pain/character/'intense & throbbing' and gingivae/swelling/present and gingivae/erythema/present and miscellaneous/'local lymphadenopathy'/present and pain/'initiated by'/'clenching, biting or chewing' and tooth/mobility/present then diagnosis/group/abscess with certainty(0.9). Conclusions may contain certainty factors. Inference can be either backward chaining or mixed. The former is normal backward chaining, giving a single firm conclusion if one has been deduced or else as a list of possible conclusions in order of their certainties. Mixed mode is a "mixed" inference strategy which first prompts you to enter your initial findings and then tries to deduce one or more of the goals. If a firm conclusion is not reached, it then tries to solve the problem by backward-chaining. After PROTEST has given a conclusion, you can ask to see its chain of reasoning. A sample knowledge base, for dental diagnosis, is included. [JNP] SIZE : 325 kilobytes. CHECKED ON EDINBURGH-COMPATIBLE (POPLOG) PROLOG : yes. occasionally, some messages seem to go missing, possibly because of an incompatibility in terminals. PORTABILITY : the terminal-control predicates are terminal-specific. INTERNAL DOCUMENTATION : Each important predicate comes with a brief comment describing its purpose. There is a user manual. ======================================================================== SHAPIRO'S PROLOG DEBUGGER Written by E. Y. Shapiro Contributed by Norbert Fuchs, Department of Computer Science, Zurich University Shelved on the 3rd of October 1988 This is the program from Appendix II (pp 185-213) of Algorithmic Program Debugging, MIT Press, 1982. Some of the parts are interesting and useful for other purposes. The program contains very few comments, because it comes from the Appendix of a book whose main text describes it in great detail. You will need the book before you can make sense of this code. [JNP] SIZE: 40 kilobytes. CHECKED ON EDINBURGH-COMPATIBLE (POPLOG) PROLOG : No. PORTABILITY : Contains % comments. INTERNAL DOCUMENTATION : Very brief description of each main section. ======================================================================== PROLOG FILE SEPARATOR Jocelyn Paine Shelved on the 9th of December 1987 Amended on the 21st of December 1987 This program allows one to separate text files which have been packed into a larger file. In particular, you can use it to separate files belonging to the Prolog Library which have been packed in this way. The main predicate is 'split', of arity zero. It asks you for the name of a composite text file. Type this name on a line, terminated by RETURN. 'split' then splits that file into its component subfiles. Each subfile must have this structure:
zero or more times [JNP] SIZE : 7 kilobytes. CHECKED ON EDINBURGH-COMPATIBLE (POPLOG) PROLOG : yes. PORTABILITY : Should be easy. Hints are given in the program. INTERNAL DOCUMENTATION : Comments for each predicate, plus a more detailed description of the program, and a sample composite file. NB: If your implementation doesn't optimise tail recursion, or doesn't collect unused atoms, the program may run out of space (though I've tried to avoid recursion as much as possible). ======================================================================== PROLOG STATIC CALL ANALYSER Contributed by John Cugini, National Bureau of Standards Received on the 30th of July, 1988 Shelved on the 30th of July, 1988 This is a quickie static cross-reference analyzer. You load it in, and it'll tell you which predicates are (statically) invoking which other predicates. [JC] SIZE : 12 kilobytes. CHECKED ON EDINBURGH-COMPATIBLE (POPLOG) PROLOG : yes. PORTABILITY : Fairly easy. I've documented possible problems at the head of the source file. DOCUMENTATION : A comment for each main predicate, and my description of portability problems. ======================================================================== EDINBURGH PROLOG TOOLS Contributed by the AI Applications Institute, Edinburgh University Received on the 14th of April 1988 Shelved on the 6th of July 1988 UNIVERSITY OF EDINBURGH AIAI/PSG103/87 AI APPLICATIONS INSTITUTE PROGRAMMING SYSTEMS GROUP Issued by Note No. 103 Ken Johnson Robert Rae Structure and Contents of the Prolog library 12th November 1987 _______________________________________________________________________________ The DEC-10 Prolog Library was an extraordinary and catholic collection of Prolog routines, largely written by research workers and students in Professor Alan Bundy's Mathematical Reasoning Group at the Department of Artificial Intelligence at the University of Edinburgh. In summer 1987 we sifted through the enormous amount of material in this library, grouping similar material together and converting some of the more used programs into Edinburgh Prolog. These programs are all examples of Prolog programming to deal with objects and problems of many kinds. (Some of these examples are very good examples, others are not so; some are well commented, some have separate documentation, some have none.) You may be able to load tools for low-level operations into your code ready-made, or you may gain insight into how to write good Prolog (as we did) through just browsing amongst the source code here. Files which have their names in lower case have been checked, converted, and are believed to work in Edinburgh Prolog running under UNIX. They have had any DEC-10/TOPS-10 specific features eliminated and replaced by UNIX equivalents. Some of the DEC-10 file names were changed after the files were converted, normally expanding the six character abbreviation into something more meaningful. Files that have their names in upper case are still in DECsystem- 10 Prolog. It is difficult to sort things into categories. We have tried to do it and to avoid a rag-bag "Miscellaneous" category, but undoubtedly there will be files that you'll think have been put into the wrong place. The top level directories that we have identified are data, demo, io, prolog, tools and util. Most of these are reasonably self-explanatory: data contains files relating to data structure definition and manipulation; demo contains files of demonstration and teaching material; io contains files relating to input and output of structured and unstructured data; prologcontains files of common extensions to the Prolog language and definitions of parts of the Prolog system in Prolog; tools contains files relating to the development of Prolog programs; util all the files in this directory are links to files which already exist in some other part of the library. They were identified originally for use with the PRESS system and were grouped together for convenience. They have proved useful to other systems since. _______________________________________________________________________________ These files are all supplied "as is", with NO guarantee of any kind. If things don't work, fix them and mail the fix to us, if you can. Otherwise complain and we will fix them if we can. Obviously we cannot undertake to do this within any particular time limit. Electronic mail to nip@uk.ac.ed will reach us. These files are all in the "public domain" so you can use them freely, copy them, incorporate them into programs of your own and so forth without payment. The work of producing them in the first place and of organising them as detailed here has been funded over the years at Edinburgh University mainly by the Science and Engineering Research Council. Their dissemination has been encouraged by the Alvey Special Interest Group: Artificial Intelligence. We would appreciate it if you were to acknowledge these bodies when you use or re-distribute any of these files. _______________________________________________________________________________ The files of the original DEC-10 Prolog Library have been divided up into categories to give the following directory structure: [omitted. JNP] This is the contents of the Prolog Library in alphabetical order of file name. Any files whose names end in .HLP are text files which explain another Prolog file, and they are not listed below. All the others are listed with a one-line description. advice.pl Interlisp like advice package. ANDOR.pl Meta circular interpreter maintaining extended and-or tree. applic.pl Function application routines based on "apply". ARC3.pl Mackworth's AC-3 algorithm. ARCH1.PRB Winston arch domain. Inference version. ARCH3.PRB Winston arch domain. ARHC2.PRB Winston arch domain, with inference rules. arith.ops Arithmetic operator declarations. arith.pl Arithmetic operations. arrays.pl Updateable arrays. ask.pl Ask questions that have a one-character answer. assoc.lists.pl Association lists. BACKUP.pl Rename a file according to a back-up convention. bagutl.pl Utilities for "bags". between.pl Generate successive integers. bfs.pl Missionaries and Cannibals: breadth first search. BREADTH_FIRST.pl Define a schema for breadth-first search. BUNDLE.pl Bundle and unbundle files. CC.pl Conditional compilation. CLAUSE.pl Convert a formula in FOPC to clausal form. CONN Operator definitions for logical connectives. Contents This file. count.pl Information about a valid Prolog file. CRYPTA.pl Solve cryptarithmetic puzzles. CTYPES.pl Character classification. DCSG.ex Example grammar for DCSG.pl. DCSG.pl Definite Clause Slash Grammar. DEC10.pl DEC-10 compatibility file for C-Prolog 1.4a. DECONS.pl Construct and take apart Prolog control structures. depth.pl Find or check the depth of a term. DEPTH_FIRST.pl Define a schema for a depth-first search. dfs.pl Missionaries and Cannibals depth first search. DISTFIX.ex Load DISTFIX.pl and define some examples. DISTFIX.pl Read Prolog terms with extended syntax. edit.pl Invoke an editor and return to Prolog. EIGHT_PUZZLE.pl Illustrate the searching methods. evans.pl Evans geometric analogy program. expand.pl Simple macro expansion. EXPON.pl Synthesis of an exponentiation routine. figure.pl Figures for the Evans program. files.pl Routines for playing with files. flags.pl Global variables. flat.pl Flatten trees to lists and back. FOCUS Reconstruction of Winston learning program. FEACH.pl Redefine foreach/5. GELRAN.pl Random number package. gensym.pl Create new atoms. getfile.pl Prompt for a file name. graphs.pl Graph processing utilities. GUESS_FIRST.pl Define a schema for a guess-first search. heaps.pl Implement "heaps". HELP.pl Prints extracts from help files. HELP2.pl Extracts predicate names and descriptions from files. HELPER.pl Prints extracts from help files. help_directories.txtList of directories that contain ".HLP" files. heu.pl Missionaries and Cannibals: Heuristic search version. IDBACK.def Unit interface clauses for IDBACK.pl. IDBACK.pl Intelligent backtracking. IMISCE.pl Miscellaneous interpreted routines. INFER Inference package for focus program. INVOCA.pl Fancy control structures. ISOLAX.PRB Description space for learning isolate rule. ixref.def Definitions for ixref.pl. ixref.pl Interactive cross referencer. keep.pl Keep predicate(s) in a file. lazy.pl Lazy lists. LEARN Part of Winston's program. LIB.pl Version of Vax "lib" predicate. LIB2.pl Version of Vax "lib" predicate. listut.pl List handling utilities. logarr.pl Arrays with logarithmic access time. logodb.pl Logo-like inference package. long.pl Rational arithmetic. MAKERC Make records from lists of relations. MAKE_UTIL Create the utilities baseload from this library. map.pl Implement finite maps. medic.pl Mode error diagnosis in interpreted code. metutl.pl Meta logical operations. MODULE.pl Elementary module system for DEC-10 Prolog. multil.pl List-of-lists utilities. mycin.pl Version of the "mycin" program. NOT.pl Suspicious negation. OCCUR.pl Routines for checking number and place of occurrence. order.pl Define the "ordered" predicates. ordset.pl Ordered set manipulation. OXO.pl Noughts and crosses production system. PIM.PRB Artificial inference testing example for focussing. PORSTR.pl Portray lists of characters as strings. pp.pl Prolog pretty printer. PROJEC.pl Select k'th argument of each element of a list. PROLOG.TYP Definition of Prolog types for typecheck.pl. PUTSTR.pl Write out large blocks of text. QUEENS.pl Solve the N queens problem. queues.pl Queue operations. random.pl Random number generator. RDTOK.gen Tokeniser in reasonably standard Prolog. RDTOK.pl Reads tokens up to next ".". READ.pl Read Prolog terms in DEC-10 syntax. read_in.pl Read in a sentence as a list of words. read_sent.pl A flexible input facility. RECON.pl Version of consult and reconsult. royalty.pl Royal family data base. RULES.pl Production rules system. samsort.pl A sorting routine that exploits existing order. setof.pl Implementations of setof, bagof and findall. setutl.pl Set manipulation utilities. solution.txt Solution printed by Evans' program. SORTS.pl Definition of keysort and sort. STRIO.pl Prolog input and output to character strings. struct.pl General term hacking. SUBTRA.pl Production rules for subtraction by borrowing. SUM.SOL.pl Cryptarithmetic solution. SUM1.pl Example sum for use with RULES and SUBTRA. SUM2.pl Example sum for use with RULES and SUBTRA. SUM3.pl Example sum for use with RULES and SUBTRA. SYSTEM.pl Table of built-in predicates. system_preds.pl Table of built-in predicates. termin.pl Test for missing base cases. TEST.pl Test compiled routines by interpreting them. tidy.pl Algebraic expression simplifier. TIMING.pl Time execution of predicate. TIMING.POP Time execution of predicate (POP2 component). TOPLEVEL.pl Prolog top level. trace.pl Produce tracing messages. TREES.pl Updateable binary trees. trysee.pl Search directories and extensions to find a file. type.pl Command to display files. typecheck.pl Prolog type checker. UNFOLD.pl Unit resolution. UPDATE.pl For updating data base relations. UTIL Utilities for focussing program. util.ops Operator declarations for utilities package. util.sav Saved state for Edinburgh Prolog ver 1.5.01 (14 Aug 1987). VCHECK.pl Check for mis-spelt variables. WINST Consult all focussing files. WINST.MIC WINST.REF Focussing cross reference. WINST2.CMD WPLANC.pl Conditional plan generator. WPO.pl Operator declarations for WPLANC.pl. writef.pl Formatted write. XGPROC.pl Translate XGs to Prolog. XREF.DEF Cross referencer definitions. XREF.pl Cross referencer. XRF.pl Cross referencer program. XRFCOL.pl Collecting-up module of the cross referencer. XRFDEF.pl Handles .def files for the cross referencer. XRFMOD.pl Update declarations in Prolog source file. XRFOUT.pl Output module for the cross referencer. XRFTST.BAR Cross referencer test file. XRFTST.FOO Cross referencer test file. XRFTTY.pl Terminal interaction for cross referencer. [AIAI] TOTAL SIZE : 1122 kilobytes. CHECKED ON EDINBURGH-COMPATIBLE (POPLOG) PROLOG : no. PORTABILITY : I haven't examined them in detail, but some will need changing from C-Prolog. DOCUMENTATION : It varies. Some have detailed internal comments and help files; others have almost nothing. ======================================================================== PROLOG TURTLE GRAPHICS Contributed by Salleh Mustaffa, University of Manchester Received on the 17th of November 1987 Shelved on the 6th of December 1987 Amended on the 17th Of December 1987 Copyright (c) 1987 by David Lau-Kee, Univ. of York. Permission is granted to use or modify this code provided this notice is included in all complete or partial copies. I enclose a turtle graphics program written by David Lau-Kee. It came from a posting to the Prolog Digest some months ago. It had a few syntactic errors which I have corrected. The program is said to be terminal specific and probably works best on a colour VT-100 terminal, but I've only been able to see it in action on a monochrome VT-100. I have not been able to get it to work properly on a Sun terminal (even after hours of flipping through the ANSII manuals for the Sun). I think it is also Unix specific, but I may be wrong. I suspect the initial errors that I had to contend with initially are due to the control characters in the program which are not properly transmitted in the mail. [Salleh Mustaffa] The basic idea came from a colleague's thought that it would be useful to be able to show the progress of instantiations in a goal. To be really useful there needs to be some means of "unshowing" the partial groundings, so that the display is always consistent with a snapshot of the state of the system. Really this program is only an experiment on that concept. It has *lots* of rough edges and *lots* of nasty constructs... However, it does provide an interesting way of "watching" Prolog at work. A much reduced "turtle graphics" environment is presented. (Basically you can tell the turtle to turn 90 deg. clockwise or anticlockwise, and to move forward X steps.) The "interesting" feature is that backtracking over these primitives results in them being undone. For example, I have defined anysq(X) to be four sets of 'forward X steps, turn'. If I try to satisfy 'anysq(4), fail.' then all the possible solutions to: 'anysq(4).', where 'forward (drawing) X' and 'backward (erasing) X' satisfy the goal 'forward X', and 'turn clockwise' and 'turn anticlockwise' satisfy 'turn' are drawn. I wrote the program for C-Prolog 1.5, but it wouldn't require much effort to move it to other Prologs. It *is* terminal specific - I use a Microcolour m2200 in ANSII mode (basically vt100 plus colour) - but again, if your terminal has ANSII features, it won't be a problem to hack it straight. One thing may be worth thinking about: When a line is undrawn it is sometimes helpful to leave a record of it. I cope with this by switching the undo colour from black to white. This is ok on a colour terminal where the lines themselves are other than white, but it would be a bit confusing in monochrome... maybe half-intensity or something? The program is slower than it really needs to be. Previously the undo would act like paint stripper, cutting right down to the black of the background. This version paints in layers, undoing strips off a layer. (Great if you've got a lot of colours.) For a 5-fold speed increase take out the layers. [David Lau-Kee] I've reformatted the program, changed % comments to /* .. */, and made a few other syntactic changes. [JNP] SIZE : 18 kilobytes. CHECKED ON EDINBURGH-COMPATIBLE (POPLOG) PROLOG : yes. Doesn't use any non-standard predicates, but won't run on our (VT100) terminals. However, the appearance of the screen is almost correct - small changes to the terminal-handling predicates should make it work. PORTABILITY : the cursor-moving commands are terminal-specific. INTERNAL DOCUMENTATION : The cursor-addressing predicates carry very brief descriptions of what they're supposed to do. ======================================================================== PROLOG TYPE-CHECKER Contributed by R.A.O'Keefe Authors: Alan Mycroft & R.A.O'Keefe Received on the 14th of November 1987 Shelved on the 6th of December 1987 Amended and re-shelved for the 16th of August 1988 This program was sent to the Prolog Digest Bulletin Board on the 14th of November 1987. [JNP]. This is the type-checker as it stood in 1984 for DEC-10 Prolog + Edinburgh library (pretty much the code that was handed out at the Albufeira Workshop in '83, in fact). It has not been upgraded to Quintus Prolog; it doesn't handle modules, and it was never considered to be particularly good code. Comments and improvements welcome. [Richard O'Keefe]. This program defines a "type-checked consult" operation load(Files) where Files is an atom or a list of atoms. There is no analogue of the reconsult operation. In the Files type declarations may be given in addition to the usual sort of commands, questions, clauses, and declarations. You can put the type declarations in separate files, so that load(['foo.typ','foo.pl']) can be used to type-check and load the interpreted version, and compile('foo.pl') can be used to compile the same code. Note that declarations have to be processed before clauses using the things declared. There are two new declarations: type --> {| }.. . e.g. type tree(T) --> empty | tree(T,tree(T),tree(T)). and pred {, }.. . e.g. pred append(list(T), list(T), list(T)). You may use a semicolon instead of a vertical bar if you like. As a convenience for defining grammar rules, rule p(T1,...,Tk). has the same effect as pred p(T1,...,Tk,list(T_),list(T_)). where T_ is not further specified. 'C'/3 is predefined as pred 'C'(list(X), X, list(X)). [Richard O'Keefe and Alan Mycroft]. I've made the program more portable, and commented on all the portability problems I could find. [JNP] SIZE : 49 kilobytes. CHECKED ON EDINBURGH-COMPATIBLE (POPLOG) PROLOG : yes. PORTABILITY : Nasty in the original, but I've fixed, or at least remarked on, the problems I could find. INTERNAL DOCUMENTATION : Comments with important predicates, and a brief description of the method. ======================================================================== STRUCTURES IN PROLOG By Jean G. Vaucher, De'partement d' informatique et R.O., Universite' de Montre'al Shelved on the 15th of August 1989 This package is taken from "Record manipulation in Prolog" (Short Communication), Jean G. Vaucher, De'partement d' informatique et R.O., Universite' de Montre'al. in "Software - Practice and Experience", Vol _19_(8), pp. 801-807, (August 1989). It provides a set of primitive predicates and operators that allow the arguments of Prolog structures to be accessed by name rather than position, and that implement Lisp-style property lists. These make it more convenient to write programs that are easily understood and modified. [JNP] Examples: --------- ?- def_record( person(name,age,address) ). Define a template for the 'person' structure. ?- inst( person, P ), field( P..name, 'Matthew Latner Linton' ), field( P..name, Z ). Create a 'person' in P, set its name, and unify that name with Z. ?- def_record( address(number,street,town) ). Template for the 'address' structure. ?- inst( address, A ), inst( person, P ), field( P..address, A ), field( P..age, 25 ), field( P..address..street, 'St. Peter's Street' ). field( P..address..town, 'Hanningtown' ). Create an address A and person P, and set some fields. ?- inst( person, P ), field( P..name, 'Fred' ), field( P..age, 25 ), update( P..name, 'Bert', P2 ). Create a person, and use 'update' to make a modified copy. SIZE : 18 kilobytes. CHECKED ON EDINBURGH-COMPATIBLE (POPLOG) PROLOG : yes. PORTABILITY : Easy. INTERNAL DOCUMENTATION : Long description of how to use the predicates, and a brief description of how they work: adequate given their simplicity. ======================================================================== PROLOG CURSOR-ADDRESSING PREDICATES Jocelyn Paine Shelved on the 21st of December 1987 There are two sets of predicates, one for VT100s and one for VT52s. They: move to X,Y; clear a line or page; set inverse or normal video. SIZE : 4 kilobytes. CHECKED ON EDINBURGH-COMPATIBLE (POPLOG) PROLOG : yes. PORTABILITY : No known problems. INTERNAL DOCUMENTATION : Comments for each predicate.