perm filename AICONF.SOS[L70,TES] blob sn#049709 filedate 1973-06-13 generic text, type T, neo UTF8
00100	.DEVICE XGP
00200	.!XGPLFTMAR ← 4 ;
00300	.!XGPCOMMANDS ← "/PMAR=2400/XLINE=9" ;
00400	.FONT 1 "NGR30" ;
00500	.FONT B "CLAR30" ;
00600	.FONT F "FIX25" ;
00700	.FONT 2 "SUP" ;  PATCH ← DDT ;
00800	.TURN ON "α#{%" ;
00900	.AT "↑[" $( "%2" )$ ;
00950	.AT "]" $( "%*" )$ ;
01000	.PAGE FRAME 60 HIGH 57 WIDE
01100	.AREA TEXT LINES 1 TO 60 CHARS 1 TO 57
01200	.NEXT PAGE
01300	.MACRO SEC(NAME) ⊂IF LINES < 8*SPREAD THEN NEXT PAGE; SKIP SPREAD ;
01400	.ONCE CENTER
01500	%B{}NAME%*
01600	.BREAK⊃
01700	.MACRO SS(NAME) ⊂IF LINES < 5*SPREAD THEN NEXT PAGE; SKIP SPREAD ;
01800	.ONCE FLUSH LEFT
01900	%B{}NAME %*
02000	.ONCE PREFACE 1⊃
02100	.MACRO B ⊂ SKIP 1 ; BEGIN SELECT F ;
02200	.GROUP ; INDENT 6 ; NOFILL ; SINGLE SPACE ;⊃ ;
02300	.MACRO E ⊂END⊃
02400	.MACRO EC ⊂ SKIP 1; END CONTINUE ⊃
02500	.MACRO EB ⊂ E ; B ⊃
02600	.REQUIRE "REF1.PUB" SOURCE_FILE
     

01200	.PREFACE 1
01300	.INDENT 4
01400	.GROUP SKIP 20
02900	
02905	.BEGIN PREFACE 0 ;
02910	.ONCE FLUSH LEFT
02920	---------------------------------------------
03000	.ONCE INDENT 0 ;
03100	*###This work was supported (in part) by Grant PHS MH 06645-11 from the
03200	National Institute of Mental Health, and (in part) by the Advanced
03300	Research Projects Agency of the Office of the Secretary of Defense (SD-183).
03400	
03500	The views and conclusions contained in this document are those of the
03600	authors and should not be interpreted as necessarily representing the
03700	official policies, either expressed or implied, of the Advanced
03800	Research Projects Agency, NIMH, or the U.S. Government.
03900	.ONCE FLUSH LEFT
04000	---------------------------------------------
04100	.ONCE INDENT 0 ;
04200	**##Present affiliation: Xerox Corporation (Palo Alto Research Center).
04250	
04300	.END ;
04400	.SEC Abstract
04500	
04600	LISP70 is a descendant of LISP which
04700	emphasizes pattern-directed computation and extensibility.
04800	A function can be defined
04900	by a set of pattern rewrite rules as well as by the normal LAMBDA method.
05000	New rewrite rules can be added to a previously defined function; thus
05100	a LISP70 function is said to be "extensible".  It is possible to have
05200	new rules merged in automatically such that special cases are
05300	checked before general cases.  Some of the facilities of the rewrite system are
05400	described and a variety of applications are demonstrated.
     

