X-Git-Url: http://repo.macrolet.net/gitweb/?a=blobdiff_plain;f=BUGS;h=4b009c11566065249bb7475e8b3deb9b1f886643;hb=aa8c8cd473f1d487fa2c1a7490c78a59b9955bbe;hp=e6de843dcf159e1a72f73772516fcde0d2d88810;hpb=62b0a9c5190806368487d46d8773734cb1ee3a25;p=sbcl.git diff --git a/BUGS b/BUGS index e6de843..4b009c1 100644 --- a/BUGS +++ b/BUGS @@ -94,6 +94,9 @@ WORKAROUND: 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. @@ -195,19 +198,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. - - (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 @@ -585,18 +575,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 @@ -675,15 +653,6 @@ WORKAROUND: (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)) @@ -742,6 +711,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) @@ -895,17 +869,6 @@ WORKAROUND: (1+ *faa*)) (faa 1d0) => type error -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) @@ -931,24 +894,6 @@ WORKAROUND: (see also bug 117) -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 @@ -1017,14 +962,6 @@ WORKAROUND: 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 @@ -1073,17 +1010,6 @@ WORKAROUND: The problem is that both EVALs sequentially write to the same LVAR. -305: - (Reported by Dave Roberts.) - Local INLINE/NOTINLINE declaration removes local FTYPE declaration: - - (defun quux (x) - (declare (ftype (function () (integer 0 10)) fee) - (inline fee)) - (1+ (fee))) - - uses generic arithmetic with INLINE and fixnum without. - 306: "Imprecise unions of array types" a.(defun foo (x) (declare (optimize speed) @@ -1110,13 +1036,6 @@ WORKAROUND: around the same time regarding a call to LIST on sparc with 1000 arguments) and other implementation limit constants. -311: "Tokeniser not thread-safe" - (see also Robert Marlow sbcl-help "Multi threaded read chucking a - spak" 2004-04-19) - The tokenizer's use of *read-buffer* and *read-buffer-length* causes - spurious errors should two threads attempt to tokenise at the same - time. - 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. @@ -1160,20 +1079,6 @@ WORKAROUND: #(1 2 ((SB-IMPL::|,|) + 2 2) 4) which probably isn't intentional. -323: "REPLACE, BIT-BASH and large strings" - The transform for REPLACE on simple-base-strings uses BIT-BASH, which - at present has an upper limit in size. Consequently, in sbcl-0.8.10 - (defun foo () - (declare (optimize speed (safety 1))) - (let ((x (make-string 140000000)) - (y (make-string 140000000))) - (length (replace x y)))) - (foo) - gives - debugger invoked on a TYPE-ERROR in thread 2412: - The value 1120000000 is not of type (MOD 536870911). - (see also "more and better sequence transforms" sbcl-devel 2004-05-10) - 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 @@ -1436,25 +1341,6 @@ WORKAROUND: method is applicable, and yet matches neither of the method group qualifier patterns. -341: PPRINT-LOGICAL-BLOCK / PPRINT-FILL / PPRINT-LINEAR sharing detection. - (from Paul Dietz' test suite) - - CLHS on PPRINT-LINEAR and PPRINT-FILL (and PPRINT-TABULAR, though - that's slightly different) states that these functions perform - circular and shared structure detection on their object. Therefore, - - a.(let ((*print-circle* t)) - (pprint-linear *standard-output* (let ((x '(a))) (list x x)))) - should print "(#1=(A) #1#)" - - b.(let ((*print-circle* t)) - (pprint-linear *standard-output* - (let ((x (cons nil nil))) (setf (cdr x) x) x))) - should print "#1=(NIL . #1#)" - - (it is likely that the fault lies in PPRINT-LOGICAL-BLOCK, as - suggested by the suggested implementation of PPRINT-TABULAR) - 343: MOP:COMPUTE-DISCRIMINATING-FUNCTION overriding causes error Even the simplest possible overriding of COMPUTE-DISCRIMINATING-FUNCTION, suggested in the PCL implementation @@ -2042,44 +1928,223 @@ WORKAROUND: #.SB-EXT:SINGLE/DOUBLE-FLOAT-POSITIVE-INFINITY. These tests have been disabled on Darwin for now. -373: profiling issues on ppc/darwin - The following bit from smoke.impure.lisp fails on ppc/darwin: - (progn - (defun profiled-fun () - (random 1d0)) - (profile profiled-fun) - (loop repeat 100000 do (profiled-fun)) - (report)) - dropping into the debugger with a TYPE-ERROR: - The value -1073741382 is not of type UNSIGNED-BYTE. - The test has been disabled on Darwin till the bug is fixed. - -374: BIT-AND problem on ppc/darwin: - The BIT-AND test in bit-vector.impure-cload.lisp results in - fatal error encountered in SBCL pid 8356: - GC invariant lost, file "gc-common.c", line 605 - on ppc/darwin. Test disabled for the duration. - -375: MISC.555 - (compile nil '(lambda (p1) - (declare (optimize (speed 1) (safety 2) (debug 2) (space 0)) - (type keyword p1)) - (keywordp p1))) - - fails on hairy type check in IR2. - - 1. KEYWORDP is MAYBE-INLINE expanded (before TYPEP-like - transformation could eliminate it). - - 2. From the only call of KEYWORDP the type of its argument is - derived to be KEYWORD. - - 2. Type check for P1 is generated; it uses KEYWORDP to perform the - check, and so references the local function; from the KEYWORDP - argument type new CAST to KEYWORD is generated. The compiler - loops forever. - -376: MISC.563 - Type deriver for CONJUGATE thinks that it returns an object of the - same type as its argument, which is wrong for such types as (EQL - #C(1 2)). +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. + +381: incautious calls to EQUAL in fasl dumping + Compiling + (frob #(#1=(a #1#))) + (frob #(#1=(b #1#))) + (frob #(#1=(a #1#))) + in sbcl-0.9.0 causes CONTROL-STACK-EXHAUSTED. My (WHN) impression + is that this follows from the use of (MAKE-HASH-TABLE :TEST 'EQUAL) + to detect sharing, in which case fixing it might require either + getting less ambitious about detecting shared list structure, or + implementing the moral equivalent of EQUAL hash tables in a + cycle-tolerant way. + +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. + +387: + 12:10 < jsnell> the package-lock test is basically due to a change in the test + behaviour when you install a handler for error around it. I + thought I'd disabled the test for now, but apparently that was + my imagination + 12:19 < Xophe> jsnell: ah, I see the problem in the package-locks stuff + 12:19 < Xophe> it's the same problem as we had with compiler-error conditions + 12:19 < Xophe> the thing that's signalled up and down the stack is a subtype of + ERROR, where it probably shouldn't be + +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). + +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. + +394: (SETF CLASS-NAME)/REINITIALIZE-INSTANCE bug + (found by PFD ansi-tests) + in sbcl-0.9.7.15, (SETF (CLASS-NAME ) 'NIL) causes + (FIND-CLASS NIL) to return a #. + +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. + +401: "optimizer runaway on bad constant type specifiers in TYPEP" + In 0.9.12.3 (and probably many earlier versions), COMPILE-FILE on + (defun ouch401 () + (etypecase (signum (- x y)) + ((-1 nil)) + ((0 1) (oops "shouldn't happen")))) + or just + (defun foo401 (x) + (typep x '(-1 nil))) + spins emitting what seems to be an endless series of compiler + warnings like + ; --> TYPEP TYPEP TYPEP TYPEP TYPEP TYPEP TYPEP TYPEP TYPEP TYPEP + ; --> TYPEP TYPEP TYPEP TYPEP TYPEP TYPEP TYPEP TYPEP TYPEP TYPEP + ; --> TYPEP + ; ==> + ; (TYPEP SB-C::OBJECT '(-1 NIL)) + ; + ; caught WARNING: + ; illegal type specifier for TYPEP: (-1 NIL)