0.8.16.43: Fixes for various CLOS/MOP bugs
[sbcl.git] / BUGS
diff --git a/BUGS b/BUGS
index 61eb424..48ca825 100644 (file)
--- a/BUGS
+++ b/BUGS
@@ -167,6 +167,12 @@ WORKAROUND:
   then requesting a BACKTRACE at the debugger prompt gives no information
   about where in the user program the problem occurred.
 
+  (this is apparently mostly fixed on the SPARC and PPC architectures:
+  while giving the backtrace the system complains about "unknown
+  source location: using block start", but apart from that the
+  backtrace seems reasonable.  See tests/debug.impure.lisp for a test
+  case)
+
 64:
   Using the pretty-printer from the command prompt gives funny
   results, apparently because the pretty-printer doesn't know
@@ -190,20 +196,6 @@ WORKAROUND:
   e-mail on cmucl-help@cons.org on 2001-01-16 and 2001-01-17 from WHN
   and Pierre Mai.)
 
-79:
-  as pointed out by Dan Barlow on sbcl-devel 2000-07-02:
-  The PICK-TEMPORARY-FILE-NAME utility used by LOAD-FOREIGN uses
-  an easily guessable temporary filename in a way which might open
-  applications using LOAD-FOREIGN to hijacking by malicious users
-  on the same machine. Incantations for doing this safely are
-  floating around the net in various "how to write secure programs
-  despite Unix" documents, and it would be good to (1) fix this in 
-  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)
-
 83:
   RANDOM-INTEGER-EXTRA-BITS=10 may not be large enough for the RANDOM
   RNG to be high quality near RANDOM-FIXNUM-MAX; it looks as though
@@ -481,20 +473,6 @@ WORKAROUND:
 
   This is probably the same bug as 216
 
-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.
-
 173:
   The compiler sometimes tries to constant-fold expressions before
   it checks to see whether they can be reached. This can lead to 
@@ -883,26 +861,12 @@ WORKAROUND:
   b. The same for CSUBTYPEP.
 
 262: "yet another bug in inline expansion of local functions"
-  Compiler fails on
-
-    (defun foo (x y)
-      (declare (integer x y))
-      (+ (block nil
-            (flet ((xyz (u)
-                     (declare (integer u))
-                     (if (> (1+ (the unsigned-byte u)) 0)
-                         (+ 1 u)
-                         (return (+ 38 (cos (/ u 78)))))))
-              (declare (inline xyz))
-              (return-from foo
-                (* (funcall (eval #'xyz) x)
-                   (if (> x 30)
-                       (funcall (if (> x 5) #'xyz #'identity)
-                                (+ x 13))
-                       38)))))
-         (sin (* x y))))
-
-  Urgh... It's time to write IR1-copier.
+  During inline expansion of a local function Python can try to
+  reference optimized away objects (functions, variables, CTRANs from
+  tags and blocks), which later may lead to problems. Some of the
+  cases are worked around by forbidding expansion in such cases, but
+  the better way would be to reimplement inline expansion by copying
+  IR1 structures.
 
 266:
   David Lichteblau provided (sbcl-devel 2003-06-01) a patch to fix
@@ -922,9 +886,6 @@ WORKAROUND:
                (list x y)))
         (funcall (eval #'foo) 1)))
 
-269:
-  SCALE-FLOAT should accept any integer for its second argument.
-
 270:
   In the following function constraint propagator optimizes nothing:
 
@@ -1126,14 +1087,6 @@ WORKAROUND:
   gives the error
     failed AVER: "(NOT (AND (NOT EQUALP) CERTAINP))"
 
-302: Undefined type messes up DATA-VECTOR-REF expansion.
-  Compiling this file
-    (defun dis (s ei x y)
-      (declare (type (simple-array function (2)) s) (type ei ei))
-      (funcall (aref s ei) x y))
-  on sbcl-0.8.7.36/X86/Linux causes a BUG to be signalled:
-    full call to SB-KERNEL:DATA-VECTOR-REF
-
 303: "nonlinear LVARs" (aka MISC.293)
     (defun buu (x)
       (multiple-value-call #'list
@@ -1178,23 +1131,6 @@ WORKAROUND:
                collect `(array ,(sb-vm:saetp-specifier x)))))
     => NIL, T (when it should be T, T)
 
-308: "Characters without names"
-    (reported by Bruno Haible sbcl-devel "character names are missing"
-    2004-04-19)
-  (graphic-char-p (code-char 255))
-  => NIL
-  (char-name (code-char 255))
-  => NIL
-
-  SBCL is unsure of what to do about characters with codes in the
-  range 128-255.  Currently they are treated as non-graphic, but don't
-  have names, which is not compliant with the standard.  Various fixes
-  are possible, such as
-  * giving them names such as NON-ASCII-128;
-  * reducing CHAR-CODE-LIMIT to 127 (almost certainly unpopular);
-  * making the characters graphic (makes a certain amount of sense);
-  * biting the bullet and implementing Unicode (probably quite hard).
-
 309: "Dubious values for implementation limits"
     (reported by Bruno Haible sbcl-devel "Incorrect value of
     multiple-values-limit" 2004-04-19)
@@ -1242,15 +1178,20 @@ WORKAROUND:
 318: "stack overflow in compiler warning with redefined class"
   reported by Bruno Haible sbcl-devel "various SBCL bugs" from CLISP
   test suite.
-    (setq *print-pretty* nil)
     (defstruct foo a)
     (setf (find-class 'foo) nil)
     (defstruct foo slot-1)
-  gives 
-    ...#<SB-KERNEL:STRUCTURE-CLASSOID #<SB-KERNEL:STRUCTURE-CLASSOID #<SB-KERNEL:STRUCTURE-CLASSOID #<SB-KERNEL:STRUCTUREControl stack guard page temporarily disabled: proceed with caution
-  (it's not really clear what it should give: is (SETF FIND-CLASS)
-  meant to be enough to delete structure classes from the system?
-  Giving a stack overflow is definitely suboptimal, though.)
+  This used to give a stack overflow from within the printer, which has
+  been fixed as of 0.8.16.11. Current result:
+    ; caught ERROR:
+    ;   can't compile TYPEP of anonymous or undefined class:
+    ;     #<SB-KERNEL:STRUCTURE-CLASSOID FOO>
+    ...
+    debugger invoked on a TYPE-ERROR in thread 19973:
+      The value NIL is not of type FUNCTION.
+
+  CSR notes: it's not really clear what it should give: is (SETF FIND-CLASS)
+    meant to be enough to delete structure classes from the system?
 
 319: "backquote with comma inside array"
   reported by Bruno Haible sbcl-devel "various SBCL bugs" from CLISP
@@ -1389,48 +1330,6 @@ WORKAROUND:
     debugger invoked on a SB-INT:BUG in thread 27726:
       fasl stack not empty when it should be
 
-333: "CHECK-TYPE TYPE-ERROR-DATUM place"
-  (reported by Tony Martinez sbcl-devel 2004-05-23)
-  When CHECK-TYPE signals a TYPE-ERROR, the TYPE-ERROR-DATUM holds the
-  lisp symbolic place in question rather than the place's value.  This
-  seems wrong.
-
-334: "COMPUTE-SLOTS used to add slots to classes"
-  (reported by Bruno Haible sbcl-devel 2004-06-01)
-  a. Adding a local slot does not work:
-    (use-package "SB-PCL")
-    (defclass b (a) ())
-    (defmethod compute-slots ((class (eql (find-class 'b))))
-      (append (call-next-method)
-              (list (make-instance 'standard-effective-slot-definition
-                      :name 'y
-                      :allocation :instance))))
-    (defclass a () ((x :allocation :class)))
-    ;; A should now have a shared slot, X, and a local slot, Y.
-    (mapcar #'slot-definition-location (class-slots (find-class 'b)))
-  yields
-    There is no applicable method for the generic function
-      #<STANDARD-GENERIC-FUNCTION CLASS-SLOTS (3)>
-    when called with arguments
-      (NIL).
-
-  b. Adding a class slot does not work:
-    (use-package "SB-PCL")
-    (defclass b (a) ())
-    (defmethod compute-slots ((class (eql (find-class 'b))))
-      (append (call-next-method)
-              (list (make-instance 'standard-effective-slot-definition
-                      :name 'y
-                      :allocation :class))))
-    (defclass a () ((x :allocation :class)))
-    ;; A should now have two shared slots, X and Y.
-    (mapcar #'slot-definition-location (class-slots (find-class 'b)))
-  yields
-    There is no applicable method for the generic function
-      #<STANDARD-GENERIC-FUNCTION SB-PCL::CLASS-SLOT-CELLS (1)>
-    when called with arguments
-      (NIL).
-   
 336: "slot-definitions must retain the generic functions of accessors"
   reported by Tony Martinez:
     (defclass foo () ((bar :reader foo-bar)))
@@ -1546,20 +1445,6 @@ WORKAROUND:
       (test-um12 17))
     fails with NO-APPLICABLE-METHOD.
 
-338: "MOP specializers as type specifiers"
-  (reported by Bruno Haible sbcl-devel 2004-06-11)
-
-  ANSI 7.6.2 says: 
-    Because every valid parameter specializer is also a valid type
-    specifier, the function typep can be used during method selection
-    to determine whether an argument satisfies a parameter
-    specializer.
-
-  however, SBCL's EQL specializers are not type specifiers:
-    (defmethod foo ((x (eql 4.0))) 3.0)
-    (typep 1 (first (sb-pcl:method-specializers *)))
-  gives an error.
-
 339: "DEFINE-METHOD-COMBINATION bugs"
   (reported by Bruno Haible via the clisp test suite)
 
@@ -1597,3 +1482,112 @@ WORKAROUND:
   should signal an invalid-method-error, as the :IGNORE (NUMBER)
   method is applicable, and yet matches neither of the method group
   qualifier patterns.
+
+341: PPRINT-LOGICAL-BLOCK / PPRINT-FILL / PPRINT-LINEAR sharing detection.
+  (from Paul Dietz' test suite)
+
+  CLHS on PPRINT-LINEAR and PPRINT-FILL (and PPRINT-TABULAR, though
+  that's slightly different) states that these functions perform
+  circular and shared structure detection on their object.  Therefore,
+
+  a.(let ((*print-circle* t))
+      (pprint-linear *standard-output* (let ((x '(a))) (list x x))))
+    should print "(#1=(A) #1#)"
+
+  b.(let ((*print-circle* t))
+      (pprint-linear *standard-output* 
+                     (let ((x (cons nil nil))) (setf (cdr x) x) x)))
+    should print "#1=(NIL . #1#)"
+
+  (it is likely that the fault lies in PPRINT-LOGICAL-BLOCK, as
+  suggested by the suggested implementation of PPRINT-TABULAR)
+
+342: PPRINT-TABULAR / PPRINT-LOGICAL-BLOCK logical block start position
+  The logical block introduced by PPRINT-LOGICAL-BLOCK should not
+  include the prefix, so that
+    (pprint-tabular *standard-output* '(1 2 3) t nil 2)
+  should print
+  "(1 2 3)" rather than "(1  2 3)".
+
+343: MOP:COMPUTE-DISCRIMINATING-FUNCTION overriding causes error
+  Even the simplest possible overriding of
+  COMPUTE-DISCRIMINATING-FUNCTION, suggested in the PCL implementation
+  as "canonical", does not work:
+    (defclass my-generic-function (standard-generic-function) ()
+      (:metaclass funcallable-standard-class))
+    (defmethod compute-discriminating-function ((gf my-generic-function))
+      (let ((dfun (call-next-method)))
+        (lambda (&rest args)
+          (apply dfun args))))
+    (defgeneric foo (x)
+      (:generic-function-class my-generic-function))
+    (defmethod foo (x) (+ x x))
+    (foo 5)
+  signals an error.  This error is the same even if the LAMBDA is
+  replaced by (FUNCTION (SB-KERNEL:INSTANCE-LAMBDA ...)).  Maybe the
+  SET-FUNCALLABLE-INSTANCE-FUN scary stuff in
+  src/code/target-defstruct.lisp is broken?  This seems to be broken
+  in CMUCL 18e, so it's not caused by a recent change.
+
+344: more (?) ROOM T problems (possibly part of bug 108)
+  In sbcl-0.8.12.51, and off and on leading up to it, the
+  SB!VM:MEMORY-USAGE operations in ROOM T caused 
+       unhandled condition (of type SB-INT:BUG):
+           failed AVER: "(SAP= CURRENT END)"
+  Several clever people have taken a shot at this without fixing
+  it; this time around (before sbcl-0.8.13 release) I (WHN) just
+  commented out the SB!VM:MEMORY-USAGE calls until someone figures
+  out how to make them work reliably with the rest of the GC.
+
+  (Note: there's at least one dubious thing in room.lisp: see the
+  comment in VALID-OBJ)
+
+345: backtrace on x86 undefined function
+  In sbcl-0.8.13 (and probably earlier versions), code of the form
+    (flet ((test () (#:undefined-fun 42)))
+      (funcall #'test))
+  yields the debugger with a poorly-functioning backtrace.  Brian
+  Downing fixed most of the problems on non-x86 architectures, but on
+  the x86 the backtrace from this evaluation does not reveal anything
+  about the problem.  (See tests in debug.impure.lisp)
+
+346: alpha backtrace
+  In sbcl-0.8.13, all backtraces from errors caused by internal errors
+  on the alpha seem to have a "bogus stack frame".
+
+348:
+  Structure slot setters do not preserve evaluation order:
+
+    (defstruct foo (x))
+
+    (let ((i (eval '-2))
+          (x (make-foo)))
+      (funcall #'(setf foo-x)
+               (incf i)
+               (aref (vector x) (incf i)))
+      (foo-x x))
+    => error
+
+349: PPRINT-INDENT rounding implementation decisions
+  At present, pprint-indent (and indeed the whole pretty printer)
+  more-or-less assumes that it's using a monospace font.  That's
+  probably not too silly an assumption, but one piece of information
+  the current implementation loses is from requests to indent by a
+  non-integral amount.  As of sbcl-0.8.15.9, the system silently
+  truncates the indentation to an integer at the point of request, but
+  maybe the non-integral value should be propagated through the
+  pprinter and only truncated at output?  (So that indenting by 1/2
+  then 3/2 would indent by two spaces, not one?)
+
+352: forward-referenced-class trouble
+ reported by Bruno Haible on sbcl-devel
+   (defclass c (a) ())
+   (setf (class-name (find-class 'a)) 'b)
+   (defclass a () (x))
+   (defclass b () (y))
+   (make-instance 'c)
+ Expected: an instance of c, with a slot named x
+ Got: debugger invoked on a SIMPLE-ERROR in thread 78906:
+        While computing the class precedence list of the class named C.
+        The class named B is a forward referenced class.
+        The class named B is a direct superclass of the class named C.