Friday, Dec 5,1980  LQ+5D.18H.52M.7S.     LISP 2057       - JonL -


1) Seven items of previous LISP RECENT (dated Oct 28,1980) have been emended:
    1a) Documentation available for (STATUS USRHUNK) etc. 
    1b) Both " and # are set up in the initial environment as readmacros.
    1c) CATCH and THROW are now autoloading macros from LISP:MLMAC.  
    1d) Warnings about MacLISP incompatibilites with NIL, and how to
	 overcome the most common ones.
    1e) +INTERNAL-PERMUTIBLE-P is an autoloading subr from LISP:MACAID.
    1f) PAIRP and FBOUNDP are now initial system subrs;  (PAIRP x) is the 
	 same as (EQ (TYPEP x) 'LIST),  and (FBOUNDP x) is non-null iff
	 x is a symbol with a functional "property".
    1g) Several "internal" subrs exist to augment compiled code:
	 *LDB, *DPB, *LOAD-BYTE, and *DEPOSIT-BYTE
    1h) At user level, the function's name is FIND-METHOD (rather than SI:...)
	 Also the names now are  SI:MAKE-EXTEND, SI:EXTEND, SI:EXTEND-LENGTH, 
	   SI:XREF, and SI:XSET  rather than the *:<...>  versions.
  [more exposition below]
2) ** Incompatible change**" ARRAYDIMS called on a "NIL" type array will 
    return (NIL ...) instead of (T ...) as formerly.
   New Functions, as on the LISPMachine:
	(ARRAY-DIMENSION-N <i> <array>) gets i'th dimension number of <array>
	(ARRAY-/#-DIMS <array>) gets the number of dimensions
	(ARRAY-TYPE <array>) is the same as (CAR (ARRAYDIMS <array>))
3) DEFVST "macros" now all share code to minimize space.
   Interpretive access to structure components checks the type of the struct.
   New macros STRUCT-LET and STRUCT-SETF have featureful convience.
  [more exposition below]
4) Three new functions autoloadable from DEFMAX file:
   MACROEXPAND-1*M is a multiple-value returning subr of 1 arg
      called like  (MSETQ-CALL (X ?) (MACROEXPAND-1*M Y))
   +INTERNAL-TRY-AUTOLOADP a subr of 1 argument autoloadable from DEFMAX, 
     tries to autoload a function's autoload file, if it has one.
   FLUSH-MACROMEMOS  -- to flush the macromemo "cache"; and some new
		settings for the switch DEFMACRO-DISPLACE-CALL
  [more exposition below]
5) Some more LISPM-compatible autoloadable facilities, and error facilities.
   CERROR, FERROR, and ERROR-RESTART as on LISPM, from LISP:CERROR file.
     also a new subr +INTERNAL-LOSSAGE of three args, for use when an 
     "unreasonable" point is reached.
   Y-OR-N-P from LISP:YESNOP file, for interactive querying.
   New "error-checking" routines from LISP:ERRCK file
	Documentation below for CHECK-TYPE and CHECK-SUBSEQUENCE.
  [more exposition below]
6) SXHASH may dynamically be adjusted to be more anti-symmetric
  [more exposition below]
7) LOOP and DEFINE-LOOP-PATH are now autoloading
   See the documentation file .INFO.;LISP LOOP, or the LCS Technical Report
   "LOOP Iteration Macro"  MIT/LCS/TM-169.
8) DELASSQ, a new LSUBR of 2 or three args, is a cross between DELQ and ASSQ
	(DELASSQ 'A '((A . 1) (B . 2) (A  . 3))) ==> ( (B . 2) )
	but remember, that like DELQ, rplacds are being done.
9) #(...) notation is usable now whenever the VECTOR package is loaded; the
	print method for vectors generatates this syntax, and # will read it.
   #B is usabe when the BITS package is loaded;
   #T is usable when the EXTEND packages is loaded (any new NIL data type
	usage will load EXTEND).  In MacLISP, #T is synonymous with T.
   #*400000000* now reads in correctly.
10) Four new internal subrs, to help with various STRING packages:
	+INTERNAL-CHAR-N   	 +INTERNAL-RPLACHAR-N
	+INTERNAL-STRING-WORD-N  +INTERNAL-SET-STRING-WORD-N
  [more exposition below]
11) Value of the variable PURCOPY is a list of things which the
     PURCOPY function should not actually copy.  For example, CLASS objects 
     should never be moved, and hence can't be PURCOPYied.
12) The function SQOZ/| is no longer part of the basic system -- it is
	defined in the GETMIDASOP file.

For TWENEX users:
X1) Twenex MacLISP offers a parsable "init file" facility now 
    CURSORPOS and "rubout" of TTY input now work on systems with VTS
  [more exposition below]

____________________________________________________________________________

1) Six items of previous LISP recent have been emmended significantly:
   1a) Documentation available for (STATUS USRHUNK) etc. 
   1b) Both " and # are set up in the initial environment as readmacros.
   1c) CATCH and THROW are now autoloading macros from LISP:MLMAC.  
   1d) Warnings about MacLISP incompatibilites with NIL, and how to
        overcome the most common ones.
   1e) +INTERNAL-PERMUTIBLE-P is an autoloading subr from LISP:MACAID.
   1f) PAIRP and FBOUNDP are now initial system subrs;  (PAIRP x) is the 
	same as (EQ (TYPEP x) 'LIST),  and (FBOUNDP x) is non-null iff
	x is a symbol with a functional "property".
   1g) Several "internal" subrs exist to augment compiled code:
	*LDB, *DPB, *LOAD-BYTE, and *DEPOSIT-BYTE
   1h) At user level, the function's name is FIND-METHOD (rather than SI:...)
	 Also the names now are  SI:MAKE-EXTEND, SI:EXTEND, SI:EXTEND-LENGTH, 
	   SI:XREF, and SI:XSET  rather than the *:<...>  versions.

  1a) Four new STATUS calls permit hooks into system functions, when given
      hunks as arguments -- used as the basis of the EXTEND system, as
      the LISP RECENT note of Oct 28,1980, item 3.   See the documentation 
      file  ".INFO.;LISP SEND" on ITS systems and "LISP:SEND.DOC" on 
      TOPS-10/20 systems.  See also ".INFO.;LISP EXTEND" on ITS systems and 
      "LISP:EXTEND.DOC" TOPS-10/20 systems.  
   (SSTATUS USRHUNK <function>) specifies the "user hunk" predicate, which
	determines whether to "hook into" a user-provided definition for
	some system facility, or to treat the data strictly as a hunk.
   (SSTATUS SENDI <function>)  specifies a "SEND" interpreter -- <function>
	is invoked in order to send a "message" to a "user hunk", when a
	hunk which passes the "usrhunk" test is given as argument to any of
	    EQUAL  SUBST  PURCOPY  EVAL  PRINT  EXPLODE  FLATSIZE
	    ALPHALESSP  SAMEPNAMEP  NAMESTRING  SXHASH
	or to any of the following out-of-core facilities
	    GFLATSIZE  SPRINT  USERATOMS-HOOK  DESCRIBE  WHICH-OPERATIONS    
	See the file LISP:SEND.DOC (or .INFO.;LISP SEND on ITS systems)
   (SSTATUS CALLI <call-interpreter>)  specifies a "transfer function" to be
	used when when a "user hunk" is FUNCALL'd.  This is a hand-coded
	substitute for the IAPPLY internal LISP routine.
	See the file LISP:SEND.DOC (or .INFO.;LISP SEND on ITS systems)
   (SSTATUS VECTOR `(<vectorp> <vector-length> <vref>)) specifies the functions
	for LEXPR-FUNCALL to use for determining if the argument to be spread
	is a vector, determining its length, and accessing its elements.
	This allows one to do (LEXPR-FUNCALL #'LIST 'A 'B #(C D E)), for
	example, yielding (A B C D E).

  1b)	Both " and # are set up in the initial environment as readmacros.
   # still requires the file LISP:SHARPM.FASL, but the default function 
   for " will still create a pseudo-string (un-intern'd symbol) rather than 
   requiring the full STRING support package; loading in the file 
   LISP:STRING.FASL will do a SETSYNTAX on " to get real STRINGs.

  1c) CATCH and THROW will expand according to the old syntax, but someday 
   this may change;  currently (CATCH exp tag) ==>  (*CATCH 'tag exp)
   and similarly for THROW.


  1d)	A MacLISP pre-loaded with most of the NIL facilities, is obtained by
   running the subsystem NILAID (NILAID^K on ITS systems);  this is more-
   or-less a union of the MacLISP and NIL facilities, but one must remember 
   the following incompatibilities: 
    (1) The nullist is identified with the symbol |NIL| in MacLISP, but 
	has a unique new data type in NIL, so NIL code which depends on 
	the non-symbolness of the nullist wil lose -- check your usages
	of SYMBOLP.
    (2) The function atom is "false" for hunks in MacLISP, and thus is 
	"false" for STRINGs, VECTORs and all other data embedded into the 
	USRHUNK feature, so it would be more compatible to use (PAIRP X) 
	rather than (NOT (ATOM X)), if you want to distinguish cons cells.  
	The function LISTP is equivalent to (OR (NULL X) (PAIRP X)).
    (3) FBOUNDP in NIL will only return "true" or "false" -- namely #T 
	or () -- but in MacLISP, it returns the information from the GETL
	function, when "true";  thus there is more information in the
	MacLISP result.
	    Since there are no real SUBR objects in MacLISP, the result of 
	FSYMEVAL will not be compatible; but used in limited ways, it will 
	work, e.g. (FSET 'MUMBLE (FSYMEVAL x)).
    (4) CATCH (and THROW) in MacLISP still has the old semantics, but in NIL 
	and NILAID it has the new, namely the same as *CATCH (and *THROW);
	use the * versions and be safe.
    (5) CASEQ will not work on CHARACTER objects in MacLISP
    (6) DEFUN will not keep track of the "documentation" string.
    (7) No real package system is set up -- so GET-PNAME merely returns
	the portion of a pname-string following the first ":" (if any).

   1e) +INTERNAL-PERMUTIBLE-P is an autoloading subr from LISP:MACAID.
	(+INTERNAL-PERMUTIBLE-P l)  is non-() iff the forms on the list 'l' 
	may be EVAL'd in any order, and get the same results/effects.  For 
	example  (5 (MUMBLE X))  is permutible, since nothing which happens 
	inside MUMLBE can affect the value of 5;  but  (X (RPLACA Y))  is not 
	permutible, since X may point to a list which is updated by the RPLACA.

   1g) Currently, the compiler may turn LDB into a call to the internal 
	subr *LDB, which has args the same as LDB except the "ppss" arg has 
	been lsh'd by 30. places (also, no type-checking is done on the args).
	Similar remarks apply for *DPB, *LOAD-BYTE, and *DEPOSIT-BYTE.   
	Another alternative is that it may turn LDB into a LSH followed by 
	a LOGIOR.  Someday, it may open-code these into an actual pdp10 LDB.

   1h) For a certain amount of time, the EXTEND file will probably also put
	macro definitions on *:<foo> to become SI:<foo>, the names
	EXTEND, EXTEND-LENGTH, MAKE-EXTEND, XREF, and XSET.

3) DEFVST "macros" now all share code to minimize space.
   Interpretive access to structure components checks the type of the struct.
   New macros STRUCT-LET and STRUCT-SETF have featureful convience.

	Accessor macros for a structure generally gave rise to a modest
   amount of code, but a new scheme has just been implemented in which
   all such macros use precisely one function;  each accessor macro, or
   constructor macro, needs only two properties on its property list -- 
   a MACRO property pointing the the single expander function, and a
   small SELECTOR or CONSTRUCTOR property.  Similarly, the output of
   the DEFVST macro is significantly smaller, due to calling an 
   initialization function which will be autoloaded when needed, 
   rather than expanding out lots of lisp code.   In interpreter usages   
   of selector "macros" (in *RSET mode) the code will certify that a 
   selector macro is being applied to a structure of the correct type;
   if not, a proceedable error will be performed.
	STRUCT-LET and STRUCT-SETF have been devised to facilitate
   multiple settings, or gettings, of structure components.   For example, 
   suppose DESK is a strucure with four components, defined like 
   (DEFVST DESK A B C D), and suppose that <grey> is a DESK possibly
   created by (SETQ <grey> (CONS-A-DESK C 'FULL)).  Then
     (STRUCT-SETF (DESK <grey>) (A 'PAPER) (B 25.) (D (folders)))
   expands into a short program to fill in the DESK-A, DESK-B, and DESK-D 
   components of <grey>.   Also
     (STRUCT-LET (DESK <grey>) (A (D) (MIDDLE-DRAWER B))
	... do-some-work ... )
   would lambda-bind the variables A, D, and MIDDLE-DRAWER respectively to 
   the DESK-A, DESK-D and DESK-B components of <grey> and then do further
   work, indicated like the implicit progn of a LET.
	The code for DEFVST has been split up into three files.  The new
   file DEFVSX (and auxillary file for structure usage) contains various
   common selector-macro expansion functions, constructor functions, etc;
   the file DEFVST now contains only the DEFVST macro itself, and all the
   various "methods" applicable to objects in the class STRUCT-CLASS.  It
   should be possible to have a file of code which defines and uses
   structures, but which when compiled needs neither file loaded;  the
   DEFVSX file would be loaded if in the resultant object environment
   it becomes necessary to expand any accessor/constructor macros at runtime.
   One needn't have DEFVST loaded except when compiling, or when wanting the 
   more refined methods available through the EXTEND class hierarchy (as
   opposed to treating structures merely as hunks).
	The third file is DEFVSY, and is loaded whenever the output of
   DEFVST, in the runtime environment, actually is constructing up new
   instances of a defined structure.  DEFVSY takes about 250. words of 
   binary program space, and thus will probably "pay for itself" in
   terms of the code saved in the CONS-A-foo expansions.   DEFVSX takes
   about 590.; and DEFVST takes about 1040.
	DEFVST created structures interface into the MacLISP (and NIL)
   CLASS system, but they do not load it if not already loaded.  Structure
   instances created before the CLASS system is loaded will leave around
   a "skeleton" class, which the cooperating EXTEND file will "flesh out"
   when it is loaded.  Typical usage of structures should cause no
   overhead in the run-time environment except possibly the DEFVSY file
   and a few "skeletal" classes.

4) Three new functions autoloadable from DEFMAX file:
   MACROEXPAND-1*M is a multiple-value returning subr of 1 arg
      called like  (MSETQ-CALL (X ?) (MACROEXPAND-1*M Y))
   +INTERNAL-TRY-AUTOLOADP a subr of 1 argument autoloadable from DEFMAX, 
     tries to autoload a function's autoload file, if it has one.
   FLUSH-MACROMEMOS  -- to flush the macromemo "cache"; and some new
		settings for the switch DEFMACRO-DISPLACE-CALL

   MACROEXPAND-1*M does one step in the macroexpansion of its argument, 
   and returns that expansion (or the original form if it didn't represent
   a macro call, and also returns a flag, T or (), telling whether or not 
   any expansion was done.

   The argument to +INTERNAL-TRY-AUTOLOADP should be a symbol; it tries to 
   load in the file from the autoload property of its argument, if there is 
   one.   Non-null return value iff it did the loading.


	A user may request flushing all the "cacheings" for expansions
   of a macro FOO by doing (FLUSH-MACROMEMOS 'FOO () ), and may flush
   all "cacheings" by (FLUSH-MACROMEMOS () () ).  Here, the word "flush"
   really means "invalidate", and generally nothing is done during
   "flushing" except updating some validation counter.  
	This problem may be more thoroughly described by the following
   explanation.  When DEFMACRO is used to define a macro, the value of  
   thes witch  DEFMACRO-DISPLACE-CALL  determines whether the original  
   cell which started out with a macro call will be displaced, either by 
   the result of the macro expansion directly, or by an "expanded" marker
   which acts like a "cache" for the expansion; a third alternative
   is not to displace, but to enter into a hash table.  A problem arises
   in trying to determine when to invalidate such "cache" or hash-table
   entries; clearly, such an invalidating must be done when the particular
   macro is redefined, but many macros call the function MACROEXPAND,
   and hence the value of their expansion would likely be changed by 
   redefining some other (totally random?) macro.  As a step in solving
   this problem, the durrent DEFMAX code recognized four conditions --
   A "cached" or hash-tabled expansion which becomes invalid: 
     1) Only when the particular macro which gave rise to it is redefined.
     2) When any macro is re-defined (including the one for which the
	expansions itself was done).  All formerly compiled DEFMACROs
	will currently fall into this category.
     3) When a new structure is defined (by means of DEFVST); this would
	be the case for a generalized structure-hacking macro such
	as STRUCT-LET, which utilizes information about a structure
	being decomposed, as well as any sub-macroexpansions.
     4) When the user requests that all "cacheings" for this particular
	macro, say FOO, be flushed -- this can now be done by 
	(FLUSH-MACROMEMOS 'FOO () ) -- 	or when the user requests that all 
	"cacheings" or hash-tableings be invalidated;  this can now be done 
	by (FLUSH-MACROMEMOS () () ).
   Currently, a test of the switch DEFMACRO-DISPLACE-CALL at performed at
   macro-definition time to determine which one of 1-3 will be the case:
    (EQ DEFMACRO-DISPLACE-CALL MACROEXPAND) 		   -- case 1
    (EQ DEFMACRO-DISPLACE-CALL '|defvst-construction/||)   -- case 3
    (NULL DEFMACRO-DISPLACE-CALL) 			   -- no "cacheing"
    (EQ DEFMACRO-DISPLACE-CALL 'DEFMACRO-DISPLACE)	   -- direct displace
     any other value for DEFMACRO-DISPLACE-CALL		   -- case 2
   Note that the value which selects case 1 is not the (interned) symbol
   MACROEXPANDED, but its value as a global variable;  this is a "safety"
   feature so that one will be less likely to get case 1 accidentally.
   Also note that the second argument to FLUSH-MACROMEMOS, if not null,
   is a signal to set up the right kind of flusher:
	case 1 -- 	'FLUSH-MACROMEMOS 	
	case 2 -- 	value of MACROEXPEND
	case 3 -- 	'|defvst-construction/||

5) Some more LISPM-compatible autoloadable facilities, and error facilities.
   CERROR, FERROR, and ERROR-RESTART as on LISPM, from LISP:CERROR file.
     also a new subr +INTERNAL-LOSSAGE of three args, for use when an 
     "unreasonable" point is reached.
   Y-OR-N-P from LISP:YESNOP file, for interactive querying.
   New "error-checking" routines from LISP:ERRCK file
	Documentation below for CHECK-TYPE and CHECK-SUBSEQUENCE.

   Only CHECK-TYPE, CHECK-SUBSEQUENCE and +INTERNAL-LOSSAGE aren't documented 
   in the LISPM manual.  The first two are macros which produce code calling
   some internal subrs.
	 CHECK-TYPE takes a variable name (which it "quotes"), a function 
   usable as a type-testing predicate, and a symbol naming the routine which
   wants the test done.  CHECK-SUBSEQUENCE sets up a multiple return
   value call and thus wants a list of variable names (again "unquoted"), 
   the name of a sequence type such as LIST, VECTOR, STRING or BITS (or null 
   which means any "sequence" is acceptable), and the name of the routine
   which wants the test done.  In each case, the macro produces code to
   pass the "variables" to the internal checker, and to setq them to
   the possibly-corrected return values; if the type of the main argument
   isn't correct, a :WRONG-TYPE-ARGUMENT condition is signalled to CERROR,
   and the corresponding variable is set to the returned value;  similarly,
   if the subsequence designated by the two more variables for "start
   index" and "number of items" doesn't lie within the main argument,
   then a :INCONSISTENT-ARGUMENTS condition is signalled.   Examples:
     (CHECK-TYPE X #'FLONUMP 'Hooperbylic-SIN) 
     (CHECK-SUBSEQUENCE (IN-STRING 1ST-CHAR-INDEX NCHARS) 'STRING 'MY-DOIT)
   The "number of items" variable may be written as (), in which case the
   check is merely that the index is valid for the sequence;  also, it may
   be calculated up by the internal routine to coincide with the end of the
   sequence, by passing an optional 5th arg of ().  E.g.
     (CHECK-SUBSEQUENCE (IN-STRING 1ST-CHAR-INDEX HAUMANY) 
			'STRING 
			'MY-DOIT
			() 
			() )
   would have one effect like 
     (SETQ HAUMANY (- (STRING-LENGTH IN-STRING) 1ST-CHAR-INDEX))

      +INTERNAL-LOSSAGE is for use when system code is admittedly
   incomplete, or some unfathomable point has been reached.
   (+INTERNAL-LOSSAGE <msg> <fun> <datum>) will print a message identifying
   this point, and run a FAIL-ACT error.  <msg> should be an identifier, and 
   <fun> should be the name of the function which is complaining;  <datum> if 
   non-() may be an associated piece of data.


6) SXHASH  may dynamically be adjusted to be more anti-symmetric
	It seems that most persons are in favor of a change in the SXHASH
   algorithm which would break its current symmetric behaviour on lists;
   as the consequences of making this change are rather light, we offer
   a status call which will dynamically do it; but the initial setting
   is still the old way.  Someday soon, we may set the default state
   to be this new anti-symmetric version.  The consequences of having two 
   different sxhash'ers for lists are primarily that extra space may be 
   taken when loading in previously compiled files, or when using the
   EXPR-HASH feature;  thus the change-over will likely be co-ordinated
   with a massive re-compilation of all system FASL files, and probably
   all MACSYMA files.
	(SSTATUS SXHASH 'T), the current default, causes SXHASH to maintain 
   compatibility with the algorithm prior to the date Nov 3, 1980; 
   (SSTATUS SXHASH () ) activates the new alogrithm
	(defun SXHASH-FOR-LIST (x)
	   (+ (rot (sxhash (car x)) 11.) (rot (sxhash (cdr x)) 7)))
   Note that the use of an output from sxhash should be such that
   "all bits are considered".  For example, if you want to reduce the range
   further to something less than the 36-bit 2's complement number that comes
   out, don't just take the low 18. bits or something like that, but take 
   the remainder upon division by a suitable prime.


10) Four new internal subrs, to help with various STRING packages:
	+INTERNAL-CHAR-N   	 +INTERNAL-RPLACHAR-N
	+INTERNAL-STRING-WORD-N  +INTERNAL-SET-STRING-WORD-N

   The first two are interrupt-protected, non-checking versions of 
   CHAR-N and RPLACHAR-N; the second two are similar, but deal
   with PDP10 words rather than characters.  STRAUX (the STRing
   AUXillary file) will guarantee that these functions exist, either
   by noting their presence in the lisp system, or by supplying
   a somewhat-less-than-perfect version itself.


X1) Twenex MacLISP offers a parsable "init file" facility now 
    CURSORPOS and "rubout" of TTY input now work on systems with VTS
	As with MacLISP other on operating-systems, a space right after
   the subsystem name causes supression of the init facility.  Thus,
     @MACLISP<cr>		;gets the default, LISP.INI, if it exists
     @MACLISP<space><cr>	;stops the search for an init file.
     @MACLISP FOO.BAR		;gets FOO.BAR as a LISP.INI file
   TOPS-20 systems may soon get the Virtual Terminal Service developed
    by Mike Travers at MIT-XX (now with Foonly); MacLISP uses it to
    achieve CURSORPOS and a "rubout" facililty for type-in