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.
+
+ [much later, in 2006-08] in fact it's no longer erroneous to use
+ WITH-SLOTS on structure-classes. However, including :METACLASS
+ STRUCTURE-CLASS in the class definition gives a whole bunch of
+ function redefinition warnings, so we're still not good to close
+ this bug...
+
c. (fixed in 0.8.4.23)
201: "Incautious type inference from compound types"
(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
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)
method is applicable, and yet matches neither of the method group
qualifier patterns.
-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
The class named B is a forward referenced class.
The class named B is a direct superclass of the class named C.
+ [ Is this actually a bug? DEFCLASS only replaces an existing class
+ when the class name is the proper name of that class, and in the
+ above code the class found by (FIND-CLASS 'A) does not have a
+ proper name. CSR, 2006-08-07 ]
+
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
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
Expected: #<STANDARD-CLASS TYPECHECKING-READER-CLASS>
Got: ERROR "The assertion SB-PCL::WRAPPERS failed."
+ [ This test case does not cause the error any more. However,
+ similar problems can be observed with
+
+ (defclass foo (standard-class) ()
+ (:metaclass sb-mop:funcallable-standard-class))
+ (sb-mop:finalize-inheritance (find-class 'foo))
+ ;; ERROR, ABORT
+ (defclass bar (standard-class) ())
+ (make-instance 'bar)
+ ]
+
357: defstruct inheritance of initforms
(reported by Bruno Haible)
When defstruct and defclass (with :metaclass structure-class) are mixed,
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 #<SB-MOP:FUNCALLABLE-STANDARD-CLASS STANDARD-GENERIC-FUNCTION>.
- 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:
Expected: #<SB-MOP:FUNCALLABLE-STANDARD-CLASS STANDARD-GENERIC-FUNCTION>
Got: #<SB-MOP:FUNCALLABLE-STANDARD-CLASS MY-GENERIC-FUNCTION>
-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
Expected: ERROR
Got: #<SB-MOP:STANDARD-DIRECT-SLOT-DEFINITION FOO>
-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: #<STANDARD-METHOD GOO (#<STANDARD-CLASS FOO>)>
- Got: ERROR "#<STANDARD-CLASS FOO> 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: #(#<SB-KERNEL:LAYOUT for T {500E1E9}> ...)
-
- 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)))
SB-PCL::SPECIALIZER-APPLICABLE-USING-TYPE-P cannot handle the second argument
(UNSIGNED-BYTE 8).
+ [ Can't trigger this any more, as of 2006-08-07 ]
+
389:
(reported several times on sbcl-devel, by Rick Taube, Brian Rowe and
others)
(FOO 1 2)
gives NO-APPLICABLE-METHOD rather than an argument count error.
-394: (SETF CLASS-NAME)/REINITIALIZE-INSTANCE bug
- (found by PFD ansi-tests)
- in sbcl-0.9.7.15, (SETF (CLASS-NAME <class>) 'NIL) causes
- (FIND-CLASS NIL) to return a #<STANDARD-CLASS NIL>.
-
395: Unicode and streams
One of the remaining problems in SBCL's Unicode support is the lack
of generality in certain streams.