0.8.21.37: fix bug 305
[sbcl.git] / BUGS
diff --git a/BUGS b/BUGS
index 2ee474b..ba4e1f1 100644 (file)
--- a/BUGS
+++ b/BUGS
@@ -84,33 +84,12 @@ WORKAROUND:
 
   d: (fixed in 0.8.1.5)
 
-7:
-  The "compiling top-level form:" output ought to be condensed.
-  Perhaps any number of such consecutive lines ought to turn into a
-  single "compiling top-level forms:" line.
-
-19:
-  (I *think* this is a bug. It certainly seems like strange behavior. But
-  the ANSI spec is scary, dark, and deep.. -- WHN)
-    (FORMAT NIL  "~,1G" 1.4) => "1.    "
-    (FORMAT NIL "~3,1G" 1.4) => "1.    "
-
 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.
 
-32:
-  The printer doesn't report closures very well. This is true in 
-  CMU CL 18b as well:
-    (PRINT #'CLASS-NAME)
-  gives
-    #<Closure Over Function "DEFUN STRUCTURE-SLOT-ACCESSOR" {134D1A1}>
-  It would be nice to make closures have a settable name slot,
-  and make things like DEFSTRUCT and FLET, which create closures,
-  set helpful values into this slot.
-
 33:
   And as long as we're wishing, it would be awfully nice if INSPECT could
   also report on closures, telling about the values of the bound variables.
@@ -156,10 +135,6 @@ WORKAROUND:
   so they could be supported after all. Very likely 
   SIGCONTEXT-FLOATING-POINT-MODES could now be supported, too.
 
-60:
-  The debugger LIST-LOCATIONS command doesn't work properly.
-  (How should it work properly?)
-
 61:
   Compiling and loading
     (DEFUN FAIL (X) (THROW 'FAIL-TAG X))
@@ -167,11 +142,11 @@ 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
+  (this is apparently mostly fixed on the SPARC, PPC, and x86 architectures:
+  while giving the backtrace the non-x86 systems 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)
+  backtrace seems reasonable. On x86 this is masked by bug 353. See
+  tests/debug.impure.lisp for a test case)
 
 64:
   Using the pretty-printer from the command prompt gives funny
@@ -378,24 +353,6 @@ WORKAROUND:
    a STYLE-WARNING for references to variables similar to locals might
    be a good thing.)
 
-125:
-   (as reported by Gabe Garza on cmucl-help 2001-09-21)
-       (defvar *tmp* 3)
-       (defun test-pred (x y)
-         (eq x y))
-       (defun test-case ()
-         (let* ((x *tmp*)
-                (func (lambda () x)))
-           (print (eq func func))
-           (print (test-pred func func))
-           (delete func (list func))))
-   Now calling (TEST-CASE) gives output
-     NIL
-     NIL
-     (#<FUNCTION {500A9EF9}>)
-   Evidently Python thinks of the lambda as a code transformation so
-   much that it forgets that it's also an object.
-
 135:
   Ideally, uninterning a symbol would allow it, and its associated
   FDEFINITION and PROCLAIM data, to be reclaimed by the GC. However,
@@ -437,6 +394,10 @@ WORKAROUND:
   conformance problem, since seems hard to construct useful code
   where it matters.)
 
+  [ partially fixed by CSR in 0.8.17.17 because of a PFD ansi-tests
+    report that (COMPLEX RATIO) was failing; still failing on types of
+    the form (AND NUMBER (SATISFIES REALP) (SATISFIES ZEROP)). ]
+
   b. (fixed in 0.8.3.43)
 
 146:
@@ -861,26 +822,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
@@ -940,6 +887,14 @@ WORKAROUND:
 
   (fixed in 0.8.2.51, but a test case would be good)
 
+276:
+  b. The same as in a., but using MULTIPLE-VALUE-SETQ instead of SETQ.
+  c. (defvar *faa*)
+     (defmethod faa ((*faa* double-float))
+           (set '*faa* (when (< *faa* 0) (- *faa*)))
+           (1+ *faa*))
+     (faa 1d0) => type error
+
 278:
   a.
     (defun foo ()
@@ -1118,17 +1073,6 @@ WORKAROUND:
 
   The problem is that both EVALs sequentially write to the same LVAR.
 
-305:
-  (Reported by Dave Roberts.)
-  Local INLINE/NOTINLINE declaration removes local FTYPE declaration:
-
-    (defun quux (x)
-      (declare (ftype (function () (integer 0 10)) fee)
-               (inline fee))
-      (1+ (fee)))
-
-  uses generic arithmetic with INLINE and fixnum without.
-
 306: "Imprecise unions of array types"
   a.(defun foo (x)
       (declare (optimize speed)
@@ -1179,16 +1123,6 @@ WORKAROUND:
     Expected: (2 6 15 38)
     Got:      ERROR
 
-317: "FORMAT of floating point numbers"
-  reported by Bruno Haible sbcl-devel "various SBCL bugs" from CLISP
-  test suite.
-    (format nil "~1F" 10) => "0." ; "10." expected
-    (format nil "~0F" 10) => "0." ; "10." expected
-    (format nil "~2F" 1234567.1) => "1000000." ; "1234567." expected
-  it would be nice if whatever fixed this also untangled the two
-  competing implementations of floating point printing (Steele and
-  White, and Burger and Dybvig) present in src/code/print.lisp
-
 318: "stack overflow in compiler warning with redefined class"
   reported by Bruno Haible sbcl-devel "various SBCL bugs" from CLISP
   test suite.
@@ -1319,12 +1253,6 @@ WORKAROUND:
      in the wrapper, and then to update the instance just run through
      all the old wrappers in order from oldest to newest.
 
-331: "lazy creation of CLOS classes for user-defined conditions"
-    (defstruct foo)
-    (defstruct (bar (:include foo)))
-    (sb-mop:class-direct-subclasses (find-class 'foo))
-  returns NIL, rather than a singleton list containing the BAR class.
-
 332: "fasl stack inconsistency in structure redefinition"
   (reported by Tim Daly Jr sbcl-devel 2004-05-06)
   Even though structure redefinition is undefined by the standard, the
@@ -1516,13 +1444,6 @@ WORKAROUND:
   (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
@@ -1556,32 +1477,10 @@ WORKAROUND:
   (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
@@ -1593,5 +1492,588 @@ WORKAROUND:
   pprinter and only truncated at output?  (So that indenting by 1/2
   then 3/2 would indent by two spaces, not one?)
 
-351: suboptimal error handling/reporting when compiling (PUSH (LET ...)) 
-  (fixed in 0.8.16.37)
+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.
+
+353: debugger suboptimalities on x86
+ On x86 backtraces for undefined functions start with a bogus stack
+ frame, and  backtraces for throws to unknown catch tags with a "no 
+ debug information" frame. These are both due to CODE-COMPONENT-FROM-BITS
+ (used on non-x86 platforms) being a more complete solution then what
+ is done on x86.
+
+ On x86/linux large portions of tests/debug.impure.lisp have been commented
+ out as failures. The probable culprit for these problems is in x86-call-context
+ (things work fine on x86/freebsd).
+
+ More generally, the debugger internals suffer from excessive x86/non-x86
+ conditionalization and OAOOMization: refactoring the common parts would
+ be good.
+
+354: XEPs in backtraces
+ Under default compilation policy
+   (defun test ()
+     (throw :unknown t))
+   (test)
+ Has the XEP for TEST in the backtrace, not the TEST frame itself.
+ (sparc and x86 at least)
+
+ Since SBCL 0.8.20.1 this is hidden unless *SHOW-ENTRY-POINT-DETAILS*
+ is true (instead there appear two TEST frames at least on ppc). The
+ underlying cause seems to be that SB-C::TAIL-ANNOTATE will not merge
+ the tail-call for the XEP, since Python has by that time proved that
+ the function can never return; same happens if the function holds an
+ unconditional call to ERROR.
+
+355: change-class of generic-function
+    (reported by Bruno Haible)
+  The MOP doesn't support change-class on a generic-function. However, SBCL
+  apparently supports it, since it doesn't give an error or warning when doing
+  so so. Then, however, it produces wrong results for calls to this generic 
+  function.
+  ;;; The effective-methods cache:
+  (progn
+    (defgeneric testgf35 (x))
+    (defmethod testgf35 ((x integer))
+      (cons 'integer (if (next-method-p) (call-next-method))))
+    (defmethod testgf35 ((x real))
+      (cons 'real (if (next-method-p) (call-next-method))))
+    (defclass customized5-generic-function (standard-generic-function)
+      ()
+      (:metaclass sb-pcl:funcallable-standard-class))
+    (defmethod sb-pcl:compute-effective-method ((gf customized5-generic-function) method-combination methods)
+      `(REVERSE ,(call-next-method)))
+    (list
+      (testgf35 3)
+      (progn
+        (change-class #'testgf35 'customized5-generic-function)
+        (testgf35 3))))
+  Expected: ((INTEGER REAL) (REAL INTEGER))
+  Got:      ((INTEGER REAL) (INTEGER REAL))
+  ;;; The discriminating-function cache:
+  (progn
+    (defgeneric testgf36 (x))
+    (defmethod testgf36 ((x integer))
+      (cons 'integer (if (next-method-p) (call-next-method))))
+    (defmethod testgf36 ((x real))
+      (cons 'real (if (next-method-p) (call-next-method))))
+    (defclass customized6-generic-function (standard-generic-function)
+      ()
+      (:metaclass sb-pcl:funcallable-standard-class))
+    (defmethod sb-pcl:compute-discriminating-function ((gf customized6-generic-function))
+      (let ((orig-df (call-next-method)))
+        #'(lambda (&rest arguments)
+            (reverse (apply orig-df arguments)))))
+    (list
+      (testgf36 3)
+      (progn
+        (change-class #'testgf36 'customized6-generic-function)
+        (testgf36 3))))
+  Expected: ((INTEGER REAL) (REAL INTEGER))
+  Got:      ((INTEGER REAL) (INTEGER REAL))
+
+356: PCL corruption
+    (reported by Bruno Haible)
+  After the "layout depth conflict" error, the CLOS is left in a state where
+  it's not possible to define new standard-class subclasses any more.
+  Test case:
+  (defclass prioritized-dispatcher ()
+    ((dependents :type list :initform nil)))
+  (defmethod sb-pcl:validate-superclass ((c1 sb-pcl:funcallable-standard-class) 
+                                         (c2 (eql (find-class 'prioritized-dispatcher))))
+    t)
+  (defclass prioritized-generic-function (prioritized-dispatcher standard-generic-function)
+    ()
+    (:metaclass sb-pcl:funcallable-standard-class))
+  ;; ERROR, Quit the debugger with ABORT
+  (defclass typechecking-reader-class (standard-class)
+    ())
+  Expected: #<STANDARD-CLASS TYPECHECKING-READER-CLASS>
+  Got:      ERROR "The assertion SB-PCL::WRAPPERS failed."
+
+357: defstruct inheritance of initforms
+    (reported by Bruno Haible)
+  When defstruct and defclass (with :metaclass structure-class) are mixed,
+  1. some slot initforms are ignored by the DEFSTRUCT generated constructor
+     function, and 
+  2. all slot initforms are ignored by MAKE-INSTANCE. (This can be arguably
+     OK for initforms that were given in a DEFSTRUCT form, but for those
+     given in a DEFCLASS form, I think it qualifies as a bug.)
+  Test case:
+  (defstruct structure02a
+    slot1
+    (slot2 t)
+    (slot3 (floor pi)))
+  (defclass structure02b (structure02a)
+    ((slot4 :initform -44)
+     (slot5)
+     (slot6 :initform t)
+     (slot7 :initform (floor (* pi pi)))
+     (slot8 :initform 88))
+    (:metaclass structure-class))
+  (defstruct (structure02c (:include structure02b (slot8 -88)))
+    slot9 
+    (slot10 t)
+    (slot11 (floor (exp 3))))
+  ;; 1. Form:
+  (let ((a (make-structure02c)))
+    (list (structure02c-slot4 a)
+          (structure02c-slot5 a)
+          (structure02c-slot6 a)
+          (structure02c-slot7 a)))
+  Expected: (-44 nil t 9)
+  Got: (SB-PCL::..SLOT-UNBOUND.. SB-PCL::..SLOT-UNBOUND..
+        SB-PCL::..SLOT-UNBOUND.. SB-PCL::..SLOT-UNBOUND..)
+  ;; 2. Form:
+  (let ((b (make-instance 'structure02c)))
+    (list (structure02c-slot2 b)
+          (structure02c-slot3 b)
+          (structure02c-slot4 b)
+          (structure02c-slot6 b)
+          (structure02c-slot7 b)
+          (structure02c-slot8 b)
+          (structure02c-slot10 b)
+          (structure02c-slot11 b)))
+  Expected: (t 3 -44 t 9 -88 t 20)
+  Got: (0 0 0 0 0 0 0 0)
+
+358: :DECLARE argument to ENSURE-GENERIC-FUNCTION 
+    (reported by Bruno Haible)
+  According to ANSI CL, ensure-generic-function must accept a :DECLARE
+  keyword argument. In SBCL 0.8.16 it does not.
+  Test case:
+  (progn
+    (ensure-generic-function 'foo113 :declare '((optimize (speed 3))))
+    (sb-pcl:generic-function-declarations #'foo113))
+  Expected: ((OPTIMIZE (SPEED 3)))
+  Got: ERROR
+    Invalid initialization argument:
+      :DECLARE
+    in call for class #<SB-MOP:FUNCALLABLE-STANDARD-CLASS STANDARD-GENERIC-FUNCTION>.
+  See also:
+    The ANSI Standard, Section 7.1.2
+
+  Bruno notes: The MOP specifies that ensure-generic-function accepts :DECLARATIONS.
+  The easiest way to be compliant to both specs is to accept both (exclusively
+  or cumulatively).
+
+359: wrong default value for ensure-generic-function's :generic-function-class argument
+    (reported by Bruno Haible)
+  ANSI CL is silent on this, but the MOP's specification of ENSURE-GENERIC-FUNCTION says:
+   "The remaining arguments are the complete set of keyword arguments
+    received by ENSURE-GENERIC-FUNCTION."
+  and the spec of ENSURE-GENERIC-FUNCTION-USING-CLASS:
+   ":GENERIC-FUNCTION-CLASS - a class metaobject or a class name. If it is not
+    supplied, it defaults to the class named STANDARD-GENERIC-FUNCTION."
+  This is not the case in SBCL. Test case:
+   (defclass my-generic-function (standard-generic-function)
+     ()
+     (:metaclass sb-pcl:funcallable-standard-class))
+   (setf (fdefinition 'foo1)
+         (make-instance 'my-generic-function :name 'foo1))
+   (ensure-generic-function 'foo1
+     :generic-function-class (find-class 'standard-generic-function))
+   (class-of #'foo1)
+   ; => #<SB-MOP:FUNCALLABLE-STANDARD-CLASS STANDARD-GENERIC-FUNCTION>
+   (setf (fdefinition 'foo2)
+         (make-instance 'my-generic-function :name 'foo2))
+   (ensure-generic-function 'foo2)
+   (class-of #'foo2)
+  Expected: #<SB-MOP:FUNCALLABLE-STANDARD-CLASS STANDARD-GENERIC-FUNCTION>
+  Got:      #<SB-MOP:FUNCALLABLE-STANDARD-CLASS MY-GENERIC-FUNCTION>
+
+360: CALL-METHOD not recognized in method-combination body
+  (reported by Bruno Haible)
+  This method combination, which adds 'redo' and 'return' restarts for each
+  method invocation to standard method combination, gives an error in SBCL.
+  (defun prompt-for-new-values ()
+    (format *debug-io* "~&New values: ")
+    (list (read *debug-io*)))
+  (defun add-method-restarts (form method)
+    (let ((block (gensym))
+          (tag (gensym)))
+      `(BLOCK ,block
+         (TAGBODY
+           ,tag
+           (RETURN-FROM ,block
+             (RESTART-CASE ,form
+               (METHOD-REDO ()
+                 :REPORT (LAMBDA (STREAM) (FORMAT STREAM "Try calling ~S again." ,method))
+                 (GO ,tag))
+               (METHOD-RETURN (L)
+                 :REPORT (LAMBDA (STREAM) (FORMAT STREAM "Specify return values for ~S call." ,method))
+                 :INTERACTIVE (LAMBDA () (PROMPT-FOR-NEW-VALUES))
+                 (RETURN-FROM ,block (VALUES-LIST L)))))))))
+  (defun convert-effective-method (efm)
+    (if (consp efm)
+      (if (eq (car efm) 'CALL-METHOD)
+        (let ((method-list (third efm)))
+          (if (or (typep (first method-list) 'method) (rest method-list))
+            ; Reduce the case of multiple methods to a single one.
+            ; Make the call to the next-method explicit.
+            (convert-effective-method
+              `(CALL-METHOD ,(second efm)
+                 ((MAKE-METHOD
+                    (CALL-METHOD ,(first method-list) ,(rest method-list))))))
+            ; Now the case of at most one method.
+            (if (typep (second efm) 'method)
+              ; Wrap the method call in a RESTART-CASE.
+              (add-method-restarts
+                (cons (convert-effective-method (car efm))
+                      (convert-effective-method (cdr efm)))
+                (second efm))
+              ; Normal recursive processing.
+              (cons (convert-effective-method (car efm))
+                    (convert-effective-method (cdr efm))))))
+        (cons (convert-effective-method (car efm))
+              (convert-effective-method (cdr efm))))
+      efm))
+  (define-method-combination standard-with-restarts ()
+         ((around (:around))
+          (before (:before))
+          (primary () :required t)
+          (after (:after)))
+    (flet ((call-methods-sequentially (methods)
+             (mapcar #'(lambda (method)
+                         `(CALL-METHOD ,method))
+                     methods)))
+      (let ((form (if (or before after (rest primary))
+                    `(MULTIPLE-VALUE-PROG1
+                       (PROGN
+                         ,@(call-methods-sequentially before)
+                         (CALL-METHOD ,(first primary) ,(rest primary)))
+                       ,@(call-methods-sequentially (reverse after)))
+                    `(CALL-METHOD ,(first primary)))))
+        (when around
+          (setq form
+                `(CALL-METHOD ,(first around)
+                              (,@(rest around) (MAKE-METHOD ,form)))))
+        (convert-effective-method form))))
+  (defgeneric testgf16 (x) (:method-combination standard-with-restarts))
+  (defclass testclass16a () ())
+  (defclass testclass16b (testclass16a) ())
+  (defclass testclass16c (testclass16a) ())
+  (defclass testclass16d (testclass16b testclass16c) ())
+  (defmethod testgf16 ((x testclass16a))
+    (list 'a
+          (not (null (find-restart 'method-redo)))
+          (not (null (find-restart 'method-return)))))
+  (defmethod testgf16 ((x testclass16b))
+    (cons 'b (call-next-method)))
+  (defmethod testgf16 ((x testclass16c))
+    (cons 'c (call-next-method)))
+  (defmethod testgf16 ((x testclass16d))
+    (cons 'd (call-next-method)))
+  (testgf16 (make-instance 'testclass16d))
+
+  Expected: (D B C A T T)
+  Got: ERROR CALL-METHOD outside of a effective method form
+
+  This is a bug because ANSI CL HyperSpec/Body/locmac_call-m__make-method
+  says
+   "The macro call-method invokes the specified method, supplying it with
+    arguments and with definitions for call-next-method and for next-method-p.
+    If the invocation of call-method is lexically inside of a make-method,
+    the arguments are those that were supplied to that method. Otherwise
+    the arguments are those that were supplied to the generic function."
+  and the example uses nothing more than these two cases (as you can see by
+  doing (trace convert-effective-method)).
+
+361: initialize-instance of standard-reader-method ignores :function argument
+    (reported by Bruno Haible)
+  Pass a custom :function argument to initialize-instance of a
+  standard-reader-method instance, but it has no effect.
+  ;; Check that it's possible to define reader methods that do typechecking.
+  (progn
+    (defclass typechecking-reader-method (sb-pcl:standard-reader-method)
+      ())
+    (defmethod initialize-instance ((method typechecking-reader-method) &rest initargs
+                                    &key slot-definition)
+      (let ((name (sb-pcl:slot-definition-name slot-definition))
+            (type (sb-pcl:slot-definition-type slot-definition)))
+        (apply #'call-next-method method
+               :function #'(lambda (args next-methods)
+                             (declare (ignore next-methods))
+                             (apply #'(lambda (instance)
+                                        (let ((value (slot-value instance name)))
+                                          (unless (typep value type)
+                                            (error "Slot ~S of ~S is not of type ~S: ~S"
+                                                   name instance type value))
+                                          value))
+                                    args))
+               initargs)))
+    (defclass typechecking-reader-class (standard-class)
+      ())
+    (defmethod sb-pcl:validate-superclass ((c1 typechecking-reader-class) (c2 standard-class))
+      t)
+    (defmethod reader-method-class ((class typechecking-reader-class) direct-slot &rest args)
+      (find-class 'typechecking-reader-method))
+    (defclass testclass25 ()
+      ((pair :type (cons symbol (cons symbol null)) :initarg :pair :accessor testclass25-pair))
+      (:metaclass typechecking-reader-class))
+   (macrolet ((succeeds (form)
+                 `(not (nth-value 1 (ignore-errors ,form)))))
+      (let ((p (list 'abc 'def))
+            (x (make-instance 'testclass25)))
+        (list (succeeds (make-instance 'testclass25 :pair '(seventeen 17)))
+              (succeeds (setf (testclass25-pair x) p))
+              (succeeds (setf (second p) 456))
+              (succeeds (testclass25-pair x))
+              (succeeds (slot-value x 'pair))))))
+  Expected: (t t t nil t)
+  Got:      (t t t t t)
+
+  (inspect (first (sb-pcl:generic-function-methods #'testclass25-pair)))
+  shows that the method was created with a FAST-FUNCTION slot but with a
+  FUNCTION slot of NIL.
+
+362: missing error when a slot-definition is created without a name
+    (reported by Bruno Haible)
+  The MOP says about slot-definition initialization:
+  "The :NAME argument is a slot name. An ERROR is SIGNALled if this argument
+   is not a symbol which can be used as a variable name. An ERROR is SIGNALled
+   if this argument is not supplied."
+  Test case:
+   (make-instance (find-class 'sb-pcl:standard-direct-slot-definition))
+  Expected: ERROR
+  Got: #<SB-MOP:STANDARD-DIRECT-SLOT-DEFINITION NIL>
+
+363: missing error when a slot-definition is created with a wrong documentation object
+    (reported by Bruno Haible)
+  The MOP says about slot-definition initialization:
+  "The :DOCUMENTATION argument is a STRING or NIL. An ERROR is SIGNALled
+   if it is not. This argument default to NIL during initialization."
+  Test case:
+   (make-instance (find-class 'sb-pcl:standard-direct-slot-definition)
+                  :name 'foo
+                  :documentation 'not-a-string)
+  Expected: ERROR
+  Got: #<SB-MOP:STANDARD-DIRECT-SLOT-DEFINITION FOO>
+
+364: does not support class objects as specializer names
+   (reported by Bruno Haible)
+  According to ANSI CL 7.6.2, class objects are valid specializer names,
+  and "Parameter specializer names are used in macros intended as the
+  user-level interface (defmethod)". DEFMETHOD's syntax section doesn't
+  mention this possibility in the BNF for parameter-specializer-name;
+  however, this appears to be an editorial omission, since the CLHS
+  mentions issue CLASS-OBJECT-SPECIALIZER:AFFIRM as being approved
+  by X3J13. SBCL doesn't support it:
+   (defclass foo () ())
+   (defmethod goo ((x #.(find-class 'foo))) x)
+  Expected: #<STANDARD-METHOD GOO (#<STANDARD-CLASS FOO>)>
+  Got:      ERROR "#<STANDARD-CLASS FOO> is not a legal class name."
+
+365: mixin on generic-function subclass
+    (reported by Bruno Haible)
+  a mixin class
+    (defclass prioritized-dispatcher ()
+      ((dependents :type list :initform nil)))
+  on a generic-function subclass:
+    (defclass prioritized-generic-function (prioritized-dispatcher standard-generic-function)
+      ()
+      (:metaclass sb-pcl:funcallable-standard-class))
+  SBCL gives an error on this, telling to define a method on SB-MOP:VALIDATE-SUPERCLASS. If done,
+    (defmethod sb-pcl:validate-superclass ((c1 sb-pcl:funcallable-standard-class) 
+                                           (c2 (eql (find-class 'prioritized-dispatcher))))
+      t)
+  then, however,
+    (defclass prioritized-generic-function (prioritized-dispatcher standard-generic-function)
+      ()
+      (:metaclass sb-pcl:funcallable-standard-class))
+  => debugger invoked on a SIMPLE-ERROR in thread 6687:
+    layout depth conflict: #(#<SB-KERNEL:LAYOUT for T {500E1E9}> ...)
+  Further discussion on this: http://thread.gmane.org/gmane.lisp.steel-bank.general/491
+
+366: cannot define two generic functions with user-defined class
+   (reported by Bruno Haible)
+  it is possible to define one generic function class and an instance
+  of it. But attempting to do the same thing again, in the same session,
+  leads to a "Control stack exhausted" error. Test case:
+    (defclass my-generic-function-1 (standard-generic-function)
+      ()
+      (:metaclass sb-pcl:funcallable-standard-class))
+    (defgeneric testgf-1 (x) (:generic-function-class my-generic-function-1)
+      (:method ((x integer)) (cons 'integer nil)))
+    (defclass my-generic-function-2 (standard-generic-function)
+      ()
+      (:metaclass sb-pcl:funcallable-standard-class))
+    (defgeneric testgf-2 (x) (:generic-function-class my-generic-function-2)
+      (:method ((x integer)) (cons 'integer nil)))
+  => SB-KERNEL::CONTROL-STACK-EXHAUSTED
+
+367: TYPE-ERROR at compile time, undetected TYPE-ERROR at runtime
+  This test program
+    (declaim (optimize (safety 3) (debug 2) (speed 2) (space 1)))
+    (defstruct e367)
+    (defstruct i367)
+    (defstruct g367
+      (i367s (make-array 0 :fill-pointer t) :type (or (vector i367) null)))
+    (defstruct s367
+      (g367 (error "missing :G367") :type g367 :read-only t))
+    ;;; In sbcl-0.8.18, commenting out this (DECLAIM (FTYPE ... R367))
+    ;;; gives an internal error at compile time:
+    ;;;    The value #<SB-KERNEL:NAMED-TYPE NIL> is not of
+    ;;;    type SB-KERNEL:VALUES-TYPE.
+    (declaim (ftype (function ((vector i367) e367) (or s367 null)) r367))
+    (declaim (ftype (function ((vector e367)) (values)) h367))
+    (defun frob (v w)
+      (let ((x (g367-i367s (make-g367))))
+        (let* ((y (or (r367 x w)
+                      (h367 x)))
+               (z (s367-g367 y)))
+          (format t "~&Y=~S Z=~S~%" y z)
+          (g367-i367s z))))
+    (defun r367 (x y) (declare (ignore x y)) nil)
+    (defun h367 (x) (declare (ignore x)) (values))
+    ;;; In sbcl-0.8.18, executing this form causes an low-level error
+    ;;;   segmentation violation at #X9B0E1F4
+    ;;; (instead of the TYPE-ERROR that one might like).
+    (frob 0 (make-e367))
+  can be made to cause two different problems, as noted in the comments:
+    bug 367a: Compile and load the file. No TYPE-ERROR is signalled at 
+      run time (in the (S367-G367 Y) form of FROB, when Y is NIL 
+      instead of an instance of S367). Instead (on x86/Linux at least)
+      we end up with a segfault.
+    bug 367b: Comment out the (DECLAIM (FTYPE ... R367)), and compile 
+      the file. The compiler fails with TYPE-ERROR at compile time.
+
+368: miscompiled OR (perhaps related to bug 367)
+  Trying to relax type declarations to find a workaround for bug 367,
+  it turns out that even when the return type isn't declared (or 
+  declared to be T, anyway) the system remains confused about type 
+  inference in code similar to that for bug 367:
+    (in-package :cl-user)
+    (declaim (optimize (safety 3) (debug 2) (speed 2) (space 1)))
+    (defstruct e368)
+    (defstruct i368)
+    (defstruct g368
+      (i368s (make-array 0 :fill-pointer t) :type (or (vector i368) null)))
+    (defstruct s368
+      (g368 (error "missing :G368") :type g368 :read-only t))
+    (declaim (ftype (function (fixnum (vector i368) e368) t) r368))
+    (declaim (ftype (function (fixnum (vector e368)) t) h368))
+    (defparameter *h368-was-called-p* nil)
+    (defun nsu (vertices e368)
+      (let ((i368s (g368-i368s (make-g368))))
+        (let ((fuis (r368 0 i368s e368)))
+          (format t "~&FUIS=~S~%" fuis)
+          (or fuis (h368 0 i368s)))))
+    (defun r368 (w x y)
+      (declare (ignore w x y))
+      nil)
+    (defun h368 (w x)
+      (declare (ignore w x))
+      (setf *h368-was-called-p* t)
+      (make-s368 :g368 (make-g368)))
+    (trace r368 h368)
+    (format t "~&calling NSU~%")
+    (let ((nsu (nsu #() (make-e368))))
+      (format t "~&NSU returned ~S~%" nsu)
+      (format t "~&*H368-WAS-CALLED-P*=~S~%" *h368-was-called-p*)
+      (assert (s368-p nsu))
+      (assert *h368-was-called-p*))
+  In sbcl-0.8.18, both ASSERTs fail, and (DISASSEMBLE 'NSU) shows
+  that no call to H368 is compiled.
+
+369: unlike-an-intersection behavior of VALUES-TYPE-INTERSECTION
+  In sbcl-0.8.18.2, the identity $(x \cap y \cap y)=(x \cap y)$ 
+  does not hold for VALUES-TYPE-INTERSECTION, even for types which
+  can be intersected exactly, so that ASSERTs fail in this test case:
+    (in-package :cl-user)
+    (let ((types (mapcar #'sb-c::values-specifier-type 
+                         '((values (vector package) &optional)
+                           (values (vector package) &rest t)
+                           (values (vector hash-table) &rest t)
+                           (values (vector hash-table) &optional)
+                           (values t &optional)
+                           (values t &rest t)
+                           (values nil &optional)
+                           (values nil &rest t)
+                           (values sequence &optional)
+                           (values sequence &rest t)
+                           (values list &optional)
+                           (values list &rest t)))))
+       (dolist (x types)
+         (dolist (y types)
+           (let ((i (sb-c::values-type-intersection x y)))
+             (assert (sb-c::type= i (sb-c::values-type-intersection i x)))
+             (assert (sb-c::type= i (sb-c::values-type-intersection i y)))))))
+
+370: reader misbehaviour on large-exponent floats
+    (read-from-string "1.0s1000000000000000000000000000000000000000")
+  causes the reader to attempt to create a very large bignum (which it
+  will then attempt to coerce to a rational).  While this isn't
+  completely wrong, it is probably not ideal -- checking the floating
+  point control word state and then returning the relevant float
+  (most-positive-short-float or short-float-infinity) or signalling an
+  error immediately would seem to make more sense.
+
+372: floating-point overflow not signalled on ppc/darwin
+ The following assertions in float.pure.lisp fail on ppc/darwin 
+ (Mac OS X version 10.3.7):
+   (assert (raises-error? (scale-float 1.0 most-positive-fixnum)
+                         floating-point-overflow))
+   (assert (raises-error? (scale-float 1.0d0 (1+ most-positive-fixnum))
+                          floating-point-overflow)))
+ as the SCALE-FLOAT just returns 
+ #.SB-EXT:SINGLE/DOUBLE-FLOAT-POSITIVE-INFINITY. These tests have been
+ disabled on Darwin for now.
+
+374: BIT-AND problem on ppc/darwin:
+  The BIT-AND test in bit-vector.impure-cload.lisp results in
+    fatal error encountered in SBCL pid 8356:
+    GC invariant lost, file "gc-common.c", line 605
+  on ppc/darwin. Test disabled for the duration.
+
+375: MISC.555
+    (compile nil '(lambda (p1)
+                   (declare (optimize (speed 1) (safety 2) (debug 2) (space 0))
+                            (type keyword p1))
+                   (keywordp p1)))
+
+  fails on hairy type check in IR2.
+
+  1. KEYWORDP is MAYBE-INLINE expanded (before TYPEP-like
+     transformation could eliminate it).
+
+  2. From the only call of KEYWORDP the type of its argument is
+     derived to be KEYWORD.
+
+  2. Type check for P1 is generated; it uses KEYWORDP to perform the
+     check, and so references the local function; from the KEYWORDP
+     argument type new CAST to KEYWORD is generated. The compiler
+     loops forever.
+
+377: Memory fault error reporting
+  On those architectures where :C-STACK-IS-CONTROL-STACK is in
+  *FEATURES*, we handle SIG_MEMORY_FAULT (SEGV or BUS) on an altstack,
+  so we cannot handle the signal directly (as in interrupt_handle_now())
+  in the case when the signal comes from some external agent (the user
+  using kill(1), or a fault in some foreign code, for instance).  As
+  of sbcl-0.8.20.20, this is fixed by calling
+  arrange_return_to_lisp_function() to a new error-signalling
+  function, but as a result the error reporting is poor: we cannot
+  even tell the user at which address the fault occurred.  We should
+  arrange such that arguments can be passed to the function called from
+  arrange_return_to_lisp_function(), but this looked hard to do in
+  general without suffering from memory leaks.
+
+378: floating-point exceptions not signalled on x86-64
+  Floating point traps are currently not enabled on the x86-64 port.
+  This is true for at least overflow detection (as tested in
+  float.pure.lisp) and divide-by-zero.
+
+379: TRACE :ENCAPSULATE NIL broken on ppc/darwin
+  See commented-out test-case in debug.impure.lisp.