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