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