X-Git-Url: http://repo.macrolet.net/gitweb/?a=blobdiff_plain;f=BUGS;h=1cb8b2c050e027e098c8d059bc0de730414b6e5d;hb=9abfd1a2b22862570c15ffa5129b1196d0480290;hp=887ffbe70c17428c579217cb399f78b199b223f5;hpb=4ec46046e59ce00abe3e53bce16fdfb2c4c57362;p=sbcl.git diff --git a/BUGS b/BUGS index 887ffbe..1cb8b2c 100644 --- a/BUGS +++ b/BUGS @@ -21,6 +21,36 @@ but instead (MAKE-FOO) the program loops endlessly instead of printing the object. +If you run into a signal related bug, you are getting fatal errors +such as 'signal N is [un]blocked' or just hangs, and you want to send +a useful bug report then: + +- compile sbcl with ldb support (feature :sb-ldb, see + base-target-features.lisp-expr) and change '#define QSHOW_SIGNAL 0' + to '#define QSHOW_SIGNAL 1' in src/runtime/runtime.h. + +- isolate a smallish test case, run it + +- if it just hangs kill it with sigabrt: kill -ABRT + +- print the backtrace from ldb by typing 'ba' + +- attach gdb: gdb -p and get backtraces for all threads: + thread apply all ba + +- if multiple threads are in play then still in gdb, try to get Lisp + backtrace for all threads: 'thread apply all + call_backtrace_from_fp($ebp, 100)'. Substitute $ebp with $rbp on + x86-64. + +- send a report with the backtraces and the output (both stdout, + stderr) produced by sbcl + +- don't forget to include OS and SBCL version + +- if available include info on outcome of the same test with other + versions of SBCL, OS, ... + NOTES: @@ -77,13 +107,6 @@ WORKAROUND: Such code should compile without complaint and work correctly either on SBCL or on any other completely compliant Common Lisp system. - b: &AUX argument in a boa-constructor without a default value means - "do not initilize this slot" and does not cause type error. But - an error may be signalled at read time and it would be good if - SBCL did it. - - d: (fixed in 0.8.1.5) - 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. @@ -347,28 +370,6 @@ WORKAROUND: forever, even when it is uninterned and all other references to it are lost. -143: - (reported by Jesse Bouwman 2001-10-24 through the unfortunately - prominent SourceForge web/db bug tracking system, which is - unfortunately not a reliable way to get a timely response from - the SBCL maintainers) - In the course of trying to build a test case for an - application error, I encountered this behavior: - If you start up sbcl, and then lay on CTRL-C for a - minute or two, the lisp process will eventually say: - %PRIMITIVE HALT called; the party is over. - and throw you into the monitor. If I start up lisp, - attach to the process with strace, and then do the same - (abusive) thing, I get instead: - access failure in heap page not marked as write-protected - and the monitor again. I don't know enough to have the - faintest idea of what is going on here. - This is with sbcl 6.12, uname -a reports: - Linux prep 2.2.19 #4 SMP Tue Apr 24 13:59:52 CDT 2001 i686 unknown - I (WHN) have verified that the same thing occurs on sbcl-0.pre7.141 - under OpenBSD 2.9 on my X86 laptop. Do be patient when you try it: - 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 @@ -416,6 +417,8 @@ WORKAROUND: isn't too surprising since there are many differences in stack implementation and GC conservatism between the X86 and other ports.) + (Can't reproduce on x86 linux as of 1.0.20.23 - MGL) + This is probably the same bug as 216 173: @@ -479,6 +482,11 @@ WORKAROUND: (print (incf start 22)) (print (incf start 26)))))) + [ Update: 1.0.14.36 improved this quite a bit (20-25%) by + eliminating useless work from PROPAGATE-FROM-SETS -- but as alluded + below, maybe we should be smarter about when to decide a derived + type is "good enough". ] + This example could be solved with clever enough constraint propagation or with SSA, but consider @@ -551,11 +559,6 @@ WORKAROUND: c. The cross-compiler cannot inline functions defined in a non-null lexical environment. -206: ":SB-FLUID feature broken" - (reported by Antonio Martinez-Shotton sbcl-devel 2002-10-07) - Enabling :SB-FLUID in the target-features list in sbcl-0.7.8 breaks - the build. - 207: "poorly distributed SXHASH results for compound data" SBCL's SXHASH could probably try a little harder. ANSI: "the intent is that an implementation should make a good-faith @@ -604,21 +607,14 @@ WORKAROUND: can erroneously return T. 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 - ANSI 17.2 "the consequences are unspecified", which by ANSI 1.4.2 - means that the effect is "unpredictable but harmless". It's not - clear what that actually means; it may preclude conforming - implementations from signalling errors. - b. COUNT, REMOVE and the like give priority to a :TEST-NOT argument - when conflict occurs. As a quality of implementation issue, it - might be preferable to treat :TEST and :TEST-NOT as being in some - sense the same &KEY, and effectively take the first test function in - the argument list. - c. Again, a quality of implementation issue: it would be good to issue a - STYLE-WARNING at compile-time for calls with :TEST-NOT, and a - WARNING for calls with both :TEST and :TEST-NOT; possibly this - latter should be WARNed about at execute-time too. + + We should verify that our handling of :TEST-NOT and :TEST is consistent + for all functions that accept them: that is, signal an error if both + are specified. + + Similarly, a compile-time full warning for calls with both would be good. + + We might also consider a compile-time style warning for :TEST-NOT. 216: "debugger confused by frames with invalid number of arguments" In sbcl-0.7.8.51, executing e.g. (VECTOR-PUSH-EXTEND T), BACKTRACE, Q @@ -627,26 +623,9 @@ 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 - -235: "type system and inline expansion" - a. - (declaim (ftype (function (cons) number) acc)) - (declaim (inline acc)) - (defun acc (c) - (the number (car c))) + (Can't reproduce on x86 linux as of 1.0.20.22 - MGL) - (defun foo (x y) - (values (locally (declare (optimize (safety 0))) - (acc x)) - (locally (declare (optimize (safety 3))) - (acc y)))) - - (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. + This is probably the same bug as 162 237: "Environment arguments to type functions" a. Functions SUBTYPEP, TYPEP, UPGRADED-ARRAY-ELEMENT-TYPE, and @@ -658,32 +637,6 @@ WORKAROUND: calls of the form (TYPEP 1 'INTEGER NIL), even though this is just as optimizeable as (TYPEP 1 'INTEGER). -238: "REPL compiler overenthusiasm for CLOS code" - From the REPL, - * (defclass foo () ()) - * (defmethod bar ((x foo) (foo foo)) (call-next-method)) - causes approximately 100 lines of code deletion notes. Some - discussion on this issue happened under the title 'Three "interesting" - bugs in PCL', resulting in a fix for this oververbosity from the - compiler proper; however, the problem persists in the interactor - because the notion of original source is not preserved: for the - compiler, the original source of the above expression is (DEFMETHOD - BAR ((X FOO) (FOO FOO)) (CALL-NEXT-METHOD)), while by the time the - compiler gets its hands on the code needing compilation from the REPL, - it has been macroexpanded several times. - - A symptom of the same underlying problem, reported by Tony Martinez: - * (handler-case - (with-input-from-string (*query-io* " no") - (yes-or-no-p)) - (simple-type-error () 'error)) - ; in: LAMBDA NIL - ; (SB-KERNEL:FLOAT-WAIT) - ; - ; note: deleting unreachable code - ; compilation unit finished - ; printed 1 note - 242: "WRITE-SEQUENCE suboptimality" (observed from clx performance) In sbcl-0.7.13, WRITE-SEQUENCE of a sequence of type @@ -837,14 +790,6 @@ WORKAROUND: (fixed in 0.8.2.51, but a test case would be good) -276: - 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 The binding of ABS-FOO is a (VALUES (INTEGER 0 0) @@ -1046,7 +991,7 @@ WORKAROUND: (open "/dev/zero" :element-type '(unsigned-byte 1025)) gives an error in sbcl-0.8.10. -325: "CLOSE :ABORT T on supeseding streams" +325: "CLOSE :ABORT T on superseding streams" Closing a stream opened with :IF-EXISTS :SUPERSEDE with :ABORT T leaves no file on disk, even if one existed before opening. @@ -1129,25 +1074,6 @@ WORKAROUND: 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))) @@ -1253,21 +1179,6 @@ WORKAROUND: 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 @@ -1298,52 +1209,6 @@ WORKAROUND: (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: @@ -1392,30 +1257,6 @@ WORKAROUND: 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 @@ -1453,19 +1294,6 @@ WORKAROUND: 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 () @@ -1511,6 +1339,8 @@ WORKAROUND: 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"). + (format nil "~E" 0.01) => "10.e-3" (should be "1.e-2"); + (format nil "~G" 0.01) => "10.e-3" (should be "1.e-2"); 386: SunOS/x86 stack exhaustion handling broken According to , the @@ -1548,20 +1378,6 @@ WORKAROUND: (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) @@ -1663,17 +1479,6 @@ WORKAROUND: 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) @@ -1713,6 +1518,10 @@ WORKAROUND: 3: (SB-C::BOUND-FUNC ...) 4: (SB-C::%SINGLE-FLOAT-DERIVE-TYPE-AUX ...) + These are now fixed, but (COERCE HUGE 'SINGLE-FLOAT) still signals a + type-error at runtime. The question is, should it instead signal a + floating-point overflow, or return an infinity? + 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 @@ -1769,13 +1578,6 @@ WORKAROUND: implementation of read circularity, using a symbol as a marker for the previously-referenced object. -415: Issues creating large arrays on x86-64/Linux and x86/Darwin - - (make-array (1- array-dimension-limit)) - - causes a GC invariant violation on x86-64/Linux, and - an unhandled SIGILL on x86/Darwin. - 416: backtrace confusion (defun foo (x) @@ -1801,67 +1603,26 @@ WORKAROUND: 419: stack-allocated indirect closure variables are not popped - (locally (declare (optimize speed (safety 0))) (defun bug419 (x) (multiple-value-call #'list (eval '(values 1 2 3)) (let ((x x)) - (declare (dynamic-extent x)) + (declare (sb-int:truly-dynamic-extent x)) (flet ((mget (y) (+ x y)) (mset (z) (incf x z))) (declare (dynamic-extent #'mget #'mset)) - ((lambda (f g) (eval `(progn ,f ,g (values 4 5 6)))) #'mget #'mset)))))) - - (ASSERT (EQUAL (BUG419) '(1 2 3 4 5 6))) => failure - -420: The MISC.556 test from gcl/ansi-tests/misc.lsp fails hard. - -In sbcl-1.0.13 on Linux/x86, executing - (FUNCALL - (COMPILE NIL - '(LAMBDA (P1 P2) - (DECLARE - (OPTIMIZE (SPEED 1) (SAFETY 0) (DEBUG 0) (SPACE 0)) - (TYPE (MEMBER 8174.8604) P1) (TYPE (MEMBER -95195347) P2)) - (FLOOR P1 P2))) - 8174.8604 -95195347) -interactively causes - SB-SYS:MEMORY-FAULT-ERROR: Unhandled memory fault at #x8. -The gcl/ansi-tests/doit.lisp program terminates prematurely shortly after -MISC.556 by falling into gdb with - fatal error encountered in SBCL pid 2827: Unhandled SIGILL -unless the MISC.556 test is commented out. - -Analysis: + and a number of other arithmetic functions exhibit the -same behaviour. Here's the underlying problem: On x86 we perform -single-float + integer normally using double-precision, and then -coerce the result back to single-float. (The FILD instruction always -gives us a double-float, and unless we do MOVE-FROM-SINGLE it remains -one. Or so it seems to me, and that would also explain the observed -behaviour below.) - -During IR1 we derive the types for both - - (+ ) ; uses double-precision - (+ (FLOAT )) ; uses single-precision - -and get a mismatch for a number of unlucky arguments. This leads to -derived result type NIL, and ends up flushing the whole whole -operation -- and finally we generate code without a return sequence, -and fall through to whatever. - -The use of double-precision in the first case appears to be an -(un)happy accident -- interval arithmetic gives us the -double-precision result because that's what the backend does. - - (+ 8172.0 (coerce -95195347 'single-float)) ; => -9.518717e7 - (+ 8172.0 -95195347) ; => -9.5187176e7 - (coerce (+ 8172.0 (coerce -95195347 'double-float)) 'single-float) - ; => -9.5187176e7 - -Which should be fixed, the IR1, or the backend? + ((lambda (f g) (eval `(progn ,f ,g (values 4 5 6)))) #'mget #'mset))))) + + (ASSERT (EQUAL (BUG419 42) '(1 2 3 4 5 6))) => failure + + Note: as of SBCL 1.0.16.29 this bug no longer affects user code, as + SB-INT:TRULY-DYNAMIC-EXTENT needs to be used instead of + DYNAMIC-EXTENT for this to happen. Proper fix for this bug requires + (Nikodemus thinks) storing the relevant LAMBDA-VARs in a + :DYNAMIC-EXTENT cleanup, and teaching stack analysis how to deal + with them. 421: READ-CHAR-NO-HANG misbehaviour on Windows Console: @@ -1879,3 +1640,42 @@ Which should be fixed, the IR1, or the backend? behaves ...erratically. Reported by Kevin Reid on sbcl-devel 2007-07-06. (We don't _have_ to check things like this, but we generally try to check returns in safe code, so we should here too.) + +424: toplevel closures and *CHECK-CONSISTENCY* + + The following breaks under COMPILE-FILE if *CHECK-CONSISTENCY* is true. + + (let ((exported-symbols-alist + (loop for symbol being the external-symbols of :cl + collect (cons symbol + (concatenate 'string + "#" + (string-downcase symbol)))))) + (defun hyperdoc-lookup (symbol) + (cdr (assoc symbol exported-symbols-alist)))) + + (Test-case adapted from CL-PPCRE.) + +428: TIMER SCHEDULE-STRESS and PARALLEL-UNSCHEDULE in + timer.impure.lisp fails + + Failure modes vary. Core problem seems to be (?) recursive entry to + RUN-EXPIRED-TIMERS. + +429: compiler hangs + + Compiling a file with this contents makes the compiler loop in + ORDER-UVL-SETS: + + (declaim (inline storage)) + (defun storage (x) + (the (simple-array flt (*)) (unknown x))) + + (defun test1 (lumps &key cg) + (let ((nodes (map 'list (lambda (lump) (storage lump)) + lumps))) + (setf (aref nodes 0) 2) + (assert (every #'~= (apply #'concatenate 'list nodes) '(2 3 6 9))))) + +431: alien strucure redefinition doesn't work as expected + fixed in 1.0.21.29