X-Git-Url: http://repo.macrolet.net/gitweb/?a=blobdiff_plain;f=BUGS;h=c5ccffdd36272d054ea0173b91033f3ac1e5ee4a;hb=964e644f3f1ec2c169b1def87f11e2f5b09a748e;hp=0ad71a7026ce7ddd6344a3be8a3c06de1b2698b4;hpb=c41cb4c87eae7b04f844dca5f7edb5086c5d2d68;p=sbcl.git diff --git a/BUGS b/BUGS index 0ad71a7..c5ccffd 100644 --- a/BUGS +++ b/BUGS @@ -32,8 +32,6 @@ have gone away (typically because they were fixed, but sometimes for other reasons, e.g. because they were moved elsewhere). -KNOWN BUGS OF NO SPECIAL CLASS: - 2: DEFSTRUCT almost certainly should overwrite the old LAYOUT information instead of just punting when a contradictory structure definition @@ -91,15 +89,6 @@ WORKAROUND: 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) @@ -167,31 +156,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 - character streams, e.g. (MAKE-STRING-INPUT-STREAM "abc"). - 60: The debugger LIST-LOCATIONS command doesn't work properly. (How should it work properly?) @@ -272,6 +236,11 @@ WORKAROUND: GC, so that thereafter memory usage can never be reduced below that level. + (As of 0.8.7.3 it's likely that the latter half of this bug is fixed. + The interaction between gencgc and the variables used by + save-lisp-and-die is still nonoptimal, though, so no respite from + big core files yet) + 98: In sbcl-0.6.11.41 (and in all earlier SBCL, and in CMU CL), out-of-line structure slot setters are horribly inefficient @@ -332,6 +301,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. @@ -360,27 +338,7 @@ WORKAROUND: your pre-0.7.0 state of grace with #+sbcl (declaim (notinline find position find-if position-if)) ; bug 117.. -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. + (see also bug 279) 124: As of version 0.pre7.14, SBCL's implementation of MACROLET makes @@ -456,17 +414,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 @@ -498,17 +445,7 @@ WORKAROUND: conformance problem, since seems hard to construct useful code where it matters.) - b. - * (defun foo (x) - (declare (type (double-float -0d0) x)) - (declare (optimize speed)) - (+ x (sqrt (log (random 1d0))))) - debugger invoked on condition of type SIMPLE-ERROR: - bad thing to be a type specifier: ((COMPLEX - (DOUBLE-FLOAT 0.0d0 - #.SB-EXT:DOUBLE-FLOAT-POSITIVE-INFINITY)) - #C(0.0d0 #.SB-EXT:DOUBLE-FLOAT-POSITIVE-INFINITY) - #C(0.0d0 #.SB-EXT:DOUBLE-FLOAT-POSITIVE-INFINITY)) + b. (fixed in 0.8.3.43) 146: Floating point errors are reported poorly. E.g. on x86 OpenBSD @@ -542,6 +479,8 @@ WORKAROUND: isn't too surprising since there are many differences in stack implementation and GC conservatism between the X86 and other ports.) + This is probably the same bug as 216 + 167: In sbcl-0.7.3.11, compiling the (illegal) code (in-package :cl-user) @@ -626,12 +565,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 @@ -651,8 +584,7 @@ WORKAROUND: classes). This means that at present erroneous attempts to use WITH-SLOTS and the like on classes with metaclass STRUCTURE-CLASS won't get the corresponding STYLE-WARNING. - c. the examples in CLHS 7.6.5.1 (regarding generic function lambda - lists and &KEY arguments) do not signal errors when they should. + c. (fixed in 0.8.4.23) 201: "Incautious type inference from compound types" a. (reported by APD sbcl-devel 2002-09-17) @@ -739,11 +671,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 @@ -758,20 +685,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 @@ -796,6 +709,8 @@ WORKAROUND: the bad VECTOR-PUSH-EXTEND frame causes GC problems, though that may not be the actual problem. (CMU CL 18c doesn't have problems with this.) + This is probably the same bug as 162 + 217: "Bad type operations with FUNCTION types" In sbcl.0.7.7: @@ -822,20 +737,6 @@ WORKAROUND: produce invalid code, but type checking is not accurate.) 233: bugs in constraint propagation - a. - (defun foo (x) - (declare (optimize (speed 2) (safety 3))) - (let ((y 0d0)) - (values - (the double-float x) - (setq y (+ x 1d0)) - (setq x 3d0) - (quux y (+ y 2d0) (* y 3d0))))) - (foo 4) => segmentation violation - - (see usage of CONTINUATION-ASSERTED-TYPE in USE-RESULT-CONSTRAINTS) - (see also bug 236) - b. (declaim (optimize (speed 2) (safety 3))) (defun foo (x y) @@ -895,18 +796,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 @@ -929,13 +818,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)) @@ -998,11 +882,6 @@ 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 @@ -1025,12 +904,6 @@ WORKAROUND: 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(). - 266: David Lichteblau provided (sbcl-devel 2003-06-01) a patch to fix behaviour of streams with element-type (SIGNED-BYTE 8). The patch @@ -1064,10 +937,6 @@ WORKAROUND: (bignum "hip") (t "zuz"))) -272: - All forms of GC hooks (including notifiers and finalisers) are currently - (since 0.8.0) broken for gencgc (i.e. x86) users - 273: Compilation of the following two forms causes "X is unbound" error: @@ -1083,7 +952,9 @@ WORKAROUND: 274: CLHS says that type declaration of a symbol macro should not affect - its expansion, but in SBCL it does. + its expansion, but in SBCL it does. (If you like magic and want to + fix it, don't forget to change all uses of MACROEXPAND to + MACROEXPAND*.) 275: The following code (taken from CLOCC) takes a lot of time to compile: @@ -1094,18 +965,6 @@ 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) - -277: - IGNORE/IGNORABLE declarations should be acceptable for symbol - macros. - 278: a. (defun foo () @@ -1115,7 +974,7 @@ WORKAROUND: uses generic arithmetic. - b. For the example above, the compiler does not issue a note. + 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 @@ -1140,40 +999,548 @@ WORKAROUND: (declare (type (integer 1 100) abs-foo)) (print abs-foo))) -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))))) - -DEFUNCT CATEGORIES OF BUGS - IR1-#: - These labels were used for bugs related to the old IR1 interpreter. - The # values reached 6 before the category was closed down. + (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 + strongly suspected problems, as of 0.8.3.10: please update this + bug instead of creating new ones + + localtime() - called for timezone calculations in code/time.lisp + +284: Thread safety: special variables + There are lots of special variables in SBCL, and I feel sure that at + least some of them are indicative of potentially thread-unsafe + parts of the system. See doc/internals/notes/threading-specials + +286: "recursive known functions" + Self-call recognition conflicts with known function + recognition. Currently cross compiler and target COMPILE do not + recognize recursion, and in target compiler it can be disabled. We + can always disable it for known functions with RECURSIVE attribute, + but there remains a possibility of a function with a + (tail)-recursive simplification pass and transforms/VOPs for base + cases. + +287: PPC/Linux miscompilation or corruption in first GC + When the runtime is compiled with -O3 on certain PPC/Linux machines, a + segmentation fault is reported at the point of first triggered GC, + during the compilation of DEFSTRUCT WRAPPER. As a temporary workaround, + the runtime is no longer compiled with -O3 on PPC/Linux, but it is likely + that this merely obscures, not solves, the underlying problem; as and when + underlying problems are fixed, it would be worth trying again to provoke + this problem. + +288: fundamental cross-compilation issues (from old UGLINESS file) + Using host floating point numbers to represent target floating point + numbers, or host characters to represent target characters, is + theoretically shaky. (The characters are OK as long as the characters + are in the ANSI-guaranteed character set, though, so they aren't a + real problem as long as the sources don't need anything but that; + the floats are a real problem.) + +289: "type checking and source-transforms" + a. + (block nil (let () (funcall #'+ (eval 'nil) (eval '1) (return :good)))) + signals type error. + + Our policy is to check argument types at the moment of a call. It + disagrees with ANSI, which says that type assertions are put + immediately onto argument expressions, but is easier to implement in + IR1 and is more compatible to type inference, inline expansion, + etc. IR1-transforms automatically keep this policy, but source + transforms for associative functions (such as +), being applied + during IR1-convertion, do not. It may be tolerable for direct calls + (+ x y z), but for (FUNCALL #'+ x y z) it is non-conformant. + + b. Another aspect of this problem is efficiency. [x y + z +] + requires less registers than [x y z + +]. This transformation is + currently performed with source transforms, but it would be good to + also perform it in IR1 optimization phase. + +290: Alpha floating point and denormalized traps + In SBCL 0.8.3.6x on the alpha, we work around what appears to be a + hardware or kernel deficiency: the status of the enable/disable + denormalized-float traps bit seems to be ambiguous; by the time we + get to os_restore_fp_control after a trap, denormalized traps seem + to be enabled. Since we don't want a trap every time someone uses a + denormalized float, in general, we mask out that bit when we restore + the control word; however, this clobbers any change the user might + have made. + +296: + (reported by Adam Warner, sbcl-devel 2003-09-23) + + The --load toplevel argument does not perform any sanitization of its + argument. As a result, files with Lisp pathname pattern characters + (#\* or #\?, for instance) or quotation marks can cause the system + to perform arbitrary behaviour. + +297: + LOOP with non-constant arithmetic step clauses suffers from overzealous + type constraint: code of the form + (loop for d of-type double-float from 0d0 to 10d0 by x collect d) + compiles to a type restriction on X of (AND DOUBLE-FLOAT (REAL + (0))). However, an integral value of X should be legal, because + successive adds of integers to double-floats produces double-floats, + so none of the type restrictions in the code is violated. + +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))" + +302: Undefined type messes up DATA-VECTOR-REF expansion. + Compiling this file + (defun dis (s ei x y) + (declare (type (simple-array function (2)) s) (type ei ei)) + (funcall (aref s ei) x y)) + on sbcl-0.8.7.36/X86/Linux causes a BUG to be signalled: + full call to SB-KERNEL:DATA-VECTOR-REF + +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. + +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) + (type (or (array cons) (array vector)) x)) + (elt (aref x 0) 0)) + (foo #((0))) => TYPE-ERROR + + relatedly, + + 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) + +308: "Characters without names" + (reported by Bruno Haible sbcl-devel "character names are missing" + 2004-04-19) + (graphic-char-p (code-char 255)) + => NIL + (char-name (code-char 255)) + => NIL + + SBCL is unsure of what to do about characters with codes in the + range 128-255. Currently they are treated as non-graphic, but don't + have names, which is not compliant with the standard. Various fixes + are possible, such as + * giving them names such as NON-ASCII-128; + * reducing CHAR-CODE-LIMIT to 127 (almost certainly unpopular); + * making the characters graphic (makes a certain amount of sense); + * biting the bullet and implementing Unicode (probably quite hard). + +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. + +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. + ;; + ;; 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 + +317: "FORMAT of floating point numbers" + reported by Bruno Haible sbcl-devel "various SBCL bugs" from CLISP + test suite. + (format nil "~1F" 10) => "0." ; "10." expected + (format nil "~0F" 10) => "0." ; "10." expected + (format nil "~2F" 1234567.1) => "1000000." ; "1234567." expected + it would be nice if whatever fixed this also untangled the two + competing implementations of floating point printing (Steele and + White, and Burger and Dybvig) present in src/code/print.lisp + +318: "stack overflow in compiler warning with redefined class" + reported by Bruno Haible sbcl-devel "various SBCL bugs" from CLISP + test suite. + (setq *print-pretty* nil) + (defstruct foo a) + (setf (find-class 'foo) nil) + (defstruct foo slot-1) + gives + ...#)) 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. + +331: "lazy creation of CLOS classes for user-defined conditions" + (defstruct foo) + (defstruct (bar (:include foo))) + (sb-mop:class-direct-subclasses (find-class 'foo)) + returns NIL, rather than a singleton list containing the BAR class. + +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. + +337: MAKE-METHOD and user-defined method classes + (reported by Bruno Haible sbcl-devel 2004-06-11) + + In the presence of + +(defclass user-method (standard-method) (myslot)) +(defmacro def-user-method (name &rest rest) + (let* ((lambdalist-position (position-if #'listp rest)) + (qualifiers (subseq rest 0 lambdalist-position)) + (lambdalist (elt rest lambdalist-position)) + (body (subseq rest (+ lambdalist-position 1))) + (required-part + (subseq lambdalist 0 (or + (position-if + (lambda (x) (member x lambda-list-keywords)) + lambdalist) + (length lambdalist)))) + (specializers (mapcar #'find-class + (mapcar (lambda (x) (if (consp x) (second x) t)) + required-part))) + (unspecialized-required-part + (mapcar (lambda (x) (if (consp x) (first x) x)) required-part)) + (unspecialized-lambdalist + (append unspecialized-required-part + (subseq lambdalist (length required-part))))) + `(PROGN + (ADD-METHOD #',name + (MAKE-INSTANCE 'USER-METHOD + :QUALIFIERS ',qualifiers + :LAMBDA-LIST ',unspecialized-lambdalist + :SPECIALIZERS ',specializers + :FUNCTION + (LAMBDA (ARGUMENTS NEXT-METHODS-LIST) + (FLET ((NEXT-METHOD-P () NEXT-METHODS-LIST) + (CALL-NEXT-METHOD (&REST NEW-ARGUMENTS) + (UNLESS NEW-ARGUMENTS (SETQ NEW-ARGUMENTS ARGUMENTS)) + (IF (NULL NEXT-METHODS-LIST) + (ERROR "no next method for arguments ~:S" ARGUMENTS) + (FUNCALL (SB-PCL:METHOD-FUNCTION + (FIRST NEXT-METHODS-LIST)) + NEW-ARGUMENTS (REST NEXT-METHODS-LIST))))) + (APPLY #'(LAMBDA ,unspecialized-lambdalist ,@body) ARGUMENTS))))) + ',name))) + + (progn + (defgeneric test-um03 (x)) + (defmethod test-um03 ((x integer)) + (list* 'integer x (not (null (next-method-p))) (call-next-method))) + (def-user-method test-um03 ((x rational)) + (list* 'rational x (not (null (next-method-p))) (call-next-method))) + (defmethod test-um03 ((x real)) + (list 'real x (not (null (next-method-p))))) + (test-um03 17)) + works, but + + a.(progn + (defgeneric test-um10 (x)) + (defmethod test-um10 ((x integer)) + (list* 'integer x (not (null (next-method-p))) (call-next-method))) + (defmethod test-um10 ((x rational)) + (list* 'rational x (not (null (next-method-p))) (call-next-method))) + (defmethod test-um10 ((x real)) + (list 'real x (not (null (next-method-p))))) + (defmethod test-um10 :after ((x real))) + (def-user-method test-um10 :around ((x integer)) + (list* 'around-integer x + (not (null (next-method-p))) (call-next-method))) + (defmethod test-um10 :around ((x rational)) + (list* 'around-rational x + (not (null (next-method-p))) (call-next-method))) + (defmethod test-um10 :around ((x real)) + (list* 'around-real x (not (null (next-method-p))) (call-next-method))) + (test-um10 17)) + fails with a type error, and + + b.(progn + (defgeneric test-um12 (x)) + (defmethod test-um12 ((x integer)) + (list* 'integer x (not (null (next-method-p))) (call-next-method))) + (defmethod test-um12 ((x rational)) + (list* 'rational x (not (null (next-method-p))) (call-next-method))) + (defmethod test-um12 ((x real)) + (list 'real x (not (null (next-method-p))))) + (defmethod test-um12 :after ((x real))) + (defmethod test-um12 :around ((x integer)) + (list* 'around-integer x + (not (null (next-method-p))) (call-next-method))) + (defmethod test-um12 :around ((x rational)) + (list* 'around-rational x + (not (null (next-method-p))) (call-next-method))) + (def-user-method test-um12 :around ((x real)) + (list* 'around-real x (not (null (next-method-p))) (call-next-method))) + (test-um12 17)) + fails with NO-APPLICABLE-METHOD. + +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. qualifier matching incorrect + (progn + (define-method-combination mc27 () + ((normal ()) + (ignored (:ignore :unused))) + `(list 'result + ,@(mapcar #'(lambda (method) `(call-method ,method)) normal))) + (defgeneric test-mc27 (x) + (:method-combination mc27) + (:method :ignore ((x number)) (/ 0))) + (test-mc27 7)) + + should signal an invalid-method-error, as the :IGNORE (NUMBER) + method is applicable, and yet matches neither of the method group + qualifier patterns. + +340: SETF of VALUES using too many values + (fixed in sbcl-0.8.12.10)