b50388f3a757f829cfed8bc3bdb60e3fc307fee2
[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 bug descriptions which
31 have gone away (typically because they were fixed, but sometimes for
32 other reasons, e.g. because they were moved elsewhere).
33
34
35 KNOWN BUGS OF NO SPECIAL CLASS:
36
37 2:
38   DEFSTRUCT almost certainly should overwrite the old LAYOUT information
39   instead of just punting when a contradictory structure definition
40   is loaded. As it is, if you redefine DEFSTRUCTs in a way which 
41   changes their layout, you probably have to rebuild your entire
42   program, even if you know or guess enough about the internals of
43   SBCL to wager that this (undefined in ANSI) operation would be safe.
44
45 3:
46   ANSI specifies that a type mismatch in a structure slot
47   initialization value should not cause a warning.
48 WORKAROUND:
49   This one might not be fixed for a while because while we're big
50   believers in ANSI compatibility and all, (1) there's no obvious
51   simple way to do it (short of disabling all warnings for type
52   mismatches everywhere), and (2) there's a good portable
53   workaround. ANSI justifies this specification by saying 
54     The restriction against issuing a warning for type mismatches
55     between a slot-initform and the corresponding slot's :TYPE
56     option is necessary because a slot-initform must be specified
57     in order to specify slot options; in some cases, no suitable
58     default may exist.
59   In SBCL, as in CMU CL (or, for that matter, any compiler which
60   really understands Common Lisp types) a suitable default does
61   exist, in all cases, because the compiler understands the concept
62   of functions which never return (i.e. has return type NIL, e.g.
63   ERROR). Thus, as a portable workaround, you can use a call to
64   some known-never-to-return function as the default. E.g.
65     (DEFSTRUCT FOO
66       (BAR (ERROR "missing :BAR argument")
67            :TYPE SOME-TYPE-TOO-HAIRY-TO-CONSTRUCT-AN-INSTANCE-OF))
68   or 
69     (DECLAIM (FTYPE () NIL) MISSING-ARG) 
70     (DEFUN REQUIRED-ARG () ; workaround for SBCL non-ANSI slot init typing
71       (ERROR "missing required argument")) 
72     (DEFSTRUCT FOO
73       (BAR (REQUIRED-ARG) :TYPE TRICKY-TYPE-OF-SOME-SORT)
74       (BLETCH (REQUIRED-ARG) :TYPE TRICKY-TYPE-OF-SOME-SORT)
75       (N-REFS-SO-FAR 0 :TYPE (INTEGER 0)))
76   Such code will compile without complaint and work correctly either
77   on SBCL or on a completely compliant Common Lisp system.
78
79 6:
80   bogus warnings about undefined functions for magic functions like
81   SB!C::%%DEFUN and SB!C::%DEFCONSTANT when cross-compiling files
82   like src/code/float.lisp. Fixing this will probably require
83   straightening out enough bootstrap consistency issues that
84   the cross-compiler can run with *TYPE-SYSTEM-INITIALIZED*.
85   Instead, the cross-compiler runs in a slightly flaky state
86   which is sane enough to compile SBCL itself, but which is
87   also unstable in several ways, including its inability
88   to really grok function declarations.
89
90 7:
91   The "byte compiling top-level form:" output ought to be condensed.
92   Perhaps any number of such consecutive lines ought to turn into a
93   single "byte compiling top-level forms:" line.
94
95 8:
96   Compiling a file containing the erroneous program
97         (DEFSTRUCT FOO
98           A
99           B)
100         (DEFSTRUCT (BAR (:INCLUDE FOO))
101           A
102           B)
103   gives only the not-very-useful message
104         caught ERROR:
105           (during macroexpansion)
106         Condition PROGRAM-ERROR was signalled.
107   (The specific message which says that the problem was duplicate
108   slot names gets lost.)
109
110 9:
111   The handling of IGNORE declarations on lambda list arguments of
112   DEFMETHOD is at least weird, and in fact seems broken and useless.
113   I should fix up another layer of binding, declared IGNORABLE, for
114   typed lambda list arguments.
115
116 10:
117   The way that the compiler munges types with arguments together
118   with types with no arguments (in e.g. TYPE-EXPAND) leads to
119   weirdness visible to the user:
120         (DEFTYPE FOO () 'FIXNUM)
121         (TYPEP 11 'FOO) => T
122         (TYPEP 11 '(FOO)) => T, which seems weird
123         (TYPEP 11 'FIXNUM) => T
124         (TYPEP 11 '(FIXNUM)) signals an error, as it should
125   The situation is complicated by the presence of Common Lisp types
126   like UNSIGNED-BYTE (which can either be used in list form or alone)
127   so I'm not 100% sure that the behavior above is actually illegal.
128   But I'm 90+% sure, and someday perhaps I'll be motivated to look it up..
129
130 11:
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 12:
140   The type system doesn't understand the KEYWORD type very well:
141         (SUBTYPEP 'KEYWORD 'SYMBOL) => NIL, NIL
142   It might be possible to fix this by changing the definition of
143   KEYWORD to (AND SYMBOL (SATISFIES KEYWORDP)), but the type system
144   would need to be a bit smarter about AND types, too:
145         (SUBTYPEP '(AND SYMBOL KEYWORD) 'SYMBOL) => NIL, NIL
146   (The type system does know something about AND types already,
147         (SUBTYPEP '(AND INTEGER FLOAT) 'NUMBER) => T, T
148         (SUBTYPEP '(AND INTEGER FIXNUM) 'NUMBER) =>T, T
149   so likely this is a small patch.)
150
151 13:
152   Floating point infinities are screwed up. [When I was converting CMU CL
153   to SBCL, I was looking for complexity to delete, and I thought it was safe
154   to just delete support for floating point infinities. It wasn't: they're
155   generated by the floating point hardware even when we remove support
156   for them in software. -- WHN] Support for them should be restored.
157
158 14:
159   The ANSI syntax for non-STANDARD method combination types in CLOS is
160         (DEFGENERIC FOO (X) (:METHOD-COMBINATION PROGN))
161         (DEFMETHOD FOO PROGN ((X BAR)) (PRINT 'NUMBER))
162   If you mess this up, omitting the PROGN qualifier in in DEFMETHOD,
163         (DEFGENERIC FOO (X) (:METHOD-COMBINATION PROGN))
164         (DEFMETHOD FOO ((X BAR)) (PRINT 'NUMBER))
165   the error mesage is not easy to understand:
166            INVALID-METHOD-ERROR was called outside the dynamic scope
167         of a method combination function (inside the body of
168         DEFINE-METHOD-COMBINATION or a method on the generic
169         function COMPUTE-EFFECTIVE-METHOD).
170   It would be better if it were more informative, a la
171            The method combination type for this method (STANDARD) does
172         not match the method combination type for the generic function
173         (PROGN).
174   Also, after you make the mistake of omitting the PROGN qualifier
175   on a DEFMETHOD, doing a new DEFMETHOD with the correct qualifier
176   no longer works:
177         (DEFMETHOD FOO PROGN ((X BAR)) (PRINT 'NUMBER))
178   gives
179            INVALID-METHOD-ERROR was called outside the dynamic scope
180         of a method combination function (inside the body of
181         DEFINE-METHOD-COMBINATION or a method on the generic
182         function COMPUTE-EFFECTIVE-METHOD).
183   This is not very helpful..
184
185 15:
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 16:
192   The ANSI spec says that CONS can be a compound type spec, e.g.
193   (CONS FIXNUM REAL). SBCL doesn't support this.
194
195 17:
196   from Paolo Amoroso on the CMU CL mailing list 27 Feb 2000:
197 I use CMU CL 18b under Linux. When COMPILE-FILE is supplied a physical
198 pathname, the type of the corresponding compiled file is X86F:
199         * (compile-file "/home/paolo/lisp/tools/foo")
200         Python version 1.0, VM version Intel x86 on 27 FEB 0 06:00:46 pm.
201         Compiling: /home/paolo/lisp/tools/foo.lisp 27 FEB 0 05:57:42 pm
202         Converted SQUARE.
203         Compiling DEFUN SQUARE:
204         Byte Compiling Top-Level Form:
205         /home/paolo/lisp/tools/foo.x86f written.
206         Compilation finished in 0:00:00.
207         #p"/home/paolo/lisp/tools/foo.x86f"
208         NIL
209         NIL
210 But when the function is called with a logical pathname, the file type
211 becomes FASL:
212         * (compile-file "tools:foo")
213         Python version 1.0, VM version Intel x86 on 27 FEB 0 06:01:04 pm.
214         Compiling: /home/paolo/lisp/tools/foo.lisp 27 FEB 0 05:57:42 pm
215         Converted SQUARE.
216         Compiling DEFUN SQUARE:
217         Byte Compiling Top-Level Form:
218         TOOLS:FOO.FASL written.
219         Compilation finished in 0:00:00.
220         #p"/home/paolo/lisp/tools/foo.fasl"
221         NIL
222         NIL
223
224 18:
225   from DTC on the CMU CL mailing list 25 Feb 2000:
226 ;;; Compiler fails when this file is compiled.
227 ;;;
228 ;;; Problem shows up in delete-block within ir1util.lisp. The assertion
229 ;;; (assert (member (functional-kind lambda) '(:let :mv-let :assignment)))
230 ;;; fails within bind node branch.
231 ;;;
232 ;;; Note that if c::*check-consistency* is enabled then an un-reached
233 ;;; entry is also reported.
234 ;;;
235 (defun foo (val)
236   (declare (values nil))
237   nil)
238 (defun bug (val)
239   (multiple-value-call
240       #'(lambda (res)
241           (block nil
242             (tagbody
243              loop
244                (when res
245                  (return nil))
246                (go loop))))
247     (foo val))
248   (catch 'ccc1
249     (throw 'ccc1
250       (block bbbb
251         (tagbody
252
253            (let ((ttt #'(lambda () (go cccc))))
254              (declare (special ttt))
255              (return-from bbbb nil))
256
257          cccc
258            (return-from bbbb nil))))))
259
260 19:
261   (I *think* this is a bug. It certainly seems like strange behavior. But
262   the ANSI spec is scary, dark, and deep..)
263     (FORMAT NIL  "~,1G" 1.4) => "1.    "
264     (FORMAT NIL "~3,1G" 1.4) => "1.    "
265
266 20:
267   from Marco Antoniotti on cmucl-imp mailing list 1 Mar 2000:
268         (defclass ccc () ())
269         (setf (find-class 'ccc1) (find-class 'ccc))
270         (defmethod zut ((c ccc1)) 123)
271   DTC's recommended workaround from the mailing list 3 Mar 2000:
272         (setf (pcl::find-class 'ccc1) (pcl::find-class 'ccc))
273
274 22:
275   The ANSI spec, in section "22.3.5.2 Tilde Less-Than-Sign: Logical Block",
276   says that an error is signalled if ~W, ~_, ~<...~:>, ~I, or ~:T is used
277   inside "~<..~>" (without the colon modifier on the closing syntax).
278   However, SBCL doesn't do this:
279         * (FORMAT T "~<munge~wegnum~>" 12)
280         munge12egnum
281         NIL
282
283 23:
284   When too many files are opened, OPEN will fail with an
285   uninformative error message 
286         error in function OPEN: error opening #P"/tmp/foo.lisp": NIL
287   instead of saying that too many files are open.
288
289 24:
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 25:
297   from CMU CL mailing list 01 May 2000 
298
299 I realize I can take care of this by doing (proclaim (ignore pcl::.slots1.))
300 but seeing as .slots0. is not-exported, shouldn't it be ignored within the
301 +expansion
302 when not used?
303  
304 In: DEFMETHOD FOO-BAR-BAZ (RESOURCE-TYPE)
305   (DEFMETHOD FOO-BAR-BAZ
306              ((SELF RESOURCE-TYPE))
307              (SETF (SLOT-VALUE SELF 'NAME) 3))
308 --> BLOCK MACROLET PCL::FAST-LEXICAL-METHOD-FUNCTIONS
309 --> PCL::BIND-FAST-LEXICAL-METHOD-MACROS MACROLET
310 --> PCL::BIND-LEXICAL-METHOD-FUNCTIONS LET PCL::BIND-ARGS LET* PCL::PV-BINDING
311 --> PCL::PV-BINDING1 PCL::PV-ENV LET
312 ==>
313   (LET ((PCL::.SLOTS0. #))
314     (PROGN SELF)
315     (BLOCK FOO-BAR-BAZ
316       (LET #
317         #)))
318 Warning: Variable PCL::.SLOTS0. defined but never used.
319  
320 Compilation unit finished.
321   1 warning
322
323 #<Standard-Method FOO-BAR-BAZ (RESOURCE-TYPE) {480918FD}>
324
325 26:
326   reported by Sam Steingold on the cmucl-imp mailing list 12 May 2000:
327
328 Also, there is another bug: `array-displacement' should return an array
329 or nil as first value (as per ANSI CL), while CMUCL declares it as
330 returning an array as first value always.
331
332 27:
333   Sometimes (SB-EXT:QUIT) fails with 
334         Argh! maximum interrupt nesting depth (4096) exceeded, exiting
335         Process inferior-lisp exited abnormally with code 1
336   I haven't noticed a repeatable case of this yet.
337
338 29:
339   some sort of bug in inlining and RETURN-FROM in sbcl-0.6.5: Compiling
340     (DEFUN BAR? (X)
341       (OR (NAR? X)
342           (BLOCK USED-BY-SOME-Y?
343             (FLET ((FROB (STK)
344                      (DOLIST (Y STK)
345                        (UNLESS (REJECTED? Y)
346                          (RETURN-FROM USED-BY-SOME-Y? T)))))
347               (DECLARE (INLINE FROB))
348               (FROB (RSTK X))
349               (FROB (MRSTK X)))
350             NIL)))
351   gives
352    error in function SB-KERNEL:ASSERT-ERROR:
353    The assertion (EQ (SB-C::CONTINUATION-KIND SB-C::CONT) :BLOCK-START) failed.
354   This is still present in sbcl-0.6.8.
355
356 30:
357   The CMU CL reader code takes liberties in binding the standard read table
358   when reading the names of characters. Tim Moore posted a patch to the 
359   CMU CL mailing list Mon, 22 May 2000 21:30:41 -0700.
360
361 31:
362   In some cases the compiler believes type declarations on array
363   elements without checking them, e.g.
364         (DECLAIM (OPTIMIZE (SAFETY 3) (SPEED 1) (SPACE 1)))
365         (DEFSTRUCT FOO A B)
366         (DEFUN BAR (X)
367           (DECLARE (TYPE (SIMPLE-ARRAY CONS 1) X))
368           (WHEN (CONSP (AREF X 0))
369             (PRINT (AREF X 0))))
370         (BAR (VECTOR (MAKE-FOO :A 11 :B 12)))
371   prints
372         #S(FOO :A 11 :B 12) 
373   in SBCL 0.6.5 (and also in CMU CL 18b). This does not happen for
374   all cases, e.g. the type assumption *is* checked if the array
375   elements are declared to be of some structure type instead of CONS.
376
377 32:
378   The printer doesn't report closures very well. This is true in 
379   CMU CL 18b as well:
380     (PRINT #'CLASS-NAME)
381   gives
382     #<Closure Over Function "DEFUN STRUCTURE-SLOT-ACCESSOR" {134D1A1}>
383   It would be nice to make closures have a settable name slot,
384   and make things like DEFSTRUCT and FLET, which create closures,
385   set helpful values into this slot.
386
387 33:
388   And as long as we're wishing, it would be awfully nice if INSPECT could
389   also report on closures, telling about the values of the bound variables.
390
391 34:
392   as reported by Robert Strandh on the CMU CL mailing list 12 Jun 2000:
393     $ cat xx.lisp
394     (defconstant +a-constant+ (make-instance 'a-class))
395     (defconstant +another-constant+ (vector +a-constant+))
396     $ lisp
397     CMU Common Lisp release x86-linux 2.4.19  8 February 2000 build 456,
398     running on
399     bobby
400     Send bug reports and questions to your local CMU CL maintainer,
401     or to pvaneynd@debian.org
402     or to cmucl-help@cons.org. (prefered)
403     type (help) for help, (quit) to exit, and (demo) to see the demos
404     Loaded subsystems:
405       Python 1.0, target Intel x86
406       CLOS based on PCL version:  September 16 92 PCL (f)
407     * (defclass a-class () ())
408     #<STANDARD-CLASS A-CLASS {48027BD5}>
409     * (compile-file "xx.lisp")
410     Python version 1.0, VM version Intel x86 on 12 JUN 00 08:12:55 am.
411     Compiling:
412     /home/strandh/Research/Functional/Common-Lisp/CLIM/Development/McCLIM
413     /xx.lisp 12 JUN 00 07:47:14 am
414     Compiling Load Time Value of (PCL::GET-MAKE-INSTANCE-FUNCTION-SYMBOL
415     '(A-CLASS NIL NIL)):
416     Byte Compiling Top-Level Form:
417     Error in function C::DUMP-STRUCTURE:  Attempt to dump invalid
418     structure:
419       #<A-CLASS {4803A5B5}>
420     How did this happen?
421
422 35:
423   The compiler assumes that any time a function of declared FTYPE
424   doesn't signal an error, its arguments were of the declared type.
425   E.g. compiling and loading
426     (DECLAIM (OPTIMIZE (SAFETY 3)))
427     (DEFUN FACTORIAL (X) (GAMMA (1+ X)))
428     (DECLAIM (FTYPE (FUNCTION (UNSIGNED-BYTE) FACTORIAL)))
429     (DEFUN FOO (X)
430       (COND ((> (FACTORIAL X) 1.0E6)
431              (FORMAT T "too big~%"))
432             ((INTEGERP X)
433              (FORMAT T "exactly ~S~%" (FACTORIAL X)))
434             (T
435              (FORMAT T "approximately ~S~%" (FACTORIAL X)))))
436   then executing
437     (FOO 1.5)
438   will cause the INTEGERP case to be selected, giving bogus output a la
439     exactly 1.33..
440   This violates the "declarations are assertions" principle.
441   According to the ANSI spec, in the section "System Class FUNCTION",
442   this is a case of "lying to the compiler", but the lying is done
443   by the code which calls FACTORIAL with non-UNSIGNED-BYTE arguments,
444   not by the unexpectedly general definition of FACTORIAL. In any case,
445   "declarations are assertions" means that lying to the compiler should
446   cause an error to be signalled, and should not cause a bogus
447   result to be returned. Thus, the compiler should not assume
448   that arbitrary functions check their argument types. (It might
449   make sense to add another flag (CHECKED?) to DEFKNOWN to 
450   identify functions which *do* check their argument types.)
451
452 36:
453   As pointed out by Martin Cracauer on the CMU CL mailing list
454   13 Jun 2000, the :FILE-LENGTH operation for 
455   FD-STREAM-MISC-ROUTINE is broken for large files: it says
456   (THE INDEX SIZE) even though SIZE can be larger than INDEX.
457
458 37:
459   In SBCL 0.6.5 (and CMU CL 18b) compiling and loading
460         (in-package :cl-user)
461         (declaim (optimize (safety 3)
462                            (debug 3)
463                            (compilation-speed 2)
464                            (space 1)
465                            (speed 2)
466                            #+nil (sb-ext:inhibit-warnings 2)))
467         (declaim (ftype (function * (values)) emptyvalues))
468         (defun emptyvalues (&rest rest) (declare (ignore rest)) (values))
469         (defstruct foo x y)
470         (defgeneric assertoid ((x t)))
471         (defmethod assertoid ((x t)) "just a placeholder")
472         (defun bar (ht)
473           (declare (type hash-table ht))
474           (let ((res
475                  (block blockname
476                    (progn
477                     (prog1
478                         (emptyvalues)
479                       (assertoid (hash-table-count ht)))))))
480             (unless (typep res 'foo)
481               (locally
482                (common-lisp-user::bad-result-from-assertive-typed-fun
483                 'bar
484                 res)))))
485   then executing
486         (bar (make-hash-table))
487   causes the failure
488         Error in KERNEL::UNDEFINED-SYMBOL-ERROR-HANDLER:
489           the function C::%INSTANCE-TYPEP is undefined.
490   %INSTANCE-TYPEP is always supposed to be IR1-transformed away, but for
491   some reason -- the (VALUES) return value declaration? -- the optimizer is
492   confused and compiles a full call to %INSTANCE-TYPEP (which doesn't exist
493   as a function) instead.
494
495 37a:
496   The %INSTANCE-TYPEP problem in bug 37 comes up also when compiling
497   and loading
498         (IN-PACKAGE :CL-USER)
499         (LOCALLY
500           (DECLARE (OPTIMIZE (SAFETY 3) (SPEED 2) (SPACE 2)))
501           (DECLAIM (FTYPE (FUNCTION (&REST T) (VALUES)) EMPTYVALUES))
502           (DEFUN EMPTYVALUES (&REST REST)
503             (DECLARE (IGNORE REST))
504             (VALUES))
505           (DEFSTRUCT DUMMYSTRUCT X Y)
506           (DEFUN FROB-EMPTYVALUES (X)
507             (LET ((RES (EMPTYVALUES X X X)))
508               (UNLESS (TYPEP RES 'DUMMYSTRUCT)
509                 'EXPECTED-RETURN-VALUE))))
510         (ASSERT (EQ (FROB-EMPTYVALUES 11) 'EXPECTED-RETURN-VALUE))
511
512
513 38:
514   DEFMETHOD doesn't check the syntax of &REST argument lists properly,
515   accepting &REST even when it's not followed by an argument name:
516         (DEFMETHOD FOO ((X T) &REST) NIL)
517
518 39:
519   On the CMU CL mailing list 26 June 2000, Douglas Crosher wrote
520
521   Hannu Rummukainen wrote:
522   ...
523   > There's something weird going on with the compilation of the attached
524   > code.  Compiling and loading the file in a fresh lisp, then invoking
525   > (test-it) gives
526   Thanks for the bug report, nice to have this one fixed. It was a bug
527   in the x86 backend, the < VOP. A fix has been committed to the main
528   source, see the file compiler/x86/float.lisp.
529
530   Probably the same bug exists in SBCL.
531
532 40:
533   TYPEP treats the result of UPGRADED-ARRAY-ELEMENT-TYPE as gospel,
534   so that (TYPEP (MAKE-ARRAY 3) '(VECTOR SOMETHING-NOT-DEFINED-YET))
535   returns (VALUES T T). Probably it should be an error instead,
536   complaining that the type SOMETHING-NOT-DEFINED-YET is not defined.
537
538 41:
539   TYPEP of VALUES types is sometimes implemented very inefficiently, e.g. in 
540         (DEFTYPE INDEXOID () '(INTEGER 0 1000))
541         (DEFUN FOO (X)
542           (DECLARE (TYPE INDEXOID X))
543           (THE (VALUES INDEXOID)
544             (VALUES X)))
545   where the implementation of the type check in function FOO 
546   includes a full call to %TYPEP. There are also some fundamental problems
547   with the interpretation of VALUES types (inherited from CMU CL, and
548   from the ANSI CL standard) as discussed on the cmucl-imp@cons.org
549   mailing list, e.g. in Robert Maclachlan's post of 21 Jun 2000.
550
551 42:
552   The definitions of SIGCONTEXT-FLOAT-REGISTER and
553   %SET-SIGCONTEXT-FLOAT-REGISTER in x86-vm.lisp say they're not
554   supported on FreeBSD because the floating point state is not saved,
555   but at least as of FreeBSD 4.0, the floating point state *is* saved,
556   so they could be supported after all. Very likely 
557   SIGCONTEXT-FLOATING-POINT-MODES could now be supported, too.
558
559 43:
560   (as discussed by Douglas Crosher on the cmucl-imp mailing list ca. 
561   Aug. 10, 2000): CMUCL currently interprets 'member as '(member); same
562   issue with 'union, 'and, 'or etc. So even though according to the
563   ANSI spec, bare 'MEMBER, 'AND, and 'OR are not legal types, CMUCL
564   (and now SBCL) interpret them as legal types.
565
566 44:
567   ANSI specifies DEFINE-SYMBOL-MACRO, but it's not defined in SBCL.
568   CMU CL added it ca. Aug 13, 2000, after some discussion on the mailing
569   list, and it is probably possible to use substantially the same 
570   patches to add it to SBCL.
571
572 45:
573   a slew of floating-point-related errors reported by Peter Van Eynde
574   on July 25, 2000:
575         a: (SQRT -9.0) fails, because SB-KERNEL::COMPLEX-SQRT is undefined.
576            Similarly, COMPLEX-ASIN, COMPLEX-ACOS, COMPLEX-ACOSH, and others
577            aren't found.
578         b: SBCL's value for LEAST-POSITIVE-SHORT-FLOAT is bogus, and 
579            should probably be 1.4012985e-45. In SBCL,
580            (/ LEAST-POSITIVE-SHORT-FLOAT 2) returns a number smaller
581            than LEAST-POSITIVE-SHORT-FLOAT. Similar problems 
582            exist for LEAST-NEGATIVE-SHORT-FLOAT, LEAST-POSITIVE-LONG-FLOAT,
583            and LEAST-NEGATIVE-LONG-FLOAT.
584         c: Many expressions generate floating infinity:
585                 (/ 1 0.0)
586                 (/ 1 0.0d0)
587                 (EXPT 10.0 1000)
588                 (EXPT 10.0d0 1000)
589            PVE's regression tests want them to raise errors. SBCL
590            generates the infinities instead, which may or may not be
591            conforming behavior, but then blow it by being unable to
592            output the infinities, since support for infinities is generally
593            broken, and in particular SB-IMPL::OUTPUT-FLOAT-INFINITY is
594            undefined.
595         d: (in section12.erg) various forms a la 
596                 (FLOAT 1 DOUBLE-FLOAT-EPSILON)
597            don't give the right behavior.
598
599 46:
600   type safety errors reported by Peter Van Eynde July 25, 2000:
601         a: (COERCE (QUOTE (A B C)) (QUOTE (VECTOR * 4)))
602            => #(A B C)
603            In general lengths of array type specifications aren't
604            checked by COERCE, so it fails when the spec is
605            (VECTOR 4), (STRING 2), (SIMPLE-BIT-VECTOR 3), or whatever.
606         b: CONCATENATE has the same problem of not checking the length
607            of specified output array types. MAKE-SEQUENCE and MAP and
608            MERGE also have the same problem.
609         c: (COERCE 'AND 'FUNCTION) returns something related to
610            (MACRO-FUNCTION 'AND), but ANSI says it should raise an error.
611         d: ELT signals SIMPLE-ERROR if its index argument
612            isn't a valid index for its sequence argument, but should 
613            signal TYPE-ERROR instead.
614         e: FILE-LENGTH is supposed to signal a type error when its
615            argument is not a stream associated with a file, but doesn't.
616         f: (FLOAT-RADIX 2/3) should signal an error instead of 
617            returning 2.
618         g: (LOAD "*.lsp") should signal FILE-ERROR.
619         h: (MAKE-CONCATENATED-STREAM (MAKE-STRING-OUTPUT-STREAM))
620            should signal TYPE-ERROR.
621         i: MAKE-TWO-WAY-STREAM doesn't check that its arguments can
622            be used for input and output as needed. It should fail with
623            TYPE-ERROR when handed e.g. the results of
624            MAKE-STRING-INPUT-STREAM or MAKE-STRING-OUTPUT-STREAM in
625            the inappropriate positions, but doesn't.
626         j: (PARSE-NAMESTRING (COERCE (LIST #\f #\o #\o (CODE-CHAR 0) #\4 #\8)
627                             (QUOTE STRING)))
628            should probably signal an error instead of making a pathname with
629            a null byte in it.
630         k: READ-BYTE is supposed to signal TYPE-ERROR when its argument is 
631            not a binary input stream, but instead cheerfully reads from
632            character streams, e.g. (MAKE-STRING-INPUT-STREAM "abc").
633
634 47:
635   DEFCLASS bugs reported by Peter Van Eynde July 25, 2000:
636         a: (DEFCLASS FOO () (A B A)) should signal a PROGRAM-ERROR, and
637            doesn't.
638         b: (DEFCLASS FOO () (A B A) (:DEFAULT-INITARGS X A X B)) should
639            signal a PROGRAM-ERROR, and doesn't.
640         c: (DEFCLASS FOO07 NIL ((A :ALLOCATION :CLASS :ALLOCATION :CLASS))),
641            and other DEFCLASS forms with duplicate specifications in their
642            slots, should signal a PROGRAM-ERROR, and doesn't.
643         d: (DEFGENERIC IF (X)) should signal a PROGRAM-ERROR, but instead
644            causes a COMPILER-ERROR.
645
646 48:
647   SYMBOL-MACROLET bugs reported by Peter Van Eynde July 25, 2000:
648         a: (SYMBOL-MACROLET ((T TRUE)) ..) should probably signal
649            PROGRAM-ERROR, but SBCL accepts it instead.
650         b: SYMBOL-MACROLET should refuse to bind something which is
651            declared as a global variable, signalling PROGRAM-ERROR.
652         c: SYMBOL-MACROLET should signal PROGRAM-ERROR if something
653            it binds is declared SPECIAL inside.
654
655 49:
656   LOOP bugs reported by Peter Van Eynde July 25, 2000:
657         a: (LOOP WITH (A B) DO (PRINT 1)) is a syntax error according to
658            the definition of WITH clauses given in the ANSI spec, but
659            compiles and runs happily in SBCL.
660         b: a messy one involving package iteration:
661 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<))))
662 Should be: (("blah" "blah2") ("blah2"))
663 SBCL: (("blah") ("blah2"))
664         * (LET ((X 1)) (LOOP FOR I BY (INCF X) FROM X TO 10 COLLECT I))
665           doesn't work -- SBCL's LOOP says BY isn't allowed in a FOR clause.
666
667 50:
668   type system errors reported by Peter Van Eynde July 25, 2000:
669         a: (SUBTYPEP 'BIGNUM 'INTEGER) => NIL, NIL
670            but should be (VALUES T T) instead.
671         b: (SUBTYPEP 'EXTENDED-CHAR 'CHARACTER) => NIL, NIL
672            but should be (VALUES T T) instead.
673         c: (SUBTYPEP '(INTEGER (0) (0)) 'NIL) dies with nested errors.
674         d: In general, the system doesn't like '(INTEGER (0) (0)) -- it
675            blows up at the level of SPECIFIER-TYPE with
676            "Lower bound (0) is greater than upper bound (0)." Probably
677            SPECIFIER-TYPE should return NIL instead.
678         e: (TYPEP 0 '(COMPLEX (EQL 0)) fails with
679            "Component type for Complex is not numeric: (EQL 0)."
680            This might be easy to fix; the type system already knows
681            that (SUBTYPEP '(EQL 0) 'NUMBER) is true.
682         f: The type system doesn't know about the condition system,
683            so that e.g. (TYPEP 'SIMPLE-ERROR 'ERROR)=>NIL.
684         g: The type system isn't all that smart about relationships
685            between hairy types, as shown in the type.erg test results,
686            e.g. (SUBTYPEP 'CONS '(NOT ATOM)) => NIL, NIL.
687
688 51:
689   miscellaneous errors reported by Peter Van Eynde July 25, 2000:
690         a: (PROGN
691             (DEFGENERIC FOO02 (X))
692             (DEFMETHOD FOO02 ((X NUMBER)) T)
693             (LET ((M (FIND-METHOD (FUNCTION FOO02)
694                                   NIL
695                                   (LIST (FIND-CLASS (QUOTE NUMBER))))))
696               (REMOVE-METHOD (FUNCTION FOO02) M)
697               (DEFGENERIC FOO03 (X))
698               (ADD-METHOD (FUNCTION FOO03) M)))
699            should give an error, but SBCL allows it.
700         b: READ should probably return READER-ERROR, not the bare 
701            arithmetic error, when input a la "1/0" or "1e1000" causes
702            an arithmetic error.
703
704 52:
705   It has been reported (e.g. by Peter Van Eynde) that there are 
706   several metaobject protocol "errors". (In order to fix them, we might
707   need to document exactly what metaobject protocol specification
708   we're following -- the current code is just inherited from PCL.)
709
710 53:
711   another error from Peter Van Eynde 5 September 2000:
712   (FORMAT NIL "~F" "FOO") should work, but instead reports an error.
713   PVE submitted a patch to deal with this bug, but it exposes other
714   comparably serious bugs, so I didn't apply it. It looks as though
715   the FORMAT code needs a fair amount of rewriting in order to comply
716   with the various details of the ANSI spec.
717
718 54:
719   The implementation of #'+ returns its single argument without
720   type checking, e.g. (+ "illegal") => "illegal".
721
722 55:
723   In sbcl-0.6.7, there is no doc string for CL:PUSH, probably 
724   because it's defined with the DEFMACRO-MUNDANELY macro and something
725   is wrong with doc string setting in that macro.
726
727 56:
728   Attempting to use COMPILE on something defined by DEFMACRO fails:
729         (DEFMACRO FOO (X) (CONS X X))
730         (COMPILE 'FOO)
731 Error in function C::GET-LAMBDA-TO-COMPILE:
732    #<Closure Over Function "DEFUN (SETF MACRO-FUNCTION)" {480E21B1}> was defined in a non-null environment.
733
734 58:
735   (SUBTYPEP '(AND ZILCH INTEGER) 'ZILCH)
736   => NIL, NIL
737
738 59:
739   CL:*DEFAULT-PATHNAME-DEFAULTS* doesn't behave as ANSI suggests (reflecting
740   current working directory). And there's no supported way to update
741   or query the current working directory (a la Unix "chdir" and "pwd"),
742   which is functionality that ILISP needs (and currently gets with low-level
743   hacks).
744
745 60:
746   The debugger LIST-LOCATIONS command doesn't work properly.
747
748 61:
749   Compiling and loading
750     (DEFUN FAIL (X) (THROW 'FAIL-TAG X))
751     (FAIL 12)
752   then requesting a BACKTRACE at the debugger prompt gives no information
753   about where in the user program the problem occurred.
754
755 62:
756   The compiler is supposed to do type inference well enough that 
757   the declaration in
758     (TYPECASE X
759       ((SIMPLE-ARRAY SINGLE-FLOAT)
760        (LOCALLY
761          (DECLARE (TYPE (SIMPLE-ARRAY SINGLE-FLOAT) X))
762          ..))
763       ..)
764   is redundant. However, as reported by Juan Jose Garcia Ripoll for
765   CMU CL, it sometimes doesn't. Adding declarations is a pretty good
766   workaround for the problem for now, but can't be done by the TYPECASE
767   macros themselves, since it's too hard for the macro to detect
768   assignments to the variable within the clause. 
769     Note: The compiler *is* smart enough to do the type inference in
770   many cases. This case, derived from a couple of MACROEXPAND-1
771   calls on Ripoll's original test case,
772     (DEFUN NEGMAT (A)
773       (DECLARE (OPTIMIZE SPEED (SAFETY 0)))
774       (COND ((TYPEP A '(SIMPLE-ARRAY SINGLE-FLOAT)) NIL
775              (LET ((LENGTH (ARRAY-TOTAL-SIZE A)))
776                (LET ((I 0) (G2554 LENGTH))
777                  (DECLARE (TYPE REAL G2554) (TYPE REAL I))
778                  (TAGBODY
779                   SB-LOOP::NEXT-LOOP
780                   (WHEN (>= I G2554) (GO SB-LOOP::END-LOOP))
781                   (SETF (ROW-MAJOR-AREF A I) (- (ROW-MAJOR-AREF A I)))
782                   (GO SB-LOOP::NEXT-LOOP)
783                   SB-LOOP::END-LOOP))))))
784   demonstrates the problem; but the problem goes away if the TAGBODY
785   and GO forms are removed (leaving the SETF in ordinary, non-looping
786   code), or if the TAGBODY and GO forms are retained, but the 
787   assigned value becomes 0.0 instead of (- (ROW-MAJOR-AREF A I)).
788
789 63:
790   Paul Werkowski wrote on cmucl-imp@cons.org 2000-11-15
791     I am looking into this problem that showed up on the cmucl-help
792     list. It seems to me that the "implementation specific environment
793     hacking functions" found in pcl/walker.lisp are completely messed
794     up. The good thing is that they appear to be barely used within
795     PCL and the munged environment object is passed to cmucl only
796     in calls to macroexpand-1, which is probably why this case fails.
797   SBCL uses essentially the same code, so if the environment hacking
798   is screwed up, it affects us too.
799
800 64:
801   Using the pretty-printer from the command prompt gives funny
802   results, apparently because the pretty-printer doesn't know
803   about user's command input, including the user's carriage return
804   that the user, and therefore the pretty-printer thinks that
805   the new output block should start indented 2 or more characters
806   rightward of the correct location.
807
808 65:
809   As reported by Carl Witty on submit@bugs.debian.org 1999-05-08,
810   compiling this file
811 (in-package "CL-USER")
812 (defun equal-terms (termx termy)
813   (labels
814     ((alpha-equal-bound-term-lists (listx listy)
815        (or (and (null listx) (null listy))
816            (and listx listy
817                 (let ((bindings-x (bindings-of-bound-term (car listx)))
818                       (bindings-y (bindings-of-bound-term (car listy))))
819                   (if (and (null bindings-x) (null bindings-y))
820                       (alpha-equal-terms (term-of-bound-term (car listx))
821                                          (term-of-bound-term (car listy)))
822                       (and (= (length bindings-x) (length bindings-y))
823                            (prog2
824                                (enter-binding-pairs (bindings-of-bound-term (car listx))
825                                                     (bindings-of-bound-term (car listy)))
826                                (alpha-equal-terms (term-of-bound-term (car listx))
827                                                   (term-of-bound-term (car listy)))
828                              (exit-binding-pairs (bindings-of-bound-term (car listx))
829                                                  (bindings-of-bound-term (car listy)))))))
830                 (alpha-equal-bound-term-lists (cdr listx) (cdr listy)))))
831
832      (alpha-equal-terms (termx termy)
833        (if (and (variable-p termx)
834                 (variable-p termy))
835            (equal-bindings (id-of-variable-term termx)
836                            (id-of-variable-term termy))
837            (and (equal-operators-p (operator-of-term termx) (operator-of-term termy))
838                 (alpha-equal-bound-term-lists (bound-terms-of-term termx)
839                                               (bound-terms-of-term termy))))))
840
841     (or (eq termx termy)
842         (and termx termy
843              (with-variable-invocation (alpha-equal-terms termx termy))))))
844   causes an assertion failure
845     The assertion (EQ (C::LAMBDA-TAIL-SET C::CALLER)
846                       (C::LAMBDA-TAIL-SET (C::LAMBDA-HOME C::CALLEE))) failed.
847
848   Bob Rogers reports (1999-07-28 on cmucl-imp@cons.org) a smaller test
849   case with the same problem:
850 (defun parse-fssp-alignment ()
851   ;; Given an FSSP alignment file named by the argument . . .
852   (labels ((get-fssp-char ()
853              (get-fssp-char))
854            (read-fssp-char ()
855              (get-fssp-char)))
856     ;; Stub body, enough to tickle the bug.
857     (list (read-fssp-char)
858           (read-fssp-char))))
859
860 66:
861   ANSI specifies that the RESULT-TYPE argument of CONCATENATE must be
862   a subtype of SEQUENCE, but CONCATENATE doesn't check this properly:
863     (CONCATENATE 'SIMPLE-ARRAY #(1 2) '(3)) => #(1 2 3)
864   This also leads to funny behavior when derived type specifiers
865   are used, as originally reported by Milan Zamazal for CMU CL (on the
866   Debian bugs mailing list (?) 2000-02-27), then reported by Martin
867   Atzmueller for SBCL (2000-10-01 on sbcl-devel@lists.sourceforge.net):
868     (DEFTYPE FOO () 'SIMPLE-ARRAY)
869     (CONCATENATE 'FOO #(1 2) '(3)) 
870       => #<ARRAY-TYPE SIMPLE-ARRAY> is a bad type specifier for
871            sequence functions.
872   The derived type specifier FOO should act the same way as the 
873   built-in type SIMPLE-ARRAY here, but it doesn't. That problem
874   doesn't seem to exist for sequence types:
875     (DEFTYPE BAR () 'SIMPLE-VECTOR)
876     (CONCATENATE 'BAR #(1 2) '(3)) => #(1 2 3)
877
878
879 67:
880   As reported by Winton Davies on a CMU CL mailing list 2000-01-10,
881   and reported for SBCL by Martin Atzmueller 2000-10-20: (TRACE GETHASH)
882   crashes SBCL. In general tracing anything which is used in the 
883   implementation of TRACE is likely to have the same problem.
884
885 KNOWN BUGS RELATED TO THE IR1 INTERPRETER
886
887 (Note: At some point, the pure interpreter (actually a semi-pure
888 interpreter aka "the IR1 interpreter") will probably go away, replaced
889 by constructs like
890   (DEFUN EVAL (X) (FUNCALL (COMPILE NIL (LAMBDA ..)))))
891 and at that time these bugs should either go away automatically or
892 become more tractable to fix. Until then, they'll probably remain,
893 since some of them aren't considered urgent, and the rest are too hard
894 to fix as long as so many special cases remain. After the IR1
895 interpreter goes away is also the preferred time to start
896 systematically exterminating cases where debugging functionality
897 (backtrace, breakpoint, etc.) breaks down, since getting rid of the
898 IR1 interpreter will reduce the number of special cases we need to
899 support.)
900
901 IR1-1:
902   The FUNCTION special operator doesn't check properly whether its
903   argument is a function name. E.g. (FUNCTION (X Y)) returns a value
904   instead of failing with an error. (Later attempting to funcall the
905   value does cause an error.) 
906
907 IR1-2:
908   COMPILED-FUNCTION-P bogusly reports T for interpreted functions:
909         * (DEFUN FOO (X) (- 12 X))
910         FOO
911         * (COMPILED-FUNCTION-P #'FOO)
912         T
913
914 IR1-3:
915   Executing 
916     (DEFVAR *SUPPRESS-P* T)
917     (EVAL '(UNLESS *SUPPRESS-P*
918              (EVAL-WHEN (:COMPILE-TOPLEVEL :LOAD-TOPLEVEL :EXECUTE)
919                (FORMAT T "surprise!"))))
920   prints "surprise!". Probably the entire EVAL-WHEN mechanism ought to be
921   rewritten from scratch to conform to the ANSI definition, abandoning
922   the *ALREADY-EVALED-THIS* hack which is used in sbcl-0.6.8.9 (and
923   in the original CMU CL source, too). This should be easier to do --
924   though still nontrivial -- once the various IR1 interpreter special
925   cases are gone.
926
927 IR1-3a:
928   EVAL-WHEN's idea of what's a toplevel form is even more screwed up 
929   than the example in IR1-3 would suggest, since COMPILE-FILE and
930   COMPILE both print both "right now!" messages when compiling the
931   following code,
932     (LAMBDA (X)
933       (COND (X
934              (EVAL-WHEN (:COMPILE-TOPLEVEL :LOAD-TOPLEVEL :EXECUTE)
935                (PRINT "yes! right now!"))
936              "yes!")
937             (T
938              (EVAL-WHEN (:COMPILE-TOPLEVEL :LOAD-TOPLEVEL :EXECUTE)
939                (PRINT "no! right now!"))
940              "no!")))
941   and while EVAL doesn't print the "right now!" messages, the first
942   FUNCALL on the value returned by EVAL causes both of them to be printed.
943
944 IR1-4:
945   The system accepts DECLAIM in most places where DECLARE would be 
946   accepted, without even issuing a warning. ANSI allows this, but since
947   it's fairly easy to mistype DECLAIM instead of DECLARE, and the
948   meaning is rather different, and it's unlikely that the user
949   has a good reason for doing DECLAIM not at top level, it would be 
950   good to issue a STYLE-WARNING when this happens. A possible
951   fix would be to issue STYLE-WARNINGs for DECLAIMs not at top level,
952   or perhaps to issue STYLE-WARNINGs for any EVAL-WHEN not at top level.
953   [This is considered an IR1-interpreter-related bug because until
954   EVAL-WHEN is rewritten, which won't happen until after the IR1
955   interpreter is gone, the system's notion of what's a top-level form
956   and what's not will remain too confused to fix this problem.]