00100	.SEC Background
00200	
00300	During the past decade,
00400	LISP↑[{REF MCCARTHY_LISP}] has been a principal programming language for artificial
00500	intelligence and other frontier applications of computers.
00600	Like other widely used languages, it has spawned many variants,
00700	each attempting to make one or more improvements.
00800	Among the aspects that have received particular attention are
00900	notation,↑[{ref ABRAHAMS_LISP2},{ref ENEA_MLISP},{ref
01000	.LANDIN_ISWIM},{ref SMITH_MLISP}] control
01100	structure,↑[{REF BURSTALL_POP2},{ref HEWITT_THESIS},{REF
01200	.RULIFSON_QA4},{REF SMITH_BACK}] data base
01300	management,↑[{REF HEWITT_PLANNER},{REF RULIFSON_QA4},{REF SUSSMAN_CONNIVER}]
01400	interactive editing and debugging,↑[{ref TEITELMAN_DWIM}]
01500	and execution efficiency.
01600	
01700	A need for a successor to LISP has been recognized,↑[{ref BOBROW_SUCCESSOR}] and
01800	several efforts in this direction are under way.  The approach being taken with
01900	TENEX-LISP is to begin with an excellent debugging system↑[{REF TEITELMAN_BBNLISP}]
02000	and to add on flexible control structure.↑[{ref BOBROW_CONTROL}]#
02100	The approach taken by LISP70 and by
02200	ECL↑[{REF WEGBREIT_ECL}] is to begin with an extensible kernel language which
02300	users can tailor and tune to their own needs.
02400	
02500	"Tailoring" a language means defining facilities which assist in the solution
02600	of particular kinds of problems which may have been unanticipated by the
02700	designers of the kernel.  "Tuning" a language means specifying more efficient
02800	implementations for statements which
02900	are executed frequently in particular programs.
03000	
03100	A language that can be used on only one computer is not of universal utility;
03200	the ability to transfer programs between computers increases its value.
03300	However, a
03400	language that is extensible both upward and downward
03500	is difficult to transport if downward extensions mention
03600	machine-dependent features.↑[{REF DICKMAN_ETC},{REF DUBY_EXT}]#
03700	This consideration suggests the use of a machine-independent low-level
03800	language↑[{REF BROWN_LOWL}] in terms of which to describe downward extensions.
     

00100	.SEC Capabilities of LISP70
00200	
00300	The aim of LISP70 is to provide a
00400	flexible and parsimonious programming medium for symbolic processing
00500	and an efficient implementation for that medium on several machines.
00600	
00700	The semantics of the LISP70 kernel subsumes LISP1.5 and Algol-60 semantics.  The
00800	syntax provides three high-level notations: S-expressions,
00900	Algol-like MLISP expressions, and pattern-directed rewrite rules.
01000	The syntax and semantics can both be extended as described later in
01100	this paper.  By extension, it is feasible to incorporate the capabilities of
01200	virtually any other programming language.
01300	Of course, one would take
01400	advantage of the techniques developed by its previous implementors;
01500	LISP70 simply provides a convenient medium for doing this.
01600	
01700	To maximize efficiency and to eliminate the possibility of an inconsistent
01800	compiler and interpreter, all programs in LISP70 are compiled.  There is no
01900	interpreter in the usual sense; the function EVAL compiles its argument
02000	with respect to the current environment and then executes the machine-language
02100	code.  To extend the language, extensions need only be made to
02200	the compiler, not also to an interpreter.
02300	
02400	One disadvantage of a compiler is that certain sophisticated debugging techniques
02500	such as the "BREAKIN" of TENEX-LISP↑[{REF TEITELMAN_BBNLISP}] are more
02600	difficult to implement than in an interpreter.  However, we feel that the
02700	extra effort needed for this is worth expending to retain the advantages
02800	of a compiler.
02900	
03000	LISP70 generates code for an
03100	"ideal LISP machine" called "ML" and only the translation from ML to object
03200	machine language is machine-dependent.  Thus, downward extensions can be
03300	factored into a machine-independent and a machine-dependent part, and during
03400	program transfer, the machine-dependent recoding (if any) is clearly isolated.
03500	An execution image on one computer could be transliterated to ML and
03600	transported to a different machine.  This capability could be used to transport
03700	programs around computer networks, and for bootstrapping of the compiler itself.
03800	
03900	In order to execute the EVAL function, the compiler and parts of the symbol table
04000	must be present during execution.  This requirement and the goal of extensibility
04100	are met by a pattern-directed translator whose rules are compiled into
04200	dense and efficient code.  The same pattern matcher as used in the translator
04300	also is available for goal-directed
04400	procedure invocation in A.I. programs.
04500	
04600	Among the specific improvements LISP70 makes to LISP are
04700	backtrack and coroutine control structure,
04800	streaming,
04900	long-term memory for large data bases,
05000	data typing,
05200	pattern-directed computation, and
05300	extensible functions.
05310	The implementation provides dynamic storage
05320	allocation, relocation, and segmentation.
05400	
05500	The subjects to be covered in the present paper are
05600	pattern-directed computation and extensible functions.
     

