0.7.13.4:
[sbcl.git] / BUGS
diff --git a/BUGS b/BUGS
index a90c4a5..1b6c039 100644 (file)
--- a/BUGS
+++ b/BUGS
@@ -42,7 +42,8 @@ KNOWN BUGS OF NO SPECIAL CLASS:
   program, even if you know or guess enough about the internals of
   SBCL to wager that this (undefined in ANSI) operation would be safe.
 
-3:
+3: "type checking of structure slots"
+  a:
   ANSI specifies that a type mismatch in a structure slot
   initialization value should not cause a warning.
 WORKAROUND:
@@ -78,6 +79,28 @@ WORKAROUND:
   Such code should compile without complaint and work correctly either
   on SBCL or on any other completely compliant Common Lisp system.
 
+  b: &AUX argument in a boa-constructor without a default value means
+     "do not initilize this slot" and does not cause type error. But
+     an error may be signalled at read time and it would be good if
+     SBCL did it.
+
+  c: Reading of not initialized slot sometimes causes SEGV.
+
+  d:
+    (declaim (optimize (safety 3) (speed 1) (space 1)))
+    (defstruct foo
+      x y)
+    (defstruct (stringwise-foo (:include foo
+                                         (x "x" :type simple-string)
+                                         (y "y" :type simple-string))))
+    (defparameter *stringwise-foo*
+      (make-stringwise-foo))
+    (setf (foo-x *stringwise-foo*) 0)
+    (defun frob-stringwise-foo (sf)
+      (aref (stringwise-foo-x sf) 0))
+    (frob-stringwise-foo *stringwise-foo*)
+  SEGV.
+
 6:
   bogus warnings about undefined functions for magic functions like
   SB!C::%%DEFUN and SB!C::%DEFCONSTANT when cross-compiling files
@@ -293,40 +316,6 @@ WORKAROUND:
   then requesting a BACKTRACE at the debugger prompt gives no information
   about where in the user program the problem occurred.
 
-62:
-  The compiler is supposed to do type inference well enough that 
-  the declaration in
-    (TYPECASE X
-      ((SIMPLE-ARRAY SINGLE-FLOAT)
-       (LOCALLY
-         (DECLARE (TYPE (SIMPLE-ARRAY SINGLE-FLOAT) X))
-         ..))
-      ..)
-  is redundant. However, as reported by Juan Jose Garcia Ripoll for
-  CMU CL, it sometimes doesn't. Adding declarations is a pretty good
-  workaround for the problem for now, but can't be done by the TYPECASE
-  macros themselves, since it's too hard for the macro to detect
-  assignments to the variable within the clause. 
-    Note: The compiler *is* smart enough to do the type inference in
-  many cases. This case, derived from a couple of MACROEXPAND-1
-  calls on Ripoll's original test case,
-    (DEFUN NEGMAT (A)
-      (DECLARE (OPTIMIZE SPEED (SAFETY 0)))
-      (COND ((TYPEP A '(SIMPLE-ARRAY SINGLE-FLOAT)) NIL
-             (LET ((LENGTH (ARRAY-TOTAL-SIZE A)))
-               (LET ((I 0) (G2554 LENGTH))
-                 (DECLARE (TYPE REAL G2554) (TYPE REAL I))
-                 (TAGBODY
-                  SB-LOOP::NEXT-LOOP
-                  (WHEN (>= I G2554) (GO SB-LOOP::END-LOOP))
-                  (SETF (ROW-MAJOR-AREF A I) (- (ROW-MAJOR-AREF A I)))
-                  (GO SB-LOOP::NEXT-LOOP)
-                  SB-LOOP::END-LOOP))))))
-  demonstrates the problem; but the problem goes away if the TAGBODY
-  and GO forms are removed (leaving the SETF in ordinary, non-looping
-  code), or if the TAGBODY and GO forms are retained, but the 
-  assigned value becomes 0.0 instead of (- (ROW-MAJOR-AREF A I)).
-
 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
@@ -637,7 +626,6 @@ WORKAROUND:
 
   (note the space between the comma and the point)
 
-
 143:
   (reported by Jesse Bouwman 2001-10-24 through the unfortunately
   prominent SourceForge web/db bug tracking system, which is 
@@ -728,11 +716,6 @@ WORKAROUND:
   expansion, leaving garbage consisting of infinished blocks of the
   partially converted function.)
 
-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)
-
 162:
   (reported by Robert E. Brown 2002-04-16) 
   When a function is called with too few arguments, causing the
@@ -944,6 +927,11 @@ WORKAROUND:
 
      (see bug 203)
 
+  c. (defun foo (x y)
+       (locally (declare (type fixnum x y))
+         (+ x (* 2 y))))
+     (foo 1.1 2) => 5.1
+
 194: "no error from (THE REAL '(1 2 3)) in some cases"
   fixed parts:
     a. In sbcl-0.7.7.9, 
@@ -1178,21 +1166,22 @@ WORKAROUND:
   would be to put the check between evaluation of arguments, but it
   could be tricky to check result types of PROG1, IF etc.
 
