0.7.4.1:
[sbcl.git] / BUGS
diff --git a/BUGS b/BUGS
index c3fef6a..ad7b82a 100644 (file)
--- a/BUGS
+++ b/BUGS
@@ -142,37 +142,12 @@ WORKAROUND:
   DTC's recommended workaround from the mailing list 3 Mar 2000:
        (setf (pcl::find-class 'ccc1) (pcl::find-class 'ccc))
 
-22:
-  The ANSI spec, in section "22.3.5.2 Tilde Less-Than-Sign: Logical Block",
-  says that an error is signalled if ~W, ~_, ~<...~:>, ~I, or ~:T is used
-  inside "~<..~>" (without the colon modifier on the closing syntax).
-  However, SBCL doesn't do this:
-       * (FORMAT T "~<munge~wegnum~>" 12)
-       munge12egnum
-       NIL
-
 27:
   Sometimes (SB-EXT:QUIT) fails with 
        Argh! maximum interrupt nesting depth (4096) exceeded, exiting
        Process inferior-lisp exited abnormally with code 1
   I haven't noticed a repeatable case of this yet.
 
-31:
-  In some cases the compiler believes type declarations on array
-  elements without checking them, e.g.
-       (DECLAIM (OPTIMIZE (SAFETY 3) (SPEED 1) (SPACE 1)))
-       (DEFSTRUCT FOO A B)
-       (DEFUN BAR (X)
-         (DECLARE (TYPE (SIMPLE-ARRAY CONS 1) X))
-         (WHEN (CONSP (AREF X 0))
-           (PRINT (AREF X 0))))
-       (BAR (VECTOR (MAKE-FOO :A 11 :B 12)))
-  prints
-       #S(FOO :A 11 :B 12) 
-  in SBCL 0.6.5 (and also in CMU CL 18b). This does not happen for
-  all cases, e.g. the type assumption *is* checked if the array
-  elements are declared to be of some structure type instead of CONS.
-
 32:
   The printer doesn't report closures very well. This is true in 
   CMU CL 18b as well:
@@ -285,9 +260,6 @@ WORKAROUND:
           MERGE also have the same problem.
        c: (COERCE 'AND 'FUNCTION) returns something related to
           (MACRO-FUNCTION 'AND), but ANSI says it should raise an error.
-       f: (FLOAT-RADIX 2/3) should signal an error instead of 
-          returning 2.
-       g: (LOAD "*.lsp") should signal FILE-ERROR.
        h: (MAKE-CONCATENATED-STREAM (MAKE-STRING-OUTPUT-STREAM))
           should signal TYPE-ERROR.
        i: MAKE-TWO-WAY-STREAM doesn't check that its arguments can
@@ -295,10 +267,6 @@ WORKAROUND:
           TYPE-ERROR when handed e.g. the results of
           MAKE-STRING-INPUT-STREAM or MAKE-STRING-OUTPUT-STREAM in
           the inappropriate positions, but doesn't.
-       j: (PARSE-NAMESTRING (COERCE (LIST #\f #\o #\o (CODE-CHAR 0) #\4 #\8)
-                           (QUOTE STRING)))
-          should probably signal an error instead of making a pathname with
-          a null byte in it.
        k: READ-BYTE is supposed to signal TYPE-ERROR when its argument is 
           not a binary input stream, but instead cheerfully reads from
           character streams, e.g. (MAKE-STRING-INPUT-STREAM "abc").
@@ -594,18 +562,6 @@ WORKAROUND:
   bootstrap on a system which uses a different value of CHAR-CODE-LIMIT
   than SBCL does.
 
-91:
-  (subtypep '(or (integer -1 1)
-                 unsigned-byte)
-            '(or (rational -1 7)
-                 unsigned-byte
-                 (integer -1 1))) => NIL,T
-  An analogous problem with SINGLE-FLOAT and REAL types was fixed in 
-  sbcl-0.6.11.22, but some peculiarites of the RATIO type make it 
-  awkward to generalize the fix to INTEGER and RATIONAL. It's not 
-  clear what's the best fix. (See the "bug in type handling" discussion
-  on cmucl-imp ca. 2001-03-22 and ca. 2001-02-12.)
-
 94a: 
   Inconsistencies between derived and declared VALUES return types for
   DEFUN aren't checked very well. E.g. the logic which successfully
@@ -695,7 +651,7 @@ WORKAROUND:
   but SBCL doesn't do this. (Also as reported by AL in the same
   message, SBCL depended on this nonconforming behavior to build
   itself, because of the way that **CURRENT-SEGMENT** was implemented.
-  As of sbcl-0.6.12.x, this dependence on the nonconforming behavior
+  As of sbcl-0.7.3.x, this dependence on the nonconforming behavior
   has been fixed, but the nonconforming behavior remains.)
 
 104:
@@ -940,9 +896,6 @@ WORKAROUND:
    Evidently Python thinks of the lambda as a code transformation so
    much that it forgets that it's also an object.
 
-126:
-  (fixed in 0.pre7.41)
-
 127:
   The DEFSTRUCT section of the ANSI spec, in the :CONC-NAME section,
   specifies a precedence rule for name collisions between slot accessors of
@@ -1046,36 +999,6 @@ WORKAROUND:
   still some functions named "hairy arg processor" and
   "SB-INT:&MORE processor".
 
-140:
-  (reported by Alexey Dejneka sbcl-devel 2002-01-03)
-
-  SUBTYPEP does not work well with redefined classes:
-  ---
-  * (defclass a () ())
-  #<STANDARD-CLASS A>
-  * (defclass b () ())
-  #<STANDARD-CLASS B>
-  * (subtypep 'b 'a)
-  NIL
-  T
-  * (defclass b (a) ())
-  #<STANDARD-CLASS B>
-  * (subtypep 'b 'a)
-  T
-  T
-  * (defclass b () ())
-  #<STANDARD-CLASS B>
-   
-  ;;; And now...
-  * (subtypep 'b 'a)
-  T
-  T
-
-  This is probably due to underzealous clearing of the type caches; a
-  brute-force solution in that case would be to make a defclass expand
-  into something that included a call to SB-KERNEL::CLEAR-TYPE-CACHES,
-  but there may be a better solution.
-
 141: 
   Pretty-printing nested backquotes doesn't work right, as 
   reported by Alexey Dejneka sbcl-devel 2002-01-13:
@@ -1146,54 +1069,6 @@ WORKAROUND:
   It should be possible to be much more specific (overflow, division
   by zero, etc.) and of course the "How can this be?" should be fixable.
 