00100	.SEC Pattern Directed Computation
00200	
00300	.SS Rewrite Rules
00400	
00500	Many of the data tranformations performed in LISP applications are more
00600	easily described by pattern matching rules than by
00700	algorithms.↑[{REF ENEA_INTEGRATE},{REF GUZMAN_CONVERT},{REF
00800	.HEWITT_PLANNER},{REF RULIFSON_QA4},{REF SUSSMAN_CONNIVER},{REF TEITELMAN_FLIP}]#
00900	In addition,
01000	pattern matching rules are appropriate for the description of
01100	input-output conversion, parsing, and compiling.↑[{REF SMITH_MLISP2}]#
01200	LISP70 places great emphasis on "pattern rewrite
01300	rules"↑[{REF COLBY_DOC},{REF COLBY_WATT},{REF KAY_FLEX},{REF WEIZENBAUM_ELIZA}]
01400	as an alternative and adjunct to algorithms as a means of defining functions.
01500	
01600	A brief explanation of rewrite rule syntax and semantics will be
01700	presented with some examples to demonstrate the clarity of the notation.
01800	
01900	Each rule is of the form DEC→REC.  The DEC (decomposer) is matched against
02000	the "input stream".  If it matches, then the REC (recomposer) generates
02100	the "output stream".
02200	
02300	A literal in a pattern is represented by itself
02400	if it is an identifier or number, or preceded by a quote (') if it is
02500	a special character.
02600	.B
02700	RULES OF SQUARE =
02800		2 → 4,
02900		5 → 25,
03000		12 → 144 ;
03100	.E
03200	A private variable
03300	of the rule is represented by an identifier prefixed by a colon (:);
03400	it may be bound to only one value during operation of the rule.
03500	.B
03600	RULES OF EQUAL =
03700		:X :X → T,
03800		:X :Y → NIL ;
03900	.E
04000	A list is represented by a pair of parentheses
04100	surrounding the representations of its elements.
04200	A segment of zero or more elements is represented by an ellipsis symbol (α.α.α.).
04300	.B
04400	RULES OF CAR =
04500		(:X ...) → :X ;
04600	.EB
04700	RULES OF CDR =
04800		(:X ...) → (...) ;
04900	.EB
05000	RULES OF CONS =
05100		:X (...) → (:X ...) ;
05200	.EB
05300	RULES OF ATOM =
05400		(:X ...) → NIL,
05500		:X 	 → T  ;
05600	.EB
05700	RULES OF APPEND =
05800		(...) (...) → (... ...) ;
05900	.E
06000	
06100	If a segment needs a name, it is represented by an identifier prefixed by
06200	a double-colon (::).
06300	.B
06400	RULES OF ASSOC =
06500		:X (... (:X ::Y) ...) → (:X ::Y),
06600		:X (...)   	      →  NIL    ;
06700	.E
06800	A function F(X,Y,Z) can be called in a pattern
06900	by the construct: <F#:X#:Y#:Z>.
07000	.B
07100	RULES OF LENGTH =
07200		( )	  →  0,
07300		(:X ...)  →  <ADD1 <LENGTH (...)>> ;
07400	.E
07500	
07600	The facilities described so far are standard in most pattern-directed
07700	languages.
     

00100	.SS List Structure Transformations
00200	
00300	The following set of rules defines a function
00400	MOVE_BLOCK of three arguments: a block to be moved,
00500	a location to which it should be moved, and a representation of the current
00600	world.  The function moves block :B from its current location in the world to
00700	location :TO, and the transformed representation of the world is returned.
00800	.B
00900	RULES OF MOVE_BLOCK =
01000	
01100	 :B :TO (... (:TO ... :B ...) ...)
01200	      → (... (:TO ... :B ...) ...),
01300	
01400	 :B :TO (... (... :B ...) ... (:TO ...   ) ...)
01500	      → (... (...    ...) ... (:TO ... :B) ...),
01600	
01700	 :B :TO (... (:TO ...   ) ... (... :B ...) ...)
01800	      → (... (:TO ... :B) ... (...    ...) ...),
01900	
02000	 :B :TO (... (... :B ...) ...)
02100	      → (... (...    ...) ... (:TO :B)),
02200	
02300	 :B :TO (...)
02400	      → <ERROR (BLOCK :B NOT IN (...))> ;
02500	.EC
02600	In the first case, the block is already where it belongs, so the world does
02700	not change;
02800	in the second, the block is moved to the right; in the third, to the left;
02900	in the fourth, the location :TO does not exist yet and is created; in
03000	the last case, :B is not in the world and the ERROR routine is called.
03100	
03200	Functions such as MOVE_BLOCK have been used in a simple planning program written by
03300	one of the authors.
03400	Imagine writing MOVE_BLOCK as an algorithm; it would require the use of
03500	auxiliary functions or of a PROG with state variables and loops.  Bugs would
03600	be more likely in the algorithm because its operation would not be so lucid.
     

00100	.SS Replacement
00200	
00300	A function call in a DEC pattern is called a "replacement".
00400	A replacement has two interesting aspects.
00500	First, if the function
00600	requires more arguments than it is passed,
00700	it will take additional arguments off the front of the
00800	input stream.
00900	Furthermore, the value returned by a replacement is
01000	appended to the front of the input stream.
01100	Thus, the replacement <F> behaves like a
01200	non-terminal symbol of a top-down parser.  In effect, the function
01300	F is invoked to translate a substream of the input stream, and
01400	that substream is replaced by its translation.  The altered input stream can
01500	then continue to be matched by the pattern to the right of <F>.
01600	
01700	The following example is from the MLISP compiler, which calls itself
01800	recursively to translate the condition and arms of an IF-statement to LISP:
01900	.B
02000	RULES OF MLISP =
02100	
02200	  IF <MLISP>:X THEN <MLISP>:Y ELSE <MLISP>:Z
02300	      → (COND (:X :Y) (T :Z)),
02400	
02500	  IF <MLISP>:X THEN <MLISP>:Y
02600	      → (COND (:X :Y) (T NIL)),
02700	
02800	  IF <MLISP>:X
02900	      → <ERROR (MISSING THEN)>,
03000	
03100	  IF  → <ERROR (ILLEGAL EXPRESSION AFTER IF)>;
03200	.E
03300	Here is another example.  The predicate PALINDROME is true iff the input
03400	stream is a mirror image of itself, i.e., if the left and right ends are equal
03500	and the middle is itself a palindrome.
03600	.B
03700	RULES OF PALINDROME =    :X    	→      	T,
03800	
03900	                      :X :X    	→       T,
04000	
04100	        :X <PALINDROME>T :X     →      	T,
04200	
04300	                       	...    	→      	NIL;
04400	.E
     

00100	.SEC Extensible Functions
00200	
00300	New rules may be added to an existing set of rewrite rules under program control;
00400	thus, any compiler table or any other system of rewrite rules can be extended
00500	by the user.  For this reason, a set of rewrite rules is said to be an
00600	"extensible function".  The "ALSO" clause is used to add cases to an extensible
00700	function:
00800	.B
00900	RULES OF MLISP ALSO =
01000	
01100	  IF <MLISP>:X THEN <MLISP>:Y ELSE
01200	      → <ERROR (MISSING EXPRESSION AFTER ELSE)>,
01300	
01400	  IF <MLISP>:X THEN
01500	      → <ERROR (MISSING EXPRESSION AFTER THEN)>;
01600	.E
01700	Extensions can be made effective throughout the program or only in the current
01800	block, as the user wishes.
01900	
02000	A regular LAMBDA function can also be extended.
02100	Its bound variables are considered
02200	analogous to a DEC and its body analogous to a REC.  Accordingly, the compiler
02300	converts it to an equivalent rewrite function of one rule before extending it.
     

00100	.SS The Extensible Compiler
00200	
00300	To make an extensible compiler practical, the casual user must be able to
00400	understand how it works in order to change it.
00500	We have found this to be no problem with users of MLISP2, the predecessor
00600	to LISP70.  Its
00700	extensible compiler has been used to write parsers quickly by
00800	A.I. researchers previously unfamiliar with parsing techniques.
00900	
01000	To demonstrate that it is not
01100	inordinately difficult to understand the LISP70 compiler, those rules which
01200	get involved in translating a particular statement from MLISP to LAP/PDP-10 are
01300	shown below.  A simplified LISP70 (typeless and unhierarchical)
01400	is used in the examples, but the real thing is not much more complicated.
01500	
01600	The statement to be translated is:
01700	.B
01800		IF A < B THEN C ELSE D
01900	.EC
02000	The rules invoked in the MLISP-to-LISP translator are:
02100	.B
02200	RULES OF MLISP =
02300	
02400	  IF <MLISP>:X THEN <MLISP>:Y ELSE <MLISP>:Z
02500		→ (COND (:X :Y) (T :Z)),
02600	
02700	  :X  '<  :Y
02800		→ (LESSP :X :Y),
02900	
03000	  :VAR	→ :VAR ;
03100	.EC
03200	The LISP translation is thus:
03300	.B
03400		(COND ((LESSP A B) C) (T D))
03500	.E
03600	
03700	The LISP-to-ML compiler below utilizes the following feature: if a colon variable
03800	occurs in the REC but it did not occur in the DEC, an "existential value"
03900	(which is something like a generated symbol) is bound to it.
04000	Here, the existential value is used as a compiler-generated label.
04100	
04200	The language ML is based on the machine language of the Burroughs 5000 and
04300	its descendants.  For example,
04400	the ML operator "DJUMPF" means "destructive jump if false".  It jumps only
04500	if the top of the stack is false but always pops the stack.
04600	
04700	.B
04800	RULES OF COMPILE =
04900	
05000		(COND (T :E))
05100		      →	<COMPILE :E>,
05200	
05300		(COND (:B :E) ...)
05400		      →	<COMPILE :B>
05500			(DJUMPF :ELSE)
05600			<COMPILE :E>
05700			(JUMP :OUT)
05800			(LABEL :ELSE)
05900			<COMPILE (COND ...)>
06000			(LABEL :OUT),
06100	
06200		(LESSP :A :B)
06300		      →	<COMPILE :A>
06400			<COMPILE :B>
06500			(FETCH (FUNCTION LESSP)),
06600	
06700		:V    →	(FETCH (VARIABLE :V)) ;
06800	.E
06900	The unoptimized ML-to-LAP translator below assumes that the stack
07000	of the ideal machine is represented on the PDP-10 by a
07100	single stack based on register "P", that there is a single working
07200	register "VAL", and that variables can be
07300	accessed from fixed locations in memory.  (None of this is really true
07400	in the actual implementation.)
07500	.B
07600	RULES OF ML =
07700	
07800		(DJUMPF :LBL)
07900		      →	(POP P VAL)
08000			(JUMPE VAL :LBL),
08100	
08200		(JUMP :LBL)
08300		      →	(JUMPA VAL :LBL),
08400	
08500		(LABEL :LBL)
08600		      →	:LBL,
08700	
08800		(FETCH (FUNCTION LESSP))
08900		      →	(POP P VAL)
09000			(CAMG VAL 0 P)
09100			(SKIPA VAL NIL)
09200			(MOVEI VAL T)
09300			(MOVEM VAL 0 P),
09400	
09500		(FETCH (VARIABLE :V))
09600		      → (PUSH P :V) ;
09700	.E
09800	The code generated is thus:
09900	.B
10000		ML		        LAP
10100	
10200	(FETCH (VARIABLE A))	    (PUSH P A)
10300	(FETCH (VARIABLE B))	    (PUSH P B)
10400	(FETCH (FUNCTION LESSP))    (POP P VAL)
10500				    (CAMG VAL 0 P)
10600				    (SKIPA VAL ZERO)
10700				    (MOVEI VAL 1)
10800				    (MOVEM VAL 0 P)
10900	(DJUMPF E0001)		    (POP P VAL)
11000				    (JUMPE VAL E0001)
11100	(FETCH (VARIABLE C))	    (PUSH P C)
11200	(JUMP E0002)		    (JUMPA VAL E0002)
11300	(LABEL E0001)	        E0001
11400	(FETCH (VARIABLE D))	    (PUSH P D)
11500	(LABEL E0002)	        E0002
11600	.EC
11700	In the actual compiler, special rules for optimizing conditionals, a peephole
11800	optimizer, and additional working registers reduce this to six instructions.
     

00100	.SEC Automatic Ordering Of Rewrite Rules
00200	
00300	In most pattern matchers, candidate patterns to match an input stream are
00400	tried either in order of appearance on a list or in an essentially random
00500	order not obvious to the programmer.  LISP70 tries matches in an order
00600	specified by an "ordering function" associated with each set of rewrite
00700	rules.
00800	
00900	One common ordering is "BY APPEARANCE", which is appropriate when the
01000	programmer wants conscious control of the ordering.  Another is
01100	"BY SPECIFICITY", which is useful in left-to-right parsers and other
01200	applications where the compiler can be trusted to order the rules so that
01300	more specific cases are tried before more general ones.  When neither of
01400	these standard functions is appropriate, the programmer can define and use
01500	specialized ordering functions, or can extend SPECIFICITY to meet the
01600	special requirements.
01700	
01800	Automatic ordering is convenient for a user who is extending
01900	a compiler, a natural language parser, or an inference system.  It can
02000	eliminate the need to study the existing rules simply to determine where
02100	to position a new rule.  Ordering functions can also be designed to detect
02200	inconsistencies and ambiguities and to discover opportunities for
02300	generalization of similar rules.
02400	
02500	As an example, take the LISP-TO-ML translator "COMPILE",
02600	which includes the following rule for the intrinsic function PLUS (slightly
02700	simplified for presentation):
02800	.B
02900	RULES OF COMPILE =
03000	
03100		(PLUS :X :Y)
03200		      →	<COMPILE :X>
03300			<COMPILE :Y>
03400			(FETCH (FUNCTION PLUS)) ;
03500	.E
03600	To add special cases to the compiler for sums including the constant zero,
03700	the user could include the following declaration in a program:
03800	.B
03900	RULES OF COMPILE ALSO =
04000	
04100		(PLUS :X 0) → <COMPILE :X>,
04200	
04300		(PLUS 0 :X) → <COMPILE :X> ;
04400	.E
04500	The compiler is ordered by SPECIFICITY, which knows that the
04600	literal %F0%* is more specific than the variable :X or :Y.
04700	Therefore, both of the new rules would be ordered before the original
04800	PLUS rule.
04900	Suppose the added rules were placed after the general rule;
05000	then the original rule would get first crack at every input stream,
05100	and sums with zero would not be processed as special cases.
     

00100	.SS An Ordering Function
00200	
00300	The complete definition of the ordering function SPECIFICITY
00400	is beyond the scope of this paper.  It works roughly as follows.
00500	Comparing DEC patterns by a left-to-right scan, it considers
00600	literals more specific than variables and a colon variable at its second
00700	occurrence more specific than one at its first occurrence.
00800	The specificity of a replacement <F>
00900	is that of the most general rule in the function F.
01000	
01100	A DEC with an ellipsis
01200	is considered to expand to multiple rules in which the ellipsis
01300	is replaced by 0, 1, 2, 3, ... %F∞%* consecutive variables.  The specificity of
01400	each expanded rule is considered separately.  Observe that between
01500	two expansions of an elliptic rule some other rewrite rule of intermediate
01600	specificity may lie.  Example:
01700	.B
01800	RULES OF SILLY =
01900		A ... B ... C	→	1,
02000		A B :X :Y	→	2;
02100	.EC
02200	Two of the expansions of the first rule are:
02300	.B
02400		A B :X C	→	1,
02500		A :Z B C	→	1,
02600	.EC
02700	and the second rule of SILLY comes between these in specificity.
02800	
02900	SPECIFICITY is itself defined by a system of rewrite rules.
03000	To give a flavor of how this is done, a very simplified SPECIFICITY will be defined.
03100	It takes two arguments (DEC patterns translated to LISP notation) and
03200	returns them in the proper order.
03300	.B
03400	RULES OF SPECIFICITY =
03500	
03600	  (COLON :V) (LITERAL :L)
03700		→ (ORDER (LITERAL :L) (COLON :V)),
03800	
03900	  (LITERAL :L) (COLON :V)
04000		→ (ORDER (LITERAL :L) (COLON :V)) ;
04100	.E
     

00100	.SEC Additional Facilities
00300	The programmer can specify either deterministic or non-deterministic matching;
00400	the former case generates faster code while the latter provides for backtracking.
00500	Other facilities of the rewrite system include side-conditions, conjunctive match,
00600	disjunctive match, non-match, repetition, evaluation of LISP and MLISP expressions,
00700	look-ahead, look-behind, and reversible rules.
00800	
00900	DEC patterns can be used outside of rewrite rules for decomposition of data
01000	structures in MLISP statements.
     

00100	.sec Applications
00200	
00300	It is easy to
00400	define a system of inference rules, of assertions, or of beliefs as a rewrite
00500	function.
00600	From a set of rules can be retrieved either all of the assertions or the first
00700	that match a given pattern.
00800	A robot planner could be organized into RULES OF PHYSICS,
00900	RULES OF INITIAL_CONDITIONS,
01000	RULES OF INFERENCE,
01100	RULES OF STRATEGY,
01200	etc.  Note that goal-directed
01300	procedure invocation is performed within each of these functions separately.
01400	This allows for segmentation of large programs.
01500	Furthermore, it averts the need to rummage around a conglomerate
01600	data base of unrelated rules.
01700	
01800	Rewrite rules are a useful tool for natural language analysis,
01900	whether the methods used
02000	are based on phrase structure grammar, features, keywords, or word patterns.
02100	A use of LISP70 with the latter method is described in a companion
02200	paper.↑[{REF ENEA_IDIOLECT}]#  The program described therein utilizes the
02300	replacement facility extensively.
     

00100	.sec Implementation of Rewrite Functions
00200	
00300	In the initial implementation of LISP70, rewrite rules are processed in a
00400	top-down, left-to-right manner.  During the ordering phase,
00500	the rules of each extensible
00600	function are factored from the left to avoid repetition of
00700	identical tests in identical circumstances.  The resulting code is a
00800	discrimination tree that eliminates many choice-points for backtracking.
00900	
01000	The backtracking implementation is an improvement of that developed for
01100	MLISP2.↑[{REF SMITH_BACK}]#  It incurs little overhead of either time or space.
01200	
01300	The machine code generated for rewrite rules consists primarily of
01400	calls on scanning and testing functions.  These functions are generic and will
01500	process input and output of streams of any type, including lists, character
01600	strings, files, and coroutines.
01700	For example, streaming↑[{REF LEAVENWORTH_STREAMING}]
01800	intermediate results of compiler passes
01900	between coroutines circumvents expensive temporary storage allocation and
02000	speeds up the compiler.
     

00100	.SEC Conclusions
00200	
00300	Some of the design decisions of LISP70 are contrary to trends seen in other
00400	"successors to LISP".  The goals of these languages are similar, but their
00500	means are often quite diverse.
00600	
00700	Concern with good notation does not have to compromise the development
00800	of powerful facilities; indeed, good notation can make those facilities
00900	more convenient to use.  People who "think in Algol" should not have to
01000	cope with S-expressions to write algorithms.
01100	Neither should people who "think in patterns".
01200	Rewrites, MLISP, and LISP can
01300	be mixed, and the most appropriate means of defining a given function can be
01400	selected.
01500	
01600	LISP70 does not limit the use of pattern rewrite rules to
01700	a few facilities like goal-achievement and assertion-retrieval.  A set of
01800	rules can be applied to arguments like any other function, and can
01900	stream data from any type of structure or process to any other.
02000	
02100	Automatic ordering does not prevent the programmer from seizing control,
02200	but allows him to relinquish control to a procedure of
02300	his choosing to save him tedious study of an existing program when making
02400	extensions.
02500	
02600	Preliminary versions of LISP70 have been run on a PDP-10 using a bootstrap
02700	compiler.  As of June 15, a production version has not been completed.
02800	The language has been used successfully
02900	in programs for question-answering and planning.
03000	Extensions are planned to
03100	improve its control structure, editing, and debugging capabilities, and
03200	versions will be bootstrapped to other computers.
     

00100	.SEC Acknowledgment
00200	
00300	The authors wish to thank Alan Kay for valuable insights.
     

00100	.<< REFERENCES >>
00110	.AT "↑[" $()$ ;
00120	.AT "]" $()$ ;
00200	.FONT 8 "NGR25" ;
00300	.FONT 9 "NGB25" ;
00350	.SELECT 8
00400	.BREAK
00500	.REQUIRE "REF2.PUB" SOURCE_FILE