0.7.10.10:
[sbcl.git] / BUGS
diff --git a/BUGS b/BUGS
index 36986f9..3c403d6 100644 (file)
--- a/BUGS
+++ b/BUGS
@@ -283,10 +283,6 @@ WORKAROUND:
   need to document exactly what metaobject protocol specification
   we're following -- the current code is just inherited from PCL.)
 
-54:
-  The implementation of #'+ returns its single argument without
-  type checking, e.g. (+ "illegal") => "illegal".
-
 60:
   The debugger LIST-LOCATIONS command doesn't work properly.
 
@@ -356,9 +352,6 @@ WORKAROUND:
   crashes SBCL. In general tracing anything which is used in the 
   implementation of TRACE is likely to have the same problem.
 
-72:
-  (DECLAIM (OPTIMIZE ..)) doesn't work properly inside LOCALLY forms.
-
 75:
   As reported by Martin Atzmueller on sbcl-devel 26 Dec 2000,
   ANSI says that WITH-OUTPUT-TO-STRING should have a keyword
@@ -385,6 +378,9 @@ WORKAROUND:
   LOAD-FOREIGN, and (2) hunt for any other code which uses temporary
   files and make it share the same new safe logic.
 
+  (partially alleviated in sbcl-0.7.9.32 by a fix by Matthew Danish to
+   make the temporary filename less easily guessable)
+
 82: 
   Functions are assigned names based on the context in which they're
   defined. This is less than ideal for the functions which are
@@ -499,18 +495,6 @@ WORKAROUND:
   the first time around, until regression tests are written I'm not 
   comfortable merging the patches in the CVS version of SBCL.
 
