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