f9d65a12939347c3be670ee09b9cff35c461beb4
[sbcl.git] / BUGS
1 REPORTING BUGS
2
3 Bugs can be reported on the help mailing list
4   sbcl-help@lists.sourceforge.net
5 or on the development mailing list
6   sbcl-devel@lists.sourceforge.net
7
8 Please please please include enough information in a bug report
9 that someone reading it can reproduce the problem, i.e. don't write
10      Subject: apparent bug in PRINT-OBJECT (or *PRINT-LENGTH*?)
11      PRINT-OBJECT doesn't seem to work with *PRINT-LENGTH*. Is this a bug?
12 but instead
13      Subject: apparent bug in PRINT-OBJECT (or *PRINT-LENGTH*?)
14      In sbcl-1.2.3 running under OpenBSD 4.5 on my Alpha box, when
15      I compile and load the file
16        (DEFSTRUCT (FOO (:PRINT-OBJECT (LAMBDA (X Y)
17                                         (LET ((*PRINT-LENGTH* 4))
18                                           (PRINT X Y)))))
19          X Y)
20      then at the command line type
21        (MAKE-FOO)
22      the program loops endlessly instead of printing the object.
23
24
25 KNOWN PORT-SPECIFIC BUGS
26
27 The breakpoint-based TRACE facility doesn't work properly in the
28 OpenBSD port of sbcl-0.6.7.
29
30 KNOWN BUGS
31
32 (There is also some information on bugs in the manual page and in the
33 TODO file. Eventually more such information may move here.)
34
35 * The FUNCTION special operator doesn't check properly whether its
36   argument is a function name. E.g. (FUNCTION (X Y)) returns a value
37   instead of failing with an error. (Later attempting to funcall the
38   value does cause an error.)
39
40 * Failure in initialization files is not handled gracefully -- it's 
41   a throw to TOP-LEVEL-CATCHER, which is not caught until we enter
42   TOPLEVEL-REPL. Code should be added to catch such THROWs even when
43   we're not in TOPLEVEL-REPL and do *something* with them (probably
44   complaining about an error outside TOPLEVEL-REPL, perhaps printing
45   a BACKTRACE, then terminating execution of SBCL).
46
47 * COMPILED-FUNCTION-P bogusly reports T for interpreted functions:
48         * (DEFUN FOO (X) (- 12 X))
49         FOO
50         * (COMPILED-FUNCTION-P #'FOO)
51         T
52
53 * DEFSTRUCT should almost certainly overwrite the old LAYOUT information
54   instead of just punting when a contradictory structure definition
55   is loaded.
56
57 * It should cause a STYLE-WARNING, not a full WARNING, when a structure
58   slot default value does not match the declared structure slot type.
59   (The current behavior is consistent with SBCL's behavior elsewhere,
60   and would not be a problem, except that the other behavior is 
61   specifically required by the ANSI spec.)
62
63 * It should cause a STYLE-WARNING, not a WARNING, when the system ignores
64   an FTYPE proclamation for a slot accessor.
65
66 * Error reporting on various stream-requiring operations is not 
67   very good when the stream argument has the wrong type, because
68   the operation tries to fall through to Gray stream code, and then
69   dies because it's undefined. E.g. 
70     (PRINT-UNREADABLE-OBJECT (*STANDARD-OUTPUT* 1))
71   gives the error message
72     error in SB-KERNEL::UNDEFINED-SYMBOL-ERROR-HANDLER:
73       The function SB-IMPL::STREAM-WRITE-STRING is undefined.
74   It would be more useful and correct to signal a TYPE-ERROR:
75     not a STREAM: 1
76   (It wouldn't be terribly difficult to write stubs for all the 
77   Gray stream functions that the old CMU CL code expects, with
78   each stub just raising the appropriate TYPE-ERROR.)
79
80 * bogus warnings about undefined functions for magic functions like
81   SB!C::%%DEFUN and SB!C::%DEFCONSTANT when cross-compiling files
82   like src/code/float.lisp
83
84 * The "byte compiling top-level form:" output ought to be condensed.
85   Perhaps any number of such consecutive lines ought to turn into a
86   single "byte compiling top-level forms:" line.
87
88 * The handling of IGNORE declarations on lambda list arguments of DEFMETHOD
89   is at least weird, and in fact seems broken and useless. I should 
90   fix up another layer of binding, declared IGNORABLE, for typed
91   lambda list arguments.
92
93 * Compiling a file containing the erroneous program
94         (DEFSTRUCT FOO
95           A
96           B)
97         (DEFSTRUCT (BAR (:INCLUDE FOO))
98           A
99           B)
100   gives only the not-very-useful message
101         caught ERROR:
102           (during macroexpansion)
103         Condition PROGRAM-ERROR was signalled.
104   (The specific message which says that the problem was duplicate
105   slot names gets lost.)
106
107 * The way that the compiler munges types with arguments together
108   with types with no arguments (in e.g. TYPE-EXPAND) leads to
109   weirdness visible to the user:
110         (DEFTYPE FOO () 'FIXNUM)
111         (TYPEP 11 'FOO) => T
112         (TYPEP 11 '(FOO)) => T, which seems weird
113         (TYPEP 11 'FIXNUM) => T
114         (TYPEP 11 '(FIXNUM)) signals an error, as it should
115   The situation is complicated by the presence of Common Lisp types
116   like UNSIGNED-BYTE (which can either be used in list form or alone)
117   so I'm not 100% sure that the behavior above is actually illegal.
118   But I'm 90+% sure, and someday perhaps I'll be motivated to look it up..
119
120 * It would be nice if the
121         caught ERROR:
122           (during macroexpansion)
123   said what macroexpansion was at fault, e.g.
124         caught ERROR:
125           (during macroexpansion of IN-PACKAGE,
126           during macroexpansion of DEFFOO)
127
128 * The type system doesn't understand the KEYWORD type very well:
129         (SUBTYPEP 'KEYWORD 'SYMBOL) => NIL, NIL
130   It might be possible to fix this by changing the definition of
131   KEYWORD to (AND SYMBOL (SATISFIES KEYWORDP)), but the type system
132   would need to be a bit smarter about AND types, too:
133         (SUBTYPEP '(AND SYMBOL KEYWORD) 'SYMBOL) => NIL, NIL
134   (The type system does know something about AND types already,
135         (SUBTYPEP '(AND INTEGER FLOAT) 'NUMBER) => T, T
136         (SUBTYPEP '(AND INTEGER FIXNUM) 'NUMBER) =>T, T
137   so likely this is a small patch.)
138
139 * Floating point infinities are screwed up. [When I was converting CMU CL
140   to SBCL, I was looking for complexity to delete, and I thought it was safe
141   to just delete support for floating point infinities. It wasn't: they're
142   generated by the floating point hardware even when we remove support
143   for them in software. -- WHN] Support for them should be restored.
144
145 * The ANSI syntax for non-STANDARD method combination types in CLOS is
146         (DEFGENERIC FOO (X) (:METHOD-COMBINATION PROGN))
147         (DEFMETHOD FOO PROGN ((X BAR)) (PRINT 'NUMBER))
148   If you mess this up, omitting the PROGN qualifier in in DEFMETHOD,
149         (DEFGENERIC FOO (X) (:METHOD-COMBINATION PROGN))
150         (DEFMETHOD FOO ((X BAR)) (PRINT 'NUMBER))
151   the error mesage is not easy to understand:
152            INVALID-METHOD-ERROR was called outside the dynamic scope
153         of a method combination function (inside the body of
154         DEFINE-METHOD-COMBINATION or a method on the generic
155         function COMPUTE-EFFECTIVE-METHOD).
156   It would be better if it were more informative, a la
157            The method combination type for this method (STANDARD) does
158         not match the method combination type for the generic function
159         (PROGN).
160   Also, after you make the mistake of omitting the PROGN qualifier
161   on a DEFMETHOD, doing a new DEFMETHOD with the correct qualifier
162   no longer works:
163         (DEFMETHOD FOO PROGN ((X BAR)) (PRINT 'NUMBER))
164   gives
165            INVALID-METHOD-ERROR was called outside the dynamic scope
166         of a method combination function (inside the body of
167         DEFINE-METHOD-COMBINATION or a method on the generic
168         function COMPUTE-EFFECTIVE-METHOD).
169   This is not very helpful..
170
171 * (SUBTYPEP '(FUNCTION (T BOOLEAN) NIL)
172             '(FUNCTION (FIXNUM FIXNUM) NIL)) => T, T
173   (Also, when this is fixed, we can enable the code in PROCLAIM which 
174   checks for incompatible FTYPE redeclarations.)
175
176 * The ANSI spec says that CONS can be a compound type spec, e.g.
177   (CONS FIXNUM REAL). SBCL doesn't support this.
178
179 * from Paolo Amoroso on the CMU CL mailing list 27 Feb 2000:
180    I use CMU CL 18b under Linux. When COMPILE-FILE is supplied a physical
181 pathname, the type of the corresponding compiled file is X86F:
182         * (compile-file "/home/paolo/lisp/tools/foo")
183         Python version 1.0, VM version Intel x86 on 27 FEB 0 06:00:46 pm.
184         Compiling: /home/paolo/lisp/tools/foo.lisp 27 FEB 0 05:57:42 pm
185         Converted SQUARE.
186         Compiling DEFUN SQUARE:
187         Byte Compiling Top-Level Form:
188         /home/paolo/lisp/tools/foo.x86f written.
189         Compilation finished in 0:00:00.
190         #p"/home/paolo/lisp/tools/foo.x86f"
191         NIL
192         NIL
193 But when the function is called with a logical pathname, the file type
194 becomes FASL:
195         * (compile-file "tools:foo")
196         Python version 1.0, VM version Intel x86 on 27 FEB 0 06:01:04 pm.
197         Compiling: /home/paolo/lisp/tools/foo.lisp 27 FEB 0 05:57:42 pm
198         Converted SQUARE.
199         Compiling DEFUN SQUARE:
200         Byte Compiling Top-Level Form:
201         TOOLS:FOO.FASL written.
202         Compilation finished in 0:00:00.
203         #p"/home/paolo/lisp/tools/foo.fasl"
204         NIL
205         NIL
206
207 * from DTC on the CMU CL mailing list 25 Feb 2000:
208 ;;; Compiler fails when this file is compiled.
209 ;;;
210 ;;; Problem shows up in delete-block within ir1util.lisp. The assertion
211 ;;; (assert (member (functional-kind lambda) '(:let :mv-let :assignment)))
212 ;;; fails within bind node branch.
213 ;;;
214 ;;; Note that if c::*check-consistency* is enabled then an un-reached
215 ;;; entry is also reported.
216 ;;;
217 (defun foo (val)
218   (declare (values nil))
219   nil)
220 (defun bug (val)
221   (multiple-value-call
222       #'(lambda (res)
223           (block nil
224             (tagbody
225              loop
226                (when res
227                  (return nil))
228                (go loop))))
229     (foo val))
230   (catch 'ccc1
231     (throw 'ccc1
232       (block bbbb
233         (tagbody
234
235            (let ((ttt #'(lambda () (go cccc))))
236              (declare (special ttt))
237              (return-from bbbb nil))
238
239          cccc
240            (return-from bbbb nil))))))
241
242 * (I *think* this is a bug. It certainly seems like strange behavior. But
243   the ANSI spec is scary, dark, and deep..)
244     (FORMAT NIL  "~,1G" 1.4) => "1.    "
245     (FORMAT NIL "~3,1G" 1.4) => "1.    "
246
247 * from Marco Antoniotti on cmucl-imp mailing list 1 Mar 2000:
248         (defclass ccc () ())
249         (setf (find-class 'ccc1) (find-class 'ccc))
250         (defmethod zut ((c ccc1)) 123)
251   DTC's recommended workaround from the mailing list 3 Mar 2000:
252         (setf (pcl::find-class 'ccc1) (pcl::find-class 'ccc))
253
254 * There's probably a bug in the compiler handling of special variables
255   in closures, inherited from the CMU CL code, as reported on the
256   CMU CL mailing list. There's a patch for this on the CMU CL
257   mailing list too:
258     Message-ID: <38C8E188.A1E38B5E@jeack.com.au>
259     Date: Fri, 10 Mar 2000 22:50:32 +1100
260     From: "Douglas T. Crosher" <dtc@jeack.com.au>
261
262 * The ANSI spec, in section "22.3.5.2 Tilde Less-Than-Sign: Logical Block",
263   says that an error is signalled if ~W, ~_, ~<...~:>, ~I, or ~:T is used
264   inside "~<..~>" (without the colon modifier on the closing syntax).
265   However, SBCL doesn't do this:
266         * (FORMAT T "~<munge~wegnum~>" 12)
267         munge12egnum
268         NIL
269
270 * When too many files are opened, OPEN will fail with an
271   uninformative error message 
272         error in function OPEN: error opening #P"/tmp/foo.lisp": NIL
273   instead of saying that too many files are open.
274
275 * Right now, when COMPILE-FILE has a read error, it actually pops
276   you into the debugger before giving up on the file. It should
277   instead handle the error, perhaps issuing (and handling)
278   a secondary error "caught ERROR: unrecoverable error during compilation"
279   and then return with FAILURE-P true,
280
281 * from CMU CL mailing list 01 May 2000 
282
283 I realize I can take care of this by doing (proclaim (ignore pcl::.slots1.))
284 but seeing as .slots0. is not-exported, shouldn't it be ignored within the
285 +expansion
286 when not used?
287  
288 In: DEFMETHOD FOO-BAR-BAZ (RESOURCE-TYPE)
289   (DEFMETHOD FOO-BAR-BAZ
290              ((SELF RESOURCE-TYPE))
291              (SETF (SLOT-VALUE SELF 'NAME) 3))
292 --> BLOCK MACROLET PCL::FAST-LEXICAL-METHOD-FUNCTIONS
293 --> PCL::BIND-FAST-LEXICAL-METHOD-MACROS MACROLET
294 --> PCL::BIND-LEXICAL-METHOD-FUNCTIONS LET PCL::BIND-ARGS LET* PCL::PV-BINDING
295 --> PCL::PV-BINDING1 PCL::PV-ENV LET
296 ==>
297   (LET ((PCL::.SLOTS0. #))
298     (PROGN SELF)
299     (BLOCK FOO-BAR-BAZ
300       (LET #
301         #)))
302 Warning: Variable PCL::.SLOTS0. defined but never used.
303  
304 Compilation unit finished.
305   1 warning
306
307 #<Standard-Method FOO-BAR-BAZ (RESOURCE-TYPE) {480918FD}>
308
309 * reported by Sam Steingold on the cmucl-imp mailing list 12 May 2000:
310
311 Also, there is another bug: `array-displacement' should return an array
312 or nil as first value (as per ANSI CL), while CMUCL declares it as
313 returning an array as first value always.
314
315 * Sometimes (SB-EXT:QUIT) fails with 
316         Argh! maximum interrupt nesting depth (4096) exceeded, exiting
317         Process inferior-lisp exited abnormally with code 1
318   I haven't noticed a repeatable case of this yet.
319
320 * The system accepts DECLAIM in most places where DECLARE would be 
321   accepted, without even issuing a warning. ANSI allows this, but since
322   it's fairly easy to mistype DECLAIM instead of DECLARE, and the
323   meaning is rather different, and it's unlikely that the user
324   has a good reason for doing DECLAIM not at top level, it would be 
325   good to issue a STYLE-WARNING when this happens. A possible
326   fix would be to issue STYLE-WARNINGs for DECLAIMs not at top level,
327   or perhaps to issue STYLE-WARNINGs for any EVAL-WHEN not at top level.
328
329 * There seems to be some sort of bug in the interaction of the
330   normal compiler, the byte compiler, and type predicates.
331   Compiling and loading this file
332     (IN-PACKAGE :CL-USER)
333     (DEFSTRUCT FOO A B)
334     (PROGN
335      (DECLAIM (FTYPE (FUNCTION (FOO) FOO) FOO-BAR))
336      (DECLAIM (INLINE FOO-BAR))
337      (DEFUN FOO-BAR (FOO)
338        (DECLARE (TYPE FOO FOO))
339        (LET ((RESULT2605 (BLOCK FOO-BAR (PROGN (THE FOO (FOO-A FOO))))))
340          (UNLESS (TYPEP RESULT2605 'FOO)
341            (LOCALLY (ERROR "OOPS")))
342          (THE FOO RESULT2605)))
343      'FOO-BAR)
344     (DEFPARAMETER *FOO* (MAKE-FOO :A (MAKE-FOO)))
345     (UNLESS (EQ *PRINT-LEVEL* 133)
346       (DEFUN CK? ()
347         (LABELS ((FLOOD ()
348                     (WHEN (TYPEP *X* 'FOO)
349                       (FOO-BAR *Y*))))))
350       (PRINT 11)
351       (PRINT (FOO-BAR *FOO*))
352       (PRINT 12))
353   in sbcl-0.6.5 (or also in CMU CL 18b for FreeBSD) gives a call
354   to the undefined function SB-C::%INSTANCE-TYPEP. %INSTANCE-TYPEP
355   is not defined as a function because it's supposed to
356   be transformed away. My guess is what's happening is that
357   the mixture of toplevel and non-toplevel stuff and inlining
358   is confusing the system into compiling an %INSTANCE-TYPEP
359   form into byte code, where the DEFTRANSFORM which is supposed
360   to get rid of such forms is not effective.
361
362 * some sort of bug in inlining and RETURN-FROM in sbcl-0.6.5: Compiling
363     (DEFUN BAR? (X)
364       (OR (NAR? X)
365           (BLOCK USED-BY-SOME-Y?
366             (FLET ((FROB (STK)
367                      (DOLIST (Y STK)
368                        (UNLESS (REJECTED? Y)
369                          (RETURN-FROM USED-BY-SOME-Y? T)))))
370               (DECLARE (INLINE FROB))
371               (FROB (RSTK X))
372               (FROB (MRSTK X)))
373             NIL)))
374   gives
375    error in function SB-KERNEL:ASSERT-ERROR:
376    The assertion (EQ (SB-C::CONTINUATION-KIND SB-C::CONT) :BLOCK-START) failed.
377
378 * The CMU CL reader code takes liberties in binding the standard read table
379   when reading the names of characters. Tim Moore posted a patch to the 
380   CMU CL mailing list Mon, 22 May 2000 21:30:41 -0700.
381
382 * In some cases the compiler believes type declarations on array
383   elements without checking them, e.g.
384         (DECLAIM (OPTIMIZE (SAFETY 3) (SPEED 1) (SPACE 1)))
385         (DEFSTRUCT FOO A B)
386         (DEFUN BAR (X)
387           (DECLARE (TYPE (SIMPLE-ARRAY CONS 1) X))
388           (WHEN (CONSP (AREF X 0))
389             (PRINT (AREF X 0))))
390         (BAR (VECTOR (MAKE-FOO :A 11 :B 12)))
391   prints
392         #S(FOO :A 11 :B 12) 
393   in SBCL 0.6.5 (and also in CMU CL 18b). This does not happen for
394   all cases, e.g. the type assumption *is* checked if the array
395   elements are declared to be of some structure type instead of CONS.
396
397 * The printer doesn't report closures very well. This is true in 
398   CMU CL 18b as well:
399     (PRINT #'CLASS-NAME)
400   gives
401     #<Closure Over Function "DEFUN STRUCTURE-SLOT-ACCESSOR" {134D1A1}>
402   It would be nice to make closures have a settable name slot,
403   and make things like DEFSTRUCT and FLET, which create closures,
404   set helpful values into this slot.
405
406 * And as long as we're wishing, it would be awfully nice if INSPECT could
407   also report on closures, telling about the values of the bound variables.
408
409 * as reported by Robert Strandh on the CMU CL mailing list 12 Jun 2000:
410     $ cat xx.lisp
411     (defconstant +a-constant+ (make-instance 'a-class))
412     (defconstant +another-constant+ (vector +a-constant+))
413     $ lisp
414     CMU Common Lisp release x86-linux 2.4.19  8 February 2000 build 456,
415     running on
416     bobby
417     Send bug reports and questions to your local CMU CL maintainer,
418     or to pvaneynd@debian.org
419     or to cmucl-help@cons.org. (prefered)
420     type (help) for help, (quit) to exit, and (demo) to see the demos
421     Loaded subsystems:
422       Python 1.0, target Intel x86
423       CLOS based on PCL version:  September 16 92 PCL (f)
424     * (defclass a-class () ())
425     #<STANDARD-CLASS A-CLASS {48027BD5}>
426     * (compile-file "xx.lisp")
427     Python version 1.0, VM version Intel x86 on 12 JUN 00 08:12:55 am.
428     Compiling:
429     /home/strandh/Research/Functional/Common-Lisp/CLIM/Development/McCLIM
430     /xx.lisp 12 JUN 00 07:47:14 am
431     Compiling Load Time Value of (PCL::GET-MAKE-INSTANCE-FUNCTION-SYMBOL
432     '(A-CLASS NIL NIL)):
433     Byte Compiling Top-Level Form:
434     Error in function C::DUMP-STRUCTURE:  Attempt to dump invalid
435     structure:
436       #<A-CLASS {4803A5B5}>
437     How did this happen?
438
439 * The compiler assumes that any time a function of declared FTYPE
440   doesn't signal an error, its arguments were of the declared type.
441   E.g. compiling and loading
442     (DECLAIM (OPTIMIZE (SAFETY 3)))
443     (DEFUN FACTORIAL (X) (GAMMA (1+ X)))
444     (DECLAIM (FTYPE (FUNCTION (UNSIGNED-BYTE) FACTORIAL)))
445     (DEFUN FOO (X)
446       (COND ((> (FACTORIAL X) 1.0E6)
447              (FORMAT T "too big~%"))
448             ((INTEGERP X)
449              (FORMAT T "exactly ~S~%" (FACTORIAL X)))
450             (T
451              (FORMAT T "approximately ~S~%" (FACTORIAL X)))))
452   then executing
453     (FOO 1.5)
454   will cause the INTEGERP case to be selected, giving bogus output a la
455     exactly 1.33..
456   This violates the "declarations are assertions" principle.
457   According to the ANSI spec, in the section "System Class FUNCTION",
458   this is a case of "lying to the compiler", but the lying is done
459   by the code which calls FACTORIAL with non-UNSIGNED-BYTE arguments,
460   not by the unexpectedly general definition of FACTORIAL. In any case,
461   "declarations are assertions" means that lying to the compiler should
462   cause an error to be signalled, and should not cause a bogus
463   result to be returned. Thus, the compiler should not assume
464   that arbitrary functions check their argument types. (It might
465   make sense to add another flag (CHECKED?) to DEFKNOWN to 
466   identify functions which *do* check their argument types.)
467
468 * As pointed out by Martin Cracauer on the CMU CL mailing list
469   13 Jun 2000, the :FILE-LENGTH operation for 
470   FD-STREAM-MISC-ROUTINE is broken for large files: it says
471   (THE INDEX SIZE) even though SIZE can be larger than INDEX.
472
473 * In SBCL 0.6.5 (and CMU CL 18b) compiling and loading
474         (in-package :cl-user)
475         (declaim (optimize (safety 3)
476                            (debug 3)
477                            (compilation-speed 2)
478                            (space 1)
479                            (speed 2)
480                            #+nil (sb-ext:inhibit-warnings 2)))
481         (declaim (ftype (function * (values)) emptyvalues))
482         (defun emptyvalues (&rest rest) (declare (ignore rest)) (values))
483         (defstruct foo x y)
484         (defgeneric assertoid ((x t)))
485         (defmethod assertoid ((x t)) "just a placeholder")
486         (defun bar (ht)
487           (declare (type hash-table ht))
488           (let ((res
489                  (block blockname
490                    (progn
491                     (prog1
492                         (emptyvalues)
493                       (assertoid (hash-table-count ht)))))))
494             (unless (typep res 'foo)
495               (locally
496                (common-lisp-user::bad-result-from-assertive-typed-fun
497                 'bar
498                 res)))))
499   then executing
500         (bar (make-hash-table))
501   causes the failure
502         Error in KERNEL::UNDEFINED-SYMBOL-ERROR-HANDLER:
503           the function C::%INSTANCE-TYPEP is undefined.
504   %INSTANCE-TYPEP is always supposed to be IR1-transformed away, but for
505   some reason -- the (VALUES) return value declaration? -- the optimizer is
506   confused and compiles a full call to %INSTANCE-TYPEP (which doesn't exist
507   as a function) instead.
508
509 * DEFMETHOD doesn't check the syntax of &REST argument lists properly,
510   accepting &REST even when it's not followed by an argument name:
511         (DEFMETHOD FOO ((X T) &REST) NIL)
512
513 * On the CMU CL mailing list 26 June 2000, Douglas Crosher wrote
514
515   Hannu Rummukainen wrote:
516   ...
517   > There's something weird going on with the compilation of the attached
518   > code.  Compiling and loading the file in a fresh lisp, then invoking
519   > (test-it) gives
520   Thanks for the bug report, nice to have this one fixed. It was a bug
521   in the x86 backend, the < VOP. A fix has been committed to the main
522   source, see the file compiler/x86/float.lisp.
523
524   Probably the same bug exists in SBCL.
525
526 * TYPEP treats the result of UPGRADED-ARRAY-ELEMENT-TYPE as gospel,
527   so that (TYPEP (MAKE-ARRAY 3) '(VECTOR SOMETHING-NOT-DEFINED-YET))
528   returns (VALUES T T). Probably it should be an error instead,
529   complaining that the type SOMETHING-NOT-DEFINED-YET is not defined.
530
531 * TYPEP of VALUES types is sometimes implemented very inefficiently, e.g. in 
532         (DEFTYPE INDEXOID () '(INTEGER 0 1000))
533         (DEFUN FOO (X)
534           (DECLARE (TYPE INDEXOID X))
535           (THE (VALUES INDEXOID)
536             (VALUES X)))
537   where the implementation of the type check in function FOO 
538   includes a full call to %TYPEP. There are also some fundamental problems
539   with the interpretation of VALUES types (inherited from CMU CL, and
540   from the ANSI CL standard) as discussed on the cmucl-imp@cons.org
541   mailing list, e.g. in Robert Maclachlan's post of 21 Jun 2000.
542
543 * The definitions of SIGCONTEXT-FLOAT-REGISTER and
544   %SET-SIGCONTEXT-FLOAT-REGISTER in x86-vm.lisp say they're not
545   supported on FreeBSD because the floating point state is not saved,
546   but at least as of FreeBSD 4.0, the floating point state *is* saved,
547   so they could be supported after all. Very likely 
548   SIGCONTEXT-FLOATING-POINT-MODES could now be supported, too.
549
550 * (as discussed by Douglas Crosher on the cmucl-imp mailing list ca. 
551   Aug. 10, 2000): CMUCL currently interprets 'member as '(member); same issue
552   with 'union, 'and, 'or etc. So even though according to the ANSI spec,
553   bare 'MEMBER, 'AND, and 'OR are not legal types, CMUCL (and now
554   SBCL) interpret them as legal types.
555
556 * ANSI specifies DEFINE-SYMBOL-MACRO, but it's not defined in SBCL.
557   CMU CL added it ca. Aug 13, 2000, after some discussion on the mailing
558   list, and it is probably possible to use substantially the same 
559   patches to add it to SBCL.
560
561 * a slew of floating-point-related errors reported by Peter Van Eynde
562   on July 25, 2000:
563         * (SQRT -9.0) fails, because SB-KERNEL::COMPLEX-SQRT is undefined.
564           Similarly, COMPLEX-ASIN, COMPLEX-ACOS, COMPLEX-ACOSH, and others
565           aren't found.
566         * SBCL's value for LEAST-POSITIVE-SHORT-FLOAT is bogus, and 
567           should probably be 1.4012985e-45. In SBCL,
568           (/ LEAST-POSITIVE-SHORT-FLOAT 2) returns a number smaller
569           than LEAST-POSITIVE-SHORT-FLOAT. Similar problems 
570           exist for LEAST-NEGATIVE-SHORT-FLOAT, LEAST-POSITIVE-LONG-FLOAT,
571           and LEAST-NEGATIVE-LONG-FLOAT.
572         * Many expressions generate floating infinity:
573                 (/ 1 0.0)
574                 (/ 1 0.0d0)
575                 (EXPT 10.0 1000)
576                 (EXPT 10.0d0 1000)
577           PVE's regression tests want them to raise errors. SBCL
578           generates the infinities instead, which may or may not be
579           conforming behavior, but then blow it by being unable to
580           output the infinities, since support for infinities is generally
581           broken, and in particular SB-IMPL::OUTPUT-FLOAT-INFINITY is
582           undefined.
583         * (in section12.erg) various forms a la 
584           (FLOAT 1 DOUBLE-FLOAT-EPSILON) don't give the right behavior.
585
586 * type safety errors reported by Peter Van Eynde July 25, 2000:
587         * (COERCE (QUOTE (A B C)) (QUOTE (VECTOR * 4)))
588           => #(A B C)
589           In general lengths of array type specifications aren't
590           checked by COERCE, so it fails when the spec is
591           (VECTOR 4), (STRING 2), (SIMPLE-BIT-VECTOR 3), or whatever.
592         * CONCATENATE has the same problem of not checking the length
593           of specified output array types. MAKE-SEQUENCE and MAP and
594           MERGE also have the same problem.
595         * (COERCE 'AND 'FUNCTION) returns something related to
596           (MACRO-FUNCTION 'AND), but ANSI says it should raise an error.
597         * ELT signals SIMPLE-ERROR if its index argument
598           isn't a valid index for its sequence argument, but should 
599           signal TYPE-ERROR instead.
600         * FILE-LENGTH is supposed to signal a type error when its
601           argument is not a stream associated with a file, but doesn't.
602         * (FLOAT-RADIX 2/3) should signal an error instead of 
603           returning 2.
604         * (LOAD "*.lsp") should signal FILE-ERROR.
605         * (MAKE-CONCATENATED-STREAM (MAKE-STRING-OUTPUT-STREAM))
606           should signal TYPE-ERROR.
607         * MAKE-TWO-WAY-STREAM doesn't check that its arguments can
608           be used for input and output as needed. It should fail with
609           TYPE-ERROR when handed e.g. the results of MAKE-STRING-INPUT-STREAM
610           or MAKE-STRING-OUTPUT-STREAM in the inappropriate positions,
611           but doesn't.
612         * (PARSE-NAMESTRING (COERCE (LIST #\f #\o #\o (CODE-CHAR 0) #\4 #\8)
613                             (QUOTE STRING)))
614           should probably signal an error instead of making a pathname with
615           a null byte in it.
616         * READ-BYTE is supposed to signal TYPE-ERROR when its argument is 
617           not a binary input stream, but instead cheerfully reads from
618           character streams, e.g. (MAKE-STRING-INPUT-STREAM "abc").
619
620 * DEFCLASS bugs reported by Peter Van Eynde July 25, 2000:
621         * (DEFCLASS FOO () (A B A)) should signal a PROGRAM-ERROR, and doesn't.
622         * (DEFCLASS FOO () (A B A) (:DEFAULT-INITARGS X A X B)) should
623           signal a PROGRAM-ERROR, and doesn't.
624         * (DEFCLASS FOO07 NIL ((A :ALLOCATION :CLASS :ALLOCATION :CLASS))),
625           and other DEFCLASS forms with duplicate specifications in their
626           slots, should signal a PROGRAM-ERROR, and doesn't.
627         * (DEFGENERIC IF (X)) should signal a PROGRAM-ERROR, but instead
628           causes a COMPILER-ERROR.
629
630 * SYMBOL-MACROLET bugs reported by Peter Van Eynde July 25, 2000:
631         * (SYMBOL-MACROLET ((T TRUE)) ..) should probably signal
632           PROGRAM-ERROR, but SBCL accepts it instead.
633         * SYMBOL-MACROLET should refuse to bind something which is
634           declared as a global variable, signalling PROGRAM-ERROR.
635         * SYMBOL-MACROLET should signal PROGRAM-ERROR if something
636           it binds is declared SPECIAL inside.
637
638 * LOOP bugs reported by Peter Van Eynde July 25, 2000:
639         * (LOOP WITH (A B) DO (PRINT 1)) is a syntax error according to
640           the definition of WITH clauses given in the ANSI spec, but
641           compiles and runs happily in SBCL.
642         * a messy one involving package iteration:
643 interpreted Form: (LET ((PACKAGE (MAKE-PACKAGE "LOOP-TEST"))) (INTERN "blah" PACKAGE) (LET ((BLAH2 (INTERN "blah2" PACKAGE))) (EXPORT BLAH2 PACKAGE)) (LIST (SORT (LOOP FOR SYM BEING EACH PRESENT-SYMBOL OF PACKAGE FOR SYM-NAME = (SYMBOL-NAME SYM) COLLECT SYM-NAME) (FUNCTION STRING<)) (SORT (LOOP FOR SYM BEING EACH EXTERNAL-SYMBOL OF PACKAGE FOR SYM-NAME = (SYMBOL-NAME SYM) COLLECT SYM-NAME) (FUNCTION STRING<))))
644 Should be: (("blah" "blah2") ("blah2"))
645 SBCL: (("blah") ("blah2"))
646         * (LET ((X 1)) (LOOP FOR I BY (INCF X) FROM X TO 10 COLLECT I))
647           doesn't work -- SBCL's LOOP says BY isn't allowed in a FOR clause.
648
649 * type system errors reported by Peter Van Eynde July 25, 2000:
650         * (SUBTYPEP 'BIGNUM 'INTEGER) => NIL, NIL
651           but should be (VALUES T T) instead.
652         * (SUBTYPEP 'EXTENDED-CHAR 'CHARACTER) => NIL, NIL
653           but should be (VALUES T T) instead.
654         * (SUBTYPEP '(INTEGER (0) (0)) 'NIL) dies with nested errors.
655         * In general, the system doesn't like '(INTEGER (0) (0)) -- it
656           blows up at the level of SPECIFIER-TYPE with
657           "Lower bound (0) is greater than upper bound (0)." Probably
658           SPECIFIER-TYPE should return NIL instead.
659         * (TYPEP 0 '(COMPLEX (EQL 0)) fails with
660           "Component type for Complex is not numeric: (EQL 0)."
661           This might be easy to fix; the type system already knows
662           that (SUBTYPEP '(EQL 0) 'NUMBER) is true.
663         * The type system doesn't know about the condition system,
664           so that e.g. (TYPEP 'SIMPLE-ERROR 'ERROR)=>NIL.
665         * The type system isn't all that smart about relationships
666           between hairy types, as shown in the type.erg test results,
667           e.g. (SUBTYPEP 'CONS '(NOT ATOM)) => NIL, NIL.
668
669 * miscellaneous errors reported by Peter Van Eynde July 25, 2000:
670         * (PROGN
671             (DEFGENERIC FOO02 (X))
672             (DEFMETHOD FOO02 ((X NUMBER)) T)
673             (LET ((M (FIND-METHOD (FUNCTION FOO02)
674                                   NIL
675                                   (LIST (FIND-CLASS (QUOTE NUMBER))))))
676               (REMOVE-METHOD (FUNCTION FOO02) M)
677               (DEFGENERIC FOO03 (X))
678               (ADD-METHOD (FUNCTION FOO03) M)))
679            should give an error, but SBCL allows it.
680         * READ should probably return READER-ERROR, not the bare 
681           arithmetic error, when input a la "1/0" or "1e1000" causes
682           an arithmetic error.
683         * There are several metaobject protocol "errors". (In order to fix
684           them, we might need to document exactly what metaobject
685           protocol specification we're following -- the current code is
686           just inherited from PCL.)
687         * (BUTLAST NIL) should return NIL. (This appears to be a compiler
688           bug, since the definition of BUTLAST, when interpreted, does
689           give (BUTLAST NIL)=>NIL.)
690
691 * another error from Peter Van Eynde 5 September 2000:
692   (FORMAT NIL "~F" "FOO") should work, but instead reports an error.
693   PVE submitted a patch to deal with this bug, but it exposes other
694   comparably serious bugs, so I didn't apply it. It looks as though
695   the FORMAT code needs a fair amount of rewriting in order to comply
696   with the various details of the ANSI spec.
697
698 * The bug discussed on the cmucl-imp@cons.org mailing list ca. 5 September,
699   simplified by Douglas Crosher down to
700         (defun tickle-bug ()
701           (labels ((fun1 ()
702                      (fun2))
703                    (fun2 ()                             
704                      (when nil
705                        (tagbody
706                         tag
707                           (fun2)
708                           (go tag)))
709                      (when nil
710                        (tagbody
711                         tag
712                           (fun1)
713                           (go tag)))))
714             (fun1)
715             nil))
716   causes the same problem on SBCL: compiling it fails with 
717         :LET fell through ECASE expression.
718   Very likely the patch discussed there is appropriate for SBCL
719   as well, but I don't understand it, so I didn't apply it.
720
721 * The implementation of #'+ returns its single argument without
722   type checking, e.g. (+ "illegal") => "illegal".
723
724 * In sbcl-0.6.7, there is no doc string for CL:PUSH, probably 
725   because it's defined with the DEFMACRO-MUNDANELY macro and something
726   is wrong with doc string setting in that macro.
727
728 * Attempting to use COMPILE on something defined by DEFMACRO fails:
729         (DEFMACRO FOO (X) (CONS X X))
730         (COMPILE 'FOO)
731 Error in function C::GET-LAMBDA-TO-COMPILE:
732    #<Closure Over Function "DEFUN (SETF MACRO-FUNCTION)" {480E21B1}> was defined in a non-null environment.
733
734 * In sbcl-0.6.7, the compiler accepted a bogus declaration
735   (TYPE INDEX LENGTH) in the definition of BUTLAST, and then died
736   with infinite regress of errors when the BUTLAST function was
737   executed with a LIST=NIL which would cause LENGTH to be -1.
738   I fixed the bogus declaration, but I should come back and see
739   whether the system's inability to recover from the bogus declaration
740   (by signalling a TYPE-ERROR and dropping into the debugger) was 
741   a compiler problem which remains to be fixed, or one of the 
742   unrelated infinite-regress-errors problems, many related to 
743   revised signal handling, which were fixed around the same time.
744
745 * Even when FINISH-OUTPUT is called, the system doesn't in general
746   flush the last line of output unless it's terminated by a newline.
747   (This is particularly annoying because several Lisp functions like
748   PRINT *precede* their output with a newline, instead of following
749   it with a newline.)
750
751 * (SUBTYPEP '(AND ZILCH INTEGER) 'ZILCH) => NIL, NIL