FRIDAY  JULY 19,1974   NM+8H.29M.40S.   LISP 861   - GLS -

BRIEF SYNOPSIS:

[1] NEW FUNCTIONS:  UPROBE, UCLOSE, UAPPEND
[2] DEFPROP NOW DOES REMPROP FIRST, AS DEFUN ALWAYS HAS
[3] (NOINTERRUPT 'TTY) - NEW NOINTERUPT OPTION
[4] PDLFRAME HAS DISAPPEARED - USE EVALFRAME
[5] (SSTATUS CRFILE ...)  SETS UREAD FILE NAME DEFAULTS
[6] VALUE OF // INTERACTS WITH ERRLIST; *, +, - MENTIONED
[7] ONE MAY THROW OUT OF A USER INTERRUPT NOW
[8] APPLYFRAMES WIN BETTER - FEAR NOT
[9] UNPURIFY$G DEPURIFIES ALL PAGES - PURIFY$G WILL REPURIFY THEM
[:] COMPLR/NCOMPLR HAVE PRIVATE OBARRAY AS WELL AS READTABLE
[;] MIDAS AND FASLOAD COOPERATE
----------------------------------------------------------------
[1] THREE NEW FUNCTIONS FOR OLD I/O:
   [1A] UPROBE TAKES ARGUMENTS LIKE UREAD, AND TRIES TO FIND
	THE FILE SPECIFIED.  IF IT EXISTS, UPROBE RETURNS THE
	ACTUAL FILE NAMES; IF NOT, IT RETURNS NIL.
   [1B] UCLOSE (OF NO ARGUMENTS) CLOSES THE UREAD INPUT
	CHANNEL.  THIS IS PRIMARILY OF USE BEFORE CALLING THE
	SUSPEND FUNCTION.
   [1C] UAPPEND (ARGUMENTS LIKE UREAD) OPENS THE SPECIFIED
	FILE, WHICH MUST ALREADY EXIST, FOR WRITING.
	THE FILE IS RENAMED TO BE ".LISP. APPEND", AND BECOMES
	NON-ACCESSIBLE (YOU SEE A * NEXT TO IT IN THE
	DIRECTORY).  ANY OUTPUT DIRECTED TO THE UWRITE OUTPUT
	CHANNEL (THE ^R SWITCH) IS THEN OUTPUT TO THIS FILE,
	APPENDED TO THE PREVIOUS CONTENTS.  WHEN THE FILE
	IS EVENTUALLY CLOSED WITH UFILE, IT WILL TAKE ON THE
	FILE NAMES SPECIFIED BY UFILE, AND WILL CONTAIN ITS
	OLD CONTENTS WITH THE NEW MATERIAL TACKED ONTO THE
	END.  NOTE THAT UAPPEND IS REALLY MORE LIKE NCONC
	THAN APPEND! I.E. IT DOES NOT COPY THE FILE, BUT
	ADDS ONTO THE EXISTING ONE, CLOBBERING IN NEW DATA.

[2] DEFPROP USED TO BE DESCRIBED AS
	(DEFUN DEFPROP FEXPR (X)
	       (PUTPROP (CAR X) (CADR X) (CADDR X)))
    THANKS TO AGITATION BY CERTAIN PARTIES, IT IS NOW
	(DEFUN DEFPROP FEXPR (X)
	       (REMPROP (CAR X) (CADDR X))
	       (PUTPROP (CAR X) (CADR X) (CADDR X)))
    THAT IS, DEFPROP IS GUARANTEED TO PUT THE NEW PROPERTY
    AT THE HEAD OF THE PROPERTY LIST.  NOTE THAT DEFUN HAS DONE
    SUCH REMPROPING IN THE PAST ALREADY.

[3] NOINTERRUPT HAS BEEN EXTENDED TO HAVE THREE STATES:
	(NOINTERRUPT T) CAUSES ALL ASYNCHRONOUS USER
		INTERRUPTS TO BE DELAYED (AS BEFORE;
		"ASYNCHRONOUS" INTERRUPTS ARE PRESENTLY
		TTY CONTROL CHARS AND THE ALARMCLOCK)
	(NOINTERRUPT NIL) LETS SUCH INTERRUPTS GO THROUGH
		IMMEDIATELY (THE INITIAL STATE); ANY
		DELAYED INTERRUPTS ARE RUN DURING THIS CALL.
   ***  (NOINTERRUPT 'TTY) CAUSES ONLY TTY INTERRUPTS TO
		BE DELAYED, AND LETS OTHERS GO THROUGH.
		IN THIS WAY ONE CAN SUPPRESS ^G QUITS, ETC.,
		BUT STILL ALLOW CLOCK INTERRUPTS.

[4] PDLFRAME, A SYNONYM FOR EVALFRAME, HAS DISAPPEARED.
    USE EVALFRAME FROM NOW ON.

[5] (SSTATUS CRFILE FOO BAR) WILL SET THE UREAD FILE NAME
    DEFAULTS TO "FOO BAR".  (STATUS CRFILE) READS THEM,
    AS BEFORE.

[6] THE ATOM // IS NOW A VARIABLE, USED IN CONJUNCTION
    WITH ERRLIST.  WHEN AN ERROR PROPAGATES BACK TO TOP LEVEL,
    THEN WHERE THE TOP LEVEL FORMERLY DID
		(MAPC (FUNCTION EVAL) ERRLIST)
    IT NOW DOES INSTEAD
		(MAPC (FUNCTION EVAL) //)
    AND WHEN AN ERROR OCCURS, THEN (SETQ // ERRLIST)
    IS PERFORMED.  THUS THIS NEW MECHANISM WORKS ALMOST LIKE
    THE OLD, WITH ONE IMPROVEMENT (SUGGESTED MY MACRAKIS):
    ONE CAN LAMBDA-BIND ERRLIST OVER A COMPUTATION, AND IF
    AN ERROR OCCURS THE CURRENT ERRLIST WILL BE USED AND NOT
    THE TOP-LEVEL ERRLIST.  THIS MAY SOMETIMES BE A DESIRABLE
    ALTERNATIVE TO ERRSET.
    RECALL AGAIN THAT *, +, AND - ALSO HAVE MEANINGFUL VALUES:
	*  CONTAINS THE LAST THING TYPED OUT BY LISP'S TOP
	   LEVEL.  THUS IF YOU FORGOT TO TYPE A SETQ AROUND
	   THE PREVIOUS FORM, YOU CAN STILL RETRIEVE THE
	   RESULTANT VALUE.
	+  CONTAINS THE LAST THING READ BY LISP'S TOP LEVEL.
	   THIS IS USEFUL IN CASE OF A TYPING ERROR; YOU CAN
	   SAVE THE FORM AND MAYBE EDIT IT.
	-  CONTAINS THE CURRENT THING READ BY THE TOP LEVEL
	   (WHEN EVALUATION OF THE THING IS COMPLETED, THEN
	   SOMETHING LIKE (SETQ + -) HAPPENS).
    NOTE THAT ERROR BREAKS SAVE +, SO THAT IF YOU SAY:
	(PLUS 3 'A)		;LOSEY LOSEY
	A NON-NUMERIC VALUE	;LISP COMPLAINS
	;BKPT WRNG-TYPE-ARG
	(PLUS 3 5)		;DO SOME STUFF IN THE BREAK
	10
	$P			;RETURN FROM BREAK
	A NON-NUMERIC VALUE	;LISP GRIPES AGAIN
	(SETQ FOO +)		;NOW SAVE VALUE OF +
	(PLUS 3 'A)		;IT IS FORM THAT LOST

[7] FORMERLY USER INTERRUPTS WERE AN IMMOVABLE WALL WITH
    RESPECT TO THROWS; NOW THEY ARE TRANSPARENT.  THIS
    MEANS THAT YOU CAN THROW OUT OF A USER INTERRUPT IN
    THE OBVIOUS MANNER.  EXAMPLE:

	(SSTATUS INTERRUPT 0 '(LAMBDA (X) (THROW NIL ABORT))
	(CATCH (HAIRY-COMPUTATION) ABORT)	;HAIRY MESS

    IN THIS WAY ONE CAN ABORT THE HAIRY MESS BY TYPING ^@.

[8] SOME PEOPLE HAVE COMPLAINED OF SUPER-SLOWNESS WHEN RUNNING
    IN *RSET MODE.  THIS WAS DUE TO FAULTY DESIGN IN THE
    APPLYFRAME ROUTINES, WHCIH CAUSED CONSING ON EVERY
    FUNCTION CALL.  THIS HAS BEEN CORRECTED, SO DON'T FEAR
    TO USE *RSET MODE NOW.

[9] UNPURIFY$G TO A LISP OR BLISP WILL UNPURIFY ALL PURE
    PAGES IN THE LISP BY COPYING THEM.  THIS IS PRIMARILY
    SO THAT JPG CAN WIN WHEN DUMPING MACSYMA.  PURIFY$G
    WILL THEN REPURIFY THE (COPIED) PAGES.

[:] NCOMPLR WINS WITH ARRAYCALL NOW, BUT COMPLR DOES NOT.
    ALSO, BOTH COMPLR AND NCOMPLR HAVE A PRIVATE OBARRAY
    AS WELL AS READTABLE (CALLED COBARRAY AND CREADTABLE).

[;] GREENBLATT (RG) HAS HACKED MIDAS SO THAT IT CAN PRODUCE
    FASL FORMAT OUTPUT; THUS ONE CAN USE ALL THE MACRO
    FEATURES TO PRODUCE CODE TO LOAD INTO LISP.
    THE FOLLOWING IS A COPY OF  AI:MIDAS;FASL >  WRITTEN BY RG.


FASL Feature In Midas.

	Midas can now assemble FASL files that can be loaded
by LISP in the same manner as LAP FASL output.  This mode is
entered by the .FASL pseudo op, which must appear at the
beginning of the file before any storage words.
	After .FASL has been seen, the assembly becomes a
two pass relocatable assembly.  However, certain
restrictions and "changes of interpretation" apply.
	Global symbols (declared as usual with " or .GLOBAL)
are persmissible. However, since the output is to be loaded
with FASLOAD using DDT's symbol table instead of STINK,
there are quite a few differences in detail.
	For symbols defined within the current assembly, the
only effect of being declared GLOBAL is that the GLOBAL
information is passed on to FASL when the symbol table is
written at the end of pass 2.  This in combination with the
SYMBOLS switch in FASLOAD determines whether the symbol gets
loaded into DDT's symbol table.  If SYMBOLS is NIL, no
symbols will be loaded; if SYMBOLS is EQ to SYMBOLS, only
globals will be loaded; and if SYMBOLS is T, all symbols
(local and global) will be loaded.  Once the symbol is
loaded (or not), the information as to its GLOBALness is
lost and, of course, makes no further difference. The
initial state when LISP is loaded is NIL.
	GLOBAL symbols not defined in the current assembly
are also legal, but there are additional restrictions as to
where in a storage word they may appear and what masking may
be specified (as compared to a normal relocatable assembly).
Briefly, they may appear as in a storage word as a full
word, a right half, a left half, or an accumulator. They may
be negated, but can not be operated on with any other
operator.  Error printouts will be produced if they appear
elsewhere.  When the symbol is encountered by FASLOAD, DDT's
symbol table is consulted.  If it is defined at that time,
OK, otherwise FASLOAD will generate an error.
	Any sort of global parameter assignment or location
assignment is Forbidden.  .LOP, .LVAL1, .LVAL2, etc are not
available.


New Pseudo OPs Available only in FASL assemblies.

	The following pseudos are available to facilitate
the communication between MIDAS assembled programs and LISP
(particularily with regard to list structure).

.ENTRY function type args

	Function is an atom and is taken as the name of
	a function beginning at the current location.  Type
	should be one of SUBR, FSUBR or LSUBR, and has the
	obvious interpretation.  Args is a numeric-valued field
	which is passed thru to FASLOAD and used to construct
	the args property of the function.  If it is zero, no
	args property is created. Otherwise it is considered to
	be a halfword divided into two 9 bit bytes, each of
	which is converted as follows:
		      byte    result
			0	nil
			777	777
	otherwise	n	n-1
	These two items are then CONSed and from the
	args property.

The following pseudos may appear in constants!!

.ATOM atom

	followed by a LISP atom in "MIDAS" format (see below). 
	May only appear in right half (or entire word) of a
	storage word.  Assembles into a pointer to the atom
	header of the specified atom.

.SPECI atom

	similar to .ATOM but assembles into a pointer to the
	SPECIAL value cell of the specified atom.

.FUNCT atom

	similar to .ATOM, but invokes special action by FASLOAD
	in case the PURESW is on. Normally used in function
	calls. Briefly, if FASLOAD is going to purify the
	function it is loading, it must "snap the links" first.
	If .FUNCT is used, the location will be examined by
	FASLOAD and the link snapped if possible before
	purification.
     Typical usage:
	CALL 2,.FUNCT EQUAL	;calls equal as a function of 2 args
				; note: the CALL is not defined
				; or treated specially by MIDAS.

.ARRAY atom

	similar to .ATOM, but assembles into a pointer to the
	Array SAR.

.SX S-expression

	similar to .ATOM, but handles a LISP S-expression. 
	(See below).

.SXEVA S-expression

	reads S expression. This S expression is EVALed (for
	effect presumably) at FASLOAD time.  The resulting
	value is thrown away. Does not form part of storage
	word.

.SXE S-expression

	Similar to .SX but list is EVALed at FASLOAD time.  The
	resulting value is assembled into storage word.


The MIDAS "LISP READER"

	By a conspiracy between MIDAS and FASLOAD, a version
of the LISP reader is available.  However, due to historical
reasons (mostly, i.e. the FASLOAD format was originally
intended only to deal with COMPLR type output), there are a
number of "glitches" (see below for list).  These will
probably tend to go away in the fullness of time.

a) numeric ATOM

	The first character of a LISP atom is examined
specially. If it is a # or &, the atom is declared to be
numeric and either fixed (#) or floating (&).  Midas then
proceeds to input a normal numberic field (terminated, note,
by either space or comma). This value is then "stored" in
the appropriate "space" (fixnum space or flonum space).

b) other ATOMs (also known as PNAME atoms or (LISP) SYMBOLS)

	If the first character of the  atom is not # or &,
the atom is a "PNAME" atom. / becomes a single character
quote character as in LISP.  The atom may be indefinitely
long.  The atom will be terminated by an unquoted space,
carrige return, tab, (, ), or semicolon. Unquoted linefeeds
are ignored and do not become part of the atom.  The
character that terminates the atom is "used up" unless it is
a ( or ). Note that period is a legal constituent of a atom
and does not terminate it or act specially.

c) lists.

	Work normally, but note following caution relative
to dot notation: . does not terminate atoms.  Thus, to
invoke dot notation, the dot must be left delimited by a
space, tab, parenthesis, or other character that does
terminate atoms.

Glitches:

     1) Restriction on pass dependant list
	structure -- In any list reading operation, no new
	atoms not previously encountered may be
	encountered for the first time on pass 2. 
	However, this restriction does not apply to
	atom-only reading operations (.ATOM, .SPECI,
	.FUNCT etc).
     2) Single quote for quoting does not exist (no
	other macro characters exist either.)
     3) Numbers must be flagged as above always.
		MOVEI A,.ATOM 123	;LOSES - gives pointer
					; to PNAME type atom
					; with PNAME 123. it is
					; not numeric.
	use:
		MOVEI A,.ATOM #123	;WINS
     4) No provision exists to reference "GLOBALSYMS"
	in FASLOAD. This mostly means only that DDT must
	be present to load a MIDAS assembled FASL file.
	(some simple COMPLR and LAP FASL files can
	successfully be FASLOADed by, for example, a
	disowned LISP running without a DDT.
     5) LOC is illegal in a FASL assembly.  BLOCK of a
	non-relocatable quantity is ok.
     6) Currently, symbol loading is VERY slow.  Thus
	use SYMBOLS nil, (the initial state) unless
	symbols are necessary.
     7) Midas does not know about any LISP symbols or
	UUOs specially. Use them as globals until someone
	gets around to fixing up a .INSRT file with the
	appropriate defs.
     8) .ATOM "should" be a special case of .SX . 
	However, it is handled separately because of the
	following "reasons":
	     a) The previously noted restriction on pass
		dependent LISTS.
	     b) Midas can do constants optimization on
		atoms ppearing in constants (on both pass one
		and pass two) but not on LISTS. Therefore,
		each list is guaranteed to take a separate
		word in the constants area even if it is
		identical to some other list which also
		appears in a constant.
	     c) Each list takes an additional entry in
		FASLOAD's "atom" table.  This is a temporary
		table that is flushed after the FASLOADing is
		complete.  Of course, .SX still works for
		atoms modulo the above noted restrictions and
		inefficencies.