Initial revision
[sbcl.git] / src / pcl / boot.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
26 (sb-int:file-comment
27  "$Header$")
28 \f
29 #|
30
31 The CommonLoops evaluator is meta-circular.
32
33 Most of the code in PCL is methods on generic functions, including
34 most of the code that actually implements generic functions and method
35 lookup.
36
37 So, we have a classic bootstrapping problem. The solution to this is
38 to first get a cheap implementation of generic functions running,
39 these are called early generic functions. These early generic
40 functions and the corresponding early methods and early method lookup
41 are used to get enough of the system running that it is possible to
42 create real generic functions and methods and implement real method
43 lookup. At that point (done in the file FIXUP) the function
44 fix-early-generic-functions is called to convert all the early generic
45 functions to real generic functions.
46
47 The cheap generic functions are built using the same
48 funcallable-instance objects real generic-functions are made out of.
49 This means that as PCL is being bootstrapped, the cheap generic
50 function objects which are being created are the same objects which
51 will later be real generic functions. This is good because:
52   - we don't cons garbage structure, and
53   - we can keep pointers to the cheap generic function objects
54     during booting because those pointers will still point to
55     the right object after the generic functions are all fixed up.
56
57 This file defines the defmethod macro and the mechanism used to expand
58 it. This includes the mechanism for processing the body of a method.
59 DEFMETHOD basically expands into a call to LOAD-DEFMETHOD, which
60 basically calls ADD-METHOD to add the method to the generic-function.
61 These expansions can be loaded either during bootstrapping or when PCL
62 is fully up and running.
63
64 An important effect of this arrangement is it means we can compile
65 files with defmethod forms in them in a completely running PCL, but
66 then load those files back in during bootstrapping. This makes
67 development easier. It also means there is only one set of code for
68 processing defmethod. Bootstrapping works by being sure to have
69 load-method be careful to call only primitives which work during
70 bootstrapping.
71
72 |#
73
74 ;;; FIXME: SB-KERNEL::PCL-CHECK-WRAPPER-VALIDITY-HOOK shouldn't be a
75 ;;; separate function. Instead, we should define a simple placeholder
76 ;;; version of SB-PCL:CHECK-WRAPPER-VALIDITY where
77 ;;; SB-KERNEL::PCL-CHECK-WRAPPER-VALIDITY is defined now, then just
78 ;;; let the later real PCL DEFUN of SB-PCL:CHECK-WRAPPER-VALIDITY
79 ;;; overwrite it.
80 (setf (symbol-function 'sb-kernel::pcl-check-wrapper-validity-hook)
81       #'check-wrapper-validity)
82
83 (declaim (notinline make-a-method
84                     add-named-method
85                     ensure-generic-function-using-class
86
87                     add-method
88                     remove-method))
89
90 (defvar *early-functions*
91         '((make-a-method early-make-a-method
92                          real-make-a-method)
93           (add-named-method early-add-named-method
94                             real-add-named-method)
95           ))
96
97 ;;; For each of the early functions, arrange to have it point to its early
98 ;;; definition. Do this in a way that makes sure that if we redefine one
99 ;;; of the early definitions the redefinition will take effect. This makes
100 ;;; development easier.
101 ;;;
102 ;;; The function which generates the redirection closure is pulled out into
103 ;;; a separate piece of code because of a bug in ExCL which causes this not
104 ;;; to work if it is inlined.
105 ;;; FIXME: We no longer need to worry about ExCL now, so we could unscrew this.
106 (eval-when (:load-toplevel :execute)
107
108 (defun redirect-early-function-internal (real early)
109   (setf (gdefinition real)
110         (set-function-name
111          #'(lambda (&rest args)
112              (apply (the function (symbol-function early)) args))
113          real)))
114
115 (dolist (fns *early-functions*)
116   (let ((name (car fns))
117         (early-name (cadr fns)))
118     (redirect-early-function-internal name early-name)))
119
120 ) ; EVAL-WHEN
121
122 ;;; *GENERIC-FUNCTION-FIXUPS* is used by fix-early-generic-functions to
123 ;;; convert the few functions in the bootstrap which are supposed to be
124 ;;; generic functions but can't be early on.
125 (defvar *generic-function-fixups*
126   '((add-method
127      ((generic-function method)  ;lambda-list
128       (standard-generic-function method) ;specializers
129       real-add-method))          ;method-function
130     (remove-method
131      ((generic-function method)
132       (standard-generic-function method)
133       real-remove-method))
134     (get-method
135      ((generic-function qualifiers specializers &optional (errorp t))
136       (standard-generic-function t t)
137       real-get-method))
138     (ensure-generic-function-using-class
139      ((generic-function function-name
140                         &key generic-function-class environment
141                         &allow-other-keys)
142       (generic-function t)
143       real-ensure-gf-using-class--generic-function)
144      ((generic-function function-name
145                         &key generic-function-class environment
146                         &allow-other-keys)
147       (null t)
148       real-ensure-gf-using-class--null))
149     (make-method-lambda
150      ((proto-generic-function proto-method lambda-expression environment)
151       (standard-generic-function standard-method t t)
152       real-make-method-lambda))
153     (make-method-initargs-form
154      ((proto-generic-function proto-method
155                               lambda-expression
156                               lambda-list environment)
157       (standard-generic-function standard-method t t t)
158       real-make-method-initargs-form))
159     (compute-effective-method
160      ((generic-function combin applicable-methods)
161       (generic-function standard-method-combination t)
162       standard-compute-effective-method))))
163 \f
164 (defmacro defgeneric (function-name lambda-list &body options)
165   (expand-defgeneric function-name lambda-list options))
166
167 (defun expand-defgeneric (function-name lambda-list options)
168   (when (listp function-name)
169     (do-standard-defsetf-1 (sb-int:function-name-block-name function-name)))
170   (let ((initargs ())
171         (methods ()))
172     (flet ((duplicate-option (name)
173              (error 'sb-kernel:simple-program-error
174                     :format-control "The option ~S appears more than once."
175                     :format-arguments (list name)))
176            (expand-method-definition (qab) ; QAB = qualifiers, arglist, body
177              (let* ((arglist-pos (position-if #'listp qab))
178                     (arglist (elt qab arglist-pos))
179                     (qualifiers (subseq qab 0 arglist-pos))
180                     (body (nthcdr (1+ arglist-pos) qab)))
181                (when (not (equal (cadr (getf initargs :method-combination))
182                                  qualifiers))
183                  (error "bad method specification in DEFGENERIC ~A~%~
184                          -- qualifier mismatch for lambda list ~A"
185                         function-name arglist))
186                `(defmethod ,function-name ,@qualifiers ,arglist ,@body))))
187       (macrolet ((initarg (key) `(getf initargs ,key)))
188         (dolist (option options)
189           (let ((car-option (car option)))
190             (case car-option
191               (declare
192                (push (cdr option) (initarg :declarations)))
193               ((:argument-precedence-order :method-combination)
194                (if (initarg car-option)
195                    (duplicate-option car-option)
196                    (setf (initarg car-option)
197                          `',(cdr option))))
198               ((:documentation :generic-function-class :method-class)
199                (unless (sb-int:proper-list-of-length-p option 2)
200                  (error "bad list length for ~S" option))
201                (if (initarg car-option)
202                    (duplicate-option car-option)
203                    (setf (initarg car-option) `',(cadr option))))
204               (:method
205                (push (cdr option) methods))
206               (t
207                ;; ANSI requires that unsupported things must get a
208                ;; PROGRAM-ERROR.
209                (error 'sb-kernel:simple-program-error
210                       :format-control "unsupported option ~S"
211                       :format-arguments (list option))))))
212
213         (when (initarg :declarations)
214           (setf (initarg :declarations)
215                 `',(initarg :declarations))))
216       `(progn
217          (eval-when (:compile-toplevel :load-toplevel :execute)
218            (compile-or-load-defgeneric ',function-name))
219          ,(make-top-level-form
220            `(defgeneric ,function-name)
221            *defgeneric-times*
222            `(load-defgeneric ',function-name ',lambda-list ,@initargs))
223          ,@(mapcar #'expand-method-definition methods)
224          `,(function ,function-name)))))
225
226 (defun compile-or-load-defgeneric (function-name)
227   (sb-kernel:proclaim-as-function-name function-name)
228   (sb-kernel:note-name-defined function-name :function)
229   (unless (eq (sb-int:info :function :where-from function-name) :declared)
230     (setf (sb-int:info :function :where-from function-name) :defined)
231     (setf (sb-int:info :function :type function-name)
232           (sb-kernel:specifier-type 'function))))
233
234 (defun load-defgeneric (function-name lambda-list &rest initargs)
235   (when (listp function-name)
236     (do-standard-defsetf-1 (cadr function-name)))
237   (when (fboundp function-name)
238     (sb-kernel::style-warn "redefining ~S in DEFGENERIC" function-name))
239   (apply #'ensure-generic-function
240          function-name
241          :lambda-list lambda-list
242          :definition-source `((defgeneric ,function-name)
243                               ,*load-truename*)
244          initargs))
245 \f
246 (defmacro defmethod (&rest args &environment env)
247   (declare (arglist name
248                     {method-qualifier}*
249                     specialized-lambda-list
250                     &body body))
251   (multiple-value-bind (name qualifiers lambda-list body)
252       (parse-defmethod args)
253     (multiple-value-bind (proto-gf proto-method)
254         (prototypes-for-make-method-lambda name)
255       (expand-defmethod name
256                         proto-gf
257                         proto-method
258                         qualifiers
259                         lambda-list
260                         body
261                         env))))
262
263 (defun prototypes-for-make-method-lambda (name)
264   (if (not (eq *boot-state* 'complete))
265       (values nil nil)
266       (let ((gf? (and (gboundp name)
267                       (gdefinition name))))
268         (if (or (null gf?)
269                 (not (generic-function-p gf?)))
270             (values (class-prototype (find-class 'standard-generic-function))
271                     (class-prototype (find-class 'standard-method)))
272             (values gf?
273                     (class-prototype (or (generic-function-method-class gf?)
274                                          (find-class 'standard-method))))))))
275
276 ;;; takes a name which is either a generic function name or a list specifying
277 ;;; a setf generic function (like: (SETF <generic-function-name>)). Returns
278 ;;; the prototype instance of the method-class for that generic function.
279 ;;;
280 ;;; If there is no generic function by that name, this returns the default
281 ;;; value, the prototype instance of the class STANDARD-METHOD. This default
282 ;;; value is also returned if the spec names an ordinary function or even a
283 ;;; macro. In effect, this leaves the signalling of the appropriate error
284 ;;; until load time.
285 ;;;
286 ;;; Note: During bootstrapping, this function is allowed to return NIL.
287 (defun method-prototype-for-gf (name)
288   (let ((gf? (and (gboundp name)
289                   (gdefinition name))))
290     (cond ((neq *boot-state* 'complete) nil)
291           ((or (null gf?)
292                (not (generic-function-p gf?)))          ; Someone else MIGHT
293                                                         ; error at load time.
294            (class-prototype (find-class 'standard-method)))
295           (t
296             (class-prototype (or (generic-function-method-class gf?)
297                                  (find-class 'standard-method)))))))
298 \f
299 (defvar *optimize-asv-funcall-p* nil)
300 (defvar *asv-readers*)
301 (defvar *asv-writers*)
302 (defvar *asv-boundps*)
303
304 (defun expand-defmethod (name
305                          proto-gf
306                          proto-method
307                          qualifiers
308                          lambda-list
309                          body
310                          env)
311   (when (listp name)
312     (do-standard-defsetf-1 (cadr name)))
313   (let ((*make-instance-function-keys* nil)
314         (*optimize-asv-funcall-p* t)
315         (*asv-readers* nil) (*asv-writers* nil) (*asv-boundps* nil))
316     (declare (special *make-instance-function-keys*))
317     (multiple-value-bind (method-lambda unspecialized-lambda-list specializers)
318         (add-method-declarations name qualifiers lambda-list body env)
319       (multiple-value-bind (method-function-lambda initargs)
320           (make-method-lambda proto-gf proto-method method-lambda env)
321         (let ((initargs-form (make-method-initargs-form proto-gf
322                                                         proto-method
323                                                         method-function-lambda
324                                                         initargs
325                                                         env)))
326           `(progn
327              ;; Note: We could DECLAIM the type of the generic
328              ;; function here, since ANSI specifies that we create it
329              ;; if it does not exist. However, I chose not to, because
330              ;; I think it's more useful to support a style of
331              ;; programming where every generic function has an
332              ;; explicit DEFGENERIC and any typos in DEFMETHODs are
333              ;; warned about. Otherwise
334              ;;   (DEFGENERIC FOO-BAR-BLETCH ((X T)))
335              ;;   (DEFMETHOD FOO-BAR-BLETCH ((X HASH-TABLE)) ..)
336              ;;   (DEFMETHOD FOO-BRA-BLETCH ((X SIMPLE-VECTOR)) ..)
337              ;;   (DEFMETHOD FOO-BAR-BLETCH ((X VECTOR)) ..)
338              ;;   (DEFMETHOD FOO-BAR-BLETCH ((X ARRAY)) ..)
339              ;;   (DEFMETHOD FOO-BAR-BLETCH ((X LIST)) ..)
340              ;; compiles without raising an error and runs without
341              ;; raising an error (since SIMPLE-VECTOR cases fall
342              ;; through to VECTOR) but still doesn't do what was
343              ;; intended. I hate that kind of bug (code which silently
344              ;; gives the wrong answer), so we don't do a DECLAIM
345              ;; here. -- WHN 20000229
346              ,@(when *make-instance-function-keys*
347                  `((get-make-instance-functions
348                     ',*make-instance-function-keys*)))
349              ,@(when (or *asv-readers* *asv-writers* *asv-boundps*)
350                  `((initialize-internal-slot-gfs*
351                     ',*asv-readers* ',*asv-writers* ',*asv-boundps*)))
352              ,(make-defmethod-form name qualifiers specializers
353                                    unspecialized-lambda-list
354                                    (if proto-method
355                                        (class-name (class-of proto-method))
356                                        'standard-method)
357                                    initargs-form
358                                    (getf (getf initargs ':plist)
359                                          ':pv-table-symbol))))))))
360
361 (defun interned-symbol-p (x)
362   (and (symbolp x) (symbol-package x)))
363
364 (defun make-defmethod-form (name qualifiers specializers
365                                  unspecialized-lambda-list method-class-name
366                                  initargs-form &optional pv-table-symbol)
367   (let (fn
368         fn-lambda)
369     (if (and (interned-symbol-p (sb-int:function-name-block-name name))
370              (every #'interned-symbol-p qualifiers)
371              (every #'(lambda (s)
372                         (if (consp s)
373                             (and (eq (car s) 'eql)
374                                  (constantp (cadr s))
375                                  (let ((sv (eval (cadr s))))
376                                    (or (interned-symbol-p sv)
377                                        (integerp sv)
378                                        (and (characterp sv)
379                                             (standard-char-p sv)))))
380                             (interned-symbol-p s)))
381                     specializers)
382              (consp initargs-form)
383              (eq (car initargs-form) 'list*)
384              (memq (cadr initargs-form) '(:function :fast-function))
385              (consp (setq fn (caddr initargs-form)))
386              (eq (car fn) 'function)
387              (consp (setq fn-lambda (cadr fn)))
388              (eq (car fn-lambda) 'lambda))
389         (let* ((specls (mapcar (lambda (specl)
390                                  (if (consp specl)
391                                      `(,(car specl) ,(eval (cadr specl)))
392                                    specl))
393                                specializers))
394                (mname `(,(if (eq (cadr initargs-form) ':function)
395                              'method 'fast-method)
396                         ,name ,@qualifiers ,specls))
397                (mname-sym (intern (let ((*print-pretty* nil))
398                                     (format nil "~S" mname)))))
399           `(eval-when ,*defmethod-times*
400             (defun ,mname-sym ,(cadr fn-lambda)
401               ,@(cddr fn-lambda))
402             ,(make-defmethod-form-internal
403               name qualifiers `',specls
404               unspecialized-lambda-list method-class-name
405               `(list* ,(cadr initargs-form)
406                       #',mname-sym
407                       ,@(cdddr initargs-form))
408               pv-table-symbol)))
409         (make-top-level-form
410          `(defmethod ,name ,@qualifiers ,specializers)
411          *defmethod-times*
412          (make-defmethod-form-internal
413           name qualifiers
414           `(list ,@(mapcar #'(lambda (specializer)
415                                (if (consp specializer)
416                                    ``(,',(car specializer)
417                                       ,,(cadr specializer))
418                                    `',specializer))
419                     specializers))
420           unspecialized-lambda-list method-class-name
421           initargs-form
422           pv-table-symbol)))))
423
424 (defun make-defmethod-form-internal
425     (name qualifiers specializers-form unspecialized-lambda-list
426      method-class-name initargs-form &optional pv-table-symbol)
427   `(load-defmethod
428     ',method-class-name
429     ',name
430     ',qualifiers
431     ,specializers-form
432     ',unspecialized-lambda-list
433     ,initargs-form
434     ;; Paper over a bug in KCL by passing the cache-symbol here in addition to
435     ;; in the list. FIXME: We should no longer need to do this.
436     ',pv-table-symbol))
437
438 (defmacro make-method-function (method-lambda &environment env)
439   (make-method-function-internal method-lambda env))
440
441 (defun make-method-function-internal (method-lambda &optional env)
442   (multiple-value-bind (proto-gf proto-method)
443       (prototypes-for-make-method-lambda nil)
444     (multiple-value-bind (method-function-lambda initargs)
445         (make-method-lambda proto-gf proto-method method-lambda env)
446       (make-method-initargs-form proto-gf
447                                  proto-method
448                                  method-function-lambda
449                                  initargs
450                                  env))))
451
452 (defun add-method-declarations (name qualifiers lambda-list body env)
453   (multiple-value-bind (parameters unspecialized-lambda-list specializers)
454       (parse-specialized-lambda-list lambda-list)
455     (declare (ignore parameters))
456     (multiple-value-bind (documentation declarations real-body)
457         (extract-declarations body env)
458       (values `(lambda ,unspecialized-lambda-list
459                  ,@(when documentation `(,documentation))
460                  (declare (method-name ,(list name qualifiers specializers)))
461                  (declare (method-lambda-list ,@lambda-list))
462                  ,@declarations
463                  ,@real-body)
464               unspecialized-lambda-list specializers))))
465
466 (defun real-make-method-initargs-form (proto-gf proto-method
467                                        method-lambda initargs env)
468   (declare (ignore proto-gf proto-method))
469   (unless (and (consp method-lambda) (eq (car method-lambda) 'lambda))
470     (error "The METHOD-LAMBDA argument to MAKE-METHOD-FUNCTION, ~S,~
471             is not a lambda form."
472            method-lambda))
473   (make-method-initargs-form-internal method-lambda initargs env))
474
475 (unless (fboundp 'make-method-initargs-form)
476   (setf (gdefinition 'make-method-initargs-form)
477         (symbol-function 'real-make-method-initargs-form)))
478
479 (defun real-make-method-lambda (proto-gf proto-method method-lambda env)
480   (declare (ignore proto-gf proto-method))
481   (make-method-lambda-internal method-lambda env))
482
483 (defun make-method-lambda-internal (method-lambda &optional env)
484   (unless (and (consp method-lambda) (eq (car method-lambda) 'lambda))
485     (error "The METHOD-LAMBDA argument to MAKE-METHOD-LAMBDA, ~S,~
486             is not a lambda form."
487            method-lambda))
488   (multiple-value-bind (documentation declarations real-body)
489       (extract-declarations (cddr method-lambda) env)
490     (let* ((name-decl (get-declaration 'method-name declarations))
491            (sll-decl (get-declaration 'method-lambda-list declarations))
492            (method-name (when (consp name-decl) (car name-decl)))
493            (generic-function-name (when method-name (car method-name)))
494            (specialized-lambda-list (or sll-decl (cadr method-lambda))))
495       (multiple-value-bind (parameters lambda-list specializers)
496           (parse-specialized-lambda-list specialized-lambda-list)
497         (let* ((required-parameters
498                 (mapcar #'(lambda (r s) (declare (ignore s)) r)
499                         parameters
500                         specializers))
501                (slots (mapcar #'list required-parameters))
502                (calls (list nil))
503                (parameters-to-reference
504                 (make-parameter-references specialized-lambda-list
505                                            required-parameters
506                                            declarations
507                                            method-name
508                                            specializers))
509                (class-declarations
510                 `(declare
511                   ;; FIXME: Are these (DECLARE (SB-PCL::CLASS FOO BAR))
512                   ;; declarations used for anything any more?
513                   ,@(remove nil
514                             (mapcar (lambda (a s) (and (symbolp s)
515                                                        (neq s 't)
516                                                        `(class ,a ,s)))
517                                     parameters
518                                     specializers))
519                   ;; These TYPE declarations weren't in the original
520                   ;; PCL code, but Python likes them a lot. (We're
521                   ;; telling the compiler about our knowledge of
522                   ;; specialized argument types so that it can avoid
523                   ;; run-time type overhead, which can be a big win
524                   ;; for Python.)
525                   ,@(mapcar (lambda (a s)
526                               (cond ((and (consp s)
527                                           (eql (car s) 'eql))
528                                      ;; KLUDGE: ANSI, in its wisdom, says
529                                      ;; that EQL-SPECIALIZER-FORMs in EQL
530                                      ;; specializers are evaluated at
531                                      ;; DEFMETHOD expansion time. Thus,
532                                      ;; although one might think that in
533                                      ;;   (DEFMETHOD FOO ((X PACKAGE)
534                                      ;;                   (Y (EQL 12))
535                                      ;;      ..))
536                                      ;; the PACKAGE and (EQL 12) forms are
537                                      ;; both parallel type names, they're
538                                      ;; not, as is made clear when you do
539                                      ;;   (DEFMETHOD FOO ((X PACKAGE)
540                                      ;;                   (Y (EQL 'BAR)))
541                                      ;;     ..)
542                                      ;; where Y needs to be a symbol
543                                      ;; named "BAR", not some cons made by
544                                      ;; (CONS 'QUOTE 'BAR). I.e. when
545                                      ;; the EQL-SPECIALIZER-FORM is (EQL 'X),
546                                      ;; it requires an argument to be of
547                                      ;; type (EQL X). It'd be easy to transform
548                                      ;; one to the other, but it'd be somewhat
549                                      ;; messier to do so while ensuring that
550                                      ;; the EQL-SPECIALIZER-FORM is only
551                                      ;; EVAL'd once. (The new code wouldn't
552                                      ;; be messy, but it'd require a big
553                                      ;; transformation of the old code.)
554                                      ;; So instead we punt. -- WHN 20000610
555                                      '(ignorable))
556                                     ((not (eq *boot-state* 'complete))
557                                      ;; KLUDGE: PCL, in its wisdom, 
558                                      ;; sometimes calls methods with
559                                      ;; types which don't match their
560                                      ;; specializers. (Specifically, it calls
561                                      ;; ENSURE-CLASS-USING-CLASS (T NULL)
562                                      ;; with a non-NULL second argument.)
563                                      ;; Hopefully it only does this kind
564                                      ;; of weirdness when bootstrapping..
565                                      ;; -- WHN 20000610
566                                      '(ignorable))
567                                     (t
568                                      ;; Otherwise, we can make Python
569                                      ;; very happy.
570                                      `(type ,s ,a))))
571                             parameters
572                             specializers)))
573                (method-lambda
574                 ;; Remove the documentation string and insert the
575                 ;; appropriate class declarations. The documentation
576                 ;; string is removed to make it easy for us to insert
577                 ;; new declarations later, they will just go after the
578                 ;; cadr of the method lambda. The class declarations
579                 ;; are inserted to communicate the class of the method's
580                 ;; arguments to the code walk.
581                 `(lambda ,lambda-list
582                    ,class-declarations
583                    ,@declarations
584                    (declare (ignorable ,@parameters-to-reference))
585
586                    ;; FIXME: should become FUNCTION-NAME-BLOCK-NAME
587                    (block ,(if (listp generic-function-name)
588                                (cadr generic-function-name)
589                              generic-function-name)
590                      ,@real-body)))
591                (constant-value-p (and (null (cdr real-body))
592                                       (constantp (car real-body))))
593                (constant-value (and constant-value-p
594                                     (eval (car real-body))))
595                ;; FIXME: This can become a bare AND (no IF), just like
596                ;; the expression for CONSTANT-VALUE just above.
597                (plist (if (and constant-value-p
598                                (or (typep constant-value
599                                           '(or number character))
600                                    (and (symbolp constant-value)
601                                         (symbol-package constant-value))))
602                           (list :constant-value constant-value)
603                           ()))
604                (applyp (dolist (p lambda-list nil)
605                          (cond ((memq p '(&optional &rest &key))
606                                 (return t))
607                                ((eq p '&aux)
608                                 (return nil))))))
609           (multiple-value-bind
610               (walked-lambda call-next-method-p closurep next-method-p-p)
611               (walk-method-lambda method-lambda
612                                   required-parameters
613                                   env
614                                   slots
615                                   calls)
616             (multiple-value-bind
617                 (ignore walked-declarations walked-lambda-body)
618                 (extract-declarations (cddr walked-lambda))
619               (declare (ignore ignore))
620               (when (or next-method-p-p call-next-method-p)
621                 (setq plist (list* :needs-next-methods-p 't plist)))
622               (when (some #'cdr slots)
623                 (multiple-value-bind (slot-name-lists call-list)
624                     (slot-name-lists-from-slots slots calls)
625                   (let ((pv-table-symbol (make-symbol "pv-table")))
626                     (setq plist
627                           `(,@(when slot-name-lists
628                                 `(:slot-name-lists ,slot-name-lists))
629                               ,@(when call-list
630                                   `(:call-list ,call-list))
631                               :pv-table-symbol ,pv-table-symbol
632                               ,@plist))
633                     (setq walked-lambda-body
634                           `((pv-binding (,required-parameters
635                                          ,slot-name-lists
636                                          ,pv-table-symbol)
637                                         ,@walked-lambda-body))))))
638               (when (and (memq '&key lambda-list)
639                          (not (memq '&allow-other-keys lambda-list)))
640                 (let ((aux (memq '&aux lambda-list)))
641                 (setq lambda-list (nconc (ldiff lambda-list aux)
642                                          (list '&allow-other-keys)
643                                          aux))))
644               (values `(lambda (.method-args. .next-methods.)
645                          (simple-lexical-method-functions
646                           (,lambda-list .method-args. .next-methods.
647                                         :call-next-method-p
648                                         ,call-next-method-p
649                                         :next-method-p-p ,next-method-p-p
650                                         :closurep ,closurep
651                                         :applyp ,applyp)
652                           ,@walked-declarations
653                           ,@walked-lambda-body))
654                       `(,@(when plist
655                       `(:plist ,plist))
656                           ,@(when documentation
657                           `(:documentation ,documentation)))))))))))
658
659 (unless (fboundp 'make-method-lambda)
660   (setf (gdefinition 'make-method-lambda)
661         (symbol-function 'real-make-method-lambda)))
662
663 (defmacro simple-lexical-method-functions ((lambda-list
664                                             method-args
665                                             next-methods
666                                             &rest lmf-options)
667                                            &body body)
668   `(progn
669      ,method-args ,next-methods
670      (bind-simple-lexical-method-macros (,method-args ,next-methods)
671        (bind-lexical-method-functions (,@lmf-options)
672          (bind-args (,lambda-list ,method-args)
673            ,@body)))))
674
675 (defmacro fast-lexical-method-functions ((lambda-list
676                                           next-method-call
677                                           args
678                                           rest-arg
679                                           &rest lmf-options)
680                                          &body body)
681  `(bind-fast-lexical-method-macros (,args ,rest-arg ,next-method-call)
682     (bind-lexical-method-functions (,@lmf-options)
683       (bind-args (,(nthcdr (length args) lambda-list) ,rest-arg)
684         ,@body))))
685
686 (defmacro bind-simple-lexical-method-macros ((method-args next-methods)
687                                              &body body)
688   `(macrolet ((call-next-method-bind (&body body)
689                 `(let ((.next-method. (car ,',next-methods))
690                        (,',next-methods (cdr ,',next-methods)))
691                    .next-method. ,',next-methods
692                    ,@body))
693               (call-next-method-body (cnm-args)
694                 `(if .next-method.
695                      (funcall (if (std-instance-p .next-method.)
696                                   (method-function .next-method.)
697                                   .next-method.) ; for early methods
698                               (or ,cnm-args ,',method-args)
699                               ,',next-methods)
700                      (error "no next method")))
701               (next-method-p-body ()
702                 `(not (null .next-method.))))
703      ,@body))
704
705 (defstruct method-call
706   (function #'identity :type function)
707   call-method-args)
708
709 #-sb-fluid (declaim (sb-ext:freeze-type method-call))
710
711 (defmacro invoke-method-call1 (function args cm-args)
712   `(let ((.function. ,function)
713          (.args. ,args)
714          (.cm-args. ,cm-args))
715      (if (and .cm-args. (null (cdr .cm-args.)))
716          (funcall .function. .args. (car .cm-args.))
717          (apply .function. .args. .cm-args.))))
718
719 (defmacro invoke-method-call (method-call restp &rest required-args+rest-arg)
720   `(invoke-method-call1 (method-call-function ,method-call)
721                         ,(if restp
722                              `(list* ,@required-args+rest-arg)
723                              `(list ,@required-args+rest-arg))
724                         (method-call-call-method-args ,method-call)))
725
726 (defstruct fast-method-call
727   (function #'identity :type function)
728   pv-cell
729   next-method-call
730   arg-info)
731
732 #-sb-fluid (declaim (sb-ext:freeze-type fast-method-call))
733
734 (defmacro fmc-funcall (fn pv-cell next-method-call &rest args)
735   `(funcall ,fn ,pv-cell ,next-method-call ,@args))
736
737 (defmacro invoke-fast-method-call (method-call &rest required-args+rest-arg)
738   `(fmc-funcall (fast-method-call-function ,method-call)
739                 (fast-method-call-pv-cell ,method-call)
740                 (fast-method-call-next-method-call ,method-call)
741                 ,@required-args+rest-arg))
742
743 (defstruct fast-instance-boundp
744   (index 0 :type fixnum))
745
746 #-sb-fluid (declaim (sb-ext:freeze-type fast-instance-boundp))
747
748 (eval-when (:compile-toplevel :load-toplevel :execute)
749
750 (defvar *allow-emf-call-tracing-p* nil)
751 (defvar *enable-emf-call-tracing-p* #-testing nil #+testing t)
752
753 ) ; EVAL-WHEN
754 \f
755 ;;;; effective method functions
756
757 (defvar *emf-call-trace-size* 200)
758 (defvar *emf-call-trace* nil)
759 (defvar *emf-call-trace-index* 0)
760
761 ;;; This function was in the CMU CL version of PCL (ca Debian 2.4.8)
762 ;;; without explanation. It appears to be intended for debugging, so
763 ;;; it might be useful someday, so I haven't deleted it.
764 ;;; But it isn't documented and isn't used for anything now, so
765 ;;; I've conditionalized it out of the base system. -- WHN 19991213
766 #+sb-show
767 (defun show-emf-call-trace ()
768   (when *emf-call-trace*
769     (let ((j *emf-call-trace-index*)
770           (*enable-emf-call-tracing-p* nil))
771       (format t "~&(The oldest entries are printed first)~%")
772       (dotimes-fixnum (i *emf-call-trace-size*)
773         (let ((ct (aref *emf-call-trace* j)))
774           (when ct (print ct)))
775         (incf j)
776         (when (= j *emf-call-trace-size*)
777           (setq j 0))))))
778
779 (defun trace-emf-call-internal (emf format args)
780   (unless *emf-call-trace*
781     (setq *emf-call-trace* (make-array *emf-call-trace-size*)))
782   (setf (aref *emf-call-trace* *emf-call-trace-index*)
783         (list* emf format args))
784   (incf *emf-call-trace-index*)
785   (when (= *emf-call-trace-index* *emf-call-trace-size*)
786     (setq *emf-call-trace-index* 0)))
787
788 (defmacro trace-emf-call (emf format args)
789   (when *allow-emf-call-tracing-p*
790     `(when *enable-emf-call-tracing-p*
791        (trace-emf-call-internal ,emf ,format ,args))))
792
793 (defmacro invoke-effective-method-function-fast
794     (emf restp &rest required-args+rest-arg)
795   `(progn
796      (trace-emf-call ,emf ,restp (list ,@required-args+rest-arg))
797      (invoke-fast-method-call ,emf ,@required-args+rest-arg)))
798
799 (defmacro invoke-effective-method-function (emf restp
800                                                 &rest required-args+rest-arg)
801   (unless (constantp restp)
802     (error "The RESTP argument is not constant."))
803   (setq restp (eval restp))
804   `(progn
805      (trace-emf-call ,emf ,restp (list ,@required-args+rest-arg))
806      (cond ((typep ,emf 'fast-method-call)
807              (invoke-fast-method-call ,emf ,@required-args+rest-arg))
808            ,@(when (and (null restp) (= 1 (length required-args+rest-arg)))
809                `(((typep ,emf 'fixnum)
810                   (let* ((.slots. (get-slots-or-nil
811                                    ,(car required-args+rest-arg)))
812                          (value (when .slots. (%instance-ref .slots. ,emf))))
813                     (if (eq value ',*slot-unbound*)
814                         (slot-unbound-internal ,(car required-args+rest-arg)
815                                                ,emf)
816                         value)))))
817            ,@(when (and (null restp) (= 2 (length required-args+rest-arg)))
818                `(((typep ,emf 'fixnum)
819                   (let ((.new-value. ,(car required-args+rest-arg))
820                         (.slots. (get-slots-or-nil
821                                   ,(car required-args+rest-arg))))
822                     (when .slots. ; just to avoid compiler warnings
823                       (setf (%instance-ref .slots. ,emf) .new-value.))))))
824            #||
825            ,@(when (and (null restp) (= 1 (length required-args+rest-arg)))
826                `(((typep ,emf 'fast-instance-boundp)
827                   (let ((.slots. (get-slots-or-nil
828                                   ,(car required-args+rest-arg))))
829                     (and .slots.
830                          (not (eq (%instance-ref
831                                    .slots. (fast-instance-boundp-index ,emf))
832                                   ',*slot-unbound*)))))))
833            ||#
834            (t
835             (etypecase ,emf
836               (method-call
837                (invoke-method-call ,emf ,restp ,@required-args+rest-arg))
838               (function
839                ,(if restp
840                     `(apply (the function ,emf) ,@required-args+rest-arg)
841                     `(funcall (the function ,emf)
842                               ,@required-args+rest-arg))))))))
843
844 (defun invoke-emf (emf args)
845   (trace-emf-call emf t args)
846   (etypecase emf
847     (fast-method-call
848      (let* ((arg-info (fast-method-call-arg-info emf))
849             (restp (cdr arg-info))
850             (nreq (car arg-info)))
851        (if restp
852            (let* ((rest-args (nthcdr nreq args))
853                   (req-args (ldiff args rest-args)))
854              (apply (fast-method-call-function emf)
855                     (fast-method-call-pv-cell emf)
856                     (fast-method-call-next-method-call emf)
857                     (nconc req-args (list rest-args))))
858            (cond ((null args)
859                   (if (eql nreq 0)
860                       (invoke-fast-method-call emf)
861                       (error "wrong number of args")))
862                  ((null (cdr args))
863                   (if (eql nreq 1)
864                       (invoke-fast-method-call emf (car args))
865                       (error "wrong number of args")))
866                  ((null (cddr args))
867                   (if (eql nreq 2)
868                       (invoke-fast-method-call emf (car args) (cadr args))
869                       (error "wrong number of args")))
870                  (t
871                   (apply (fast-method-call-function emf)
872                          (fast-method-call-pv-cell emf)
873                          (fast-method-call-next-method-call emf)
874                          args))))))
875     (method-call
876      (apply (method-call-function emf)
877             args
878             (method-call-call-method-args emf)))
879     (fixnum
880      (cond ((null args) (error "1 or 2 args were expected."))
881            ((null (cdr args))
882             (let ((value (%instance-ref (get-slots (car args)) emf)))
883               (if (eq value *slot-unbound*)
884                   (slot-unbound-internal (car args) emf)
885                   value)))
886            ((null (cddr args))
887             (setf (%instance-ref (get-slots (cadr args)) emf)
888                   (car args)))
889            (t (error "1 or 2 args were expected."))))
890     (fast-instance-boundp
891      (if (or (null args) (cdr args))
892          (error "1 arg was expected.")
893          (not (eq (%instance-ref (get-slots (car args))
894                                  (fast-instance-boundp-index emf))
895                   *slot-unbound*))))
896     (function
897      (apply emf args))))
898
899 ;; KLUDGE: A comment from the original PCL said "This can be improved alot."
900 (defun gf-make-function-from-emf (gf emf)
901   (etypecase emf
902     (fast-method-call (let* ((arg-info (gf-arg-info gf))
903                              (nreq (arg-info-number-required arg-info))
904                              (restp (arg-info-applyp arg-info)))
905                         #'(lambda (&rest args)
906                             (trace-emf-call emf t args)
907                             (apply (fast-method-call-function emf)
908                                    (fast-method-call-pv-cell emf)
909                                    (fast-method-call-next-method-call emf)
910                                    (if restp
911                                        (let* ((rest-args (nthcdr nreq args))
912                                               (req-args (ldiff args
913                                                                rest-args)))
914                                          (nconc req-args rest-args))
915                                        args)))))
916     (method-call #'(lambda (&rest args)
917                      (trace-emf-call emf t args)
918                      (apply (method-call-function emf)
919                             args
920                             (method-call-call-method-args emf))))
921     (function emf)))
922 \f
923 (defmacro bind-fast-lexical-method-macros ((args rest-arg next-method-call)
924                                            &body body)
925   `(macrolet ((call-next-method-bind (&body body)
926                 `(let () ,@body))
927               (call-next-method-body (cnm-args)
928                 `(if ,',next-method-call
929                      ,(if (and (null ',rest-arg)
930                                (consp cnm-args)
931                                (eq (car cnm-args) 'list))
932                           `(invoke-effective-method-function
933                             ,',next-method-call nil
934                             ,@(cdr cnm-args))
935                           (let ((call `(invoke-effective-method-function
936                                         ,',next-method-call
937                                         ,',(not (null rest-arg))
938                                         ,@',args
939                                         ,@',(when rest-arg `(,rest-arg)))))
940                             `(if ,cnm-args
941                                  (bind-args ((,@',args
942                                               ,@',(when rest-arg
943                                                     `(&rest ,rest-arg)))
944                                              ,cnm-args)
945                                             ,call)
946                                  ,call)))
947                      (error "no next method")))
948               (next-method-p-body ()
949                 `(not (null ,',next-method-call))))
950      ,@body))
951
952 (defmacro bind-lexical-method-functions
953     ((&key call-next-method-p next-method-p-p closurep applyp)
954      &body body)
955   (cond ((and (null call-next-method-p) (null next-method-p-p)
956               (null closurep)
957               (null applyp))
958          `(let () ,@body))
959          ((and (null closurep)
960                (null applyp))
961          ;; OK to use MACROLET, and all args are mandatory
962          ;; (else APPLYP would be true).
963          `(call-next-method-bind
964             (macrolet ((call-next-method (&rest cnm-args)
965                          `(call-next-method-body ,(when cnm-args
966                                                     `(list ,@cnm-args))))
967                        (next-method-p ()
968                          `(next-method-p-body)))
969                ,@body)))
970         (t
971          `(call-next-method-bind
972             (flet (,@(and call-next-method-p
973                           '((call-next-method (&rest cnm-args)
974                               (call-next-method-body cnm-args))))
975                    ,@(and next-method-p-p
976                           '((next-method-p ()
977                               (next-method-p-body)))))
978               ,@body)))))
979
980 (defmacro bind-args ((lambda-list args) &body body)
981   (let ((args-tail '.args-tail.)
982         (key '.key.)
983         (state 'required))
984     (flet ((process-var (var)
985              (if (memq var lambda-list-keywords)
986                  (progn
987                    (case var
988                      (&optional  (setq state 'optional))
989                      (&key            (setq state 'key))
990                      (&allow-other-keys)
991                      (&rest          (setq state 'rest))
992                      (&aux            (setq state 'aux))
993                      (otherwise
994                       (error "encountered the non-standard lambda list keyword ~S"
995                              var)))
996                    nil)
997                  (case state
998                    (required `((,var (pop ,args-tail))))
999                    (optional (cond ((not (consp var))
1000                                     `((,var (when ,args-tail
1001                                               (pop ,args-tail)))))
1002                                    ((null (cddr var))
1003                                     `((,(car var) (if ,args-tail
1004                                                       (pop ,args-tail)
1005                                                       ,(cadr var)))))
1006                                    (t
1007                                     `((,(caddr var) ,args-tail)
1008                                       (,(car var) (if ,args-tail
1009                                                       (pop ,args-tail)
1010                                                       ,(cadr var)))))))
1011                    (rest `((,var ,args-tail)))
1012                    (key (cond ((not (consp var))
1013                                `((,var (get-key-arg ,(make-keyword var)
1014                                                     ,args-tail))))
1015                               ((null (cddr var))
1016                                (multiple-value-bind (keyword variable)
1017                                    (if (consp (car var))
1018                                        (values (caar var)
1019                                                (cadar var))
1020                                        (values (make-keyword (car var))
1021                                                (car var)))
1022                                  `((,key (get-key-arg1 ,keyword ,args-tail))
1023                                    (,variable (if (consp ,key)
1024                                                   (car ,key)
1025                                                   ,(cadr var))))))
1026                               (t
1027                                (multiple-value-bind (keyword variable)
1028                                    (if (consp (car var))
1029                                        (values (caar var)
1030                                                (cadar var))
1031                                        (values (make-keyword (car var))
1032                                                (car var)))
1033                                  `((,key (get-key-arg1 ,keyword ,args-tail))
1034                                    (,(caddr var) ,key)
1035                                    (,variable (if (consp ,key)
1036                                                   (car ,key)
1037                                                   ,(cadr var))))))))
1038                    (aux `(,var))))))
1039       (let ((bindings (mapcan #'process-var lambda-list)))
1040         `(let* ((,args-tail ,args)
1041                 ,@bindings)
1042            (declare (ignorable ,args-tail))
1043            ,@body)))))
1044
1045 (defun get-key-arg (keyword list)
1046   (loop (when (atom list) (return nil))
1047         (when (eq (car list) keyword) (return (cadr list)))
1048         (setq list (cddr list))))
1049
1050 (defun get-key-arg1 (keyword list)
1051   (loop (when (atom list) (return nil))
1052         (when (eq (car list) keyword) (return (cdr list)))
1053         (setq list (cddr list))))
1054
1055 (defun walk-method-lambda (method-lambda required-parameters env slots calls)
1056   (let ((call-next-method-p nil)   ; flag indicating that CALL-NEXT-METHOD
1057                                    ; should be in the method definition
1058         (closurep nil)             ; flag indicating that #'CALL-NEXT-METHOD
1059                                    ; was seen in the body of a method
1060         (next-method-p-p nil))     ; flag indicating that NEXT-METHOD-P
1061                                    ; should be in the method definition
1062     (flet ((walk-function (form context env)
1063              (cond ((not (eq context ':eval)) form)
1064                    ;; FIXME: Jumping to a conclusion from the way it's used
1065                    ;; above, perhaps CONTEXT should be called SITUATION
1066                    ;; (after the term used in the ANSI specification of
1067                    ;; EVAL-WHEN) and given modern ANSI keyword values
1068                    ;; like :LOAD-TOPLEVEL.
1069                    ((not (listp form)) form)
1070                    ((eq (car form) 'call-next-method)
1071                     (setq call-next-method-p 't)
1072                     form)
1073                    ((eq (car form) 'next-method-p)
1074                     (setq next-method-p-p 't)
1075                     form)
1076                    ((and (eq (car form) 'function)
1077                          (cond ((eq (cadr form) 'call-next-method)
1078                                 (setq call-next-method-p 't)
1079                                 (setq closurep t)
1080                                 form)
1081                                ((eq (cadr form) 'next-method-p)
1082                                 (setq next-method-p-p 't)
1083                                 (setq closurep t)
1084                                 form)
1085                                (t nil))))
1086                    (;; FIXME: should be MEMQ or FIND :TEST #'EQ
1087                     (and (or (eq (car form) 'slot-value)
1088                              (eq (car form) 'set-slot-value)
1089                              (eq (car form) 'slot-boundp))
1090                          (constantp (caddr form)))
1091                     (let ((parameter (can-optimize-access form
1092                                                           required-parameters
1093                                                           env)))
1094                       ;; FIXME: could be
1095                       ;;   (LET ((FUN (ECASE (CAR FORM) ..)))
1096                       ;;     (FUNCALL FUN SLOTS PARAMETER FORM))
1097                       (ecase (car form)
1098                         (slot-value
1099                          (optimize-slot-value     slots parameter form))
1100                         (set-slot-value
1101                          (optimize-set-slot-value slots parameter form))
1102                         (slot-boundp
1103                          (optimize-slot-boundp    slots parameter form)))))
1104                    ((and (eq (car form) 'apply)
1105                          (consp (cadr form))
1106                          (eq (car (cadr form)) 'function)
1107                          (generic-function-name-p (cadr (cadr form))))
1108                     (optimize-generic-function-call
1109                      form required-parameters env slots calls))
1110                    ((generic-function-name-p (car form))
1111                     (optimize-generic-function-call
1112                      form required-parameters env slots calls))
1113                    ((and (eq (car form) 'asv-funcall)
1114                          *optimize-asv-funcall-p*)
1115                     (case (fourth form)
1116                       (reader (push (third form) *asv-readers*))
1117                       (writer (push (third form) *asv-writers*))
1118                       (boundp (push (third form) *asv-boundps*)))
1119                     `(,(second form) ,@(cddddr form)))
1120                    (t form))))
1121
1122       (let ((walked-lambda (walk-form method-lambda env #'walk-function)))
1123         (values walked-lambda
1124                 call-next-method-p
1125                 closurep
1126                 next-method-p-p)))))
1127
1128 (defun generic-function-name-p (name)
1129   (and (sb-int:legal-function-name-p name)
1130        (gboundp name)
1131        (if (eq *boot-state* 'complete)
1132            (standard-generic-function-p (gdefinition name))
1133            (funcallable-instance-p (gdefinition name)))))
1134
1135 (defun make-parameter-references (specialized-lambda-list
1136                                   required-parameters
1137                                   declarations
1138                                   method-name
1139                                   specializers)
1140   (flet ((ignoredp (symbol)
1141            (dolist (decl (cdar declarations))
1142              (when (and (eq (car decl) 'ignore)
1143                         (memq symbol (cdr decl)))
1144                (return t)))))
1145     (gathering ((references (collecting)))
1146       (iterate ((s (list-elements specialized-lambda-list))
1147                 (p (list-elements required-parameters)))
1148         (progn p)
1149         (cond ((not (listp s)))
1150               ((ignoredp (car s))
1151                (warn "In DEFMETHOD ~S, there is a~%~
1152                       redundant IGNORE declaration for the parameter ~S."
1153                      method-name
1154                      specializers
1155                      (car s)))
1156               (t
1157                (gather (car s) references)))))))
1158 \f
1159 (defvar *method-function-plist* (make-hash-table :test 'eq))
1160 (defvar *mf1* nil)
1161 (defvar *mf1p* nil)
1162 (defvar *mf1cp* nil)
1163 (defvar *mf2* nil)
1164 (defvar *mf2p* nil)
1165 (defvar *mf2cp* nil)
1166
1167 (defun method-function-plist (method-function)
1168   (unless (eq method-function *mf1*)
1169     (rotatef *mf1* *mf2*)
1170     (rotatef *mf1p* *mf2p*)
1171     (rotatef *mf1cp* *mf2cp*))
1172   (unless (or (eq method-function *mf1*) (null *mf1cp*))
1173     (setf (gethash *mf1* *method-function-plist*) *mf1p*))
1174   (unless (eq method-function *mf1*)
1175     (setf *mf1* method-function
1176           *mf1cp* nil
1177           *mf1p* (gethash method-function *method-function-plist*)))
1178   *mf1p*)
1179
1180 (defun #-setf SETF\ SB-PCL\ METHOD-FUNCTION-PLIST
1181        #+setf (setf method-function-plist)
1182     (val method-function)
1183   (unless (eq method-function *mf1*)
1184     (rotatef *mf1* *mf2*)
1185     (rotatef *mf1cp* *mf2cp*)
1186     (rotatef *mf1p* *mf2p*))
1187   (unless (or (eq method-function *mf1*) (null *mf1cp*))
1188     (setf (gethash *mf1* *method-function-plist*) *mf1p*))
1189   (setf *mf1* method-function
1190         *mf1cp* t
1191         *mf1p* val))
1192
1193 (defun method-function-get (method-function key &optional default)
1194   (getf (method-function-plist method-function) key default))
1195
1196 (defun #-setf SETF\ SB-PCL\ METHOD-FUNCTION-GET
1197        #+setf (setf method-function-get)
1198     (val method-function key)
1199   (setf (getf (method-function-plist method-function) key) val))
1200
1201 (defun method-function-pv-table (method-function)
1202   (method-function-get method-function :pv-table))
1203
1204 (defun method-function-method (method-function)
1205   (method-function-get method-function :method))
1206
1207 (defun method-function-needs-next-methods-p (method-function)
1208   (method-function-get method-function :needs-next-methods-p t))
1209 \f
1210 (defmacro method-function-closure-generator (method-function)
1211   `(method-function-get ,method-function 'closure-generator))
1212
1213 (defun load-defmethod
1214     (class name quals specls ll initargs &optional pv-table-symbol)
1215   (when (listp name) (do-standard-defsetf-1 (cadr name)))
1216   (setq initargs (copy-tree initargs))
1217   (let ((method-spec (or (getf initargs ':method-spec)
1218                          (make-method-spec name quals specls))))
1219     (setf (getf initargs ':method-spec) method-spec)
1220     (record-definition 'method method-spec)
1221     (load-defmethod-internal class name quals specls
1222                              ll initargs pv-table-symbol)))
1223
1224 (defun load-defmethod-internal
1225     (method-class gf-spec qualifiers specializers lambda-list
1226                   initargs pv-table-symbol)
1227   (when (listp gf-spec) (do-standard-defsetf-1 (cadr gf-spec)))
1228   (when pv-table-symbol
1229     (setf (getf (getf initargs ':plist) :pv-table-symbol)
1230           pv-table-symbol))
1231   ;; FIXME: It seems as though I should be able to get this to work.
1232   ;; But it keeps on screwing up PCL bootstrapping.
1233   #+nil
1234   (when (and (eq *boot-state* 'complete)
1235              (fboundp gf-spec))
1236     (let* ((gf (symbol-function gf-spec))
1237            (method (and (generic-function-p gf)
1238                         (find-method gf
1239                                      qualifiers
1240                                      (mapcar #'find-class specializers)
1241                                      nil))))
1242       (when method
1243         (sb-kernel::style-warn "redefining ~S~{ ~S~} ~S in DEFMETHOD"
1244                                gf-spec qualifiers specializers))))
1245   (let ((method (apply #'add-named-method
1246                        gf-spec qualifiers specializers lambda-list
1247                        :definition-source `((defmethod ,gf-spec
1248                                                 ,@qualifiers
1249                                               ,specializers)
1250                                             ,*load-truename*)
1251                        initargs)))
1252     (unless (or (eq method-class 'standard-method)
1253                 (eq (find-class method-class nil) (class-of method)))
1254       ;; FIXME: should be STYLE-WARNING?
1255       (format *error-output*
1256               "~&At the time the method with qualifiers ~:S and~%~
1257                specializers ~:S on the generic function ~S~%~
1258                was compiled, the method-class for that generic function was~%~
1259                ~S. But, the method class is now ~S, this~%~
1260                may mean that this method was compiled improperly.~%"
1261               qualifiers specializers gf-spec
1262               method-class (class-name (class-of method))))
1263     method))
1264
1265 (defun make-method-spec (gf-spec qualifiers unparsed-specializers)
1266   `(method ,gf-spec ,@qualifiers ,unparsed-specializers))
1267
1268 (defun initialize-method-function (initargs &optional return-function-p method)
1269   (let* ((mf (getf initargs ':function))
1270          (method-spec (getf initargs ':method-spec))
1271          (plist (getf initargs ':plist))
1272          (pv-table-symbol (getf plist ':pv-table-symbol))
1273          (pv-table nil)
1274          (mff (getf initargs ':fast-function)))
1275     (flet ((set-mf-property (p v)
1276              (when mf
1277                (setf (method-function-get mf p) v))
1278              (when mff
1279                (setf (method-function-get mff p) v))))
1280       (when method-spec
1281         (when mf
1282           (setq mf (set-function-name mf method-spec)))
1283         (when mff
1284           (let ((name `(,(or (get (car method-spec) 'fast-sym)
1285                              (setf (get (car method-spec) 'fast-sym)
1286                                    ;; KLUDGE: If we're going to be
1287                                    ;; interning private symbols in our
1288                                    ;; a this way, it would be cleanest
1289                                    ;; to use a separate package
1290                                    ;; %PCL-PRIVATE or something, and
1291                                    ;; failing that, to use a special
1292                                    ;; symbol prefix denoting privateness.
1293                                    ;; -- WHN 19991201
1294                                    (intern (format nil "FAST-~A"
1295                                                    (car method-spec))
1296                                            *pcl-package*)))
1297                          ,@(cdr method-spec))))
1298             (set-function-name mff name)
1299             (unless mf
1300               (set-mf-property :name name)))))
1301       (when plist
1302         (let ((snl (getf plist :slot-name-lists))
1303               (cl (getf plist :call-list)))
1304           (when (or snl cl)
1305             (setq pv-table (intern-pv-table :slot-name-lists snl
1306                                             :call-list cl))
1307             (when pv-table (set pv-table-symbol pv-table))
1308             (set-mf-property :pv-table pv-table)))
1309         (loop (when (null plist) (return nil))
1310               (set-mf-property (pop plist) (pop plist)))
1311         (when method
1312           (set-mf-property :method method))
1313         (when return-function-p
1314           (or mf (method-function-from-fast-function mff)))))))
1315 \f
1316 (defun analyze-lambda-list (lambda-list)
1317   ;;(declare (values nrequired noptional keysp restp allow-other-keys-p
1318   ;;             keywords keyword-parameters))
1319   (flet ((parse-keyword-argument (arg)
1320            (if (listp arg)
1321                (if (listp (car arg))
1322                    (caar arg)
1323                    (make-keyword (car arg)))
1324                (make-keyword arg))))
1325     (let ((nrequired 0)
1326           (noptional 0)
1327           (keysp nil)
1328           (restp nil)
1329           (allow-other-keys-p nil)
1330           (keywords ())
1331           (keyword-parameters ())
1332           (state 'required))
1333       (dolist (x lambda-list)
1334         (if (memq x lambda-list-keywords)
1335             (case x
1336               (&optional         (setq state 'optional))
1337               (&key           (setq keysp 't
1338                                        state 'key))
1339               (&allow-other-keys (setq allow-other-keys-p 't))
1340               (&rest         (setq restp 't
1341                                        state 'rest))
1342               (&aux           (return t))
1343               (otherwise
1344                 (error "encountered the non-standard lambda list keyword ~S" x)))
1345             (ecase state
1346               (required  (incf nrequired))
1347               (optional  (incf noptional))
1348               (key       (push (parse-keyword-argument x) keywords)
1349                          (push x keyword-parameters))
1350               (rest      ()))))
1351       (values nrequired noptional keysp restp allow-other-keys-p
1352               (reverse keywords)
1353               (reverse keyword-parameters)))))
1354
1355 (defun keyword-spec-name (x)
1356   (let ((key (if (atom x) x (car x))))
1357     (if (atom key)
1358         (intern (symbol-name key) *keyword-package*)
1359         (car key))))
1360
1361 (defun ftype-declaration-from-lambda-list (lambda-list name)
1362   (multiple-value-bind (nrequired noptional keysp restp allow-other-keys-p
1363                                   keywords keyword-parameters)
1364       (analyze-lambda-list lambda-list)
1365     (declare (ignore keyword-parameters))
1366     (let* ((old (sb-c::info :function :type name)) ;FIXME:FDOCUMENTATION instead?
1367            (old-ftype (if (sb-c::function-type-p old) old nil))
1368            (old-restp (and old-ftype (sb-c::function-type-rest old-ftype)))
1369            (old-keys (and old-ftype
1370                           (mapcar #'sb-c::key-info-name
1371                                   (sb-c::function-type-keywords old-ftype))))
1372            (old-keysp (and old-ftype (sb-c::function-type-keyp old-ftype)))
1373            (old-allowp (and old-ftype (sb-c::function-type-allowp old-ftype)))
1374            (keywords (union old-keys (mapcar #'keyword-spec-name keywords))))
1375       `(function ,(append (make-list nrequired :initial-element 't)
1376                           (when (plusp noptional)
1377                             (append '(&optional)
1378                                     (make-list noptional :initial-element 't)))
1379                           (when (or restp old-restp)
1380                             '(&rest t))
1381                           (when (or keysp old-keysp)
1382                             (append '(&key)
1383                                     (mapcar #'(lambda (key)
1384                                                 `(,key t))
1385                                             keywords)
1386                                     (when (or allow-other-keys-p old-allowp)
1387                                       '(&allow-other-keys)))))
1388                  *))))
1389
1390 (defun defgeneric-declaration (spec lambda-list)
1391   (when (consp spec)
1392     (setq spec (get-setf-function-name (cadr spec))))
1393   `(ftype ,(ftype-declaration-from-lambda-list lambda-list spec) ,spec))
1394 \f
1395 ;;;; early generic function support
1396
1397 (defvar *early-generic-functions* ())
1398
1399 (defun ensure-generic-function (function-name
1400                                 &rest all-keys
1401                                 &key environment
1402                                 &allow-other-keys)
1403   (declare (ignore environment))
1404   (let ((existing (and (gboundp function-name)
1405                        (gdefinition function-name))))
1406     (if (and existing
1407              (eq *boot-state* 'complete)
1408              (null (generic-function-p existing)))
1409         (generic-clobbers-function function-name)
1410         (apply #'ensure-generic-function-using-class
1411                existing function-name all-keys))))
1412
1413 (defun generic-clobbers-function (function-name)
1414   (error 'sb-kernel:simple-program-error
1415          :format-control
1416          "~S already names an ordinary function or a macro."
1417          :format-arguments (list function-name)))
1418
1419 (defvar *sgf-wrapper*
1420   (boot-make-wrapper (early-class-size 'standard-generic-function)
1421                      'standard-generic-function))
1422
1423 (defvar *sgf-slots-init*
1424   (mapcar #'(lambda (canonical-slot)
1425               (if (memq (getf canonical-slot :name) '(arg-info source))
1426                   *slot-unbound*
1427                   (let ((initfunction (getf canonical-slot :initfunction)))
1428                     (if initfunction
1429                         (funcall initfunction)
1430                         *slot-unbound*))))
1431           (early-collect-inheritance 'standard-generic-function)))
1432
1433 (defvar *sgf-method-class-index*
1434   (bootstrap-slot-index 'standard-generic-function 'method-class))
1435
1436 (defun early-gf-p (x)
1437   (and (fsc-instance-p x)
1438        (eq (instance-ref (get-slots x) *sgf-method-class-index*)
1439            *slot-unbound*)))
1440
1441 (defvar *sgf-methods-index*
1442   (bootstrap-slot-index 'standard-generic-function 'methods))
1443
1444 (defmacro early-gf-methods (gf)
1445   `(instance-ref (get-slots ,gf) *sgf-methods-index*))
1446
1447 (defvar *sgf-arg-info-index*
1448   (bootstrap-slot-index 'standard-generic-function 'arg-info))
1449
1450 (defmacro early-gf-arg-info (gf)
1451   `(instance-ref (get-slots ,gf) *sgf-arg-info-index*))
1452
1453 (defvar *sgf-dfun-state-index*
1454   (bootstrap-slot-index 'standard-generic-function 'dfun-state))
1455
1456 (defstruct (arg-info
1457              (:conc-name nil)
1458              (:constructor make-arg-info ()))
1459   (arg-info-lambda-list :no-lambda-list)
1460   arg-info-precedence
1461   arg-info-metatypes
1462   arg-info-number-optional
1463   arg-info-key/rest-p
1464   arg-info-keywords ;nil        no keyword or rest allowed
1465                     ;(k1 k2 ..) each method must accept these keyword arguments
1466                     ;T    must have &key or &rest
1467
1468   gf-info-simple-accessor-type ; nil, reader, writer, boundp
1469   (gf-precompute-dfun-and-emf-p nil) ; set by set-arg-info
1470
1471   gf-info-static-c-a-m-emf
1472   (gf-info-c-a-m-emf-std-p t)
1473   gf-info-fast-mf-p)
1474
1475 #-sb-fluid (declaim (sb-ext:freeze-type arg-info))
1476
1477 (defun arg-info-valid-p (arg-info)
1478   (not (null (arg-info-number-optional arg-info))))
1479
1480 (defun arg-info-applyp (arg-info)
1481   (or (plusp (arg-info-number-optional arg-info))
1482       (arg-info-key/rest-p arg-info)))
1483
1484 (defun arg-info-number-required (arg-info)
1485   (length (arg-info-metatypes arg-info)))
1486
1487 (defun arg-info-nkeys (arg-info)
1488   (count-if #'(lambda (x) (neq x 't)) (arg-info-metatypes arg-info)))
1489
1490 ;;; Keep pages clean by not setting if the value is already the same.
1491 (defmacro esetf (pos val)
1492   (let ((valsym (gensym "value")))
1493     `(let ((,valsym ,val))
1494        (unless (equal ,pos ,valsym)
1495          (setf ,pos ,valsym)))))
1496
1497 (defun set-arg-info (gf &key new-method (lambda-list nil lambda-list-p)
1498                         argument-precedence-order)
1499   (let* ((arg-info (if (eq *boot-state* 'complete)
1500                        (gf-arg-info gf)
1501                        (early-gf-arg-info gf)))
1502          (methods (if (eq *boot-state* 'complete)
1503                       (generic-function-methods gf)
1504                       (early-gf-methods gf)))
1505          (was-valid-p (integerp (arg-info-number-optional arg-info)))
1506          (first-p (and new-method (null (cdr methods)))))
1507     (when (and (not lambda-list-p) methods)
1508       (setq lambda-list (gf-lambda-list gf)))
1509     (when (or lambda-list-p
1510               (and first-p
1511                    (eq (arg-info-lambda-list arg-info) ':no-lambda-list)))
1512       (multiple-value-bind (nreq nopt keysp restp allow-other-keys-p keywords)
1513           (analyze-lambda-list lambda-list)
1514         (when (and methods (not first-p))
1515           (let ((gf-nreq (arg-info-number-required arg-info))
1516                 (gf-nopt (arg-info-number-optional arg-info))
1517                 (gf-key/rest-p (arg-info-key/rest-p arg-info)))
1518             (unless (and (= nreq gf-nreq)
1519                          (= nopt gf-nopt)
1520                          (eq (or keysp restp) gf-key/rest-p))
1521               (error "The lambda-list ~S is incompatible with ~
1522                      existing methods of ~S."
1523                      lambda-list gf))))
1524         (when lambda-list-p
1525           (esetf (arg-info-lambda-list arg-info) lambda-list))
1526         (when (or lambda-list-p argument-precedence-order
1527                   (null (arg-info-precedence arg-info)))
1528           (esetf (arg-info-precedence arg-info)
1529                  (compute-precedence lambda-list nreq
1530                                      argument-precedence-order)))
1531         (esetf (arg-info-metatypes arg-info) (make-list nreq))
1532         (esetf (arg-info-number-optional arg-info) nopt)
1533         (esetf (arg-info-key/rest-p arg-info) (not (null (or keysp restp))))
1534         (esetf (arg-info-keywords arg-info)
1535                (if lambda-list-p
1536                    (if allow-other-keys-p t keywords)
1537                    (arg-info-key/rest-p arg-info)))))
1538     (when new-method
1539       (check-method-arg-info gf arg-info new-method))
1540     (set-arg-info1 gf arg-info new-method methods was-valid-p first-p)
1541     arg-info))
1542
1543 (defun check-method-arg-info (gf arg-info method)
1544   (multiple-value-bind (nreq nopt keysp restp allow-other-keys-p keywords)
1545       (analyze-lambda-list (if (consp method)
1546                                (early-method-lambda-list method)
1547                                (method-lambda-list method)))
1548     (flet ((lose (string &rest args)
1549              (error
1550               "attempt to add the method ~S to the generic function ~S.~%~
1551                But ~A"
1552               method
1553               gf
1554               (apply #'format nil string args)))
1555            (compare (x y)
1556              (if (> x y) "more" "fewer")))
1557       (let ((gf-nreq (arg-info-number-required arg-info))
1558             (gf-nopt (arg-info-number-optional arg-info))
1559             (gf-key/rest-p (arg-info-key/rest-p arg-info))
1560             (gf-keywords (arg-info-keywords arg-info)))
1561         (unless (= nreq gf-nreq)
1562           (lose
1563            "the method has ~A required arguments than the generic function."
1564            (compare nreq gf-nreq)))
1565         (unless (= nopt gf-nopt)
1566           (lose
1567            "the method has ~S optional arguments than the generic function."
1568            (compare nopt gf-nopt)))
1569         (unless (eq (or keysp restp) gf-key/rest-p)
1570           (error
1571            "The method and generic function differ in whether they accept~%~
1572             &REST or &KEY arguments."))
1573         (when (consp gf-keywords)
1574           (unless (or (and restp (not keysp))
1575                       allow-other-keys-p
1576                       (every #'(lambda (k) (memq k keywords)) gf-keywords))
1577             (lose "the method does not accept each of the keyword arguments~%~
1578                    ~S."
1579                   gf-keywords)))))))
1580
1581 (defun set-arg-info1 (gf arg-info new-method methods was-valid-p first-p)
1582   (let* ((existing-p (and methods (cdr methods) new-method))
1583          (nreq (length (arg-info-metatypes arg-info)))
1584          (metatypes (if existing-p
1585                         (arg-info-metatypes arg-info)
1586                         (make-list nreq)))
1587          (type (if existing-p
1588                    (gf-info-simple-accessor-type arg-info)
1589                    nil)))
1590     (when (arg-info-valid-p arg-info)
1591       (dolist (method (if new-method (list new-method) methods))
1592         (let* ((specializers (if (or (eq *boot-state* 'complete)
1593                                      (not (consp method)))
1594                                  (method-specializers method)
1595                                  (early-method-specializers method t)))
1596                (class (if (or (eq *boot-state* 'complete) (not (consp method)))
1597                           (class-of method)
1598                           (early-method-class method)))
1599                (new-type (when (and class
1600                                     (or (not (eq *boot-state* 'complete))
1601                                         (eq (generic-function-method-combination gf)
1602                                             *standard-method-combination*)))
1603                            (cond ((eq class *the-class-standard-reader-method*)
1604                                   'reader)
1605                                  ((eq class *the-class-standard-writer-method*)
1606                                   'writer)
1607                                  ((eq class *the-class-standard-boundp-method*)
1608                                   'boundp)))))
1609           (setq metatypes (mapcar #'raise-metatype metatypes specializers))
1610           (setq type (cond ((null type) new-type)
1611                            ((eq type new-type) type)
1612                            (t nil)))))
1613       (esetf (arg-info-metatypes arg-info) metatypes)
1614       (esetf (gf-info-simple-accessor-type arg-info) type)))
1615   (when (or (not was-valid-p) first-p)
1616     (multiple-value-bind (c-a-m-emf std-p)
1617         (if (early-gf-p gf)
1618             (values t t)
1619             (compute-applicable-methods-emf gf))
1620       (esetf (gf-info-static-c-a-m-emf arg-info) c-a-m-emf)
1621       (esetf (gf-info-c-a-m-emf-std-p arg-info) std-p)
1622       (unless (gf-info-c-a-m-emf-std-p arg-info)
1623         (esetf (gf-info-simple-accessor-type arg-info) t))))
1624   (unless was-valid-p
1625     (let ((name (if (eq *boot-state* 'complete)
1626                     (generic-function-name gf)
1627                     (early-gf-name gf))))
1628       (esetf (gf-precompute-dfun-and-emf-p arg-info)
1629              (let* ((sym (if (atom name) name (cadr name)))
1630                     (pkg-list (cons *pcl-package*
1631                                     (package-use-list *pcl-package*))))
1632                (and sym (symbolp sym)
1633                     (not (null (memq (symbol-package sym) pkg-list)))
1634                     (not (find #\space (symbol-name sym))))))))
1635   (esetf (gf-info-fast-mf-p arg-info)
1636          (or (not (eq *boot-state* 'complete))
1637              (let* ((method-class (generic-function-method-class gf))
1638                     (methods (compute-applicable-methods
1639                               #'make-method-lambda
1640                               (list gf (class-prototype method-class)
1641                                     '(lambda) nil))))
1642                (and methods (null (cdr methods))
1643                     (let ((specls (method-specializers (car methods))))
1644                       (and (classp (car specls))
1645                            (eq 'standard-generic-function
1646                                (class-name (car specls)))
1647                            (classp (cadr specls))
1648                            (eq 'standard-method
1649                                (class-name (cadr specls)))))))))
1650   arg-info)
1651
1652 ;;; This is the early definition of ensure-generic-function-using-class.
1653 ;;;
1654 ;;; The static-slots field of the funcallable instances used as early generic
1655 ;;; functions is used to store the early methods and early discriminator code
1656 ;;; for the early generic function. The static slots field of the fins
1657 ;;; contains a list whose:
1658 ;;;    CAR    -   a list of the early methods on this early gf
1659 ;;;    CADR   -   the early discriminator code for this method
1660 (defun ensure-generic-function-using-class (existing spec &rest keys
1661                                             &key (lambda-list nil lambda-list-p)
1662                                             &allow-other-keys)
1663   (declare (ignore keys))
1664   (cond ((and existing (early-gf-p existing))
1665          existing)
1666         ((assoc spec *generic-function-fixups* :test #'equal)
1667          (if existing
1668              (make-early-gf spec lambda-list lambda-list-p existing)
1669              (error "The function ~S is not already defined." spec)))
1670         (existing
1671          (error "~S should be on the list ~S."
1672                 spec
1673                 '*generic-function-fixups*))
1674         (t
1675          (pushnew spec *early-generic-functions* :test #'equal)
1676          (make-early-gf spec lambda-list lambda-list-p))))
1677
1678 (defun make-early-gf (spec &optional lambda-list lambda-list-p function)
1679   (let ((fin (allocate-funcallable-instance *sgf-wrapper* *sgf-slots-init*)))
1680     (set-funcallable-instance-function
1681      fin
1682      (or function
1683          (if (eq spec 'print-object)
1684              #'(sb-kernel:instance-lambda (instance stream)
1685                  (print-unreadable-object (instance stream :identity t)
1686                    (format stream "std-instance")))
1687              #'(sb-kernel:instance-lambda (&rest args)
1688                  (declare (ignore args))
1689                  (error "The function of the funcallable-instance ~S~
1690                          has not been set." fin)))))
1691     (setf (gdefinition spec) fin)
1692     (bootstrap-set-slot 'standard-generic-function fin 'name spec)
1693     (bootstrap-set-slot 'standard-generic-function fin 'source *load-truename*)
1694     (set-function-name fin spec)
1695     (let ((arg-info (make-arg-info)))
1696       (setf (early-gf-arg-info fin) arg-info)
1697       (when lambda-list-p
1698         (proclaim (defgeneric-declaration spec lambda-list))
1699         (set-arg-info fin :lambda-list lambda-list)))
1700     fin))
1701
1702 (defun set-dfun (gf &optional dfun cache info)
1703   (when cache
1704     (setf (cache-owner cache) gf))
1705   (let ((new-state (if (and dfun (or cache info))
1706                        (list* dfun cache info)
1707                        dfun)))
1708     (if (eq *boot-state* 'complete)
1709         (setf (gf-dfun-state gf) new-state)
1710         (setf (instance-ref (get-slots gf) *sgf-dfun-state-index*) new-state)))
1711   dfun)
1712
1713 (defun gf-dfun-cache (gf)
1714   (let ((state (if (eq *boot-state* 'complete)
1715                    (gf-dfun-state gf)
1716                    (instance-ref (get-slots gf) *sgf-dfun-state-index*))))
1717     (typecase state
1718       (function nil)
1719       (cons (cadr state)))))
1720
1721 (defun gf-dfun-info (gf)
1722   (let ((state (if (eq *boot-state* 'complete)
1723                    (gf-dfun-state gf)
1724                    (instance-ref (get-slots gf) *sgf-dfun-state-index*))))
1725     (typecase state
1726       (function nil)
1727       (cons (cddr state)))))
1728
1729 (defvar *sgf-name-index*
1730   (bootstrap-slot-index 'standard-generic-function 'name))
1731
1732 (defun early-gf-name (gf)
1733   (instance-ref (get-slots gf) *sgf-name-index*))
1734
1735 (defun gf-lambda-list (gf)
1736   (let ((arg-info (if (eq *boot-state* 'complete)
1737                       (gf-arg-info gf)
1738                       (early-gf-arg-info gf))))
1739     (if (eq ':no-lambda-list (arg-info-lambda-list arg-info))
1740         (let ((methods (if (eq *boot-state* 'complete)
1741                            (generic-function-methods gf)
1742                            (early-gf-methods gf))))
1743           (if (null methods)
1744               (progn
1745                 (warn "no way to determine the lambda list for ~S" gf)
1746                 nil)
1747               (let* ((method (car (last methods)))
1748                      (ll (if (consp method)
1749                              (early-method-lambda-list method)
1750                              (method-lambda-list method)))
1751                      (k (member '&key ll)))
1752                 (if k
1753                     (append (ldiff ll (cdr k)) '(&allow-other-keys))
1754                     ll))))
1755         (arg-info-lambda-list arg-info))))
1756
1757 (defmacro real-ensure-gf-internal (gf-class all-keys env)
1758   `(progn
1759      (cond ((symbolp ,gf-class)
1760             (setq ,gf-class (find-class ,gf-class t ,env)))
1761            ((classp ,gf-class))
1762            (t
1763             (error "The :GENERIC-FUNCTION-CLASS argument (~S) was neither a~%~
1764                     class nor a symbol that names a class."
1765                    ,gf-class)))
1766      (remf ,all-keys :generic-function-class)
1767      (remf ,all-keys :environment)
1768      (let ((combin (getf ,all-keys :method-combination '.shes-not-there.)))
1769        (unless (eq combin '.shes-not-there.)
1770          (setf (getf ,all-keys :method-combination)
1771                (find-method-combination (class-prototype ,gf-class)
1772                                         (car combin)
1773                                         (cdr combin)))))))
1774
1775 (defun real-ensure-gf-using-class--generic-function
1776        (existing
1777         function-name
1778         &rest all-keys
1779         &key environment (lambda-list nil lambda-list-p)
1780              (generic-function-class 'standard-generic-function gf-class-p)
1781         &allow-other-keys)
1782   (real-ensure-gf-internal generic-function-class all-keys environment)
1783   (unless (or (null gf-class-p)
1784               (eq (class-of existing) generic-function-class))
1785     (change-class existing generic-function-class))
1786   (prog1
1787       (apply #'reinitialize-instance existing all-keys)
1788     (when lambda-list-p
1789       (proclaim (defgeneric-declaration function-name lambda-list)))))
1790
1791 (defun real-ensure-gf-using-class--null
1792        (existing
1793         function-name
1794         &rest all-keys
1795         &key environment (lambda-list nil lambda-list-p)
1796              (generic-function-class 'standard-generic-function)
1797         &allow-other-keys)
1798   (declare (ignore existing))
1799   (real-ensure-gf-internal generic-function-class all-keys environment)
1800   (prog1
1801       (setf (gdefinition function-name)
1802             (apply #'make-instance generic-function-class
1803                    :name function-name all-keys))
1804     (when lambda-list-p
1805       (proclaim (defgeneric-declaration function-name lambda-list)))))
1806 \f
1807 (defun get-generic-function-info (gf)
1808   ;; values   nreq applyp metatypes nkeys arg-info
1809   (multiple-value-bind (applyp metatypes arg-info)
1810       (let* ((arg-info (if (early-gf-p gf)
1811                            (early-gf-arg-info gf)
1812                            (gf-arg-info gf)))
1813              (metatypes (arg-info-metatypes arg-info)))
1814         (values (arg-info-applyp arg-info)
1815                 metatypes
1816                 arg-info))
1817     (values (length metatypes) applyp metatypes
1818             (count-if #'(lambda (x) (neq x 't)) metatypes)
1819             arg-info)))
1820
1821 (defun early-make-a-method (class qualifiers arglist specializers initargs doc
1822                             &optional slot-name)
1823   (initialize-method-function initargs)
1824   (let ((parsed ())
1825         (unparsed ()))
1826     ;; Figure out whether we got class objects or class names as the
1827     ;; specializers and set parsed and unparsed appropriately. If we
1828     ;; got class objects, then we can compute unparsed, but if we got
1829     ;; class names we don't try to compute parsed.
1830     ;;
1831     ;; Note that the use of not symbolp in this call to every should be
1832     ;; read as 'classp' we can't use classp itself because it doesn't
1833     ;; exist yet.
1834     (if (every #'(lambda (s) (not (symbolp s))) specializers)
1835         (setq parsed specializers
1836               unparsed (mapcar #'(lambda (s)
1837                                    (if (eq s 't) 't (class-name s)))
1838                                specializers))
1839         (setq unparsed specializers
1840               parsed ()))
1841     (list :early-method           ;This is an early method dammit!
1842
1843           (getf initargs ':function)
1844           (getf initargs ':fast-function)
1845
1846           parsed                  ;The parsed specializers. This is used
1847                                   ;by early-method-specializers to cache
1848                                   ;the parse. Note that this only comes
1849                                   ;into play when there is more than one
1850                                   ;early method on an early gf.
1851
1852           (list class        ;A list to which real-make-a-method
1853                 qualifiers      ;can be applied to make a real method
1854                 arglist    ;corresponding to this early one.
1855                 unparsed
1856                 initargs
1857                 doc
1858                 slot-name))))
1859
1860 (defun real-make-a-method
1861        (class qualifiers lambda-list specializers initargs doc
1862         &optional slot-name)
1863   (setq specializers (parse-specializers specializers))
1864   (apply #'make-instance class
1865          :qualifiers qualifiers
1866          :lambda-list lambda-list
1867          :specializers specializers
1868          :documentation doc
1869          :slot-name slot-name
1870          :allow-other-keys t
1871          initargs))
1872
1873 (defun early-method-function (early-method)
1874   (values (cadr early-method) (caddr early-method)))
1875
1876 (defun early-method-class (early-method)
1877   (find-class (car (fifth early-method))))
1878
1879 (defun early-method-standard-accessor-p (early-method)
1880   (let ((class (first (fifth early-method))))
1881     (or (eq class 'standard-reader-method)
1882         (eq class 'standard-writer-method)
1883         (eq class 'standard-boundp-method))))
1884
1885 (defun early-method-standard-accessor-slot-name (early-method)
1886   (seventh (fifth early-method)))
1887
1888 ;;; Fetch the specializers of an early method. This is basically just a
1889 ;;; simple accessor except that when the second argument is t, this converts
1890 ;;; the specializers from symbols into class objects. The class objects
1891 ;;; are cached in the early method, this makes bootstrapping faster because
1892 ;;; the class objects only have to be computed once.
1893 ;;; NOTE:
1894 ;;;  the second argument should only be passed as T by early-lookup-method.
1895 ;;;  this is to implement the rule that only when there is more than one
1896 ;;;  early method on a generic function is the conversion from class names
1897 ;;;  to class objects done.
1898 ;;;  the corresponds to the fact that we are only allowed to have one method
1899 ;;;  on any generic function up until the time classes exist.
1900 (defun early-method-specializers (early-method &optional objectsp)
1901   (if (and (listp early-method)
1902            (eq (car early-method) :early-method))
1903       (cond ((eq objectsp 't)
1904              (or (fourth early-method)
1905                  (setf (fourth early-method)
1906                        (mapcar #'find-class (cadddr (fifth early-method))))))
1907             (t
1908              (cadddr (fifth early-method))))
1909       (error "~S is not an early-method." early-method)))
1910
1911 (defun early-method-qualifiers (early-method)
1912   (cadr (fifth early-method)))
1913
1914 (defun early-method-lambda-list (early-method)
1915   (caddr (fifth early-method)))
1916
1917 (defun early-add-named-method (generic-function-name
1918                                qualifiers
1919                                specializers
1920                                arglist
1921                                &rest initargs)
1922   (let* ((gf (ensure-generic-function generic-function-name))
1923          (existing
1924            (dolist (m (early-gf-methods gf))
1925              (when (and (equal (early-method-specializers m) specializers)
1926                         (equal (early-method-qualifiers m) qualifiers))
1927                (return m))))
1928          (new (make-a-method 'standard-method
1929                              qualifiers
1930                              arglist
1931                              specializers
1932                              initargs
1933                              ())))
1934     (when existing (remove-method gf existing))
1935     (add-method gf new)))
1936
1937 ;;; This is the early version of add-method. Later this will become a
1938 ;;; generic function. See fix-early-generic-functions which has special
1939 ;;; knowledge about add-method.
1940 (defun add-method (generic-function method)
1941   (when (not (fsc-instance-p generic-function))
1942     (error "Early add-method didn't get a funcallable instance."))
1943   (when (not (and (listp method) (eq (car method) :early-method)))
1944     (error "Early add-method didn't get an early method."))
1945   (push method (early-gf-methods generic-function))
1946   (set-arg-info generic-function :new-method method)
1947   (unless (assoc (early-gf-name generic-function) *generic-function-fixups*
1948                  :test #'equal)
1949     (update-dfun generic-function)))
1950
1951 ;;; This is the early version of REMOVE-METHOD..
1952 (defun remove-method (generic-function method)
1953   (when (not (fsc-instance-p generic-function))
1954     (error "An early remove-method didn't get a funcallable instance."))
1955   (when (not (and (listp method) (eq (car method) :early-method)))
1956     (error "An early remove-method didn't get an early method."))
1957   (setf (early-gf-methods generic-function)
1958         (remove method (early-gf-methods generic-function)))
1959   (set-arg-info generic-function)
1960   (unless (assoc (early-gf-name generic-function) *generic-function-fixups*
1961                  :test #'equal)
1962     (update-dfun generic-function)))
1963
1964 ;;; ..and the early version of GET-METHOD.
1965 (defun get-method (generic-function qualifiers specializers
1966                                     &optional (errorp t))
1967   (if (early-gf-p generic-function)
1968       (or (dolist (m (early-gf-methods generic-function))
1969             (when (and (or (equal (early-method-specializers m nil)
1970                                   specializers)
1971                            (equal (early-method-specializers m 't)
1972                                   specializers))
1973                        (equal (early-method-qualifiers m) qualifiers))
1974               (return m)))
1975           (if errorp
1976               (error "can't get early method")
1977               nil))
1978       (real-get-method generic-function qualifiers specializers errorp)))
1979
1980 (defvar *fegf-debug-p* nil)
1981
1982 (defun fix-early-generic-functions (&optional (noisyp *fegf-debug-p*))
1983   (let ((accessors nil))
1984     ;; Rearrange *EARLY-GENERIC-FUNCTIONS* to speed up
1985     ;; FIX-EARLY-GENERIC-FUNCTIONS.
1986     (dolist (early-gf-spec *early-generic-functions*)
1987       (when (every #'early-method-standard-accessor-p
1988                    (early-gf-methods (gdefinition early-gf-spec)))
1989         (push early-gf-spec accessors)))
1990     (dolist (spec (nconc accessors
1991                          '(accessor-method-slot-name
1992                            generic-function-methods
1993                            method-specializers
1994                            specializerp
1995                            specializer-type
1996                            specializer-class
1997                            slot-definition-location
1998                            slot-definition-name
1999                            class-slots
2000                            gf-arg-info
2001                            class-precedence-list
2002                            slot-boundp-using-class
2003                            (setf slot-value-using-class)
2004                            slot-value-using-class
2005                            structure-class-p
2006                            standard-class-p
2007                            funcallable-standard-class-p
2008                            specializerp)))
2009       (setq *early-generic-functions*
2010             (cons spec (delete spec *early-generic-functions* :test #'equal))))
2011
2012     (dolist (early-gf-spec *early-generic-functions*)
2013       (when noisyp (format t "~&~S..." early-gf-spec))
2014       (let* ((gf (gdefinition early-gf-spec))
2015              (methods (mapcar #'(lambda (early-method)
2016                                   (let ((args (copy-list (fifth
2017                                                           early-method))))
2018                                     (setf (fourth args)
2019                                           (early-method-specializers
2020                                            early-method t))
2021                                     (apply #'real-make-a-method args)))
2022                               (early-gf-methods gf))))
2023         (setf (generic-function-method-class gf) *the-class-standard-method*)
2024         (setf (generic-function-method-combination gf)
2025               *standard-method-combination*)
2026         (set-methods gf methods)))
2027
2028     (dolist (fns *early-functions*)
2029       (setf (gdefinition (car fns)) (symbol-function (caddr fns))))
2030
2031     (dolist (fixup *generic-function-fixups*)
2032       (let* ((fspec (car fixup))
2033              (gf (gdefinition fspec))
2034              (methods (mapcar #'(lambda (method)
2035                                   (let* ((lambda-list (first method))
2036                                          (specializers (second method))
2037                                          (method-fn-name (third method))
2038                                          (fn-name (or method-fn-name fspec))
2039                                          (fn (symbol-function fn-name))
2040                                          (initargs
2041                                           (list :function
2042                                                 (set-function-name
2043                                                  #'(lambda (args next-methods)
2044                                                      (declare (ignore
2045                                                                next-methods))
2046                                                      (apply fn args))
2047                                                  `(call ,fn-name)))))
2048                                     (declare (type function fn))
2049                                     (make-a-method 'standard-method
2050                                                    ()
2051                                                    lambda-list
2052                                                    specializers
2053                                                    initargs
2054                                                    nil)))
2055                               (cdr fixup))))
2056         (setf (generic-function-method-class gf) *the-class-standard-method*)
2057         (setf (generic-function-method-combination gf)
2058               *standard-method-combination*)
2059         (set-methods gf methods)))))
2060 \f
2061 ;;; PARSE-DEFMETHOD is used by DEFMETHOD to parse the &REST argument into
2062 ;;; the 'real' arguments. This is where the syntax of DEFMETHOD is really
2063 ;;; implemented.
2064 (defun parse-defmethod (cdr-of-form)
2065   ;;(declare (values name qualifiers specialized-lambda-list body))
2066   (let ((name (pop cdr-of-form))
2067         (qualifiers ())
2068         (spec-ll ()))
2069     (loop (if (and (car cdr-of-form) (atom (car cdr-of-form)))
2070               (push (pop cdr-of-form) qualifiers)
2071               (return (setq qualifiers (nreverse qualifiers)))))
2072     (setq spec-ll (pop cdr-of-form))
2073     (values name qualifiers spec-ll cdr-of-form)))
2074
2075 (defun parse-specializers (specializers)
2076   (flet ((parse (spec)
2077            (let ((result (specializer-from-type spec)))
2078              (if (specializerp result)
2079                  result
2080                  (if (symbolp spec)
2081                      (error "~S was used as a specializer,~%~
2082                              but is not the name of a class."
2083                             spec)
2084                      (error "~S is not a legal specializer." spec))))))
2085     (mapcar #'parse specializers)))
2086
2087 (defun unparse-specializers (specializers-or-method)
2088   (if (listp specializers-or-method)
2089       (flet ((unparse (spec)
2090                (if (specializerp spec)
2091                    (let ((type (specializer-type spec)))
2092                      (if (and (consp type)
2093                               (eq (car type) 'class))
2094                          (let* ((class (cadr type))
2095                                 (class-name (class-name class)))
2096                            (if (eq class (find-class class-name nil))
2097                                class-name
2098                                type))
2099                          type))
2100                    (error "~S is not a legal specializer." spec))))
2101         (mapcar #'unparse specializers-or-method))
2102       (unparse-specializers (method-specializers specializers-or-method))))
2103
2104 (defun parse-method-or-spec (spec &optional (errorp t))
2105   ;;(declare (values generic-function method method-name))
2106   (let (gf method name temp)
2107     (if (method-p spec) 
2108         (setq method spec
2109               gf (method-generic-function method)
2110               temp (and gf (generic-function-name gf))
2111               name (if temp
2112                        (intern-function-name
2113                          (make-method-spec temp
2114                                            (method-qualifiers method)
2115                                            (unparse-specializers
2116                                              (method-specializers method))))
2117                        (make-symbol (format nil "~S" method))))
2118         (multiple-value-bind (gf-spec quals specls)
2119             (parse-defmethod spec)
2120           (and (setq gf (and (or errorp (gboundp gf-spec))
2121                              (gdefinition gf-spec)))
2122                (let ((nreq (compute-discriminating-function-arglist-info gf)))
2123                  (setq specls (append (parse-specializers specls)
2124                                       (make-list (- nreq (length specls))
2125                                                  :initial-element
2126                                                  *the-class-t*)))
2127                  (and
2128                    (setq method (get-method gf quals specls errorp))
2129                    (setq name
2130                          (intern-function-name (make-method-spec gf-spec
2131                                                                  quals
2132                                                                  specls))))))))
2133     (values gf method name)))
2134 \f
2135 (defun extract-parameters (specialized-lambda-list)
2136   (multiple-value-bind (parameters ignore1 ignore2)
2137       (parse-specialized-lambda-list specialized-lambda-list)
2138     (declare (ignore ignore1 ignore2))
2139     parameters))
2140
2141 (defun extract-lambda-list (specialized-lambda-list)
2142   (multiple-value-bind (ignore1 lambda-list ignore2)
2143       (parse-specialized-lambda-list specialized-lambda-list)
2144     (declare (ignore ignore1 ignore2))
2145     lambda-list))
2146
2147 (defun extract-specializer-names (specialized-lambda-list)
2148   (multiple-value-bind (ignore1 ignore2 specializers)
2149       (parse-specialized-lambda-list specialized-lambda-list)
2150     (declare (ignore ignore1 ignore2))
2151     specializers))
2152
2153 (defun extract-required-parameters (specialized-lambda-list)
2154   (multiple-value-bind (ignore1 ignore2 ignore3 required-parameters)
2155       (parse-specialized-lambda-list specialized-lambda-list)
2156     (declare (ignore ignore1 ignore2 ignore3))
2157     required-parameters))
2158
2159 (defun parse-specialized-lambda-list (arglist &optional post-keyword)
2160   ;;(declare (values parameters lambda-list specializers required-parameters))
2161   (let ((arg (car arglist)))
2162     (cond ((null arglist) (values nil nil nil nil))
2163           ((eq arg '&aux)
2164            (values nil arglist nil))
2165           ((memq arg lambda-list-keywords)
2166            (unless (memq arg '(&optional &rest &key &allow-other-keys &aux))
2167              ;; Warn about non-standard lambda-list-keywords, but then
2168              ;; go on to treat them like a standard lambda-list-keyword
2169              ;; what with the warning its probably ok.
2170              ;;
2171              ;; FIXME: This shouldn't happen now that this is maintained
2172              ;; as part of SBCL, should it? Perhaps this is now
2173              ;; "internal error: unrecognized lambda-list keyword ~S"?
2174              (warn "Unrecognized lambda-list keyword ~S in arglist.~%~
2175                     Assuming that the symbols following it are parameters,~%~
2176                     and not allowing any parameter specializers to follow~%~
2177                     to follow it."
2178                    arg))
2179            ;; When we are at a lambda-list keyword, the parameters don't
2180            ;; include the lambda-list keyword; the lambda-list does include
2181            ;; the lambda-list keyword; and no specializers are allowed to
2182            ;; follow the lambda-list keywords (at least for now).
2183            (multiple-value-bind (parameters lambda-list)
2184                (parse-specialized-lambda-list (cdr arglist) t)
2185              (values parameters
2186                      (cons arg lambda-list)
2187                      ()
2188                      ())))
2189           (post-keyword
2190            ;; After a lambda-list keyword there can be no specializers.
2191            (multiple-value-bind (parameters lambda-list)
2192                (parse-specialized-lambda-list (cdr arglist) t)
2193              (values (cons (if (listp arg) (car arg) arg) parameters)
2194                      (cons arg lambda-list)
2195                      ()
2196                      ())))
2197           (t
2198            (multiple-value-bind (parameters lambda-list specializers required)
2199                (parse-specialized-lambda-list (cdr arglist))
2200              (values (cons (if (listp arg) (car arg) arg) parameters)
2201                      (cons (if (listp arg) (car arg) arg) lambda-list)
2202                      (cons (if (listp arg) (cadr arg) 't) specializers)
2203                      (cons (if (listp arg) (car arg) arg) required)))))))
2204 \f
2205 (eval-when (:load-toplevel :execute)
2206   (setq *boot-state* 'early))
2207 \f
2208 ;;; FIXME: In here there was a #-CMU definition of SYMBOL-MACROLET which used
2209 ;;; %WALKER stuff. That suggests to me that maybe the code walker stuff was
2210 ;;; only used for implementing stuff like that; maybe it's not needed any more?
2211 ;;; Hunt down what it was used for and see.
2212
2213 (defmacro with-slots (slots instance &body body)
2214   (let ((in (gensym)))
2215     `(let ((,in ,instance))
2216        (declare (ignorable ,in))
2217        ,@(let ((instance (if (and (consp instance) (eq (car instance) 'the))
2218                              (third instance)
2219                              instance)))
2220            (and (symbolp instance)
2221                 `((declare (variable-rebinding ,in ,instance)))))
2222        ,in
2223        (symbol-macrolet ,(mapcar #'(lambda (slot-entry)
2224                                      (let ((variable-name
2225                                             (if (symbolp slot-entry)
2226                                                 slot-entry
2227                                                 (car slot-entry)))
2228                                            (slot-name
2229                                             (if (symbolp slot-entry)
2230                                                 slot-entry
2231                                                 (cadr slot-entry))))
2232                                        `(,variable-name
2233                                           (slot-value ,in ',slot-name))))
2234                                  slots)
2235                         ,@body))))
2236
2237 (defmacro with-accessors (slots instance &body body)
2238   (let ((in (gensym)))
2239     `(let ((,in ,instance))
2240        (declare (ignorable ,in))
2241        ,@(let ((instance (if (and (consp instance) (eq (car instance) 'the))
2242                              (third instance)
2243                              instance)))
2244            (and (symbolp instance)
2245                 `((declare (variable-rebinding ,in ,instance)))))
2246        ,in
2247        (symbol-macrolet ,(mapcar #'(lambda (slot-entry)
2248                                    (let ((variable-name (car slot-entry))
2249                                          (accessor-name (cadr slot-entry)))
2250                                      `(,variable-name
2251                                         (,accessor-name ,in))))
2252                                slots)
2253           ,@body))))