0.7.10.10:
[sbcl.git] / BUGS
diff --git a/BUGS b/BUGS
index fb9a754..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.
 
@@ -382,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
@@ -503,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.
@@ -633,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,
@@ -649,15 +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.
-
 141: 
   Pretty-printing nested backquotes doesn't work right, as 
   reported by Alexey Dejneka sbcl-devel 2002-01-13:
@@ -781,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)
@@ -820,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 
@@ -1018,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, 
@@ -1044,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).
@@ -1115,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
@@ -1124,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)
@@ -1148,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))
@@ -1168,7 +1086,7 @@ WORKAROUND:
 
        ; in: LAMBDA NIL
        ;     (FOO :Y 1 :Y 2)
-       ; 
+       ;
        ; caught STYLE-WARNING:
        ;   The variable #:G15 is defined but never used.
 
@@ -1178,14 +1096,14 @@ WORKAROUND:
   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)
@@ -1198,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.
@@ -1276,7 +1194,7 @@ WORKAROUND:
 219: "DEFINE-COMPILER-MACRO in non-toplevel contexts evaluated at compile-time"
   In sbcl-0.7.9:
 
-  * (defun foo (x) 
+  * (defun foo (x)
       (when x
         (define-compiler-macro bar (&whole whole)
           (declare (ignore whole))
@@ -1290,6 +1208,81 @@ WORKAROUND:
   * (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-#:
     These labels were used for bugs related to the old IR1 interpreter.