711696fbb27b9c6af1ac26aef368d4f6d2535c6d
[sbcl.git] / src / pcl / defcombin.lisp
1 ;;;; This software is part of the SBCL system. See the README file for
2 ;;;; more information.
3
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
8 ;;;; information.
9
10 ;;;; copyright information from original PCL sources:
11 ;;;;
12 ;;;; Copyright (c) 1985, 1986, 1987, 1988, 1989, 1990 Xerox Corporation.
13 ;;;; All rights reserved.
14 ;;;;
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
18 ;;;; control laws.
19 ;;;;
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
22 ;;;; specification.
23
24 (in-package "SB-PCL")
25 \f
26 (defmacro define-method-combination (&whole form &rest args)
27   (declare (ignore args))
28   `(progn
29      (with-single-package-locked-error
30          (:symbol ',(second form) "defining ~A as a method combination"))
31      ,(if (and (cddr form)
32                (listp (caddr form)))
33           (expand-long-defcombin form)
34           (expand-short-defcombin form))))
35 \f
36 ;;;; standard method combination
37
38 ;;; The STANDARD method combination type is implemented directly by
39 ;;; the class STANDARD-METHOD-COMBINATION. The method on
40 ;;; COMPUTE-EFFECTIVE-METHOD does standard method combination directly
41 ;;; and is defined by hand in the file combin.lisp. The method for
42 ;;; FIND-METHOD-COMBINATION must appear in this file for bootstrapping
43 ;;; reasons.
44 (defmethod find-method-combination ((generic-function generic-function)
45                                     (type-name (eql 'standard))
46                                     options)
47   (when options
48     (method-combination-error
49       "STANDARD method combination accepts no options."))
50   *standard-method-combination*)
51 \f
52 ;;;; short method combinations
53 ;;;;
54 ;;;; Short method combinations all follow the same rule for computing the
55 ;;;; effective method. So, we just implement that rule once. Each short
56 ;;;; method combination object just reads the parameters out of the object
57 ;;;; and runs the same rule.
58
59 (defun expand-short-defcombin (whole)
60   (let* ((type-name (cadr whole))
61          (documentation
62            (getf (cddr whole) :documentation))
63          (identity-with-one-arg
64            (getf (cddr whole) :identity-with-one-argument nil))
65          (operator
66            (getf (cddr whole) :operator type-name)))
67     `(load-short-defcombin
68      ',type-name ',operator ',identity-with-one-arg ',documentation
69       (sb-c:source-location))))
70
71 (defun load-short-defcombin (type-name operator ioa doc source-location)
72   (let* ((specializers
73            (list (find-class 'generic-function)
74                  (intern-eql-specializer type-name)
75                  *the-class-t*))
76          (old-method
77            (get-method #'find-method-combination () specializers nil))
78          (new-method nil))
79     (setq new-method
80           (make-instance 'standard-method
81             :qualifiers ()
82             :specializers specializers
83             :lambda-list '(generic-function type-name options)
84             :function (lambda (args nms &rest cm-args)
85                         (declare (ignore nms cm-args))
86                         (apply
87                          (lambda (gf type-name options)
88                            (declare (ignore gf))
89                            (short-combine-methods
90                             type-name options operator ioa new-method doc))
91                          args))
92             :definition-source source-location))
93     (when old-method
94       (remove-method #'find-method-combination old-method))
95     (add-method #'find-method-combination new-method)
96     (setf (random-documentation type-name 'method-combination) doc)
97     type-name))
98
99 (defun short-combine-methods (type-name options operator ioa method doc)
100   (cond ((null options) (setq options '(:most-specific-first)))
101         ((equal options '(:most-specific-first)))
102         ((equal options '(:most-specific-last)))
103         (t
104          (method-combination-error
105           "Illegal options to a short method combination type.~%~
106            The method combination type ~S accepts one option which~%~
107            must be either :MOST-SPECIFIC-FIRST or :MOST-SPECIFIC-LAST."
108           type-name)))
109   (make-instance 'short-method-combination
110                  :type-name type-name
111                  :options options
112                  :operator operator
113                  :identity-with-one-argument ioa
114                  :definition-source method
115                  :documentation doc))
116
117 (defmethod compute-effective-method ((generic-function generic-function)
118                                      (combin short-method-combination)
119                                      applicable-methods)
120   (let ((type-name (method-combination-type-name combin))
121         (operator (short-combination-operator combin))
122         (ioa (short-combination-identity-with-one-argument combin))
123         (order (car (method-combination-options combin)))
124         (around ())
125         (primary ()))
126     (flet ((invalid (gf combin m)
127              (return-from compute-effective-method
128                `(%invalid-qualifiers ',gf ',combin ',m))))
129       (dolist (m applicable-methods)
130         (let ((qualifiers (method-qualifiers m)))
131           (cond ((null qualifiers) (invalid generic-function combin m))
132                 ((cdr qualifiers) (invalid generic-function combin m))
133                 ((eq (car qualifiers) :around)
134                  (push m around))
135                 ((eq (car qualifiers) type-name)
136                  (push m primary))
137                 (t (invalid generic-function combin m))))))
138     (setq around (nreverse around))
139     (ecase order
140       (:most-specific-last) ; nothing to be done, already in correct order
141       (:most-specific-first
142        (setq primary (nreverse primary))))
143     (let ((main-method
144             (if (and (null (cdr primary))
145                      (not (null ioa)))
146                 `(call-method ,(car primary) ())
147                 `(,operator ,@(mapcar (lambda (m) `(call-method ,m ()))
148                                       primary)))))
149       (cond ((null primary)
150              ;; As of sbcl-0.8.0.80 we don't seem to need to need
151              ;; to do anything messy like
152              ;;        `(APPLY (FUNCTION (IF AROUND
153              ;;                              'NO-PRIMARY-METHOD
154              ;;                              'NO-APPLICABLE-METHOD)
155              ;;                           ',GENERIC-FUNCTION
156              ;;                           .ARGS.)
157              ;; here because (for reasons I don't understand at the
158              ;; moment -- WHN) control will never reach here if there
159              ;; are no applicable methods, but instead end up
160              ;; in NO-APPLICABLE-METHODS first.
161              ;;
162              ;; FIXME: The way that we arrange for .ARGS. to be bound
163              ;; here seems weird. We rely on EXPAND-EFFECTIVE-METHOD-FUNCTION
164              ;; recognizing any form whose operator is %NO-PRIMARY-METHOD
165              ;; as magical, and carefully surrounding it with a
166              ;; LAMBDA form which binds .ARGS. But...
167              ;;   1. That seems fragile, because the magicalness of
168              ;;      %NO-PRIMARY-METHOD forms is scattered around
169              ;;      the system. So it could easily be broken by
170              ;;      locally-plausible maintenance changes like,
171              ;;      e.g., using the APPLY expression above.
172              ;;   2. That seems buggy w.r.t. to MOPpish tricks in
173              ;;      user code, e.g.
174              ;;         (DEFMETHOD COMPUTE-EFFECTIVE-METHOD :AROUND (...)
175              ;;           `(PROGN ,(CALL-NEXT-METHOD) (INCF *MY-CTR*)))
176              `(%no-primary-method ',generic-function .args.))
177             ((null around) main-method)
178             (t
179              `(call-method ,(car around)
180                            (,@(cdr around) (make-method ,main-method))))))))
181
182 (defmethod invalid-qualifiers ((gf generic-function)
183                                (combin short-method-combination)
184                                method)
185   (let ((qualifiers (method-qualifiers method))
186         (type-name (method-combination-type-name combin)))
187     (let ((why (cond
188                  ((null qualifiers) "has no qualifiers")
189                  ((cdr qualifiers) "has too many qualifiers")
190                  (t (aver (and (neq (car qualifiers) type-name)
191                                (neq (car qualifiers) :around)))
192                     "has an invalid qualifier"))))
193       (invalid-method-error
194        method
195        "The method ~S on ~S ~A.~%~
196         The method combination type ~S was defined with the~%~
197         short form of DEFINE-METHOD-COMBINATION and so requires~%~
198         all methods have either the single qualifier ~S or the~%~
199         single qualifier :AROUND."
200        method gf why type-name type-name))))
201 \f
202 ;;;; long method combinations
203
204 (defun expand-long-defcombin (form)
205   (let ((type-name (cadr form))
206         (lambda-list (caddr form))
207         (method-group-specifiers (cadddr form))
208         (body (cddddr form))
209         (args-option ())
210         (gf-var nil))
211     (when (and (consp (car body)) (eq (caar body) :arguments))
212       (setq args-option (cdr (pop body))))
213     (when (and (consp (car body)) (eq (caar body) :generic-function))
214       (setq gf-var (cadr (pop body))))
215     (multiple-value-bind (documentation function)
216         (make-long-method-combination-function
217           type-name lambda-list method-group-specifiers args-option gf-var
218           body)
219       `(load-long-defcombin ',type-name ',documentation #',function
220                             ',args-option (sb-c:source-location)))))
221
222 (defvar *long-method-combination-functions* (make-hash-table :test 'eq))
223
224 (defun load-long-defcombin
225     (type-name doc function args-lambda-list source-location)
226   (let* ((specializers
227            (list (find-class 'generic-function)
228                  (intern-eql-specializer type-name)
229                  *the-class-t*))
230          (old-method
231            (get-method #'find-method-combination () specializers nil))
232          (new-method
233            (make-instance 'standard-method
234              :qualifiers ()
235              :specializers specializers
236              :lambda-list '(generic-function type-name options)
237              :function (lambda (args nms &rest cm-args)
238                          (declare (ignore nms cm-args))
239                          (apply
240                           (lambda (generic-function type-name options)
241                             (declare (ignore generic-function))
242                             (make-instance 'long-method-combination
243                                            :type-name type-name
244                                            :options options
245                                            :args-lambda-list args-lambda-list
246                                            :documentation doc))
247                           args))
248              :definition-source source-location)))
249     (setf (gethash type-name *long-method-combination-functions*) function)
250     (when old-method (remove-method #'find-method-combination old-method))
251     (add-method #'find-method-combination new-method)
252     (setf (random-documentation type-name 'method-combination) doc)
253     type-name))
254
255 (defmethod compute-effective-method ((generic-function generic-function)
256                                      (combin long-method-combination)
257                                      applicable-methods)
258   (funcall (gethash (method-combination-type-name combin)
259                     *long-method-combination-functions*)
260            generic-function
261            combin
262            applicable-methods))
263
264 (defun make-long-method-combination-function
265        (type-name ll method-group-specifiers args-option gf-var body)
266   (declare (ignore type-name))
267   (multiple-value-bind (real-body declarations documentation)
268       (parse-body body)
269     (let ((wrapped-body
270             (wrap-method-group-specifier-bindings method-group-specifiers
271                                                   declarations
272                                                   real-body)))
273       (when gf-var
274         (push `(,gf-var .generic-function.) (cadr wrapped-body)))
275
276       (when args-option
277         (setq wrapped-body (deal-with-args-option wrapped-body args-option)))
278
279       (when ll
280         (setq wrapped-body
281               `(apply #'(lambda ,ll ,wrapped-body)
282                       (method-combination-options .method-combination.))))
283
284       (values
285         documentation
286         `(lambda (.generic-function. .method-combination. .applicable-methods.)
287            (declare (ignorable .generic-function.
288                      .method-combination. .applicable-methods.))
289            (block .long-method-combination-function. ,wrapped-body))))))
290
291 (define-condition long-method-combination-error
292     (reference-condition simple-error)
293   ()
294   (:default-initargs
295       :references (list '(:ansi-cl :macro define-method-combination))))
296
297 ;;; NOTE:
298 ;;;
299 ;;; The semantics of long form method combination in the presence of
300 ;;; multiple methods with the same specializers in the same method
301 ;;; group are unclear by the spec: a portion of the standard implies
302 ;;; that an error should be signalled, and another is more lenient.
303 ;;;
304 ;;; It is reasonable to allow a single method group of * to bypass all
305 ;;; rules, as this is explicitly stated in the standard.
306
307 (defun group-cond-clause (name tests specializer-cache star-only)
308   (let ((maybe-error-clause
309          (if star-only
310              `(setq ,specializer-cache .specializers.)
311              `(if (and (equal ,specializer-cache .specializers.)
312                        (not (null .specializers.)))
313                   (return-from .long-method-combination-function.
314                     '(error 'long-method-combination-error
315                       :format-control "More than one method of type ~S ~
316                                        with the same specializers."
317                       :format-arguments (list ',name)))
318                   (setq ,specializer-cache .specializers.)))))
319     `((or ,@tests)
320       ,maybe-error-clause
321       (push .method. ,name))))
322
323 (defun wrap-method-group-specifier-bindings
324     (method-group-specifiers declarations real-body)
325   (let (names specializer-caches cond-clauses required-checks order-cleanups)
326     (let ((nspecifiers (length method-group-specifiers)))
327       (dolist (method-group-specifier method-group-specifiers)
328         (multiple-value-bind (name tests description order required)
329             (parse-method-group-specifier method-group-specifier)
330           (declare (ignore description))
331           (let ((specializer-cache (gensym)))
332             (push name names)
333             (push specializer-cache specializer-caches)
334             (push (group-cond-clause name tests specializer-cache
335                                      (and (eq (cadr method-group-specifier) '*)
336                                           (= nspecifiers 1)))
337                   cond-clauses)
338             (when required
339               (push `(when (null ,name)
340                       (return-from .long-method-combination-function.
341                         '(error 'long-method-combination-error
342                           :format-control "No ~S methods."
343                           :format-arguments (list ',name))))
344                     required-checks))
345             (loop (unless (and (constantp order)
346                                (neq order (setq order
347                                                 (constant-form-value order))))
348                     (return t)))
349             (push (cond ((eq order :most-specific-first)
350                          `(setq ,name (nreverse ,name)))
351                         ((eq order :most-specific-last) ())
352                         (t
353                          `(ecase ,order
354                            (:most-specific-first
355                             (setq ,name (nreverse ,name)))
356                            (:most-specific-last))))
357                   order-cleanups))))
358       `(let (,@(nreverse names) ,@(nreverse specializer-caches))
359         ,@declarations
360         (dolist (.method. .applicable-methods.)
361           (let ((.qualifiers. (method-qualifiers .method.))
362                 (.specializers. (method-specializers .method.)))
363             (declare (ignorable .qualifiers. .specializers.))
364             (cond ,@(nreverse cond-clauses))))
365         ,@(nreverse required-checks)
366         ,@(nreverse order-cleanups)
367         ,@real-body))))
368
369 (defun parse-method-group-specifier (method-group-specifier)
370   ;;(declare (values name tests description order required))
371   (let* ((name (pop method-group-specifier))
372          (patterns ())
373          (tests
374            (let (collect)
375              (block collect-tests
376                (loop
377                  (if (or (null method-group-specifier)
378                          (memq (car method-group-specifier)
379                                '(:description :order :required)))
380                      (return-from collect-tests t)
381                      (let ((pattern (pop method-group-specifier)))
382                        (push pattern patterns)
383                        (push (parse-qualifier-pattern name pattern)
384                              collect)))))
385              (nreverse collect))))
386     (values name
387             tests
388             (getf method-group-specifier :description
389                   (make-default-method-group-description patterns))
390             (getf method-group-specifier :order :most-specific-first)
391             (getf method-group-specifier :required nil))))
392
393 (defun parse-qualifier-pattern (name pattern)
394   (cond ((eq pattern '()) `(null .qualifiers.))
395         ((eq pattern '*) t)
396         ((symbolp pattern) `(,pattern .qualifiers.))
397         ((listp pattern) `(qualifier-check-runtime ',pattern .qualifiers.))
398         (t (error "In the method group specifier ~S,~%~
399                    ~S isn't a valid qualifier pattern."
400                   name pattern))))
401
402 (defun qualifier-check-runtime (pattern qualifiers)
403   (loop (cond ((and (null pattern) (null qualifiers))
404                (return t))
405               ((eq pattern '*) (return t))
406               ((and pattern qualifiers (eq (car pattern) (car qualifiers)))
407                (pop pattern)
408                (pop qualifiers))
409               (t (return nil)))))
410
411 (defun make-default-method-group-description (patterns)
412   (if (cdr patterns)
413       (format nil
414               "methods matching one of the patterns: ~{~S, ~} ~S"
415               (butlast patterns) (car (last patterns)))
416       (format nil
417               "methods matching the pattern: ~S"
418               (car patterns))))
419
420 ;;; This baby is a complete mess. I can't believe we put it in this
421 ;;; way. No doubt this is a large part of what drives MLY crazy.
422 ;;;
423 ;;; At runtime (when the effective-method is run), we bind an intercept
424 ;;; lambda-list to the arguments to the generic function.
425 ;;;
426 ;;; At compute-effective-method time, the symbols in the :arguments
427 ;;; option are bound to the symbols in the intercept lambda list.
428 ;;;
429 ;;; FIXME: in here we have not one but two mini-copies of a weird
430 ;;; hybrid of PARSE-LAMBDA-LIST and PARSE-DEFMACRO-LAMBDA-LIST.
431 (defun deal-with-args-option (wrapped-body args-lambda-list)
432   (let ((intercept-rebindings
433          (let (rebindings)
434            (dolist (arg args-lambda-list (nreverse rebindings))
435              (unless (member arg lambda-list-keywords)
436                (typecase arg
437                  (symbol (push `(,arg ',arg) rebindings))
438                  (cons
439                   (unless (symbolp (car arg))
440                     (error "invalid lambda-list specifier: ~S." arg))
441                   (push `(,(car arg) ',(car arg)) rebindings))
442                  (t (error "invalid lambda-list-specifier: ~S." arg)))))))
443         (nreq 0)
444         (nopt 0)
445         (whole nil))
446     ;; Count the number of required and optional parameters in
447     ;; ARGS-LAMBDA-LIST into NREQ and NOPT, and set WHOLE to the
448     ;; name of a &WHOLE parameter, if any.
449     (when (member '&whole (rest args-lambda-list))
450       (error 'simple-program-error
451              :format-control "~@<The value of the :ARGUMENTS option of ~
452                 DEFINE-METHOD-COMBINATION is~2I~_~S,~I~_but &WHOLE may ~
453                 only appear first in the lambda list.~:>"
454              :format-arguments (list args-lambda-list)))
455     (loop with state = 'required
456           for arg in args-lambda-list do
457             (if (memq arg lambda-list-keywords)
458                 (setq state arg)
459                 (case state
460                   (required (incf nreq))
461                   (&optional (incf nopt))
462                   (&whole (setq whole arg state 'required)))))
463     ;; This assumes that the head of WRAPPED-BODY is a let, and it
464     ;; injects let-bindings of the form (ARG 'SYM) for all variables
465     ;; of the argument-lambda-list; SYM is a gensym.
466     (aver (memq (first wrapped-body) '(let let*)))
467     (setf (second wrapped-body)
468           (append intercept-rebindings (second wrapped-body)))
469     ;; Be sure to fill out the args lambda list so that it can be too
470     ;; short if it wants to.
471     (unless (or (memq '&rest args-lambda-list)
472                 (memq '&allow-other-keys args-lambda-list))
473       (let ((aux (memq '&aux args-lambda-list)))
474         (setq args-lambda-list
475               (append (ldiff args-lambda-list aux)
476                       (if (memq '&key args-lambda-list)
477                           '(&allow-other-keys)
478                           '(&rest .ignore.))
479                       aux))))
480     ;; .GENERIC-FUNCTION. is bound to the generic function in the
481     ;; method combination function, and .GF-ARGS* is bound to the
482     ;; generic function arguments in effective method functions
483     ;; created for generic functions having a method combination that
484     ;; uses :ARGUMENTS.
485     ;;
486     ;; The DESTRUCTURING-BIND binds the parameters of the
487     ;; ARGS-LAMBDA-LIST to actual generic function arguments.  Because
488     ;; ARGS-LAMBDA-LIST may be shorter or longer than the generic
489     ;; function's lambda list, which is only known at run time, this
490     ;; destructuring has to be done on a slighly modified list of
491     ;; actual arguments, from which values might be stripped or added.
492     ;;
493     ;; Using one of the variable names in the body inserts a symbol
494     ;; into the effective method, and running the effective method
495     ;; produces the value of actual argument that is bound to the
496     ;; symbol.
497     `(let ((inner-result. ,wrapped-body)
498            (gf-lambda-list (generic-function-lambda-list .generic-function.)))
499        `(destructuring-bind ,',args-lambda-list
500             (frob-combined-method-args
501              .gf-args. ',gf-lambda-list
502              ,',nreq ,',nopt)
503           ,,(when (memq '.ignore. args-lambda-list)
504               ''(declare (ignore .ignore.)))
505           ;; If there is a &WHOLE in the args-lambda-list, let
506           ;; it result in the actual arguments of the generic-function
507           ;; not the frobbed list.
508           ,,(when whole
509               ``(setq ,',whole .gf-args.))
510           ,inner-result.))))
511
512 ;;; Partition VALUES into three sections: required, optional, and the
513 ;;; rest, according to required, optional, and other parameters in
514 ;;; LAMBDA-LIST.  Make the required and optional sections NREQ and
515 ;;; NOPT elements long by discarding values or adding NILs.  Value is
516 ;;; the concatenated list of required and optional sections, and what
517 ;;; is left as rest from VALUES.
518 (defun frob-combined-method-args (values lambda-list nreq nopt)
519   (loop with section = 'required
520         for arg in lambda-list
521         if (memq arg lambda-list-keywords) do
522           (setq section arg)
523           (unless (eq section '&optional)
524             (loop-finish))
525         else if (eq section 'required)
526           count t into nr
527           and collect (pop values) into required
528         else if (eq section '&optional)
529           count t into no
530           and collect (pop values) into optional
531         finally
532           (flet ((frob (list n m)
533                    (cond ((> n m) (butlast list (- n m)))
534                          ((< n m) (nconc list (make-list (- m n))))
535                          (t list))))
536             (return (nconc (frob required nr nreq)
537                            (frob optional no nopt)
538                            values)))))
539