-228: "function-lambda-expression problems"
-  in sbcl-0.7.9.6x, from the REPL:
-    * (progn (declaim (inline foo)) (defun foo (x) x))
-    FOO
-    * (function-lambda-expression #'foo)
-    (SB-C:LAMBDA-WITH-LEXENV NIL NIL NIL (X) (BLOCK FOO X)), NIL, FOO
-  but this first return value is not suitable for input to FUNCTION or
-  COMPILE, as required by ANSI.
-
 229:
   (subtypep 'function '(function)) => nil, t.
 
-233:
-  Bug in constraint propagation:
+231: "SETQ does not correctly check the type of a variable being set"
+  b.
+    (defun foo (x z)
+      (declare (type integer x))
+      (locally (declare (type (real 1) x))
+        (setq x z))
+      (list x z))
+    (foo 0 0) => (0 0).
+
+  (fixed in 0.7.12.8)
 
+233: bugs in constraint propagation
+  a.
   (defun foo (x)
     (declare (optimize (speed 2) (safety 3)))
     (let ((y 0d0))
@@ -1204,6 +1193,114 @@ WORKAROUND:
   (foo 4) => segmentation violation
 
   (see usage of CONTINUATION-ASSERTED-TYPE in USE-RESULT-CONSTRAINTS)
+  (see also bug 236)
+
+  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
+
+234:
+  (fixed in sbcl-0.7.10.36)
+
+235: "type system and inline expansion"
+  a.
+  (declaim (ftype (function (cons) number) acc))
+  (declaim (inline acc))
+  (defun acc (c)
+    (the number (car c)))
+
+  (defun foo (x y)
+    (values (locally (declare (optimize (safety 0)))
+              (acc x))
+            (locally (declare (optimize (safety 3)))
+              (acc y))))
+
+  (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.
+
+236: "THE semantics is broken"
+
+  (defun foo (a f)
+    (declare (optimize (speed 2) (safety 0)))
+    (+ 1d0
+       (the double-float
+         (multiple-value-prog1
+             (svref a 0)
+           (unless f (return-from foo 0))))))
+
+  (foo #(4) nil) => SEGV
+
+  VOP selection thinks that in unsafe code result type assertions
+  should be valid immediately. (See also bug 233a.)
+
+  The similar problem exists for TRULY-THE.
+
+237: "Environment arguments to type functions"
+  a. Functions SUBTYPEP, TYPEP, UPGRADED-ARRAY-ELEMENT-TYPE, and 
+     UPGRADED-COMPLEX-PART-TYPE now have an optional environment
+     argument, but they ignore it completely.  This is almost 
+     certainly not correct.
+  b. Also, the compiler's optimizers for TYPEP have not been informed
+     about the new argument; consequently, they will not transform
+     calls of the form (TYPEP 1 'INTEGER NIL), even though this is
+     just as optimizeable as (TYPEP 1 'INTEGER).
+
+238: "REPL compiler overenthusiasm for CLOS code"
+  From the REPL,
+    * (defclass foo () ())
+    * (defmethod bar ((x foo) (foo foo)) (call-next-method))
+  causes approximately 100 lines of code deletion notes.  Some
+  discussion on this issue happened under the title 'Three "interesting"
+  bugs in PCL', resulting in a fix for this oververbosity from the
+  compiler proper; however, the problem persists in the interactor
+  because the notion of original source is not preserved: for the
+  compiler, the original source of the above expression is (DEFMETHOD
+  BAR ((X FOO) (FOO FOO)) (CALL-NEXT-METHOD)), while by the time the
+  compiler gets its hands on the code needing compilation from the REPL,
+  it has been macroexpanded several times.
+
+240:
+  "confused lexical/special warnings in MULTIPLE-VALUE-BIND"
+  (from tonyms on #lisp IRC 2003-02-25)
+  In sbcl-0.7.12.55, compiling 
+    (cl:in-package :cl-user)
+    (defvar *foo* 0)
+    (defvar *bar* 1)
+    (defun bar ()
+      (multiple-value-bind (*foo* *bar*) 'eleventy-one
+        (bletch)))
+    (defun bletch () (format t "~&*FOO*=~S *BAR*=~S" *foo* *bar*))
+    (bar)
+  gives warnings like "using the lexical binding of the symbol *FOO*"
+  even though LOADing the fasl file shows that in fact the special
+  bindings are being used.
+
+241:
+  "DEFCLASS mysteriously remembers uninterned accessor names."
+  (from tonyms on #lisp IRC 2003-02-25)
+  In sbcl-0.7.12.55, typing
+    (defclass foo () ((bar :accessor foo-bar)))
+    (profile foo-bar)
+    (unintern 'foo-bar)
+    (defclass foo () ((bar :accessor foo-bar)))
+  gives the error message
+    "#:FOO-BAR already names an ordinary function or a macro."
+  So it's somehow checking the uninterned old accessor name instead
+  of the new requested accessor name, which seems broken to me (WHN).
 
 DEFUNCT CATEGORIES OF BUGS
   IR1-#: