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