0.7.7.13:
[sbcl.git] / BUGS
diff --git a/BUGS b/BUGS
index fc6d731..211bc1d 100644 (file)
--- a/BUGS
+++ b/BUGS
@@ -1,4 +1,4 @@
-REPORTING BUGS
+tREPORTING BUGS
 
 Bugs can be reported on the help mailing list
   sbcl-help@lists.sourceforge.net
@@ -89,6 +89,9 @@ WORKAROUND:
   also unstable in several ways, including its inability
   to really grok function declarations.
 
+  As of sbcl-0.7.5, sbcl's cross-compiler does run with
+  *TYPE-SYSTEM-INITIALIZED*; however, this bug remains.
+
 7:
   The "compiling top-level form:" output ought to be condensed.
   Perhaps any number of such consecutive lines ought to turn into a
@@ -142,37 +145,12 @@ WORKAROUND:
   DTC's recommended workaround from the mailing list 3 Mar 2000:
        (setf (pcl::find-class 'ccc1) (pcl::find-class 'ccc))
 
-22:
-  The ANSI spec, in section "22.3.5.2 Tilde Less-Than-Sign: Logical Block",
-  says that an error is signalled if ~W, ~_, ~<...~:>, ~I, or ~:T is used
-  inside "~<..~>" (without the colon modifier on the closing syntax).
-  However, SBCL doesn't do this:
-       * (FORMAT T "~<munge~wegnum~>" 12)
-       munge12egnum
-       NIL
-
 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.
 
-31:
-  In some cases the compiler believes type declarations on array
-  elements without checking them, e.g.
-       (DECLAIM (OPTIMIZE (SAFETY 3) (SPEED 1) (SPACE 1)))
-       (DEFSTRUCT FOO A B)
-       (DEFUN BAR (X)
-         (DECLARE (TYPE (SIMPLE-ARRAY CONS 1) X))
-         (WHEN (CONSP (AREF X 0))
-           (PRINT (AREF X 0))))
-       (BAR (VECTOR (MAKE-FOO :A 11 :B 12)))
-  prints
-       #S(FOO :A 11 :B 12) 
-  in SBCL 0.6.5 (and also in CMU CL 18b). This does not happen for
-  all cases, e.g. the type assumption *is* checked if the array
-  elements are declared to be of some structure type instead of CONS.
-
 32:
   The printer doesn't report closures very well. This is true in 
   CMU CL 18b as well:
