X-Git-Url: http://repo.macrolet.net/gitweb/?a=blobdiff_plain;f=BUGS;h=48ca825687a223c01fbd848d1df0b7acb5d1dad6;hb=f4e8bca5eaa6e6db42299fe2f3852fb2e07508c7;hp=5dd6895bdaa5e91b0f5baa3ce2dcd634cfaacdce;hpb=ba2143e06b11101674720393e6f6c30a23113a4b;p=sbcl.git diff --git a/BUGS b/BUGS index 5dd6895..48ca825 100644 --- a/BUGS +++ b/BUGS @@ -89,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) @@ -165,25 +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. - 60: The debugger LIST-LOCATIONS command doesn't work properly. (How should it work properly?) @@ -195,6 +167,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 and PPC architectures: + while giving the backtrace the system complains about "unknown + source location: using block start", but apart from that the + backtrace seems reasonable. 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 +196,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,20 +332,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. - 124: As of version 0.pre7.14, SBCL's implementation of MACROLET makes the entire lexical environment at the point of MACROLET available @@ -456,15 +406,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 @@ -532,20 +473,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 @@ -722,7 +649,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 @@ -848,18 +774,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 @@ -947,26 +861,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 @@ -986,9 +886,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: @@ -1029,14 +926,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) - 278: a. (defun foo () @@ -1073,39 +962,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*) @@ -1209,18 +1065,6 @@ WORKAROUND: successive adds of integers to double-floats produces double-floats, so none of the type restrictions in the code is violated. -298: (aka PFD MISC.183) - Compiler fails on - - (defun foo () - (multiple-value-call #'bar - (ext) - (catch 'tag (return-from foo (int))))) - - This program violates "unknown values LVAR stack discipline": if INT - returns, values returned by (EXT) must be removed from under that of - (INT). - 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 @@ -1243,14 +1087,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 @@ -1294,3 +1130,464 @@ WORKAROUND: ,@(loop for x across sb-vm:*specialized-array-element-type-properties* collect `(array ,(sb-vm:saetp-specifier x))))) => NIL, T (when it should be T, T) + +309: "Dubious values for implementation limits" + (reported by Bruno Haible sbcl-devel "Incorrect value of + multiple-values-limit" 2004-04-19) + (values-list (make-list 1000000)), on x86/linux, signals a stack + exhaustion condition, despite MULTIPLE-VALUES-LIMIT being + significantly larger than 1000000. There are probably similar + dubious values for CALL-ARGUMENTS-LIMIT (see cmucl-help/cmucl-imp + around the same time regarding a call to LIST on sparc with 1000 + arguments) and other implementation limit constants. + +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. + (defstruct foo a) + (setf (find-class 'foo) nil) + (defstruct foo slot-1) + This used to give a stack overflow from within the printer, which has + been fixed as of 0.8.16.11. Current result: + ; caught ERROR: + ; can't compile TYPEP of anonymous or undefined class: + ; # + ... + debugger invoked on a TYPE-ERROR in thread 19973: + The value NIL is not of type FUNCTION. + + CSR notes: it's not really clear what it should give: is (SETF FIND-CLASS) + meant to be enough to delete structure classes from the system? + +319: "backquote with comma inside array" + reported by Bruno Haible sbcl-devel "various SBCL bugs" from CLISP + test suite. + (read-from-string "`#1A(1 2 ,(+ 2 2) 4)") + gives + #(1 2 ((SB-IMPL::|,|) + 2 2) 4) + which probably isn't intentional. + +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. + +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. + +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) + +342: PPRINT-TABULAR / PPRINT-LOGICAL-BLOCK logical block start position + The logical block introduced by PPRINT-LOGICAL-BLOCK should not + include the prefix, so that + (pprint-tabular *standard-output* '(1 2 3) t nil 2) + should print + "(1 2 3)" rather than "(1 2 3)". + +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) + +345: backtrace on x86 undefined function + In sbcl-0.8.13 (and probably earlier versions), code of the form + (flet ((test () (#:undefined-fun 42))) + (funcall #'test)) + yields the debugger with a poorly-functioning backtrace. Brian + Downing fixed most of the problems on non-x86 architectures, but on + the x86 the backtrace from this evaluation does not reveal anything + about the problem. (See tests in debug.impure.lisp) + +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". + +348: + Structure slot setters do not preserve evaluation order: + + (defstruct foo (x)) + + (let ((i (eval '-2)) + (x (make-foo))) + (funcall #'(setf foo-x) + (incf i) + (aref (vector x) (incf i))) + (foo-x x)) + => error + +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.