-147:
-  (reported by Alexey Dejneka sbcl-devel 2002-01-28)
-  Compiling a file containing
-    (deftype digit () '(member #\1))
-    (defun parse-num (string ind)
-      (flet ((digs ()
-               (let (old-index)
-                 (if (and (< ind ind)
-                          (typep (char string ind) 'digit))
-                     nil))))))
-  in sbcl-0.7.1 causes the compiler to fail with
-    internal error, failed AVER: "(= (LENGTH (BLOCK-SUCC CALL-BLOCK)) 1)" 
-  This problem seems to have been introduced by the sbcl-0.pre7.* compiler
-  changes, since 0.pre7.73 and 0.6.13 don't suffer from it. A related
-  test case is
-    (defun parse-num (index)
-      (let (num x)
-        (flet ((digs ()
-                 (setq num index))
-               (z ()
-                 (let ()
-                   (setq x nil))))
-          (when (and (digs) (digs)) x))))
-  In sbcl-0.7.1, this second test case failed with the same
-    internal error, failed AVER: "(= (LENGTH (BLOCK-SUCC CALL-BLOCK)) 1)" 
-  After the APD patches in sbcl-0.7.1.2 (new consistency check in
-  TARGET-IF-DESIRABLE, plus a fix in meta-vmdef.lisp to keep the
-  new consistency check from failing routinely) this second test case
-  failed in FIND-IN-PHYSENV instead. Fixes in sbcl-0.7.1.3 (not
-  closing over unreferenced variables) made this second test case
-  compile without error, but the original test case still fails.
-  Another way to get rid of the DEFTYPE without changing the symptom
-  of the bug is
-    (defvar *ch*)
-    (defun parse-num (string ind)
-      (flet ((digs ()
-               (let ()
-                 (if (and (< ind ind)
-                         (sb-int:memq *ch* '(#\1)))
-                     nil))))))
-  In sbcl-0.7.1.3, this fails with
-    internal error, failed AVER: "(= (LENGTH (BLOCK-SUCC CALL-BLOCK)) 1)" 
-  The problem occurs while the inline expansion of MEMQ,
-  #<LAMBDA :%DEBUG-NAME "varargs entry point for SB-C::.ANONYMOUS.">
-  is being LET-converted after having its second REF deleted, leaving
-  it with only one entry in LEAF-REFS.
-  
 148:
   In sbcl-0.7.1.3 on x86, COMPILE-FILE on the file
     (in-package :cl-user)
@@ -1251,14 +1126,133 @@ WORKAROUND:
   but it has happened in more complicated cases (which I haven't
   figured out how to reproduce).
 
-155:
-  Executing 
-    (defclass standard-gadget (basic-gadget) ())
-    (defclass basic-gadget () ())
-  gives an error:
-    The slot SB-PCL::DIRECT-SUPERCLASSES is unbound in the
-    object #<SB-PCL::STANDARD-CLASS "unbound">.
-  (reported by Brian Spilsbury sbcl-devel 2002-04-09)
+156:
+  FUNCTION-LAMBDA-EXPRESSION doesn't work right in 0.7.0 or 0.7.2.9:
+    * (function-lambda-expression #'(lambda (x) x))
+    debugger invoked on condition of type TYPE-ERROR:
+      The value NIL is not of type SB-C::DEBUG-SOURCE
+  (reported by Alexey Dejneka sbcl-devel 2002-04-12)
+
+157:
+  Functions SUBTYPEP, TYPEP, UPGRADED-ARRAY-ELEMENT-TYPE, and 
+  UPGRADED-COMPLEX-PART-TYPE should have an optional environment argument.
+  (reported by Alexey Dejneka sbcl-devel 2002-04-12)
+
+162:
+  (reported by Robert E. Brown 2002-04-16) 
+  When a function is called with too few arguments, causing the
+  debugger to be entered, the uninitialized slots in the bad call frame 
+  seem to cause GCish problems, being interpreted as tagged data even
+  though they're not. In particular, executing ROOM in the
+  debugger at that point causes AVER failures:
+    * (machine-type)
+    "X86"
+    * (lisp-implementation-version)
+    "0.7.2.12"
+    * (typep 10)
+    ...
+    0] (room)
+    ...
+    failed AVER: "(SAP= CURRENT END)"
+  (Christophe Rhodes reports that this doesn't occur on the SPARC, which
+  isn't too surprising since there are many differences in stack
+  implementation and GC conservatism between the X86 and other ports.)
+
+165:
+  Array types with element-types of some unknown type are falsely being
+  assumed to be of type (ARRAY T) by the compiler in some cases. The
+  following code demonstrates the problem:
+
+  (defun foo (x)
+    (declare (type (vector bar) x))
+    (aref x 1))
+  (deftype bar () 'single-float)
+  (foo (make-array 3 :element-type 'bar))
+    -> TYPE-ERROR "The value #(0.0 0.0 0.0) is not of type (VECTOR BAR)."
+  (typep (make-array 3 :element-type 'bar) '(vector bar))
+    -> T
+
+  The easy solution is to make the functions which depend on knowing
+  the upgraded-array-element-type (in compiler/array-tran and
+  compiler/generic/vm-tran as of sbcl-0.7.3.x) be slightly smarter about
+  unknown types; an alternative is to have the
+  specialized-element-type slot in the ARRAY-TYPE structure be
+  *WILD-TYPE* for UNKNOWN-TYPE element types.
+
+166:
+  Compiling 
+    (in-package :cl-user)
+    (defstruct uustk)
+    (defmethod permanentize ((uustk uustk))
+      (flet ((frob (hash-table test-for-deletion)
+               )
+             (obj-entry.stale? (oe)
+               (destructuring-bind (key . datum) oe
+                 (declare (type simple-vector key))
+                 (deny0 (void? datum))
+                 (some #'stale? key))))
+        (declare (inline frob obj-entry.stale?))
+        (frob (uustk.args-hash->obj-alist uustk)
+              #'obj-entry.stale?)
+        (frob (uustk.hash->memoized-objs-list uustk)
+              #'objs.stale?))
+      (call-next-method))
+  in sbcl-0.7.3.11 causes an assertion failure, 
+    failed AVER:
+      "(NOT
+(AND (NULL (BLOCK-SUCC B))
+      (NOT (BLOCK-DELETE-P B))
+      (NOT (EQ B (COMPONENT-HEAD #)))))"
+
+167:
+  In sbcl-0.7.3.11, compiling the (illegal) code 
+    (in-package :cl-user)
+    (defmethod prove ((uustk uustk))
+      (zap ((frob () nil))
+        (frob)))
+  gives the (not terribly clear) error message
+    ; caught ERROR:
+    ;   (during macroexpansion of (DEFMETHOD PROVE ...))
+    ; can't get template for (FROB NIL NIL)
+  The problem seems to be that the code walker used by the DEFMETHOD
+  macro is unhappy with the illegal syntax in the method body, and
+  is giving an unclear error message.
+
+168:
+  (reported by Dan Barlow on sbcl-devel 2002-05-10)
+  In sbcl-0.7.3.12, doing
+    (defstruct foo bar baz)
+    (compile nil (lambda (x) (or x (foo-baz x))))
+  gives an error
+    debugger invoked on condition of type SB-INT:BUG:
+       full call to SB-KERNEL:%INSTANCE-REF
+    This is probably a bug in SBCL itself. [...]
+  Since this is a reasonable user error, it shouldn't be reported as 
+  an SBCL bug. 
+
+169:
+  (reported by Alexey Dejneka on sbcl-devel 2002-05-12)
+  * (defun test (n)
+      (let ((*x* n))
+        (declare (special *x*))
+        (getx)))
+  ; in: LAMBDA NIL
+  ;     (LET ((*X* N))
+  ;     (DECLARE (SPECIAL *X*))
+  ;     (GETX))
+  ;
+  ; caught STYLE-WARNING:
+  ;   using the lexical binding of the symbol *X*, not the
+  ; dynamic binding, even though the symbol name follows the usual naming
+  ; convention (names like *FOO*) for special variables
+  ; compilation unit finished
+  ;   caught 1 STYLE-WARNING condition
+  But the code works as it should. Checked in 0.6.12.43 and later.
+
+171:
+  (reported by Pierre Mai while investigating bug 47):
+    (DEFCLASS FOO () ((A :SILLY T))) 
+  signals a SIMPLE-ERROR, not a PROGRAM-ERROR.
 
 DEFUNCT CATEGORIES OF BUGS
   IR1-#: