1 ;;;; This software is part of the SBCL system. See the README file for
4 ;;;; This software is derived from software originally released by Xerox
5 ;;;; Corporation. Copyright and release statements follow. Later modifications
6 ;;;; to the software are in the public domain and are provided with
7 ;;;; absolutely no warranty. See the COPYING and CREDITS files for more
10 ;;;; copyright information from original PCL sources:
12 ;;;; Copyright (c) 1985, 1986, 1987, 1988, 1989, 1990 Xerox Corporation.
13 ;;;; All rights reserved.
15 ;;;; Use and copying of this software and preparation of derivative works based
16 ;;;; upon this software are permitted. Any distribution of this software or
17 ;;;; derivative works must comply with all applicable United States export
20 ;;;; This software is made available AS IS, and Xerox Corporation makes no
21 ;;;; warranty about the software, its performance or its conformity to any
28 ;;; Methods themselves are simple inanimate objects. Most properties of
29 ;;; methods are immutable, methods cannot be reinitialized. The following
30 ;;; properties of methods can be changed:
31 ;;; METHOD-GENERIC-FUNCTION
35 ;;; Error checking is done in before methods. Because of the simplicity of
36 ;;; standard method objects the standard primary method can fill the slots.
38 ;;; Methods are not reinitializable.
40 (define-condition metaobject-initialization-violation
41 (reference-condition simple-error
)
44 (macrolet ((def (name args control
)
45 `(defmethod ,name
,args
46 (declare (ignore initargs
))
47 (error 'metaobject-initialization-violation
48 :format-control
,(format nil
"~@<~A~@:>" control
)
49 :format-arguments
(list ',name
)
50 :references
(list '(:amop
:initialization method
))))))
51 (def reinitialize-instance
((method method
) &rest initargs
)
52 "Method objects cannot be redefined by ~S.")
53 (def change-class
((method method
) new
&rest initargs
)
54 "Method objects cannot be redefined by ~S.")
55 ;; NEW being a subclass of method is dealt with in the general
56 ;; method of CHANGE-CLASS
57 (def update-instance-for-redefined-class
((method method
) added discarded
59 "No behaviour specified for ~S on method objects.")
60 (def update-instance-for-different-class
(old (new method
) &rest initargs
)
61 "No behaviour specified for ~S on method objects.")
62 (def update-instance-for-different-class
((old method
) new
&rest initargs
)
63 "No behaviour specified for ~S on method objects."))
65 (define-condition invalid-method-initarg
(simple-program-error)
66 ((method :initarg
:method
:reader invalid-method-initarg-method
))
69 (format s
"~@<In initialization of ~S:~2I~_~?~@:>"
70 (invalid-method-initarg-method c
)
71 (simple-condition-format-control c
)
72 (simple-condition-format-arguments c
)))))
74 (defun invalid-method-initarg (method format-control
&rest args
)
75 (error 'invalid-method-initarg
:method method
76 :format-control format-control
:format-arguments args
))
78 (defun check-documentation (method doc
)
79 (unless (or (null doc
) (stringp doc
))
80 (invalid-method-initarg method
"~@<~S of ~S is neither ~S nor a ~S.~@:>"
81 :documentation doc
'null
'string
)))
82 (defun check-lambda-list (method ll
)
85 (defun check-method-function (method fun
)
86 (unless (functionp fun
)
87 (invalid-method-initarg method
"~@<~S of ~S is not a ~S.~@:>"
88 :function fun
'function
)))
90 (defun check-qualifiers (method qualifiers
)
91 (flet ((improper-list ()
92 (invalid-method-initarg method
93 "~@<~S of ~S is an improper list.~@:>"
94 :qualifiers qualifiers
)))
95 (dolist-carefully (q qualifiers improper-list
)
96 (unless (and q
(atom q
))
97 (invalid-method-initarg method
98 "~@<~S, in ~S ~S, is not a non-~S atom.~@:>"
99 q
:qualifiers qualifiers
'null
)))))
101 (defun check-slot-name (method name
)
102 (unless (symbolp name
)
103 (invalid-method-initarg "~@<~S of ~S is not a ~S.~@:>"
104 :slot-name name
'symbol
)))
106 (defun check-specializers (method specializers
)
107 (flet ((improper-list ()
108 (invalid-method-initarg method
109 "~@<~S of ~S is an improper list.~@:>"
110 :specializers specializers
)))
111 (dolist-carefully (s specializers improper-list
)
112 (unless (specializerp s
)
113 (invalid-method-initarg method
114 "~@<~S, in ~S ~S, is not a ~S.~@:>"
115 s
:specializers specializers
'specializer
)))
116 ;; KLUDGE: ANSI says that it's not valid to have methods
117 ;; specializing on classes which are "not defined", leaving
118 ;; unclear what the definedness of a class is; AMOP suggests that
119 ;; forward-referenced-classes, since they have proper names and
120 ;; all, are at least worthy of some level of definition. We allow
121 ;; methods specialized on forward-referenced-classes, but it's
122 ;; non-portable and potentially dubious, so
123 (let ((frcs (remove-if-not #'forward-referenced-class-p specializers
)))
125 (style-warn "~@<Defining a method using ~
126 ~V[~;~1{~S~}~;~1{~S and ~S~}~:;~{~#[~;and ~]~S~^, ~}~] ~
127 as ~2:*~V[~;a specializer~:;specializers~].~@:>"
128 (length frcs
) frcs
)))))
130 (defmethod shared-initialize :before
131 ((method standard-method
) slot-names
&key
132 qualifiers lambda-list specializers function documentation
)
133 (declare (ignore slot-names
))
134 ;; FIXME: it's not clear to me (CSR, 2006-08-09) why methods get
135 ;; this extra paranoia and nothing else does; either everything
136 ;; should be aggressively checking initargs, or nothing much should.
137 ;; In either case, it would probably be better to have :type
138 ;; declarations in slots, which would then give a suitable type
139 ;; error (if we implement type-checking for slots...) rather than
140 ;; this hand-crafted thing.
141 (check-qualifiers method qualifiers
)
142 (check-lambda-list method lambda-list
)
143 (check-specializers method specializers
)
144 (check-method-function method function
)
145 (check-documentation method documentation
))
147 (defmethod shared-initialize :before
148 ((method standard-accessor-method
) slot-names
&key
149 slot-name slot-definition
)
150 (declare (ignore slot-names
))
151 (unless slot-definition
152 (check-slot-name method slot-name
)))
154 (defmethod shared-initialize :after
((method standard-method
) slot-names
155 &rest initargs
&key
((method-cell method-cell
)))
156 (declare (ignore slot-names method-cell
))
157 (initialize-method-function initargs method
))
159 (defvar *the-class-generic-function
*
160 (find-class 'generic-function
))
161 (defvar *the-class-standard-generic-function
*
162 (find-class 'standard-generic-function
))
164 (defmethod shared-initialize :before
165 ((generic-function standard-generic-function
)
167 &key
(name nil namep
)
168 (lambda-list () lambda-list-p
)
169 argument-precedence-order
172 (method-class nil method-class-supplied-p
)
173 (method-combination nil method-combination-supplied-p
))
174 (declare (ignore slot-names
175 declarations argument-precedence-order documentation
176 lambda-list lambda-list-p
))
179 (set-fun-name generic-function name
))
181 (flet ((initarg-error (initarg value string
)
182 (error "when initializing the generic function ~S:~%~
183 The ~S initialization argument was: ~A.~%~
185 generic-function initarg value string
)))
186 (cond (method-class-supplied-p
187 (when (symbolp method-class
)
188 (setq method-class
(find-class method-class
)))
189 (unless (and (classp method-class
)
190 (*subtypep
(class-eq-specializer method-class
)
192 (initarg-error :method-class
194 "a subclass of the class METHOD"))
195 (setf (slot-value generic-function
'method-class
) method-class
))
196 ((slot-boundp generic-function
'method-class
))
198 (initarg-error :method-class
200 "a subclass of the class METHOD")))
201 (cond (method-combination-supplied-p
202 (unless (method-combination-p method-combination
)
203 (initarg-error :method-combination
205 "a method combination object")))
206 ((slot-boundp generic-function
'%method-combination
))
208 (initarg-error :method-combination
210 "a method combination object")))))
212 (defun find-generic-function (name &optional
(errorp t
))
213 (let ((fun (and (fboundp name
) (fdefinition name
))))
215 ((and fun
(typep fun
'generic-function
)) fun
)
216 (errorp (error "No generic function named ~S." name
))
219 (defun real-add-named-method (generic-function-name qualifiers
220 specializers lambda-list
&rest other-initargs
)
221 (unless (and (fboundp generic-function-name
)
222 (typep (fdefinition generic-function-name
) 'generic-function
))
223 (warn 'implicit-generic-function-warning
:name generic-function-name
))
224 (let* ((existing-gf (find-generic-function generic-function-name nil
))
227 (ensure-generic-function
228 generic-function-name
229 :generic-function-class
(class-of existing-gf
))
230 (ensure-generic-function generic-function-name
)))
231 (proto (method-prototype-for-gf generic-function-name
)))
232 ;; FIXME: Destructive modification of &REST list.
233 (setf (getf (getf other-initargs
'plist
) :name
)
234 (make-method-spec generic-function qualifiers specializers
))
235 (let ((new (apply #'make-instance
(class-of proto
)
236 :qualifiers qualifiers
:specializers specializers
237 :lambda-list lambda-list other-initargs
)))
238 (add-method generic-function new
)
241 (define-condition find-method-length-mismatch
242 (reference-condition simple-error
)
244 (:default-initargs
:references
(list '(:ansi-cl
:function find-method
))))
246 (defun real-get-method (generic-function qualifiers specializers
248 always-check-specializers
)
249 (let ((lspec (length specializers
))
250 (methods (generic-function-methods generic-function
)))
251 (when (or methods always-check-specializers
)
252 (let ((nreq (length (arg-info-metatypes (gf-arg-info
253 generic-function
)))))
254 ;; Since we internally bypass FIND-METHOD by using GET-METHOD
255 ;; instead we need to to this here or users may get hit by a
256 ;; failed AVER instead of a sensible error message.
257 (when (/= lspec nreq
)
259 'find-method-length-mismatch
261 "~@<The generic function ~S takes ~D required argument~:P; ~
262 was asked to find a method with specializers ~S~@:>"
263 :format-arguments
(list generic-function nreq specializers
)))))
265 (dolist (method methods
)
266 (let ((mspecializers (method-specializers method
)))
267 (aver (= lspec
(length mspecializers
)))
268 (when (and (equal qualifiers
(safe-method-qualifiers method
))
269 (every #'same-specializer-p specializers
270 (method-specializers method
)))
275 (error "~@<There is no method on ~S with ~
276 ~:[no qualifiers~;~:*qualifiers ~S~] ~
277 and specializers ~S.~@:>"
278 generic-function qualifiers specializers
))))))
280 (defmethod find-method ((generic-function standard-generic-function
)
281 qualifiers specializers
&optional
(errorp t
))
282 ;; ANSI about FIND-METHOD: "The specializers argument contains the
283 ;; parameter specializers for the method. It must correspond in
284 ;; length to the number of required arguments of the generic
285 ;; function, or an error is signaled."
287 ;; This error checking is done by REAL-GET-METHOD.
289 generic-function qualifiers
290 ;; ANSI for FIND-METHOD seems to imply that in fact specializers
291 ;; should always be passed in parsed form instead of being parsed
292 ;; at this point. Since there's no ANSI-blessed way of getting an
293 ;; EQL specializer, that seems unnecessarily painful, so we are
294 ;; nice to our users. -- CSR, 2007-06-01
295 (parse-specializers generic-function specializers
) errorp t
))
297 ;;; Compute various information about a generic-function's arglist by looking
298 ;;; at the argument lists of the methods. The hair for trying not to use
299 ;;; &REST arguments lives here.
300 ;;; The values returned are:
301 ;;; number-of-required-arguments
302 ;;; the number of required arguments to this generic-function's
303 ;;; discriminating function
305 ;;; whether or not this generic-function's discriminating
306 ;;; function takes an &rest argument.
307 ;;; specialized-argument-positions
308 ;;; a list of the positions of the arguments this generic-function
309 ;;; specializes (e.g. for a classical generic-function this is the
311 (defmethod compute-discriminating-function-arglist-info
312 ((generic-function standard-generic-function
))
313 ;;(declare (values number-of-required-arguments &rest-argument-p
314 ;; specialized-argument-postions))
315 (let ((number-required nil
)
317 (specialized-positions ())
318 (methods (generic-function-methods generic-function
)))
319 (dolist (method methods
)
320 (multiple-value-setq (number-required restp specialized-positions
)
321 (compute-discriminating-function-arglist-info-internal
322 generic-function method number-required restp specialized-positions
)))
323 (values number-required restp
(sort specialized-positions
#'<))))
325 (defun compute-discriminating-function-arglist-info-internal
326 (generic-function method number-of-requireds restp
327 specialized-argument-positions
)
328 (declare (ignore generic-function
)
329 (type (or null fixnum
) number-of-requireds
))
331 (declare (fixnum requireds
))
332 ;; Go through this methods arguments seeing how many are required,
333 ;; and whether there is an &rest argument.
334 (dolist (arg (method-lambda-list method
))
335 (cond ((eq arg
'&aux
) (return))
336 ((memq arg
'(&optional
&rest
&key
))
337 (return (setq restp t
)))
338 ((memq arg lambda-list-keywords
))
339 (t (incf requireds
))))
340 ;; Now go through this method's type specifiers to see which
341 ;; argument positions are type specified. Treat T specially
342 ;; in the usual sort of way. For efficiency don't bother to
343 ;; keep specialized-argument-positions sorted, rather depend
344 ;; on our caller to do that.
346 (dolist (type-spec (method-specializers method
))
347 (unless (eq type-spec
*the-class-t
*)
348 (pushnew pos specialized-argument-positions
:test
#'eq
))
350 ;; Finally merge the values for this method into the values
351 ;; for the exisiting methods and return them. Note that if
352 ;; num-of-requireds is NIL it means this is the first method
353 ;; and we depend on that.
354 (values (min (or number-of-requireds requireds
) requireds
)
356 (and number-of-requireds
(/= number-of-requireds requireds
)))
357 specialized-argument-positions
)))
359 (defun make-discriminating-function-arglist (number-required-arguments restp
)
360 (nconc (let ((args nil
))
361 (dotimes (i number-required-arguments
)
362 (push (format-symbol *package
* ;; ! is this right?
363 "Discriminating Function Arg ~D"
368 `(&rest
,(format-symbol *package
*
369 "Discriminating Function &rest Arg")))))
371 (defmethod generic-function-argument-precedence-order
372 ((gf standard-generic-function
))
373 (aver (eq *boot-state
* 'complete
))
374 (loop with arg-info
= (gf-arg-info gf
)
375 with lambda-list
= (arg-info-lambda-list arg-info
)
376 for argument-position in
(arg-info-precedence arg-info
)
377 collect
(nth argument-position lambda-list
)))
379 (defmethod generic-function-lambda-list ((gf generic-function
))
382 (defmethod gf-fast-method-function-p ((gf standard-generic-function
))
383 (gf-info-fast-mf-p (slot-value gf
'arg-info
)))
385 (defmethod initialize-instance :after
((gf standard-generic-function
)
386 &key
(lambda-list nil lambda-list-p
)
387 argument-precedence-order
)
388 (with-slots (arg-info) gf
391 :lambda-list lambda-list
392 :argument-precedence-order argument-precedence-order
)
394 (when (arg-info-valid-p arg-info
)
397 (defmethod reinitialize-instance :around
398 ((gf standard-generic-function
) &rest args
&key
399 (lambda-list nil lambda-list-p
) (argument-precedence-order nil apo-p
))
400 (let ((old-mc (generic-function-method-combination gf
)))
401 (prog1 (call-next-method)
402 ;; KLUDGE: EQ is too strong a test.
403 (unless (eq old-mc
(generic-function-method-combination gf
))
404 (flush-effective-method-cache gf
))
406 ((and lambda-list-p apo-p
)
408 :lambda-list lambda-list
409 :argument-precedence-order argument-precedence-order
))
410 (lambda-list-p (set-arg-info gf
:lambda-list lambda-list
))
411 (t (set-arg-info gf
)))
412 (when (arg-info-valid-p (gf-arg-info gf
))
414 (map-dependents gf
(lambda (dependent)
415 (apply #'update-dependent gf dependent args
))))))
417 (declaim (special *lazy-dfun-compute-p
*))
419 (defun set-methods (gf methods
)
420 (setf (generic-function-methods gf
) nil
)
421 (loop (when (null methods
) (return gf
))
422 (real-add-method gf
(pop methods
) methods
)))
424 (define-condition new-value-specialization
(reference-condition error
)
425 ((%method
:initarg
:method
:reader new-value-specialization-method
))
428 (format s
"~@<Cannot add method ~S to ~S, as it specializes the ~
429 new-value argument.~@:>"
430 (new-value-specialization-method c
)
431 #'(setf slot-value-using-class
))))
432 (:default-initargs
:references
433 (list '(:sbcl
:node
"Metaobject Protocol")
434 '(:amop
:generic-function
(setf slot-value-using-class
)))))
436 (defgeneric values-for-add-method
(gf method
)
437 (:method
((gf standard-generic-function
) (method standard-method
))
438 ;; KLUDGE: Just a single generic dispatch, and everything else
439 ;; comes from permutation vectors. Would be nicer to define
440 ;; REAL-ADD-METHOD with a proper method so that we could efficiently
441 ;; use SLOT-VALUE there.
443 ;; Optimization note: REAL-ADD-METHOD has a lot of O(N) stuff in it (as
444 ;; does PCL as a whole). It should not be too hard to internally store
445 ;; many of the things we now keep in lists as either purely functional
446 ;; O(log N) sets, or --if we don't mind the memory cost-- using
447 ;; specialized hash-tables: most things are used to answer questions about
448 ;; set-membership, not ordering.
449 (values (slot-value gf
'%lock
)
450 (slot-value method
'qualifiers
)
451 (slot-value method
'specializers
)
452 (slot-value method
'lambda-list
)
453 (slot-value method
'%generic-function
)
454 (slot-value gf
'name
))))
456 (define-condition print-object-stream-specializer
(reference-condition simple-warning
)
459 :references
(list '(:ansi-cl
:function print-object
))
460 :format-control
"~@<Specializing on the second argument to ~S has ~
461 unportable effects, and also interferes with ~
462 precomputation of print functions for exceptional ~
464 :format-arguments
(list 'print-object
)))
466 (defun real-add-method (generic-function method
&optional skip-dfun-update-p
)
467 (flet ((similar-lambda-lists-p (old-method new-lambda-list
)
468 (multiple-value-bind (a-nreq a-nopt a-keyp a-restp
)
469 (analyze-lambda-list (method-lambda-list old-method
))
470 (multiple-value-bind (b-nreq b-nopt b-keyp b-restp
)
471 (analyze-lambda-list new-lambda-list
)
472 (and (= a-nreq b-nreq
)
474 (eq (or a-keyp a-restp
)
475 (or b-keyp b-restp
)))))))
476 (multiple-value-bind (lock qualifiers specializers new-lambda-list
478 (values-for-add-method generic-function method
)
480 (error "~@<The method ~S is already part of the generic ~
481 function ~S; it can't be added to another generic ~
482 function until it is removed from the first one.~@:>"
484 (when (and (eq name
'print-object
) (not (eq (second specializers
) *the-class-t
*)))
485 (warn 'print-object-stream-specializer
))
487 ;; System lock because interrupts need to be disabled as
488 ;; well: it would be bad to unwind and leave the gf in an
489 ;; inconsistent state.
490 (sb-thread::with-recursive-system-spinlock
(lock)
491 (let ((existing (get-method generic-function
496 ;; If there is already a method like this one then we must get
497 ;; rid of it before proceeding. Note that we call the generic
498 ;; function REMOVE-METHOD to remove it rather than doing it in
499 ;; some internal way.
500 (when (and existing
(similar-lambda-lists-p existing new-lambda-list
))
501 (remove-method generic-function existing
))
503 ;; KLUDGE: We have a special case here, as we disallow
504 ;; specializations of the NEW-VALUE argument to (SETF
505 ;; SLOT-VALUE-USING-CLASS). GET-ACCESSOR-METHOD-FUNCTION is
506 ;; the optimizing function here: it precomputes the effective
507 ;; method, assuming that there is no dispatch to be done on
508 ;; the new-value argument.
509 (when (and (eq generic-function
#'(setf slot-value-using-class
))
510 (not (eq *the-class-t
* (first specializers
))))
511 (error 'new-value-specialization
:method method
))
513 (setf (method-generic-function method
) generic-function
)
514 (pushnew method
(generic-function-methods generic-function
) :test
#'eq
)
515 (dolist (specializer specializers
)
516 (add-direct-method specializer method
))
518 ;; KLUDGE: SET-ARG-INFO contains the error-detecting logic for
519 ;; detecting attempts to add methods with incongruent lambda
520 ;; lists. However, according to Gerd Moellmann on cmucl-imp,
521 ;; it also depends on the new method already having been added
522 ;; to the generic function. Therefore, we need to remove it
524 (let ((remove-again-p t
))
527 (set-arg-info generic-function
:new-method method
)
528 (setq remove-again-p nil
))
530 (remove-method generic-function method
))))
532 ;; KLUDGE II: ANSI saith that it is not an error to add a
533 ;; method with invalid qualifiers to a generic function of the
534 ;; wrong kind; it's only an error at generic function
535 ;; invocation time; I dunno what the rationale was, and it
536 ;; sucks. Nevertheless, it's probably a programmer error, so
537 ;; let's warn anyway. -- CSR, 2003-08-20
538 (let ((mc (generic-function-method-combination generic-functioN
)))
540 ((eq mc
*standard-method-combination
*)
541 (when (and qualifiers
543 (not (memq (car qualifiers
)
544 '(:around
:before
:after
)))))
545 (warn "~@<Invalid qualifiers for standard method ~
546 combination in method ~S:~2I~_~S.~@:>"
548 ((short-method-combination-p mc
)
549 (let ((mc-name (method-combination-type-name mc
)))
550 (when (or (null qualifiers
)
552 (and (neq (car qualifiers
) :around
)
553 (neq (car qualifiers
) mc-name
)))
554 (warn "~@<Invalid qualifiers for ~S method combination ~
555 in method ~S:~2I~_~S.~@:>"
556 mc-name method qualifiers
))))))
558 (unless skip-dfun-update-p
559 (update-ctors 'add-method
560 :generic-function generic-function
562 (update-dfun generic-function
))
563 (map-dependents generic-function
565 (update-dependent generic-function
566 dep
'add-method method
)))))
567 (serious-condition (c)
571 (defun real-remove-method (generic-function method
)
572 (when (eq generic-function
(method-generic-function method
))
573 (let ((lock (gf-lock generic-function
)))
574 ;; System lock because interrupts need to be disabled as well:
575 ;; it would be bad to unwind and leave the gf in an inconsistent
577 (sb-thread::with-recursive-system-spinlock
(lock)
578 (let* ((specializers (method-specializers method
))
579 (methods (generic-function-methods generic-function
))
580 (new-methods (remove method methods
)))
581 (setf (method-generic-function method
) nil
582 (generic-function-methods generic-function
) new-methods
)
583 (dolist (specializer (method-specializers method
))
584 (remove-direct-method specializer method
))
585 (set-arg-info generic-function
)
586 (update-ctors 'remove-method
587 :generic-function generic-function
589 (update-dfun generic-function
)
590 (map-dependents generic-function
592 (update-dependent generic-function
593 dep
'remove-method method
)))))))
596 (defun compute-applicable-methods-function (generic-function arguments
)
597 (values (compute-applicable-methods-using-types
599 (types-from-args generic-function arguments
'eql
))))
601 (defmethod compute-applicable-methods
602 ((generic-function generic-function
) arguments
)
603 (values (compute-applicable-methods-using-types
605 (types-from-args generic-function arguments
'eql
))))
607 (defmethod compute-applicable-methods-using-classes
608 ((generic-function generic-function
) classes
)
609 (compute-applicable-methods-using-types
611 (types-from-args generic-function classes
'class-eq
)))
613 (defun proclaim-incompatible-superclasses (classes)
614 (setq classes
(mapcar (lambda (class)
619 (dolist (class classes
)
620 (dolist (other-class classes
)
621 (unless (eq class other-class
)
622 (pushnew other-class
(class-incompatible-superclass-list class
) :test
#'eq
)))))
624 (defun superclasses-compatible-p (class1 class2
)
625 (let ((cpl1 (cpl-or-nil class1
))
626 (cpl2 (cpl-or-nil class2
)))
628 (dolist (ic (class-incompatible-superclass-list sc1
))
630 (return-from superclasses-compatible-p nil
))))))
633 #'proclaim-incompatible-superclasses
634 '(;; superclass class
635 (built-in-class std-class structure-class
) ; direct subclasses of pcl-class
636 (standard-class funcallable-standard-class
)
637 ;; superclass metaobject
638 (class eql-specializer class-eq-specializer method method-combination
639 generic-function slot-definition
)
640 ;; metaclass built-in-class
641 (number sequence character
; direct subclasses of t, but not array
642 standard-object structure-object
) ; or symbol
643 (number array character symbol
; direct subclasses of t, but not
644 standard-object structure-object
) ; sequence
645 (complex float rational
) ; direct subclasses of number
646 (integer ratio
) ; direct subclasses of rational
647 (list vector
) ; direct subclasses of sequence
648 (cons null
) ; direct subclasses of list
649 (string bit-vector
) ; direct subclasses of vector
652 (defmethod same-specializer-p ((specl1 specializer
) (specl2 specializer
))
655 (defmethod same-specializer-p ((specl1 class
) (specl2 class
))
658 (defmethod specializer-class ((specializer class
))
661 (defmethod same-specializer-p ((specl1 class-eq-specializer
)
662 (specl2 class-eq-specializer
))
663 (eq (specializer-class specl1
) (specializer-class specl2
)))
665 (defmethod same-specializer-p ((specl1 eql-specializer
)
666 (specl2 eql-specializer
))
667 (eq (specializer-object specl1
) (specializer-object specl2
)))
669 (defmethod specializer-class ((specializer eql-specializer
))
670 (class-of (slot-value specializer
'object
)))
672 (defun specializer-class-or-nil (specializer)
673 (and (standard-specializer-p specializer
)
674 (specializer-class specializer
)))
676 (defun error-need-at-least-n-args (function n
)
677 (error 'simple-program-error
678 :format-control
"~@<The function ~2I~_~S ~I~_requires ~
679 at least ~W argument~:P.~:>"
680 :format-arguments
(list function n
)))
682 (defun types-from-args (generic-function arguments
&optional type-modifier
)
683 (multiple-value-bind (nreq applyp metatypes nkeys arg-info
)
684 (get-generic-fun-info generic-function
)
685 (declare (ignore applyp metatypes nkeys
))
686 (let ((types-rev nil
))
687 (dotimes-fixnum (i nreq
)
690 (error-need-at-least-n-args (generic-function-name generic-function
)
692 (let ((arg (pop arguments
)))
693 (push (if type-modifier
`(,type-modifier
,arg
) arg
) types-rev
)))
694 (values (nreverse types-rev
) arg-info
))))
696 (defun get-wrappers-from-classes (nkeys wrappers classes metatypes
)
697 (let* ((w wrappers
) (w-tail w
) (mt-tail metatypes
))
698 (dolist (class (if (listp classes
) classes
(list classes
)))
699 (unless (eq t
(car mt-tail
))
700 (let ((c-w (class-wrapper class
)))
701 (unless c-w
(return-from get-wrappers-from-classes nil
))
704 (setf (car w-tail
) c-w
705 w-tail
(cdr w-tail
)))))
706 (setq mt-tail
(cdr mt-tail
)))
709 (defun sdfun-for-caching (gf classes
)
710 (let ((types (mapcar #'class-eq-type classes
)))
711 (multiple-value-bind (methods all-applicable-and-sorted-p
)
712 (compute-applicable-methods-using-types gf types
)
713 (let ((generator (get-secondary-dispatch-function1
714 gf methods types nil t all-applicable-and-sorted-p
)))
715 (make-callable gf methods generator
716 nil
(mapcar #'class-wrapper classes
))))))
718 (defun value-for-caching (gf classes
)
719 (let ((methods (compute-applicable-methods-using-types
720 gf
(mapcar #'class-eq-type classes
))))
721 (method-plist-value (car methods
) :constant-value
)))
723 (defun default-secondary-dispatch-function (generic-function)
725 (let ((methods (compute-applicable-methods generic-function args
)))
727 (let ((emf (get-effective-method-function generic-function
729 (invoke-emf emf args
))
730 (apply #'no-applicable-method generic-function args
)))))
733 (loop (when (atom x
) (return (eq x y
)))
734 (when (atom y
) (return nil
))
735 (unless (eq (car x
) (car y
)) (return nil
))
739 (defvar *std-cam-methods
* nil
)
741 (defun compute-applicable-methods-emf (generic-function)
742 (if (eq *boot-state
* 'complete
)
743 (let* ((cam (gdefinition 'compute-applicable-methods
))
744 (cam-methods (compute-applicable-methods-using-types
745 cam
(list `(eql ,generic-function
) t
))))
746 (values (get-effective-method-function cam cam-methods
)
748 (or *std-cam-methods
*
749 (setq *std-cam-methods
*
750 (compute-applicable-methods-using-types
751 cam
(list `(eql ,cam
) t
)))))))
752 (values #'compute-applicable-methods-function t
)))
754 (defun compute-applicable-methods-emf-std-p (gf)
755 (gf-info-c-a-m-emf-std-p (gf-arg-info gf
)))
757 (defvar *old-c-a-m-gf-methods
* nil
)
759 (defun update-all-c-a-m-gf-info (c-a-m-gf)
760 (let ((methods (generic-function-methods c-a-m-gf
)))
761 (if (and *old-c-a-m-gf-methods
*
762 (every (lambda (old-method)
763 (member old-method methods
:test
#'eq
))
764 *old-c-a-m-gf-methods
*))
765 (let ((gfs-to-do nil
)
766 (gf-classes-to-do nil
))
767 (dolist (method methods
)
768 (unless (member method
*old-c-a-m-gf-methods
* :test
#'eq
)
769 (let ((specl (car (method-specializers method
))))
770 (if (eql-specializer-p specl
)
771 (pushnew (specializer-object specl
) gfs-to-do
:test
#'eq
)
772 (pushnew (specializer-class specl
) gf-classes-to-do
:test
#'eq
)))))
773 (map-all-generic-functions
775 (when (or (member gf gfs-to-do
:test
#'eq
)
776 (dolist (class gf-classes-to-do nil
)
778 (class-precedence-list (class-of gf
))
780 (update-c-a-m-gf-info gf
)))))
781 (map-all-generic-functions #'update-c-a-m-gf-info
))
782 (setq *old-c-a-m-gf-methods
* methods
)))
784 (defun update-gf-info (gf)
785 (update-c-a-m-gf-info gf
)
786 (update-gf-simple-accessor-type gf
))
788 (defun update-c-a-m-gf-info (gf)
789 (unless (early-gf-p gf
)
790 (multiple-value-bind (c-a-m-emf std-p
)
791 (compute-applicable-methods-emf gf
)
792 (let ((arg-info (gf-arg-info gf
)))
793 (setf (gf-info-static-c-a-m-emf arg-info
) c-a-m-emf
)
794 (setf (gf-info-c-a-m-emf-std-p arg-info
) std-p
)))))
796 (defun update-gf-simple-accessor-type (gf)
797 (let ((arg-info (gf-arg-info gf
)))
798 (setf (gf-info-simple-accessor-type arg-info
)
799 (let* ((methods (generic-function-methods gf
))
800 (class (and methods
(class-of (car methods
))))
803 (cond ((or (eq class
*the-class-standard-reader-method
*)
804 (eq class
*the-class-global-reader-method
*))
806 ((or (eq class
*the-class-standard-writer-method
*)
807 (eq class
*the-class-global-writer-method
*))
809 ((or (eq class
*the-class-standard-boundp-method
*)
810 (eq class
*the-class-global-boundp-method
*))
812 (when (and (gf-info-c-a-m-emf-std-p arg-info
)
814 (dolist (method (cdr methods
) t
)
815 (unless (eq class
(class-of method
)) (return nil
)))
816 (eq (generic-function-method-combination gf
)
817 *standard-method-combination
*))
821 ;;; CMUCL (Gerd's PCL, 2002-04-25) comment:
823 ;;; Return two values. First value is a function to be stored in
824 ;;; effective slot definition SLOTD for reading it with
825 ;;; SLOT-VALUE-USING-CLASS, setting it with (SETF
826 ;;; SLOT-VALUE-USING-CLASS) or testing it with
827 ;;; SLOT-BOUNDP-USING-CLASS. GF is one of these generic functions,
828 ;;; TYPE is one of the symbols READER, WRITER, BOUNDP. CLASS is
831 ;;; Second value is true if the function returned is one of the
832 ;;; optimized standard functions for the purpose, which are used
833 ;;; when only standard methods are applicable.
835 ;;; FIXME: Change all these wacky function names to something sane.
836 (defun get-accessor-method-function (gf type class slotd
)
837 (let* ((std-method (standard-svuc-method type
))
838 (str-method (structure-svuc-method type
))
839 (types1 `((eql ,class
) (class-eq ,class
) (eql ,slotd
)))
840 (types (if (eq type
'writer
) `(t ,@types1
) types1
))
841 (methods (compute-applicable-methods-using-types gf types
))
842 (std-p (null (cdr methods
))))
845 (get-optimized-std-accessor-method-function class slotd type
)
846 (let* ((optimized-std-fun
847 (get-optimized-std-slot-value-using-class-method-function
850 `((,(car (or (member std-method methods
:test
#'eq
)
851 (member str-method methods
:test
#'eq
)
853 'get-accessor-method-function
)))
854 ,optimized-std-fun
)))
856 (let ((wrappers (list (wrapper-of class
)
857 (class-wrapper class
)
858 (wrapper-of slotd
))))
859 (if (eq type
'writer
)
860 (cons (class-wrapper *the-class-t
*) wrappers
)
862 (sdfun (get-secondary-dispatch-function
863 gf methods types method-alist wrappers
)))
864 (get-accessor-from-svuc-method-function class slotd sdfun type
)))
867 ;;; used by OPTIMIZE-SLOT-VALUE-BY-CLASS-P (vector.lisp)
868 (defun update-slot-value-gf-info (gf type
)
870 (update-std-or-str-methods gf type
))
871 (when (and (standard-svuc-method type
) (structure-svuc-method type
))
872 (flet ((update-accessor-info (class)
873 (when (class-finalized-p class
)
874 (dolist (slotd (class-slots class
))
875 (compute-slot-accessor-info slotd type gf
)))))
877 (update-accessor-info *new-class
*)
878 (map-all-classes #'update-accessor-info
'slot-object
)))))
880 (defvar *standard-slot-value-using-class-method
* nil
)
881 (defvar *standard-setf-slot-value-using-class-method
* nil
)
882 (defvar *standard-slot-boundp-using-class-method
* nil
)
883 (defvar *condition-slot-value-using-class-method
* nil
)
884 (defvar *condition-setf-slot-value-using-class-method
* nil
)
885 (defvar *condition-slot-boundp-using-class-method
* nil
)
886 (defvar *structure-slot-value-using-class-method
* nil
)
887 (defvar *structure-setf-slot-value-using-class-method
* nil
)
888 (defvar *structure-slot-boundp-using-class-method
* nil
)
890 (defun standard-svuc-method (type)
892 (reader *standard-slot-value-using-class-method
*)
893 (writer *standard-setf-slot-value-using-class-method
*)
894 (boundp *standard-slot-boundp-using-class-method
*)))
896 (defun set-standard-svuc-method (type method
)
898 (reader (setq *standard-slot-value-using-class-method
* method
))
899 (writer (setq *standard-setf-slot-value-using-class-method
* method
))
900 (boundp (setq *standard-slot-boundp-using-class-method
* method
))))
902 (defun condition-svuc-method (type)
904 (reader *condition-slot-value-using-class-method
*)
905 (writer *condition-setf-slot-value-using-class-method
*)
906 (boundp *condition-slot-boundp-using-class-method
*)))
908 (defun set-condition-svuc-method (type method
)
910 (reader (setq *condition-slot-value-using-class-method
* method
))
911 (writer (setq *condition-setf-slot-value-using-class-method
* method
))
912 (boundp (setq *condition-slot-boundp-using-class-method
* method
))))
914 (defun structure-svuc-method (type)
916 (reader *structure-slot-value-using-class-method
*)
917 (writer *structure-setf-slot-value-using-class-method
*)
918 (boundp *structure-slot-boundp-using-class-method
*)))
920 (defun set-structure-svuc-method (type method
)
922 (reader (setq *structure-slot-value-using-class-method
* method
))
923 (writer (setq *structure-setf-slot-value-using-class-method
* method
))
924 (boundp (setq *structure-slot-boundp-using-class-method
* method
))))
926 (defun update-std-or-str-methods (gf type
)
927 (dolist (method (generic-function-methods gf
))
928 (let ((specls (method-specializers method
)))
929 (when (and (or (not (eq type
'writer
))
930 (eq (pop specls
) *the-class-t
*))
931 (every #'classp specls
))
932 (cond ((and (eq (class-name (car specls
)) 'std-class
)
933 (eq (class-name (cadr specls
)) 'standard-object
)
934 (eq (class-name (caddr specls
))
935 'standard-effective-slot-definition
))
936 (set-standard-svuc-method type method
))
937 ((and (eq (class-name (car specls
)) 'condition-class
)
938 (eq (class-name (cadr specls
)) 'condition
)
939 (eq (class-name (caddr specls
))
940 'condition-effective-slot-definition
))
941 (set-condition-svuc-method type method
))
942 ((and (eq (class-name (car specls
)) 'structure-class
)
943 (eq (class-name (cadr specls
)) 'structure-object
)
944 (eq (class-name (caddr specls
))
945 'structure-effective-slot-definition
))
946 (set-structure-svuc-method type method
)))))))
948 (defun mec-all-classes-internal (spec precompute-p
)
949 (let ((wrapper (class-wrapper (specializer-class spec
))))
950 (unless (or (not wrapper
) (invalid-wrapper-p wrapper
))
951 (cons (specializer-class spec
)
954 (not (or (eq spec
*the-class-t
*)
955 (eq spec
*the-class-slot-object
*)
956 (eq spec
*the-class-standard-object
*)
957 (eq spec
*the-class-structure-object
*)))
958 (let ((sc (class-direct-subclasses spec
)))
960 (mapcan (lambda (class)
961 (mec-all-classes-internal class precompute-p
))
964 (defun mec-all-classes (spec precompute-p
)
965 (let ((classes (mec-all-classes-internal spec precompute-p
)))
966 (if (null (cdr classes
))
968 (let* ((a-classes (cons nil classes
))
970 (loop (when (null (cdr tail
))
971 (return (cdr a-classes
)))
972 (let ((class (cadr tail
))
974 (if (dolist (c ttail nil
)
975 (when (eq class c
) (return t
)))
976 (setf (cdr tail
) (cddr tail
))
977 (setf tail
(cdr tail
)))))))))
979 (defun mec-all-class-lists (spec-list precompute-p
)
982 (let* ((car-all-classes (mec-all-classes (car spec-list
)
984 (all-class-lists (mec-all-class-lists (cdr spec-list
)
986 (mapcan (lambda (list)
987 (mapcar (lambda (c) (cons c list
)) car-all-classes
))
990 (defun make-emf-cache (generic-function valuep cache classes-list new-class
)
991 (let* ((arg-info (gf-arg-info generic-function
))
992 (nkeys (arg-info-nkeys arg-info
))
993 (metatypes (arg-info-metatypes arg-info
))
994 (wrappers (unless (eq nkeys
1) (make-list nkeys
)))
995 (precompute-p (gf-precompute-dfun-and-emf-p arg-info
)))
996 (flet ((add-class-list (classes)
997 (when (or (null new-class
) (memq new-class classes
))
998 (let ((%wrappers
(get-wrappers-from-classes
999 nkeys wrappers classes metatypes
)))
1000 (when (and %wrappers
(not (probe-cache cache %wrappers
)))
1001 (let ((value (cond ((eq valuep t
)
1002 (sdfun-for-caching generic-function
1004 ((eq valuep
:constant-value
)
1005 (value-for-caching generic-function
1007 ;; need to get them again, as finalization might
1008 ;; have happened in between, which would
1009 ;; invalidate wrappers.
1010 (let ((wrappers (get-wrappers-from-classes
1011 nkeys wrappers classes metatypes
)))
1012 (when (if (atom wrappers
)
1013 (not (invalid-wrapper-p wrappers
))
1014 (every (complement #'invalid-wrapper-p
)
1016 (setq cache
(fill-cache cache wrappers value
))))))))))
1018 (mapc #'add-class-list classes-list
)
1019 (dolist (method (generic-function-methods generic-function
))
1020 (mapc #'add-class-list
1021 (mec-all-class-lists (method-specializers method
)
1025 (defmacro class-test
(arg class
)
1027 ((eq class
*the-class-t
*) t
)
1028 ((eq class
*the-class-slot-object
*)
1029 `(not (typep (classoid-of ,arg
) 'built-in-classoid
)))
1030 ((eq class
*the-class-standard-object
*)
1031 `(or (std-instance-p ,arg
) (fsc-instance-p ,arg
)))
1032 ((eq class
*the-class-funcallable-standard-object
*)
1033 `(fsc-instance-p ,arg
))
1035 `(typep ,arg
',(class-name class
)))))
1037 (defmacro class-eq-test
(arg class
)
1038 `(eq (class-of ,arg
) ',class
))
1040 (defmacro eql-test
(arg object
)
1041 `(eql ,arg
',object
))
1043 (defun dnet-methods-p (form)
1045 (or (eq (car form
) 'methods
)
1046 (eq (car form
) 'unordered-methods
))))
1048 ;;; This is CASE, but without gensyms.
1049 (defmacro scase
(arg &rest clauses
)
1050 `(let ((.case-arg.
,arg
))
1051 (cond ,@(mapcar (lambda (clause)
1052 (list* (cond ((null (car clause
))
1054 ((consp (car clause
))
1055 (if (null (cdar clause
))
1060 ((member (car clause
) '(t otherwise
))
1063 `(eql .case-arg.
',(car clause
))))
1068 (defmacro mcase
(arg &rest clauses
) `(scase ,arg
,@clauses
))
1070 (defun generate-discrimination-net (generic-function methods types sorted-p
)
1071 (let* ((arg-info (gf-arg-info generic-function
))
1072 (c-a-m-emf-std-p (gf-info-c-a-m-emf-std-p arg-info
))
1073 (precedence (arg-info-precedence arg-info
)))
1074 (generate-discrimination-net-internal
1075 generic-function methods types
1076 (lambda (methods known-types
)
1078 (and c-a-m-emf-std-p
1080 (let ((sorted-methods nil
))
1082 (copy-list methods
) precedence
1084 (when sorted-methods
(return-from one-order-p nil
))
1085 (setq sorted-methods methods
)))
1086 (setq methods sorted-methods
))
1088 `(methods ,methods
,known-types
)
1089 `(unordered-methods ,methods
,known-types
)))
1090 (lambda (position type true-value false-value
)
1091 (let ((arg (dfun-arg-symbol position
)))
1092 (if (eq (car type
) 'eql
)
1093 (let* ((false-case-p (and (consp false-value
)
1094 (or (eq (car false-value
) 'scase
)
1095 (eq (car false-value
) 'mcase
))
1096 (eq arg
(cadr false-value
))))
1097 (false-clauses (if false-case-p
1099 `((t ,false-value
))))
1100 (case-sym (if (and (dnet-methods-p true-value
)
1102 (eq (car false-value
) 'mcase
)
1103 (dnet-methods-p false-value
)))
1106 (type-sym `(,(cadr type
))))
1108 (,type-sym
,true-value
)
1110 `(if ,(let ((arg (dfun-arg-symbol position
)))
1112 (class `(class-test ,arg
,(cadr type
)))
1113 (class-eq `(class-eq-test ,arg
,(cadr type
)))))
1118 (defun class-from-type (type)
1119 (if (or (atom type
) (eq (car type
) t
))
1122 (and (dolist (type (cdr type
) *the-class-t
*)
1123 (when (and (consp type
) (not (eq (car type
) 'not
)))
1124 (return (class-from-type type
)))))
1126 (eql (class-of (cadr type
)))
1127 (class-eq (cadr type
))
1128 (class (cadr type
)))))
1130 (defun precompute-effective-methods (gf caching-p
&optional classes-list-p
)
1131 (let* ((arg-info (gf-arg-info gf
))
1132 (methods (generic-function-methods gf
))
1133 (precedence (arg-info-precedence arg-info
))
1134 (*in-precompute-effective-methods-p
* t
)
1136 (generate-discrimination-net-internal
1138 (lambda (methods known-types
)
1140 (when classes-list-p
1141 (push (mapcar #'class-from-type known-types
) classes-list
))
1142 (let ((no-eql-specls-p (not (methods-contain-eql-specializer-p
1147 (get-secondary-dispatch-function1
1148 gf methods known-types
1149 nil caching-p no-eql-specls-p
))))))
1150 (lambda (position type true-value false-value
)
1151 (declare (ignore position type true-value false-value
))
1154 (if (and (consp type
) (eq (car type
) 'eql
))
1155 `(class-eq ,(class-of (cadr type
)))
1159 ;;; We know that known-type implies neither new-type nor `(not ,new-type).
1160 (defun augment-type (new-type known-type
)
1161 (if (or (eq known-type t
)
1162 (eq (car new-type
) 'eql
))
1164 (let ((so-far (if (and (consp known-type
) (eq (car known-type
) 'and
))
1166 (list known-type
))))
1167 (unless (eq (car new-type
) 'not
)
1169 (mapcan (lambda (type)
1170 (unless (*subtypep new-type type
)
1175 `(and ,new-type
,@so-far
)))))
1177 (defun generate-discrimination-net-internal
1178 (gf methods types methods-function test-fun type-function
)
1179 (let* ((arg-info (gf-arg-info gf
))
1180 (precedence (arg-info-precedence arg-info
))
1181 (nreq (arg-info-number-required arg-info
))
1182 (metatypes (arg-info-metatypes arg-info
)))
1183 (labels ((do-column (p-tail contenders known-types
)
1185 (let* ((position (car p-tail
))
1186 (known-type (or (nth position types
) t
)))
1187 (if (eq (nth position metatypes
) t
)
1188 (do-column (cdr p-tail
) contenders
1189 (cons (cons position known-type
)
1191 (do-methods p-tail contenders
1192 known-type
() known-types
)))
1193 (funcall methods-function contenders
1194 (let ((k-t (make-list nreq
)))
1195 (dolist (index+type known-types
)
1196 (setf (nth (car index
+type
) k-t
)
1199 (do-methods (p-tail contenders known-type winners known-types
)
1201 ;; is a (sorted) list of methods that must be discriminated.
1203 ;; is the type of this argument, constructed from tests
1206 ;; is a (sorted) list of methods that are potentially
1207 ;; applicable after the discrimination has been made.
1208 (if (null contenders
)
1209 (do-column (cdr p-tail
)
1211 (cons (cons (car p-tail
) known-type
)
1213 (let* ((position (car p-tail
))
1214 (method (car contenders
))
1215 (specl (nth position
(method-specializers method
)))
1216 (type (funcall type-function
1217 (type-from-specializer specl
))))
1218 (multiple-value-bind (app-p maybe-app-p
)
1219 (specializer-applicable-using-type-p type known-type
)
1220 (flet ((determined-to-be (truth-value)
1221 (if truth-value app-p
(not maybe-app-p
)))
1222 (do-if (truth &optional implied
)
1223 (let ((ntype (if truth type
`(not ,type
))))
1228 (augment-type ntype known-type
))
1230 (append winners
`(,method
))
1233 (cond ((determined-to-be nil
) (do-if nil t
))
1234 ((determined-to-be t
) (do-if t t
))
1235 (t (funcall test-fun position type
1236 (do-if t
) (do-if nil
))))))))))
1237 (do-column precedence methods
()))))
1239 (defun compute-secondary-dispatch-function (generic-function net
&optional
1240 method-alist wrappers
)
1241 (function-funcall (compute-secondary-dispatch-function1 generic-function net
)
1242 method-alist wrappers
))
1244 (defvar *eq-case-table-limit
* 15)
1245 (defvar *case-table-limit
* 10)
1247 (defun compute-mcase-parameters (case-list)
1248 (unless (eq t
(caar (last case-list
)))
1249 (error "The key for the last case arg to mcase was not T"))
1250 (let* ((eq-p (dolist (case case-list t
)
1251 (unless (or (eq (car case
) t
)
1252 (symbolp (caar case
)))
1254 (len (1- (length case-list
)))
1255 (type (cond ((= len
1)
1259 *eq-case-table-limit
*
1260 *case-table-limit
*))
1266 (defmacro mlookup
(key info default
&optional eq-p type
)
1267 (unless (or (eq eq-p t
) (null eq-p
))
1268 (bug "Invalid eq-p argument: ~S" eq-p
))
1272 (declare (optimize (inhibit-warnings 3)))
1273 (,(if eq-p
'eq
'eql
) ,key
(car ,info
)))
1277 `(dolist (e ,info
,default
)
1279 (declare (optimize (inhibit-warnings 3)))
1280 (,(if eq-p
'eq
'eql
) (car e
) ,key
))
1283 `(gethash ,key
,info
,default
))))
1285 (defun net-test-converter (form)
1287 (default-test-converter form
)
1289 ((invoke-effective-method-function invoke-fast-method-call
1290 invoke-effective-narrow-method-function
)
1297 `(mlookup ,(cadr form
)
1300 ,@(compute-mcase-parameters (cddr form
))))
1301 (t (default-test-converter form
)))))
1303 (defun net-code-converter (form)
1305 (default-code-converter form
)
1307 ((methods unordered-methods
)
1308 (let ((gensym (gensym)))
1312 (let ((mp (compute-mcase-parameters (cddr form
)))
1313 (gensym (gensym)) (default (gensym)))
1314 (values `(mlookup ,(cadr form
) ,gensym
,default
,@mp
)
1315 (list gensym default
))))
1317 (default-code-converter form
)))))
1319 (defun net-constant-converter (form generic-function
)
1320 (or (let ((c (methods-converter form generic-function
)))
1323 (default-constant-converter form
)
1326 (let* ((mp (compute-mcase-parameters (cddr form
)))
1327 (list (mapcar (lambda (clause)
1328 (let ((key (car clause
))
1329 (meth (cadr clause
)))
1330 (cons (if (consp key
) (car key
) key
)
1332 meth generic-function
))))
1334 (default (car (last list
))))
1335 (list (list* :mcase mp
(nbutlast list
))
1338 (default-constant-converter form
))))))
1340 (defun methods-converter (form generic-function
)
1341 (cond ((and (consp form
) (eq (car form
) 'methods
))
1343 (get-effective-method-function1 generic-function
(cadr form
))))
1344 ((and (consp form
) (eq (car form
) 'unordered-methods
))
1345 (default-secondary-dispatch-function generic-function
))))
1347 (defun convert-methods (constant method-alist wrappers
)
1348 (if (and (consp constant
)
1349 (eq (car constant
) '.methods.
))
1350 (funcall (cdr constant
) method-alist wrappers
)
1353 (defun convert-table (constant method-alist wrappers
)
1354 (cond ((and (consp constant
)
1355 (eq (car constant
) :mcase
))
1356 (let ((alist (mapcar (lambda (k+m
)
1358 (convert-methods (cdr k
+m
)
1362 (mp (cadr constant
)))
1369 (let ((table (make-hash-table :test
(if (car mp
) 'eq
'eql
))))
1371 (setf (gethash (car k
+m
) table
) (cdr k
+m
)))
1374 (defun compute-secondary-dispatch-function1 (generic-function net
1375 &optional function-p
)
1377 ((and (eq (car net
) 'methods
) (not function-p
))
1378 (get-effective-method-function1 generic-function
(cadr net
)))
1380 (let* ((name (generic-function-name generic-function
))
1381 (arg-info (gf-arg-info generic-function
))
1382 (metatypes (arg-info-metatypes arg-info
))
1383 (nargs (length metatypes
))
1384 (applyp (arg-info-applyp arg-info
))
1385 (fmc-arg-info (cons nargs applyp
))
1386 (arglist (if function-p
1387 (make-dfun-lambda-list nargs applyp
)
1388 (make-fast-method-call-lambda-list nargs applyp
))))
1389 (multiple-value-bind (cfunction constants
)
1392 ,@(unless function-p
1393 `((declare (ignore .pv. .next-method-call.
))))
1394 (locally (declare #.
*optimize-speed
*)
1396 ,(make-emf-call nargs applyp
'emf
))))
1397 #'net-test-converter
1398 #'net-code-converter
1400 (net-constant-converter form generic-function
)))
1401 (lambda (method-alist wrappers
)
1402 (let* ((alist (list nil
))
1404 (dolist (constant constants
)
1405 (let* ((a (or (dolist (a alist nil
)
1406 (when (eq (car a
) constant
)
1410 constant method-alist wrappers
)
1412 constant method-alist wrappers
)))))
1414 (setf (cdr alist-tail
) new
)
1415 (setf alist-tail new
)))
1416 (let ((function (apply cfunction
(mapcar #'cdr
(cdr alist
)))))
1419 (make-fast-method-call
1420 :function
(set-fun-name function
`(sdfun-method ,name
))
1421 :arg-info fmc-arg-info
))))))))))
1423 (defvar *show-make-unordered-methods-emf-calls
* nil
)
1425 (defun make-unordered-methods-emf (generic-function methods
)
1426 (when *show-make-unordered-methods-emf-calls
*
1427 (format t
"~&make-unordered-methods-emf ~S~%"
1428 (generic-function-name generic-function
)))
1429 (lambda (&rest args
)
1430 (let* ((types (types-from-args generic-function args
'eql
))
1431 (smethods (sort-applicable-methods generic-function
1434 (emf (get-effective-method-function generic-function smethods
)))
1435 (invoke-emf emf args
))))
1437 ;;; The value returned by compute-discriminating-function is a function
1438 ;;; object. It is called a discriminating function because it is called
1439 ;;; when the generic function is called and its role is to discriminate
1440 ;;; on the arguments to the generic function and then call appropriate
1441 ;;; method functions.
1443 ;;; A discriminating function can only be called when it is installed as
1444 ;;; the funcallable instance function of the generic function for which
1445 ;;; it was computed.
1447 ;;; More precisely, if compute-discriminating-function is called with
1448 ;;; an argument <gf1>, and returns a result <df1>, that result must
1449 ;;; not be passed to apply or funcall directly. Rather, <df1> must be
1450 ;;; stored as the funcallable instance function of the same generic
1451 ;;; function <gf1> (using SET-FUNCALLABLE-INSTANCE-FUNCTION). Then the
1452 ;;; generic function can be passed to funcall or apply.
1454 ;;; An important exception is that methods on this generic function are
1455 ;;; permitted to return a function which itself ends up calling the value
1456 ;;; returned by a more specific method. This kind of `encapsulation' of
1457 ;;; discriminating function is critical to many uses of the MOP.
1459 ;;; As an example, the following canonical case is legal:
1461 ;;; (defmethod compute-discriminating-function ((gf my-generic-function))
1462 ;;; (let ((std (call-next-method)))
1464 ;;; (print (list 'call-to-gf gf arg))
1465 ;;; (funcall std arg))))
1467 ;;; Because many discriminating functions would like to use a dynamic
1468 ;;; strategy in which the precise discriminating function changes with
1469 ;;; time it is important to specify how a discriminating function is
1470 ;;; permitted itself to change the funcallable instance function of the
1471 ;;; generic function.
1473 ;;; Discriminating functions may set the funcallable instance function
1474 ;;; of the generic function, but the new value must be generated by making
1475 ;;; a call to COMPUTE-DISCRIMINATING-FUNCTION. This is to ensure that any
1476 ;;; more specific methods which may have encapsulated the discriminating
1477 ;;; function will get a chance to encapsulate the new, inner discriminating
1480 ;;; This implies that if a discriminating function wants to modify itself
1481 ;;; it should first store some information in the generic function proper,
1482 ;;; and then call compute-discriminating-function. The appropriate method
1483 ;;; on compute-discriminating-function will see the information stored in
1484 ;;; the generic function and generate a discriminating function accordingly.
1486 ;;; The following is an example of a discriminating function which modifies
1487 ;;; itself in accordance with this protocol:
1489 ;;; (defmethod compute-discriminating-function ((gf my-generic-function))
1491 ;;; (cond (<some condition>
1492 ;;; <store some info in the generic function>
1493 ;;; (set-funcallable-instance-function
1495 ;;; (compute-discriminating-function gf))
1496 ;;; (funcall gf arg))
1498 ;;; <call-a-method-of-gf>))))
1500 ;;; Whereas this code would not be legal:
1502 ;;; (defmethod compute-discriminating-function ((gf my-generic-function))
1504 ;;; (cond (<some condition>
1505 ;;; (set-funcallable-instance-function
1507 ;;; (lambda (a) ..))
1508 ;;; (funcall gf arg))
1510 ;;; <call-a-method-of-gf>))))
1512 ;;; NOTE: All the examples above assume that all instances of the class
1513 ;;; my-generic-function accept only one argument.
1515 (defun slot-value-using-class-dfun (class object slotd
)
1516 (declare (ignore class
))
1517 (function-funcall (slot-definition-reader-function slotd
) object
))
1519 (defun setf-slot-value-using-class-dfun (new-value class object slotd
)
1520 (declare (ignore class
))
1521 (function-funcall (slot-definition-writer-function slotd
) new-value object
))
1523 (defun slot-boundp-using-class-dfun (class object slotd
)
1524 (declare (ignore class
))
1525 (function-funcall (slot-definition-boundp-function slotd
) object
))
1527 (defun special-case-for-compute-discriminating-function-p (gf)
1528 (or (eq gf
#'slot-value-using-class
)
1529 (eq gf
#'(setf slot-value-using-class
))
1530 (eq gf
#'slot-boundp-using-class
)))
1533 (defmethod compute-discriminating-function ((gf standard-generic-function
))
1534 (let ((dfun-state (slot-value gf
'dfun-state
)))
1535 (when (special-case-for-compute-discriminating-function-p gf
)
1536 ;; if we have a special case for
1537 ;; COMPUTE-DISCRIMINATING-FUNCTION, then (at least for the
1538 ;; special cases implemented as of 2006-05-09) any information
1539 ;; in the cache is misplaced.
1540 (aver (null dfun-state
)))
1541 (typecase dfun-state
1543 (when (eq gf
#'compute-applicable-methods
)
1544 (update-all-c-a-m-gf-info gf
))
1546 ((eq gf
#'slot-value-using-class
)
1547 (update-slot-value-gf-info gf
'reader
)
1548 #'slot-value-using-class-dfun
)
1549 ((eq gf
#'(setf slot-value-using-class
))
1550 (update-slot-value-gf-info gf
'writer
)
1551 #'setf-slot-value-using-class-dfun
)
1552 ((eq gf
#'slot-boundp-using-class
)
1553 (update-slot-value-gf-info gf
'boundp
)
1554 #'slot-boundp-using-class-dfun
)
1555 ;; KLUDGE: PRINT-OBJECT is not a special-case in the sense
1556 ;; of having a desperately special discriminating function.
1557 ;; However, it is important that the machinery for printing
1558 ;; conditions for stack and heap exhaustion, and the
1559 ;; restarts offered by the debugger, work without consuming
1560 ;; many extra resources. This way (testing by name of GF
1561 ;; rather than by identity) was the only way I found to get
1562 ;; this to bootstrap, given that the PRINT-OBJECT generic
1563 ;; function is only set up later, in
1564 ;; SRC;PCL;PRINT-OBJECT.LISP. -- CSR, 2008-06-09
1565 ((eq (slot-value gf
'name
) 'print-object
)
1566 (let ((nkeys (nth-value 3 (get-generic-fun-info gf
))))
1568 ;; KLUDGE: someone has defined a method
1569 ;; specialized on the second argument: punt.
1571 (make-initial-dfun gf
))
1573 (multiple-value-bind (dfun cache info
)
1574 (make-caching-dfun gf po-cache
)
1575 (set-dfun gf dfun cache info
)))
1576 ;; the relevant PRINT-OBJECT methods get defined
1577 ;; late, by delayed DEF!METHOD. We mustn't cache
1578 ;; the effective method for our classes earlier
1579 ;; than the relevant PRINT-OBJECT methods are
1581 ((boundp 'sb-impl
::*delayed-def
!method-args
*)
1582 (make-initial-dfun gf
))
1583 (t (multiple-value-bind (dfun cache info
)
1584 (make-final-dfun-internal
1586 (list (list (find-class 'sb-kernel
::control-stack-exhausted
))
1587 (list (find-class 'sb-kernel
::heap-exhausted-error
))
1588 (list (find-class 'restart
))))
1589 (setq po-cache cache
)
1590 (set-dfun gf dfun cache info
))))))
1591 ((gf-precompute-dfun-and-emf-p (slot-value gf
'arg-info
))
1592 (make-final-dfun gf
))
1594 (make-initial-dfun gf
))))
1595 (function dfun-state
)
1596 (cons (car dfun-state
))))))
1598 (defmethod update-gf-dfun ((class std-class
) gf
)
1599 (let ((*new-class
* class
)
1600 (arg-info (gf-arg-info gf
)))
1602 ((special-case-for-compute-discriminating-function-p gf
))
1603 ((gf-precompute-dfun-and-emf-p arg-info
)
1604 (multiple-value-bind (dfun cache info
)
1605 (make-final-dfun-internal gf
)
1606 (update-dfun gf dfun cache info
))))))
1608 (defmethod (setf class-name
) (new-value class
)
1609 (let ((classoid (wrapper-classoid (class-wrapper class
))))
1610 (if (and new-value
(symbolp new-value
))
1611 (setf (classoid-name classoid
) new-value
)
1612 (setf (classoid-name classoid
) nil
)))
1613 (reinitialize-instance class
:name new-value
)
1616 (defmethod (setf generic-function-name
) (new-value generic-function
)
1617 (reinitialize-instance generic-function
:name new-value
)
1620 (defmethod function-keywords ((method standard-method
))
1621 (multiple-value-bind (nreq nopt keysp restp allow-other-keys-p
1622 keywords keyword-parameters
)
1623 (analyze-lambda-list (if (consp method
)
1624 (early-method-lambda-list method
)
1625 (method-lambda-list method
)))
1626 (declare (ignore nreq nopt keysp restp keywords
))
1627 (values keywords allow-other-keys-p
)))
1629 (defmethod function-keyword-parameters ((method standard-method
))
1630 (multiple-value-bind (nreq nopt keysp restp allow-other-keys-p
1631 keywords keyword-parameters
)
1632 (analyze-lambda-list (if (consp method
)
1633 (early-method-lambda-list method
)
1634 (method-lambda-list method
)))
1635 (declare (ignore nreq nopt keysp restp keywords
))
1636 (values keyword-parameters allow-other-keys-p
)))
1638 (defun method-ll->generic-function-ll
(ll)
1639 (multiple-value-bind
1640 (nreq nopt keysp restp allow-other-keys-p keywords keyword-parameters
)
1641 (analyze-lambda-list ll
)
1642 (declare (ignore nreq nopt keysp restp allow-other-keys-p keywords
))
1643 (remove-if (lambda (s)
1644 (or (memq s keyword-parameters
)
1645 (eq s
'&allow-other-keys
)))
1648 ;;; This is based on the rules of method lambda list congruency
1649 ;;; defined in the spec. The lambda list it constructs is the pretty
1650 ;;; union of the lambda lists of the generic function and of all its
1651 ;;; methods. It doesn't take method applicability into account at all
1654 ;;; (Notice that we ignore &AUX variables as they're not part of the
1655 ;;; "public interface" of a function.)
1657 (defmethod generic-function-pretty-arglist
1658 ((generic-function standard-generic-function
))
1659 (let ((gf-lambda-list (generic-function-lambda-list generic-function
))
1660 (methods (generic-function-methods generic-function
)))
1663 (multiple-value-bind (gf.required gf.optional gf.rest gf.keys gf.allowp
)
1664 (%split-arglist gf-lambda-list
)
1665 ;; Possibly extend the keyword parameters of the gf by
1666 ;; additional key parameters of its methods:
1667 (let ((methods.keys nil
) (methods.allowp nil
))
1669 (multiple-value-bind (m.keyparams m.allow-other-keys
)
1670 (function-keyword-parameters m
)
1671 (setq methods.keys
(union methods.keys m.keyparams
:key
#'maybe-car
))
1672 (setq methods.allowp
(or methods.allowp m.allow-other-keys
))))
1673 (let ((arglist '()))
1674 (when (or gf.allowp methods.allowp
)
1675 (push '&allow-other-keys arglist
))
1676 (when (or gf.keys methods.keys
)
1677 ;; We make sure that the keys of the gf appear before
1678 ;; those of its methods, since they're probably more
1679 ;; generally appliable.
1680 (setq arglist
(nconc (list '&key
) gf.keys
1681 (nset-difference methods.keys gf.keys
)
1684 (setq arglist
(nconc (list '&rest gf.rest
) arglist
)))
1686 (setq arglist
(nconc (list '&optional
) gf.optional arglist
)))
1687 (nconc gf.required arglist
)))))))
1689 (defun maybe-car (thing)
1695 (defun %split-arglist
(lambda-list)
1696 ;; This function serves to shrink the number of returned values of
1697 ;; PARSE-LAMBDA-LIST to something handier.
1698 (multiple-value-bind (required optional restp rest keyp keys allowp
1699 auxp aux morep more-context more-count
)
1700 (parse-lambda-list lambda-list
)
1701 (declare (ignore restp keyp auxp aux morep
))
1702 (declare (ignore more-context more-count
))
1703 (values required optional rest keys allowp
)))