0.8.17.30:
[sbcl.git] / BUGS
diff --git a/BUGS b/BUGS
index 5b3d799..010c3b7 100644 (file)
--- a/BUGS
+++ b/BUGS
@@ -104,9 +104,10 @@ WORKAROUND:
 32:
   The printer doesn't report closures very well. This is true in 
   CMU CL 18b as well:
-    (PRINT #'CLASS-NAME)
+    (defstruct foo bar)
+    (print #'foo-bar)
   gives
-    #<Closure Over Function "DEFUN STRUCTURE-SLOT-ACCESSOR" {134D1A1}>
+    #<FUNCTION "CLOSURE" {406974D5}>
   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.
@@ -167,11 +168,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
@@ -437,6 +438,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 +866,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
@@ -1101,14 +1092,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
@@ -1153,23 +1136,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)
@@ -1217,15 +1183,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
@@ -1339,12 +1310,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
@@ -1536,13 +1501,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
@@ -1576,32 +1534,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
@@ -1613,38 +1549,413 @@ WORKAROUND:
   pprinter and only truncated at output?  (So that indenting by 1/2
   then 3/2 would indent by two spaces, not one?)
 
-350: heap overflow when printing bignums
-  (reported by Bruno Haible 2004-10-08)
-  In sbcl-0.8.15.18,
-    * (DEFPARAMETER *BIG* (ASH 1 1000000))
-    *BIG*
-    * (PRINT *BIG*)
-    Argh! gc_find_freeish_pages failed (restart_page), nbytes=110152.
-  It should be straightforward to push the heap overflow threshold
-  up to much larger bignums; CSR pointed out it would help to use a 
-  bignum-printing algorithm which bisected the printed number,
-  rather than stripping off digits one by one.
-
-351: suboptimal error handling/reporting when compiling (PUSH (LET ...)) 
-  In sbcl-0.8.15.18,
-    * (defvar *b*)
-    *B*
-    * (defun oops ()
-        (push *b*
-              (let ((b *b*))
-                (aref b 1))))
-  causes the compiler to die with a TYPE-ERROR in SB-C::EXTRACT-LET-VARS,
-    The value #:G4 is not of type LIST.
-  Since the (LET ...) expression is being misused in PUSH as a 
-  SETFable place, it would be more helpful to fail as in 
-    * (defun oops2 () (setf (let ((b *b*)) (aref b 1)) *b*))
-  with compiler conditions errors like 
-    ; in: LAMBDA NIL
-    ;     ((B *B*))
-    ; caught ERROR:
-    ;   illegal function call
-  and
-    ; caught WARNING:
-    ;   The function (SETF LET) is undefined, and its name is reserved 
-    ;   by ANSI CL so that even if it were defined later, the code 
-    ;   doing so would not be portable.
+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.
+
+ 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)
+
+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
+