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