X-Git-Url: http://repo.macrolet.net/gitweb/?a=blobdiff_plain;f=BUGS;h=0e990ce6ff103296b8ce3973603a56ef6f94ed33;hb=832f3b5652ae1b4a8888829cd4a1b391a8ca9952;hp=4860f0797c6b6128a7e04b32bfa1bf47c0733992;hpb=23cadc8d86d40f5b1e625ae0469043fa3e8362ce;p=sbcl.git diff --git a/BUGS b/BUGS index 4860f07..0e990ce 100644 --- a/BUGS +++ b/BUGS @@ -513,6 +513,13 @@ WORKAROUND: classes). This means that at present erroneous attempts to use WITH-SLOTS and the like on classes with metaclass STRUCTURE-CLASS won't get the corresponding STYLE-WARNING. + + [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" @@ -900,7 +907,7 @@ WORKAROUND: strongly suspected problems, as of 0.8.3.10: please update this bug instead of creating new ones - localtime() - called for timezone calculations in code/time.lisp + gethostbyname, gethostbyaddr in sb-bsd-sockets 284: Thread safety: special variables There are lots of special variables in SBCL, and I feel sure that at @@ -916,15 +923,6 @@ WORKAROUND: (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 @@ -1208,101 +1206,6 @@ WORKAROUND: 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) @@ -1325,41 +1228,7 @@ WORKAROUND: 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. - -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. + c. (fixed in sbcl-0.9.15.15) 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 @@ -1402,6 +1271,11 @@ WORKAROUND: 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 @@ -1432,53 +1306,6 @@ WORKAROUND: 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 @@ -1498,6 +1325,17 @@ WORKAROUND: Expected: # 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, @@ -1544,26 +1382,6 @@ WORKAROUND: 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: @@ -1589,151 +1407,6 @@ WORKAROUND: 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: @@ -1757,59 +1430,6 @@ WORKAROUND: 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))) @@ -2043,6 +1663,8 @@ WORKAROUND: 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) @@ -2060,11 +1682,6 @@ WORKAROUND: (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 ) 'NIL) causes - (FIND-CLASS NIL) to return a #. - 395: Unicode and streams One of the remaining problems in SBCL's Unicode support is the lack of generality in certain streams. @@ -2129,5 +1746,69 @@ WORKAROUND: For some more details see comments for (define-alien-type-method (c-string :deport-gen) ...) in host-c-call.lisp. -401: "optimizer runaway on bad constant type specifiers in TYPEP" - (fixed in 0.9.12.12) +402: "DECLAIM DECLARATION does not inform the PCL code-walker" + reported by Vincent Arkesteijn: + + (declaim (declaration foo)) + (defgeneric bar (x)) + (defmethod bar (x) + (declare (foo x)) + x) + + ==> WARNING: The declaration FOO is not understood by + SB-PCL::SPLIT-DECLARATIONS. + Please put FOO on one of the lists SB-PCL::*NON-VAR-DECLARATIONS*, + SB-PCL::*VAR-DECLARATIONS-WITH-ARG*, or + SB-PCL::*VAR-DECLARATIONS-WITHOUT-ARG*. + (Assuming it is a variable declaration without argument). + +403: FORMAT/PPRINT-LOGICAL-BLOCK of CONDITIONs ignoring *PRINT-CIRCLE* + In sbcl-0.9.13.34, + (defparameter *c* + (make-condition 'simple-error + :format-control "ow... ~S" + :format-arguments '(#1=(#1#)))) + (setf *print-circle* t *print-level* 4) + (format nil "~@<~A~:@>" *c*) + gives + "ow... (((#)))" + where I (WHN) believe the correct result is "ow... #1=(#1#)", + like the result from (PRINC-TO-STRING *C*). The question of + what the correct result is is complicated by the hairy text in + the Hyperspec "22.3.5.2 Tilde Less-Than-Sign: Logical Block", + Other than the difference in its argument, ~@<...~:> is + exactly the same as ~<...~:> except that circularity detection + is not applied if ~@<...~:> is encountered at top level in a + format string. + But because the odd behavior happens even without the at-sign, + (format nil "~<~A~:@>" (list *c*)) ; => "ow... (((#)))" + and because something seemingly similar can happen even in + PPRINT-LOGICAL-BLOCK invoked directly without FORMAT, + (pprint-logical-block (*standard-output* '(some nonempty list)) + (format *standard-output* "~A" '#1=(#1#))) + (which prints "(((#)))" to *STANDARD-OUTPUT*), I don't think + that the 22.3.5.2 trickiness is fundamental to the problem. + + My guess is that the problem is related to the logic around the MODE + argument to CHECK-FOR-CIRCULARITY, but I haven't reverse-engineered + enough of the intended meaning of the different MODE values to be + confident of this. + +404: nonstandard DWIMness in LOOP with unportably-ordered clauses + In sbcl-0.9.13, the code + (loop with stack = (make-array 2 :fill-pointer 2 :initial-element t) + for length = (length stack) + while (plusp length) + for element = (vector-pop stack) + collect element) + compiles without error or warning and returns (T T). Unfortunately, + it is inconsistent with the ANSI definition of the LOOP macro, + because it mixes up VARIABLE-CLAUSEs with MAIN-CLAUSEs. Furthermore, + SBCL's interpretation of the intended meaning is only one possible, + unportable interpretation of the noncompliant code; in CLISP 2.33.2, + the code compiles with a warning + LOOP: FOR clauses should occur before the loop's main body + and then fails at runtime with + VECTOR-POP: #() has length zero + perhaps because CLISP has shuffled the clauses into an + ANSI-compliant order before proceeding.