0.8.0.71:
[sbcl.git] / BUGS
diff --git a/BUGS b/BUGS
index ab82a20..e4dd346 100644 (file)
--- a/BUGS
+++ b/BUGS
@@ -108,23 +108,6 @@ WORKAROUND:
   Perhaps any number of such consecutive lines ought to turn into a
   single "compiling top-level forms:" line.
 
-10:
-  The way that the compiler munges types with arguments together
-  with types with no arguments (in e.g. TYPE-EXPAND) leads to
-  weirdness visible to the user:
-       (DEFTYPE FOO () 'FIXNUM)
-       (TYPEP 11 'FOO) => T
-       (TYPEP 11 '(FOO)) => T, which seems weird
-       (TYPEP 11 'FIXNUM) => T
-       (TYPEP 11 '(FIXNUM)) signals an error, as it should
-  The situation is complicated by the presence of Common Lisp types
-  like UNSIGNED-BYTE (which can either be used in list form or alone)
-  so I'm not 100% sure that the behavior above is actually illegal.
-  But I'm 90+% sure, and the following related behavior,
-       (TYPEP 11 'AND) => T
-  treating the bare symbol AND as equivalent to '(AND), is specifically
-  forbidden (by the ANSI specification of the AND type).
-
 11:
   It would be nice if the
        caught ERROR:
@@ -207,13 +190,6 @@ WORKAROUND:
   so they could be supported after all. Very likely 
   SIGCONTEXT-FLOATING-POINT-MODES could now be supported, too.
 
-43:
-  (as discussed by Douglas Crosher on the cmucl-imp mailing list ca. 
-  Aug. 10, 2000): CMUCL currently interprets 'member as '(member); same
-  issue with 'union, 'and, 'or etc. So even though according to the
-  ANSI spec, bare 'MEMBER, 'AND, and 'OR are not legal types, CMUCL
-  (and now SBCL) interpret them as legal types.
-
 45:
   a slew of floating-point-related errors reported by Peter Van Eynde
   on July 25, 2000:
@@ -381,7 +357,7 @@ WORKAROUND:
     As a workaround for the problem, #'(SETF FOO) expressions can
   be replaced with (EFFICIENT-SETF-FUNCTION FOO), where
 (defmacro efficient-setf-function (place-function-name)
-  (or #+sbcl (and (sb-impl::info :function :accessor-for place-function-name)
+  (or #+sbcl (and (sb-int:info :function :accessor-for place-function-name)
                  ;; a workaround for the problem, encouraging the
                  ;; inline expansion of the structure accessor, so
                  ;; that the compiler can optimize its type test
@@ -566,22 +542,6 @@ WORKAROUND:
   under OpenBSD 2.9 on my X86 laptop. Do be patient when you try it:
   it took more than two minutes (but less than five) for me.
 
-144: 
-  (This was once known as IR1-4, but it lived on even after the
-  IR1 interpreter went to the big bit bucket in the sky.)
-  The system accepts DECLAIM in most places where DECLARE would be 
-  accepted, without even issuing a warning. ANSI allows this, but since
-  it's fairly easy to mistype DECLAIM instead of DECLARE, and the
-  meaning is rather different, and it's unlikely that the user
-  has a good reason for doing DECLAIM not at top level, it would be 
-  good to issue a STYLE-WARNING when this happens. A possible
-  fix would be to issue STYLE-WARNINGs for DECLAIMs not at top level,
-  or perhaps to issue STYLE-WARNINGs for any EVAL-WHEN not at top level.
-  [This is considered an IR1-interpreter-related bug because until
-  EVAL-WHEN is rewritten, which won't happen until after the IR1
-  interpreter is gone, the system's notion of what's a top-level form
-  and what's not will remain too confused to fix this problem.]
-
 145:
   ANSI allows types `(COMPLEX ,FOO) to use very hairy values for
   FOO, e.g. (COMPLEX (AND REAL (SATISFIES ODDP))). The old CMU CL
@@ -636,7 +596,6 @@ 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) 
@@ -713,44 +672,6 @@ WORKAROUND:
           :FAST-MODE NIL)
 
 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]
-
-  In recent SBCL the following example also illustrates this bug:
-
     (time (compile
            nil
            '(lambda ()
@@ -800,8 +721,8 @@ WORKAROUND:
      lists and &KEY arguments) do not signal errors when they should.
 
 
-201: "Incautious type inference from compound CONS types"
-  (reported by APD sbcl-devel 2002-09-17)
+201: "Incautious type inference from compound types"
+  a. (reported by APD sbcl-devel 2002-09-17)
     (DEFUN FOO (X)
       (LET ((Y (CAR (THE (CONS INTEGER *) X))))
         (SETF (CAR X) NIL)
@@ -814,6 +735,17 @@ WORKAROUND:
 
     (FOO ' (1 . 2)) => "NIL IS INTEGER, Y = 1"
 
+  b.
+    * (defun foo (x)
+        (declare (type (array * (4 4)) x))
+        (let ((y x))
+          (setq x (make-array '(4 4)))
+          (adjust-array y '(3 5))
+          (= (array-dimension y 0) (eval `(array-dimension ,y 0)))))
+    FOO
+    * (foo (make-array '(4 4) :adjustable t))
+    NIL
+
 205: "environment issues in cross compiler"
   (These bugs have no impact on user code, but should be fixed or
   documented.)
@@ -1009,17 +941,6 @@ WORKAROUND:
 
   (foo '(nil) '(t)) => NIL, T.
 
-  b. (reported by brown on #lisp 2003-01-21)
-
-    (defun find-it (x)
-      (declare (optimize (speed 3) (safety 0)))
-      (declare (notinline mapcar))
-      (let ((z (mapcar #'car x)))
-        (find 'foobar z)))
-
-  Without (DECLARE (NOTINLINE MAPCAR)), Python cannot derive that Z is
-  LIST.
-
 237: "Environment arguments to type functions"
   a. Functions SUBTYPEP, TYPEP, UPGRADED-ARRAY-ELEMENT-TYPE, and 
      UPGRADED-COMPLEX-PART-TYPE now have an optional environment
@@ -1093,14 +1014,6 @@ WORKAROUND:
   a. On X86 an immediate operand for IMUL is printed incorrectly.
   b. On X86 operand size prefix is not recognized.
 
-246: "NTH-VALUE scaling problem"
-  NTH-VALUE's current implementation for constant integers scales in
-  compile-time as O(n^4), as indeed must the optional dispatch
-  mechanism on which it is implemented.  While it is unlikely to
-  matter in real user code, it's still unpleasant to observe that
-  (NTH-VALUE 1000 (VALUES-LIST (MAKE-LIST 1001))) takes several hours
-  to compile.
-
 248: "reporting errors in type specifier syntax"
   (TYPEP 1 '(SYMBOL NIL)) says something about "unknown type
   specifier".
@@ -1113,70 +1026,25 @@ 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
+256:
+  Compiler does not emit warnings for
 
-    (let () (list (the fixnum (the unsigned-byte (eval -1)))))
+  a. (lambda () (svref (make-array 8 :adjustable t) 1))
 
-  (fixed in 0.8.0.34)
+  b. (lambda (x)
+       (list (let ((y (the real x)))
+               (unless (floatp y) (error ""))
+               y)
+             (integer-length x)))
 
-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.
+  c. (lambda (x)
+       (declare (optimize (debug 0)))
+       (declare (type vector x))
+       (list (fill-pointer x)
+             (svref x 1)))
 
-255: 
-  In sbcl-0.8.0.52, COMPILE-FILE on
-    (cl:in-package :cl-user)
-    (declaim (optimize (safety 3) (debug 2) (speed 2) (space 1)))
-    (defvar *1*)
-    (defvar *2*)
-    (defstruct v a b)
-    (defstruct w)
-    (defstruct yam (v nil :type (or v null)))
-    (defstruct un u)
-    (defstruct (bod (:include un)) bo)
-    (defstruct (bad (:include bod)) ba)
-    (declaim (ftype (function ((or w bad) (or w bad)) (values)) %ufm))
-    (defun %ufm (base bound) (froj base bound *1*) (values))
-    (declaim (ftype (function ((vector t)) (or w bad)) %pu))
-    (defun %pu (pds) *2*)
-    (defun uu (yam)
-      (let ((v (yam-v az)))
-        (%ufm v
-              (flet ((project (x) (frob x 0)))
-                (let ((avecname *1*))
-                  (multiple-value-prog1
-                      (progn (%pu avecname))
-                    (frob)))))))
-  fails with 
-    failed AVER:
-      "(AND (EQ (CONTINUATION-KIND START) INSIDE-BLOCK) (NOT (BLOCK-DELETE-P BLOCK)))"
+257:
+  Complex array type does not have corresponding type specifier.
 
 DEFUNCT CATEGORIES OF BUGS
   IR1-#: