X-Git-Url: http://repo.macrolet.net/gitweb/?a=blobdiff_plain;f=BUGS;h=55bb75401e83e04c09f9de8cdd045e92fc3e4b9b;hb=17532463fa19f2fc2aba53b65c32e200a27ccd6a;hp=788da3e6cdf1a77920485fbb01128d60ad52b6c7;hpb=227096b878fee7afae9d3bc2cee5df01449bca2d;p=sbcl.git diff --git a/BUGS b/BUGS index 788da3e..55bb754 100644 --- a/BUGS +++ b/BUGS @@ -84,46 +84,13 @@ WORKAROUND: d: (fixed in 0.8.1.5) -7: - The "compiling top-level form:" output ought to be condensed. - Perhaps any number of such consecutive lines ought to turn into a - single "compiling top-level forms:" line. - -11: - It would be nice if the - caught ERROR: - (during macroexpansion) - said what macroexpansion was at fault, e.g. - caught ERROR: - (during macroexpansion of IN-PACKAGE, - during macroexpansion of DEFFOO) - -19: - (I *think* this is a bug. It certainly seems like strange behavior. But - the ANSI spec is scary, dark, and deep.. -- WHN) - (FORMAT NIL "~,1G" 1.4) => "1. " - (FORMAT NIL "~3,1G" 1.4) => "1. " - -27: - Sometimes (SB-EXT:QUIT) fails with - Argh! maximum interrupt nesting depth (4096) exceeded, exiting - Process inferior-lisp exited abnormally with code 1 - I haven't noticed a repeatable case of this yet. - -32: - The printer doesn't report closures very well. This is true in - CMU CL 18b as well: - (PRINT #'CLASS-NAME) - gives - # - It would be nice to make closures have a settable name slot, - and make things like DEFSTRUCT and FLET, which create closures, - set helpful values into this slot. - 33: And as long as we're wishing, it would be awfully nice if INSPECT could also report on closures, telling about the values of the bound variables. + Currently INSPECT and DESCRIBE do show the values, but showing the + names of the bindings would be even nicer. + 35: The compiler assumes that any time a function of declared FTYPE doesn't signal an error, its arguments were of the declared type. @@ -165,38 +132,6 @@ WORKAROUND: so they could be supported after all. Very likely SIGCONTEXT-FLOATING-POINT-MODES could now be supported, too. -45: - a slew of floating-point-related errors reported by Peter Van Eynde - on July 25, 2000: - c: Many expressions generate floating infinity on x86/Linux: - (/ 1 0.0) - (/ 1 0.0d0) - (EXPT 10.0 1000) - (EXPT 10.0d0 1000) - PVE's regression tests want them to raise errors. sbcl-0.7.0.5 - on x86/Linux generates the infinities instead. That might or - might not be conforming behavior, but it's also inconsistent, - which is almost certainly wrong. (Inconsistency: (/ 1 0.0) - should give the same result as (/ 1.0 0.0), but instead (/ 1 0.0) - generates SINGLE-FLOAT-POSITIVE-INFINITY and (/ 1.0 0.0) - signals an error. - d: (in section12.erg) various forms a la - (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 - string-input streams, e.g. (MAKE-STRING-INPUT-STREAM "abc"). - [ Bug was reported as "from character streams", but in 0.8.3.10 we - get correct behaviour from (WITH-OPEN-FILE (i "/dev/zero") (READ-BYTE i)) ] - - -60: - The debugger LIST-LOCATIONS command doesn't work properly. - (How should it work properly?) - 61: Compiling and loading (DEFUN FAIL (X) (THROW 'FAIL-TAG X)) @@ -204,6 +139,12 @@ WORKAROUND: then requesting a BACKTRACE at the debugger prompt gives no information about where in the user program the problem occurred. + (this is apparently mostly fixed on the SPARC, PPC, and x86 architectures: + while giving the backtrace the non-x86 systems complains about "unknown + source location: using block start", but apart from that the + backtrace seems reasonable. On x86 this is masked by bug 353. See + tests/debug.impure.lisp for a test case) + 64: Using the pretty-printer from the command prompt gives funny results, apparently because the pretty-printer doesn't know @@ -227,19 +168,8 @@ WORKAROUND: e-mail on cmucl-help@cons.org on 2001-01-16 and 2001-01-17 from WHN and Pierre Mai.) -79: - as pointed out by Dan Barlow on sbcl-devel 2000-07-02: - The PICK-TEMPORARY-FILE-NAME utility used by LOAD-FOREIGN uses - an easily guessable temporary filename in a way which might open - applications using LOAD-FOREIGN to hijacking by malicious users - on the same machine. Incantations for doing this safely are - floating around the net in various "how to write secure programs - despite Unix" documents, and it would be good to (1) fix this in - LOAD-FOREIGN, and (2) hunt for any other code which uses temporary - files and make it share the same new safe logic. - - (partially alleviated in sbcl-0.7.9.32 by a fix by Matthew Danish to - make the temporary filename less easily guessable) + (Actually this has changed changed since, and types as above are + now supported. This may be a bug.) 83: RANDOM-INTEGER-EXTRA-BITS=10 may not be large enough for the RANDOM @@ -265,14 +195,6 @@ WORKAROUND: holding... * is not equivalent to T in many cases, such as (VECTOR *) /= (VECTOR T). -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. - 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 @@ -333,6 +255,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. @@ -363,28 +294,6 @@ WORKAROUND: (see also bug 279) -118: - as reported by Eric Marsden on cmucl-imp@cons.org 2001-08-14: - (= (FLOAT 1 DOUBLE-FLOAT-EPSILON) - (+ (FLOAT 1 DOUBLE-FLOAT-EPSILON) DOUBLE-FLOAT-EPSILON)) => T - when of course it should be NIL. (He says it only fails for X86, - not SPARC; dunno about Alpha.) - - Also, "the same problem exists for LONG-FLOAT-EPSILON, - DOUBLE-FLOAT-NEGATIVE-EPSILON, LONG-FLOAT-NEGATIVE-EPSILON (though - for the -negative- the + is replaced by a - in the test)." - - 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 @@ -431,24 +340,6 @@ WORKAROUND: a STYLE-WARNING for references to variables similar to locals might be a good thing.) -125: - (as reported by Gabe Garza on cmucl-help 2001-09-21) - (defvar *tmp* 3) - (defun test-pred (x y) - (eq x y)) - (defun test-case () - (let* ((x *tmp*) - (func (lambda () x))) - (print (eq func func)) - (print (test-pred func func)) - (delete func (list func)))) - Now calling (TEST-CASE) gives output - NIL - NIL - (#) - Evidently Python thinks of the lambda as a code transformation so - much that it forgets that it's also an object. - 135: Ideally, uninterning a symbol would allow it, and its associated FDEFINITION and PROCLAIM data, to be reclaimed by the GC. However, @@ -459,17 +350,6 @@ WORKAROUND: forever, even when it is uninterned and all other references to it are lost. -141: "pretty printing and backquote" - a. - * '``(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) - 143: (reported by Jesse Bouwman 2001-10-24 through the unfortunately prominent SourceForge web/db bug tracking system, which is @@ -501,6 +381,10 @@ WORKAROUND: conformance problem, since seems hard to construct useful code where it matters.) + [ partially fixed by CSR in 0.8.17.17 because of a PFD ansi-tests + report that (COMPLEX RATIO) was failing; still failing on types of + the form (AND NUMBER (SATISFIES REALP) (SATISFIES ZEROP)). ] + b. (fixed in 0.8.3.43) 146: @@ -537,20 +421,6 @@ WORKAROUND: This is probably the same bug as 216 -167: - In sbcl-0.7.3.11, compiling the (illegal) code - (in-package :cl-user) - (defmethod prove ((uustk uustk)) - (zap ((frob () nil)) - (frob))) - gives the (not terribly clear) error message - ; caught ERROR: - ; (during macroexpansion of (DEFMETHOD PROVE ...)) - ; can't get template for (FROB NIL NIL) - The problem seems to be that the code walker used by the DEFMETHOD - macro is unhappy with the illegal syntax in the method body, and - is giving an unclear error message. - 173: The compiler sometimes tries to constant-fold expressions before it checks to see whether they can be reached. This can lead to @@ -621,12 +491,6 @@ WORKAROUND: The careful type of X is {2k} :-(. Is it really important to be able to work with unions of many intervals? -190: "PPC/Linux pipe? buffer? bug" - In sbcl-0.7.6, the run-program.test.sh test script sometimes hangs - on the PPC/Linux platform, waiting for a zombie env process. This - is a classic symptom of buffer filling and deadlock, but it seems - only sporadically reproducible. - 191: "Miscellaneous PCL deficiencies" (reported by Alexey Dejneka sbcl-devel 2002-08-04) a. DEFCLASS does not inform the compiler about generated @@ -646,8 +510,14 @@ 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. + + [much later, in 2006-08] in fact it's no longer erroneous to use + WITH-SLOTS on structure-classes. However, including :METACLASS + STRUCTURE-CLASS in the class definition gives a whole bunch of + function redefinition warnings, so we're still not good to close + this bug... + + c. (fixed in 0.8.4.23) 201: "Incautious type inference from compound types" a. (reported by APD sbcl-devel 2002-09-17) @@ -709,18 +579,6 @@ WORKAROUND: 211: "keywords processing" a. :ALLOW-OTHER-KEYS T should allow a function to receive an odd number of keyword arguments. - e. Compiling - - (flet ((foo (&key y) (list y))) - (list (foo :y 1 :y 2))) - - issues confusing message - - ; in: LAMBDA NIL - ; (FOO :Y 1 :Y 2) - ; - ; caught STYLE-WARNING: - ; The variable #:G15 is defined but never used. 212: "Sequence functions and circular arguments" COERCE, MERGE and CONCATENATE go into an infinite loop when given @@ -734,11 +592,6 @@ 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) 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 @@ -753,20 +606,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 @@ -793,40 +632,6 @@ WORKAROUND: This is probably the same bug as 162 -217: "Bad type operations with FUNCTION types" - In sbcl.0.7.7: - - * (values-type-union (specifier-type '(function (base-char))) - (specifier-type '(function (integer)))) - - # - - It causes insertion of wrong type assertions into generated - code. E.g. - - (defun foo (x s) - (let ((f (etypecase x - (character #'write-char) - (integer #'write-byte)))) - (funcall f x s) - (etypecase x - (character (write-char x s)) - (integer (write-byte x s))))) - - 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.) - -233: bugs in constraint propagation - 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 - 235: "type system and inline expansion" a. (declaim (ftype (function (cons) number) acc)) @@ -842,6 +647,10 @@ WORKAROUND: (foo '(nil) '(t)) => NIL, T. + As of 0.9.15.41 this seems to be due to ACC being inlined only once + inside FOO, which results in the second call reusing the FUNCTIONAL + resulting from the first -- which doesn't check the type. + 237: "Environment arguments to type functions" a. Functions SUBTYPEP, TYPEP, UPGRADED-ARRAY-ELEMENT-TYPE, and UPGRADED-COMPLEX-PART-TYPE now have an optional environment @@ -878,18 +687,6 @@ WORKAROUND: ; compilation unit finished ; printed 1 note -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). - 242: "WRITE-SEQUENCE suboptimality" (observed from clx performance) In sbcl-0.7.13, WRITE-SEQUENCE of a sequence of type @@ -897,6 +694,11 @@ WORKAROUND: (UNSIGNED-BYTE 8) will write to the stream one byte at a time, rather than writing the sequence in one go, leading to severe performance degradation. + As of sbcl-0.9.0.36, this is solved for fd-streams, so is less of a + problem in practice. (Fully fixing this would require adding a + ansi-stream-n-bout slot and associated methods to write a byte + sequence to ansi-stream, similar to the existing ansi-stream-sout + slot/functions.) 243: "STYLE-WARNING overenthusiasm for unused variables" (observed from clx compilation) @@ -912,13 +714,8 @@ WORKAROUND: ; The variable Y is defined but never used. 245: bugs in disassembler - 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)) @@ -932,11 +729,7 @@ WORKAROUND: a. (lambda () (svref (make-array 8 :adjustable t) 1)) - b. (lambda (x) - (list (let ((y (the real x))) - (unless (floatp y) (error "")) - y) - (integer-length x))) + b. (fixed at some point before 1.0.4.10) c. (lambda (x) (declare (optimize (debug 0))) @@ -981,38 +774,13 @@ WORKAROUND: b. The same for CSUBTYPEP. -261: - * (let () (list (the (values &optional fixnum) (eval '(values))))) - debugger invoked on condition of type TYPE-ERROR: - The value NIL is not of type FIXNUM. - 262: "yet another bug in inline expansion of local functions" - Compiler fails on - - (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. - -265: - SB-EXT:RUN-PROGRAM is currently non-functional on Linux/PPC; - attempting to use it leads to segmentation violations. This is - probably because of a bogus implementation of - os_restore_fp_control(). + During inline expansion of a local function Python can try to + reference optimized away objects (functions, variables, CTRANs from + tags and blocks), which later may lead to problems. Some of the + cases are worked around by forbidding expansion in such cases, but + the better way would be to reimplement inline expansion by copying + IR1 structures. 266: David Lichteblau provided (sbcl-devel 2003-06-01) a patch to fix @@ -1032,9 +800,6 @@ WORKAROUND: (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: @@ -1076,23 +841,12 @@ WORKAROUND: (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) + b. The same as in a., but using MULTIPLE-VALUE-SETQ instead of SETQ. + c. (defvar *faa*) + (defmethod faa ((*faa* double-float)) + (set '*faa* (when (< *faa* 0) (- *faa*))) + (1+ *faa*)) + (faa 1d0) => type error 279: type propagation error -- correctly inferred type goes astray? In sbcl-0.8.3 and sbcl-0.8.1.47, the warning @@ -1119,75 +873,12 @@ WORKAROUND: (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. - -282: "type checking in full calls" - In current (0.8.3.6) implementation a CAST in a full call argument - is not checked; but the continuation between the CAST and the - combination has the "checked" type and CAST performs unsafe - coercion; this may lead to errors: if FOO is declared to take a - FIXNUM, this code will produce garbage on a machine with 30-bit - fixnums: - - (foo (aref (the (array (unsigned-byte 32)) x))) - 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 + strongly suspected problems, as of 1.0.3.13: 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 @@ -1202,30 +893,13 @@ WORKAROUND: (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) - 288a: 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.) - 288b: The compiler still makes assumptions about cross-compilation-host - implementation of ANSI CL: - 288b1: Simple bit vectors are distinct from simple vectors (in - DEFINE-STORAGE-BASE and elsewhere). (Actually, I'm not *sure* - that things would really break if this weren't so, but I - strongly suspect that they would.) - 288b2: SINGLE-FLOAT is distinct from DOUBLE-FLOAT. (This is - in a sense just one aspect of bug 288a.) + 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. @@ -1256,5 +930,865 @@ WORKAROUND: the control word; however, this clobbers any change the user might have made. -292: - (fixed in 0.8.3.74) +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. + +300: (reported by Peter Graves) Function PEEK-CHAR checks PEEK-TYPE + argument type only after having read a character. This is caused + with EXPLICIT-CHECK attribute in DEFKNOWN. The similar problem + exists with =, /=, <, >, <=, >=. They were fixed, but it is probably + less error prone to have EXPLICIT-CHECK be a local declaration, + being put into the definition, instead of an attribute being kept in + a separate file; maybe also put it into SB-EXT? + +301: ARRAY-SIMPLE-=-TYPE-METHOD breaks on corner cases which can arise + in NOTE-ASSUMED-TYPES + In sbcl-0.8.7.32, compiling the file + (defun foo (x y) + (declare (type integer x)) + (declare (type (vector (or hash-table bit)) y)) + (bletch 2 y)) + (defun bar (x y) + (declare (type integer x)) + (declare (type (simple-array base (2)) y)) + (bletch 1 y)) + gives the error + failed AVER: "(NOT (AND (NOT EQUALP) CERTAINP))" + +303: "nonlinear LVARs" (aka MISC.293) + (defun buu (x) + (multiple-value-call #'list + (block foo + (multiple-value-prog1 + (eval '(values :a :b :c)) + (catch 'bar + (if (> x 0) + (return-from foo + (eval `(if (> ,x 1) + 1 + (throw 'bar (values 3 4))))))))))) + + (BUU 1) returns garbage. + + The problem is that both EVALs sequentially write to the same LVAR. + +306: "Imprecise unions of array types" + + a. fixed in SBCL 0.9.15.48 + + b.(subtypep + 'array + `(or + ,@(loop for x across sb-vm:*specialized-array-element-type-properties* + collect `(array ,(sb-vm:saetp-specifier x))))) + => NIL, T (when it should be T, T) + +309: "Dubious values for implementation limits" + (reported by Bruno Haible sbcl-devel "Incorrect value of + multiple-values-limit" 2004-04-19) + (values-list (make-list 1000000)), on x86/linux, signals a stack + exhaustion condition, despite MULTIPLE-VALUES-LIMIT being + significantly larger than 1000000. There are probably similar + dubious values for CALL-ARGUMENTS-LIMIT (see cmucl-help/cmucl-imp + around the same time regarding a call to LIST on sparc with 1000 + arguments) and other implementation limit constants. + +314: "LOOP :INITIALLY clauses and scope of initializers" + reported by Bruno Haible sbcl-devel "various SBCL bugs" from CLISP + test suite, originally by Thomas F. Burdick. + ;; + ;; According to the HyperSpec 6.1.2.1.4, in for-as-equals-then, var is + ;; initialized to the result of evaluating form1. 6.1.7.2 says that + ;; initially clauses are evaluated in the loop prologue, which precedes all + ;; loop code except for the initial settings provided by with, for, or as. + (loop :for x = 0 :then (1+ x) + :for y = (1+ x) :then (ash y 1) + :for z :across #(1 3 9 27 81 243) + :for w = (+ x y z) + :initially (assert (zerop x)) :initially (assert (= 2 w)) + :until (>= w 100) :collect w) + Expected: (2 6 15 38) + Got: ERROR + +318: "stack overflow in compiler warning with redefined class" + reported by Bruno Haible sbcl-devel "various SBCL bugs" from CLISP + test suite. + (defstruct foo a) + (setf (find-class 'foo) nil) + (defstruct foo slot-1) + This used to give a stack overflow from within the printer, which has + been fixed as of 0.8.16.11. Current result: + ; caught ERROR: + ; can't compile TYPEP of anonymous or undefined class: + ; # + ... + debugger invoked on a TYPE-ERROR in thread 19973: + The value NIL is not of type FUNCTION. + + CSR notes: it's not really clear what it should give: is (SETF FIND-CLASS) + meant to be enough to delete structure classes from the system? + +319: "backquote with comma inside array" + reported by Bruno Haible sbcl-devel "various SBCL bugs" from CLISP + test suite. + (read-from-string "`#1A(1 2 ,(+ 2 2) 4)") + gives + #(1 2 ((SB-IMPL::|,|) + 2 2) 4) + which probably isn't intentional. + +324: "STREAMs and :ELEMENT-TYPE with large bytesize" + In theory, (open foo :element-type '(unsigned-byte )) should work + for all positive integral . At present, it only works for up + to about 1024 (and similarly for signed-byte), so + (open "/dev/zero" :element-type '(unsigned-byte 1025)) + gives an error in sbcl-0.8.10. + +325: "CLOSE :ABORT T on supeseding streams" + Closing a stream opened with :IF-EXISTS :SUPERSEDE with :ABORT T leaves no + file on disk, even if one existed before opening. + + The illegality of this is not crystal clear, as the ANSI dictionary + entry for CLOSE says that when :ABORT is T superseded files are not + superseded (ie. the original should be restored), whereas the OPEN + entry says about :IF-EXISTS :SUPERSEDE "If possible, the + implementation should not destroy the old file until the new stream + is closed." -- implying that even though undesirable, early deletion + is legal. Restoring the original would none the less be the polite + thing to do. + +326: "*PRINT-CIRCLE* crosstalk between streams" + In sbcl-0.8.10.48 it's possible for *PRINT-CIRCLE* references to be + mixed between streams when output operations are intermingled closely + enough (as by doing output on S2 from within (PRINT-OBJECT X S1) in the + test case below), so that e.g. the references #2# appears on a stream + with no preceding #2= on that stream to define it (because the #2= was + sent to another stream). + (cl:in-package :cl-user) + (defstruct foo index) + (defparameter *foo* (make-foo :index 4)) + (defstruct bar) + (defparameter *bar* (make-bar)) + (defparameter *tangle* (list *foo* *bar* *foo*)) + (defmethod print-object ((foo foo) stream) + (let ((index (foo-index foo))) + (format *trace-output* + "~&-$- emitting FOO ~D, ambient *BAR*=~S~%" + index *bar*) + (format stream "[FOO ~D]" index)) + foo) + (let ((tsos (make-string-output-stream)) + (ssos (make-string-output-stream))) + (let ((*print-circle* t) + (*trace-output* tsos) + (*standard-output* ssos)) + (prin1 *tangle* *standard-output*)) + (let ((string (get-output-stream-string ssos))) + (unless (string= string "(#1=[FOO 4] #S(BAR) #1#)") + ;; In sbcl-0.8.10.48 STRING was "(#1=[FOO 4] #2# #1#)".:-( + (error "oops: ~S" string))))) + It might be straightforward to fix this by turning the + *CIRCULARITY-HASH-TABLE* and *CIRCULARITY-COUNTER* variables into + per-stream slots, but (1) it would probably be sort of messy faking + up the special variable binding semantics using UNWIND-PROTECT and + (2) it might be sort of a pain to test that no other bugs had been + introduced. + +328: "Profiling generic functions", transplanted from #241 + (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." + + Problem: when a generic function is profiled, it appears as an ordinary + function to PCL. (Remembering the uninterned accessor is OK, as the + redefinition must be able to remove old accessors from their generic + functions.) + +329: "Sequential class redefinition" + reported by Bruno Haible: + (defclass reactor () ((max-temp :initform 10000000))) + (defvar *r1* (make-instance 'reactor)) + (defvar *r2* (make-instance 'reactor)) + (slot-value *r1* 'max-temp) + (slot-value *r2* 'max-temp) + (defclass reactor () ((uptime :initform 0))) + (slot-value *r1* 'uptime) + (defclass reactor () ((uptime :initform 0) (max-temp :initform 10000))) + (slot-value *r1* 'max-temp) ; => 10000 + (slot-value *r2* 'max-temp) ; => 10000000 oops... + + Possible solution: + The method effective when the wrapper is obsoleted can be saved + in the wrapper, and then to update the instance just run through + all the old wrappers in order from oldest to newest. + +332: "fasl stack inconsistency in structure redefinition" + (reported by Tim Daly Jr sbcl-devel 2004-05-06) + Even though structure redefinition is undefined by the standard, the + following behaviour is suboptimal: running + (defun stimulate-sbcl () + (let ((filename (format nil "/tmp/~A.lisp" (gensym)))) + ;;create a file which redefines a structure incompatibly + (with-open-file (f filename :direction :output :if-exists :supersede) + (print '(defstruct astruct foo) f) + (print '(defstruct astruct foo bar) f)) + ;;compile and load the file, then invoke the continue restart on + ;;the structure redefinition error + (handler-bind ((error (lambda (c) (continue c)))) + (load (compile-file filename))))) + (stimulate-sbcl) + and choosing the CONTINUE restart yields the message + debugger invoked on a SB-INT:BUG in thread 27726: + fasl stack not empty when it should be + +336: "slot-definitions must retain the generic functions of accessors" + reported by Tony Martinez: + (defclass foo () ((bar :reader foo-bar))) + (defun foo-bar (x) x) + (defclass foo () ((bar :reader get-bar))) ; => error, should work + + Note: just punting the accessor removal if the fdefinition + is not a generic function is not enough: + + (defclass foo () ((bar :reader foo-bar))) + (defvar *reader* #'foo-bar) + (defun foo-bar (x) x) + (defclass foo () ((bar :initform 'ok :reader get-bar))) + (funcall *reader* (make-instance 'foo)) ; should be an error, since + ; the method must be removed + ; by the class redefinition + + Fixing this should also fix a subset of #328 -- update the + description with a new test-case then. + +339: "DEFINE-METHOD-COMBINATION bugs" + (reported by Bruno Haible via the clisp test suite) + + a. Syntax checking laxity (should produce errors): + i. (define-method-combination foo :documentation :operator) + ii. (define-method-combination foo :documentation nil) + iii. (define-method-combination foo nil) + iv. (define-method-combination foo nil nil + (:arguments order &aux &key)) + v. (define-method-combination foo nil nil (:arguments &whole)) + vi. (define-method-combination foo nil nil (:generic-function)) + vii. (define-method-combination foo nil nil (:generic-function bar baz)) + viii. (define-method-combination foo nil nil (:generic-function (bar))) + ix. (define-method-combination foo nil ((3))) + x. (define-method-combination foo nil ((a))) + + b. define-method-combination arguments lambda list badness + i. &aux args are currently unsupported; + ii. default values of &optional and &key arguments are ignored; + iii. supplied-p variables for &optional and &key arguments are not + bound. + + c. (fixed in sbcl-0.9.15.15) + +344: more (?) ROOM T problems (possibly part of bug 108) + In sbcl-0.8.12.51, and off and on leading up to it, the + SB!VM:MEMORY-USAGE operations in ROOM T caused + unhandled condition (of type SB-INT:BUG): + failed AVER: "(SAP= CURRENT END)" + Several clever people have taken a shot at this without fixing + it; this time around (before sbcl-0.8.13 release) I (WHN) just + commented out the SB!VM:MEMORY-USAGE calls until someone figures + out how to make them work reliably with the rest of the GC. + + (Note: there's at least one dubious thing in room.lisp: see the + comment in VALID-OBJ) + +346: alpha backtrace + In sbcl-0.8.13, all backtraces from errors caused by internal errors + on the alpha seem to have a "bogus stack frame". + +349: PPRINT-INDENT rounding implementation decisions + At present, pprint-indent (and indeed the whole pretty printer) + more-or-less assumes that it's using a monospace font. That's + probably not too silly an assumption, but one piece of information + the current implementation loses is from requests to indent by a + non-integral amount. As of sbcl-0.8.15.9, the system silently + truncates the indentation to an integer at the point of request, but + maybe the non-integral value should be propagated through the + pprinter and only truncated at output? (So that indenting by 1/2 + then 3/2 would indent by two spaces, not one?) + +352: forward-referenced-class trouble + reported by Bruno Haible on sbcl-devel + (defclass c (a) ()) + (setf (class-name (find-class 'a)) 'b) + (defclass a () (x)) + (defclass b () (y)) + (make-instance 'c) + Expected: an instance of c, with a slot named x + Got: debugger invoked on a SIMPLE-ERROR in thread 78906: + While computing the class precedence list of the class named C. + The class named B is a forward referenced class. + The class named B is a direct superclass of the class named C. + + [ Is this actually a bug? DEFCLASS only replaces an existing class + when the class name is the proper name of that class, and in the + above code the class found by (FIND-CLASS 'A) does not have a + proper name. CSR, 2006-08-07 ] + +353: debugger suboptimalities on x86 + On x86 backtraces for undefined functions start with a bogus stack + frame, and backtraces for throws to unknown catch tags with a "no + debug information" frame. These are both due to CODE-COMPONENT-FROM-BITS + (used on non-x86 platforms) being a more complete solution then what + is done on x86. + + On x86/linux large portions of tests/debug.impure.lisp have been commented + out as failures. The probable culprit for these problems is in x86-call-context + (things work fine on x86/freebsd). + + More generally, the debugger internals suffer from excessive x86/non-x86 + conditionalization and OAOOMization: refactoring the common parts would + be good. + +354: XEPs in backtraces + Under default compilation policy + (defun test () + (throw :unknown t)) + (test) + Has the XEP for TEST in the backtrace, not the TEST frame itself. + (sparc and x86 at least) + + Since SBCL 0.8.20.1 this is hidden unless *SHOW-ENTRY-POINT-DETAILS* + is true (instead there appear two TEST frames at least on ppc). The + underlying cause seems to be that SB-C::TAIL-ANNOTATE will not merge + the tail-call for the XEP, since Python has by that time proved that + the function can never return; same happens if the function holds an + unconditional call to ERROR. + +356: PCL corruption + (reported by Bruno Haible) + After the "layout depth conflict" error, the CLOS is left in a state where + it's not possible to define new standard-class subclasses any more. + Test case: + (defclass prioritized-dispatcher () + ((dependents :type list :initform nil))) + (defmethod sb-pcl:validate-superclass ((c1 sb-pcl:funcallable-standard-class) + (c2 (eql (find-class 'prioritized-dispatcher)))) + t) + (defclass prioritized-generic-function (prioritized-dispatcher standard-generic-function) + () + (:metaclass sb-pcl:funcallable-standard-class)) + ;; ERROR, Quit the debugger with ABORT + (defclass typechecking-reader-class (standard-class) + ()) + Expected: # + Got: ERROR "The assertion SB-PCL::WRAPPERS failed." + + [ This test case does not cause the error any more. However, + similar problems can be observed with + + (defclass foo (standard-class) () + (:metaclass sb-mop:funcallable-standard-class)) + (sb-mop:finalize-inheritance (find-class 'foo)) + ;; ERROR, ABORT + (defclass bar (standard-class) ()) + (make-instance 'bar) + ] + +357: defstruct inheritance of initforms + (reported by Bruno Haible) + When defstruct and defclass (with :metaclass structure-class) are mixed, + 1. some slot initforms are ignored by the DEFSTRUCT generated constructor + function, and + 2. all slot initforms are ignored by MAKE-INSTANCE. (This can be arguably + OK for initforms that were given in a DEFSTRUCT form, but for those + given in a DEFCLASS form, I think it qualifies as a bug.) + Test case: + (defstruct structure02a + slot1 + (slot2 t) + (slot3 (floor pi))) + (defclass structure02b (structure02a) + ((slot4 :initform -44) + (slot5) + (slot6 :initform t) + (slot7 :initform (floor (* pi pi))) + (slot8 :initform 88)) + (:metaclass structure-class)) + (defstruct (structure02c (:include structure02b (slot8 -88))) + slot9 + (slot10 t) + (slot11 (floor (exp 3)))) + ;; 1. Form: + (let ((a (make-structure02c))) + (list (structure02c-slot4 a) + (structure02c-slot5 a) + (structure02c-slot6 a) + (structure02c-slot7 a))) + Expected: (-44 nil t 9) + Got: (SB-PCL::..SLOT-UNBOUND.. SB-PCL::..SLOT-UNBOUND.. + SB-PCL::..SLOT-UNBOUND.. SB-PCL::..SLOT-UNBOUND..) + ;; 2. Form: + (let ((b (make-instance 'structure02c))) + (list (structure02c-slot2 b) + (structure02c-slot3 b) + (structure02c-slot4 b) + (structure02c-slot6 b) + (structure02c-slot7 b) + (structure02c-slot8 b) + (structure02c-slot10 b) + (structure02c-slot11 b))) + Expected: (t 3 -44 t 9 -88 t 20) + Got: (0 0 0 0 0 0 0 0) + +359: wrong default value for ensure-generic-function's :generic-function-class argument + (reported by Bruno Haible) + ANSI CL is silent on this, but the MOP's specification of ENSURE-GENERIC-FUNCTION says: + "The remaining arguments are the complete set of keyword arguments + received by ENSURE-GENERIC-FUNCTION." + and the spec of ENSURE-GENERIC-FUNCTION-USING-CLASS: + ":GENERIC-FUNCTION-CLASS - a class metaobject or a class name. If it is not + supplied, it defaults to the class named STANDARD-GENERIC-FUNCTION." + This is not the case in SBCL. Test case: + (defclass my-generic-function (standard-generic-function) + () + (:metaclass sb-pcl:funcallable-standard-class)) + (setf (fdefinition 'foo1) + (make-instance 'my-generic-function :name 'foo1)) + (ensure-generic-function 'foo1 + :generic-function-class (find-class 'standard-generic-function)) + (class-of #'foo1) + ; => # + (setf (fdefinition 'foo2) + (make-instance 'my-generic-function :name 'foo2)) + (ensure-generic-function 'foo2) + (class-of #'foo2) + Expected: # + Got: # + +362: missing error when a slot-definition is created without a name + (reported by Bruno Haible) + The MOP says about slot-definition initialization: + "The :NAME argument is a slot name. An ERROR is SIGNALled if this argument + is not a symbol which can be used as a variable name. An ERROR is SIGNALled + if this argument is not supplied." + Test case: + (make-instance (find-class 'sb-pcl:standard-direct-slot-definition)) + Expected: ERROR + Got: # + +363: missing error when a slot-definition is created with a wrong documentation object + (reported by Bruno Haible) + The MOP says about slot-definition initialization: + "The :DOCUMENTATION argument is a STRING or NIL. An ERROR is SIGNALled + if it is not. This argument default to NIL during initialization." + Test case: + (make-instance (find-class 'sb-pcl:standard-direct-slot-definition) + :name 'foo + :documentation 'not-a-string) + Expected: ERROR + Got: # + +369: unlike-an-intersection behavior of VALUES-TYPE-INTERSECTION + In sbcl-0.8.18.2, the identity $(x \cap y \cap y)=(x \cap y)$ + does not hold for VALUES-TYPE-INTERSECTION, even for types which + can be intersected exactly, so that ASSERTs fail in this test case: + (in-package :cl-user) + (let ((types (mapcar #'sb-c::values-specifier-type + '((values (vector package) &optional) + (values (vector package) &rest t) + (values (vector hash-table) &rest t) + (values (vector hash-table) &optional) + (values t &optional) + (values t &rest t) + (values nil &optional) + (values nil &rest t) + (values sequence &optional) + (values sequence &rest t) + (values list &optional) + (values list &rest t))))) + (dolist (x types) + (dolist (y types) + (let ((i (sb-c::values-type-intersection x y))) + (assert (sb-c::type= i (sb-c::values-type-intersection i x))) + (assert (sb-c::type= i (sb-c::values-type-intersection i y))))))) + +370: reader misbehaviour on large-exponent floats + (read-from-string "1.0s1000000000000000000000000000000000000000") + causes the reader to attempt to create a very large bignum (which it + will then attempt to coerce to a rational). While this isn't + completely wrong, it is probably not ideal -- checking the floating + point control word state and then returning the relevant float + (most-positive-short-float or short-float-infinity) or signalling an + error immediately would seem to make more sense. + +372: floating-point overflow not signalled on ppc/darwin + The following assertions in float.pure.lisp fail on ppc/darwin + (Mac OS X version 10.3.7): + (assert (raises-error? (scale-float 1.0 most-positive-fixnum) + floating-point-overflow)) + (assert (raises-error? (scale-float 1.0d0 (1+ most-positive-fixnum)) + floating-point-overflow))) + as the SCALE-FLOAT just returns + #.SB-EXT:SINGLE/DOUBLE-FLOAT-POSITIVE-INFINITY. These tests have been + disabled on Darwin for now. + +377: Memory fault error reporting + On those architectures where :C-STACK-IS-CONTROL-STACK is in + *FEATURES*, we handle SIG_MEMORY_FAULT (SEGV or BUS) on an altstack, + so we cannot handle the signal directly (as in interrupt_handle_now()) + in the case when the signal comes from some external agent (the user + using kill(1), or a fault in some foreign code, for instance). As + of sbcl-0.8.20.20, this is fixed by calling + arrange_return_to_lisp_function() to a new error-signalling + function, but as a result the error reporting is poor: we cannot + even tell the user at which address the fault occurred. We should + arrange such that arguments can be passed to the function called from + arrange_return_to_lisp_function(), but this looked hard to do in + general without suffering from memory leaks. + +379: TRACE :ENCAPSULATE NIL broken on ppc/darwin + See commented-out test-case in debug.impure.lisp. + +380: Accessor redefinition fails because of old accessor name + When redefining an accessor, SB-PCL::FIX-SLOT-ACCESSORS may try to + find the generic function named by the old accessor name using + ENSURE-GENERIC-FUNCTION and then remove the old accessor's method in + the GF. If the old name does not name a function, or if the old name + does not name a generic function, no attempt to find the GF or remove + any methods is made. + + However, if an unrelated GF with an incompatible lambda list exists, + the class redefinition will fail when SB-PCL::REMOVE-READER-METHOD + tries to find and remove a method with an incompatible lambda list + from the unrelated generic function. + +382: externalization unexpectedly changes array simplicity + COMPILE-FILE and LOAD + (defun foo () + (let ((x #.(make-array 4 :fill-pointer 0))) + (values (eval `(typep ',x 'simple-array)) + (typep x 'simple-array)))) + then (FOO) => T, NIL. + + Similar problems exist with SIMPLE-ARRAY-P, ARRAY-HEADER accessors + and all array dimension functions. + +383: ASH'ing non-constant zeros + Compiling + (lambda (b) + (declare (type (integer -2 14) b)) + (declare (ignorable b)) + (ash (imagpart b) 57)) + on PPC (and other platforms, presumably) gives an error during the + emission of FASH-ASH-LEFT/FIXNUM=>FIXNUM as the assembler attempts to + stuff a too-large constant into the immediate field of a PPC + instruction. Either the VOP should be fixed or the compiler should be + taught how to transform this case away, paying particular attention + to side-effects that might occur in the arguments to ASH. + +384: Compiler runaway on very large character types + + (compile nil '(lambda (x) + (declare (type (member #\a 1) x)) + (the (member 1 nil) x))) + + The types apparently normalize into a very large type, and the compiler + gets lost in REMOVE-DUPLICATES. Perhaps the latter should use + a better algorithm (one based on hash tables, say) on very long lists + when :TEST has its default value? + + A simpler example: + + (compile nil '(lambda (x) (the (not (eql #\a)) x))) + + (partially fixed in 0.9.3.1, but a better representation for these + types is needed.) + +385: + (format nil "~4,1F" 0.001) => "0.00" (should be " 0.0"); + (format nil "~4,1@F" 0.001) => "+.00" (should be "+0.0"). + +386: SunOS/x86 stack exhaustion handling broken + According to , the + stack exhaustion checking (implemented with a write-protected guard + page) does not work on SunOS/x86. + +388: + (found by Dmitry Bogomolov) + + (defclass foo () ((x :type (unsigned-byte 8)))) + (defclass bar () ((x :type symbol))) + (defclass baz (foo bar) ()) + + causes error + + SB-PCL::SPECIALIZER-APPLICABLE-USING-TYPE-P cannot handle the second argument + (UNSIGNED-BYTE 8). + + [ Can't trigger this any more, as of 2006-08-07 ] + +389: + (reported several times on sbcl-devel, by Rick Taube, Brian Rowe and + others) + + ROUND-NUMERIC-BOUND assumes that float types always have a FORMAT + specifying whether they're SINGLE or DOUBLE. This is true for types + computed by the type system itself, but the compiler type derivation + short-circuits this and constructs non-canonical types. A temporary + fix was made to ROUND-NUMERIC-BOUND for the sbcl-0.9.6 release, but + the right fix is to remove the abstraction violation in the + compiler's type deriver. + +393: Wrong error from methodless generic function + (DEFGENERIC FOO (X)) + (FOO 1 2) + gives NO-APPLICABLE-METHOD rather than an argument count error. + +395: Unicode and streams + One of the remaining problems in SBCL's Unicode support is the lack + of generality in certain streams. + a. FILL-POINTER-STREAMs: SBCL refuses to write (e.g. using FORMAT) + to streams made from strings that aren't character strings with + fill-pointers: + (let ((v (make-array 5 :fill-pointer 0 :element-type 'standard-char))) + (format v "foo") + v) + should return a non-simple base string containing "foo" but + instead errors. + + (reported on sbcl-help by "tichy") + +396: block-compilation bug + (let ((x 1)) + (dotimes (y 10) + (let ((y y)) + (when (funcall (eval #'(lambda (x) (eql x 2))) y) + (defun foo (z) + (incf x (incf y z)))))) + (defun bar (z) + (foo z) + (values x))) + (bar 1) => 11, should be 4. + +397: SLEEP accuracy + The more interrupts arrive the less accurate SLEEP's timing gets. + (time (sb-thread:terminate-thread + (prog1 (sb-thread:make-thread (lambda () + (loop + (princ #\!) + (force-output) + (sb-ext:gc)))) + (sleep 1)))) + +398: GC-unsafe SB-ALIEN string deporting + Translating a Lisp string to an alien string by taking a SAP to it + as done by the :DEPORT-GEN methods for C-STRING and UTF8-STRING + is not safe, since the Lisp string can move. For example the + following code will fail quickly on both cheneygc and pre-0.9.8.19 + GENCGC: + + (setf (bytes-consed-between-gcs) 4096) + (define-alien-routine "strcmp" int (s1 c-string) (s2 c-string)) + + (loop + (let ((string "hello, world")) + (assert (zerop (strcmp string string))))) + + (This will appear to work on post-0.9.8.19 GENCGC, since + the GC no longer zeroes memory immediately after releasing + it after a minor GC. Either enabling the READ_PROTECT_FREE_PAGES + #define in gencgc.c or modifying the example so that a major + GC will occasionally be triggered would unmask the bug.) + + On cheneygc the only solution would seem to be allocating some alien + memory, copying the data over, and arranging that it's freed once we + return. For GENCGC we could instead try to arrange that the string + from which the SAP is taken is always pinned. + + For some more details see comments for (define-alien-type-method + (c-string :deport-gen) ...) in host-c-call.lisp. + +402: "DECLAIM DECLARATION does not inform the PCL code-walker" + reported by Vincent Arkesteijn: + + (declaim (declaration foo)) + (defgeneric bar (x)) + (defmethod bar (x) + (declare (foo x)) + x) + + ==> WARNING: The declaration FOO is not understood by + SB-PCL::SPLIT-DECLARATIONS. + Please put FOO on one of the lists SB-PCL::*NON-VAR-DECLARATIONS*, + SB-PCL::*VAR-DECLARATIONS-WITH-ARG*, or + SB-PCL::*VAR-DECLARATIONS-WITHOUT-ARG*. + (Assuming it is a variable declaration without argument). + +403: FORMAT/PPRINT-LOGICAL-BLOCK of CONDITIONs ignoring *PRINT-CIRCLE* + In sbcl-0.9.13.34, + (defparameter *c* + (make-condition 'simple-error + :format-control "ow... ~S" + :format-arguments '(#1=(#1#)))) + (setf *print-circle* t *print-level* 4) + (format nil "~@<~A~:@>" *c*) + gives + "ow... (((#)))" + where I (WHN) believe the correct result is "ow... #1=(#1#)", + like the result from (PRINC-TO-STRING *C*). The question of + what the correct result is is complicated by the hairy text in + the Hyperspec "22.3.5.2 Tilde Less-Than-Sign: Logical Block", + Other than the difference in its argument, ~@<...~:> is + exactly the same as ~<...~:> except that circularity detection + is not applied if ~@<...~:> is encountered at top level in a + format string. + But because the odd behavior happens even without the at-sign, + (format nil "~<~A~:@>" (list *c*)) ; => "ow... (((#)))" + and because something seemingly similar can happen even in + PPRINT-LOGICAL-BLOCK invoked directly without FORMAT, + (pprint-logical-block (*standard-output* '(some nonempty list)) + (format *standard-output* "~A" '#1=(#1#))) + (which prints "(((#)))" to *STANDARD-OUTPUT*), I don't think + that the 22.3.5.2 trickiness is fundamental to the problem. + + My guess is that the problem is related to the logic around the MODE + argument to CHECK-FOR-CIRCULARITY, but I haven't reverse-engineered + enough of the intended meaning of the different MODE values to be + confident of this. + +404: nonstandard DWIMness in LOOP with unportably-ordered clauses + In sbcl-0.9.13, the code + (loop with stack = (make-array 2 :fill-pointer 2 :initial-element t) + for length = (length stack) + while (plusp length) + for element = (vector-pop stack) + collect element) + compiles without error or warning and returns (T T). Unfortunately, + it is inconsistent with the ANSI definition of the LOOP macro, + because it mixes up VARIABLE-CLAUSEs with MAIN-CLAUSEs. Furthermore, + SBCL's interpretation of the intended meaning is only one possible, + unportable interpretation of the noncompliant code; in CLISP 2.33.2, + the code compiles with a warning + LOOP: FOR clauses should occur before the loop's main body + and then fails at runtime with + VECTOR-POP: #() has length zero + perhaps because CLISP has shuffled the clauses into an + ANSI-compliant order before proceeding. + +405: a TYPE-ERROR in MERGE-LETS exercised at DEBUG 3 + In sbcl-0.9.16.21 on linux/86, compiling + (declaim (optimize (debug 3))) + (defstruct foo bar) + (let () + (flet ((i (x) (frob x (foo-bar foo)))) + (i :five))) + causes a TYPE-ERROR + The value NIL is not of type SB-C::PHYSENV. + in MERGE-LETS. + +406: functional has external references -- failed aver + Given the following food in a single file + (eval-when (:compile-toplevel :load-toplevel :execute) + (defstruct foo3)) + (defstruct bar + (foo #.(make-foo3))) + as of 0.9.18.11 the file compiler breaks on it: + failed AVER: "(NOT (FUNCTIONAL-HAS-EXTERNAL-REFERENCES-P CLAMBDA))" + Defining the missing MAKE-LOAD-FORM method makes the error go away. + +407: misoptimization of loop, COERCE 'FLOAT, and HANDLER-CASE for bignums + (reported by Ariel Badichi on sbcl-devel 2007-01-09) + 407a: In sbcl-1.0.1 on Linux x86, + (defun foo () + (loop for n from (expt 2 1024) do + (handler-case + (coerce n 'single-float) + (simple-type-error () + (format t "Got here.~%") + (return-from foo))))) + (foo) + causes an infinite loop, where handling the error would be expected. + 407b: In sbcl-1.0.1 on Linux x86, + (defun bar () + (loop for n from (expt 2 1024) do + (handler-case + (format t "~E~%" (coerce n 'single-float)) + (simple-type-error () + (format t "Got here.~%") + (return-from bar))))) + fails to compile, with + Too large to be represented as a SINGLE-FLOAT: ... + from + 0: ((LABELS SB-BIGNUM::CHECK-EXPONENT) ...) + 1: ((LABELS SB-BIGNUM::FLOAT-FROM-BITS) ...) + 2: (SB-KERNEL:%SINGLE-FLOAT ...) + 3: (SB-C::BOUND-FUNC ...) + 4: (SB-C::%SINGLE-FLOAT-DERIVE-TYPE-AUX ...) + +408: SUBTYPEP confusion re. OR of SATISFIES of not-yet-defined predicate + As reported by Levente M\'{e}sz\'{a}ros sbcl-devel 2006-02-20, + (aver (equal (multiple-value-list + (subtypep '(or (satisfies x) string) + '(or (satisfies x) integer))) + '(nil nil))) + fails. Also, beneath that failure lurks another failure, + (aver (equal (multiple-value-list + (subtypep 'string + '(or (satisfies x) integer))) + '(nil nil))) + Having looked at this for an hour or so in sbcl-1.0.2, and + specifically having looked at the output from + laptop$ sbcl + * (let ((x 'string) + (y '(or (satisfies x) integer))) + (trace sb-kernel::union-complex-subtypep-arg2 + sb-kernel::invoke-complex-subtypep-arg1-method + sb-kernel::type-union + sb-kernel::type-intersection + sb-kernel::type=) + (subtypep x y)) + my (WHN) impression is that the problem is that the semantics of TYPE= + are wrong for what the UNION-COMPLEX-SUBTYPEP-ARG2 code is trying + to use it for. The comments on the definition of TYPE= probably + date back to CMU CL and seem to define it as a confusing thing: + its primary value is something like "certainly equal," and its + secondary value is something like "certain about that certainty." + I'm left uncertain how to fix UNION-COMPLEX-SUBTYPEP-ARG2 without + reducing its generality by removing the TYPE= cleverness. Possibly + the tempting TYPE/= relative defined next to it might be a + suitable replacement for the purpose. Probably, though, it would + be best to start by reverse engineering exactly what TYPE= and + TYPE/= do, and writing an explanation which is so clear that one + can see immediately what it's supposed to mean in odd cases like + (TYPE= '(SATISFIES X) 'INTEGER) when X isn't defined yet. + +409: MORE TYPE SYSTEM PROBLEMS + Found while investigating an optimization failure for extended + sequences. The extended sequence type implementation was altered to + work around the problem, but the fundamental problem remains, to wit: + (sb-kernel:type= (sb-kernel:specifier-type '(or float ratio)) + (sb-kernel:specifier-type 'single-float)) + returns NIL, NIL on sbcl-1.0.3. + (probably related to bug #408) + +410: read circularities and type declarations + Consider the definition + (defstruct foo (a 0 :type (not symbol))) + followed by + (setf *print-circle* t) ; just in case + (read-from-string "#1=#s(foo :a #1#)") + This gives a type error (#:G1 is not a (NOT SYMBOL)) because of the + implementation of read circularity, using a symbol as a marker for + the previously-referenced object. + +411: NAN issues on x86-64 + Test :NAN-COMPARISONS in float.pure.lisp fails on x86-64, and has been + disabled on those platforms. Since x86 does not exhibit any problems + the problem is probably with the new FP implementation.