1.0.3.23: fix sb-posix timeval struct
[sbcl.git] / BUGS
diff --git a/BUGS b/BUGS
index 0e0dfaf..f97463e 100644 (file)
--- a/BUGS
+++ b/BUGS
@@ -84,37 +84,19 @@ WORKAROUND:
 
   d: (fixed in 0.8.1.5)
 
 
   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.
 
 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.
 
 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.
 
+  Currently INSPECT and DESCRIBE do show the values, but showing the
+  names of the bindings would be even nicer.
+
 35:
   The compiler assumes that any time a function of declared FTYPE
   doesn't signal an error, its arguments were of the declared type.
 35:
   The compiler assumes that any time a function of declared FTYPE
   doesn't signal an error, its arguments were of the declared type.
@@ -156,10 +138,6 @@ WORKAROUND:
   so they could be supported after all. Very likely 
   SIGCONTEXT-FLOATING-POINT-MODES could now be supported, too.
 
   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))
 61:
   Compiling and loading
     (DEFUN FAIL (X) (THROW 'FAIL-TAG X))
@@ -167,11 +145,11 @@ WORKAROUND:
   then requesting a BACKTRACE at the debugger prompt gives no information
   about where in the user program the problem occurred.
 
   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
   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
 
 64:
   Using the pretty-printer from the command prompt gives funny
@@ -220,19 +198,6 @@ WORKAROUND:
   holding... * is not equivalent to T in many cases, such as 
     (VECTOR *) /= (VECTOR T).
 
   holding... * is not equivalent to T in many cases, such as 
     (VECTOR *) /= (VECTOR T).
 
-95:
-  The facility for dumping a running Lisp image to disk gets confused
-  when run without the PURIFY option, and creates an unnecessarily large
-  core file (apparently representing memory usage up to the previous
-  high-water mark). Moreover, when the file is loaded, it confuses the
-  GC, so that thereafter memory usage can never be reduced below that
-  level.
-
-  (As of 0.8.7.3 it's likely that the latter half of this bug is fixed.
-  The interaction between gencgc and the variables used by
-  save-lisp-and-die is still nonoptimal, though, so no respite from
-  big core files yet)
-
 98:
   In sbcl-0.6.11.41 (and in all earlier SBCL, and in CMU
   CL), out-of-line structure slot setters are horribly inefficient
 98:
   In sbcl-0.6.11.41 (and in all earlier SBCL, and in CMU
   CL), out-of-line structure slot setters are horribly inefficient
@@ -378,24 +343,6 @@ WORKAROUND:
    a STYLE-WARNING for references to variables similar to locals might
    be a good thing.)
 
    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,
 135:
   Ideally, uninterning a symbol would allow it, and its associated
   FDEFINITION and PROCLAIM data, to be reclaimed by the GC. However,
@@ -437,6 +384,10 @@ WORKAROUND:
   conformance problem, since seems hard to construct useful code
   where it matters.)
 
   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:
   b. (fixed in 0.8.3.43)
 
 146:
@@ -562,6 +513,13 @@ WORKAROUND:
      classes).  This means that at present erroneous attempts to use
      WITH-SLOTS and the like on classes with metaclass STRUCTURE-CLASS
      won't get the corresponding STYLE-WARNING.
      classes).  This means that at present erroneous attempts to use
      WITH-SLOTS and the like on classes with metaclass STRUCTURE-CLASS
      won't get the corresponding STYLE-WARNING.
+
+     [much later, in 2006-08] in fact it's no longer erroneous to use
+     WITH-SLOTS on structure-classes.  However, including :METACLASS
+     STRUCTURE-CLASS in the class definition gives a whole bunch of
+     function redefinition warnings, so we're still not good to close
+     this bug...
+
   c. (fixed in 0.8.4.23)
 
 201: "Incautious type inference from compound types"
   c. (fixed in 0.8.4.23)
 
 201: "Incautious type inference from compound types"
@@ -624,18 +582,6 @@ WORKAROUND:
 211: "keywords processing"
   a. :ALLOW-OTHER-KEYS T should allow a function to receive an odd
      number of keyword arguments.
 211: "keywords processing"
   a. :ALLOW-OTHER-KEYS T should allow a function to receive an odd
      number of keyword arguments.
