4fcc2ef2c25e0710321b9d6cc63d2a7de4716c91
[sbcl.git] / src / pcl / combin.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 (defun get-method-function (method &optional method-alist wrappers)
27   (let ((fn (cadr (assoc method method-alist))))
28     (if fn
29         (values fn nil nil nil)
30         (multiple-value-bind (mf fmf)
31             (if (listp method)
32                 (early-method-function method)
33                 (values nil (safe-method-fast-function method)))
34           (let* ((pv-table (and fmf (method-plist-value method :pv-table))))
35             (if (and fmf (or (null pv-table) wrappers))
36                 (let* ((pv-wrappers (when pv-table
37                                       (pv-wrappers-from-all-wrappers
38                                        pv-table wrappers)))
39                        (pv-cell (when (and pv-table pv-wrappers)
40                                   (pv-table-lookup pv-table pv-wrappers))))
41                   (values mf t fmf pv-cell))
42                 (values
43                  (or mf (if (listp method)
44                             (bug "early method with no method-function")
45                             (method-function method)))
46                  t nil nil)))))))
47
48 (defun make-effective-method-function (generic-function form &optional
49                                        method-alist wrappers)
50   (funcall (make-effective-method-function1 generic-function form
51                                             (not (null method-alist))
52                                             (not (null wrappers)))
53            method-alist wrappers))
54
55 (defun make-effective-method-function1 (generic-function form
56                                         method-alist-p wrappers-p)
57   (if (and (listp form)
58            (eq (car form) 'call-method))
59       (make-effective-method-function-simple generic-function form)
60       ;; We have some sort of `real' effective method. Go off and get a
61       ;; compiled function for it. Most of the real hair here is done by
62       ;; the GET-FUN mechanism.
63       (make-effective-method-function-internal generic-function form
64                                                method-alist-p wrappers-p)))
65
66 (defun make-effective-method-fun-type (generic-function
67                                        form
68                                        method-alist-p
69                                        wrappers-p)
70   (if (and (listp form)
71            (eq (car form) 'call-method))
72       (let* ((cm-args (cdr form))
73              (method (car cm-args)))
74         (when method
75           (if (if (listp method)
76                   (eq (car method) :early-method)
77                   (method-p method))
78               (if method-alist-p
79                   t
80                   (multiple-value-bind (mf fmf)
81                       (if (listp method)
82                           (early-method-function method)
83                           (values nil (safe-method-fast-function method)))
84                     (declare (ignore mf))
85                     (let* ((pv-table (and fmf (method-plist-value method :pv-table))))
86                       (if (and fmf (or (null pv-table) wrappers-p))
87                           'fast-method-call
88                           'method-call))))
89               (if (and (consp method) (eq (car method) 'make-method))
90                   (make-effective-method-fun-type
91                    generic-function (cadr method) method-alist-p wrappers-p)
92                   (type-of method)))))
93       'fast-method-call))
94
95 (defun make-effective-method-function-simple
96     (generic-function form &optional no-fmf-p)
97   ;; The effective method is just a call to CALL-METHOD. This opens up
98   ;; the possibility of just using the method function of the method as
99   ;; the effective method function.
100   ;;
101   ;; But we have to be careful. If that method function will ask for
102   ;; the next methods we have to provide them. We do not look to see
103   ;; if there are next methods, we look at whether the method function
104   ;; asks about them. If it does, we must tell it whether there are
105   ;; or aren't to prevent the leaky next methods bug.
106   (let* ((cm-args (cdr form))
107          (fmf-p (and (null no-fmf-p)
108                      (or (not (eq *boot-state* 'complete))
109                          (gf-fast-method-function-p generic-function))
110                      (null (cddr cm-args))))
111          (method (car cm-args))
112          (cm-args1 (cdr cm-args)))
113     (lambda (method-alist wrappers)
114       (make-effective-method-function-simple1 generic-function
115                                               method
116                                               cm-args1
117                                               fmf-p
118                                               method-alist
119                                               wrappers))))
120
121 (defun make-emf-from-method
122     (method cm-args &optional gf fmf-p method-alist wrappers)
123   (multiple-value-bind (mf real-mf-p fmf pv-cell)
124       (get-method-function method method-alist wrappers)
125     (if fmf
126         (let* ((next-methods (car cm-args))
127                (next (make-effective-method-function-simple1
128                       gf (car next-methods)
129                       (list* (cdr next-methods) (cdr cm-args))
130                       fmf-p method-alist wrappers))
131                (arg-info (method-plist-value method :arg-info))
132                (default (cons nil nil))
133                (value (method-plist-value method :constant-value default)))
134           (if (eq value default)
135               (make-fast-method-call :function fmf :pv-cell pv-cell
136                                      :next-method-call next :arg-info arg-info)
137               (make-constant-fast-method-call
138                :function fmf :pv-cell pv-cell :next-method-call next
139                :arg-info arg-info :value value)))
140         (if real-mf-p
141             (flet ((frob-cm-arg (arg)
142                      (if (if (listp arg)
143                              (eq (car arg) :early-method)
144                              (method-p arg))
145                          arg
146                          (if (and (consp arg) (eq (car arg) 'make-method))
147                              (let ((emf (make-effective-method-function
148                                          gf (cadr arg) method-alist wrappers)))
149                                (etypecase emf
150                                  (method-call
151                                   (make-instance 'standard-method
152                                                  :specializers nil ; XXX
153                                                  :qualifiers nil ; XXX
154                                                  :function (method-call-function emf)))
155                                  (fast-method-call
156                                   (let* ((fmf (fast-method-call-function emf))
157                                          (fun (method-function-from-fast-method-call emf))
158                                          (mf (%make-method-function fmf nil)))
159                                     (set-funcallable-instance-function mf fun)
160                                     (make-instance 'standard-method
161                                                    :specializers nil ; XXX
162                                                    :qualifiers nil
163                                                    :function mf)))))
164                              arg))))
165               (let* ((default (cons nil nil))
166                      (value
167                       (method-plist-value method :constant-value default))
168                      ;; FIXME: this is wrong.  Very wrong.  It assumes
169                      ;; that the only place that can have make-method
170                      ;; calls is in the list structure of the second
171                      ;; argument to CALL-METHOD, but AMOP says that
172                      ;; CALL-METHOD can be more complicated if
173                      ;; COMPUTE-EFFECTIVE-METHOD (and presumably
174                      ;; MAKE-METHOD-LAMBDA) is adjusted to match.
175                      ;;
176                      ;; On the other hand, it's a start, because
177                      ;; without this calls to MAKE-METHOD in method
178                      ;; combination where one of the methods is of a
179                      ;; user-defined class don't work at all.  -- CSR,
180                      ;; 2006-08-05
181                      (args (cons (mapcar #'frob-cm-arg (car cm-args))
182                                  (cdr cm-args))))
183                 (if (eq value default)
184                     (make-method-call :function mf :call-method-args args)
185                     (make-constant-method-call :function mf :value value
186                                                :call-method-args args))))
187             mf))))
188
189 (defun make-effective-method-function-simple1
190     (gf method cm-args fmf-p &optional method-alist wrappers)
191   (when method
192     (if (if (listp method)
193             (eq (car method) :early-method)
194             (method-p method))
195         (make-emf-from-method method cm-args gf fmf-p method-alist wrappers)
196         (if (and (consp method) (eq (car method) 'make-method))
197             (make-effective-method-function gf
198                                             (cadr method)
199                                             method-alist wrappers)
200             method))))
201
202 (defvar *global-effective-method-gensyms* ())
203 (defvar *rebound-effective-method-gensyms*)
204
205 (defun get-effective-method-gensym ()
206   (or (pop *rebound-effective-method-gensyms*)
207       (let ((new (format-symbol *pcl-package*
208                                 "EFFECTIVE-METHOD-GENSYM-~D"
209                                 (length *global-effective-method-gensyms*))))
210         (setq *global-effective-method-gensyms*
211               (append *global-effective-method-gensyms* (list new)))
212         new)))
213
214 (let ((*rebound-effective-method-gensyms* ()))
215   (dotimes-fixnum (i 10) (get-effective-method-gensym)))
216
217 (defun expand-effective-method-function (gf effective-method &optional env)
218   (declare (ignore env))
219   (multiple-value-bind (nreq applyp metatypes nkeys arg-info)
220       (get-generic-fun-info gf)
221     (declare (ignore nreq nkeys arg-info))
222     (let ((ll (make-fast-method-call-lambda-list metatypes applyp))
223           (check-applicable-keywords
224            (when (and applyp (gf-requires-emf-keyword-checks gf))
225              '((check-applicable-keywords))))
226           (error-p (or (eq (first effective-method) '%no-primary-method)
227                        (eq (first effective-method) '%invalid-qualifiers)))
228           (mc-args-p
229            (when (eq *boot-state* 'complete)
230              ;; Otherwise the METHOD-COMBINATION slot is not bound.
231              (let ((combin (generic-function-method-combination gf)))
232                (and (long-method-combination-p combin)
233                     (long-method-combination-args-lambda-list combin))))))
234       (cond
235         (error-p
236          `(lambda (.pv-cell. .next-method-call. &rest .args.)
237            (declare (ignore .pv-cell. .next-method-call.))
238            (declare (ignorable .args.))
239            (flet ((%no-primary-method (gf args)
240                     (apply #'no-primary-method gf args))
241                   (%invalid-qualifiers (gf combin method)
242                     (invalid-qualifiers gf combin method)))
243              (declare (ignorable #'%no-primary-method #'%invalid-qualifiers))
244              ,effective-method)))
245         (mc-args-p
246          (let* ((required (make-dfun-required-args metatypes))
247                 (gf-args (if applyp
248                              `(list* ,@required
249                                      (sb-c::%listify-rest-args
250                                       .dfun-more-context.
251                                       (the (and (unsigned-byte fixnum))
252                                         .dfun-more-count.)))
253                              `(list ,@required))))
254            `(lambda ,ll
255              (declare (ignore .pv-cell. .next-method-call.))
256              (let ((.gf-args. ,gf-args))
257                (declare (ignorable .gf-args.))
258                ,@check-applicable-keywords
259                ,effective-method))))
260         (t
261          `(lambda ,ll
262            (declare (ignore ,@(if error-p ll '(.pv-cell. .next-method-call.))))
263            ,@check-applicable-keywords
264            ,effective-method))))))
265
266 (defun expand-emf-call-method (gf form metatypes applyp env)
267   (declare (ignore gf metatypes applyp env))
268   `(call-method ,(cdr form)))
269
270 (defmacro call-method (&rest args)
271   (declare (ignore args))
272   ;; the PROGN is here to defend against premature macroexpansion by
273   ;; RESTART-CASE.
274   `(progn (error "~S outside of a effective method form" 'call-method)))
275
276 (defun make-effective-method-list-fun-type
277     (generic-function form method-alist-p wrappers-p)
278   (if (every (lambda (form)
279                (eq 'fast-method-call
280                    (make-effective-method-fun-type
281                     generic-function form method-alist-p wrappers-p)))
282              (cdr form))
283       'fast-method-call
284       t))
285
286 (defun memf-test-converter (form generic-function method-alist-p wrappers-p)
287   (case (and (consp form) (car form))
288     (call-method
289      (case (make-effective-method-fun-type
290             generic-function form method-alist-p wrappers-p)
291        (fast-method-call '.fast-call-method.)
292        (t '.call-method.)))
293     (call-method-list
294      (case (make-effective-method-list-fun-type
295             generic-function form method-alist-p wrappers-p)
296        (fast-method-call '.fast-call-method-list.)
297        (t '.call-method-list.)))
298     (check-applicable-keywords 'check-applicable-keywords)
299     (t (default-test-converter form))))
300
301 ;;; CMUCL comment (2003-10-15):
302 ;;;
303 ;;;   This function is called via the GET-FUNCTION mechanism on forms
304 ;;;   of an emf lambda.  First value returned replaces FORM in the emf
305 ;;;   lambda.  Second value is a list of variable names that become
306 ;;;   closure variables.
307 (defun memf-code-converter
308     (form generic-function metatypes applyp method-alist-p wrappers-p)
309   (case (and (consp form) (car form))
310     (call-method
311      (let ((gensym (get-effective-method-gensym)))
312        (values (make-emf-call
313                 metatypes applyp gensym
314                 (make-effective-method-fun-type
315                  generic-function form method-alist-p wrappers-p))
316                (list gensym))))
317     (call-method-list
318      (let ((gensym (get-effective-method-gensym))
319            (type (make-effective-method-list-fun-type
320                   generic-function form method-alist-p wrappers-p)))
321        (values `(dolist (emf ,gensym nil)
322                  ,(make-emf-call metatypes applyp 'emf type))
323                (list gensym))))
324     (check-applicable-keywords
325      (values `(check-applicable-keywords .keyargs-start.
326                                          .valid-keys.
327                                          .dfun-more-context.
328                                          .dfun-more-count.)
329              '(.keyargs-start. .valid-keys.)))
330     (t
331      (default-code-converter form))))
332
333 (defun memf-constant-converter (form generic-function)
334   (case (and (consp form) (car form))
335     (call-method
336      (list (cons '.meth.
337                  (make-effective-method-function-simple
338                   generic-function form))))
339     (call-method-list
340      (list (cons '.meth-list.
341                  (mapcar (lambda (form)
342                            (make-effective-method-function-simple
343                             generic-function form))
344                          (cdr form)))))
345     (check-applicable-keywords
346      '(.keyargs-start. .valid-keys.))
347     (t
348      (default-constant-converter form))))
349
350 (defvar *applicable-methods*)
351 (defun make-effective-method-function-internal
352     (generic-function effective-method method-alist-p wrappers-p)
353   (multiple-value-bind (nreq applyp metatypes nkeys arg-info)
354       (get-generic-fun-info generic-function)
355     (declare (ignore nkeys arg-info))
356     (let* ((*rebound-effective-method-gensyms*
357             *global-effective-method-gensyms*)
358            (name (if (early-gf-p generic-function)
359                      (!early-gf-name generic-function)
360                      (generic-function-name generic-function)))
361            (arg-info (cons nreq applyp))
362            (effective-method-lambda (expand-effective-method-function
363                                      generic-function effective-method)))
364       (multiple-value-bind (cfunction constants)
365           (get-fun1 effective-method-lambda
366                     (lambda (form)
367                       (memf-test-converter form generic-function
368                                            method-alist-p wrappers-p))
369                     (lambda (form)
370                       (memf-code-converter form generic-function
371                                            metatypes applyp
372                                            method-alist-p wrappers-p))
373                     (lambda (form)
374                       (memf-constant-converter form generic-function)))
375         (lambda (method-alist wrappers)
376           (multiple-value-bind (valid-keys keyargs-start)
377               (when (memq '.valid-keys. constants)
378                 (compute-applicable-keywords
379                  generic-function *applicable-methods*))
380             (flet ((compute-constant (constant)
381                      (if (consp constant)
382                          (case (car constant)
383                            (.meth.
384                             (funcall (cdr constant) method-alist wrappers))
385                            (.meth-list.
386                             (mapcar (lambda (fn)
387                                       (funcall fn method-alist wrappers))
388                                     (cdr constant)))
389                            (t constant))
390                          (case constant
391                            (.keyargs-start. keyargs-start)
392                            (.valid-keys. valid-keys)
393                            (t constant)))))
394               (let ((fun (apply cfunction
395                                 (mapcar #'compute-constant constants))))
396                 (set-fun-name fun `(combined-method ,name))
397                 (make-fast-method-call :function fun
398                                        :arg-info arg-info)))))))))
399
400 (defmacro call-method-list (&rest calls)
401   `(progn ,@calls))
402
403 (defun make-call-methods (methods)
404   `(call-method-list
405     ,@(mapcar (lambda (method) `(call-method ,method ())) methods)))
406
407 (defun gf-requires-emf-keyword-checks (generic-function)
408   (member '&key (gf-lambda-list generic-function)))
409
410 (defvar *in-precompute-effective-methods-p* nil)
411
412 (defun standard-compute-effective-method
413     (generic-function combin applicable-methods)
414   (collect ((before) (primary) (after) (around))
415     (flet ((invalid (gf combin m)
416              (if *in-precompute-effective-methods-p*
417                  (return-from standard-compute-effective-method
418                    `(%invalid-qualifiers ',gf ',combin ',m))
419                  (invalid-qualifiers gf combin m))))
420       (dolist (m applicable-methods)
421         (let ((qualifiers (if (listp m)
422                               (early-method-qualifiers m)
423                               (method-qualifiers m))))
424           (cond
425             ((null qualifiers) (primary m))
426             ((cdr qualifiers) (invalid generic-function combin m))
427             ((eq (car qualifiers) :around) (around m))
428             ((eq (car qualifiers) :before) (before m))
429             ((eq (car qualifiers) :after) (after m))
430             (t (invalid generic-function combin m))))))
431     (cond ((null (primary))
432            `(%no-primary-method ',generic-function .args.))
433           ((and (null (before)) (null (after)) (null (around)))
434            ;; By returning a single call-method `form' here we enable
435            ;; an important implementation-specific optimization; that
436            ;; is, we can use the fast method function directly as the
437            ;; effective method function.
438            ;;
439            ;; However, the requirement by ANSI (CLHS 7.6.5) on generic
440            ;; function argument checking inhibits this, as we don't
441            ;; perform this checking in fast-method-functions given
442            ;; that they are not solely used for effective method
443            ;; functions, but also in combination, when they should not
444            ;; perform argument checks.
445            (let ((call-method
446                   `(call-method ,(first (primary)) ,(rest (primary)))))
447              (if (gf-requires-emf-keyword-checks generic-function)
448                  ;; the PROGN inhibits the above optimization
449                  `(progn ,call-method)
450                  call-method)))
451           (t
452            (let ((main-effective-method
453                    (if (or (before) (after))
454                        `(multiple-value-prog1
455                           (progn
456                             ,(make-call-methods (before))
457                             (call-method ,(first (primary))
458                                          ,(rest (primary))))
459                           ,(make-call-methods (reverse (after))))
460                        `(call-method ,(first (primary)) ,(rest (primary))))))
461              (if (around)
462                  `(call-method ,(first (around))
463                                (,@(rest (around))
464                                   (make-method ,main-effective-method)))
465                  main-effective-method))))))
466 \f
467 ;;; helper code for checking keywords in generic function calls.
468 (defun compute-applicable-keywords (gf methods)
469   (let ((any-keyp nil))
470     (flet ((analyze (lambda-list)
471              (multiple-value-bind (nreq nopt keyp restp allowp keys)
472                  (analyze-lambda-list lambda-list)
473                (declare (ignore nreq restp))
474                (when keyp
475                  (setq any-keyp t))
476                (values nopt allowp keys))))
477       (multiple-value-bind (nopt allowp keys)
478           (analyze (generic-function-lambda-list gf))
479         (dolist (method methods)
480           (let ((ll (if (consp method)
481                         (early-method-lambda-list method)
482                         (method-lambda-list method))))
483             (multiple-value-bind (n allowp method-keys)
484                 (analyze ll)
485               (declare (ignore n))
486               (when allowp
487                 (return-from compute-applicable-keywords (values t nopt)))
488               (setq keys (union method-keys keys)))))
489         (aver any-keyp)
490         (values (if allowp t keys) nopt)))))
491
492 (defun check-applicable-keywords (start valid-keys more-context more-count)
493   (let ((allow-other-keys-seen nil)
494         (allow-other-keys nil)
495         (i start))
496     (declare (type index i more-count)
497              (optimize speed))
498     (flet ((current-value ()
499              (sb-c::%more-arg more-context i)))
500       (declare (inline current-value))
501       (collect ((invalid))
502         (loop
503            (when (>= i more-count)
504              (when (and (invalid) (not allow-other-keys))
505                (error 'simple-program-error
506                       :format-control "~@<invalid keyword argument~P: ~
507                                    ~{~S~^, ~} (valid keys are ~{~S~^, ~}).~@:>"
508                       :format-arguments (list (length (invalid)) (invalid) valid-keys)))
509              (return))
510            (let ((key (current-value)))
511              (incf i)
512              (cond
513                ((not (symbolp key))
514                 (error 'simple-program-error
515                        :format-control "~@<keyword argument not a symbol: ~S.~@:>"
516                        :format-arguments (list key)))
517                ((= i more-count)
518                 (sb-c::%odd-key-args-error))
519                ((eq key :allow-other-keys)
520                 ;; only the leftmost :ALLOW-OTHER-KEYS has any effect
521                 (unless allow-other-keys-seen
522                   (setq allow-other-keys-seen t
523                         allow-other-keys (current-value))))
524                ((eq t valid-keys))
525                ((not (memq key valid-keys)) (invalid key))))
526            (incf i))))))
527 \f
528 ;;;; the STANDARD method combination type. This is coded by hand
529 ;;;; (rather than with DEFINE-METHOD-COMBINATION) for bootstrapping
530 ;;;; and efficiency reasons. Note that the definition of the
531 ;;;; FIND-METHOD-COMBINATION-METHOD appears in the file
532 ;;;; defcombin.lisp. This is because EQL methods can't appear in the
533 ;;;; bootstrap.
534 ;;;;
535 ;;;; The DEFCLASS for the METHOD-COMBINATION and
536 ;;;; STANDARD-METHOD-COMBINATION classes has to appear here for this
537 ;;;; reason. This code must conform to the code in the file
538 ;;;; defcombin.lisp, look there for more details.
539
540 (defun compute-effective-method (generic-function combin applicable-methods)
541   (standard-compute-effective-method generic-function
542                                      combin
543                                      applicable-methods))
544
545 (defun invalid-method-error (method format-control &rest format-arguments)
546   (let ((sb-debug:*stack-top-hint* (nth-value 1 (find-caller-name-and-frame))))
547     (error "~@<invalid method error for ~2I~_~S ~I~_method: ~2I~_~?~:>"
548            method
549            format-control
550            format-arguments)))
551
552 (defun method-combination-error (format-control &rest format-arguments)
553   (let ((sb-debug:*stack-top-hint* (nth-value 1 (find-caller-name-and-frame))))
554     (error "~@<method combination error in CLOS dispatch: ~2I~_~?~:>"
555            format-control
556            format-arguments)))