X-Git-Url: http://repo.macrolet.net/gitweb/?a=blobdiff_plain;f=src%2Fpcl%2Fboot.lisp;h=e88a9de97317aefaf039c85b0dc1d770eae838b3;hb=1ae37c6f729950b6925275cea43546b701d8fde2;hp=bdb2f183ed425486371667af15fda63c073cb500;hpb=7e00a27796fce8eb5b0ab920dda636584a011ba2;p=sbcl.git diff --git a/src/pcl/boot.lisp b/src/pcl/boot.lisp index bdb2f18..e88a9de 100644 --- a/src/pcl/boot.lisp +++ b/src/pcl/boot.lisp @@ -190,11 +190,32 @@ bootstrapping. is not allowed inside DEFGENERIC." :format-arguments (list (cadr option)))) (push (cadr option) (initarg :declarations))) - ((:argument-precedence-order :method-combination) - (if (initarg car-option) - (duplicate-option car-option) - (setf (initarg car-option) - `',(cdr option)))) + (:method-combination + (when (initarg car-option) + (duplicate-option car-option)) + (unless (symbolp (cadr option)) + (error 'simple-program-error + :format-control "METHOD-COMBINATION name not a ~ + symbol: ~S" + :format-arguments (list (cadr option)))) + (setf (initarg car-option) + `',(cdr option))) + (:argument-precedence-order + (let* ((required (parse-lambda-list lambda-list)) + (supplied (cdr option))) + (unless (= (length required) (length supplied)) + (error 'simple-program-error + :format-control "argument count discrepancy in ~ + :ARGUMENT-PRECEDENCE-ORDER clause." + :format-arguments nil)) + (when (set-difference required supplied) + (error 'simple-program-error + :format-control "unequal sets for ~ + :ARGUMENT-PRECEDENCE-ORDER clause: ~ + ~S and ~S" + :format-arguments (list required supplied))) + (setf (initarg car-option) + `',(cdr option)))) ((:documentation :generic-function-class :method-class) (unless (proper-list-of-length-p option 2) (error "bad list length for ~S" option)) @@ -242,18 +263,18 @@ bootstrapping. :definition-source `((defgeneric ,fun-name) ,*load-pathname*) initargs)) -;;; As per section 3.4.2 of the ANSI spec, generic function lambda -;;; lists have some special limitations, which we check here. +(define-condition generic-function-lambda-list-error + (reference-condition simple-program-error) + () + (:default-initargs :references (list '(:ansi-cl :section (3 4 2))))) + (defun check-gf-lambda-list (lambda-list) (flet ((ensure (arg ok) (unless ok - (error - ;; (s/invalid/non-ANSI-conforming/ because the old PCL - ;; implementation allowed this, so people got used to - ;; it, and maybe this phrasing will help them to guess - ;; why their program which worked under PCL no longer works.) - "~@" - arg lambda-list)))) + (error 'generic-function-lambda-list-error + :format-control + "~@" + :format-arguments (list arg lambda-list))))) (multiple-value-bind (required optional restp rest keyp keys allowp auxp aux morep more-context more-count) (parse-lambda-list lambda-list) @@ -478,11 +499,11 @@ bootstrapping. env)))) (defun add-method-declarations (name qualifiers lambda-list body env) + (declare (ignore env)) (multiple-value-bind (parameters unspecialized-lambda-list specializers) (parse-specialized-lambda-list lambda-list) - (declare (ignore parameters)) (multiple-value-bind (real-body declarations documentation) - (parse-body body env) + (parse-body body) (values `(lambda ,unspecialized-lambda-list ,@(when documentation `(,documentation)) ;; (Old PCL code used a somewhat different style of @@ -587,13 +608,26 @@ bootstrapping. ;; weirdness when bootstrapping.. -- WHN 20000610 '(ignorable)) (t - ;; Otherwise, we can make Python very happy. + ;; Otherwise, we can usually make Python very happy. (let ((type (info :type :kind specializer))) (ecase type ((:primitive :defined :instance :forthcoming-defclass-type) `(type ,specializer ,parameter)) ((nil) - `(type ,(class-name (find-class specializer)) ,parameter))))))) + (let ((class (find-class specializer nil))) + (if class + `(type ,(class-name class) ,parameter) + (progn + ;; we can get here, and still not have a failure + ;; case, by doing MOP programming like (PROGN + ;; (ENSURE-CLASS 'FOO) (DEFMETHOD BAR ((X FOO)) + ;; ...)). Best to let the user know we haven't + ;; been able to extract enough information: + (style-warn + "~@" + specializer + 'parameter-specializer-declaration-in-defmethod) + '(ignorable)))))))))) (defun make-method-lambda-internal (method-lambda &optional env) (unless (and (consp method-lambda) (eq (car method-lambda) 'lambda)) @@ -601,7 +635,7 @@ bootstrapping. is not a lambda form." method-lambda)) (multiple-value-bind (real-body declarations documentation) - (parse-body (cddr method-lambda) env) + (parse-body (cddr method-lambda)) (let* ((name-decl (get-declaration '%method-name declarations)) (sll-decl (get-declaration '%method-lambda-list declarations)) (method-name (when (consp name-decl) (car name-decl))) @@ -635,8 +669,9 @@ bootstrapping. ;; it can avoid run-time type dispatch overhead, ;; which can be a huge win for Python.) ;; - ;; FIXME: Perhaps these belong in - ;; ADD-METHOD-DECLARATIONS instead of here? + ;; KLUDGE: when I tried moving these to + ;; ADD-METHOD-DECLARATIONS, things broke. No idea + ;; why. -- CSR, 2004-06-16 ,@(mapcar #'parameter-specializer-declaration-in-defmethod parameters specializers))) @@ -682,7 +717,8 @@ bootstrapping. ((eq p '&aux) (return nil)))))) (multiple-value-bind - (walked-lambda call-next-method-p closurep next-method-p-p) + (walked-lambda call-next-method-p closurep + next-method-p-p setq-p) (walk-method-lambda method-lambda required-parameters env @@ -691,7 +727,7 @@ bootstrapping. (multiple-value-bind (walked-lambda-body walked-declarations walked-documentation) - (parse-body (cddr walked-lambda) env) + (parse-body (cddr walked-lambda)) (declare (ignore walked-documentation)) (when (or next-method-p-p call-next-method-p) (setq plist (list* :needs-next-methods-p t plist))) @@ -723,6 +759,7 @@ bootstrapping. :call-next-method-p ,call-next-method-p :next-method-p-p ,next-method-p-p + :setq-p ,setq-p ;; we need to pass this along ;; so that NO-NEXT-METHOD can ;; be given a suitable METHOD @@ -770,22 +807,26 @@ bootstrapping. (defmacro bind-simple-lexical-method-macros ((method-args next-methods) &body body) `(macrolet ((call-next-method-bind (&body body) - `(let ((.next-method. (car ,',next-methods)) - (,',next-methods (cdr ,',next-methods))) - .next-method. ,',next-methods - ,@body)) + `(let ((.next-method. (car ,',next-methods)) + (,',next-methods (cdr ,',next-methods))) + .next-method. ,',next-methods + ,@body)) (call-next-method-body (method-name-declaration cnm-args) - `(if .next-method. - (funcall (if (std-instance-p .next-method.) - (method-function .next-method.) - .next-method.) ; for early methods - (or ,cnm-args ,',method-args) - ,',next-methods) - (apply #'call-no-next-method ',method-name-declaration + `(if .next-method. + (funcall (if (std-instance-p .next-method.) + (method-function .next-method.) + .next-method.) ; for early methods + (or ,cnm-args ,',method-args) + ,',next-methods) + (apply #'call-no-next-method ',method-name-declaration (or ,cnm-args ,',method-args)))) (next-method-p-body () - `(not (null .next-method.)))) - ,@body)) + `(not (null .next-method.))) + (with-rebound-original-args ((call-next-method-p setq-p) + &body body) + (declare (ignore call-next-method-p setq-p)) + `(let () ,@body))) + ,@body)) (defun call-no-next-method (method-name-declaration &rest args) (destructuring-bind (name) method-name-declaration @@ -1003,85 +1044,93 @@ bootstrapping. (defmacro bind-fast-lexical-method-macros ((args rest-arg next-method-call) &body body) - `(macrolet ((narrowed-emf (emf) - ;; INVOKE-EFFECTIVE-METHOD-FUNCTION has code in it to - ;; dispatch on the possibility that EMF might be of - ;; type FIXNUM (as an optimized representation of a - ;; slot accessor). But as far as I (WHN 2002-06-11) - ;; can tell, it's impossible for such a representation - ;; to end up as .NEXT-METHOD-CALL. By reassuring - ;; INVOKE-E-M-F that when called from this context - ;; it needn't worry about the FIXNUM case, we can - ;; keep those cases from being compiled, which is - ;; good both because it saves bytes and because it - ;; avoids annoying type mismatch compiler warnings. - ;; - ;; KLUDGE: In sbcl-0.7.4.29, the compiler's type - ;; system isn't smart enough about NOT and intersection - ;; types to benefit from a (NOT FIXNUM) declaration - ;; here. -- WHN 2002-06-12 - ;; - ;; FIXME: Might the FUNCTION type be omittable here, - ;; leaving only METHOD-CALLs? Failing that, could this - ;; be documented somehow? (It'd be nice if the types - ;; involved could be understood without solving the - ;; halting problem.) - `(the (or function method-call fast-method-call) + (let* ((all-params (append args (when rest-arg (list rest-arg)))) + (rebindings (mapcar (lambda (x) (list x x)) all-params))) + `(macrolet ((narrowed-emf (emf) + ;; INVOKE-EFFECTIVE-METHOD-FUNCTION has code in it to + ;; dispatch on the possibility that EMF might be of + ;; type FIXNUM (as an optimized representation of a + ;; slot accessor). But as far as I (WHN 2002-06-11) + ;; can tell, it's impossible for such a representation + ;; to end up as .NEXT-METHOD-CALL. By reassuring + ;; INVOKE-E-M-F that when called from this context + ;; it needn't worry about the FIXNUM case, we can + ;; keep those cases from being compiled, which is + ;; good both because it saves bytes and because it + ;; avoids annoying type mismatch compiler warnings. + ;; + ;; KLUDGE: In sbcl-0.7.4.29, the compiler's type + ;; system isn't smart enough about NOT and + ;; intersection types to benefit from a (NOT FIXNUM) + ;; declaration here. -- WHN 2002-06-12 (FIXME: maybe + ;; it is now... -- CSR, 2003-06-07) + ;; + ;; FIXME: Might the FUNCTION type be omittable here, + ;; leaving only METHOD-CALLs? Failing that, could this + ;; be documented somehow? (It'd be nice if the types + ;; involved could be understood without solving the + ;; halting problem.) + `(the (or function method-call fast-method-call) ,emf)) - (call-next-method-bind (&body body) - `(let () ,@body)) - (call-next-method-body (method-name-declaration cnm-args) - `(if ,',next-method-call - ,(locally - ;; This declaration suppresses a "deleting - ;; unreachable code" note for the following IF when - ;; REST-ARG is NIL. It is not nice for debugging - ;; SBCL itself, but at least it keeps us from - ;; annoying users. - (declare (optimize (inhibit-warnings 3))) - (if (and (null ',rest-arg) - (consp cnm-args) - (eq (car cnm-args) 'list)) - `(invoke-effective-method-function - (narrowed-emf ,',next-method-call) - nil - ,@(cdr cnm-args)) - (let ((call `(invoke-effective-method-function - (narrowed-emf ,',next-method-call) - ,',(not (null rest-arg)) - ,@',args - ,@',(when rest-arg `(,rest-arg))))) - `(if ,cnm-args - (bind-args ((,@',args - ,@',(when rest-arg - `(&rest ,rest-arg))) - ,cnm-args) - ,call) - ,call)))) - ,(locally - ;; As above, this declaration suppresses code - ;; deletion notes. - (declare (optimize (inhibit-warnings 3))) - (if (and (null ',rest-arg) - (consp cnm-args) - (eq (car cnm-args) 'list)) - `(call-no-next-method ',method-name-declaration - ,@(cdr cnm-args)) - `(call-no-next-method ',method-name-declaration - ,@',args - ,@',(when rest-arg - `(,rest-arg))))))) - (next-method-p-body () - `(not (null ,',next-method-call)))) - ,@body)) + (call-next-method-bind (&body body) + `(let () ,@body)) + (call-next-method-body (method-name-declaration cnm-args) + `(if ,',next-method-call + ,(locally + ;; This declaration suppresses a "deleting + ;; unreachable code" note for the following IF + ;; when REST-ARG is NIL. It is not nice for + ;; debugging SBCL itself, but at least it + ;; keeps us from annoying users. + (declare (optimize (inhibit-warnings 3))) + (if (and (null ',rest-arg) + (consp cnm-args) + (eq (car cnm-args) 'list)) + `(invoke-effective-method-function + (narrowed-emf ,',next-method-call) + nil + ,@(cdr cnm-args)) + (let ((call `(invoke-effective-method-function + (narrowed-emf ,',next-method-call) + ,',(not (null rest-arg)) + ,@',args + ,@',(when rest-arg `(,rest-arg))))) + `(if ,cnm-args + (bind-args ((,@',args + ,@',(when rest-arg + `(&rest ,rest-arg))) + ,cnm-args) + ,call) + ,call)))) + ,(locally + ;; As above, this declaration suppresses code + ;; deletion notes. + (declare (optimize (inhibit-warnings 3))) + (if (and (null ',rest-arg) + (consp cnm-args) + (eq (car cnm-args) 'list)) + `(call-no-next-method ',method-name-declaration + ,@(cdr cnm-args)) + `(call-no-next-method ',method-name-declaration + ,@',args + ,@',(when rest-arg + `(,rest-arg))))))) + (next-method-p-body () + `(not (null ,',next-method-call))) + (with-rebound-original-args ((cnm-p setq-p) &body body) + (if (or cnm-p setq-p) + `(let ,',rebindings + (declare (ignorable ,@',all-params)) + ,@body) + `(let () ,@body)))) + ,@body))) (defmacro bind-lexical-method-functions - ((&key call-next-method-p next-method-p-p + ((&key call-next-method-p next-method-p-p setq-p closurep applyp method-name-declaration) &body body) (cond ((and (null call-next-method-p) (null next-method-p-p) - (null closurep) - (null applyp)) + (null closurep) (null applyp) (null setq-p)) `(let () ,@body)) (t `(call-next-method-bind @@ -1092,8 +1141,9 @@ bootstrapping. cnm-args)))) ,@(and next-method-p-p '((next-method-p () - (next-method-p-body))))) - ,@body))))) + (next-method-p-body))))) + (with-rebound-original-args (,call-next-method-p ,setq-p) + ,@body)))))) (defmacro bind-args ((lambda-list args) &body body) (let ((args-tail '.args-tail.) @@ -1160,8 +1210,14 @@ bootstrapping. (aux `(,var)))))) (let ((bindings (mapcan #'process-var lambda-list))) `(let* ((,args-tail ,args) - ,@bindings) - (declare (ignorable ,args-tail)) + ,@bindings + (.dummy0. + ,@(when (eq state 'optional) + `((unless (null ,args-tail) + (error 'simple-program-error + :format-control "surplus arguments: ~S" + :format-arguments (list ,args-tail))))))) + (declare (ignorable ,args-tail .dummy0.)) ,@body))))) (defun get-key-arg-tail (keyword list) @@ -1178,8 +1234,9 @@ bootstrapping. ; should be in the method definition (closurep nil) ; flag indicating that #'CALL-NEXT-METHOD ; was seen in the body of a method - (next-method-p-p nil)) ; flag indicating that NEXT-METHOD-P + (next-method-p-p nil) ; flag indicating that NEXT-METHOD-P ; should be in the method definition + (setq-p nil)) (flet ((walk-function (form context env) (cond ((not (eq context :eval)) form) ;; FIXME: Jumping to a conclusion from the way it's used @@ -1194,6 +1251,9 @@ bootstrapping. ((eq (car form) 'next-method-p) (setq next-method-p-p t) form) + ((eq (car form) 'setq) + (setq setq-p t) + form) ((and (eq (car form) 'function) (cond ((eq (cadr form) 'call-next-method) (setq call-next-method-p t) @@ -1230,7 +1290,8 @@ bootstrapping. (values walked-lambda call-next-method-p closurep - next-method-p-p))))) + next-method-p-p + setq-p))))) (defun generic-function-name-p (name) (and (legal-fun-name-p name) @@ -1310,6 +1371,7 @@ bootstrapping. (fboundp gf-spec)) (let* ((gf (fdefinition gf-spec)) (method (and (generic-function-p gf) + (generic-function-methods gf) (find-method gf qualifiers (parse-specializers specializers) @@ -1470,8 +1532,6 @@ bootstrapping. *)))) (defun defgeneric-declaration (spec lambda-list) - (when (consp spec) - (setq spec (get-setf-fun-name (cadr spec)))) `(ftype ,(ftype-declaration-from-lambda-list lambda-list spec) ,spec)) ;;;; early generic function support @@ -1571,7 +1631,7 @@ bootstrapping. ;;; Keep pages clean by not setting if the value is already the same. (defmacro esetf (pos val) - (let ((valsym (gensym "value"))) + (with-unique-names (valsym) `(let ((,valsym ,val)) (unless (equal ,pos ,valsym) (setf ,pos ,valsym))))) @@ -1707,27 +1767,21 @@ bootstrapping. (generic-function-name gf) (!early-gf-name gf)))) (esetf (gf-precompute-dfun-and-emf-p arg-info) - (let* ((sym (if (atom name) name (cadr name))) - (pkg-list (cons *pcl-package* - (package-use-list *pcl-package*)))) - ;; FIXME: given the presence of generalized function - ;; names, this test is broken. A little - ;; reverse-engineering suggests that this was intended - ;; to prevent precompilation of things on some - ;; PCL-internal automatically-constructed functions - ;; like the old "~A~A standard class ~A reader" - ;; functions. When the CADR of SB-PCL::SLOT-ACCESSOR - ;; generalized functions was *, this test returned T, - ;; not NIL, and an error was signalled in - ;; MAKE-ACCESSOR-TABLE for (DEFUN FOO (X) (SLOT-VALUE X - ;; 'ASLDKJ)). Whether the right thing to do is to fix - ;; MAKE-ACCESSOR-TABLE so that it can work in the - ;; presence of slot names that have no classes, or to - ;; restore this test to something more obvious, I don't - ;; know. -- CSR, 2003-02-14 - (and sym (symbolp sym) - (not (null (memq (symbol-package sym) pkg-list))) - (not (find #\space (symbol-name sym)))))))) + (cond + ((and (consp name) + (member (car name) + *internal-pcl-generalized-fun-name-symbols*)) + nil) + (t (let* ((symbol (fun-name-block-name name)) + (package (symbol-package symbol))) + (and (or (eq package *pcl-package*) + (memq package (package-use-list *pcl-package*))) + ;; FIXME: this test will eventually be + ;; superseded by the *internal-pcl...* test, + ;; above. While we are in a process of + ;; transition, however, it should probably + ;; remain. + (not (find #\Space (symbol-name symbol)))))))))) (esetf (gf-info-fast-mf-p arg-info) (or (not (eq *boot-state* 'complete)) (let* ((method-class (generic-function-method-class gf)) @@ -1760,6 +1814,8 @@ bootstrapping. &allow-other-keys) (declare (ignore keys)) (cond ((and existing (early-gf-p existing)) + (when lambda-list-p + (set-arg-info existing :lambda-list lambda-list)) existing) ((assoc spec *!generic-function-fixups* :test #'equal) (if existing @@ -1859,7 +1915,7 @@ bootstrapping. (method-lambda-list method))) (k (member '&key ll))) (if k - (append (ldiff ll (cdr k)) '(&allow-other-keys)) + (ldiff ll (cdr k)) ll)))) (arg-info-lambda-list arg-info)))) @@ -2278,19 +2334,38 @@ bootstrapping. (declare (ignore ignore1 ignore2 ignore3)) required-parameters)) -(defun parse-specialized-lambda-list (arglist &optional post-keyword) - ;;(declare (values parameters lambda-list specializers required-parameters)) +(define-condition specialized-lambda-list-error + (reference-condition simple-program-error) + () + (:default-initargs :references (list '(:ansi-cl :section (3 4 3))))) + +(defun parse-specialized-lambda-list + (arglist + &optional supplied-keywords (allowed-keywords '(&optional &rest &key &aux)) + &aux (specialized-lambda-list-keywords + '(&optional &rest &key &allow-other-keys &aux))) (let ((arg (car arglist))) (cond ((null arglist) (values nil nil nil nil)) ((eq arg '&aux) - (values nil arglist nil)) + (values nil arglist nil nil)) ((memq arg lambda-list-keywords) - (unless (memq arg '(&optional &rest &key &allow-other-keys &aux)) - ;; Now, since we try to conform to ANSI, non-standard - ;; lambda-list-keywords should be treated as errors. - (error 'simple-program-error - :format-control "unrecognized lambda-list keyword ~S ~ - in arglist.~%" + ;; non-standard lambda-list-keywords are errors. + (unless (memq arg specialized-lambda-list-keywords) + (error 'specialized-lambda-list-error + :format-control "unknown specialized-lambda-list ~ + keyword ~S~%" + :format-arguments (list arg))) + ;; no multiple &rest x &rest bla specifying + (when (memq arg supplied-keywords) + (error 'specialized-lambda-list-error + :format-control "multiple occurrence of ~ + specialized-lambda-list keyword ~S~%" + :format-arguments (list arg))) + ;; And no placing &key in front of &optional, either. + (unless (memq arg allowed-keywords) + (error 'specialized-lambda-list-error + :format-control "misplaced specialized-lambda-list ~ + keyword ~S~%" :format-arguments (list arg))) ;; When we are at a lambda-list keyword, the parameters ;; don't include the lambda-list keyword; the lambda-list @@ -2298,22 +2373,34 @@ bootstrapping. ;; specializers are allowed to follow the lambda-list ;; keywords (at least for now). (multiple-value-bind (parameters lambda-list) - (parse-specialized-lambda-list (cdr arglist) t) - (when (eq arg '&rest) - ;; check, if &rest is followed by a var ... - (when (or (null lambda-list) - (memq (car lambda-list) lambda-list-keywords)) - (error "Error in lambda-list:~%~ - After &REST, a DEFMETHOD lambda-list ~ - must be followed by at least one variable."))) + (parse-specialized-lambda-list (cdr arglist) + (cons arg supplied-keywords) + (if (eq arg '&key) + (cons '&allow-other-keys + (cdr (member arg allowed-keywords))) + (cdr (member arg allowed-keywords)))) + (when (and (eq arg '&rest) + (or (null lambda-list) + (memq (car lambda-list) + specialized-lambda-list-keywords) + (not (or (null (cadr lambda-list)) + (memq (cadr lambda-list) + specialized-lambda-list-keywords))))) + (error 'specialized-lambda-list-error + :format-control + "in a specialized-lambda-list, excactly one ~ + variable must follow &REST.~%" + :format-arguments nil)) (values parameters (cons arg lambda-list) () ()))) - (post-keyword + (supplied-keywords ;; After a lambda-list keyword there can be no specializers. (multiple-value-bind (parameters lambda-list) - (parse-specialized-lambda-list (cdr arglist) t) + (parse-specialized-lambda-list (cdr arglist) + supplied-keywords + allowed-keywords) (values (cons (if (listp arg) (car arg) arg) parameters) (cons arg lambda-list) ()