X-Git-Url: http://repo.macrolet.net/gitweb/?a=blobdiff_plain;f=BUGS;h=0b8a6774943c78471e80291d883a9ceef74b0a51;hb=582503547d172f95aaf118311f09fe6828a6ea72;hp=97a672161bf67e7d99f7576530a0d180d72d8af4;hpb=85029815128ff53d16013d51ad0beb79b0eb3744;p=sbcl.git diff --git a/BUGS b/BUGS index 97a6721..0b8a677 100644 --- a/BUGS +++ b/BUGS @@ -32,8 +32,6 @@ have gone away (typically because they were fixed, but sometimes for other reasons, e.g. because they were moved elsewhere). -KNOWN BUGS OF NO SPECIAL CLASS: - 2: DEFSTRUCT almost certainly should overwrite the old LAYOUT information instead of just punting when a contradictory structure definition @@ -84,24 +82,7 @@ WORKAROUND: 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 (for inline - accessors it is fixed, but out-of-line still do not perform type - check). - - 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. + d: (fixed in 0.8.1.5) 7: The "compiling top-level form:" output ought to be condensed. @@ -187,12 +168,6 @@ WORKAROUND: 45: a slew of floating-point-related errors reported by Peter Van Eynde on July 25, 2000: - b: SBCL's value for LEAST-POSITIVE-SHORT-FLOAT on the x86 is - bogus, and should probably be 1.4012985e-45. In SBCL, - (/ LEAST-POSITIVE-SHORT-FLOAT 2) returns a number smaller - than LEAST-POSITIVE-SHORT-FLOAT. Similar problems - exist for LEAST-NEGATIVE-SHORT-FLOAT, LEAST-POSITIVE-LONG-FLOAT, - and LEAST-NEGATIVE-LONG-FLOAT. c: Many expressions generate floating infinity on x86/Linux: (/ 1 0.0) (/ 1 0.0d0) @@ -209,12 +184,6 @@ WORKAROUND: (FLOAT 1 DOUBLE-FLOAT-EPSILON) don't give the right behavior. -46: - type safety errors reported by Peter Van Eynde July 25, 2000: - k: READ-BYTE is supposed to signal TYPE-ERROR when its argument is - not a binary input stream, but instead cheerfully reads from - character streams, e.g. (MAKE-STRING-INPUT-STREAM "abc"). - 60: The debugger LIST-LOCATIONS command doesn't work properly. (How should it work properly?) @@ -240,12 +209,6 @@ WORKAROUND: crashes SBCL. In general tracing anything which is used in the implementation of TRACE is likely to have the same problem. -75: - As reported by Martin Atzmueller on sbcl-devel 26 Dec 2000, - ANSI says that WITH-OUTPUT-TO-STRING should have a keyword - :ELEMENT-TYPE, but in sbcl-0.6.9 this is not defined for - WITH-OUTPUT-TO-STRING. - 78: ANSI says in one place that type declarations can be abbreviated even when the type name is not a symbol, e.g. @@ -293,34 +256,6 @@ WORKAROUND: holding... * is not equivalent to T in many cases, such as (VECTOR *) /= (VECTOR T). -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 @@ -329,6 +264,11 @@ WORKAROUND: 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 @@ -389,6 +329,15 @@ WORKAROUND: time trying to GC afterwards. Surely there's some more economical way to implement (ROOM T). + Daniel Barlow doesn't know what fixed this, but observes that it + doesn't seem to be the case in 0.8.7.3 any more. Instead, (ROOM T) + in a fresh SBCL causes + + debugger invoked on a SB-INT:BUG in thread 5911: + failed AVER: "(SAP= CURRENT END)" + + unless a GC has happened beforehand. + 117: When the compiler inline expands functions, it may be that different kinds of return values are generated from different code branches. @@ -417,6 +366,8 @@ WORKAROUND: your pre-0.7.0 state of grace with #+sbcl (declaim (notinline find position find-if position-if)) ; bug 117.. + (see also bug 279) + 118: as reported by Eric Marsden on cmucl-imp@cons.org 2001-08-14: (= (FLOAT 1 DOUBLE-FLOAT-EPSILON) @@ -431,14 +382,6 @@ WORKAROUND: Raymond Toy comments that this is tricky on the X86 since its FPU uses 80-bit precision internally. -120b: - Even in sbcl-0.pre7.x, which is supposed to be free of the old - non-ANSI behavior of treating the function return type inferred - from the current function definition as a declaration of the - return type from any function of that name, the return type of NIL - is attached to FOO in 120a above, and used to optimize code which - calls FOO. - 124: As of version 0.pre7.14, SBCL's implementation of MACROLET makes the entire lexical environment at the point of MACROLET available @@ -518,11 +461,9 @@ WORKAROUND: * '``(FOO ,@',@S) ``(FOO SB-IMPL::BACKQ-COMMA-AT S) - b. - * (write '`(, .ala.) :readably t :pretty t) - `(,.ALA.) - - (note the space between the comma and the point) + c. (reported by Paul F. Dietz) + * '`(lambda ,x) + `(LAMBDA (SB-IMPL::BACKQ-COMMA X)) 143: (reported by Jesse Bouwman 2001-10-24 through the unfortunately @@ -547,6 +488,7 @@ WORKAROUND: it took more than two minutes (but less than five) for me. 145: + a. ANSI allows types `(COMPLEX ,FOO) to use very hairy values for FOO, e.g. (COMPLEX (AND REAL (SATISFIES ODDP))). The old CMU CL COMPLEX implementation didn't deal with this, and hasn't been @@ -554,6 +496,8 @@ WORKAROUND: conformance problem, since seems hard to construct useful code where it matters.) + b. (fixed in 0.8.3.43) + 146: Floating point errors are reported poorly. E.g. on x86 OpenBSD with sbcl-0.7.1, @@ -586,6 +530,8 @@ WORKAROUND: isn't too surprising since there are many differences in stack implementation and GC conservatism between the X86 and other ports.) + This is probably the same bug as 216 + 167: In sbcl-0.7.3.11, compiling the (illegal) code (in-package :cl-user) @@ -695,8 +641,7 @@ 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. - c. the examples in CLHS 7.6.5.1 (regarding generic function lambda - lists and &KEY arguments) do not signal errors when they should. + c. (fixed in 0.8.4.23) 201: "Incautious type inference from compound types" a. (reported by APD sbcl-devel 2002-09-17) @@ -783,11 +728,7 @@ WORKAROUND: all of the arguments are circular is probably desireable). 213: "Sequence functions and type checking" - a. MAKE-SEQUENCE, COERCE, MERGE and CONCATENATE cannot deal with - various complicated, though recognizeable, CONS types [e.g. - (CONS * (CONS * NULL)) - which according to ANSI should be recognized] (and, in SAFETY 3 - code, should return a list of LENGTH 2 or signal an error) + a. (fixed in 0.8.4.36) b. MAP, when given a type argument that is SUBTYPEP LIST, does not check that it will return a sequence of the given type. Fixing it along the same lines as the others (cf. work done around @@ -802,20 +743,6 @@ WORKAROUND: (INTEGERP (CAR (MAKE-SEQUENCE '(CONS INTEGER *) 2))) can erroneously return T. -214: - SBCL 0.6.12.43 fails to compile - - (locally - (declare (optimize (inhibit-warnings 0) (compilation-speed 2))) - (flet ((foo (&key (x :vx x-p)) (list x x-p))) - (foo 1 2))) - - or a more simple example: - - (locally - (declare (optimize (inhibit-warnings 0) (compilation-speed 2))) - (lambda (x) (declare (fixnum x)) (if (< x 0) 0 (1- x)))) - 215: ":TEST-NOT handling by functions" a. FIND and POSITION currently signal errors when given non-NIL for both their :TEST and (deprecated) :TEST-NOT arguments, but by @@ -840,6 +767,8 @@ WORKAROUND: the bad VECTOR-PUSH-EXTEND frame causes GC problems, though that may not be the actual problem. (CMU CL 18c doesn't have problems with this.) + This is probably the same bug as 162 + 217: "Bad type operations with FUNCTION types" In sbcl.0.7.7: @@ -863,38 +792,9 @@ WORKAROUND: 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. Similar - problems exist with VALUES-TYPE-INTERSECTION.) - -220: - Sbcl 0.7.9 fails to compile - - (multiple-value-call #'list - (the integer (helper)) - nil) - - Type check for INTEGER, the result of which serves as the first - argument of M-V-C, is inserted after evaluation of NIL. So arguments - of M-V-C are pushed in the wrong order. As a temporary workaround - type checking was disabled for M-V-Cs in 0.7.9.13. A better solution - would be to put the check between evaluation of arguments, but it - could be tricky to check result types of PROG1, IF etc. + produce invalid code, but type checking is not accurate.) 233: bugs in constraint propagation - a. - (defun foo (x) - (declare (optimize (speed 2) (safety 3))) - (let ((y 0d0)) - (values - (the double-float x) - (setq y (+ x 1d0)) - (setq x 3d0) - (quux y (+ y 2d0) (* y 3d0))))) - (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) @@ -991,10 +891,6 @@ WORKAROUND: a. On X86 an immediate operand for IMUL is printed incorrectly. b. On X86 operand size prefix is not recognized. -248: "reporting errors in type specifier syntax" - (TYPEP 1 '(SYMBOL NIL)) says something about "unknown type - specifier". - 251: (defun foo (&key (a :x)) (declare (fixnum a)) @@ -1028,7 +924,7 @@ WORKAROUND: array types, there's no good way to tell it you're doing it intentionally so that it should shut up and just compile the code. - Another poblem is confusing error message "asserted type ARRAY + Another problem is confusing error message "asserted type ARRAY conflicts with derived type (VALUES SIMPLE-VECTOR &OPTIONAL)" during compiling (LAMBDA (V) (VALUES (SVREF V 0) (VECTOR-POP V))). @@ -1038,22 +934,311 @@ WORKAROUND: currently checks for complex arrays seem to be performed by callees.) -258: +259: + (compile nil '(lambda () (aref (make-array 0) 0))) compiles without + warning. Analogous cases with the index and length being equal and + greater than 0 are warned for; the problem here seems to be that the + type required for an array reference of this type is (INTEGER 0 (0)) + which is canonicalized to NIL. + +260: + a. + (let* ((s (gensym)) + (t1 (specifier-type s))) + (eval `(defstruct ,s)) + (type= t1 (specifier-type s))) + => NIL, NIL + + (fixed in 0.8.1.24) + + b. The same for CSUBTYPEP. + +262: "yet another bug in inline expansion of local functions" Compiler fails on - (defun u-b-sra (ad0) - (declare (special *foo* *bar*)) - (declare (optimize (safety 3) (speed 2) (space 1) (debug 1))) - (labels ((c.frob (x) - (random x)) - (ad.frob (ad) - (mapcar #'c.frob ad))) - (declare (inline c.frob ad.frob)) - (list (the list ad0) - (funcall (if (listp ad0) #'ad.frob #'print) ad0) - (funcall (if (listp ad0) #'ad.frob #'print) (reverse ad0))))) - -DEFUNCT CATEGORIES OF BUGS - IR1-#: - These labels were used for bugs related to the old IR1 interpreter. - The # values reached 6 before the category was closed down. + (defun foo (x y) + (declare (integer x y)) + (+ (block nil + (flet ((xyz (u) + (declare (integer u)) + (if (> (1+ (the unsigned-byte u)) 0) + (+ 1 u) + (return (+ 38 (cos (/ u 78))))))) + (declare (inline xyz)) + (return-from foo + (* (funcall (eval #'xyz) x) + (if (> x 30) + (funcall (if (> x 5) #'xyz #'identity) + (+ x 13)) + 38))))) + (sin (* x y)))) + + Urgh... It's time to write IR1-copier. + +266: + David Lichteblau provided (sbcl-devel 2003-06-01) a patch to fix + behaviour of streams with element-type (SIGNED-BYTE 8). The patch + looks reasonable, if not obviously correct; however, it caused the + PPC/Linux port to segfault during warm-init while loading + src/pcl/std-class.fasl. A workaround patch was made, but it would + be nice to understand why the first patch caused problems, and to + fix the cause if possible. + +268: "wrong free declaration scope" + The following code must signal type error: + + (locally (declare (optimize (safety 3))) + (flet ((foo (x &optional (y (car x))) + (declare (optimize (safety 0))) + (list x y))) + (funcall (eval #'foo) 1))) + +269: + SCALE-FLOAT should accept any integer for its second argument. + +270: + In the following function constraint propagator optimizes nothing: + + (defun foo (x) + (declare (integer x)) + (declare (optimize speed)) + (typecase x + (fixnum "hala") + (fixnum "buba") + (bignum "hip") + (t "zuz"))) + +273: + Compilation of the following two forms causes "X is unbound" error: + + (symbol-macrolet ((x pi)) + (macrolet ((foo (y) (+ x y))) + (declaim (inline bar)) + (defun bar (z) + (* z (foo 4))))) + (defun quux (z) + (bar z)) + + (See (COERCE (CDR X) 'FUNCTION) in IR1-CONVERT-INLINE-LAMBDA.) + +274: + CLHS says that type declaration of a symbol macro should not affect + its expansion, but in SBCL it does. (If you like magic and want to + fix it, don't forget to change all uses of MACROEXPAND to + MACROEXPAND*.) + +275: + The following code (taken from CLOCC) takes a lot of time to compile: + + (defun foo (n) + (declare (type (integer 0 #.large-constant) n)) + (expt 1/10 n)) + + (fixed in 0.8.2.51, but a test case would be good) + +276: + (defmethod fee ((x fixnum)) + (setq x (/ x 2)) + x) + (fee 1) => type error + + (taken from CLOCC) + +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) + &OPTIONAL), not a (INTEGER 1 536870911) + is emitted when compiling this file: + (declaim (ftype (function ((integer 0 #.most-positive-fixnum)) + (integer #.most-negative-fixnum 0)) + foo)) + (defun foo (x) + (- x)) + (defun bar (x) + (let* (;; Uncomment this for a type mismatch warning indicating + ;; that the type of (FOO X) is correctly understood. + #+nil (fs-foo (float-sign (foo x))) + ;; Uncomment this for a type mismatch warning + ;; indicating that the type of (ABS (FOO X)) is + ;; correctly understood. + #+nil (fs-abs-foo (float-sign (abs (foo x)))) + ;; something wrong with this one though + (abs-foo (abs (foo x)))) + (declare (type (integer 1 100) abs-foo)) + (print abs-foo))) + + (see also bug 117) + +280: bogus WARNING about duplicate function definition + In sbcl-0.8.3 and sbcl-0.8.1.47, if BS.MIN is defined inline, + e.g. by + (declaim (inline bs.min)) + (defun bs.min (bases) nil) + before compiling the file below, the compiler warns + Duplicate definition for BS.MIN found in one static + unit (usually a file). + when compiling + (declaim (special *minus* *plus* *stagnant*)) + (defun b.*.min (&optional (x () xp) (y () yp) &rest rest) + (bs.min avec)) + (define-compiler-macro b.*.min (&rest rest) + `(bs.min ,@rest)) + (defun afish-d-rbd (pd) + (if *stagnant* + (b.*.min (foo-d-rbd *stagnant*)) + (multiple-value-bind (reduce-fn initial-value) + (etypecase pd + (list (values #'bs.min 0)) + (vector (values #'bs.min *plus*))) + (let ((cv-ks (cv (kpd.ks pd)))) + (funcall reduce-fn d-rbds))))) + (defun bfish-d-rbd (pd) + (if *stagnant* + (b.*.min (foo-d-rbd *stagnant*)) + (multiple-value-bind (reduce-fn initial-value) + (etypecase pd + (list (values #'bs.min *minus*)) + (vector (values #'bs.min 0))) + (let ((cv-ks (cv (kpd.ks pd)))) + (funcall reduce-fn d-rbds))))) + +281: COMPUTE-EFFECTIVE-METHOD error signalling. + (slightly obscured by a non-0 default value for + SB-PCL::*MAX-EMF-PRECOMPUTE-METHODS*) + It would be natural for COMPUTE-EFFECTIVE-METHOD to signal errors + when it finds a method with invalid qualifiers. However, it + shouldn't signal errors when any such methods are not applicable to + the particular call being evaluated, and certainly it shouldn't when + simply precomputing effective methods that may never be called. + (setf sb-pcl::*max-emf-precompute-methods* 0) + (defgeneric foo (x) + (:method-combination +) + (:method ((x symbol)) 1) + (:method + ((x number)) x)) + (foo 1) -> ERROR, but should simply return 1 + + The issue seems to be that construction of a discriminating function + calls COMPUTE-EFFECTIVE-METHOD with methods that are not all applicable. + +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 + 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 + parts of the system. See doc/internals/notes/threading-specials + +286: "recursive known functions" + Self-call recognition conflicts with known function + recognition. Currently cross compiler and target COMPILE do not + recognize recursion, and in target compiler it can be disabled. We + can always disable it for known functions with RECURSIVE attribute, + but there remains a possibility of a function with a + (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 + theoretically shaky. (The characters are OK as long as the characters + are in the ANSI-guaranteed character set, though, so they aren't a + real problem as long as the sources don't need anything but that; + the floats are a real problem.) + +289: "type checking and source-transforms" + a. + (block nil (let () (funcall #'+ (eval 'nil) (eval '1) (return :good)))) + signals type error. + + Our policy is to check argument types at the moment of a call. It + disagrees with ANSI, which says that type assertions are put + immediately onto argument expressions, but is easier to implement in + IR1 and is more compatible to type inference, inline expansion, + etc. IR1-transforms automatically keep this policy, but source + transforms for associative functions (such as +), being applied + during IR1-convertion, do not. It may be tolerable for direct calls + (+ x y z), but for (FUNCALL #'+ x y z) it is non-conformant. + + b. Another aspect of this problem is efficiency. [x y + z +] + requires less registers than [x y z + +]. This transformation is + currently performed with source transforms, but it would be good to + also perform it in IR1 optimization phase. + +290: Alpha floating point and denormalized traps + In SBCL 0.8.3.6x on the alpha, we work around what appears to be a + hardware or kernel deficiency: the status of the enable/disable + denormalized-float traps bit seems to be ambiguous; by the time we + get to os_restore_fp_control after a trap, denormalized traps seem + to be enabled. Since we don't want a trap every time someone uses a + denormalized float, in general, we mask out that bit when we restore + 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 + (loop for d of-type double-float from 0d0 to 10d0 by x collect d) + compiles to a type restriction on X of (AND DOUBLE-FLOAT (REAL + (0))). However, an integral value of X should be legal, because + successive adds of integers to double-floats produces double-floats, + so none of the type restrictions in the code is violated. + +298: (aka PFD MISC.183) + Compiler fails on + + (defun foo () + (multiple-value-call #'bar + (ext) + (catch 'tag (return-from foo (int))))) + + This program violates "unknown values LVAR stack discipline": if INT + returns, values returned by (EXT) must be removed from under that of + (INT). + +299: (aka PFD MISC.186) + * (defun foo () + (declare (optimize (debug 1))) + (multiple-value-call #'list + (if (eval t) (eval '(values :a :b :c)) nil) ; (*) + (catch 'foo (throw 'foo (values :x :y))))) + FOO + * (foo) + (:X :Y) + + Operator THROW is represented with a call of a not returning funny + function %THROW, unknown values stack after the call is empty, so + the unknown values LVAR (*) is considered to be dead after the call + and, thus, before it and is popped by the stack analysis.