0.8.16.43: Fixes for various CLOS/MOP bugs
[sbcl.git] / BUGS
diff --git a/BUGS b/BUGS
index f75671b..48ca825 100644 (file)
--- a/BUGS
+++ b/BUGS
@@ -156,25 +156,6 @@ WORKAROUND:
   so they could be supported after all. Very likely 
   SIGCONTEXT-FLOATING-POINT-MODES could now be supported, too.
 
-45:
-  a slew of floating-point-related errors reported by Peter Van Eynde
-  on July 25, 2000:
-       c: Many expressions generate floating infinity on x86/Linux:
-               (/ 1 0.0)
-               (/ 1 0.0d0)
-               (EXPT 10.0 1000)
-               (EXPT 10.0d0 1000)
-          PVE's regression tests want them to raise errors. sbcl-0.7.0.5
-          on x86/Linux generates the infinities instead. That might or
-          might not be conforming behavior, but it's also inconsistent,
-           which is almost certainly wrong. (Inconsistency: (/ 1 0.0)
-          should give the same result as (/ 1.0 0.0), but instead (/ 1 0.0)
-          generates SINGLE-FLOAT-POSITIVE-INFINITY and (/ 1.0 0.0)
-          signals an error.
-       d: (in section12.erg) various forms a la 
-               (FLOAT 1 DOUBLE-FLOAT-EPSILON)
-          don't give the right behavior.
-
 60:
   The debugger LIST-LOCATIONS command doesn't work properly.
   (How should it work properly?)
@@ -186,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
@@ -209,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
@@ -359,34 +332,6 @@ WORKAROUND:
 
   (see also bug 279)
 
-118:
-   as reported by Eric Marsden on cmucl-imp@cons.org 2001-08-14:
-     (= (FLOAT 1 DOUBLE-FLOAT-EPSILON)
-        (+ (FLOAT 1 DOUBLE-FLOAT-EPSILON) DOUBLE-FLOAT-EPSILON)) => T
-   when of course it should be NIL. (He says it only fails for X86,
-   not SPARC; dunno about Alpha.)
-
-   Also, "the same problem exists for LONG-FLOAT-EPSILON,
-   DOUBLE-FLOAT-NEGATIVE-EPSILON, LONG-FLOAT-NEGATIVE-EPSILON (though
-   for the -negative- the + is replaced by a - in the test)."
-
-   Raymond Toy comments that this is tricky on the X86 since its FPU
-   uses 80-bit precision internally.
-
-   Bruno Haible comments:
-     The values are those that are expected for an IEEE double-float
-     arithmetic. The problem appears to be that the rounding is not
-     IEEE on x86 compliant: namely, values are first rounded to 64
-     bits mantissa precision, then only to 53 bits mantissa
-     precision. This gives different results than rounding to 53 bits
-     mantissa precision in a single step.
-
-     The quick "fix", to permanently change the FPU control word from
-     0x037f to 0x027f, will give problems with the fdlibm code that is
-     used for computing transcendental functions like sinh() etc.
-   so maybe we need to change the FPU control word to that for Lisp
-   code, and adjust it to the safe 0x037f for calls to C?
-
 124:
    As of version 0.pre7.14, SBCL's implementation of MACROLET makes
    the entire lexical environment at the point of MACROLET available
@@ -461,15 +406,6 @@ WORKAROUND:
   forever, even when it is uninterned and all other references to it
   are lost.
 
-141: "pretty printing and backquote"
-  a.
-    * '``(FOO ,@',@S)
-    ``(FOO SB-IMPL::BACKQ-COMMA-AT S)
-
-  c. (reported by Paul F. Dietz)
-     * '`(lambda ,x)
-     `(LAMBDA (SB-IMPL::BACKQ-COMMA X))
-
 143:
   (reported by Jesse Bouwman 2001-10-24 through the unfortunately
   prominent SourceForge web/db bug tracking system, which is 
@@ -537,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 
@@ -939,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
@@ -978,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:
 
@@ -1021,14 +926,6 @@ WORKAROUND:
 
   (fixed in 0.8.2.51, but a test case would be good)
 
-276:
-    (defmethod fee ((x fixnum))
-      (setq x (/ x 2))
-      x)
-    (fee 1) => type error
-
-  (taken from CLOCC)
-
 278:
   a.
     (defun foo ()
@@ -1190,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
@@ -1242,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)
@@ -1306,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
@@ -1381,13 +1258,13 @@ WORKAROUND:
     (let ((tsos (make-string-output-stream))
           (ssos (make-string-output-stream)))
       (let ((*print-circle* t)
-       (*trace-output* tsos)
-       (*standard-output* ssos))
+           (*trace-output* tsos)
+           (*standard-output* ssos))
         (prin1 *tangle* *standard-output*))
       (let ((string (get-output-stream-string ssos)))
         (unless (string= string "(#1=[FOO 4] #S(BAR) #1#)")
           ;; In sbcl-0.8.10.48 STRING was "(#1=[FOO 4] #2# #1#)".:-(
-          (error "oops: ~S" string))))
+          (error "oops: ~S" string)))))
   It might be straightforward to fix this by turning the
   *CIRCULARITY-HASH-TABLE* and *CIRCULARITY-COUNTER* variables into
   per-stream slots, but (1) it would probably be sort of messy faking
@@ -1453,61 +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).
-   
-335: "ATANH completely broken"
-  a. (reported by Peter Graves sbcl-devel 2004-06-01)
-    (atanh #c(1 2)), and more generally atanh of any complex with real
-    part 1, computes entirely the wrong answer.
-  b. (discovered by CSR when investigating a.)
-    (atanh most-positive-double-float), and more generally atanh of any
-    number with magnitude larger than
-    sqrt(most-positive-double-float), computes a number whose real
-    part is the imaginary part of the correct answer, and whose
-    imaginary part is the real part of the correct answer.
-  (fixes for both of these were sent CSR sbcl-devel 2004-06-02, to be merged
-   post-0.8.11)
-
 336: "slot-definitions must retain the generic functions of accessors"
   reported by Tony Martinez:
     (defclass foo () ((bar :reader foo-bar)))
@@ -1527,3 +1349,245 @@ WORKAROUND:
 
   Fixing this should also fix a subset of #328 -- update the
   description with a new test-case then.
+
+337: MAKE-METHOD and user-defined method classes
+  (reported by Bruno Haible sbcl-devel 2004-06-11)
+
+  In the presence of  
+
+(defclass user-method (standard-method) (myslot))
+(defmacro def-user-method (name &rest rest)
+  (let* ((lambdalist-position (position-if #'listp rest))
+         (qualifiers (subseq rest 0 lambdalist-position))
+         (lambdalist (elt rest lambdalist-position))
+         (body (subseq rest (+ lambdalist-position 1)))
+         (required-part 
+          (subseq lambdalist 0 (or 
+                                (position-if 
+                                 (lambda (x) (member x lambda-list-keywords))
+                                 lambdalist)
+                                (length lambdalist))))
+         (specializers (mapcar #'find-class 
+                               (mapcar (lambda (x) (if (consp x) (second x) t))
+                                       required-part)))
+         (unspecialized-required-part 
+          (mapcar (lambda (x) (if (consp x) (first x) x)) required-part))
+         (unspecialized-lambdalist 
+          (append unspecialized-required-part 
+           (subseq lambdalist (length required-part)))))
+    `(PROGN
+       (ADD-METHOD #',name
+         (MAKE-INSTANCE 'USER-METHOD
+          :QUALIFIERS ',qualifiers
+          :LAMBDA-LIST ',unspecialized-lambdalist
+          :SPECIALIZERS ',specializers
+          :FUNCTION
+          (LAMBDA (ARGUMENTS NEXT-METHODS-LIST)
+            (FLET ((NEXT-METHOD-P () NEXT-METHODS-LIST)
+                   (CALL-NEXT-METHOD (&REST NEW-ARGUMENTS)
+                     (UNLESS NEW-ARGUMENTS (SETQ NEW-ARGUMENTS ARGUMENTS))
+                     (IF (NULL NEXT-METHODS-LIST)
+                         (ERROR "no next method for arguments ~:S" ARGUMENTS)
+                         (FUNCALL (SB-PCL:METHOD-FUNCTION 
+                                   (FIRST NEXT-METHODS-LIST))
+                                  NEW-ARGUMENTS (REST NEXT-METHODS-LIST)))))
+              (APPLY #'(LAMBDA ,unspecialized-lambdalist ,@body) ARGUMENTS)))))
+       ',name)))
+
+  (progn
+    (defgeneric test-um03 (x))
+    (defmethod test-um03 ((x integer))
+      (list* 'integer x (not (null (next-method-p))) (call-next-method)))
+    (def-user-method test-um03 ((x rational))
+      (list* 'rational x (not (null (next-method-p))) (call-next-method)))
+    (defmethod test-um03 ((x real))
+      (list 'real x (not (null (next-method-p)))))
+    (test-um03 17))
+  works, but
+
+  a.(progn
+      (defgeneric test-um10 (x))
+      (defmethod test-um10 ((x integer))
+        (list* 'integer x (not (null (next-method-p))) (call-next-method)))
+      (defmethod test-um10 ((x rational))
+        (list* 'rational x (not (null (next-method-p))) (call-next-method)))
+      (defmethod test-um10 ((x real))
+        (list 'real x (not (null (next-method-p)))))
+      (defmethod test-um10 :after ((x real)))
+      (def-user-method test-um10 :around ((x integer))
+        (list* 'around-integer x 
+         (not (null (next-method-p))) (call-next-method)))
+      (defmethod test-um10 :around ((x rational))
+        (list* 'around-rational x 
+         (not (null (next-method-p))) (call-next-method)))
+      (defmethod test-um10 :around ((x real))
+        (list* 'around-real x (not (null (next-method-p))) (call-next-method)))
+      (test-um10 17))
+    fails with a type error, and
+
+  b.(progn
+      (defgeneric test-um12 (x))
+      (defmethod test-um12 ((x integer))
+        (list* 'integer x (not (null (next-method-p))) (call-next-method)))
+      (defmethod test-um12 ((x rational))
+        (list* 'rational x (not (null (next-method-p))) (call-next-method)))
+      (defmethod test-um12 ((x real))
+        (list 'real x (not (null (next-method-p)))))
+      (defmethod test-um12 :after ((x real)))
+      (defmethod test-um12 :around ((x integer))
+        (list* 'around-integer x 
+         (not (null (next-method-p))) (call-next-method)))
+      (defmethod test-um12 :around ((x rational))
+        (list* 'around-rational x 
+         (not (null (next-method-p))) (call-next-method)))
+      (def-user-method test-um12 :around ((x real))
+        (list* 'around-real x (not (null (next-method-p))) (call-next-method)))
+      (test-um12 17))
+    fails with NO-APPLICABLE-METHOD.
+
+339: "DEFINE-METHOD-COMBINATION bugs"
+  (reported by Bruno Haible via the clisp test suite)
+
+  a. Syntax checking laxity (should produce errors):
+     i. (define-method-combination foo :documentation :operator)
+    ii. (define-method-combination foo :documentation nil)
+   iii. (define-method-combination foo nil)
+    iv. (define-method-combination foo nil nil
+         (:arguments order &aux &key))
+     v. (define-method-combination foo nil nil (:arguments &whole))
+    vi. (define-method-combination foo nil nil (:generic-function))
+   vii. (define-method-combination foo nil nil (:generic-function bar baz))
+  viii. (define-method-combination foo nil nil (:generic-function (bar)))
+    ix. (define-method-combination foo nil ((3)))
+     x. (define-method-combination foo nil ((a)))
+
+  b. define-method-combination arguments lambda list badness
+     i. &aux args are currently unsupported;
+    ii. default values of &optional and &key arguments are ignored;
+   iii. supplied-p variables for &optional and &key arguments are not
+        bound.
+
+  c. qualifier matching incorrect
+  (progn
+    (define-method-combination mc27 () 
+        ((normal ()) 
+         (ignored (:ignore :unused)))
+      `(list 'result 
+             ,@(mapcar #'(lambda (method) `(call-method ,method)) normal)))
+    (defgeneric test-mc27 (x)
+      (:method-combination mc27)
+      (:method :ignore ((x number)) (/ 0)))
+    (test-mc27 7))
+
+  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.