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