X-Git-Url: http://repo.macrolet.net/gitweb/?a=blobdiff_plain;f=BUGS;h=ba4e1f1ad2f0f3f5c1fba83234def705ed340c45;hb=dc4be57ff0baeee18d43fbee1bfc1af4af50e522;hp=2304eb1ac78258e74b938a2b9b51098122ef8841;hpb=7c1298a73f97b8c71474d8aa4a7c8f863fe0718d;p=sbcl.git diff --git a/BUGS b/BUGS index 2304eb1..ba4e1f1 100644 --- a/BUGS +++ b/BUGS @@ -84,42 +84,12 @@ 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. @@ -165,29 +135,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. - -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)) @@ -195,6 +142,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 @@ -218,20 +171,6 @@ 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) - 83: RANDOM-INTEGER-EXTRA-BITS=10 may not be large enough for the RANDOM RNG to be high quality near RANDOM-FIXNUM-MAX; it looks as though @@ -368,34 +307,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. - - Bruno Haible comments: - The values are those that are expected for an IEEE double-float - arithmetic. The problem appears to be that the rounding is not - IEEE on x86 compliant: namely, values are first rounded to 64 - bits mantissa precision, then only to 53 bits mantissa - precision. This gives different results than rounding to 53 bits - mantissa precision in a single step. - - The quick "fix", to permanently change the FPU control word from - 0x037f to 0x027f, will give problems with the fdlibm code that is - used for computing transcendental functions like sinh() etc. - so maybe we need to change the FPU control word to that for Lisp - code, and adjust it to the safe 0x037f for calls to C? - 124: As of version 0.pre7.14, SBCL's implementation of MACROLET makes the entire lexical environment at the point of MACROLET available @@ -442,24 +353,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, @@ -470,15 +363,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) - - c. (reported by Paul F. Dietz) - * '`(lambda ,x) - `(LAMBDA (SB-IMPL::BACKQ-COMMA X)) - 143: (reported by Jesse Bouwman 2001-10-24 through the unfortunately prominent SourceForge web/db bug tracking system, which is @@ -510,6 +394,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: @@ -546,20 +434,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 @@ -736,7 +610,6 @@ WORKAROUND: all of the arguments are circular is probably desireable). 213: "Sequence functions and type checking" - a. (fixed in 0.8.4.36) b. MAP, when given a type argument that is SUBTYPEP LIST, does not check that it will return a sequence of the given type. Fixing it along the same lines as the others (cf. work done around @@ -862,18 +735,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 @@ -961,26 +822,12 @@ WORKAROUND: b. The same for CSUBTYPEP. 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. + 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 @@ -1000,9 +847,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: @@ -1044,12 +888,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) + 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 278: a. @@ -1087,39 +931,6 @@ 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*) @@ -1245,14 +1056,6 @@ WORKAROUND: 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 @@ -1270,17 +1073,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) @@ -1297,23 +1089,6 @@ WORKAROUND: 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) @@ -1331,21 +1106,6 @@ WORKAROUND: spurious errors should two threads attempt to tokenise at the same time. -312: - (reported by Jon Dyte) - SBCL issues a warning "Duplicate definition of FOO" compiling - - (declaim (inline foo)) - (defun foo (x) - (1+ x)) - (defun bar (y) - (list (foo y) (if (> y 1) (funcall (if (> y 0) #'foo #'identity) y)))) - - (probably related to the bug 280.) - -313: "source-transforms are Lisp-1" - (fixed in 0.8.10.2) - 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. @@ -1363,56 +1123,23 @@ WORKAROUND: Expected: (2 6 15 38) Got: ERROR -315: "no bounds check for access to displaced array" - reported by Bruno Haible sbcl-devel "various SBCL bugs" from CLISP - test suite. - (locally (declare (optimize (safety 3) (speed 0))) - (let* ((x (make-array 10 :fill-pointer 4 :element-type 'character - :initial-element #\space :adjustable t)) - (y (make-array 10 :fill-pointer 4 :element-type 'character - :displaced-to x))) - (adjust-array x '(5)) - (char y 5))) - - SBCL 0.8.10 elides the bounds check somewhere along the line, and - returns #\Nul (where an error would be much preferable, since a test - of that form but with (setf (char y 5) #\Space) potentially corrupts - the heap and certainly confuses the world if that string is used by - C code. - -316: "SHIFTF and multiple values" - reported by Bruno Haible sbcl-devel "various SBCL bugs" from CLISP - test suite. - (shiftf (values x y) (values y x)) - gives an error in sbcl-0.8.10. - - Parts of the explanation of SHIFTF in ANSI CL talk about multiple - store variables, and the X3J13 vote - SETF-MULTIPLE-STORE-VARIABLES:ALLOW also says that SHIFTF should - support multiple value places. - -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 - ...# + ... + 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 @@ -1422,44 +1149,931 @@ WORKAROUND: #(1 2 ((SB-IMPL::|,|) + 2 2) 4) which probably isn't intentional. -320: "shared to local slot in class redefinition" - reported by Bruno Haible sbcl-devel "various SBCL bugs" from CLISP - test suite. - ;; Shared slot becomes local. - ;; 4.3.6.1.: "The value of a slot that is specified as shared in - ;; the old class and as local in the new class is retained." - (multiple-value-bind (value condition) - (ignore-errors - (defclass foo85a () - ((size :initarg :size :initform 1 :allocation :class))) - (defclass foo85b (foo85a) ()) - (setq i (make-instance 'foo85b)) - (defclass foo85a () ((size :initarg :size :initform 2) (other))) - (slot-value i 'size)) - (list value (type-of condition))) - should return (1 NULL) but returns (2 NULL) in sbcl-0.8.10. See - ensuing discussion sbcl-devel for how to deal with this. - -321: "DEFINE-METHOD-COMBINATION lambda list parsing" - reported by Bruno Haible sbcl-devel "various SBCL bugs" from CLISP - test suite. - (define-method-combination w-args () - ((method-list *)) - (:arguments arg1 arg2 &aux (extra :extra)) - `(progn ,@(mapcar (lambda (method) `(call-method ,method)) method-list))) - gives a (caught) compile-time error, which can be exposed by - (defgeneric mc-test-w-args (p1 p2 s) - (:method-combination w-args) - (:method ((p1 number) (p2 t) s) - (vector-push-extend (list 'number p1 p2) s)) - (:method ((p1 string) (p2 t) s) - (vector-push-extend (list 'string p1 p2) s)) - (:method ((p1 t) (p2 t) s) (vector-push-extend (list t p1 p2) s))) - -322: "DEFSTRUCT :TYPE LIST predicate and improper lists" - reported by Bruno Haible sbcl-devel "various SBCL bugs" from CLISP - test suite. - (defstruct (a (:type list) (:initial-offset 5) :named)) - (defstruct (b (:type list) (:initial-offset 2) :named (:include a))) - (b-p (list* nil nil nil nil nil 'foo73 nil 'tail)) - gives an error in sbcl-0.8.10 +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 + 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. + +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. + +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 + as "canonical", does not work: + (defclass my-generic-function (standard-generic-function) () + (:metaclass funcallable-standard-class)) + (defmethod compute-discriminating-function ((gf my-generic-function)) + (let ((dfun (call-next-method))) + (lambda (&rest args) + (apply dfun args)))) + (defgeneric foo (x) + (:generic-function-class my-generic-function)) + (defmethod foo (x) (+ x x)) + (foo 5) + signals an error. This error is the same even if the LAMBDA is + replaced by (FUNCTION (SB-KERNEL:INSTANCE-LAMBDA ...)). Maybe the + SET-FUNCALLABLE-INSTANCE-FUN scary stuff in + src/code/target-defstruct.lisp is broken? This seems to be broken + in CMUCL 18e, so it's not caused by a recent change. + +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. + +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. + +355: change-class of generic-function + (reported by Bruno Haible) + The MOP doesn't support change-class on a generic-function. However, SBCL + apparently supports it, since it doesn't give an error or warning when doing + so so. Then, however, it produces wrong results for calls to this generic + function. + ;;; The effective-methods cache: + (progn + (defgeneric testgf35 (x)) + (defmethod testgf35 ((x integer)) + (cons 'integer (if (next-method-p) (call-next-method)))) + (defmethod testgf35 ((x real)) + (cons 'real (if (next-method-p) (call-next-method)))) + (defclass customized5-generic-function (standard-generic-function) + () + (:metaclass sb-pcl:funcallable-standard-class)) + (defmethod sb-pcl:compute-effective-method ((gf customized5-generic-function) method-combination methods) + `(REVERSE ,(call-next-method))) + (list + (testgf35 3) + (progn + (change-class #'testgf35 'customized5-generic-function) + (testgf35 3)))) + Expected: ((INTEGER REAL) (REAL INTEGER)) + Got: ((INTEGER REAL) (INTEGER REAL)) + ;;; The discriminating-function cache: + (progn + (defgeneric testgf36 (x)) + (defmethod testgf36 ((x integer)) + (cons 'integer (if (next-method-p) (call-next-method)))) + (defmethod testgf36 ((x real)) + (cons 'real (if (next-method-p) (call-next-method)))) + (defclass customized6-generic-function (standard-generic-function) + () + (:metaclass sb-pcl:funcallable-standard-class)) + (defmethod sb-pcl:compute-discriminating-function ((gf customized6-generic-function)) + (let ((orig-df (call-next-method))) + #'(lambda (&rest arguments) + (reverse (apply orig-df arguments))))) + (list + (testgf36 3) + (progn + (change-class #'testgf36 'customized6-generic-function) + (testgf36 3)))) + Expected: ((INTEGER REAL) (REAL INTEGER)) + Got: ((INTEGER REAL) (INTEGER REAL)) + +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." + +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) + +358: :DECLARE argument to ENSURE-GENERIC-FUNCTION + (reported by Bruno Haible) + According to ANSI CL, ensure-generic-function must accept a :DECLARE + keyword argument. In SBCL 0.8.16 it does not. + Test case: + (progn + (ensure-generic-function 'foo113 :declare '((optimize (speed 3)))) + (sb-pcl:generic-function-declarations #'foo113)) + Expected: ((OPTIMIZE (SPEED 3))) + Got: ERROR + Invalid initialization argument: + :DECLARE + in call for class #. + See also: + The ANSI Standard, Section 7.1.2 + + Bruno notes: The MOP specifies that ensure-generic-function accepts :DECLARATIONS. + The easiest way to be compliant to both specs is to accept both (exclusively + or cumulatively). + +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: # + +360: CALL-METHOD not recognized in method-combination body + (reported by Bruno Haible) + This method combination, which adds 'redo' and 'return' restarts for each + method invocation to standard method combination, gives an error in SBCL. + (defun prompt-for-new-values () + (format *debug-io* "~&New values: ") + (list (read *debug-io*))) + (defun add-method-restarts (form method) + (let ((block (gensym)) + (tag (gensym))) + `(BLOCK ,block + (TAGBODY + ,tag + (RETURN-FROM ,block + (RESTART-CASE ,form + (METHOD-REDO () + :REPORT (LAMBDA (STREAM) (FORMAT STREAM "Try calling ~S again." ,method)) + (GO ,tag)) + (METHOD-RETURN (L) + :REPORT (LAMBDA (STREAM) (FORMAT STREAM "Specify return values for ~S call." ,method)) + :INTERACTIVE (LAMBDA () (PROMPT-FOR-NEW-VALUES)) + (RETURN-FROM ,block (VALUES-LIST L))))))))) + (defun convert-effective-method (efm) + (if (consp efm) + (if (eq (car efm) 'CALL-METHOD) + (let ((method-list (third efm))) + (if (or (typep (first method-list) 'method) (rest method-list)) + ; Reduce the case of multiple methods to a single one. + ; Make the call to the next-method explicit. + (convert-effective-method + `(CALL-METHOD ,(second efm) + ((MAKE-METHOD + (CALL-METHOD ,(first method-list) ,(rest method-list)))))) + ; Now the case of at most one method. + (if (typep (second efm) 'method) + ; Wrap the method call in a RESTART-CASE. + (add-method-restarts + (cons (convert-effective-method (car efm)) + (convert-effective-method (cdr efm))) + (second efm)) + ; Normal recursive processing. + (cons (convert-effective-method (car efm)) + (convert-effective-method (cdr efm)))))) + (cons (convert-effective-method (car efm)) + (convert-effective-method (cdr efm)))) + efm)) + (define-method-combination standard-with-restarts () + ((around (:around)) + (before (:before)) + (primary () :required t) + (after (:after))) + (flet ((call-methods-sequentially (methods) + (mapcar #'(lambda (method) + `(CALL-METHOD ,method)) + methods))) + (let ((form (if (or before after (rest primary)) + `(MULTIPLE-VALUE-PROG1 + (PROGN + ,@(call-methods-sequentially before) + (CALL-METHOD ,(first primary) ,(rest primary))) + ,@(call-methods-sequentially (reverse after))) + `(CALL-METHOD ,(first primary))))) + (when around + (setq form + `(CALL-METHOD ,(first around) + (,@(rest around) (MAKE-METHOD ,form))))) + (convert-effective-method form)))) + (defgeneric testgf16 (x) (:method-combination standard-with-restarts)) + (defclass testclass16a () ()) + (defclass testclass16b (testclass16a) ()) + (defclass testclass16c (testclass16a) ()) + (defclass testclass16d (testclass16b testclass16c) ()) + (defmethod testgf16 ((x testclass16a)) + (list 'a + (not (null (find-restart 'method-redo))) + (not (null (find-restart 'method-return))))) + (defmethod testgf16 ((x testclass16b)) + (cons 'b (call-next-method))) + (defmethod testgf16 ((x testclass16c)) + (cons 'c (call-next-method))) + (defmethod testgf16 ((x testclass16d)) + (cons 'd (call-next-method))) + (testgf16 (make-instance 'testclass16d)) + + Expected: (D B C A T T) + Got: ERROR CALL-METHOD outside of a effective method form + + This is a bug because ANSI CL HyperSpec/Body/locmac_call-m__make-method + says + "The macro call-method invokes the specified method, supplying it with + arguments and with definitions for call-next-method and for next-method-p. + If the invocation of call-method is lexically inside of a make-method, + the arguments are those that were supplied to that method. Otherwise + the arguments are those that were supplied to the generic function." + and the example uses nothing more than these two cases (as you can see by + doing (trace convert-effective-method)). + +361: initialize-instance of standard-reader-method ignores :function argument + (reported by Bruno Haible) + Pass a custom :function argument to initialize-instance of a + standard-reader-method instance, but it has no effect. + ;; Check that it's possible to define reader methods that do typechecking. + (progn + (defclass typechecking-reader-method (sb-pcl:standard-reader-method) + ()) + (defmethod initialize-instance ((method typechecking-reader-method) &rest initargs + &key slot-definition) + (let ((name (sb-pcl:slot-definition-name slot-definition)) + (type (sb-pcl:slot-definition-type slot-definition))) + (apply #'call-next-method method + :function #'(lambda (args next-methods) + (declare (ignore next-methods)) + (apply #'(lambda (instance) + (let ((value (slot-value instance name))) + (unless (typep value type) + (error "Slot ~S of ~S is not of type ~S: ~S" + name instance type value)) + value)) + args)) + initargs))) + (defclass typechecking-reader-class (standard-class) + ()) + (defmethod sb-pcl:validate-superclass ((c1 typechecking-reader-class) (c2 standard-class)) + t) + (defmethod reader-method-class ((class typechecking-reader-class) direct-slot &rest args) + (find-class 'typechecking-reader-method)) + (defclass testclass25 () + ((pair :type (cons symbol (cons symbol null)) :initarg :pair :accessor testclass25-pair)) + (:metaclass typechecking-reader-class)) + (macrolet ((succeeds (form) + `(not (nth-value 1 (ignore-errors ,form))))) + (let ((p (list 'abc 'def)) + (x (make-instance 'testclass25))) + (list (succeeds (make-instance 'testclass25 :pair '(seventeen 17))) + (succeeds (setf (testclass25-pair x) p)) + (succeeds (setf (second p) 456)) + (succeeds (testclass25-pair x)) + (succeeds (slot-value x 'pair)))))) + Expected: (t t t nil t) + Got: (t t t t t) + + (inspect (first (sb-pcl:generic-function-methods #'testclass25-pair))) + shows that the method was created with a FAST-FUNCTION slot but with a + FUNCTION slot of NIL. + +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: # + +364: does not support class objects as specializer names + (reported by Bruno Haible) + According to ANSI CL 7.6.2, class objects are valid specializer names, + and "Parameter specializer names are used in macros intended as the + user-level interface (defmethod)". DEFMETHOD's syntax section doesn't + mention this possibility in the BNF for parameter-specializer-name; + however, this appears to be an editorial omission, since the CLHS + mentions issue CLASS-OBJECT-SPECIALIZER:AFFIRM as being approved + by X3J13. SBCL doesn't support it: + (defclass foo () ()) + (defmethod goo ((x #.(find-class 'foo))) x) + Expected: #)> + Got: ERROR "# is not a legal class name." + +365: mixin on generic-function subclass + (reported by Bruno Haible) + a mixin class + (defclass prioritized-dispatcher () + ((dependents :type list :initform nil))) + on a generic-function subclass: + (defclass prioritized-generic-function (prioritized-dispatcher standard-generic-function) + () + (:metaclass sb-pcl:funcallable-standard-class)) + SBCL gives an error on this, telling to define a method on SB-MOP:VALIDATE-SUPERCLASS. If done, + (defmethod sb-pcl:validate-superclass ((c1 sb-pcl:funcallable-standard-class) + (c2 (eql (find-class 'prioritized-dispatcher)))) + t) + then, however, + (defclass prioritized-generic-function (prioritized-dispatcher standard-generic-function) + () + (:metaclass sb-pcl:funcallable-standard-class)) + => debugger invoked on a SIMPLE-ERROR in thread 6687: + layout depth conflict: #(# ...) + + Further discussion on this: http://thread.gmane.org/gmane.lisp.steel-bank.general/491 + +366: cannot define two generic functions with user-defined class + (reported by Bruno Haible) + it is possible to define one generic function class and an instance + of it. But attempting to do the same thing again, in the same session, + leads to a "Control stack exhausted" error. Test case: + (defclass my-generic-function-1 (standard-generic-function) + () + (:metaclass sb-pcl:funcallable-standard-class)) + (defgeneric testgf-1 (x) (:generic-function-class my-generic-function-1) + (:method ((x integer)) (cons 'integer nil))) + (defclass my-generic-function-2 (standard-generic-function) + () + (:metaclass sb-pcl:funcallable-standard-class)) + (defgeneric testgf-2 (x) (:generic-function-class my-generic-function-2) + (:method ((x integer)) (cons 'integer nil))) + => SB-KERNEL::CONTROL-STACK-EXHAUSTED + +367: TYPE-ERROR at compile time, undetected TYPE-ERROR at runtime + This test program + (declaim (optimize (safety 3) (debug 2) (speed 2) (space 1))) + (defstruct e367) + (defstruct i367) + (defstruct g367 + (i367s (make-array 0 :fill-pointer t) :type (or (vector i367) null))) + (defstruct s367 + (g367 (error "missing :G367") :type g367 :read-only t)) + ;;; In sbcl-0.8.18, commenting out this (DECLAIM (FTYPE ... R367)) + ;;; gives an internal error at compile time: + ;;; The value # is not of + ;;; type SB-KERNEL:VALUES-TYPE. + (declaim (ftype (function ((vector i367) e367) (or s367 null)) r367)) + (declaim (ftype (function ((vector e367)) (values)) h367)) + (defun frob (v w) + (let ((x (g367-i367s (make-g367)))) + (let* ((y (or (r367 x w) + (h367 x))) + (z (s367-g367 y))) + (format t "~&Y=~S Z=~S~%" y z) + (g367-i367s z)))) + (defun r367 (x y) (declare (ignore x y)) nil) + (defun h367 (x) (declare (ignore x)) (values)) + ;;; In sbcl-0.8.18, executing this form causes an low-level error + ;;; segmentation violation at #X9B0E1F4 + ;;; (instead of the TYPE-ERROR that one might like). + (frob 0 (make-e367)) + can be made to cause two different problems, as noted in the comments: + bug 367a: Compile and load the file. No TYPE-ERROR is signalled at + run time (in the (S367-G367 Y) form of FROB, when Y is NIL + instead of an instance of S367). Instead (on x86/Linux at least) + we end up with a segfault. + bug 367b: Comment out the (DECLAIM (FTYPE ... R367)), and compile + the file. The compiler fails with TYPE-ERROR at compile time. + +368: miscompiled OR (perhaps related to bug 367) + Trying to relax type declarations to find a workaround for bug 367, + it turns out that even when the return type isn't declared (or + declared to be T, anyway) the system remains confused about type + inference in code similar to that for bug 367: + (in-package :cl-user) + (declaim (optimize (safety 3) (debug 2) (speed 2) (space 1))) + (defstruct e368) + (defstruct i368) + (defstruct g368 + (i368s (make-array 0 :fill-pointer t) :type (or (vector i368) null))) + (defstruct s368 + (g368 (error "missing :G368") :type g368 :read-only t)) + (declaim (ftype (function (fixnum (vector i368) e368) t) r368)) + (declaim (ftype (function (fixnum (vector e368)) t) h368)) + (defparameter *h368-was-called-p* nil) + (defun nsu (vertices e368) + (let ((i368s (g368-i368s (make-g368)))) + (let ((fuis (r368 0 i368s e368))) + (format t "~&FUIS=~S~%" fuis) + (or fuis (h368 0 i368s))))) + (defun r368 (w x y) + (declare (ignore w x y)) + nil) + (defun h368 (w x) + (declare (ignore w x)) + (setf *h368-was-called-p* t) + (make-s368 :g368 (make-g368))) + (trace r368 h368) + (format t "~&calling NSU~%") + (let ((nsu (nsu #() (make-e368)))) + (format t "~&NSU returned ~S~%" nsu) + (format t "~&*H368-WAS-CALLED-P*=~S~%" *h368-was-called-p*) + (assert (s368-p nsu)) + (assert *h368-was-called-p*)) + In sbcl-0.8.18, both ASSERTs fail, and (DISASSEMBLE 'NSU) shows + that no call to H368 is compiled. + +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. + +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. + +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. + +378: floating-point exceptions not signalled on x86-64 + Floating point traps are currently not enabled on the x86-64 port. + This is true for at least overflow detection (as tested in + float.pure.lisp) and divide-by-zero. + +379: TRACE :ENCAPSULATE NIL broken on ppc/darwin + See commented-out test-case in debug.impure.lisp.