-  e. Compiling
-
-      (flet ((foo (&key y) (list y)))
-        (list (foo :y 1 :y 2)))
-
-     issues confusing message
-
-       ; in: LAMBDA NIL
-       ;     (FOO :Y 1 :Y 2)
-       ;
-       ; caught STYLE-WARNING:
-       ;   The variable #:G15 is defined but never used.
 
 212: "Sequence functions and circular arguments"
   COERCE, MERGE and CONCATENATE go into an infinite loop when given
 
 212: "Sequence functions and circular arguments"
   COERCE, MERGE and CONCATENATE go into an infinite loop when given
@@ -689,40 +635,6 @@ WORKAROUND:
 
   This is probably the same bug as 162
 
 
   This is probably the same bug as 162
 
-217: "Bad type operations with FUNCTION types"
-  In sbcl.0.7.7:
-
-    * (values-type-union (specifier-type '(function (base-char)))
-                         (specifier-type '(function (integer))))
-
-    #<FUN-TYPE (FUNCTION (BASE-CHAR) *)>
-
-  It causes insertion of wrong type assertions into generated
-  code. E.g.
-
-    (defun foo (x s)
-      (let ((f (etypecase x
-                 (character #'write-char)
-                 (integer #'write-byte))))
-        (funcall f x s)
-        (etypecase x
-          (character (write-char x s))
-          (integer (write-byte x s)))))
-
-   Then (FOO #\1 *STANDARD-OUTPUT*) signals type error.
-
-  (In 0.7.9.1 the result type is (FUNCTION * *), so Python does not
-  produce invalid code, but type checking is not accurate.)
-
-233: bugs in constraint propagation
-  b.
-  (declaim (optimize (speed 2) (safety 3)))
-  (defun foo (x y)
-    (if (typep (prog1 x (setq x y)) 'double-float)
-        (+ x 1d0)
-        (+ x 2)))
-  (foo 1d0 5) => segmentation violation
-
 235: "type system and inline expansion"
   a.
   (declaim (ftype (function (cons) number) acc))
 235: "type system and inline expansion"
   a.
   (declaim (ftype (function (cons) number) acc))
@@ -738,6 +650,10 @@ WORKAROUND:
 
   (foo '(nil) '(t)) => NIL, T.
 
 
   (foo '(nil) '(t)) => NIL, T.
 
+  As of 0.9.15.41 this seems to be due to ACC being inlined only once
+  inside FOO, which results in the second call reusing the FUNCTIONAL
+  resulting from the first -- which doesn't check the type.
+
 237: "Environment arguments to type functions"
   a. Functions SUBTYPEP, TYPEP, UPGRADED-ARRAY-ELEMENT-TYPE, and 
      UPGRADED-COMPLEX-PART-TYPE now have an optional environment
 237: "Environment arguments to type functions"
   a. Functions SUBTYPEP, TYPEP, UPGRADED-ARRAY-ELEMENT-TYPE, and 
      UPGRADED-COMPLEX-PART-TYPE now have an optional environment
@@ -781,6 +697,11 @@ WORKAROUND:
   (UNSIGNED-BYTE 8) will write to the stream one byte at a time,
   rather than writing the sequence in one go, leading to severe
   performance degradation.
   (UNSIGNED-BYTE 8) will write to the stream one byte at a time,
   rather than writing the sequence in one go, leading to severe
   performance degradation.
+  As of sbcl-0.9.0.36, this is solved for fd-streams, so is less of a
+  problem in practice.  (Fully fixing this would require adding a
+  ansi-stream-n-bout slot and associated methods to write a byte
+  sequence to ansi-stream, similar to the existing ansi-stream-sout
+  slot/functions.)
 
 243: "STYLE-WARNING overenthusiasm for unused variables"
   (observed from clx compilation)
 
 243: "STYLE-WARNING overenthusiasm for unused variables"
   (observed from clx compilation)
@@ -861,26 +782,12 @@ WORKAROUND:
   b. The same for CSUBTYPEP.
 
 262: "yet another bug in inline expansion of local functions"
   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
 
 266:
   David Lichteblau provided (sbcl-devel 2003-06-01) a patch to fix
@@ -940,16 +847,13 @@ WORKAROUND:
 
   (fixed in 0.8.2.51, but a test case would be good)
 
 
   (fixed in 0.8.2.51, but a test case would be good)
 
-278:
-  a.
-    (defun foo ()
-      (declare (optimize speed))
-      (loop for i of-type (integer 0) from 0 by 2 below 10
-            collect i))
-
-  uses generic arithmetic.
-
-  b. (fixed in 0.8.3.6)
+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
 
 279: type propagation error -- correctly inferred type goes astray?
   In sbcl-0.8.3 and sbcl-0.8.1.47, the warning
 
 279: type propagation error -- correctly inferred type goes astray?
   In sbcl-0.8.3 and sbcl-0.8.1.47, the warning
@@ -976,32 +880,12 @@ WORKAROUND:
 
  (see also bug 117)
 
 
  (see also bug 117)
 
-281: COMPUTE-EFFECTIVE-METHOD error signalling.
-  (slightly obscured by a non-0 default value for
-   SB-PCL::*MAX-EMF-PRECOMPUTE-METHODS*)
-  It would be natural for COMPUTE-EFFECTIVE-METHOD to signal errors
-  when it finds a method with invalid qualifiers.  However, it
-  shouldn't signal errors when any such methods are not applicable to
-  the particular call being evaluated, and certainly it shouldn't when
-  simply precomputing effective methods that may never be called.
-  (setf sb-pcl::*max-emf-precompute-methods* 0)
-  (defgeneric foo (x)
-    (:method-combination +)
-    (:method ((x symbol)) 1)
-    (:method + ((x number)) x))
-  (foo 1) -> ERROR, but should simply return 1
-
-  The issue seems to be that construction of a discriminating function
-  calls COMPUTE-EFFECTIVE-METHOD with methods that are not all applicable.
-
 283: Thread safety: libc functions
   There are places that we call unsafe-for-threading libc functions
   that we should find alternatives for, or put locks around.  Known or
 283: Thread safety: libc functions
   There are places that we call unsafe-for-threading libc functions
   that we should find alternatives for, or put locks around.  Known or
-  strongly suspected problems, as of 0.8.3.10: please update this
+  strongly suspected problems, as of 1.0.3.13: please update this
   bug instead of creating new ones
 
   bug instead of creating new ones
 
-    localtime() - called for timezone calculations in code/time.lisp
-
 284: Thread safety: special variables
   There are lots of special variables in SBCL, and I feel sure that at
   least some of them are indicative of potentially thread-unsafe 
 284: Thread safety: special variables
   There are lots of special variables in SBCL, and I feel sure that at
   least some of them are indicative of potentially thread-unsafe 
@@ -1016,15 +900,6 @@ WORKAROUND:
   (tail)-recursive simplification pass and transforms/VOPs for base
   cases.
 
   (tail)-recursive simplification pass and transforms/VOPs for base
   cases.
 
-287: PPC/Linux miscompilation or corruption in first GC
-  When the runtime is compiled with -O3 on certain PPC/Linux machines, a
-  segmentation fault is reported at the point of first triggered GC,
-  during the compilation of DEFSTRUCT WRAPPER.  As a temporary workaround,
-  the runtime is no longer compiled with -O3 on PPC/Linux, but it is likely
-  that this merely obscures, not solves, the underlying problem; as and when
-  underlying problems are fixed, it would be worth trying again to provoke
-  this problem.
-
 288: fundamental cross-compilation issues (from old UGLINESS file)
   Using host floating point numbers to represent target floating point
   numbers, or host characters to represent target characters, is
 288: fundamental cross-compilation issues (from old UGLINESS file)
   Using host floating point numbers to represent target floating point
   numbers, or host characters to represent target characters, is
@@ -1062,14 +937,6 @@ WORKAROUND:
   the control word; however, this clobbers any change the user might
   have made.
 
   the control word; however, this clobbers any change the user might
   have made.
 
-296:
-  (reported by Adam Warner, sbcl-devel 2003-09-23)
-
-  The --load toplevel argument does not perform any sanitization of its
-  argument.  As a result, files with Lisp pathname pattern characters
-  (#\* or #\?, for instance) or quotation marks can cause the system
-  to perform arbitrary behaviour.
-
 297:
   LOOP with non-constant arithmetic step clauses suffers from overzealous
   type constraint: code of the form 
 297:
   LOOP with non-constant arithmetic step clauses suffers from overzealous
   type constraint: code of the form 
@@ -1101,14 +968,6 @@ WORKAROUND:
   gives the error
     failed AVER: "(NOT (AND (NOT EQUALP) CERTAINP))"
 
   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
 303: "nonlinear LVARs" (aka MISC.293)
     (defun buu (x)
       (multiple-value-call #'list
@@ -1126,25 +985,9 @@ WORKAROUND:
 
   The problem is that both EVALs sequentially write to the same LVAR.
 
 
   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"
 306: "Imprecise unions of array types"
-  a.(defun foo (x)
-      (declare (optimize speed)
-               (type (or (array cons) (array vector)) x))
-      (elt (aref x 0) 0))
-    (foo #((0))) => TYPE-ERROR
 
 
-  relatedly,
+  a. fixed in SBCL 0.9.15.48
 
   b.(subtypep 
      'array
 
   b.(subtypep 
      'array
@@ -1153,23 +996,6 @@ WORKAROUND:
                collect `(array ,(sb-vm:saetp-specifier x)))))
     => NIL, T (when it should be T, T)
 
                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)
 309: "Dubious values for implementation limits"
     (reported by Bruno Haible sbcl-devel "Incorrect value of
     multiple-values-limit" 2004-04-19)
@@ -1180,13 +1006,6 @@ WORKAROUND:
   around the same time regarding a call to LIST on sparc with 1000
   arguments) and other implementation limit constants.
 
   around the same time regarding a call to LIST on sparc with 1000
   arguments) and other implementation limit constants.
 
-311: "Tokeniser not thread-safe"
-    (see also Robert Marlow sbcl-help "Multi threaded read chucking a
-    spak" 2004-04-19)
-  The tokenizer's use of *read-buffer* and *read-buffer-length* causes
-  spurious errors should two threads attempt to tokenise at the same
-  time.
-
 314: "LOOP :INITIALLY clauses and scope of initializers"
   reported by Bruno Haible sbcl-devel "various SBCL bugs" from CLISP
   test suite, originally by Thomas F. Burdick.
 314: "LOOP :INITIALLY clauses and scope of initializers"
   reported by Bruno Haible sbcl-devel "various SBCL bugs" from CLISP
   test suite, originally by Thomas F. Burdick.
@@ -1204,28 +1023,23 @@ WORKAROUND:
     Expected: (2 6 15 38)
     Got:      ERROR
 
     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.
 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)
     (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
 
 319: "backquote with comma inside array"
   reported by Bruno Haible sbcl-devel "various SBCL bugs" from CLISP
@@ -1235,20 +1049,6 @@ WORKAROUND:
     #(1 2 ((SB-IMPL::|,|) + 2 2) 4)
   which probably isn't intentional.
 
     #(1 2 ((SB-IMPL::|,|) + 2 2) 4)
   which probably isn't intentional.
 
-323: "REPLACE, BIT-BASH and large strings"
-  The transform for REPLACE on simple-base-strings uses BIT-BASH, which
-  at present has an upper limit in size.  Consequently, in sbcl-0.8.10
-    (defun foo ()
-      (declare (optimize speed (safety 1)))
-      (let ((x (make-string 140000000))
-            (y (make-string 140000000)))
-        (length (replace x y))))
-    (foo)
-  gives 
-    debugger invoked on a TYPE-ERROR in thread 2412:
-      The value 1120000000 is not of type (MOD 536870911).
-  (see also "more and better sequence transforms" sbcl-devel 2004-05-10)
-
 324: "STREAMs and :ELEMENT-TYPE with large bytesize"
   In theory, (open foo :element-type '(unsigned-byte <x>)) should work
   for all positive integral <x>.  At present, it only works for <x> up
 324: "STREAMs and :ELEMENT-TYPE with large bytesize"
   In theory, (open foo :element-type '(unsigned-byte <x>)) should work
   for all positive integral <x>.  At present, it only works for <x> up
@@ -1339,12 +1139,6 @@ WORKAROUND:
      in the wrapper, and then to update the instance just run through
      all the old wrappers in order from oldest to newest.
 
      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
 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
@@ -1384,101 +1178,6 @@ WORKAROUND:
   Fixing this should also fix a subset of #328 -- update the
   description with a new test-case then.
 
   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)
 
 339: "DEFINE-METHOD-COMBINATION bugs"
   (reported by Bruno Haible via the clisp test suite)
 
@@ -1501,67 +1200,7 @@ WORKAROUND:
    iii. supplied-p variables for &optional and &key arguments are not
         bound.
 
    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.
+  c. (fixed in sbcl-0.9.15.15)
 
 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
 
 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
@@ -1576,32 +1215,10 @@ WORKAROUND:
   (Note: there's at least one dubious thing in room.lisp: see the
   comment in VALID-OBJ)
 
   (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".
 
 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
 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
@@ -1612,3 +1229,580 @@ WORKAROUND:
   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?)
   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.
+
+  [ Is this actually a bug?  DEFCLASS only replaces an existing class
+    when the class name is the proper name of that class, and in the
+    above code the class found by (FIND-CLASS 'A) does not have a
+    proper name.  CSR, 2006-08-07 ]
+
+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.
+
+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."
+
+  [ This test case does not cause the error any more.  However,
+    similar problems can be observed with 
+
+    (defclass foo (standard-class) ()
+      (:metaclass sb-mop:funcallable-standard-class))
+    (sb-mop:finalize-inheritance (find-class 'foo))
+    ;; ERROR, ABORT
+    (defclass bar (standard-class) ())
+    (make-instance 'bar)
+  ]
+
+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)
+
+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>
+
+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>
+
+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.
+
+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.
+
+379: TRACE :ENCAPSULATE NIL broken on ppc/darwin
+  See commented-out test-case in debug.impure.lisp.
+
+380: Accessor redefinition fails because of old accessor name
+  When redefining an accessor, SB-PCL::FIX-SLOT-ACCESSORS may try to
+  find the generic function named by the old accessor name using
+  ENSURE-GENERIC-FUNCTION and then remove the old accessor's method in
+  the GF. If the old name does not name a function, or if the old name
+  does not name a generic function, no attempt to find the GF or remove
+  any methods is made.
+
+  However, if an unrelated GF with an incompatible lambda list exists,
+  the class redefinition will fail when SB-PCL::REMOVE-READER-METHOD
+  tries to find and remove a method with an incompatible lambda list
+  from the unrelated generic function.
+
+381: incautious calls to EQUAL in fasl dumping
+  Compiling 
+    (frob #(#1=(a #1#)))
+    (frob #(#1=(b #1#)))
+    (frob #(#1=(a #1#)))
+  in sbcl-0.9.0 causes CONTROL-STACK-EXHAUSTED. My (WHN) impression 
+  is that this follows from the use of (MAKE-HASH-TABLE :TEST 'EQUAL)
+  to detect sharing, in which case fixing it might require either 
+  getting less ambitious about detecting shared list structure, or 
+  implementing the moral equivalent of EQUAL hash tables in a 
+  cycle-tolerant way.
+
+382: externalization unexpectedly changes array simplicity
+  COMPILE-FILE and LOAD
+    (defun foo ()
+      (let ((x #.(make-array 4 :fill-pointer 0)))
+        (values (eval `(typep ',x 'simple-array))
+                (typep x 'simple-array))))
+  then (FOO) => T, NIL.
+
+  Similar problems exist with SIMPLE-ARRAY-P, ARRAY-HEADER accessors
+  and all array dimension functions.
+
+383: ASH'ing non-constant zeros
+  Compiling
+    (lambda (b)
+      (declare (type (integer -2 14) b))
+      (declare (ignorable b))
+      (ash (imagpart b) 57))
+  on PPC (and other platforms, presumably) gives an error during the
+  emission of FASH-ASH-LEFT/FIXNUM=>FIXNUM as the assembler attempts to
+  stuff a too-large constant into the immediate field of a PPC
+  instruction.  Either the VOP should be fixed or the compiler should be
+  taught how to transform this case away, paying particular attention
+  to side-effects that might occur in the arguments to ASH.
+
+384: Compiler runaway on very large character types
+
+  (compile nil '(lambda (x)
+                    (declare (type (member #\a 1) x))
+                    (the (member 1 nil) x)))
+
+  The types apparently normalize into a very large type, and the compiler
+  gets lost in REMOVE-DUPLICATES.  Perhaps the latter should use
+  a better algorithm (one based on hash tables, say) on very long lists
+  when :TEST has its default value?
+
+  A simpler example:
+
+  (compile nil '(lambda (x) (the (not (eql #\a)) x)))
+
+  (partially fixed in 0.9.3.1, but a better representation for these
+   types is needed.)
+
+385:
+  (format nil "~4,1F" 0.001) => "0.00" (should be " 0.0");
+  (format nil "~4,1@F" 0.001) => "+.00" (should be "+0.0").
+
+386: SunOS/x86 stack exhaustion handling broken
+  According to <http://alfa.s145.xrea.com/sbcl/solaris-x86.html>, the
+  stack exhaustion checking (implemented with a write-protected guard
+  page) does not work on SunOS/x86.
+
+388:
+  (found by Dmitry Bogomolov)
+
+    (defclass foo () ((x :type (unsigned-byte 8))))
+    (defclass bar () ((x :type symbol)))
+    (defclass baz (foo bar) ())
+
+  causes error
+
+    SB-PCL::SPECIALIZER-APPLICABLE-USING-TYPE-P cannot handle the second argument
+    (UNSIGNED-BYTE 8).
+
+  [ Can't trigger this any more, as of 2006-08-07 ]
+
+389:
+  (reported several times on sbcl-devel, by Rick Taube, Brian Rowe and
+  others)
+
+  ROUND-NUMERIC-BOUND assumes that float types always have a FORMAT
+  specifying whether they're SINGLE or DOUBLE.  This is true for types
+  computed by the type system itself, but the compiler type derivation
+  short-circuits this and constructs non-canonical types.  A temporary
+  fix was made to ROUND-NUMERIC-BOUND for the sbcl-0.9.6 release, but
+  the right fix is to remove the abstraction violation in the
+  compiler's type deriver.
+
+393: Wrong error from methodless generic function
+    (DEFGENERIC FOO (X))
+    (FOO 1 2)
+  gives NO-APPLICABLE-METHOD rather than an argument count error.
+
+395: Unicode and streams
+  One of the remaining problems in SBCL's Unicode support is the lack
+  of generality in certain streams.
+  a. FILL-POINTER-STREAMs: SBCL refuses to write (e.g. using FORMAT)
+     to streams made from strings that aren't character strings with
+     fill-pointers:
+       (let ((v (make-array 5 :fill-pointer 0 :element-type 'standard-char)))
+         (format v "foo")
+         v)
+     should return a non-simple base string containing "foo" but
+     instead errors.
+
+     (reported on sbcl-help by "tichy")
+
+396: block-compilation bug
+    (let ((x 1))
+      (dotimes (y 10)
+        (let ((y y))
+          (when (funcall (eval #'(lambda (x) (eql x 2))) y)
+            (defun foo (z)
+              (incf x (incf y z))))))
+      (defun bar (z)
+        (foo z)
+        (values x)))
+  (bar 1) => 11, should be 4.
+
+397: SLEEP accuracy
+  The more interrupts arrive the less accurate SLEEP's timing gets.
+    (time (sb-thread:terminate-thread
+            (prog1 (sb-thread:make-thread (lambda ()
+                                            (loop
+                                             (princ #\!)
+                                             (force-output)
+                                             (sb-ext:gc))))
+              (sleep 1))))
+
+398: GC-unsafe SB-ALIEN string deporting
+  Translating a Lisp string to an alien string by taking a SAP to it
+  as done by the :DEPORT-GEN methods for C-STRING and UTF8-STRING
+  is not safe, since the Lisp string can move. For example the
+  following code will fail quickly on both cheneygc and pre-0.9.8.19
+  GENCGC: 
+
+  (setf (bytes-consed-between-gcs) 4096)
+  (define-alien-routine "strcmp" int (s1 c-string) (s2 c-string))
+     
+  (loop
+    (let ((string "hello, world"))
+       (assert (zerop (strcmp string string)))))
+     
+  (This will appear to work on post-0.9.8.19 GENCGC, since
+   the GC no longer zeroes memory immediately after releasing
+   it after a minor GC. Either enabling the READ_PROTECT_FREE_PAGES
+   #define in gencgc.c or modifying the example so that a major
+   GC will occasionally be triggered would unmask the bug.)
+
+  On cheneygc the only solution would seem to be allocating some alien
+  memory, copying the data over, and arranging that it's freed once we
+  return. For GENCGC we could instead try to arrange that the string
+  from which the SAP is taken is always pinned.
+
+  For some more details see comments for (define-alien-type-method
+  (c-string :deport-gen) ...)  in host-c-call.lisp.
+
+402: "DECLAIM DECLARATION does not inform the PCL code-walker"
+  reported by Vincent Arkesteijn:
+
+  (declaim (declaration foo))
+  (defgeneric bar (x))
+  (defmethod bar (x)
+    (declare (foo x))
+    x)
+
+  ==> WARNING: The declaration FOO is not understood by
+      SB-PCL::SPLIT-DECLARATIONS.
+      Please put FOO on one of the lists SB-PCL::*NON-VAR-DECLARATIONS*,
+      SB-PCL::*VAR-DECLARATIONS-WITH-ARG*, or
+      SB-PCL::*VAR-DECLARATIONS-WITHOUT-ARG*.
+      (Assuming it is a variable declaration without argument).
+
+403: FORMAT/PPRINT-LOGICAL-BLOCK of CONDITIONs ignoring *PRINT-CIRCLE*
+  In sbcl-0.9.13.34,
+    (defparameter *c*
+      (make-condition 'simple-error
+                      :format-control "ow... ~S"
+                      :format-arguments '(#1=(#1#))))
+    (setf *print-circle* t *print-level* 4)
+    (format nil "~@<~A~:@>" *c*)
+  gives
+    "ow... (((#)))"
+  where I (WHN) believe the correct result is "ow... #1=(#1#)",
+  like the result from (PRINC-TO-STRING *C*). The question of 
+  what the correct result is is complicated by the hairy text in 
+  the Hyperspec "22.3.5.2 Tilde Less-Than-Sign: Logical Block",
+    Other than the difference in its argument, ~@<...~:> is 
+    exactly the same as ~<...~:> except that circularity detection 
+    is not applied if ~@<...~:> is encountered at top level in a 
+    format string.
+  But because the odd behavior happens even without the at-sign, 
+    (format nil "~<~A~:@>" (list *c*)) ; => "ow... (((#)))"
+  and because something seemingly similar can happen even in 
+  PPRINT-LOGICAL-BLOCK invoked directly without FORMAT, 
+    (pprint-logical-block (*standard-output* '(some nonempty list))
+      (format *standard-output* "~A" '#1=(#1#)))
+  (which prints "(((#)))" to *STANDARD-OUTPUT*), I don't think 
+  that the 22.3.5.2 trickiness is fundamental to the problem.
+
+  My guess is that the problem is related to the logic around the MODE
+  argument to CHECK-FOR-CIRCULARITY, but I haven't reverse-engineered
+  enough of the intended meaning of the different MODE values to be
+  confident of this.
+
+404: nonstandard DWIMness in LOOP with unportably-ordered clauses
+  In sbcl-0.9.13, the code
+    (loop with stack = (make-array 2 :fill-pointer 2 :initial-element t)
+          for length = (length stack)
+          while (plusp length)
+          for element = (vector-pop stack)
+          collect element)
+  compiles without error or warning and returns (T T). Unfortunately, 
+  it is inconsistent with the ANSI definition of the LOOP macro, 
+  because it mixes up VARIABLE-CLAUSEs with MAIN-CLAUSEs. Furthermore,
+  SBCL's interpretation of the intended meaning is only one possible,
+  unportable interpretation of the noncompliant code; in CLISP 2.33.2, 
+  the code compiles with a warning
+    LOOP: FOR clauses should occur before the loop's main body
+  and then fails at runtime with 
+    VECTOR-POP: #() has length zero
+  perhaps because CLISP has shuffled the clauses into an 
+  ANSI-compliant order before proceeding.
+
+405: a TYPE-ERROR in MERGE-LETS exercised at DEBUG 3
+  In sbcl-0.9.16.21 on linux/86, compiling 
+    (declaim (optimize (debug 3)))
+    (defstruct foo bar)
+    (let ()
+      (flet ((i (x) (frob x (foo-bar foo))))
+        (i :five)))
+  causes a TYPE-ERROR 
+    The value NIL is not of type SB-C::PHYSENV.
+  in MERGE-LETS.
+
+406: functional has external references -- failed aver
+ Given the following food in a single file
+  (eval-when (:compile-toplevel :load-toplevel :execute)
+    (defstruct foo3))
+  (defstruct bar
+    (foo #.(make-foo3)))
+ as of 0.9.18.11 the file compiler breaks on it:
+  failed AVER: "(NOT (FUNCTIONAL-HAS-EXTERNAL-REFERENCES-P CLAMBDA))"
+ Defining the missing MAKE-LOAD-FORM method makes the error go away.
+
+407: misoptimization of loop, COERCE 'FLOAT, and HANDLER-CASE for bignums
+  (reported by Ariel Badichi on sbcl-devel 2007-01-09)
+  407a: In sbcl-1.0.1 on Linux x86, 
+               (defun foo ()
+                 (loop for n from (expt 2 1024) do
+                       (handler-case
+                           (coerce n 'single-float)
+                         (simple-type-error ()
+                           (format t "Got here.~%")
+                           (return-from foo)))))
+               (foo)
+        causes an infinite loop, where handling the error would be expected.
+  407b: In sbcl-1.0.1 on Linux x86, 
+               (defun bar ()
+                 (loop for n from (expt 2 1024) do
+                       (handler-case
+                           (format t "~E~%" (coerce n 'single-float))
+                         (simple-type-error ()
+                           (format t "Got here.~%")
+                           (return-from bar)))))
+        fails to compile, with
+               Too large to be represented as a SINGLE-FLOAT: ...
+       from
+               0: ((LABELS SB-BIGNUM::CHECK-EXPONENT) ...)
+               1: ((LABELS SB-BIGNUM::FLOAT-FROM-BITS) ...)
+               2: (SB-KERNEL:%SINGLE-FLOAT ...)
+               3: (SB-C::BOUND-FUNC ...)
+               4: (SB-C::%SINGLE-FLOAT-DERIVE-TYPE-AUX ...)
+
+408: SUBTYPEP confusion re. OR of SATISFIES of not-yet-defined predicate
+       As reported by Levente M\'{e}sz\'{a}ros sbcl-devel 2006-02-20,
+               (aver (equal (multiple-value-list
+                             (subtypep '(or (satisfies x) string)
+                                       '(or (satisfies x) integer)))
+                            '(nil nil)))
+       fails. Also, beneath that failure lurks another failure,
+               (aver (equal (multiple-value-list
+                              (subtypep 'string
+                                       '(or (satisfies x) integer)))
+                            '(nil nil)))
+       Having looked at this for an hour or so in sbcl-1.0.2, and
+       specifically having looked at the output from
+         laptop$ sbcl
+         * (let ((x 'string)
+                 (y '(or (satisfies x) integer)))
+             (trace sb-kernel::union-complex-subtypep-arg2
+                    sb-kernel::invoke-complex-subtypep-arg1-method
+                    sb-kernel::type-union
+                    sb-kernel::type-intersection
+                    sb-kernel::type=)
+             (subtypep x y))
+       my (WHN) impression is that the problem is that the semantics of TYPE=
+       are wrong for what the UNION-COMPLEX-SUBTYPEP-ARG2 code is trying
+       to use it for. The comments on the definition of TYPE= probably
+       date back to CMU CL and seem to define it as a confusing thing:
+       its primary value is something like "certainly equal," and its
+       secondary value is something like "certain about that certainty."
+       I'm left uncertain how to fix UNION-COMPLEX-SUBTYPEP-ARG2 without
+       reducing its generality by removing the TYPE= cleverness. Possibly
+       the tempting TYPE/= relative defined next to it might be a
+       suitable replacement for the purpose. Probably, though, it would
+       be best to start by reverse engineering exactly what TYPE= and
+       TYPE/= do, and writing an explanation which is so clear that one
+       can see immediately what it's supposed to mean in odd cases like
+       (TYPE= '(SATISFIES X) 'INTEGER) when X isn't defined yet.
+
+409: MORE TYPE SYSTEM PROBLEMS
+  Found while investigating an optimization failure for extended
+  sequences. The extended sequence type implementation was altered to
+  work around the problem, but the fundamental problem remains, to wit:
+    (sb-kernel:type= (sb-kernel:specifier-type '(or float ratio))
+                     (sb-kernel:specifier-type 'single-float))
+  returns NIL, NIL on sbcl-1.0.3.
+  (probably related to bug #408)
+
+410: read circularities and type declarations
+  Consider the definition
+    (defstruct foo (a 0 :type (not symbol)))
+  followed by
+    (setf *print-circle* t) ; just in case
+    (read-from-string "#1=#s(foo :a #1#)")
+  This gives a type error (#:G1 is not a (NOT SYMBOL)) because of the
+  implementation of read circularity, using a symbol as a marker for
+  the previously-referenced object.