0.6.12.9:
[sbcl.git] / BUGS
diff --git a/BUGS b/BUGS
index 8fa26ae..9e31673 100644 (file)
--- a/BUGS
+++ b/BUGS
@@ -104,7 +104,10 @@ WORKAROUND:
   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 someday perhaps I'll be motivated to look it up..
+  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
@@ -115,52 +118,6 @@ WORKAROUND:
          (during macroexpansion of IN-PACKAGE,
          during macroexpansion of DEFFOO)
 
-12:
-  The type system doesn't understand the KEYWORD type very well:
-       (SUBTYPEP 'KEYWORD 'SYMBOL) => NIL, NIL
-  It might be possible to fix this by changing the definition of
-  KEYWORD to (AND SYMBOL (SATISFIES KEYWORDP)), but the type system
-  would need to be a bit smarter about AND types, too:
-       (SUBTYPEP '(AND SYMBOL KEYWORD) 'SYMBOL) => NIL, NIL
-  (The type system does know something about AND types already,
-       (SUBTYPEP '(AND INTEGER FLOAT) 'NUMBER) => T, T
-       (SUBTYPEP '(AND INTEGER FIXNUM) 'NUMBER) =>T, T
-  so likely this is a small patch.)
-
-13:
-  Floating point infinities are screwed up. [When I was converting CMU CL
-  to SBCL, I was looking for complexity to delete, and I thought it was safe
-  to just delete support for floating point infinities. It wasn't: they're
-  generated by the floating point hardware even when we remove support
-  for them in software. -- WHN] Support for them should be restored.
-
-14:
-  The ANSI syntax for non-STANDARD method combination types in CLOS is
-       (DEFGENERIC FOO (X) (:METHOD-COMBINATION PROGN))
-       (DEFMETHOD FOO PROGN ((X BAR)) (PRINT 'NUMBER))
-  If you mess this up, omitting the PROGN qualifier in in DEFMETHOD,
-       (DEFGENERIC FOO (X) (:METHOD-COMBINATION PROGN))
-       (DEFMETHOD FOO ((X BAR)) (PRINT 'NUMBER))
-  the error mesage is not easy to understand:
-          INVALID-METHOD-ERROR was called outside the dynamic scope
-       of a method combination function (inside the body of
-       DEFINE-METHOD-COMBINATION or a method on the generic
-       function COMPUTE-EFFECTIVE-METHOD).
-  It would be better if it were more informative, a la
-          The method combination type for this method (STANDARD) does
-       not match the method combination type for the generic function
-       (PROGN).
-  Also, after you make the mistake of omitting the PROGN qualifier
-  on a DEFMETHOD, doing a new DEFMETHOD with the correct qualifier
-  no longer works:
-       (DEFMETHOD FOO PROGN ((X BAR)) (PRINT 'NUMBER))
-  gives
-          INVALID-METHOD-ERROR was called outside the dynamic scope
-       of a method combination function (inside the body of
-       DEFINE-METHOD-COMBINATION or a method on the generic
-       function COMPUTE-EFFECTIVE-METHOD).
-  This is not very helpful..
-
 15:
   (SUBTYPEP '(FUNCTION (T BOOLEAN) NIL)
             '(FUNCTION (FIXNUM FIXNUM) NIL)) => T, T
@@ -241,10 +198,12 @@ WORKAROUND:
 
 26:
   reported by Sam Steingold on the cmucl-imp mailing list 12 May 2000:
-
-Also, there is another bug: `array-displacement' should return an array
-or nil as first value (as per ANSI CL), while CMUCL declares it as
-returning an array as first value always.
+    Also, there is another bug: `array-displacement' should return an
+    array or nil as first value (as per ANSI CL), while CMUCL declares
+    it as returning an array as first value always.
+  (Actually, I think the old CMU CL version in SBCL never returns NIL,
+  i.e. it's not just a declaration problem, but the definition doesn't
+  behave ANSIly.)
 
 27:
   Sometimes (SB-EXT:QUIT) fails with 
@@ -372,9 +331,7 @@ returning an array as first value always.
 45:
   a slew of floating-point-related errors reported by Peter Van Eynde
   on July 25, 2000:
-       a: (SQRT -9.0) fails, because SB-KERNEL::COMPLEX-SQRT is undefined.
-          Similarly, COMPLEX-ASIN, COMPLEX-ACOS, COMPLEX-ACOSH, and others
-          aren't found.
+       a: (fixed in sbcl-0.6.11.25)
        b: SBCL's value for LEAST-POSITIVE-SHORT-FLOAT is bogus, and 
           should probably be 1.4012985e-45. In SBCL,
           (/ LEAST-POSITIVE-SHORT-FLOAT 2) returns a number smaller
@@ -388,10 +345,7 @@ returning an array as first value always.
                (EXPT 10.0d0 1000)
           PVE's regression tests want them to raise errors. SBCL
           generates the infinities instead, which may or may not be
-          conforming behavior, but then blow it by being unable to
-          output the infinities, since support for infinities is generally
-          broken, and in particular SB-IMPL::OUTPUT-FLOAT-INFINITY is
-          undefined.
+          conforming behavior.
        d: (in section12.erg) various forms a la 
                (FLOAT 1 DOUBLE-FLOAT-EPSILON)
           don't give the right behavior.
@@ -532,8 +486,18 @@ Error in function C::GET-LAMBDA-TO-COMPILE:
    #<Closure Over Function "DEFUN (SETF MACRO-FUNCTION)" {480E21B1}> was defined in a non-null environment.
 
 58:
-  (SUBTYPEP '(AND ZILCH INTEGER) 'ZILCH)
-  => NIL, NIL
+  (SUBTYPEP '(AND ZILCH INTEGER) 'ZILCH) => NIL, NIL
+  Note: I looked into fixing this in 0.6.11.15, but gave up. The
+  problem seems to be that there are two relevant type methods for
+  the subtypep operation, HAIRY :COMPLEX-SUBTYPEP-ARG2 and
+  INTERSECTION :COMPLEX-SUBTYPEP-ARG1, and only the first is
+  called. This could be fixed, but type dispatch is messy and
+  confusing enough already, I don't want to complicate it further.
+  Perhaps someday we can make CLOS cross-compiled (instead of compiled
+  after bootstrapping) so that we don't need to have the type system
+  available before CLOS, and then we can rewrite the type methods to
+  CLOS methods, and then expressing the solutions to stuff like this
+  should become much more straightforward. -- WHN 2001-03-14
 
 59:
   CL:*DEFAULT-PATHNAME-DEFAULTS* doesn't behave as ANSI suggests (reflecting
@@ -541,6 +505,16 @@ Error in function C::GET-LAMBDA-TO-COMPILE:
   or query the current working directory (a la Unix "chdir" and "pwd"),
   which is functionality that ILISP needs (and currently gets with low-level
   hacks).
+    When this is fixed, probably the more-or-less-parallel Unix-level
+  hacks
+       DEFAULT-DIRECTORY
+       %SET-DEFAULT-DIRECTORY
+       etc.?
+  should go away. Also we need to figure out what's the proper way to 
+  deal with the interaction of users assigning new values to
+  *DEFAULT-PATHNAME-DEFAULTS* and cores being saved and restored.
+  (Perhaps just make restoring from a save always overwrite the old
+  value with the new Unix-level default directory?)
 
 60:
   The debugger LIST-LOCATIONS command doesn't work properly.
@@ -799,6 +773,163 @@ Error in function C::GET-LAMBDA-TO-COMPILE:
   them as methods, and identified their generic functions and
   specializers.
 
+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
+  the mean of the distribution can be systematically O(0.1%) wrong.
+  Just increasing R-I-E-B is probably not a good solution, since
+  it would decrease efficiency more than is probably necessary. Perhaps
+  using some sort of accept/reject method would be better.
+
+84:
+  (SUBTYPEP '(SATISFIES SOME-UNDEFINED-FUN) NIL)=>NIL,T (should be NIL,NIL)
+
+85:
+  Internally the compiler sometimes evaluates
+    (sb-kernel:type/= (specifier-type '*) (specifier-type t))
+  (I stumbled across this when I added an
+    (assert (not (eq type1 *wild-type*)))
+  in the NAMED :SIMPLE-= type method.) '* isn't really a type, and
+  in a type context should probably be translated to T, and so it's
+  probably to ask whether it's equal to the T type and then (using the
+  EQ type comparison in the NAMED :SIMPLE-= type method) return NIL.
+  (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.)
+
+93:
+  In sbcl-0.6.11.26, (COMPILE 'IN-HOST-COMPILATION-MODE) in
+  src/cold/shared.lisp doesn't correctly translate the
+  interpreted function
+    (defun in-host-compilation-mode (fn)
+      (let ((*features* (cons :sb-xc-host *features*))
+            ;; the CROSS-FLOAT-INFINITY-KLUDGE, as documented in
+            ;; base-target-features.lisp-expr:
+            (*shebang-features* (set-difference *shebang-features*
+                                                '(:sb-propagate-float-type
+                                                  :sb-propagate-fun-type))))
+        (with-additional-nickname ("SB-XC" "SB!XC")
+          (funcall fn))))
+  No error is reported by the compiler, but when the function is executed,
+  it causes an error
+    TYPE-ERROR in SB-KERNEL::OBJECT-NOT-TYPE-ERROR-HANDLER:
+      (:LINUX :X86 :IEEE-FLOATING-POINT :SB-CONSTRAIN-FLOAT-TYPE :SB-TEST
+       :SB-INTERPRETER :SB-DOC :UNIX ...) is not of type SYMBOL.
+
+94a: 
+  Inconsistencies between derived and declared VALUES return types for
+  DEFUN aren't checked very well. E.g. the logic which successfully
+  catches problems like
+    (declaim (ftype (function (fixnum) float) foo))
+    (defun foo (x)
+      (declare (type integer x))
+      (values x)) ; wrong return type, detected, gives warning, good!
+  fails to catch
+    (declaim (ftype (function (t) (values t t)) bar))
+    (defun bar (x)
+      (values x)) ; wrong number of return values, no warning, bad!
+  The cause of this is seems to be that (1) the internal function 
+  VALUES-TYPES-EQUAL-OR-INTERSECT used to make the check handles its
+  arguments symmetrically, and (2) when the type checking code was
+  written back when when SBCL's code was still CMU CL, the intent
+  was that this case
+    (declaim (ftype (function (t) t) bar))
+    (defun bar (x)
+      (values x x)) ; wrong number of return values; should give warning?
+  not be warned for, because a two-valued return value is considered
+  to be compatible with callers who expects a single value to be
+  returned. That intent is probably not appropriate for modern ANSI
+  Common Lisp, but fixing this might be complicated because of other
+  divergences between auld-style and new-style handling of
+  multiple-VALUES types. (Some issues related to this were discussed
+  on cmucl-imp at some length sometime in 2000.)
+
+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.
+
+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
+  whenever the type of the slot is declared, because out-of-line
+  structure slot setters are implemented as closures to save space,
+  so the compiler doesn't compile the type test into code, but
+  instead just saves the type in a lexical closure and interprets it
+  at runtime.
+    A proper solution involves deciding whether it's really worth
+  saving space by implementing structure slot accessors as closures.
+  (If it's not worth it, the problem vanishes automatically. If it
+  is worth it, there are hacks we could use to force type tests to
+  be compiled anyway, and even shared. E.g. we could implement
+  an EQUAL hash table mapping from types to compiled type tests, 
+  and save the appropriate compiled type test as part of each lexical
+  closure; or we could make the lexical closures be placeholders
+  which overwrite their old definition as a lexical closure with
+  a new compiled definition the first time that they're called.)
+    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)
+                 ;; a workaround for the problem, encouraging the
+                 ;; inline expansion of the structure accessor, so
+                 ;; that the compiler can optimize its type test
+                 (let ((new-value (gensym "NEW-VALUE-"))
+                        (structure-value (gensym "STRUCTURE-VALUE-")))
+                   `(lambda (,new-value ,structure-value)
+                      (setf (,place-function-name ,structure-value)
+                            ,new-value))))
+      ;; no problem, can just use the ordinary expansion
+      `(function (setf ,place-function-name))))
+
+99:
+  DESCRIBE interacts poorly with *PRINT-CIRCLE*, e.g. the output from 
+    (let ((*print-circle* t)) (describe (make-hash-table)))
+  is weird,
+    #<HASH-TABLE :TEST EQL :COUNT 0 {90BBFC5}> is an . (EQL)
+    Its SIZE is 16.
+    Its REHASH-SIZE is 1.5. Its REHASH-THRESHOLD is . (1.0)
+    It holds 0 key/value pairs.
+  where the ". (EQL)" and ". (1.0)" substrings are screwups.
+  (This is likely a pretty-printer problem which happens to
+  be exercised by DESCRIBE, not actually a DESCRIBE problem.)
+
+100:
+  There's apparently a bug in CEILING optimization which caused 
+  Douglas Crosher to patch the CMU CL version. Martin Atzmueller
+  applied the patches to SBCL and they didn't seem to cause problems
+  (as reported sbcl-devel 2001-05-04). However, since the patches
+  modify nontrivial code which was apparently written incorrectly
+  the first time around, until regression tests are written I'm not 
+  comfortable merging the patches in the CVS version of SBCL.
+
 
 KNOWN BUGS RELATED TO THE IR1 INTERPRETER