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