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