1.0.4.31: remove *internal-error-context*
[sbcl.git] / BUGS
diff --git a/BUGS b/BUGS
index 87c19e6..55bb754 100644 (file)
--- a/BUGS
+++ b/BUGS
@@ -84,12 +84,6 @@ WORKAROUND:
 
   d: (fixed in 0.8.1.5)
 
-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.
-
 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.
@@ -174,6 +168,9 @@ WORKAROUND:
   e-mail on cmucl-help@cons.org on 2001-01-16 and 2001-01-17 from WHN
   and Pierre Mai.)
 
+  (Actually this has changed changed since, and types as above are
+  now supported. This may be a bug.)
+
 83:
   RANDOM-INTEGER-EXTRA-BITS=10 may not be large enough for the RANDOM
   RNG to be high quality near RANDOM-FIXNUM-MAX; it looks as though
@@ -198,19 +195,6 @@ WORKAROUND:
   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
@@ -526,6 +510,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.
+
+     [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"
@@ -641,40 +632,6 @@ WORKAROUND:
 
   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))
@@ -690,6 +647,10 @@ WORKAROUND:
 
   (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
@@ -768,11 +729,7 @@ WORKAROUND:
 
   a. (lambda () (svref (make-array 8 :adjustable t) 1))
 
-  b. (lambda (x)
-       (list (let ((y (the real x)))
-               (unless (floatp y) (error ""))
-               y)
-             (integer-length x)))
+  b. (fixed at some point before 1.0.4.10)
 
   c. (lambda (x)
        (declare (optimize (debug 0)))
@@ -891,17 +848,6 @@ WORKAROUND:
            (1+ *faa*))
      (faa 1d0) => type error
 
-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)
-
 279: type propagation error -- correctly inferred type goes astray?
   In sbcl-0.8.3 and sbcl-0.8.1.47, the warning
        The binding of ABS-FOO is a (VALUES (INTEGER 0 0)
@@ -930,11 +876,9 @@ WORKAROUND:
 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
 
-    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 
@@ -949,15 +893,6 @@ WORKAROUND:
   (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
@@ -995,14 +930,6 @@ WORKAROUND:
   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 
@@ -1052,13 +979,8 @@ WORKAROUND:
   The problem is that both EVALs sequentially write to the same LVAR.
 
 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
@@ -1120,20 +1042,6 @@ WORKAROUND:
     #(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
@@ -1263,101 +1171,6 @@ WORKAROUND:
   Fixing this should also fix a subset of #328 -- update the
   description with a new test-case then.
 
-337: MAKE-METHOD and user-defined method classes
-  (reported by Bruno Haible sbcl-devel 2004-06-11)
-
-  In the presence of  
-
-(defclass user-method (standard-method) (myslot))
-(defmacro def-user-method (name &rest rest)
-  (let* ((lambdalist-position (position-if #'listp rest))
-         (qualifiers (subseq rest 0 lambdalist-position))
-         (lambdalist (elt rest lambdalist-position))
-         (body (subseq rest (+ lambdalist-position 1)))
-         (required-part 
-          (subseq lambdalist 0 (or 
-                                (position-if 
-                                 (lambda (x) (member x lambda-list-keywords))
-                                 lambdalist)
-                                (length lambdalist))))
-         (specializers (mapcar #'find-class 
-                               (mapcar (lambda (x) (if (consp x) (second x) t))
-                                       required-part)))
-         (unspecialized-required-part 
-          (mapcar (lambda (x) (if (consp x) (first x) x)) required-part))
-         (unspecialized-lambdalist 
-          (append unspecialized-required-part 
-           (subseq lambdalist (length required-part)))))
-    `(PROGN
-       (ADD-METHOD #',name
-         (MAKE-INSTANCE 'USER-METHOD
-          :QUALIFIERS ',qualifiers
-          :LAMBDA-LIST ',unspecialized-lambdalist
-          :SPECIALIZERS ',specializers
-          :FUNCTION
-          (LAMBDA (ARGUMENTS NEXT-METHODS-LIST)
-            (FLET ((NEXT-METHOD-P () NEXT-METHODS-LIST)
-                   (CALL-NEXT-METHOD (&REST NEW-ARGUMENTS)
-                     (UNLESS NEW-ARGUMENTS (SETQ NEW-ARGUMENTS ARGUMENTS))
-                     (IF (NULL NEXT-METHODS-LIST)
-                         (ERROR "no next method for arguments ~:S" ARGUMENTS)
-                         (FUNCALL (SB-PCL:METHOD-FUNCTION 
-                                   (FIRST NEXT-METHODS-LIST))
-                                  NEW-ARGUMENTS (REST NEXT-METHODS-LIST)))))
-              (APPLY #'(LAMBDA ,unspecialized-lambdalist ,@body) ARGUMENTS)))))
-       ',name)))
-
-  (progn
-    (defgeneric test-um03 (x))
-    (defmethod test-um03 ((x integer))
-      (list* 'integer x (not (null (next-method-p))) (call-next-method)))
-    (def-user-method test-um03 ((x rational))
-      (list* 'rational x (not (null (next-method-p))) (call-next-method)))
-    (defmethod test-um03 ((x real))
-      (list 'real x (not (null (next-method-p)))))
-    (test-um03 17))
-  works, but
-
-  a.(progn
-      (defgeneric test-um10 (x))
-      (defmethod test-um10 ((x integer))
-        (list* 'integer x (not (null (next-method-p))) (call-next-method)))
-      (defmethod test-um10 ((x rational))
-        (list* 'rational x (not (null (next-method-p))) (call-next-method)))
-      (defmethod test-um10 ((x real))
-        (list 'real x (not (null (next-method-p)))))
-      (defmethod test-um10 :after ((x real)))
-      (def-user-method test-um10 :around ((x integer))
-        (list* 'around-integer x 
-         (not (null (next-method-p))) (call-next-method)))
-      (defmethod test-um10 :around ((x rational))
-        (list* 'around-rational x 
-         (not (null (next-method-p))) (call-next-method)))
-      (defmethod test-um10 :around ((x real))
-        (list* 'around-real x (not (null (next-method-p))) (call-next-method)))
-      (test-um10 17))
-    fails with a type error, and
-
-  b.(progn
-      (defgeneric test-um12 (x))
-      (defmethod test-um12 ((x integer))
-        (list* 'integer x (not (null (next-method-p))) (call-next-method)))
-      (defmethod test-um12 ((x rational))
-        (list* 'rational x (not (null (next-method-p))) (call-next-method)))
-      (defmethod test-um12 ((x real))
-        (list 'real x (not (null (next-method-p)))))
-      (defmethod test-um12 :after ((x real)))
-      (defmethod test-um12 :around ((x integer))
-        (list* 'around-integer x 
-         (not (null (next-method-p))) (call-next-method)))
-      (defmethod test-um12 :around ((x rational))
-        (list* 'around-rational x 
-         (not (null (next-method-p))) (call-next-method)))
-      (def-user-method test-um12 :around ((x real))
-        (list* 'around-real x (not (null (next-method-p))) (call-next-method)))
-      (test-um12 17))
-    fails with NO-APPLICABLE-METHOD.
-
 339: "DEFINE-METHOD-COMBINATION bugs"
   (reported by Bruno Haible via the clisp test suite)
 
@@ -1380,41 +1193,7 @@ WORKAROUND:
    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.
-
-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
@@ -1457,6 +1236,11 @@ WORKAROUND:
         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 
@@ -1487,53 +1271,6 @@ WORKAROUND:
  the function can never return; same happens if the function holds an
  unconditional call to ERROR.
 
-355: change-class of generic-function
-    (reported by Bruno Haible)
-  The MOP doesn't support change-class on a generic-function. However, SBCL
-  apparently supports it, since it doesn't give an error or warning when doing
-  so so. Then, however, it produces wrong results for calls to this generic 
-  function.
-  ;;; The effective-methods cache:
-  (progn
-    (defgeneric testgf35 (x))
-    (defmethod testgf35 ((x integer))
-      (cons 'integer (if (next-method-p) (call-next-method))))
-    (defmethod testgf35 ((x real))
-      (cons 'real (if (next-method-p) (call-next-method))))
-    (defclass customized5-generic-function (standard-generic-function)
-      ()
-      (:metaclass sb-pcl:funcallable-standard-class))
-    (defmethod sb-pcl:compute-effective-method ((gf customized5-generic-function) method-combination methods)
-      `(REVERSE ,(call-next-method)))
-    (list
-      (testgf35 3)
-      (progn
-        (change-class #'testgf35 'customized5-generic-function)
-        (testgf35 3))))
-  Expected: ((INTEGER REAL) (REAL INTEGER))
-  Got:      ((INTEGER REAL) (INTEGER REAL))
-  ;;; The discriminating-function cache:
-  (progn
-    (defgeneric testgf36 (x))
-    (defmethod testgf36 ((x integer))
-      (cons 'integer (if (next-method-p) (call-next-method))))
-    (defmethod testgf36 ((x real))
-      (cons 'real (if (next-method-p) (call-next-method))))
-    (defclass customized6-generic-function (standard-generic-function)
-      ()
-      (:metaclass sb-pcl:funcallable-standard-class))
-    (defmethod sb-pcl:compute-discriminating-function ((gf customized6-generic-function))
-      (let ((orig-df (call-next-method)))
-        #'(lambda (&rest arguments)
-            (reverse (apply orig-df arguments)))))
-    (list
-      (testgf36 3)
-      (progn
-        (change-class #'testgf36 'customized6-generic-function)
-        (testgf36 3))))
-  Expected: ((INTEGER REAL) (REAL INTEGER))
-  Got:      ((INTEGER REAL) (INTEGER REAL))
-
 356: PCL corruption
     (reported by Bruno Haible)
   After the "layout depth conflict" error, the CLOS is left in a state where
@@ -1553,6 +1290,17 @@ WORKAROUND:
   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,
@@ -1599,26 +1347,6 @@ WORKAROUND:
   Expected: (t 3 -44 t 9 -88 t 20)
   Got: (0 0 0 0 0 0 0 0)
 
-358: :DECLARE argument to ENSURE-GENERIC-FUNCTION 
-    (reported by Bruno Haible)
-  According to ANSI CL, ensure-generic-function must accept a :DECLARE
-  keyword argument. In SBCL 0.8.16 it does not.
-  Test case:
-  (progn
-    (ensure-generic-function 'foo113 :declare '((optimize (speed 3))))
-    (sb-pcl:generic-function-declarations #'foo113))
-  Expected: ((OPTIMIZE (SPEED 3)))
-  Got: ERROR
-    Invalid initialization argument:
-      :DECLARE
-    in call for class #<SB-MOP:FUNCALLABLE-STANDARD-CLASS STANDARD-GENERIC-FUNCTION>.
-  See also:
-    The ANSI Standard, Section 7.1.2
-
-  Bruno notes: The MOP specifies that ensure-generic-function accepts :DECLARATIONS.
-  The easiest way to be compliant to both specs is to accept both (exclusively
-  or cumulatively).
-
 359: wrong default value for ensure-generic-function's :generic-function-class argument
     (reported by Bruno Haible)
   ANSI CL is silent on this, but the MOP's specification of ENSURE-GENERIC-FUNCTION says:
@@ -1644,151 +1372,6 @@ WORKAROUND:
   Expected: #<SB-MOP:FUNCALLABLE-STANDARD-CLASS STANDARD-GENERIC-FUNCTION>
   Got:      #<SB-MOP:FUNCALLABLE-STANDARD-CLASS MY-GENERIC-FUNCTION>
 
-360: CALL-METHOD not recognized in method-combination body
-  (reported by Bruno Haible)
-  This method combination, which adds 'redo' and 'return' restarts for each
-  method invocation to standard method combination, gives an error in SBCL.
-  (defun prompt-for-new-values ()
-    (format *debug-io* "~&New values: ")
-    (list (read *debug-io*)))
-  (defun add-method-restarts (form method)
-    (let ((block (gensym))
-          (tag (gensym)))
-      `(BLOCK ,block
-         (TAGBODY
-           ,tag
-           (RETURN-FROM ,block
-             (RESTART-CASE ,form
-               (METHOD-REDO ()
-                 :REPORT (LAMBDA (STREAM) (FORMAT STREAM "Try calling ~S again." ,method))
-                 (GO ,tag))
-               (METHOD-RETURN (L)
-                 :REPORT (LAMBDA (STREAM) (FORMAT STREAM "Specify return values for ~S call." ,method))
-                 :INTERACTIVE (LAMBDA () (PROMPT-FOR-NEW-VALUES))
-                 (RETURN-FROM ,block (VALUES-LIST L)))))))))
-  (defun convert-effective-method (efm)
-    (if (consp efm)
-      (if (eq (car efm) 'CALL-METHOD)
-        (let ((method-list (third efm)))
-          (if (or (typep (first method-list) 'method) (rest method-list))
-            ; Reduce the case of multiple methods to a single one.
-            ; Make the call to the next-method explicit.
-            (convert-effective-method
-              `(CALL-METHOD ,(second efm)
-                 ((MAKE-METHOD
-                    (CALL-METHOD ,(first method-list) ,(rest method-list))))))
-            ; Now the case of at most one method.
-            (if (typep (second efm) 'method)
-              ; Wrap the method call in a RESTART-CASE.
-              (add-method-restarts
-                (cons (convert-effective-method (car efm))
-                      (convert-effective-method (cdr efm)))
-                (second efm))
-              ; Normal recursive processing.
-              (cons (convert-effective-method (car efm))
-                    (convert-effective-method (cdr efm))))))
-        (cons (convert-effective-method (car efm))
-              (convert-effective-method (cdr efm))))
-      efm))
-  (define-method-combination standard-with-restarts ()
-         ((around (:around))
-          (before (:before))
-          (primary () :required t)
-          (after (:after)))
-    (flet ((call-methods-sequentially (methods)
-             (mapcar #'(lambda (method)
-                         `(CALL-METHOD ,method))
-                     methods)))
-      (let ((form (if (or before after (rest primary))
-                    `(MULTIPLE-VALUE-PROG1
-                       (PROGN
-                         ,@(call-methods-sequentially before)
-                         (CALL-METHOD ,(first primary) ,(rest primary)))
-                       ,@(call-methods-sequentially (reverse after)))
-                    `(CALL-METHOD ,(first primary)))))
-        (when around
-          (setq form
-                `(CALL-METHOD ,(first around)
-                              (,@(rest around) (MAKE-METHOD ,form)))))
-        (convert-effective-method form))))
-  (defgeneric testgf16 (x) (:method-combination standard-with-restarts))
-  (defclass testclass16a () ())
-  (defclass testclass16b (testclass16a) ())
-  (defclass testclass16c (testclass16a) ())
-  (defclass testclass16d (testclass16b testclass16c) ())
-  (defmethod testgf16 ((x testclass16a))
-    (list 'a
-          (not (null (find-restart 'method-redo)))
-          (not (null (find-restart 'method-return)))))
-  (defmethod testgf16 ((x testclass16b))
-    (cons 'b (call-next-method)))
-  (defmethod testgf16 ((x testclass16c))
-    (cons 'c (call-next-method)))
-  (defmethod testgf16 ((x testclass16d))
-    (cons 'd (call-next-method)))
-  (testgf16 (make-instance 'testclass16d))
-
-  Expected: (D B C A T T)
-  Got: ERROR CALL-METHOD outside of a effective method form
-
-  This is a bug because ANSI CL HyperSpec/Body/locmac_call-m__make-method
-  says
-   "The macro call-method invokes the specified method, supplying it with
-    arguments and with definitions for call-next-method and for next-method-p.
-    If the invocation of call-method is lexically inside of a make-method,
-    the arguments are those that were supplied to that method. Otherwise
-    the arguments are those that were supplied to the generic function."
-  and the example uses nothing more than these two cases (as you can see by
-  doing (trace convert-effective-method)).
-
-361: initialize-instance of standard-reader-method ignores :function argument
-    (reported by Bruno Haible)
-  Pass a custom :function argument to initialize-instance of a
-  standard-reader-method instance, but it has no effect.
-  ;; Check that it's possible to define reader methods that do typechecking.
-  (progn
-    (defclass typechecking-reader-method (sb-pcl:standard-reader-method)
-      ())
-    (defmethod initialize-instance ((method typechecking-reader-method) &rest initargs
-                                    &key slot-definition)
-      (let ((name (sb-pcl:slot-definition-name slot-definition))
-            (type (sb-pcl:slot-definition-type slot-definition)))
-        (apply #'call-next-method method
-               :function #'(lambda (args next-methods)
-                             (declare (ignore next-methods))
-                             (apply #'(lambda (instance)
-                                        (let ((value (slot-value instance name)))
-                                          (unless (typep value type)
-                                            (error "Slot ~S of ~S is not of type ~S: ~S"
-                                                   name instance type value))
-                                          value))
-                                    args))
-               initargs)))
-    (defclass typechecking-reader-class (standard-class)
-      ())
-    (defmethod sb-pcl:validate-superclass ((c1 typechecking-reader-class) (c2 standard-class))
-      t)
-    (defmethod reader-method-class ((class typechecking-reader-class) direct-slot &rest args)
-      (find-class 'typechecking-reader-method))
-    (defclass testclass25 ()
-      ((pair :type (cons symbol (cons symbol null)) :initarg :pair :accessor testclass25-pair))
-      (:metaclass typechecking-reader-class))
-   (macrolet ((succeeds (form)
-                 `(not (nth-value 1 (ignore-errors ,form)))))
-      (let ((p (list 'abc 'def))
-            (x (make-instance 'testclass25)))
-        (list (succeeds (make-instance 'testclass25 :pair '(seventeen 17)))
-              (succeeds (setf (testclass25-pair x) p))
-              (succeeds (setf (second p) 456))
-              (succeeds (testclass25-pair x))
-              (succeeds (slot-value x 'pair))))))
-  Expected: (t t t nil t)
-  Got:      (t t t t t)
-
-  (inspect (first (sb-pcl:generic-function-methods #'testclass25-pair)))
-  shows that the method was created with a FAST-FUNCTION slot but with a
-  FUNCTION slot of NIL.
-
 362: missing error when a slot-definition is created without a name
     (reported by Bruno Haible)
   The MOP says about slot-definition initialization:
@@ -1812,133 +1395,6 @@ WORKAROUND:
   Expected: ERROR
   Got: #<SB-MOP:STANDARD-DIRECT-SLOT-DEFINITION FOO>
 
-364: does not support class objects as specializer names
-   (reported by Bruno Haible)
-  According to ANSI CL 7.6.2, class objects are valid specializer names,
-  and "Parameter specializer names are used in macros intended as the
-  user-level interface (defmethod)". DEFMETHOD's syntax section doesn't
-  mention this possibility in the BNF for parameter-specializer-name;
-  however, this appears to be an editorial omission, since the CLHS
-  mentions issue CLASS-OBJECT-SPECIALIZER:AFFIRM as being approved
-  by X3J13. SBCL doesn't support it:
-   (defclass foo () ())
-   (defmethod goo ((x #.(find-class 'foo))) x)
-  Expected: #<STANDARD-METHOD GOO (#<STANDARD-CLASS FOO>)>
-  Got:      ERROR "#<STANDARD-CLASS FOO> is not a legal class name."
-
-365: mixin on generic-function subclass
-    (reported by Bruno Haible)
-  a mixin class
-    (defclass prioritized-dispatcher ()
-      ((dependents :type list :initform nil)))
-  on a generic-function subclass:
-    (defclass prioritized-generic-function (prioritized-dispatcher standard-generic-function)
-      ()
-      (:metaclass sb-pcl:funcallable-standard-class))
-  SBCL gives an error on this, telling to define a method on SB-MOP:VALIDATE-SUPERCLASS. If done,
-    (defmethod sb-pcl:validate-superclass ((c1 sb-pcl:funcallable-standard-class) 
-                                           (c2 (eql (find-class 'prioritized-dispatcher))))
-      t)
-  then, however,
-    (defclass prioritized-generic-function (prioritized-dispatcher standard-generic-function)
-      ()
-      (:metaclass sb-pcl:funcallable-standard-class))
-  => debugger invoked on a SIMPLE-ERROR in thread 6687:
-    layout depth conflict: #(#<SB-KERNEL:LAYOUT for T {500E1E9}> ...)
-  Further discussion on this: http://thread.gmane.org/gmane.lisp.steel-bank.general/491
-
-366: cannot define two generic functions with user-defined class
-   (reported by Bruno Haible)
-  it is possible to define one generic function class and an instance
-  of it. But attempting to do the same thing again, in the same session,
-  leads to a "Control stack exhausted" error. Test case:
-    (defclass my-generic-function-1 (standard-generic-function)
-      ()
-      (:metaclass sb-pcl:funcallable-standard-class))
-    (defgeneric testgf-1 (x) (:generic-function-class my-generic-function-1)
-      (:method ((x integer)) (cons 'integer nil)))
-    (defclass my-generic-function-2 (standard-generic-function)
-      ()
-      (:metaclass sb-pcl:funcallable-standard-class))
-    (defgeneric testgf-2 (x) (:generic-function-class my-generic-function-2)
-      (:method ((x integer)) (cons 'integer nil)))
-  => SB-KERNEL::CONTROL-STACK-EXHAUSTED
-
-367: TYPE-ERROR at compile time, undetected TYPE-ERROR at runtime
-  This test program
-    (declaim (optimize (safety 3) (debug 2) (speed 2) (space 1)))
-    (defstruct e367)
-    (defstruct i367)
-    (defstruct g367
-      (i367s (make-array 0 :fill-pointer t) :type (or (vector i367) null)))
-    (defstruct s367
-      (g367 (error "missing :G367") :type g367 :read-only t))
-    ;;; In sbcl-0.8.18, commenting out this (DECLAIM (FTYPE ... R367))
-    ;;; gives an internal error at compile time:
-    ;;;    The value #<SB-KERNEL:NAMED-TYPE NIL> is not of
-    ;;;    type SB-KERNEL:VALUES-TYPE.
-    (declaim (ftype (function ((vector i367) e367) (or s367 null)) r367))
-    (declaim (ftype (function ((vector e367)) (values)) h367))
-    (defun frob (v w)
-      (let ((x (g367-i367s (make-g367))))
-        (let* ((y (or (r367 x w)
-                      (h367 x)))
-               (z (s367-g367 y)))
-          (format t "~&Y=~S Z=~S~%" y z)
-          (g367-i367s z))))
-    (defun r367 (x y) (declare (ignore x y)) nil)
-    (defun h367 (x) (declare (ignore x)) (values))
-    ;;; In sbcl-0.8.18, executing this form causes an low-level error
-    ;;;   segmentation violation at #X9B0E1F4
-    ;;; (instead of the TYPE-ERROR that one might like).
-    (frob 0 (make-e367))
-  can be made to cause two different problems, as noted in the comments:
-    bug 367a: Compile and load the file. No TYPE-ERROR is signalled at 
-      run time (in the (S367-G367 Y) form of FROB, when Y is NIL 
-      instead of an instance of S367). Instead (on x86/Linux at least)
-      we end up with a segfault.
-    bug 367b: Comment out the (DECLAIM (FTYPE ... R367)), and compile 
-      the file. The compiler fails with TYPE-ERROR at compile time.
-
-368: miscompiled OR (perhaps related to bug 367)
-  Trying to relax type declarations to find a workaround for bug 367,
-  it turns out that even when the return type isn't declared (or 
-  declared to be T, anyway) the system remains confused about type 
-  inference in code similar to that for bug 367:
-    (in-package :cl-user)
-    (declaim (optimize (safety 3) (debug 2) (speed 2) (space 1)))
-    (defstruct e368)
-    (defstruct i368)
-    (defstruct g368
-      (i368s (make-array 0 :fill-pointer t) :type (or (vector i368) null)))
-    (defstruct s368
-      (g368 (error "missing :G368") :type g368 :read-only t))
-    (declaim (ftype (function (fixnum (vector i368) e368) t) r368))
-    (declaim (ftype (function (fixnum (vector e368)) t) h368))
-    (defparameter *h368-was-called-p* nil)
-    (defun nsu (vertices e368)
-      (let ((i368s (g368-i368s (make-g368))))
-        (let ((fuis (r368 0 i368s e368)))
-          (format t "~&FUIS=~S~%" fuis)
-          (or fuis (h368 0 i368s)))))
-    (defun r368 (w x y)
-      (declare (ignore w x y))
-      nil)
-    (defun h368 (w x)
-      (declare (ignore w x))
-      (setf *h368-was-called-p* t)
-      (make-s368 :g368 (make-g368)))
-    (trace r368 h368)
-    (format t "~&calling NSU~%")
-    (let ((nsu (nsu #() (make-e368))))
-      (format t "~&NSU returned ~S~%" nsu)
-      (format t "~&*H368-WAS-CALLED-P*=~S~%" *h368-was-called-p*)
-      (assert (s368-p nsu))
-      (assert *h368-was-called-p*))
-  In sbcl-0.8.18, both ASSERTs fail, and (DISASSEMBLE 'NSU) shows
-  that no call to H368 is compiled.
-
 369: unlike-an-intersection behavior of VALUES-TYPE-INTERSECTION
   In sbcl-0.8.18.2, the identity $(x \cap y \cap y)=(x \cap y)$ 
   does not hold for VALUES-TYPE-INTERSECTION, even for types which
@@ -1983,31 +1439,6 @@ WORKAROUND:
  #.SB-EXT:SINGLE/DOUBLE-FLOAT-POSITIVE-INFINITY. These tests have been
  disabled on Darwin for now.
 
-374: BIT-AND problem on ppc/darwin:
-  The BIT-AND test in bit-vector.impure-cload.lisp results in
-    fatal error encountered in SBCL pid 8356:
-    GC invariant lost, file "gc-common.c", line 605
-  on ppc/darwin. Test disabled for the duration.
-
-375: MISC.555
-    (compile nil '(lambda (p1)
-                   (declare (optimize (speed 1) (safety 2) (debug 2) (space 0))
-                            (type keyword p1))
-                   (keywordp p1)))
-
-  fails on hairy type check in IR2.
-
-  1. KEYWORDP is MAYBE-INLINE expanded (before TYPEP-like
-     transformation could eliminate it).
-
-  2. From the only call of KEYWORDP the type of its argument is
-     derived to be KEYWORD.
-
-  2. Type check for P1 is generated; it uses KEYWORDP to perform the
-     check, and so references the local function; from the KEYWORDP
-     argument type new CAST to KEYWORD is generated. The compiler
-     loops forever.
-
 377: Memory fault error reporting
   On those architectures where :C-STACK-IS-CONTROL-STACK is in
   *FEATURES*, we handle SIG_MEMORY_FAULT (SEGV or BUS) on an altstack,
@@ -2038,18 +1469,6 @@ WORKAROUND:
   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 ()
@@ -2101,16 +1520,6 @@ WORKAROUND:
   stack exhaustion checking (implemented with a write-protected guard
   page) does not work on SunOS/x86.
 
-387:
-  12:10 < jsnell> the package-lock test is basically due to a change in the test 
-                  behaviour when you install a handler for error around it. I 
-                  thought I'd disabled the test for now, but apparently that was 
-                  my imagination
-  12:19 < Xophe> jsnell: ah, I see the problem in the package-locks stuff
-  12:19 < Xophe> it's the same problem as we had with compiler-error conditions
-  12:19 < Xophe> the thing that's signalled up and down the stack is a subtype of
-                  ERROR, where it probably shouldn't be
-
 388:
   (found by Dmitry Bogomolov)
 
@@ -2123,6 +1532,8 @@ WORKAROUND:
     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)
@@ -2134,3 +1545,250 @@ WORKAROUND:
   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.
+
+411: NAN issues on x86-64
+  Test :NAN-COMPARISONS in float.pure.lisp fails on x86-64, and has been
+  disabled on those platforms. Since x86 does not exhibit any problems
+  the problem is probably with the new FP implementation.