draft



                        the e.c.s.d lisp manual



                                                 N. H. Shelness

                                                 December, 1976


1.0 introduction


   This manual is a brief  introduction  to  the  Edinburgh  Computer
Science  Department (ECSD) LISP SYSTEM running on EMAS. It is not
intended as an introduction to LISP. There are a number of  references
listed in the bibliography that will fulfill that function.

   ECSD  LISP  was implemented by the author for undergraduate student
use, and its structure reflects this fact. It is  a  relatively  'pure'
implementation  in which functions are defined over more limited domains
than is often the case, and in which extensive error  checking  enforces
these  limitations. (ie. CAR and CDR are only defined over LISTS, and
will result in an error if applied to ATOMS.).

   It was the author's initial intent that this system would rapidly be
superceded by the UPSALLA INTERLISP  system,  when  the  later  became
available on EMAS. This has not yet been possible. Despite this fact,
the  author has no desire to recode the interpreter in assembler, nor to
flatten its procedural structure, though such changes might well  result
in a fourfold performance improvement. Instead a study has been made of
the  performance  of certain algorithms in the interpreter, and a number
of changes have been effected to reduce search times and improve  paging
behaviour. The later have turned the interpreter into a viable vechicle
for  the  solution  of small to medium scale problems, but not for large
ones. For large problems the user will have  to  wait  for  a  suitable
release of the UPSALLA INTERLISP system.

   The  structure  of  this  manual  owes a great deal to the LISP F1
USERS MANUAL. The author wishes  to  extend  his  gratitude  to  the
authors  of  that manual for providing such a good example from which he
could begin.

2.0 access


   The ECSD LISP SYSTEM is contained in the library  ECSC09.LISPLIB
and  is  entered  via the command LISP which takes a single argument of
the form '/filename' or 'filename'.

   When the filename is preceded by a slash, a LISP MEMORY  FILE  of
that  name  is  created and initialized by the lisp interpreter prior to
entering the top level loop. If a file of that name exists prior to the
call, it is first deleted.

   When the filename is not preceded by a  slash,  the  system  assumes
that  a  LISP  MEMORY  FILE  of  that  name  allready exists, and the
interpreter will enter the top level loop without altering it. If  such
a file does not exist an error is indicated.

   All  ATOMS, properties, global bindings, and LISTS are held in the
LISP MEMORY FILE. This eliminates the need for dumping  and  loading
the  contents  of  the  LISP  MEMORY between sessions, and reduces the
chance of information loss due to crashes.

   examples

   COMMAND:APPENDLIB(ECSC09.LISPLIB)

       This command enters the ECSD LISP SYSTEM  into  your  command
       library. It need only be issued once.

   COMMAND:LISP(/LISPMEMY)

       Calls   the  lisp  interpreter,  which  will  destroy  the  file
       LISPMEMY if it exists, and create and initialize a LISP MEMORY
       FILE called LISPMEMY before entering the top level loop.

   COMMAND:LISP(LISPFILE)

       Calls the lisp interpreter,  which  will  check  that  the  file
       LISPFILE  exists and is a LISP MEMORY FILE, prior to entering
       the top level loop.


3.1 lisp objects


   Only three types of LISP OBJECT exist in the ECSC LISP  SYSTEM.
These are NUMERIC ATOMS, SYMBOLIC ATOMS, and LIST CELLS.

   NUMERIC  ATOMS  are the only objects to which numeric functions may
be applied, and hence on which arithmetic  can  be  performed.  NUMERIC
ATOMS  carry  a  constant  binding  to  themselves and do not possess a
PROPERTY LIST. In the ECSD LISP SYSTEM, NUMERIC ATOMS  may  only
represent integer values. There are no floating point forms.

   SYMBOLIC  ATOMS  are  atomic objects which are not NUMERIC ATOMS.
They may carry either  constant  or  variable  bindings  to  any  LISP
OBJECT,  and in addition posses a PROPERTY LIST. The PRINTNAME of a
SYMBOLIC ATOM may be any string of ISO characters with maximum length
255.

   LIST CELLS are 2-tuples of the  form  {'car',  'cdr'},  where  both
