1
0
mirror of synced 2026-01-15 16:26:26 +00:00
Interlisp.medley/docs/ReleaseNote/SEC7-CLIMPLMNTN.TEDIT

132 lines
44 KiB
Plaintext
Raw Blame History

This file contains invisible Unicode characters

This file contains invisible Unicode characters that are indistinguishable to humans but may be processed differently by a computer. If you think that this is intentional, you can safely ignore this warning. Use the Escape button to reveal them.

1
LISP RELEASE NOTES, MEDLEY RELEASE, COMMON LISP IMPLEMENTATION
1
LISP RELEASE NOTES, MEDLEY RELEASE, COMMON LISP IMPLEMENTATION
7. COMMON LISP IMPLEMENTATION
1
7. COMMON LISP IMPLEMENTATION
1
7. COMMON LISP IMPLEMENTATION
6
This section describes new features and enhancements that implement Common Lisp into the Lisp operating environment within the Medley release. This information supplements the Common Lisp Implementation Notes, Lyric release. Medley enhancements are indicated with revision bars in the right margin.
2
New Features Since Lyric
1
The following description summarizes the new Common Lisp implementation (FEATURES NIL features NIL (7) 1 SUBNAME NEW% COMMON% LISP% SUBTEXT new% Common% Lisp% )features that have been added or changed since the Lyric release.
New compiler Interface -- The Medley compiler gives better progress reports and it is now possible to invoke the compiler on any definer (not just functions, as before).
New Implementation of Defstruct -- A new version of defstruct compiles more compactly and gives more options so that defstruct has at least as much functionality as the Interlisp record package.
Adoption of features and clarifications suggested by the Common Lisp Cleanup Committee -- Among other changes, the behavior of append on dotted lists is now better defined, and a new function xcl:row-major-aref has been added.
Common Lisp Veneer on the Interlisp record package -- A collection of macros that make the use of existing Interlisp datatypes more appealing has been added.
Performance enhancements -- A closure caching scheme now insures that repeated calls to symbol-functions of the same symbol will return EQ compiled-function objects.
New opcodes have been added for several common list functions, such as member and assoc.
Common Lisp Definers
1
The Medley release contains a new implementation of definers and a reworking of the top level of the XCL Compiler. These represent upward compatible changes that have the effect of allowing the Common Lisp compiler to print out progress reports indicating which definer is currently being compiled. To receive the full benefit of these changes, recompile any file containing a defdefiner expression.
It is now possible to compile individual definers by using any of the following forms:
Compile-Definer
1
(xcl:compile-definer(COMPILE-DEFINER (Definer) compile-definer NIL (7) 2) name type)
Compile and install the definer of type type named name .
EXAMPLE:
(xcl:compile-definer 'foo 'structures)
In this example, the definer will compile and install the structures definition of foo.
Compile-Form
1
(xcl:compile-form(COMPILE-FORM (Definer) compile-form NIL (7) 2) form)
Compile and evaluate form.
EXAMPLE:
(xcl:compile-form '(progn (defconstant c 1) (defun foo (a b) (+ c a b))))
In this example, the definer will compile and evaluate the progn using compile-file semantics.
EXAMPLE:
(xcl:compile-form '(with-collection (dotimes (i 10) (collect i))))
In this example, the definer returns:
(0 1 2 3 4 5 6 7 8 9)
Define-File-Environment
1
Rather than establishing il:makefile-environment props and il:filetypes on the root name of a file, you can define a file environment using the form:
(xcl:define-file-environment(DEFINE-FILE-ENVIRONMENT (Definer) define-file-environment NIL (7) 2) filename &key readtable package base compiler)
This produces an object of file-manager type xcl:file-environments. The filename can be either a string or a symbol. The rootname of the file is constructed by interning the filename in the Interlisp package. Puts the compiler argument (if any) under the il:filetype prop of the file rootname. Puts the readtable, package and base arguments (if any) under the il:makefile-environment prop of the file rootname. None of the arguments are evaluated. There are no defaults.
EXAMPLE:
(xcl:define-file-environment myfile :package "XCL-USER" :readtable "XCL" :compiler :compile-file)
In this example, compile-file is put under the il:filetype prop of myfile. The readtable, XCL and compile arguments are put under the il:makefile-environment prop of myfile.
NOTE: xcl:define-file-environment is a definer and hence will not be installed if il:dfnflg is il:prop or if a file is prop loaded.
Site-Name Special Uses
1
The following special variables are defined and may be set in your init file to inform Common Lisp of site information:
xcl:*short-site-name(SHORT-SITE-NAME (Variable) short-site-name NIL (7) 3)*
This variable is used in the function short-site-name.
xcl:*long-site-name(LONG-SITE-NAME (Variable) long-site-name NIL (7) 3)*
This variable is used in the function long-site-name.
EXAMPLES:
(setq xcl:*short-site-name* "AIS")
(setq xcl:*long-site-name* "Artificial Intelligence Systems")
In these examples, (short-site-name) returns "AIS" and (long-site-name) returns "Artificial Intelligence Systems".
Record Access
1
The Medley release contains several methods for accessing existing Interlisp records using Common Lisp syntax. These features help to integrate Interlisp and Common Lisp. The following sections describe these additions.
Define-Record
1
(xcl:define-record name interlisp-record-name
&key conc-name constructor predicate fast-accessors) <09><>[<5B>Definer<65><72>]<5D>
Creates a structures object named by the symbol name that provides Common Lisp accessors, settors, predicates and constructors for the Interlisp record named by the symbol interlisp-record-name. The Interlisp record must be defined before the xcl:define-record(DEFINE-RECORD (Definer) define-record NIL (7) 3) expression is evaluated. The keyword arguments are treated as in defstruct. The package of constructed names is taken from the value of *package* at the time of evaluation (as in defstruct). The system contains no predeclared define-records.
EXAMPLE:
The form:
(xcl:define-record menu il:menu)
allows you to write:
(menu-items foo) and (setf (menu-items foo) fie)
rather than:
(il:fetch (il:menu il:items) il:of foo)
Record-Fetch
1
(xcl:record-fetch(RECORD-FETCH (Macro) record-fetch NIL (7) 4) record field object) [Macro]
Evaluates object. Does not evaluate record and field. Both record and field must be symbols. Symbols with the same p-names are interned in the Interlisp package and are used to construct an il:fetch form. xcl:record-fetch may be used with setf and expands to the suitable replace form.
Record-FFetch
1
(xcl:record-ffetch(RECORD-FFETCH (Macro) record-ffetch NIL (7) 4) record field object) [Macro]
Similar to xcl:record-fetch, but an il:ffetch form is generated instead. Evaluates object. Does not evaluate record and field . Both record and field must be symbols. Symbols with the same p-names are interned in the Interlisp package and are used to construct an il:ffetch form. Ffetch may be used with setf and expands to the suitable freplace form.
Record-Create
1
(xcl:record-create(RECORD-CREATE (Macro) record-create NIL (7) 4) record &rest keyword-pairs) [Macro]
Evaluates the second element of each pair. Does not evaluate record (record must be a symbol) . A symbol with the same p-name is interned in the Interlisp package and used to construct an il:create form. The rest of the arguments form keyword pairs. The first element of each pair should be a symbol such that a symbol with the same p-name exists in the Interlisp package and names either a valid slot for this record or is one of :using, :copying, :reusing, or :smashing.
Array Reference(ARRAY% REFERENCE NIL array% reference NIL (7) 4)
1
(xcl:row-major-aref(ROW-MAJOR-AREF (Function) row-major-aref NIL (7) 4) array index) [Function]
Returns the element of array given by the row-major-index index. The array can be of any dimension. This function can be used with setf .
Shadowing of Global Macros(GLOBAL% MACRO% SHADOWING NIL global% macro% shadowing NIL (7) 4)
1
The XCL Compiler now properly handles shadowing of global macros by lexical functions. In the Lyric Compiler, lexical functions defined with (FLET (Special form) flet NIL (7) 4)flet did not shadow global definitions of the same name. This has been fixed in Medley.
Evaluating Load-time Expressions
1
The XCL Compiler now handles il:(LOAD-TIME% EXPRESSION% NIL load-time% expression% % NIL (7) 4)loadtimeconstant correctly. The new Compiler substitutes the entire expression for each reference to the value of a load-time constant. There are potential problems if the code depends on the expression being evaluated exactly once, e.g. if it contains (IDATE).
Common Lisp Defstruct Options
1
The Medley release contains a new implementation of defstruct that offers greater compiled-code compaction, and several new extensions that increase efficiency. This implementation introduces functionality that allows (DEFSTRUCT (Macro) defstruct NIL (7) 4)defstruct to parallel the Interlisp record module in flexibility. These features also help to integrate Interlisp and Common Lisp. The following sections describe these additions.
Defstruct Options
1
:(:INLINE (Defstruct option) :inline NIL (7) 5)inline
Can be one or both of :accessor and :predicate or t, implying '(:accessor :predicate) or nil, implying no optimizations allowed or :only, implying all accessors and the predicate will be inline only and not funcallable (not usable with the Lisp primitive "funcall"). The default is '(:accessor :predicate).
Copiers and constructors are never inline. The option (:inline :only) implies that no funcallable accessors will be generated (similarly, the predicate, if any, will not be funcallable).
:fast-accessors(:FAST-ACCESSORS (Defstruct option) :fast-accessors NIL (7) 5)
Can be t or nil. t implies inline accessors will not type check. The default is nil.
Note that funcallable accessors (if any), always type check, if possible.
NOTE: This represents a change from the Lyric implementation, which allowed specification of a list of slot names that had fast inline accessors.
:(:TEMPLATE (Defstruct option) :template NIL (7) 5)template
Can be t or nil, t implies that no datatype will be instantiated. (:template t) implies no :type option. The default is nil.
Templated defstructs have no predicates, copiers or constructs. It is an error to supply any such option in combination with (:template t). Templated defstructs are intended to be used as are IL:blockrecord's. It is possible for a templated defstruct to include another templated structure, but it is an error for a standard defstruct to include a templated structure.
Funcallable accessors (accessors that may be used with the Lisp primative "funcall") share code with suitable closure templates if the defstruct is compiled with the XCL Compiler. Byte compiled defstructs still generate explicit defun's for all funcallable accessors.
Defstruct Slot Options
1
:(:TYPE (Defstruct option) :type NIL (7) 5)type
The following specialized types are recognized:
(unsigned-byte {1 - 16})
(signed-byte {16, 32})
float, etc.
(member t nil)
il:fullpointer
il:xpointer
il:fullxpointer
Warning When Using Defstruct
1
(DEFSTRUCT (Macro) defstruct NIL (7) 6 SUBNAME WARNING% SUBTEXT warning% )Defstruct automatically generates a number of auxilliary functions without checking whether redefining those functions will affect the system. To avoid redefining key functions, you should be aware of the names that will be used. For example:
Do not attempt to define a Structure named TREE. This use of Defstruct implicitly redefines the built-in Common Lisp function COPY-TREE, which renders your system inoperable.
If you have already tried to define a (DEFSTRUCT TREE A B) structure by mistake, you will need to reload your system.
Macros for Collecting Objects(COLLECTING% OBJECTS NIL collecting% objects NIL (7) 6 SUBNAME MACROS% FOR% SUBTEXT macros% for% )
1
xcl:with -collection
1
(xcl:with-collection &body(WITH-COLLECTION (Macro) with-collection NIL (7) 6) forms) [Macro]
(xcl:(COLLECT (Macro) collect NIL (7) 6)collect form) [Macro]
This pair of macros is provided for efficiently collecting objects into a list. In Common Lisp, there is no direct facility provided for doing this, so one must either push objects onto a list, then reverse it, or maintain a tail pointer to the list and use rplacd to add new items. The latter has an efficient implementation in Xerox Common Lisp, and xcl:with-collection is provided to take advantage of it.
Lexically within the body of an xcl:with-collection, the macro xcl:collect is defined. It will append the value of its argument to the end of the list being collected. The value of xcl:with-collection is the collected list.
xcl:collect may be used inside of functions passed as arguments to other functions.
EXAMPLE:
(xcl:with-collection
(maphash
#'(lambda (key val)
(when (interesting-p val) (xcl:collect key)))
the-hash-table))
will collect a list of all the "interesting" keys in the order that they were encountered.
It is an error to use xcl:collect outside the scope of an xcl:with-collection. Proper lexical nesting is observed, so an instance of xcl:collect applies to the most deeply nested xcl:with-collection that is is found in.
Macros for Writing Macros(WRITING% MACROS NIL writing% macros NIL (7) 7 SUBNAME MACROS% FOR% SUBTEXT macros% for% )
1
xcl:once-only
1
(xcl:once-only(ONCE-ONLY (Macro) once-only NIL (7) 7) ({ variable }*) &body forms) [Macro]
This macro is provided to aid in writing macros. xcl:once-only helps solve the problem of multiple evaluation of subforms of a macro.
EXAMPLE:
(defmacro test (reference form)
`(setf ,reference (cons ,form ,form)))
This example has the problem that form will be evaluated twice. To avoid this, one might instead write:
(defmacro test (reference form)
(let ((value (gensym)))
`(let ((,value ,form))
(setf ,reference (cons ,value ,value)))))
This solves the problem of multiple evaluation, but introduces some others. If form is in fact something simple, like a reference to a variable or a literal, there was no need to create the temporary variable, thus "wasting" a symbol. This can be extremely important in Xerox Common Lisp as symbol space is limited and symbols are never reclaimed. If there are many temporary values to be computed, the macro definition becomes cluttered with calls to gensym that obscure the essence of the code.
xcl:once-only helps solve these problems. For each of the variables listed, xcl:once-only determines if its value (at macroexpansion time) is simple: a symbol or a literal. If it is, appearances of that variable in the macroexpansion will remain unchanged. If it is not, the macroexpansion will contain code to store the value in a temporary gensym'ed variable and use that variable in the macroexpansion. Thus, the example could be written as
(defmacro test (reference form)
(xcl:once-only (form)
`(setf ,reference (cons ,form ,form))))
Then (test (aref the-array x) y) will expand to something like
(setf (aref the-array x) (cons y y))
while (test (aref the-array x) (random-form)) will expand to something like
(let ((#:g377 (random-form)))
(setf (aref the-array x) (cons #:g377 #:g377)))
Note that xcl:once-only does not attempt to preserve order of evaluation. If this is important then you will still have to create temporary variables yourself.
Common Lisp Append Datatypes
1
A clarification adopted by X3J13 involves the behavior of the (APPEND (Function) append% NIL (7) 8 SUBNAME WITH% NON-LIST% ARGUMENT% SUBTEXT with% non-list% argument% )APPEND function with non-lists. The cdr of the last cons in any but the last argument given to APPEND is discarded (whether NIL or not) when preparing the list to be returned. In the case where there is no last cons (i.e., the argument is not a list) in any but the last list argument, the entire argument is effectively ignored. In this situation, if the last argument is a non-list, the result of APPEND can be a non-list. NB: APPEND and COPY-LIST now produce different results for non-lists.
EXAMPLE:
(append '(a b c . d) '())
produces the result:
(a b c)
EXAMPLE:
(append '(a b . c) '() 3)
produces the result:
(a b . 3)
EXAMPLE:
(append 3 17)
produces the result:
17.
Closure Cache
1
The Medley sysout contains a closure cache that provides increased time and space efficiency. Less new memory is allocated because repeated calls to symbol-function of the same symbol now will cons exactly one closure(CLOSURE NIL closure NIL (7) 8) object. Repeated calls to symbol-function of the same symbol now return EQ- compiled function objects.
Symbols and Packages
1
Pkg -goto and In-package
1
PKG-GOTO is now a synonym for IN-PACKAGE(IN-PACKAGE (Function) in-package% NIL (7) 8). The PKG-GOTO function can be used to change packages in an exec.
PKG-GOTO takes one argument, which can be either a double-quoted string, a symbol, or a package structure. This function is used to set package in an exec.
(xcl:pkg-goto(PKG-GOTO (Function) pkg-goto NIL (7) 8) package-name &key nicknames use) [Function]
PKG-GOTO operates like IN-PACKAGE, but asks for confirmation if a new package is being created. The function is useful at the top level in the exec, to avoid creating new packages when a name is misspelled.
Defpackage Export argument
1
Defpackage's (EXPORT (Function) export% NIL (7) 9)EXPORT argument now accepts strings. Optionally, strings can be given to :EXPORT instead of symbols. This is recommended when defpackage is used in the makefile-environment property of a file. The strings are interned in the package being defined and then exported.
Debugging Tools
1
(BREAKING NIL breaking NIL (7) 9)Breaking
1
Even with HELPDEPTH set to zero, some errors do not cause a break. In Koto and the old Interlisp execs in Lyric, the workaround is:
(SETTOPVAL 'HELPFLAG 'BREAK!)
In Medley and Lyric's new execs, HELPFLAG is bound but not continually reset. The workaround:
(SETQ HELPFLAG 'BREAK!)
affects the current exec until the next time you call RESET (or control-D). If you want the change in HELPFLAG to be seen by other processes, you still need to use SETTOPVAL, and RESET any execs in which you want to see the effect.
For related information, see the Medley error system variable XCL:*BREAK-ON-SIGNALS* described in Appendix E.
Advising(ADVISING NIL Advising NIL (7) 9)
1
In Lyric, putting a second piece of advice on a function caused the system to believe that the function was in fact not advised, so any further advice threw out the already existing advice. This has been fixed. In Medley, the correct list entries are made regardless of whether the function was previously advised.
In Lyric, loading a file with advice caused multiple instances of the advice to be instantiated. To prevent this, ADVISE is now changed in Medley in the following way: When a new piece of advice is put on a function, the system examines the already existing advice to see if the some advice is already there. If so, the old advice is removed before adding the new advice. Sameness is determined by a test similar to CL:EQUALP, except that case distinctions are significant in strings and characters. The priority and location of the advice is taken into account when determining the "sameness." This makes it possible, for instance, to have identical advice be both :FIRST and :LAST.
Advice is no longer replicated when loaded more than once.
The debugger and inspector now display interpreted lexical closures conveniently. Displayed lexical closure contents include the function contained, and any lexical bindings in the closure. Compiled closures are not conveniently inspectable. Common Lisp eval stack frames show their associated lexical environment in a similar manner.
The :when option to XCL:BREAK-FUNCTION no longer causes the broken function to return NIL when the break is not taken. The correct values are returned.
Argument Names Displayed for Interpreted Functions
1
In the debugger, the frame inspector window will now display the argument names for interpreted Common Lisp functions. Previously, it gave them pseudonames "arg0" "arg1" etc.
Lexical Variables Evaluated by Debugger
1
The debugger EVAL command now evaluate expressions in the lexical environment --i.e., you can evaluate an expression and use variables that are lexically bound in your code. Only the lexical environment at the point of the break can be evaluated. You can't presently back up to any given lexical environment.
EXAMPLE:
(defun fact(x)(if(= 1 x)nil(*x(fact(1-x)))))
(fact 4)
;; breaks. if you then type
EVAL x
2
Pathname Component Fixed in FS-ERROR
1
In Lyric, only one of the three FS-ERROR conditions was passed a pathname component, resulting in the File Cacher not knowing which file had the error, or resulting in pathname being lost when PROTECTION VIOLATION or FILE SYSTEM RESOURCES EXCEEDED were signaled. This problem occurred most noticeably in Lyric when Interlisp errors were translated to XCL. This condition has been fixed in Medley. FS-ERROR now correctly receives all the pathname components.
Compiler Optimizations
1
Warning when using LABELS construct(LABELS% CONSTRUCT NIL LABELS% construct NIL (7) 10 SUBNAME WARNING% SUBTEXT warning% )
1
In Lyric, use of the LABELS construct generated circular structure that would not get collected. Interpreted, a LABELS construct always creates this non-collectible structure. Compiled, such structure would be created if there were non-tail-recursive or mutually referencing subfunctions. The values of any closed-over variables are captured by this structure and thus also not collected, potentially causing large storage leaks. The latter situation has been relieved somewhat for Medley.
In Medley, the unavoidable circularity has been reduced to include only the mutually referencing functions, but not any of the other data that they access. Thus, the uncollectable structure is created only when a new copy of the code blocks are created, such a by compiling the function containing the LABELS rather than each time that function is called.
COMS added to dfasl files
1
The Medley compiler has been modified to better handle the il:define-file-info, and defpackage forms. Now, loading a dfasl file is not implicitly (SYSLOAD NIL sysload% NIL (7) 11)SYSLOAD. Since the file (COMS NIL coms% NIL (7) 11)COMS for the file is now included in the dfasl, that file will be noticed by the file manager unless the load is explicitly SYSLOAD. (SYSLOADing of compiled lcom and dfasl files is recommended.)
In Lyric, dfasls of file manager files did not contain the COMS of the file. In Medley, COMS are present in dfasl files, just as they are in lcom files. As with lcom files, the COMS will not be loaded when the LDFLG argument to LOAD is SYSLOAD, nor will the name of the file be added to FILELST, but instead will be added to SYSFILES.
Note: We discourage loading either sort of compiled file (lcom or dfasl) with any value for (LDFLG NIL ldflg% NIL (7) 11)LDFLG but SYSLOAD. Unless you intend to edit a file, you should always load it SYSLOAD. Even when you intend to edit it, it is usually preferable to SYSLOAD it and then load the source PROP. If there are too many source files for this to be practical, we recommend use of the WHERE-IS Library module.
While the location of definitions is made known to the edit interface when files are loaded, it can be very inefficient when files are not SYSLOADed. If, for example, you load ten compiled files with LDFLG=NIL and then evaluate (ED 'FOO), then the COMS of all ten files must be searched for definitions of each manager type with name FOO. With forty manager types this comes to 400 parses of COMS -- a time-consuming operation. If you instead load the compiled files SYSLOAD and the sources PROP, then no COMS need be searched, as checking for definitions of each manager type is sufficient.
Loadflg argument
1
The Medley release contains a new keyword argument to cl:load.
(cl:load(LOAD (Function) load NIL (7) 11 SUBNAME LOADFLG% SUBTYPE (Argument) SUBTEXT loadflg% ) filename &key verbose print if-does-not-exist loadflg)
The loadflg argument follows the sematics of the loadflg argument to il:load, with the exception that the loadflg argument will always be interned in the Interlisp package.
EXAMPLE:
(cl:load "Mycompiled-file.dfasl" :loadflg :sysload)
In this example, "Mycompiled-file.dfasl" will load without the file manager noticing that file.
Note: As explained in the previous section, we discourage loading either sort of compiled file (lcom or dfasl) with any value for ldflg but SYSLOAD.
Changes in CL:MAP, CL:WRITE-STRING, CL:COERCE , CL:GENSYM and IL:DEFERREDCONSTANT
1
In Lyric, a compiled call to CL:(MAP (Function) map% NIL (7) 11)MAP that had been used for effect would occasionally cons up a new list anyway. It would fail in the case that the first argument was a constant that evaluated to NIL, but not NIL itself, e.g. 'NIL. This has been fixed and no longer occurs in Medley.
CL:WRITE-STRING(WRITE-STRING (Function) write-string% NIL (7) 12) is now twice as fast and creates no new structure.
CL:(COERCE (Function) coerce% NIL (7) 12)COERCE now correctly returns the original object in all cases where Common Lisp and Lisp require it.
The CL Compiler now compiles CL:GENSYM(GENSYM (Function) gensym% NIL (7) 12) properly.
IL:(DEFERREDCONSTANT (Function) deferredconstant% NIL (7) 12)DEFERREDCONSTANT is now handled correctly by the XCL compiler.
ADD.PROCESS(ADD.PROCESS (Function) add.process% NIL (7) 12) no longer coerces the process name to a symbol. Rather, process names are treated as case-insensitive strings. Thus, you can use strings for process names, and when typing process commands to an exec, you need not worry about getting the alphabetic case correct.
Compiler keeps Special &REST arguments
1
The CL Compiler now retains special &REST arguments. The Lyric compiler(COMPILER NIL compiler NIL (7) 12 SUBNAME RETAINING% SPECIAL% ARGUMENTS% SUBTEXT retaining% special% arguments% ) threw away special &REST arguments. This has been fixed in the Medley CL Compiler.
Compiler(COMPILER NIL compiler NIL (7) 12 SUBNAME IGNORING% TEDIT% FORMATTING% SUBTEXT ignoring% TEdit% formatting% ) ignores TEdit formatting
1
COMPILE-FILE will now ignore TEdit formatting, but only if TEdit is loaded.
Compiler notices Tail-recursive Lexical Functions
1
The XCL Compiler(COMPILER NIL compiler NIL (7) 12 SUBNAME BEHAVIOR% WITH% FLETED% LEXICAL% FUNCTIONS% SUBTEXT behavior% with% FLETed% lexical% functions% ) now performs tail recursion elimination on FLETed lexical functions.
Compiler Error Message "BUG: Inconsistent stack depths seen"
1
You may occasionally see this error message while compiling. Normally, error messages from the compiler beginning with "BUG" indicate an internal compiler error. In this particular case, the compiler error may reflect an error in the code you are compiling.
There is currently no compile-time argument checking. The (COMPILER NIL compiler NIL (7) 12 SUBNAME BEHAVIOR% WITH% RECURSION% SUBTEXT behavior% with% recursion% )compiler performs an optimization that turns a tail-recursive function call into a jump back to the beginning of the function. If this tail-recursive call has the wrong number of arguments, the stack modeler in the assembler will detect this as incosistent stack depths, leading to the above error message.
EXAMPLE:
(defun bad-length (x n)
(if (endp x) n (bad-length (cdr x))))
Compiling this form will result in the error "BUG: Inconsistent stack depths seen." The recursive call to bad-length has only one argument, but the function expects two.
Thus, if you see this error message, you should check for tail-recursive function calls with the wrong number of arguments.
Format ~C and WRITE-CHAR
1
In accordance with a recommendation of X3J13, the ~C FORMAT operation with no modifiers now behaves exactly the same as WRITE-CHAR for characters with no bits. The Medley release of XCL conforms to this; the Lyric release did not. If you need to obtain the Lyric behavior of ~C(~C (Format directive) NIL NIL (7) 13), use ~:C.
WITH-OUTPUT-TO-STRING(WITH-OUTPUT-TO-STRING (Macro) with-output-to-string% NIL (7) 13) and WITH-INPUT-FROM-STRING(WITH-INPUT-FROM-STRING (Macro) with-input-from-string% NIL (7) 13)
1
For consistency with WITH-OPEN-STREAM and WITH-OPEN-FILE, WITH-OUTPUT-TO-STRING and WITH-INPUT-FROM-STRING now close the stream on exit from the form. WITH-OUTPUT-TO-STRING is now significantly faster when writing long strings.
[This page intentionally left blank](LIST ((PAGE NIL (PAPERSIZE Letter FOLIOINFO (ARABIC "7-" "") STARTINGPAGE# 1) (0 0 612 792) ((FOLIO NIL (PARALOOKS (QUAD RIGHT) CHARLOOKS (SUPERSCRIPT 0 INVISIBLE OFF SELECTPOINT OFF PROTECTED OFF SIZE 10 FAMILY MODERN OVERLINE OFF STRIKEOUT OFF UNDERLINE OFF EXPANSION REGULAR SLOPE REGULAR WEIGHT MEDIUM INVERTED OFF USERINFO NIL STYLE NIL) FORMATINFO (ARABIC "7-" "")) (270 15 288 36) NIL) (HEADING NIL (HEADINGTYPE FOOTINGR) (54 27 558 36) NIL) (TEXT NIL NIL (54 54 504 723) NIL))) (PAGE NIL (PAPERSIZE Letter FOLIOINFO (ARABIC "7-" "")) (0 0 612 792) ((FOLIO NIL (PARALOOKS (QUAD LEFT) CHARLOOKS (SUPERSCRIPT 0 INVISIBLE OFF SELECTPOINT OFF PROTECTED OFF SIZE 10 FAMILY MODERN OVERLINE OFF STRIKEOUT OFF UNDERLINE OFF EXPANSION REGULAR SLOPE REGULAR WEIGHT MEDIUM INVERTED OFF USERINFO NIL STYLE NIL) FORMATINFO (ARABIC "7-" "")) (54 15 288 36) NIL) (HEADING NIL (HEADINGTYPE FOOTINGV) (54 27 558 36) NIL) (HEADING NIL (HEADINGTYPE VERSOHEAD) (54 762 558 36) NIL) (TEXT NIL NIL (54 54 504 684) NIL))) (PAGE NIL (PAPERSIZE Letter FOLIOINFO (ARABIC "7-" "")) (0 0 612 792) ((FOLIO NIL (PARALOOKS (QUAD RIGHT) CHARLOOKS (SUPERSCRIPT 0 INVISIBLE OFF SELECTPOINT OFF PROTECTED OFF SIZE 10 FAMILY MODERN OVERLINE OFF STRIKEOUT OFF UNDERLINE OFF EXPANSION REGULAR SLOPE REGULAR WEIGHT MEDIUM INVERTED OFF USERINFO NIL STYLE NIL) FORMATINFO (ARABIC "7-" "")) (270 15 288 36) NIL) (HEADING NIL (HEADINGTYPE FOOTINGR) (54 27 558 36) NIL) (HEADING NIL (HEADINGTYPE RECTOHEAD) (54 762 558 36) NIL) (TEXT NIL NIL (54 54 504 684) NIL))))))4<00><00><01><01>TT-<01>
T3<01>
<00>T3<01><00>T3<01><00>T,-<01>T5<01><00><00>6<01>
<00><00>T6<01><00><00>T6<01><00><00>T-<01>T-<01>T-<01>2T,<00><00><01>2<00><00><01><01>2<00><00><01><01>3H<00><01><01>T7<00><01><00><00>TT7<00><00><01><00><00>TT.<00><00><01>TT7<00><00><01><00><00>TT-T3<00><00><01><00>T.<01>TT.<01>TT-<00><00><01>T3<00><00><01><01>T4HH<01><01>TT3HH<01><01>T7<01>
<00><00>TT6<00><00><01><00><00>T7<01><00><00>TT6<00><01><00><00>T6<00><00><01> <00><00>T-<00><00><01> T-<01><00><01>TF<01><01> PAGEHEADING VERSOHEADF<01><01> PAGEHEADING RECTOHEADE<01><01> PAGEHEADINGFOOTINGVE<01><01> PAGEHEADINGFOOTINGRMODERN
<03>TERMINAL
<00>
TIMESROMAN
<00>MODERN
<01>
TIMESROMAN
<01>
TIMESROMAN
<02>MODERN
<02>MODERN
<00>MODERN
MODERN
MODERN
MODERN
G9(DEFAULTFONT 1 (HELVETICA 12 BRR) (GACHA 8) (TERMINAL 8)) MODERN
TERMINAL

TIMESROMAN

TIMESROMAN
MODERN

TIMESROMAN
MODERN MODERN
MODERNMODERNMODERN
) HRULE.GETFNMODERN
 )@
( HRULE.GETFNMODERN
@ '
' HRULE.GETFNMODERN
 &
& HRULE.GETFNMODERN
  HRULE.GETFNMODERN$<00>#\  HRULE.GETFNMODERN
  HRULE.GETFNMODERN#IYIM.INDEX.GETFNC#<00># <00>#X-= #3m#<00>#H 
 HRULE.GETFNMODERN  <01>
 X! HRULE.GETFNMODERN
5IM.INDEX.GETFN
TIMESROMAN
<02> )'X

 HRULE.GETFNMODERN
/IM.INDEX.GETFN
TIMESROMAN
<02> K`C &" 
 HRULE.GETFNMODERN
   TEIM.INDEX.GETFN
TIMESROMAN
<02>
 - #;$ $Wc     
 1  ! HRULE.GETFNMODERN
y6IM.INDEX.GETFN
TIMESROMAN
<02>(4IM.INDEX.GETFN
TIMESROMAN
<02>' $? t 
 HRULE.GETFNMODERN #<00> 
 HRULE.GETFNMODERN
.  0x21IM.INDEX.GETFN
TIMESROMAN
<00>.$
 #"2" *
! HRULE.GETFNMODERN
-IM.INDEX.GETFN
TIMESROMAN
<02> 
u -! HRULE.GETFNMODERN
/IM.INDEX.GETFN
TIMESROMAN
<02>  
& t
 -! HRULE.GETFNMODERN
/IM.INDEX.GETFN
TIMESROMAN
<02>
 @ q <00>    1IM.INDEX.GETFN
 HRULE.GETFNMODERN
4IM.INDEX.GETFN
TIMESROMAN
<02> "-H AIM.INDEX.GETFN
 HRULE.GETFNMODERN
"-<00>$IM.INDEX.GETFNMODERN
X &
 HRULE.GETFNMODERN
"/ AIM.INDEX.GETFN<00> 
 HRULE.GETFNMODERN  3 <00>'IM.INDEX.GETFN
<00> 
 HRULE.GETFNMODERN
.IM.INDEX.GETFN . <00>>IM.INDEX.GETFN
TIMESROMAN
<02> Y K <00> 2IM.INDEX.GETFN <00> v  
 HRULE.GETFNMODERN
*IM.INDEX.GETFN  .                  
 HRULE.GETFNMODERN
 KIM.INDEX.GETFNMODERN
<00>  <00> { cIM.INDEX.GETFN HRULE.GETFNMODERN  
 HRULE.GETFNMODERN
3IM.INDEX.GETFN
TIMESROMAN
<02> #IM.INDEX.GETFN  W %   k   J  
8[ 
 7 "  [IM.INDEX.GETFN HRULE.GETFNMODERN ! HRULE.GETFNMODERN

'IM.INDEX.GETFN
TIMESROMAN
<02> 1
I  "+" A "3N <01> 
> <00> _ ".  ' ) 
 4 <00>  HRULE.GETFNMODERN >lIM.INDEX.GETFN<01>

 
 HRULE.GETFNMODERN  <00>IM.INDEX.GETFNn  HRULE.GETFNMODERN  HRULE.GETFNMODERN
( .IM.INDEX.GETFNG <00>  (IM.INDEX.GETFN
TIMESROMAN
<02> 
<00>   HRULE.GETFNMODERN

&IM.INDEX.GETFN
  HRULE.GETFNMODERN !IM.INDEX.GETFNMODERN
   HRULE.GETFNMODERN
<00>b Z !IM.INDEX.GETFN  HRULE.GETFNMODERN
C<01> <00> 
<V<00>5  HRULE.GETFNMODERN
<00> +  HRULE.GETFNMODERN
=  .
 )  HRULE.GETFNMODERN
<01>   HRULE.GETFNMODERN $XIM.INDEX.GETFN  HRULE.GETFNMODERN
<01>
c
  HRULE.GETFNMODERN
<00> "IM.INDEX.GETFN IM.INDEX.GETFN<00> Z Y IM.INDEX.GETFN1 W  HRULE.GETFNMODERN
6 XIM.INDEX.GETFN
TIMESROMAN
<02>' 9 a  ,a <00>  V  HRULE.GETFNMODERN
"!IM.INDEX.GETFN3IM.INDEX.GETFN7'IM.INDEX.GETFNg&'IM.INDEX.GETFN ;IM.INDEX.GETFN@ 1IM.INDEX.GETFN *  HRULE.GETFNMODERN
LrIM.INDEX.GETFNXnIM.INDEX.GETFN  HRULE.GETFNMODERN
L5  HRULE.GETFNMODERN
<00>IM.INDEX.GETFNGD  HRULE.GETFNMODERN
;jIM.INDEX.GETFN3*<00>| HRULE.GETFNMODERN
&IM.INDEX.GETFNBIM.INDEX.GETFNDIM.INDEX.GETFN HRULE.GETFNMODERN
<00>
%$r4&z<>