-104:
-  (DESCRIBE 'SB-ALIEN:DEF-ALIEN-TYPE) reports the macro argument list
-  incorrectly:
-       DEF-ALIEN-TYPE is
-         an external symbol
-         in #<PACKAGE "SB-ALIEN">.
-       Macro-function: #<FUNCTION "DEF!MACRO DEF-ALIEN-TYPE" {19F4A39}>
-         Macro arguments:  (#:whole-470 #:environment-471)
-         On Sat, May 26, 2001 09:45:57 AM CDT it was compiled from:
-         /usr/stuff/sbcl/src/code/host-alieneval.lisp
-           Created: Monday, March 12, 2001 07:47:43 AM CST
-
 108:
   (TIME (ROOM T)) reports more than 200 Mbytes consed even for
   a clean, just-started SBCL system. And it seems to be right:
@@ -518,22 +502,6 @@ WORKAROUND:
   time trying to GC afterwards. Surely there's some more economical
   way to implement (ROOM T).
 
-115:
-  reported by Martin Atzmueller 2001-06-25; originally from CMU CL bugs
-  collection:
-    (in-package :cl-user)
-    ;;; The following invokes a compiler error.
-    (declaim (optimize (speed 2) (debug 3)))
-    (defun tst ()
-      (flet ((m1 ()
-               (unwind-protect nil)))
-        (if (catch nil)
-          (m1)
-          (m1))))
-  The error message in sbcl-0.6.12.42 is
-    internal error, failed AVER:
-      "(COMMON-LISP:EQ (SB!C::TN-ENVIRONMENT SB!C:TN) SB!C::TN-ENV)"
-
 117:
   When the compiler inline expands functions, it may be that different
   kinds of return values are generated from different code branches.
@@ -584,26 +552,6 @@ WORKAROUND:
    is attached to FOO in 120a above, and used to optimize code which
    calls FOO. 
 
-122:
-   There was some sort of screwup in handling of
-   (IF (NOT (IGNORE-ERRORS ..))). E.g.
-       (defun foo1i ()
-         (if (not (ignore-errors
-                    (make-pathname :host "foo"
-                                    :directory "!bla"
-                                    :name "bar")))
-             (print "ok")
-             (error "notunlessnot")))
-   The (NOT (IGNORE-ERRORS ..)) form evaluates to T, so this should be
-   printing "ok", but instead it's going to the ERROR. This problem
-   seems to've been introduced by MNA's HANDLER-CASE patch (sbcl-devel
-   2001-07-17) and as a workaround (put in sbcl-0.pre7.14.flaky4.12)
-   I reverted back to the old weird HANDLER-CASE code. However, I
-   think the problem looks like a compiler bug in handling RETURN-FROM,
-   so I left the MNA-patched code in HANDLER-CASE (suppressed with
-   #+NIL) and I'd like to go back to see whether this really is
-   a compiler bug before I delete this BUGS entry.
-
 124:
    As of version 0.pre7.14, SBCL's implementation of MACROLET makes
    the entire lexical environment at the point of MACROLET available
@@ -668,12 +616,6 @@ WORKAROUND:
    Evidently Python thinks of the lambda as a code transformation so
    much that it forgets that it's also an object.
 
-127:
-  The DEFSTRUCT section of the ANSI spec, in the :CONC-NAME section,
-  specifies a precedence rule for name collisions between slot accessors of
-  structure classes related by inheritance. As of 0.7.0, SBCL still 
-  doesn't follow it.
-
 135:
   Ideally, uninterning a symbol would allow it, and its associated
   FDEFINITION and PROCLAIM data, to be reclaimed by the GC. However,
@@ -684,45 +626,6 @@ WORKAROUND:
   forever, even when it is uninterned and all other references to it
   are lost.
 
-136:
-  (reported by Arnaud Rouanet on cmucl-imp 2001-12-18)
-    (defmethod foo ((x integer))
-      x)
-    (defmethod foo :around ((x integer))
-      (let ((x (1+ x)))
-        (call-next-method)))
-  Now (FOO 3) should return 3, but instead it returns 4.
-
-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 bug was fixed in sbcl-0.7.4.1 by invalidating the PCL wrapper
-  class upon redefinition. Unfortunately, doing so causes bug #176 to
-  appear.  Pending further investigation, one or other of these bugs
-  might be present at any given time.
-
 141: 
   Pretty-printing nested backquotes doesn't work right, as 
   reported by Alexey Dejneka sbcl-devel 2002-01-13:
@@ -846,31 +749,6 @@ WORKAROUND:
   isn't too surprising since there are many differences in stack
   implementation and GC conservatism between the X86 and other ports.)
 
-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)
@@ -885,14 +763,6 @@ WORKAROUND:
   macro is unhappy with the illegal syntax in the method body, and
   is giving an unclear error message.
 
-172:
-  sbcl's treatment of at least macro lambda lists is too permissive;
-  e.g., in sbcl-0.7.3.7:
-    (defmacro foo (&rest rest bar) `(,bar ,rest))
-    (macroexpand '(foo quux zot)) -> (QUUX (QUUX ZOT))
-  whereas section 3.4.4 of the CLHS doesn't allow required parameters
-  to come after the rest argument.
-
 173:
   The compiler sometimes tries to constant-fold expressions before
   it checks to see whether they can be reached. This can lead to 
@@ -908,39 +778,6 @@ WORKAROUND:
   code. Since then the warning has been downgraded to STYLE-WARNING, 
   so it's still a bug but at least it's a little less annoying.
 
-176:
-  reported by Alexey Dejneka 08 Jun 2002 in sbcl-devel:
-    Playing with McCLIM, I've received an error "Unbound variable WRAPPER
-    in SB-PCL::CHECK-WRAPPER-VALIDITY".
-      (defun check-wrapper-validity (instance)
-        (let* ((owrapper (wrapper-of instance)))
-          (if (not (invalid-wrapper-p owrapper))
-              owrapper
-              (let* ((state (wrapper-state wrapper)) ; !!!
-        ...
-    I've tried to replace it with OWRAPPER, but now OBSOLETE-INSTANCE-TRAP
-    breaks with "NIL is not of type SB-KERNEL:LAYOUT".
-    SBCL 0.7.4.13.
-  partial fix: The undefined variable WRAPPER resulted from an error
-  in recent refactoring, as can be seen by comparing to the code in e.g. 
-  sbcl-0.7.2. Replacing WRAPPER with OWRAPPER (done by WHN in sbcl-0.7.4.22)
-  should bring the code back to its behavior as of sbcl-0.7.2, but
-  that still leaves the OBSOLETE-INSTANCE-TRAP bug. An example of 
-  input which triggers that bug is
-    (dotimes (i 20)
-      (let ((lastname (intern (format nil "C~D" (1- i))))
-            (name (intern (format nil "C~D" i))))
-      (eval `(defclass ,name
-                 (,@(if (= i 0) nil (list lastname)))
-               ()))
-      (eval `(defmethod initialize-instance :after ((x ,name) &rest any)
-               (declare (ignore any))))))
-    (defclass b () ())
-    (defclass c0 (b) ())
-    (make-instance 'c19)
-
-  See also bug #140.
-
 178: "AVER failure compiling confused THEs in FUNCALL"
   In sbcl-0.7.4.24, compiling
     (defun bug178 (x)
@@ -979,14 +816,6 @@ WORKAROUND:
           :ACCRUED-EXCEPTIONS (:INEXACT)
           :FAST-MODE NIL)
 
-185: "top-level forms at the REPL"
-  * (locally (defstruct foo (a 0 :type fixnum)))
-  gives an error:
-  ; caught ERROR:
-  ;   (in macroexpansion of (SB-KERNEL::%DELAYED-GET-COMPILER-LAYOUT BAR))
-  however, compiling and loading the same expression in a file works
-  as expected.
-
 187: "type inference confusion around DEFTRANSFORM time"
   (reported even more verbosely on sbcl-devel 2002-06-28 as "strange
   bug in DEFTRANSFORM")
@@ -1124,25 +953,6 @@ WORKAROUND:
 
      (see bug 203)
 
-193: "unhelpful CLOS error reporting when the primary method is missing"
-  In sbcl-0.7.7, when
-    (defmethod foo :before ((x t)) (print x))
-  is the only method defined on FOO, the error reporting when e.g.
-    (foo 12)
-  is relatively unhelpful:
-    There is no primary method for the generic function
-      #<STANDARD-GENERIC-FUNCTION FOO (1)>.
-  with the offending argument nowhere visible in the backtrace. This 
-  continues even if there *are* primary methods, just not for the 
-  specified arg type, e.g. 
-    (defmethod foo ((x character)) (print x))
-    (defmethod foo ((x string)) (print x))
-    (defmethod foo ((x pathname)) ...)
-  In that case it could be very helpful to know what argument value is
-  falling through the cracks of the defined primary methods, but the
-  error message stays the same (even BACKTRACE doesn't tell you what the
-  bad argument value is).
-
 194: "no error from (THE REAL '(1 2 3)) in some cases"
   fixed parts:
     a. In sbcl-0.7.7.9, 
@@ -1150,11 +960,11 @@ WORKAROUND:
        returns (1 2 3) instead of signalling an error. This was fixed by 
        APD's "more strict type checking patch", but although the fixed
        code (in sbcl-0.7.7.19) works (signals TYPE-ERROR) interactively,
-       it's difficult to write a regression test for it, because 
+       it's difficult to write a regression test for it, because
        (IGNORE-ERRORS (MULTIPLE-VALUE-PROG1 (PROGN (THE REAL '(1 2 3)))))
        still returns (1 2 3).
-  still-broken parts:  
-    b. (IGNORE-ERRORS (MULTIPLE-VALUE-PROG1 (PROGN (THE REAL '(1 2 3)))))    
+  still-broken parts:
+    b. (IGNORE-ERRORS (MULTIPLE-VALUE-PROG1 (PROGN (THE REAL '(1 2 3)))))
        returns (1 2 3). (As above, this shows up when writing regression
        tests for fixed-ness of part a.)
     c. Also in sbcl-0.7.7.9, (IGNORE-ERRORS (THE REAL '(1 2 3))) => (1 2 3).
@@ -1221,7 +1031,7 @@ WORKAROUND:
     (progn (the real (list 1)) t)
 
   This situation may appear during optimizing away degenerate cases of
-  certain functions: see bugs 54, 192b.
+  certain functions: see bug 192b.
 
 205: "environment issues in cross compiler"
   (These bugs have no impact on user code, but should be fixed or
@@ -1230,6 +1040,8 @@ WORKAROUND:
      lexical environment.
   b. The body of (EVAL-WHEN (:COMPILE-TOPLEVEL) ...) is evaluated in
      the null lexical environment.
+  c. The cross-compiler cannot inline functions defined in a non-null
+     lexical environment.
 
 206: ":SB-FLUID feature broken"
   (reported by Antonio Martinez-Shotton sbcl-devel 2002-10-07)
@@ -1254,7 +1066,7 @@ WORKAROUND:
   29-bit pseudorandom numbers?
 
 208: "package confusion in PCL handling of structure slot handlers"
-  In sbcl-0.7.8 compiling and loading 
+  In sbcl-0.7.8 compiling and loading
        (in-package :cl)
        (defstruct foo (slot (error "missing")) :type list :read-only t)
        (defmethod print-object ((foo foo) stream) (print nil stream))
@@ -1262,12 +1074,6 @@ WORKAROUND:
   package: FOO-SLOT". (This is fairly bad code, but still it's hard
   to see that it should cause symbols to be interned in the CL package.)
 
-209: "DOCUMENTATION generic function has wrong argument precedence order"
-  (fixed in sbcl-0.7.8.39)
-
-210: "unsafe evaluation of DEFSTRUCT slot initforms in BOA constructors"
-  (fixed in sbcl-0.7.8.35)
-
 211: "keywords processing"
   a. :ALLOW-OTHER-KEYS T should allow a function to receive an odd
      number of keyword arguments.
@@ -1280,25 +1086,24 @@ WORKAROUND:
 
        ; in: LAMBDA NIL
        ;     (FOO :Y 1 :Y 2)
-       ; 
+       ;
        ; caught STYLE-WARNING:
        ;   The variable #:G15 is defined but never used.
 
-
 212: "Sequence functions and circular arguments"
   COERCE, MERGE and CONCATENATE go into an infinite loop when given
   circular arguments; it would be good for the user if they could be
   given an error instead (ANSI 17.1.1 allows this behaviour on the part
   of the implementation, as conforming code cannot give non-proper
   sequences to these functions.  MAP also has this problem (and
-  solution), though arguably the convenience of being able to do 
-    (MAP 'LIST '+ FOO '#1=(1 . #1#)) 
+  solution), though arguably the convenience of being able to do
+    (MAP 'LIST '+ FOO '#1=(1 . #1#))
   might be classed as more important (though signalling an error when
   all of the arguments are circular is probably desireable).
 
 213: "Sequence functions and type checking"
   a. MAKE-SEQUENCE, COERCE, MERGE and CONCATENATE cannot deal with
-     various complicated, though recognizeable, CONS types [e.g. 
+     various complicated, though recognizeable, CONS types [e.g.
        (CONS * (CONS * NULL))
      which according to ANSI should be recognized] (and, in SAFETY 3
      code, should return a list of LENGTH 2 or signal an error)
@@ -1311,7 +1116,7 @@ WORKAROUND:
        (CONS INTEGER *)
      whether or not the return value is of this type.  This is
      probably permitted by ANSI (see "Exceptional Situations" under
-     ANSI MAKE-SEQUENCE), but the DERIVE-TYPE mechanism does not 
+     ANSI MAKE-SEQUENCE), but the DERIVE-TYPE mechanism does not
      know about this escape clause, so code of the form
        (INTEGERP (CAR (MAKE-SEQUENCE '(CONS INTEGER *) 2)))
      can erroneously return T.
@@ -1334,7 +1139,7 @@ WORKAROUND:
   a. FIND and POSITION currently signal errors when given non-NIL for
      both their :TEST and (deprecated) :TEST-NOT arguments, but by
      ANSI 17.2 "the consequences are unspecified", which by ANSI 1.4.2
-     means that the effect is "unpredictable but harmless.  It's not
+     means that the effect is "unpredictable but harmless".  It's not
      clear what that actually means; it may preclude conforming
      implementations from signalling errors.
   b. COUNT, REMOVE and the like give priority to a :TEST-NOT argument
@@ -1380,6 +1185,103 @@ WORKAROUND:
   produce invalid code, but type checking is not accurate. Similar
   problems exist with VALUES-TYPE-INTERSECTION.)
 
+218: "VALUES type specifier semantics"
+  (THE (VALUES ...) ...) in safe code discards extra values.
+
+  (defun test (x y) (the (values integer) (truncate x y)))
+  (test 10 4) => 2
+
+219: "DEFINE-COMPILER-MACRO in non-toplevel contexts evaluated at compile-time"
+  In sbcl-0.7.9:
+
+  * (defun foo (x)
+      (when x
+        (define-compiler-macro bar (&whole whole)
+          (declare (ignore whole))
+          (print "expanding compiler macro")
+          1)))
+  FOO
+  * (defun baz (x) (bar))
+  [ ... ]
+  "expanding compiler macro"
+  BAZ
+  * (baz t)
+  1
+
+220:
+  Sbcl 0.7.9 fails to compile
+
+  (multiple-value-call #'list
+    (the integer (helper))
+    nil)
+
+  Type check for INTEGER is inserted, the result of which serves as
+  the first argument of M-V-C, is inserted after evaluation of NIL. So
+  arguments of M-V-C are pushed in the wrong order. As a temporary
+  workaround type checking was disabled for M-V-Cs in 0.7.9.13. A
+  better solution would be to put a check between evaluation of
+  arguments, but it could be tricky to check result types of PROG1, IF
+  etc.
+
+222: "environment problems in PCL"
+  Evaluating
+
+    (symbol-macrolet ((x 1))
+      (defmethod foo (z)
+        (macrolet ((ml (form) `(progn ,form ,x)))
+          (ml (print x)))))
+
+  causes
+
+    debugger invoked on condition of type UNBOUND-VARIABLE:
+      The variable X is unbound.
+
+223: "(SETF FDEFINITION) and #' semantics broken for wrappers"
+  Although this
+    (defun foo (x)
+      (print x))
+    (defun traced (fn)
+      (lambda (&rest rest)
+        (format t "~&about to call ~S on ~S~%" fn rest)
+        (apply fn rest)
+        (format t "~&returned from ~S~%" fn)))
+    (setf (fdefinition 'foo)
+          (traced #'foo))
+    (foo 11)
+  does what one would expect, this
+    (defun bar (x)
+      (print x))
+    (let ((bar0 #'bar))
+      (setf (fdefinition 'bar)
+       (lambda (&rest rest)
+         (format t "~&about to enter BAR ~S~%" rest)
+         (apply bar0 rest)
+         (format t "~&back from BAR~%"))))
+    (bar 12)
+  recurses endlessly in sbcl-0.7.9.32. (Or it works if #' and
+  FDEFINITION are replaced by SYMBOL-FUNCTION.)
+
+224:
+  SBCL 0.7.8 fails to compile
+    (localy (declare (optimize (safety 3)))
+            (ignore-errors (progn (values-list (car (list '(1 . 2)))) t)))
+  (the LOCALY there is not a typo; any unknown function (e.g. FROB)
+  will do).
+
+228: "function-lambda-expression problems"
+  in sbcl-0.7.9.6x, from the REPL:
+    * (progn (declaim (inline foo)) (defun foo (x) x))
+    FOO
+    * (function-lambda-expression #'foo)
+    (SB-C:LAMBDA-WITH-LEXENV NIL NIL NIL (X) (BLOCK FOO X)), NIL, FOO
+  but this first return value is not suitable for input to FUNCTION or
+  COMPILE, as required by ANSI.
+
+229:
+  (subtypep 'function '(function)) => nil, t.
+
+230:
+  (fixed in 0.7.10.5)
 
 DEFUNCT CATEGORIES OF BUGS
   IR1-#: