perm filename CFUNS[CMP,SYS] blob
sn#014783 filedate 1973-07-03 generic text, type T, neo UTF8
Glossary of Lisp Compiler Functions
MACROS
DFUNC defines an EXPR.
FLUSHDEF prints a definition.
GETPROP behaves like GET.
IFIF is the logical "if and only if".
INCR is used to increment the compiler's count.
MAPDEF does lots of defprops in one compact expression.
MCONS is cons of several things.
OUTINST outputs an instruction by calling OUTSTAT.
OUTPSOP outputs a pseudo-op by calling OUTSTAT.
OUTTAG outpust a tag by calling OUTSTAT.
PDLDEPTH gives the current number of items on the push down
list.
Q is short for quote.
TAGP asks if an expression is a tag.
USERWARN prints a message warning the user of a potentally
dangerous condition in his code.
The property list manipulating functions operate primarly on
tails of the property lists of atoms. The functions which fetch a
property return the tail of the property list, beginning with the
property name. The word property below will refer to such a tail.
FIRSTPROP gets the first property from the property list of
an identifier, ie. the whole property list.
LASTPROP asks if a property is the last on the property list
of an atom.
NEXTPROP gets the next property after the one it is givenas
an argument.
PROPNAM takes a property as an argument and returns the name
of the property.
PROPTABLE takes an identifier as argument and returns the
property list.
PROPVAL takes a property and returns the value part of the
property.
DELETEPROP takes an identifier and a property name and
removes the property with that name from the identifier.
HASPROP is a predicate which asks is an atom has a property.
INITPROP plases a property on a property list, whether or not
there is one there.
SEEKPROP looks for a property name on the property list of an
atom.
SETPROP takes an identifier, a property name and a value and
sets that property to the value.
TOP LEVEL
ACTONEXPR decides the action to be taken on each expression in
a file being compiled.
ACTONMACRO expands macros at the top level in a file being compiled.
CMP is for debugging. It takes as argument either a single function
name or a function definition in the same format as DFUNC.
COMPDEF handles the compilation of a DEFPROP.
COMPFILE compiles a file.
COMPFUNC manages the compilation of a function definition.
COMPILE takes a list of function names and compiles their
definitions.
COMPILEFUN does most of the work for COMPILE and CMP.
COMPL compiles a list of files, by calling COMPFILE on each.
COMPREADS is a read and compile loop.
CURFILE gives the name of the file currently being compiled for use
in error messages.
CURFUN gives the name of the function currently being compiled for
use in error messages.
DECLARE is a function know to the compiler, which if encountered
at the top level of a file during compilation evaluates each of its
arguments.
DEFEXPR manages the compilation of a DEFPROP of an EXPR.
DEFFEXPR manages the compilation of a DEFPROP of an FEXPR.
DEFMACRO manages the compilation of a DEFPROP of a MACRO
DO*EXPR operates on a DEFPROP of a *EXPR.
DO*FEXPR operates on a DEFPROP of a *FEXPR.
DOACT dispatches the compilation of a function found at the
top level in a file which has a COMPACTION property indicating it is
to get special treatment.
DODE operates on a DE to compile the defined function.
DODF operates on a DF to compile the defined function.
DODM operates on a DM to define the macro.
DOFILE applies a functional argument to each expression in a file.
FLUSHEXPR prints out an expression on which no other action has
been taken.
FLUSHLAP prints out LAP definitions in files being compiled.
MAKDEF produces a DEFPROP expression from its arguments to hand to
COMPDEF.
MAPPUT puts a property onto a list of atoms.
PRINTMSG prints a message on the listing device for error messages
and warnings.
READLOOP reads and applies a functional argument to each
expression read.
SPECIAL is known to the compiler, and when seen at the top level
of a file being compiled declares each of its arguments to be a special
variable.
TELLTALE plows through data left after the compilation of a file
and reports various information.
TYPEFN types out a function name on the listing defivice to
show that the compilation of a function has been completed.
UNSPECIAL behaves in a way complementary to SPECIAL and removes
the special declarations from its arguments.
CINIT initializes the compiler. It does an excise and sets
the INITFN to CSTART.
CSTART attemts to read initializatin files from the disk and then
prints a message saying that the compiler has started.
PASS1
The process of the first pass of the compiler will be
referred to expansion. It is a process of putting expressions into
normal form, and recording information in tables for the use of the
second pass. Expressions are usually expanded by first expanding the
arguments then massageing the whole. Each expressin must be expanded
in accordance with the context in which it appears. An expression
which appers as an argument to a CONS must be expanded in light of
the fact that it is to be evaluated. If on the other hand, it
appears as an argument to a QUOTE, it must be left alone. The first
case will be called expansion in evaluated contest or expansion for
evaluation. The latter will be called expansion in quoted context.
In one or two contexts, ie. PROGs, things are more complicated and
atoms must be treated differently from all other expressions.
Tables are kept for both the local and the special variables.
When a variable is either bound or referenced, it is added to the
appropriate table.
Throughout the first pass a count(P1CNT) is kept of all
references to all variables. For each local variable a note is made
of the count, each time it is seen. This noted counts will be
referred to as the last appearance of the variable.
In addition to the usual function properties of atoms, the
compiler adds some for its own use. The properties *SUBR, *FUSBR,
and *LSUBR indicate functions know to be of the times SUBR, FSUBR,
and LSUBR by the compler, but whose definitions are not present. The
property *UNDEF indicates a function believed to be a SUBR but as yet
undefined. The property FUNVAR indicates a functional variable which
must not be mistaken for an ordinary function name.
DOP1 applies specfic routines to expressions whose CARs have
the P1 property, which indicates that they get special treatment.
GENFUN takes a piece of code, wraps it up as a function of no
arguments, gives it a generated name, and compiles it.
MAPP1 applies the first pass expansion process to each
element of a list.
P1 is the central function of the first pass of the compiler.
It examines the property lists of the CARs of the expressions it
processes, and acts accordingly in giving their expansion to suitable
more specialized functions.
P1ANDOR expands ANDs and ORs. Aside from expanding the
arguments, It uses P1BUG to raise the last appearance number of each
variable to the highest count seen during the AND or OR.
P1BIND operates on a list of variables to be bound by a
lambda or prog. After checking for various errors, it adds
information about them to various lists.
P1BUG raises the "last count at which seen" of variables seen
after a certain point to some larger value. This occurs in
circomstances, like PROG, where order of evaluation of expressions is
varible.
P1COND expands COND expressions. This is in many ways
similar to the process for ANDs and ORs but expansion must be mapped
over each of the tuples.
P1CONS expands CONSes. This function will try to turn a CONS
to an NCONS.
P1ELSE handles all functions not already known to the
compiler, by supposing that they are as yet undefined EXPRs. The
*UNDEF property is put on their property lists and they are added to
the list of undefined functons.
P1ERRSET compiles the argument of the ERRSET using GENFUN and
changes the expression to refer to a call on this new function.
P1EVAL expands an EVAL, attempting to make it a *EVAL.
P1FUNCTION compiles the argument of a FUNCTION statement
using GENFUN, and modifies the call to refer to this new function.
P1*FUNCTION behaves about the same as P1FUNCTION.
P1GO checks to see that the GO is really in a PROG, then if
the argument is not atomic it expands it in the usual way.
P1LABEL turns the label statement into a PROG in which the
function is bound as a prog variable.
P1PROG first binds the PROG variables, then prepares a list
of generated tags to be used in the LAP code. Finally it goes
through exppanding each expression according to whether it is an atom
or not. Atoms are left alone, while other expressions are processed
in evaluation context.
P1RETURN expands the argument of the return for evaluation,
after checking to be sure the return is inside a PROG.
P1SETQ expands its arguments differently. The second argument
of the SETQ is expanded for evaluation while the first, being a
variable, is simply checked against the tables.
P1STORE is expanded specially. Its arguments are expanded for
evaluation in reverse order.
P1SUBRARGS expands each element in a list, checking that
there not too many for the argument accumulors.
PASS1 sets up all of the various tables which are used for
the first pass to record its results, binds the variables, calls P1
etc.
PASS1FSUBR expands a call to an FSUBR. It simply returns the
expression unchanged.
PASS1FUNVAR expands both the function part and the arguments.
PASS1LSUBR expands each of the arguments without checking on
their number.
PASS1LAMDA expands the arguments, binds the variables and
finally expands the body of an internal LAMBDA, after checking that
the lambda expression has been given the correct number of arguments.
PASS1MACRO expands an appeal to a macro by applying the macro
definition to the entire expression and then expanding the result.
PASS1SUBR expands each of the arguments, checking that there
are no more arguments than available argument accumulators.
PASS1UNDEF expands the expression like PASS1SUBR and adds it
to the list of undefined functions.
SPECIALP is a predicate asking if an identifier is a special
variable.
VARB processes a variable, asking whether it has been seen
before and in what context.
VARIABLEP asks if an expression is a legitimate variable, ie.
an identifier and not a resurved constant.
INTERNAL MACROS
Several functions are logically treated as macros, though for
reasons of speed it is desirable to have their macro definitions
compiled, an option not offered in the basic Lisp system. The
compiler therefore makes use of its own extensibility to add the new
function type INMACRO. The several INMACRO definitions which follow
are therefor compiled.
It should be emphasized that in so doing the compiler is only
mmaking use of compiler facilities of which any user program might
have availed itself.
The INMACROs are APPEND, LIST, NOT and ZEROP. Their
definitions are precisely those which would be used to define
ordinary macros to preform those functions.
PASS1INMACRO is the function which expands INMACROS rather as
PASS1MACRO expands macros.
PASS2
ACEFFECTS Takes a function name as argument and returns a
mask indicating which accumulators are damaged by the a call to the
functon.
ACNUMP is a predicate which indicates if a number is used to
represent an accumualtor.
BINDARGS takes a list of arguments to a function and makes
entries in the ACS list to show which arguments are in which
accumulators.
BOOLAND carries out the compilatin of an AND, by calling
BOOLARGS.
BOOLARGS is the principal function used to compile booleans.
It takes as agruments a list of expressions to be anded or ored and
compiles them interspersed with appropriate jumps and tags.
BOOLEQ compiles an EQ for value or boolean test, by compiling
the arguments for value and generating a compare instruction. Several
cases arise, depending on whether the arguments are already available
as variables or are compiled to give temporary results. At least one
of the arguments must be in an accumulator, and, before the comparte
instruction is generated the stack must be restored in preparation
for any jump which follows.
BOOLEXPR finds and employs the appropriate function for
compileing a given boolean.
BOOLNULL compiles the function NULL, by simply reversing the
test conditions.
BOOLOR compiles OR by setting up an appropriate call to
BOOLARGS.
BOOLVALUE generates a T or NIL in a given accumualtor from a
jump to a tag, by making the fall through give a nil and arrival at
the tag give a T.
The process of compiling a function call, with little regard
for the function's type, can be divided into four parts. First the
arguments must be compiled. Second, they must be loaded into the
correct places. Third, any valuable data which are in vulnerable
places must be moved to safe loacations. Last, the calling
instruction can be output and the results marked in the storage map.
CALLFSUBR generates a call to an FSUBR by placing the
appropriatly quoted argument string in accumulator one, cleaning
valuable items out of the accumulators, generating a call to the
function and marking accumulator one as containing the result.
CALLFUNARGS generates a call to a calculated function. First
the function is calculated, then the arguments are compiled and
loaded into the accumulators. Once this has been done, the
function, which has been preserved through these events, is called in
the usual way.
CALLLSUBR This process differs slightly from the others, in
that, as the arguments go on the stack, each argument is loaded right
after it is compiled. All valuable data in the accunulators must
therefore be saved before this process is begun. Once this is
completed, the calling and marking are done as usual.
CALLSUBR This is the fundamental function call operation.
First, the arguments are compiled, without being loaded into specific
locations. These results are marked as valuable by being placed on
the LDLST, and the values of earlier arguments are preserved through
the compilation of later ones. This is designed to save pushing and
popping where possible. After the arguments have been compiled, they
are loaded, in inverse order, into the appropriate accumulators.
Next, a cleanup is done, in which valuable data remaining in the
accumulators are pushed along with the values of any special
variables whose current values will be needed later.
The various functions whose names begin with CLEAR or CLR all
are concerned with setting things to rigths in prepation for possible
hazards. In general this means that partial results will be computed
and saved in preparation for the destruction of the data on which
they depend. Some of these functions are simply ad hoc combinations
of others.
CLEAR1 runs together the functions of CLRCCLST, SAVEACS and
CLRPVARS.
CLEARBOTH runs together CLRCCLST and CLRSPECS.
CLEARAC pushes the contents of an accumulator and marks it as
empty in the map.
CLEARITALL runs together CLEARBOTH and CLEARACS.
CLEARACS pushes all valuable items in the accumuators and
marks them as empty in the map.
CLRCCLST computes the values of items waiting to be loaded
which are known to be cars or cdrs of other things. This may be
necessary as a distinct operation to making copies of the original
items since RPLACA and RPLACD operations may destroy the objects
pointed to.
CLRLOCS pushes copies of any local variables waiting to be
loaded as function arguments. This is done prior to branching, since
different assignments might be made to the variable on different
branches.
CLRPVARS initializes the PROG variables by pushing NILs on
the stack.
CLRSPECS pushes copies of any special variables waiting to be
loaded as function arguments. This is necessary whenever a function
is call whose effects on special variables are not known.
CLRSPVAR pushes a copy of one special variable, if a copy is
not already in the accumuulators or on the stack.
COMPARGS compiles a list of function arguments without
loading them.
COMPEXPR compiles a form in expression context, ie. for
value.
COMPPRED compiles a form in predicate context, ie. to be
tested for effect on the flow of control.
COMPFORM is the central routine of the compiler. It is in
charge of the compilation of all forms to be evaluated.
COMPSTAT compiles a form in statement context, ie. for
neither value nor effect on the flow of control, but only for side
effects on variables or list structure.
COPT attempts to optimize the computation of a car or cdr
by looking to see if the result is already known.
CPUSH guarantees that a copy of a valuable item is on the
stack. It first checks to see if the item is valuable, if not it is
ignored. Next, a check is made to see if the item is already on the
stack. Third, CPUSH will look for a suitable place on the stack into
which to move the item. As a last resort, it will push a copy onto
the end of the stack.
CSFUN is called by CLRCCLST to compile those cars and cars
and cdrs whose values are not already available.
CSTEP expands a car-cdr chain, using COPT at each step to
determin if the sub-results are already present.
DOP2BOOL manages the computation of a boolean expression in
any context, first compiling it as a boolean for effects on control
and then generating code to produce a value, if necessary.
DOP2ELSE manages the compilation of those functions which may
do one thing in predicate context and another in value context.
DOP2VAL manages the compilation of functions which primarily
produce values.
DVP is a predicate which decides if an item is valuable.
EQUIVTAG gives the lap tag corresponding to a prog tag.
EXITBUM generates the code for a functin exit, trying to end
with a jump instead of a call if possible.
FREEAC finds a free accumulator when one is needed for a
partial result. This function will forcefully clear an accumulator if
it must.
FREEAC1 does the work for freeac. Its arguments is the
preferred accumulator.
FINDFREEAC will find a free accumulator if there is one, but
will not forcefully clear one.
FREEZE removes from the storage map any references to the
current value of a variable , and replaces them with reverences to
the value at the time of the freeze.
FREEZE1 is a subsidiary to freeze which acts on an individual
piece of the storage map.
GENCONST generates the Lap notation of a constant or literal
word to be used in the address field of an instruction.
GETSLOT takes as argument an number indicating a storage
loaction in the accumulators or on the stack, and returns the
appropriate piece of the map.
ILOC is a functions which returns the location of an item if
it is present in memory, or returns a NIL is the item must be
computed.
ILOC1 locates a item if possible, computing it if necessary.
LISTNILS generates a list of NILs to intitialize the ACS
list.
LOADARG loads an item into an accumulator.
LOADCARCDR generates code to calculate a car or cdr.
LOADCOMP compiles a form and loads the result.
LOADSUBRARGS loads a list of items into the appropriate
accumulators to be arguments of a subr.
LOC uses ILOC1 to locate an item.
MARKVAL generates an item name, for a computed result and
enters it in the storage map in the appropriate place. This item
name is also entered on the LDLST, if necessary, to protect it.
NONSPECVARS extracts from a list of variables the ones which
are not special.
OUT1
OUTCALL
OUTCALLF
OUTCJMP
OUTENDTAG
OUTFUNCALL
OUTGOTAB
OUTJCALL
OUTJMP
OUTJRST
OUTMOVE
OUTMOVEM
OUTPOP
OUTPUSH
OUTPUTSTAT
OUTSTAT
P2*EVAL
P2ARG
P2CARCDR
P2COND
P2COND1
P2GO
P2PROG
P2PROG2
P2PROGN
P2QUOTE
P2RETURN
P2RPLAC
P2SETARG
P2SETQ
P2STORE
PASS2
PASS2LAMBDA
PROGTAG
PROTECTACS
PUTINAC
REMOVE
RESTORE
RSLSET
RST
SAVEACS
SETSLOT
SHRINKPDL
SIDEEFFECTS
SLOTCONT
SLOTLIST
SLOTPOP
SLOTPUSH
SPECBIND
SPECVARP
TESTJUMP
TRANSOUT
USEDTAGP
CMPBREAK
COMPERR
EVALREAD
LAPNOTES
USERERR
ATMARGIN
CARRETN
CURCOL
FORMF
LINEF
PRINL
PRINS
PRINTEXPR
PRINTN
PRINTSTAT
TABTO
ADDTOLIST
ASSOCR
CONSTANTP
COPY
DEINITSYM
FSUBRP
GETGET
LSUBRP
MAKESPECIAL
MAKESYM
MAKEUNSPECIAL
NEXTSYM
NTHCDR
PROGN
STARTSYM
STOPSYM
SUBRP
TOPCOPY