@@ -285,9 +263,6 @@ WORKAROUND:
           MERGE also have the same problem.
        c: (COERCE 'AND 'FUNCTION) returns something related to
           (MACRO-FUNCTION 'AND), but ANSI says it should raise an error.
-       f: (FLOAT-RADIX 2/3) should signal an error instead of 
-          returning 2.
-       g: (LOAD "*.lsp") should signal FILE-ERROR.
        h: (MAKE-CONCATENATED-STREAM (MAKE-STRING-OUTPUT-STREAM))
           should signal TYPE-ERROR.
        i: MAKE-TWO-WAY-STREAM doesn't check that its arguments can
@@ -295,10 +270,6 @@ WORKAROUND:
           TYPE-ERROR when handed e.g. the results of
           MAKE-STRING-INPUT-STREAM or MAKE-STRING-OUTPUT-STREAM in
           the inappropriate positions, but doesn't.
-       j: (PARSE-NAMESTRING (COERCE (LIST #\f #\o #\o (CODE-CHAR 0) #\4 #\8)
-                           (QUOTE STRING)))
-          should probably signal an error instead of making a pathname with
-          a null byte in it.
        k: READ-BYTE is supposed to signal TYPE-ERROR when its argument is 
           not a binary input stream, but instead cheerfully reads from
           character streams, e.g. (MAKE-STRING-INPUT-STREAM "abc").
@@ -317,10 +288,6 @@ WORKAROUND:
 
 48:
   SYMBOL-MACROLET bugs reported by Peter Van Eynde July 25, 2000:
-       a: (SYMBOL-MACROLET ((T TRUE)) ..) should probably signal
-          PROGRAM-ERROR, but SBCL accepts it instead.
-       b: SYMBOL-MACROLET should refuse to bind something which is
-          declared as a global variable, signalling PROGRAM-ERROR.
        c: SYMBOL-MACROLET should signal PROGRAM-ERROR if something
           it binds is declared SPECIAL inside.
 
@@ -413,59 +380,6 @@ WORKAROUND:
   the new output block should start indented 2 or more characters
   rightward of the correct location.
 
-65:
-  (probably related to bug #70; maybe related to bug #109)
-  As reported by Carl Witty on submit@bugs.debian.org 1999-05-08,
-  compiling this file
-(in-package "CL-USER")
-(defun equal-terms (termx termy)
-  (labels
-    ((alpha-equal-bound-term-lists (listx listy)
-       (or (and (null listx) (null listy))
-          (and listx listy
-               (let ((bindings-x (bindings-of-bound-term (car listx)))
-                     (bindings-y (bindings-of-bound-term (car listy))))
-                 (if (and (null bindings-x) (null bindings-y))
-                     (alpha-equal-terms (term-of-bound-term (car listx))
-                                        (term-of-bound-term (car listy)))
-                     (and (= (length bindings-x) (length bindings-y))
-                          (prog2
-                              (enter-binding-pairs (bindings-of-bound-term (car listx))
-                                                   (bindings-of-bound-term (car listy)))
-                              (alpha-equal-terms (term-of-bound-term (car listx))
-                                                 (term-of-bound-term (car listy)))
-                            (exit-binding-pairs (bindings-of-bound-term (car listx))
-                                                (bindings-of-bound-term (car listy)))))))
-               (alpha-equal-bound-term-lists (cdr listx) (cdr listy)))))
-
-     (alpha-equal-terms (termx termy)
-       (if (and (variable-p termx)
-               (variable-p termy))
-          (equal-bindings (id-of-variable-term termx)
-                          (id-of-variable-term termy))
-          (and (equal-operators-p (operator-of-term termx) (operator-of-term termy))
-               (alpha-equal-bound-term-lists (bound-terms-of-term termx)
-                                             (bound-terms-of-term termy))))))
-
-    (or (eq termx termy)
-       (and termx termy
-            (with-variable-invocation (alpha-equal-terms termx termy))))))
-  causes an assertion failure
-    The assertion (EQ (C::LAMBDA-TAIL-SET C::CALLER)
-                      (C::LAMBDA-TAIL-SET (C::LAMBDA-HOME C::CALLEE))) failed.
-
-  Bob Rogers reports (1999-07-28 on cmucl-imp@cons.org) a smaller test
-  case with the same problem:
-(defun parse-fssp-alignment ()
-  ;; Given an FSSP alignment file named by the argument . . .
-  (labels ((get-fssp-char ()
-            (get-fssp-char))
-          (read-fssp-char ()
-            (get-fssp-char)))
-    ;; Stub body, enough to tickle the bug.
-    (list (read-fssp-char)
-         (read-fssp-char))))
-
 66:
   ANSI specifies that the RESULT-TYPE argument of CONCATENATE must be
   a subtype of SEQUENCE, but CONCATENATE doesn't check this properly:
@@ -483,6 +397,8 @@ WORKAROUND:
   doesn't seem to exist for sequence types:
     (DEFTYPE BAR () 'SIMPLE-VECTOR)
     (CONCATENATE 'BAR #(1 2) '(3)) => #(1 2 3)
+  See also bug #46a./b., and discussion and patch sbcl-devel and
+  cmucl-imp 2002-07
 
 67:
   As reported by Winton Davies on a CMU CL mailing list 2000-01-10,
@@ -490,41 +406,6 @@ WORKAROUND:
   crashes SBCL. In general tracing anything which is used in the 
   implementation of TRACE is likely to have the same problem.
 
-68: 
-  As reported by Daniel Solaz on cmucl-help@cons.org 2000-11-23,
-  SXHASH returns the same value for all non-STRUCTURE-OBJECT instances,
-  notably including all PCL instances. There's a limit to how much
-  SXHASH can do to return unique values for instances, but at least
-  it should probably look at the class name, the way that it does
-  for STRUCTURE-OBJECTs.
-
-70:
-  (probably related to bug #65; maybe related to bug #109)
-  The compiler doesn't like &OPTIONAL arguments in LABELS and FLET
-  forms. E.g.
-    (DEFUN FIND-BEFORE (ITEM SEQUENCE &KEY (TEST #'EQL))
-      (LABELS ((FIND-ITEM (OBJ SEQ TEST &OPTIONAL (VAL NIL))
-                 (LET ((ITEM (FIRST SEQ)))
-                  (COND ((NULL SEQ)
-                         (VALUES NIL NIL))
-                        ((FUNCALL TEST OBJ ITEM)
-                         (VALUES VAL SEQ))
-                        (T     
-                         (FIND-ITEM OBJ (REST SEQ) TEST (NCONC VAL `(,ITEM))))))))
-      (FIND-ITEM ITEM SEQUENCE TEST)))
-  from David Young's bug report on cmucl-help@cons.org 30 Nov 2000
-  causes sbcl-0.6.9 to fail with
-    error in function SB-KERNEL:ASSERT-ERROR:
-       The assertion (EQ (SB-C::LAMBDA-TAIL-SET SB-C::CALLER)
-                         (SB-C::LAMBDA-TAIL-SET
-                          (SB-C::LAMBDA-HOME SB-C::CALLEE))) failed.
-
-71: 
-  (DECLAIM (OPTIMIZE ..)) doesn't work. E.g. even after 
-  (DECLAIM (OPTIMIZE (SPEED 3))), things are still optimized with
-  the previous SPEED policy. This bug will probably get fixed in
-  0.6.9.x in a general cleanup of optimization policy.
-
 72:
   (DECLAIM (OPTIMIZE ..)) doesn't work properly inside LOCALLY forms.
 
@@ -586,26 +467,6 @@ WORKAROUND:
   (I haven't tried to investigate this bug enough to guess whether
   there might be any user-level symptoms.)
 
-90: 
-  a latent cross-compilation/bootstrapping bug: The cross-compilation
-  host's CL:CHAR-CODE-LIMIT is used in target code in readtable.lisp
-  and possibly elsewhere. Instead, we should use the target system's
-  CHAR-CODE-LIMIT. This will probably cause problems if we try to 
-  bootstrap on a system which uses a different value of CHAR-CODE-LIMIT
-  than SBCL does.
-
-91:
-  (subtypep '(or (integer -1 1)
-                 unsigned-byte)
-            '(or (rational -1 7)
-                 unsigned-byte
-                 (integer -1 1))) => NIL,T
-  An analogous problem with SINGLE-FLOAT and REAL types was fixed in 
-  sbcl-0.6.11.22, but some peculiarites of the RATIO type make it 
-  awkward to generalize the fix to INTEGER and RATIONAL. It's not 
-  clear what's the best fix. (See the "bug in type handling" discussion
-  on cmucl-imp ca. 2001-03-22 and ca. 2001-02-12.)
-
 94a: 
   Inconsistencies between derived and declared VALUES return types for
   DEFUN aren't checked very well. E.g. the logic which successfully
@@ -642,11 +503,6 @@ WORKAROUND:
   GC, so that thereafter memory usage can never be reduced below that
   level.
 
-96:
-  The TRACE facility can't be used on some kinds of functions.
-  (Basically, the breakpoint facility was incompletely implemented
-  in the X86 port of CMU CL, and hasn't been fixed in SBCL.)
-
 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
@@ -689,15 +545,6 @@ WORKAROUND:
   the first time around, until regression tests are written I'm not 
   comfortable merging the patches in the CVS version of SBCL.
 
-102:
-  As reported by Arthur Lemmens sbcl-devel 2001-05-05, ANSI
-  requires that SYMBOL-MACROLET refuse to rebind special variables,
-  but SBCL doesn't do this. (Also as reported by AL in the same
-  message, SBCL depended on this nonconforming behavior to build
-  itself, because of the way that **CURRENT-SEGMENT** was implemented.
-  As of sbcl-0.6.12.x, this dependence on the nonconforming behavior
-  has been fixed, but the nonconforming behavior remains.)
-
 104:
   (DESCRIBE 'SB-ALIEN:DEF-ALIEN-TYPE) reports the macro argument list
   incorrectly:
@@ -717,25 +564,6 @@ WORKAROUND:
   time trying to GC afterwards. Surely there's some more economical
   way to implement (ROOM T).
 
-109:
-  reported by Martin Atzmueller 2001-06-25; originally from CMU CL bugs
-  collection:
-    ;;; This file fails to compile.
-    ;;; Maybe this bug is related to bugs #65, #70 in the BUGS file.
-    (in-package :cl-user)
-    (defun tst2 ()
-      (labels 
-          ((eff (&key trouble)
-             (eff)
-             ;; nil
-             ;; Uncomment and it works
-             ))
-        (eff)))
-  In SBCL 0.6.12.42, the problem is
-    internal error, failed AVER:
-      "(COMMON-LISP:EQ (SB!C::LAMBDA-TAIL-SET SB!C::CALLER)
-                  (SB!C::LAMBDA-TAIL-SET (SB!C::LAMBDA-HOME SB!C::CALLEE)))"
-
 110:
   reported by Martin Atzmueller 2001-06-25; originally from CMU CL bugs
   collection:
@@ -831,19 +659,6 @@ WORKAROUND:
    Raymond Toy comments that this is tricky on the X86 since its FPU
    uses 80-bit precision internally.
 
-120a:
-   The compiler incorrectly figures the return type of 
-       (DEFUN FOO (FRAME UP-FRAME)
-         (IF (OR (NOT FRAME)
-                 T)
-             FRAME
-             "BAR"))
-   as NIL.
-
-   This problem exists in CMU CL 18c too. When I reported it on
-   cmucl-imp@cons.org, Raymond Toy replied 23 Aug 2001 with 
-   a partial explanation, but no fix has been found yet.
-
 120b:
    Even in sbcl-0.pre7.x, which is supposed to be free of the old
    non-ANSI behavior of treating the function return type inferred
@@ -857,7 +672,9 @@ WORKAROUND:
    (IF (NOT (IGNORE-ERRORS ..))). E.g.
        (defun foo1i ()
          (if (not (ignore-errors
-                    (make-pathname :host "foo" :directory "!bla" :name "bar")))
+                    (make-pathname :host "foo"
+                                    :directory "!bla"
+                                    :name "bar")))
              (print "ok")
              (error "notunlessnot")))
    The (NOT (IGNORE-ERRORS ..)) form evaluates to T, so this should be
@@ -870,18 +687,6 @@ WORKAROUND:
    #+NIL) and I'd like to go back to see whether this really is
    a compiler bug before I delete this BUGS entry.
 
-123:
-   The *USE-IMPLEMENTATION-TYPES* hack causes bugs, particularly
-     (IN-PACKAGE :SB-KERNEL)
-     (TYPE= (SPECIFIER-TYPE '(VECTOR T))
-           (SPECIFIER-TYPE '(VECTOR UNDEFTYPE)))
-   Then because of this, the compiler bogusly optimizes
-       (TYPEP #(11) '(SIMPLE-ARRAY UNDEF-TYPE 1))
-   to T. Unfortunately, just setting *USE-IMPLEMENTATION-TYPES* to 
-   NIL around sbcl-0.pre7.14.flaky4.12 didn't work: the compiler complained
-   about type mismatches (probably harmlessly, another instance of bug 117);
-   and then cold init died with a segmentation fault.
-
 124:
    As of version 0.pre7.14, SBCL's implementation of MACROLET makes
    the entire lexical environment at the point of MACROLET available
@@ -940,9 +745,6 @@ WORKAROUND:
    Evidently Python thinks of the lambda as a code transformation so
    much that it forgets that it's also an object.
 
-126:
-  (fixed in 0.pre7.41)
-
 127:
   The DEFSTRUCT section of the ANSI spec, in the :CONC-NAME section,
   specifies a precedence rule for name collisions between slot accessors of
@@ -1033,18 +835,6 @@ WORKAROUND:
       (let ((x (1+ x)))
         (call-next-method)))
   Now (FOO 3) should return 3, but instead it returns 4.
-    
-137:
-  (SB-DEBUG:BACKTRACE) output should start with something
-  including the name BACKTRACE, not (as in 0.pre7.88)
-  just "0: (\"hairy arg processor\" ...)". Until about
-  sbcl-0.pre7.109, the names in BACKTRACE were all screwed
-  up compared to the nice useful names in sbcl-0.6.13.
-  Around sbcl-0.pre7.109, they were mostly fixed by using
-  NAMED-LAMBDA to implement DEFUN. However, there are still
-  some screwups left, e.g. as of sbcl-0.pre7.109, there are
-  still some functions named "hairy arg processor" and
-  "SB-INT:&MORE processor".
 
 140:
   (reported by Alexey Dejneka sbcl-devel 2002-01-03)
@@ -1071,10 +861,10 @@ WORKAROUND:
   T
   T
 
-  This is probably due to underzealous clearing of the type caches; a
-  brute-force solution in that case would be to make a defclass expand
-  into something that included a call to SB-KERNEL::CLEAR-TYPE-CACHES,
-  but there may be a better solution.
+  This bug was fixed in sbcl-0.7.4.1 by invalidating the PCL wrapper
+  class upon redefinition. Unfortunately, doing so causes bug #176 to
+  appear.  Pending further investication, one or other of these bugs
+  might be present at any given time.
 
 141: 
   Pretty-printing nested backquotes doesn't work right, as 
@@ -1146,54 +936,8 @@ WORKAROUND:
   It should be possible to be much more specific (overflow, division
   by zero, etc.) and of course the "How can this be?" should be fixable.
 
-147:
-  (reported by Alexey Dejneka sbcl-devel 2002-01-28)
-  Compiling a file containing
-    (deftype digit () '(member #\1))
-    (defun parse-num (string ind)
-      (flet ((digs ()
-               (let (old-index)
-                 (if (and (< ind ind)
-                          (typep (char string ind) 'digit))
-                     nil))))))
-  in sbcl-0.7.1 causes the compiler to fail with
-    internal error, failed AVER: "(= (LENGTH (BLOCK-SUCC CALL-BLOCK)) 1)" 
-  This problem seems to have been introduced by the sbcl-0.pre7.* compiler
-  changes, since 0.pre7.73 and 0.6.13 don't suffer from it. A related
-  test case is
-    (defun parse-num (index)
-      (let (num x)
-        (flet ((digs ()
-                 (setq num index))
-               (z ()
-                 (let ()
-                   (setq x nil))))
-          (when (and (digs) (digs)) x))))
-  In sbcl-0.7.1, this second test case failed with the same
-    internal error, failed AVER: "(= (LENGTH (BLOCK-SUCC CALL-BLOCK)) 1)" 
-  After the APD patches in sbcl-0.7.1.2 (new consistency check in
-  TARGET-IF-DESIRABLE, plus a fix in meta-vmdef.lisp to keep the
-  new consistency check from failing routinely) this second test case
-  failed in FIND-IN-PHYSENV instead. Fixes in sbcl-0.7.1.3 (not
-  closing over unreferenced variables) made this second test case
-  compile without error, but the original test case still fails.
-  Another way to get rid of the DEFTYPE without changing the symptom
-  of the bug is
-    (defvar *ch*)
-    (defun parse-num (string ind)
-      (flet ((digs ()
-               (let ()
-                 (if (and (< ind ind)
-                         (sb-int:memq *ch* '(#\1)))
-                     nil))))))
-  In sbcl-0.7.1.3, this fails with
-    internal error, failed AVER: "(= (LENGTH (BLOCK-SUCC CALL-BLOCK)) 1)" 
-  The problem occurs while the inline expansion of MEMQ,
-  #<LAMBDA :%DEBUG-NAME "varargs entry point for SB-C::.ANONYMOUS.">
-  is being LET-converted after having its second REF deleted, leaving
-  it with only one entry in LEAF-REFS.
-  
+  See also bugs #45.c and #183
+
 148:
   In sbcl-0.7.1.3 on x86, COMPILE-FILE on the file
     (in-package :cl-user)
@@ -1239,79 +983,13 @@ WORKAROUND:
     Is (1 . 1) of type CONS a cons? => NIL
   without signalling an error.
 
-154:
-  There's some sort of problem with aborting back out of the debugger
-  after a %DETECT-STACK-EXHAUSTION error in sbcl-0.7.1.38. In some cases
-  telling the debugger to ABORT doesn't get you back to the main REPL,
-  but instead just gives you another stack exhaustion error. The problem
-  doesn't occur in the trivial case
-    * (defun frob () (frob) (frob))
-    FROB
-    * (frob)
-  but it has happened in more complicated cases (which I haven't
-  figured out how to reproduce).
-
-155:
-  Executing 
-    (defclass standard-gadget (basic-gadget) ())
-    (defclass basic-gadget () ())
-  gives an error:
-    The slot SB-PCL::DIRECT-SUPERCLASSES is unbound in the
-    object #<SB-PCL::STANDARD-CLASS "unbound">.
-  (reported by Brian Spilsbury sbcl-devel 2002-04-09)
-
-156:
-  FUNCTION-LAMBDA-EXPRESSION doesn't work right in 0.7.0 or 0.7.2.9:
-    * (function-lambda-expression #'(lambda (x) x))
-    debugger invoked on condition of type TYPE-ERROR:
-      The value NIL is not of type SB-C::DEBUG-SOURCE
-  (reported by Alexey Dejneka sbcl-devel 2002-04-12)
-
 157:
   Functions SUBTYPEP, TYPEP, UPGRADED-ARRAY-ELEMENT-TYPE, and 
   UPGRADED-COMPLEX-PART-TYPE should have an optional environment argument.
   (reported by Alexey Dejneka sbcl-devel 2002-04-12)
 
-158:
-  Compiling the following code causes SBCL 0.7.2 to bug. This only
-  happens with optimization enabled, and only when the loop variable is
-  being incremented by more than 1.
-    (defun foo (array)
-      (declare (optimize (safety 0) (space 0) (debug 0) (speed 3)))
-      (loop for i from 0 to 10 by 2
-            do (foo (svref array i))) (svref array (1+ i)))
-  (reported by Eric Marsden sbcl-devel 2002-04-15)
-
-159:
-  * (lisp-implementation-version)
-  "0.7.2.6"
-  * (defstruct (foo
-                (:constructor make-foo (&key (bar nil bar-p)
-                                        &aux (baz (if bar-p bar 2)))))
-
-      bar
-      baz)
-  debugger invoked on condition of type SB-KERNEL::ARG-COUNT-ERROR:
-    error while parsing arguments to DESTRUCTURING-BIND:
-      invalid number of elements in
-        (BAR NIL BAR-P)
-      to satisfy lambda list
-        (SB-KERNEL::WOT &OPTIONAL (SB-KERNEL::DEF NIL SB-KERNEL::DEF-P)):
-      between 1 and 2 expected, but 3 found
-  (reported by Christophe Rhodes and Martin Atzmueller sbcl-devel
-  2002-05-15)
-
-160:
-  USER-HOMEDIR-PATHNAME returns a pathname that SBCL can't do anything
-  with.  Probably we should return an absolute physical pathname
-  instead.  (Reported by Peter van Eynde sbcl-devel 2002-03-29)
-
-161:
-  Typep on certain SATISFIES types doesn't take account of the fact
-  that the function could cause an error; e.g. (TYPEP #\! '(SATISFIES
-  FBOUNDP)) raises an error when it should return NIL.
-
 162:
+  (reported by Robert E. Brown 2002-04-16) 
   When a function is called with too few arguments, causing the
   debugger to be entered, the uninitialized slots in the bad call frame 
   seem to cause GCish problems, being interpreted as tagged data even
@@ -1326,7 +1004,410 @@ WORKAROUND:
     0] (room)
     ...
     failed AVER: "(SAP= CURRENT END)"
-  (reported by Robert E. Brown 2002-04-16)
+  (Christophe Rhodes reports that this doesn't occur on the SPARC, which
+  isn't too surprising since there are many differences in stack
+  implementation and GC conservatism between the X86 and other ports.)
+
+166:
+  Compiling 
+    (in-package :cl-user)
+    (defstruct uustk)
+    (defmethod permanentize ((uustk uustk))
+      (flet ((frob (hash-table test-for-deletion)
+               )
+             (obj-entry.stale? (oe)
+               (destructuring-bind (key . datum) oe
+                 (declare (type simple-vector key))
+                 (deny0 (void? datum))
+                 (some #'stale? key))))
+        (declare (inline frob obj-entry.stale?))
+        (frob (uustk.args-hash->obj-alist uustk)
+              #'obj-entry.stale?)
+        (frob (uustk.hash->memoized-objs-list uustk)
+              #'objs.stale?))
+      (call-next-method))
+  in sbcl-0.7.3.11 causes an assertion failure, 
+    failed AVER:
+      "(NOT
+(AND (NULL (BLOCK-SUCC B))
+      (NOT (BLOCK-DELETE-P B))
+      (NOT (EQ B (COMPONENT-HEAD #)))))"
+
+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.
+
+168:
+  (reported by Dan Barlow on sbcl-devel 2002-05-10)
+  In sbcl-0.7.3.12, doing
+    (defstruct foo bar baz)
+    (compile nil (lambda (x) (or x (foo-baz x))))
+  gives an error
+    debugger invoked on condition of type SB-INT:BUG:
+       full call to SB-KERNEL:%INSTANCE-REF
+    This is probably a bug in SBCL itself. [...]
+  Since this is a reasonable user error, it shouldn't be reported as 
+  an SBCL bug. 
+
+171:
+  (reported by Pierre Mai while investigating bug 47):
+    (DEFCLASS FOO () ((A :SILLY T))) 
+  signals a SIMPLE-ERROR, not a PROGRAM-ERROR.
+
+172:
+  sbcl's treatment of at least macro lambda lists is too permissive;
+  e.g., in sbcl-0.7.3.7:
+    (defmacro foo (&rest rest bar) `(,bar ,rest))
+    (macroexpand '(foo quux zot)) -> (QUUX (QUUX ZOT))
+  whereas section 3.4.4 of the CLHS doesn't allow required parameters
+  to come after the rest argument.
+
+173:
+  The compiler sometimes tries to constant-fold expressions before
+  it checks to see whether they can be reached. This can lead to 
+  bogus warnings about errors in the constant folding, e.g. in code
+  like 
+    (WHEN X
+      (WRITE-STRING (> X 0) "+" "0"))
+  compiled in a context where the compiler can prove that X is NIL,
+  and the compiler complains that (> X 0) causes a type error because
+  NIL isn't a valid argument to #'>. Until sbcl-0.7.4.10 or so this
+  caused a full WARNING, which made the bug really annoying because then 
+  COMPILE and COMPILE-FILE returned FAILURE-P=T for perfectly legal
+  code. Since then the warning has been downgraded to STYLE-WARNING, 
+  so it's still a bug but at least it's a little less annoying.
+
+174:
+  The error message from attempting to use a #\Return format
+  directive:
+    (format nil "~^M") ; replace "^M" with a literal #\Return
+      debugger invoked on condition of type SB-FORMAT::FORMAT-ERROR:
+      error in format:                  unknown format directive
+      ~
+       ^
+  is not terribly helpful; this is more noticeable than parallel cases
+  with e.g. #\Backspace because of the differing newline conventions
+  on various operating systems. (reported by Harald Hanche-Olsen on
+  cmucl-help 2002-05-31)
+
+176:
+  reported by Alexey Dejneka 08 Jun 2002 in sbcl-devel:
+    Playing with McCLIM, I've received an error "Unbound variable WRAPPER
+    in SB-PCL::CHECK-WRAPPER-VALIDITY".
+      (defun check-wrapper-validity (instance)
+        (let* ((owrapper (wrapper-of instance)))
+          (if (not (invalid-wrapper-p owrapper))
+              owrapper
+              (let* ((state (wrapper-state wrapper)) ; !!!
+        ...
+    I've tried to replace it with OWRAPPER, but now OBSOLETE-INSTANCE-TRAP
+    breaks with "NIL is not of type SB-KERNEL:LAYOUT".
+    SBCL 0.7.4.13.
+  partial fix: The undefined variable WRAPPER resulted from an error
+  in recent refactoring, as can be seen by comparing to the code in e.g. 
+  sbcl-0.7.2. Replacing WRAPPER with OWRAPPER (done by WHN in sbcl-0.7.4.22)
+  should bring the code back to its behavior as of sbcl-0.7.2, but
+  that still leaves the OBSOLETE-INSTANCE-TRAP bug. An example of 
+  input which triggers that bug is
+    (dotimes (i 20)
+      (let ((lastname (intern (format nil "C~D" (1- i))))
+            (name (intern (format nil "C~D" i))))
+      (eval `(defclass ,name
+                 (,@(if (= i 0) nil (list lastname)))
+               ()))
+      (eval `(defmethod initialize-instance :after ((x ,name) &rest any)
+               (declare (ignore any))))))
+    (defclass b () ())
+    (defclass c0 (b) ())
+    (make-instance 'c19)
+
+  See also bug #140.
+
+178: "AVER failure compiling confused THEs in FUNCALL"
+  In sbcl-0.7.4.24, compiling
+    (defun bug178 (x)
+      (funcall (the function (the standard-object x))))
+  gives 
+    failed AVER:
+      "(AND (EQ (IR2-CONTINUATION-PRIMITIVE-TYPE 2CONT) FUNCTION-PTYPE) (EQ CHECK T))"
+  This variant compiles OK, though:
+    (defun bug178alternative (x)
+      (funcall (the nil x)))
+
+181: "bad type specifier drops compiler into debugger"
+  Compiling 
+    (in-package :cl-user)
+    (defun bar (x)
+      (declare (type 0 x))
+      (cons x x))
+  signals 
+    bad thing to be a type specifier: 0
+  which seems fine, but also enters the debugger (instead of having
+  the compiler handle the error, convert it into a COMPILER-ERROR, and
+  continue compiling) which seems wrong.
+
+183: "IEEE floating point issues"
+  Even where floating point handling is being dealt with relatively
+  well (as of sbcl-0.7.5, on sparc/sunos and alpha; see bug #146), the
+  accrued-exceptions and current-exceptions part of the fp control
+  word don't seem to bear much relation to reality. E.g. on
+  SPARC/SunOS:
+  * (/ 1.0 0.0)
+
+  debugger invoked on condition of type DIVISION-BY-ZERO:
+    arithmetic error DIVISION-BY-ZERO signalled
+  0] (sb-vm::get-floating-point-modes)
+
+  (:TRAPS (:OVERFLOW :INVALID :DIVIDE-BY-ZERO)
+          :ROUNDING-MODE :NEAREST
+          :CURRENT-EXCEPTIONS NIL
+          :ACCRUED-EXCEPTIONS (:INEXACT)
+          :FAST-MODE NIL)
+  0] abort
+  * (sb-vm::get-floating-point-modes)
+  (:TRAPS (:OVERFLOW :INVALID :DIVIDE-BY-ZERO)
+          :ROUNDING-MODE :NEAREST
+          :CURRENT-EXCEPTIONS (:INEXACT)
+          :ACCRUED-EXCEPTIONS (:INEXACT)
+          :FAST-MODE NIL)
+
+185: "top-level forms at the REPL"
+  * (locally (defstruct foo (a 0 :type fixnum)))
+  gives an error:
+  ; caught ERROR:
+  ;   (in macroexpansion of (SB-KERNEL::%DELAYED-GET-COMPILER-LAYOUT BAR))
+  however, compiling and loading the same expression in a file works
+  as expected.
+
+187: "type inference confusion around DEFTRANSFORM time"
+  (reported even more verbosely on sbcl-devel 2002-06-28 as "strange
+  bug in DEFTRANSFORM")
+  After the file below is compiled and loaded in sbcl-0.7.5, executing
+    (TCX (MAKE-ARRAY 4 :FILL-POINTER 2) 0)
+  at the REPL returns an adjustable vector, which is wrong. Presumably
+  somehow the DERIVE-TYPE information for the output values of %WAD is
+  being mispropagated as a type constraint on the input values of %WAD,
+  and so causing the type test to be optimized away. It's unclear how
+  hand-expanding the DEFTRANSFORM would change this, but it suggests
+  the DEFTRANSFORM machinery (or at least the way DEFTRANSFORMs are
+  invoked at a particular phase) is involved.
+    (cl:in-package :sb-c)
+    (eval-when (:compile-toplevel)
+    ;;; standin for %DATA-VECTOR-AND-INDEX
+    (defknown %dvai (array index) 
+      (values t t) 
+      (foldable flushable))
+    (deftransform %dvai ((array index)
+                         (vector t)
+                         *
+                         :important t)
+      (let* ((atype (continuation-type array))
+             (eltype (array-type-specialized-element-type atype)))
+        (when (eq eltype *wild-type*)
+          (give-up-ir1-transform
+           "specialized array element type not known at compile-time"))
+        (when (not (array-type-complexp atype))
+          (give-up-ir1-transform "SIMPLE array!"))
+        `(if (array-header-p array)
+             (%wad array index nil)
+             (values array index))))
+    ;;; standin for %WITH-ARRAY-DATA
+    (defknown %wad (array index (or index null))
+      (values (simple-array * (*)) index index index)
+      (foldable flushable))
+    ;;; (Commenting out this optimizer causes the bug to go away.)
+    (defoptimizer (%wad derive-type) ((array start end))
+      (let ((atype (continuation-type array)))
+        (when (array-type-p atype)
+          (values-specifier-type
+           `(values (simple-array ,(type-specifier
+                                    (array-type-specialized-element-type atype))
+                                  (*))
+                    index index index)))))
+    ) ; EVAL-WHEN
+    (defun %wad (array start end)
+      (format t "~&in %WAD~%")
+      (%with-array-data array start end))
+    (cl:in-package :cl-user)
+    (defun tcx (v i)
+      (declare (type (vector t) v))
+      (declare (notinline sb-kernel::%with-array-data))
+      ;; (Hand-expending DEFTRANSFORM %DVAI here also causes the bug to
+      ;; go away.) 
+      (sb-c::%dvai v i))
+
+188: "compiler performance fiasco involving type inference and UNION-TYPE"
+  (In sbcl-0.7.6.10, DEFTRANSFORM CONCATENATE was commented out until this
+  bug could be fixed properly, so you won't see the bug unless you restore
+  the DEFTRANSFORM by hand.) In sbcl-0.7.5.11 on a 700 MHz Pentium III, 
+    (time (compile
+           nil
+           '(lambda ()
+              (declare (optimize (safety 3)))
+              (declare (optimize (compilation-speed 2)))
+              (declare (optimize (speed 1) (debug 1) (space 1)))
+              (let ((fn "if-this-file-exists-the-universe-is-strange"))
+                (load fn :if-does-not-exist nil)
+                (load (concatenate 'string fn ".lisp") :if-does-not-exist nil)
+                (load (concatenate 'string fn ".fasl") :if-does-not-exist nil)
+                (load (concatenate 'string fn ".misc-garbage")
+                      :if-does-not-exist nil)))))
+  reports  
+                134.552 seconds of real time
+                133.35156 seconds of user run time
+                0.03125 seconds of system run time
+                   [Run times include 2.787 seconds GC run time.]
+                0 page faults and
+                246883368 bytes consed.
+  BACKTRACE from Ctrl-C in the compilation shows that the compiler is
+  thinking about type relationships involving types like
+     #<UNION-TYPE
+       (OR (INTEGER 576 576)
+           (INTEGER 1192 1192)
+           (INTEGER 2536 2536)
+           (INTEGER 1816 1816)
+           (INTEGER 2752 2752)
+           (INTEGER 1600 1600)
+           (INTEGER 2640 2640)
+           (INTEGER 1808 1808)
+           (INTEGER 1296 1296)
+           ...)>)[:EXTERNAL]
+
+190: "PPC/Linux pipe? buffer? bug"
+  In sbcl-0.7.6, the run-program.test.sh test script sometimes hangs
+  on the PPC/Linux platform, waiting for a zombie env process.  This
+  is a classic symptom of buffer filling and deadlock, but it seems
+  only sporadically reproducible.
+
+191: "Miscellaneous PCL deficiencies"
+  (reported by Alexey Dejneka sbcl-devel 2002-08-04)
+  a. DEFCLASS does not inform the compiler about generated
+     functions. Compiling a file with
+       (DEFCLASS A-CLASS ()
+         ((A-CLASS-X)))
+       (DEFUN A-CLASS-X (A)
+         (WITH-SLOTS (A-CLASS-X) A
+           A-CLASS-X))
+     results in a STYLE-WARNING:
+       undefined-function 
+         SB-SLOT-ACCESSOR-NAME::|COMMON-LISP-USER A-CLASS-X slot READER|
+
+     APD's fix for this was checked in to sbcl-0.7.6.20, but Pierre
+     Mai points out that the declamation of functions is in fact
+     incorrect in some cases (most notably for structure
+     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.
+  c. the examples in CLHS 7.6.5.1 (regarding generic function lambda
+     lists and &KEY arguments) do not signal errors when they should.
+
+192: "Python treats free type declarations as promises."
+  a. original report by Alexey Dejneka (on sbcl-devel 2002-08-26):
+       (declaim (optimize (speed 0) (safety 3)))
+       (defun f (x)
+         (declare (real x))
+         (+ x
+            (locally (declare (single-float x))
+            (sin x))))
+     Now (F NIL) correctly gives a type error, but (F 100) gives
+     a segmentation violation.
+  b. same fundamental problem in a different way, easy to stumble
+     across if you mistype and declare the wrong index in
+     (DOTIMES (I ...) (DOTIMES (J ...) (DECLARE ...) ...)):
+       (declaim (optimize (speed 1) (safety 3)))
+       (defun trust-assertion (i)
+         (dotimes (j i)
+           (declare (type (mod 4) i)) ; when commented out, behavior changes!
+           (unless (< i 5)
+             (print j))))
+       (trust-assertion 6) ; prints nothing unless DECLARE is commented out
+
+193: "unhelpful CLOS error reporting when the primary method is missing"
+  In sbcl-0.7.7, when
+    (defmethod foo :before ((x t)) (print x))
+  is the only method defined on FOO, the error reporting when e.g.
+    (foo 12)
+  is relatively unhelpful:
+    There is no primary method for the generic function
+      #<STANDARD-GENERIC-FUNCTION FOO (1)>.
+  with the offending argument nowhere visible in the backtrace. This 
+  continues even if there *are* primary methods, just not for the 
+  specified arg type, e.g. 
+    (defmethod foo ((x character)) (print x))
+    (defmethod foo ((x string)) (print x))
+    (defmethod foo ((x pathname)) ...)
+  In that case it could be very helpful to know what argument value is
+  falling through the cracks of the defined primary methods, but the
+  error message stays the same (even BACKTRACE doesn't tell you what the
+  bad argument value is).
+
+194: "no error from (THE REAL '(1 2 3)) in some cases"
+  (Actually this entry is probably two separate bugs, as
+  Alexey Dejneka commented on sbcl-devel 2002-09-03:)
+       I don't think that placing these two bugs in one entry is
+       a good idea: they have different explanations. The second
+       (min 1 nil) is caused by flushing of unused code--IDENTITY
+       can do nothing with it. So it is really bug 122. The first
+       (min nil) is due to M-V-PROG1: substituting a continuation
+       for the result, it forgets about type assertion. The purpose
+       of IDENTITY is to save the restricted continuation from
+       inaccurate transformations.
+  In sbcl-0.7.7.9, 
+    (multiple-value-prog1 (progn (the real '(1 2 3))))
+  returns (1 2 3) instead of signalling an error. Also in sbcl-0.7.7.9,
+  a more complicated instance of this bug kept 
+  (IGNORE-ERRORS (MIN '(1 2 3))) from returning NIL as it should when
+  the MIN source transform expanded to (THE REAL '(1 2 3)), because
+  (IGNORE-ERRORS (THE REAL '(1 2 3))) returns (1 2 3).
+  Alexey Dejneka pointed out that
+  (IGNORE-ERRORS (IDENTITY (THE REAL '(1 2 3)))) works as it should.
+  (IGNORE-ERRORS (VALUES (THE REAL '(1 2 3)))) also works as it should.
+  Perhaps this is another case of VALUES type intersections behaving
+  in non-useful ways?
+    When I (WHN) tried to use the VALUES trick to work around this bug
+  in the MIN source transform, it didn't work for
+    (assert (null (ignore-errors (min 1 #(1 2 3)))))
+  Hand-expanding the source transform, I get
+    (assert (null (ignore-errors
+                   (let ((arg1 1)
+                         (arg2 (identity (the real #(1 2 3)))))
+                     (if (< arg1 arg2) arg1 arg2))))) 
+  which fails (i.e. the assertion fails, because the IGNORE-ERRORS
+  doesn't report MIN signalling a type error). At the REPL
+    (null (ignore-errors
+           (let ((arg1 1)
+                 (arg2 (identity (the real #(1 2 3)))))
+             (if (< arg1 arg2) arg1 arg2))))
+    => T
+  but when this expression is used as the body of (DEFUN FOO () ...)
+  then (FOO)=>NIL.
+
+195: "confusing reporting of not-a-REAL TYPE-ERRORs from THE REAL"
+  In sbcl-0.7.7.10, (THE REAL #(1 2 3)) signals a type error which
+  prints as "This is not a (OR SINGLE-FLOAT DOUBLE-FLOAT RATIONAL)".
+  The (OR SINGLE-FLOAT DOUBLE-FLOAT RATIONAL) representation of
+  REAL is unnecessarily confusing, especially since it relies on 
+  internal implementation knowledge that even with SHORT-FLOAT
+  and LONG-FLOAT left out of the union, this type is equal to REAL.
+  So it'd be better just to say "This is not a REAL".
+
+196: "confusing error message for unREAL second arg to ATAN"
+  (reported by Alexey Dejneka sbcl-devel 2002-09-04)
+  In sbcl-0.7.7.11,
+    * (atan 1 #c(1 2))
+    debugger invoked on condition of type SIMPLE-TYPE-ERROR:
+      Argument X is not a NUMBER: #C(1 2)
+  (The actual type problem is that argument Y is not a REAL.)
 
 DEFUNCT CATEGORIES OF BUGS
   IR1-#: