0.8.0.54:
[sbcl.git] / BUGS
diff --git a/BUGS b/BUGS
index 0715f86..109b0c9 100644 (file)
--- a/BUGS
+++ b/BUGS
@@ -199,19 +199,6 @@ WORKAROUND:
   (Also, verify that the compiler handles declared function
   return types as assertions.)
 
-41:
-  TYPEP of VALUES types is sometimes implemented very inefficiently, e.g. in 
-       (DEFTYPE INDEXOID () '(INTEGER 0 1000))
-       (DEFUN FOO (X)
-         (DECLARE (TYPE INDEXOID X))
-         (THE (VALUES INDEXOID)
-           (VALUES X)))
-  where the implementation of the type check in function FOO 
-  includes a full call to %TYPEP. There are also some fundamental problems
-  with the interpretation of VALUES types (inherited from CMU CL, and
-  from the ANSI CL standard) as discussed on the cmucl-imp@cons.org
-  mailing list, e.g. in Robert Maclachlan's post of 21 Jun 2000.
-
 42:
   The definitions of SIGCONTEXT-FLOAT-REGISTER and
   %SET-SIGCONTEXT-FLOAT-REGISTER in x86-vm.lisp say they're not
@@ -270,17 +257,6 @@ WORKAROUND:
   then requesting a BACKTRACE at the debugger prompt gives no information
   about where in the user program the problem occurred.
 
-63:
-  Paul Werkowski wrote on cmucl-imp@cons.org 2000-11-15
-    I am looking into this problem that showed up on the cmucl-help
-    list. It seems to me that the "implementation specific environment
-    hacking functions" found in pcl/walker.lisp are completely messed
-    up. The good thing is that they appear to be barely used within
-    PCL and the munged environment object is passed to cmucl only
-    in calls to macroexpand-1, which is probably why this case fails.
-  SBCL uses essentially the same code, so if the environment hacking
-  is screwed up, it affects us too.
-
 64:
   Using the pretty-printer from the command prompt gives funny
   results, apparently because the pretty-printer doesn't know
@@ -660,6 +636,7 @@ WORKAROUND:
 
   (due to reordering of the compiler this example is compiled
   successfully by 0.7.14, but the bug probably remains)
+  (possibly exercised by bug 254 test case)
 
 162:
   (reported by Robert E. Brown 2002-04-16) 
@@ -735,63 +712,6 @@ WORKAROUND:
           :ACCRUED-EXCEPTIONS (:INEXACT)
           :FAST-MODE NIL)
 
-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
@@ -926,15 +846,6 @@ WORKAROUND:
   to redo MIX using a lookup into a 256-entry s-box containing
   29-bit pseudorandom numbers?
 
-208: "package confusion in PCL handling of structure slot handlers"
-  In sbcl-0.7.8 compiling and loading
-       (in-package :cl)
-       (defstruct foo (slot (error "missing")) :type list :read-only t)
-       (defmethod print-object ((foo foo) stream) (print nil stream))
-  causes CERROR "attempting to modify a symbol in the COMMON-LISP
-  package: FOO-SLOT". (This is fairly bad code, but still it's hard
-  to see that it should cause symbols to be interned in the CL package.)
-
 211: "keywords processing"
   a. :ALLOW-OTHER-KEYS T should allow a function to receive an odd
      number of keyword arguments.
@@ -1046,12 +957,6 @@ WORKAROUND:
   produce invalid code, but type checking is not accurate. Similar
   problems exist with VALUES-TYPE-INTERSECTION.)
 
-218: "VALUES type specifier semantics"
-  (THE (VALUES ...) ...) in safe code discards extra values.
-
-  (defun test (x y) (the (values integer) (truncate x y)))
-  (test 10 4) => 2
-
 220:
   Sbcl 0.7.9 fails to compile
 
@@ -1066,9 +971,6 @@ WORKAROUND:
   would be to put the check between evaluation of arguments, but it
   could be tricky to check result types of PROG1, IF etc.
 
-229:
-  (subtypep 'function '(function)) => nil, t.
-
 233: bugs in constraint propagation
   a.
   (defun foo (x)
@@ -1187,15 +1089,6 @@ WORKAROUND:
   ; caught STYLE-WARNING:
   ;   The variable Y is defined but never used.
 
-244: "optimizing away tests for &KEY args of type declared in DEFKNOWN"
-  (caught by clocc-ansi-test :EXCEPSIT-LEGACY-1050)
-  In sbcl-0.pre8.44, (OPEN "foo" :DIRECTION :INPUT :EXTERNAL-FORMAT 'FOO)
-  succeeds with no error (ignoring the bogus :EXTERNAL-FORMAT argument)
-  apparently because the test is optimized away. The problem doesn't 
-  exist in sbcl-0.pre8.19. Deleting the (MEMBER :DEFAULT) declaration
-  for :EXTERNAL-FORMAT in DEFKNOWN OPEN (and LOAD) is a workaround for
-  the problem (and should be removed when the problem is fixed).
-
 245: bugs in disassembler
   a. On X86 an immediate operand for IMUL is printed incorrectly.
   b. On X86 operand size prefix is not recognized.
@@ -1212,18 +1105,6 @@ WORKAROUND:
   (TYPEP 1 '(SYMBOL NIL)) says something about "unknown type
   specifier".
 
-249:
-  Local functions do not check types of unused arguments:
-    (defun foo (x)
-      (flet ((bar (y)
-               (declare (fixnum y))
-               (incf x)))
-        (list (bar x) (bar x) (bar x))))
-    (foo 1.0) => (2.0 3.0 4.0)
-
-250:
-  (make-array nil :initial-element 11) causes a warning.
-
 251:
   (defun foo (&key (a :x))
     (declare (fixnum a))
@@ -1232,6 +1113,44 @@ WORKAROUND:
   does not cause a warning. (BTW: old SBCL issued a warning, but for a
   function, which was never called!)
 
+253: "type checking is embedded THEs"
+  Compiler cannot perform type checking in
+
+    (let () (list (the fixnum (the unsigned-byte (eval -1)))))
+
+  (fixed in 0.8.0.34)
+
+254: (possibly bug 148 in a new guise)
+  In sbcl-0.8.0.52, COMPILE-FILE on 
+    (cl:in-package :cl-user)
+    (declaim (optimize (safety 3) (debug 2) (speed 2) (space 1)))
+    (defstruct foo
+      (uhw2 nil :type (or package null)))
+    (macrolet ((defprojection (variant &key lexpr eexpr)
+                 (let ()
+                   `(defmethod uu ((foo foo))
+                        (let ((uhw2 (foo.uhw2 bar)))
+                          (let ()
+                            (u-flunt uhw2
+                                     (baz (funcall ,lexpr south east 1)))))))))
+      (defprojection h
+        :lexpr (lambda (south east sched)
+                 (flet ((bd (x) (bref x sched)))
+                   (let ((avecname (gafp)))
+                     (declare (type (vector t) avecname))
+                     (multiple-value-prog1
+                         (progn
+                           (setf (avec.count avecname) (length rest))
+                           (setf (aref avecname 0) (bd (h south)))
+                           (setf (aref avecname 1) (bd (h east)))
+                           (stub avecname))
+                       (paip avecname)))))
+        :eexpr (lambda (south east))))
+  fails with 
+    debugger invoked on condition of type TYPE-ERROR:
+      The value NIL is not of type SB-C::NODE.
+
+
 DEFUNCT CATEGORIES OF BUGS
   IR1-#:
     These labels were used for bugs related to the old IR1 interpreter.