'car' and 'cdr' may be any LISP OBJECT.

   There  are  two mechanisms which the LISP INTERPRETER provides for
the creation of new LISP OBJECTS. These are the  generator  functions
such  as  CONS,  PACKLIST,  GENSYM  and LIST which manipultate their
arguments (ie.   allready existent LISP OBJECTS) so as to  create  new
LISP  OBJECTS,  and  input  functions  such as READCH and READ which
allow the user to specify new LISP  OBJECTS  or  structures  of  LISP
OBJECTS from outwith the INTERPRETER.


3.2 notation


   The  LISP  OBJECTS described in the previous section only exist as
objects within the LISP INTERPRETER itself. If we are  to  manipulate
these  objects,  we  need  a notation by which we can refer to them. We
need a notation in which the interpreter can print results, and in which
we can enter information into the system.

   Versions  of  standard  LISP  S-NOTATION  are  used  with   slight
variation for input and output. In describing this notation, we need to
recognize  five  classes  of  characters. These are 'break' characters,
'escape' characters, 'digits', 'sign' characters and 'other' characters,
where the latter contains all those ISO characters  that  do  not  fall
into  the  other  four  classes,  or any ISO character that on input is
preceded by an 'escape' character. This preceding 'escape' character is
not included  in  the  internal  representation,  and  is  not  normally
printed.

   'break' characters:     '(', ')', '[', ']', '.', ' ', ''', ''
                           and any control character (ISO 0-31 decimal).

   'escape' characters:    '$', '/'.

   'digits':               '0' - '9'

   'sign' characters:      '-', '+'



   All ATOMS are delimited by, but do not include, 'break' characters.
A NUMERIC ATOM consists of a string of digits, which  may  optionally
be  preceded  by  a  single  'sign'  character.  A  SYMBOLIC  ATOM is
represented by a string  of  'digits',  'sign'  and  'other'  characters
including at least one non-'digit'.

   LIST  CELLS  are  represented in one of two notations: as a DOTTED
PAIR '(' LISP OBJECT '.' LISP OBJECT ')' or as a  LIST  '('  LISP
OBJECT ' ' LISP OBJECT ' ' LISP OBJECT ' ' . ')'. We may use the
latter  notation when the right hand LISP OBJECT of a DOTTED PAIR is
itself a DOTTED PAIR or a LIST. In such  cases  we  may  remove  the
parentheses  '('  and  ')' from the right hand LISP OBJECT and replace
the dot '.' of the DOTTED PAIR by a  space  '  '  or  any  other  ISO
control character.

   ie. (A  (A  B)) becomes (A B  C)

   By  an  additional  convention,  the  symbolic  atom NIL is used to
represent the empty LIST '()'. Therfore if the right hand object of  a
DOTTED PAIR is NIL, we may drop both the dot '.' and the NIL.

   ie. (A  (B  NIL)) becomes (A B)

   Either  notation  may  be used when inputing S-EXPRESSIONS, but the
interpreter will always print results in LIST notation where possible.

   There are two other notational details that we need to cover.  They
only  have  effect  on  input.  As  an  S-EXPRESSION  may contain many
parentheses we may use a right hand square bracket ']' as a alias for  a
string of right parentheses such that the outermost right parenthesis in
the  string  will match the innermost left square bracket '['. If there
is no left square bracket then the outermost right  parenthesis  matches
the outermost left parenthesis, and thus closes the S-EXPRESSION.

   ie.  (A  [A  (B.(C])  and (A (A (B (C] both become (A (A (B (C))))


   As it is often neccessary  to  'QUOTE'  S-EXPRESSIONS,  two  break
characters  '''  and  '' are provided as abreviations. The presense of
either character prior to an S-EXPRESSION will cause the  S-EXPRESSION
to  be  enclosed in a list of which the first element is the atom QUOTE
and the second element is the S-EXPRESSION itself.

   ie. 'A becomes (QUOTE A) while '(A B C) becomes (QUOTE (A  B C))


examples

   NUMERIC ATOMS:

       1 100 -1 -123

   SYMBOLIC ATOMS:

       A abc A/( 1$000   NOTE:  The latter two are in input notation
                           and will print as A( and 1000.

   DOTTED PAIRS and LISTS:

       (A  b) (A B C) (A '(b  c]


3.3 bindings


   In a previous section, we indicated that atoms could possess  values
in the form of bindings. There are three sorts of bindings that an atom
in the ECSD LISP system may possess: A constant binding, A number of
local  bindings,  and  A  global binding, in that order of priority. A
numeric atom possesses a single constant  binding  to  itself,  while  a
symbolic atom may posses all three.

   Symbolic  atoms  are given constant bindings when they have a single
constant use. Normally, the atoms: NIL, T, %, and  STOP  all  posses
constant bindings to themselves. If the user wishes to give other atoms
constant bindings, he may do so using the function CSET, which achieves
its  effect  by  placing the value specified in the call on the property
list of a nominated atom under  the  property  APVAL.  As  a  constant
binding  has  precedence  over  any other form of binding, an attempt to
create either a global or  local  binding  for  an  atom  that  allready
possesses  a  constant  binding  will  result in a warning message being
printed by the LISP interpreter.

   Local  bindings  are  created  by  the  LISP  interpreter  in   two
circumstances:  upon  entry  to  a  PROG  and  when  applying a LAMBDA
expression. In the first case, NIL is bound to  each  element  of  the
PROG variable list. In the second case elements of the actual argument
list  are  bound to the appropriate LAMBDA variables. This binding may
take one of three forms depending on the first argument of  the  LAMBDA
expression. If the first argument is a single symbolic atom, the entire
actual argument list is bound to it. If it is a simple list of symbolic
atoms, successive elements of the actual argument list are bound to each
successive element of it. If it is a list of symbolic atoms ending in a
dotted  atom,  successive elements of the actual argument list are bound
as in the previous case, with whatever remains of  the  actual  argument
list being bound to the dotted atom

   ie.  consider the argument list (1 2 3 4)

       Given the LAMBDA expression (LAMBDA (A B C D) ..)
       1 will be bound to A, 2 to B, 3 to C and 4 to D.

       Given the LAMBDA expression (MBDA ( B  C) ..)
       1 will be bound to A, 2 to B and the list (3 4) to C.

       Given the LAMBDA expression (LAMBDA A .)


       the list (1 2 3 4) will be bound to A.


   All  local  bindings that are created on entry to a PROG or as part
of the application of a LAMBDA expression are deleted  upon  exit  from
the PROG, or completion of the application.

   A global binding is created by the interpreter whenever the function
SET is applied to a symbolic atom that does not posses a binding. If a
local  binding  exists,  no global binding is created, instead the local
binding is altered to take the new value.

examples


lisp:(de test(a) (progn (princ a) (setq a '(a b c)) (princ a) (terpri]
test

   We define a simple function which prints the initial  value  of  A,
gives A a new binding (A B C), and then prints the new value.

lisp:a
eval error:   a
    atom is not bound to a value
   %:(reset)
lisp:(test 3)
3(a b c)
nil

   A  has no global binding as can be seen from the attempt to evaluate
it at the top level. The application of the function TEST  causes  the
value  3 to be bound to A as a local binding. It is this value that is
printed by the first call on PRINC. The binding of A is then  altered
to  the  list (A B C). It is this new binding that is printed by the
second call on PRINC. TERPRI terminates the  print  line  and  returns
NIL.

lisp:(editf test)
edit:(r 2 (b)) p
(lambda (b)
    (progn (*** ***)
           (*** *** ***)
           (*** ***)
           (***)))
edit:%c
end of editf

   Here  we  have  altered  the definition of TEST. Now when TEST is
applied, the actual argument will be bound to B.

lisp:(test 3)
eval error:   a
    atom is not bound to a value
   %:%
eval:3
3(a b c)
nil
lisp:a
(a b c)



   We again evaluate (TEST 3), but this time A has no local  binding.
As  it  also  has  no  global  binding  an error occurs. The atom 3 is
returned from the BREAK, and is printed. This time the call  on  SETQ
establishes  a global binding of the list (A B C) to A. As a global
binding has been established, the binding is retained at the top level.


3.4.1 properties


   In addition to its possible bindings,  each  symbolic  atom  in  the
ECSC LISP system possesses a list of 2-tuples of the form {KEY, LISP
OBJECT}.  This  list is called the PROPERTY LIST. It functions as a
content addressable store associated with each  symbolic  atom.  In  it
values  are stored, retrieved, and removed via their KEY, which must be
a symbolic atom.

   In some LISP systems, the property list may be accessed as the CDR
of the symbolic atom. In ECSD LISP this  is  not  allowed.   property
lists may only be manipulated using the built in set of LISP functions:
PUTPROP, DEFPROP, GETPROP, REMPROP and PROP.


3.4.2 known properties


   It has allready been noted that a number of symbolic atoms (NIL for
example)  perform  a special role in the LISP interpreter. The same is
true of a number of KEYs that may appear on the PROPERTY LIST of  a
symbolic atom.

   The  key  APVAL  is  used to identify a constant binding, while the
keys SUBR, FSUBR, EXPR and  FEXPR  are  used  to  identify  function
definitions.  It  is  possible  for a number of function definitions to
appear on the property list of a symbolic atom at the  same  time  under
different  keys,  yet a symbolic atom can have only one current function
definition. By convention in ECSD LISP, the last function  definition
to  be  PUT  onto  the  property list of an atom will be treated as the
current function definition.  If  the  active  function  definition  is
subsequently removed from the property list, the symbolic atom will then
possess  no  function  definition,  despite  the  fact  that a number of
function  definitions  may  still  exist  on  its  property  list  under
different keys.


3.5 the interpreter


   A  LISP  interpreter  consists  of  an  extensible  number of LISP
functions called from the single root function EVAL, which takes as its
argument a single S-EXPRESSION.

   The ECSD LISP interpreter is written in IMP. In it EVAL has the
following simplified form.


integerfn eval(integer form)
recordname cell(lisp cell)
recordname atom(atom cell)
integer car, cdr

! note: the cell atom_func contains the identity of the current
! function definition or constant binding associated with an atom. 
! the cell atom_form contains a type mask identifying the
! critical features of the lisp object held in atom_func.

       if form>=list base then start;           ! form is a list
          cell==list(form);  car=cell_car;  cdr=cell_cdr

          result = apply(car,evlist(cdr)) c
             if car>=list base;                 ! car is a list

          if car>=name base start;              ! car is a symbolic atom
             atom==name(car)
             cdr=evlist(cdr) if atom_form&4#0;  ! expr/subr
             result = func(atom,cdr);           ! form of apply
          finish

          result = error3;                      ! numeric atom

       finish

       if form>=name base start;                ! symbolic atom
          atom==name(form)
          result = atom_func if atom_form&7=3;  ! apval
          result = atom_bind;                   ! return binding
       finish

       result = form;                           ! numeric atom

end


   As functions may either be implemented as part  of  the  interpreter
itself  (SUBR  and  FSUBR)  or  as user specified function definitions
(EXPR or FEXPR), an additional internal function FUNC is included  in
the  ECSD  LISP  system.  FUNC  either  passes control to an internal
function or APPLYs the user provided function definition.

integerfn func(recordname atom, integer args)
recordname atom(atom cell)
recordname cell(lisp cell)
switch type(0:3)

       ->type(atom_form&3)

type(3): ! apval
type(0): ! no function definition on property list
       result = error2 unless atom_bind=error1;  ! nor a binding
       result = apply(atom_bind,evlist(args))

type(1): ! expr or fexpr
       result = apply(atom_func,args)

type(2): ! subr or fsubr
       ->mach(atom_func);            ! jump to machine subroutine.

end


integerfn apply(integer fn, args)
recordname cell(lisp cell)
integer car, cadr, caddr

       if fn>=list base then start
          cell==list(fn);  car=cell_car
          cell==list(cell_cdr);  cadr=cell_car
          cell==list(cell_cdr);  caddr=cell_car

          if car=label then start
             bind(cadr,caddr)
             result = apply(caddr,args) 
          finish

          if car=lambda then start
             bindlist(cadr,args);                ! bind argument list.
             bind(cadr,list) if cadr#nil;        ! bind rest of list.
             result = unbind(eval(caddr));       ! eval and then unbind.
          finish

          result = apply(eval(fn),args)

       finish

       if fn>=name base start;                   ! symbolic atom.
          result = func(name(fn),args)
       finish

       result = error3;                          ! numeric atom.


end



3.6 the top level loop


   The top level of the ECSD  LISP  SYSTEM  consists  of  a  (PRINT
(EVAL (READ))) loop identified by the prompt 'LISP:'.

toplev = (lambda nil
   (prog temp
   l  (prind (cond ((eq (setq temp (read 'lisp:)) 'stop) (return 'stop))
                    (t (eval temp))))
      (go l)))


   The   system  will  normally  return  to  the  top  level  when  the
S-EXPRESSION input to the system at the top level has  been  evaluated,
but  the  system  may  be  forced  back  to the top level at any time by
evaluating the function '(RESET)'. The most common  use  of  which  is
from within a BREAK, to abandon a faulty computation.

   As  may  been  seen from the above code, the top level and hence the
LISP INTERPRETER are exited when the atom STOP is  read  at  the  top
level.


3.7 breaks


   An  extremely  powerfull  feature  of the ECSD LISP SYSTEM is the
BREAK: An internally defined LISP function, that is called  by  EVAL
when EVAL fails to evaluate an S-EXPRESSION.

break = (lambda (sexp cause)
  (prog (temp)
    (inunit 0) (outunit 0)
    (errmess cause)
 l  (cond ((not (eq (setq temp (eval (read '/ / / %:))) '%))
           (prind temp) (go l)))
    (return (cond ((eq (setq temp (eval (read 'eval:))) '%) (eval sexp))
                  (t temp)))))

   The BREAK performs four functions:

   1). It freezes a computation at the point of failure.

   2). It resets the input and output streams to the console.

   3). It  enters  a (PRINT (EVAL (READ))) loop, from which the user
       may examine and alter the state of his computation using the full
       power of the LISP system.

   4). It  resumes  the  computaion  under  user  control,  either   by
       reevaluating  the  S-EXPRESSION  that  originally  failed, or by
       substituting a new S-EXPRESSION, provided by the user,  for  the
       one that failed.

   examples

   lisp:(car 1)
   eval error:   (car 1)
       argument not of the correct form in (1)
      %:%
   eval:1
   1

      The  function  CAR is not defined for atomic arguments and hence
   fails to evaluate, with the result that a  BREAK  is  entered.  The
   user first types '%', in response to the prompt '   %:', to exit from
   the BREAK LOOP, and then enters an S-EXPRESSION in responce to the
   prompt  'EVAL:'. This S-EXPRESSION, in this case the ATOM '1', is
   then evaluted and the result, in this case also  the  ATOM  '1',  is
   returned  in place of the faulty S-EXPRESSION (CAR 1). As (CAR 1)
   was input at the top level, the result  returned  by  the  top  level
   EVAL  becomes  the  ATOM '1', and it is this that is printed by the
   top level print.

   lisp:(cdr b)
   eval error:   b
       atom is not bound to a value
      %:(peek)
   eval     * (cdr b)
   end of peek
      %:(setq b '(a b c))
   (a b c)
      %:%
   eval:%
   (b c)

      As CDR is a function that evaluates its  arguments,  EVAL  will
   evaluate  B  prior to applying CDR. In this case the evaluation of
   B fails, because B has no binding. The function  '(PEEK)'  prints
   out  the  contents  of the local stack, which contains both functions
   being applied and local bindings. In this case we see that EVAL  is
   being  applied  to (CDR B). The '*' indicates application, while a
   '=' indicates a binding. There are currently no local bindings. The
   user than gives B a global binding, in this case  the  list  (A  B
   C).  If  B had possessed a local binding, SETQ would have altered
   it. The user then exits from the BREAK LOOP and in response to the
   prompt 'EVAL:' types '%' which indicates that he wishes to  continue
   the  computation  by  reevaluating  the faulty S-EXPRESSION, in this
   case the ATOM B. As B  now  possesses  a  binding,  it  evaluates
   successfully,  to  the list (A B C). The CDR of this list is the
   list (B C), and it is this that is returned to, and printed at, the
   top level.

   lisp:(de fact(n) (cond  ((zerop n) (test)) (t (times n (fact (sub1 n]
   fact

      We now successfully define the function FACT at the  top  level.
   The  definition  is  faulty, as we make use of an undefined function
   (TEST), but this will only become evident when we use  the  function
   FACT.


   lisp:(fact 4)
   eval error:   (test)
       function not defined = test
      %:(peek)
   n        = 0
   fact     * (0)
   eval     * (times n (fact (sub1 n)))
   n        = 1
   fact     * (1)
   eval     * (times n (fact (sub1 n)))
   n        = 2
   fact     * (2)
   eval     * (times n (fact (sub1 n)))
   n        = 3
   fact     * (3)
   eval     * (times n (fact (sub1 n)))
   n        = 4
   fact     * (4)
   end of peek
      %:(reset)

      In  this case we decide there is no recovery possible and wish to
   return to the top level loop.  This  is  achieved  by  the  function
   (RESET), which aborts the current computation and returns to the top
   level via an error route.  ie. EVAL does not return.

   lisp:(fact 4)
   eval error:   (test)
       function not defined = test
      %:%
   eval:1
   24

      In  this  case we substitute the ATOM 1 for the call on (TEST),
   and continue the computation, which then returns the correct answer.

   lisp:(fact 4)
   eval error:   (test)
       function not defined = test
      %:(de test () 1)
   test
      %:%
   eval:%
   24

      In this case we define the function TEST to return the  ATOM  1
   as a result, and resume the computation by reevaluating (TEST).

   lisp:(editf fact)
   edit:(r* (test) 1)
   edit:%c
   end of editf
   lisp:(fact 4)
   24

      In this case we edit the function FACT, substituting the ATOM 1
   for  all  calls on the function (TEST). This removes the error from
   the definition of FACT, with the effect  that  (FACT  4)  evaluates
   correctly. The editor is described in detail in a later section.


3.8 tracing


   Tracing  is  a  mechanism  included in EVAL which allows the use of
functions, their arguments and the values they return to be monitored on
the currently selected output  channel.  The  FSUBR  TRACE  turns  on
tracing of a nominated function, while the FSUBR UNTRACE turns it off.
The messages that are output have the following form:


               model                             example
on call:   ---> function (arg1 arg2 . argn)    ---> CONS (A B)
on return: <--- function result                  <--- CONS (A  B)


   example

   lisp:(de fact (n) (cond ((onep n) 1)
   lisp:    (t (times n (fact (sub1 n]
   fact
   lisp:(trace fact)
   fact
   lisp:(fact 4)
   ---> fact (4)
   ---> fact (3)
   ---> fact (2)
   ---> fact (1)
   <--- fact 1
   <--- fact 2
   <--- fact 6
   <--- fact 24
   24
   lisp:(untrace fact)
   fact
   lisp:(fact 4)
   24



4.0 the lisp editor


   The editor, which is itself written in LISP, is a slightly modified
version of that provided with the LISP F1 system.

   The editor provides a powerful means of examining and altering list
structures.  It  is  normally  used for modifying bindings and function
definitions. For these two uses specific FEXPRS are  provided.  EDITB
is  provided  for editing bindings, while EDITF is provided for editing
function definitions.

   The command %C will cause the editor to return to  the  environment
from which it was called.

   In  the  same  way  that a text editor maintains a text pointer, the
lisp editor maintains a list pointer. Because lists  do  not  have  the
linear  structure  of text, we will not be able to move the list pointer
in the same way that we would move a text pointer, though the concept is
similar. Instead of moving a text pointer a number  of  chartacters  or
lines  forwards or backwards in the file, we may set the list pointer to
a sub-expression of the list at which it currently points.


4.1 moving the list pointer


   The user may descend into the stucture of a list by setting the list
pointer to a sub-expression of the current list. This is done by typing
a positive integer N, which will causes the list pointer to be  set  to
the  Nth  sub-expression  of  the  current  list.  This process may be
repeated to descend further into the list being edited. The  integer  0
forces the editor back to the outermost list.

   example

   edit:p*
   (a b c (d (e)) f)
   edit:4 p
   (d (e))
   edit:2 p
   (e)
   edit:0 p*
   (a b c (d (e)) f)


4.2 printing lists


   The  lisp object at which the list pointer is pointing is printed on
the console by typing the command P. To avaid wasteful  printing,  any
list  with  sub-lists  nesting  to greater than a depth of 3, is printed
only to depth 2, after  which  the  atom  ***  is  printed  to  indicate
continuation  of  the  list. An additional command p* is included which
will print the entire list without change.

   example

   edit:p*
   (a (b (c (d))))
   edit:p
   (a (b (*** ***)))


4.3 replacing list elements


   To replace the Nth sub-expression of the current  list  by  one  or
more  S-EXPRESSIONS  type  the  comand  (R  n  e1 e2 .) where n is a
positive integer and e1, e2 . are arbitrary S-EXPRESSIONS.

   To replace all occurances of a lisp object in the current list  type
the command (R* old new) where old is the object to be replaced and new
is the object that replaces it.

   example

   edit:p*
   (a b c (d (e)) f)
   edit:4 p
   (d (e))
   edit:(r 2 (g) h (a b))
   edit:0 p*
   (a b c (d (g) h (a b)) f)
   edit:(r* a (a a)) p*
   ((a a) b c (d (g) h ((a a) b)) f)


4.4 deleting list elements


   To  delete  the  Nth  sub-expression  of  the current list type the
command (D n) where n is a positive integer.

   example

   edit:p*
   (a b c (d (e)) f)
   edit:(d 3) p*
   (a b (d (e)) f)


4.5 inserting list elements


   To insert one  or  more  expressions  immediately  before  the  Nth
sub-expression  in  the  current list type the command (I n e1 e2 .),
where n is the number of the sub-expression and e1, e2 . are arbitrary
S-EXPRESSIONS.

   example

   edit:p*
   (a b c (d (e)) f)
   edit:4 p
   (d (e))
   (i 2 (g) h)
   edit:0 p*
   (a b c (d (g) h (e)) f)


4.6 deleting parentheses


   The command (BO n) where n is a positive integer, removes the first
level of parentheses from around the nth sub-expression of  the  current
list.  This  causes  the  elements  of the nth sub-expression to become
elements of the current list.

   The command (LO n) where n  is  a  positive  integer,  removes  the
outermost  left  parenthesis  from the nth sub-expression of the current
list. The outermost right parenthesis of the  nth  sub-expression  then
becomes  the  the  outermost  right  parenthesis  of  the  current list.
Elements that were previously to the right of the nth  element  in  the
current list are lost.


   examples

   edit:p*
   (a b c (d (e)) f)
   edit:(bo 4) p
   (a b c d (e) f)
   edit:(lo 5) p
   (a b c d e)


4.7 inserting parentheses


   The  command  (BI  m  n)  places  a left parenthesis before the mth
element of the current list  and  a  right  parenthesis  after  the  nth
element  of the current list, thus subordinating a number of elements of
the current list into the mth sub-expression.

   The command (LI n) places a left parenthesis before the nth element
of the current list, and a right parenthesis at the end of  the  current
list,  thus subordinating all elements of the current list starting with
the nth element into a sub-expression which becomes the nth element.


   example

   edit:p*
   (a b c (d (e)) f)
   edit:(bi 2 3) p*
   (a (b c) (d (e)) f)
   edit:(li 2) p*
   (a ((b c) (d (e)) f))


4.8 moving parentheses


   The command (R0 m) where m is a positive integer, moves the  righ:t
parenthesis  at the end of the mth sub-expression of the current list to
the end of the current list.


   The command (RI m: n) where m and n are  positive  integers,  moves
the  righ:t  parenthesis at the end of the mth sub-expression to the end
of the nth sub-expression in the mth sub-expression. It  has  the  same
effect  as  the  command (BO m) followed by the command (BI m+n) where
m+n is a positive integer equal to the sum of m and n.


   example

   edit:p*
   (a b c (d (e)) f)
   edit:(ri 4: 1) p*
   (a b c (d) (e) f)
   edit:(ro 4) p*
   (a b c (d (e) f))


5.0 functions


********** basic functions

QUOTE, FUNCTION                                                FSUBR

CAR, CDR ...... CADDR, CDDR                                     SUBR

CONS                                                            SUBR

LIST                                                            SUBR

EXPLODE                                                         SUBR

MAKEATOM                                                        SUBR

GENSYM                                                          EXPR


********** conditions & predicates

SELECTQ                                                         FSUBR

COND                                                            FSUBR

AND                                                             FSUBR

OR                                                              FSUBR

NOT, NULL                                                       SUBR

LISTP                                                           EXPR

ATOM                                                            SUBR

NUMBERP                                                         SUBR

EVENP                                                           SUBR

ONEP                                                            SUBR

ZEROP                                                           SUBR

MINUSP                                                          EXPR

EQ                                                              SUBR

EQUAL                                                           SUBR

LESSP                                                           SUBR

GREATERP                                                        SUBR


********** list maniputaion functions

APPEND                                                          EXPR

REVERSE                                                         SUBR


LENGTH                                                          EXPR

NTH                                                             EXPR

FIND                                                            EXPR

MEMB, MEMQ                                                      SUBR

MEMBER                                                          SUBR

ASSOC                                                           SUBR


********** arithmetic manipulation functions

PLUS                                                            SUBR

*PLUS                                                           SUBR

DIFFERENCE                                                      SUBR

*DIFFERENCE                                                     SUBR

TIMES                                                           SUBR

*TIMES                                                          SUBR

QUOTIENT                                                        SUBR

*QUOTIENT                                                       SUBR

ADD1                                                            SUBR

SUB1                                                            SUBR

MINUS                                                           EXPR


********** property list manipulation

PROP                                                            SUBR

GET                                                             SUBR

GETD                                                            EXPR

PUT, PUTPROP                                                    SUBR

DEFPROP                                                         FSUBR

REM, REMPROP                                                    SUBR

DF, DE                                                          FEXPR

DEFINE                                                          FEXPR

EDITF                                                           FEXPR


********** evaluation functions


EVAL                                                            SUBR

EVLIS                                                           SUBR

APPLY                                                           SUBR

ERRSET                                                          FSUBR

MAP, MAPC, MAPLIST, MAPCAR                                      EXPR


********** imperative functions

RPLACA                                                          SUBR

RPLACD                                                          SUBR

NCONC                                                           SUBR

CSETQ                                                           FEXPR

CSET                                                            EXPR

SETQ                                                            FSUBR

SET                                                             SUBR

EDITB                                                           FEXPR


********** programming functions

PROG2                                                           SUBR

PROGN                                                           FSUBR

PROG                                                            FSUBR

RETURN                                                          SUBR

GO                                                              FSUBR


********** i/o functions

READCH                                                          SUBR

READ                                                            SUBR

TEREAD                                                          EXPR

PRINC                                                           SUBR

PRIND                                                           SUBR

PRINT                                                           EXPR

TERPRI                                                          SUBR

INUNIT                                                          SUBR


OUTUNIT                                                         SUBR

INPUT                                                           SUBR

OUTPUT                                                          SUBR


********** meta functions

TRACE                                                           FSUBR

UNTRACE                                                         FSUBR

BREAK                                                           FSUBR

UNBREAK                                                         FSUBR

PEEK                                                            SUBR

GARB                                                            SUBR

RESET                                                           SUBR

ERR                                                             SUBR

OBLIST                                                          SUBR

ALIST                                                           SUBR