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