1.0.9.56: faster typechecking/optimized std-writer-method-functions
[sbcl.git] / src / pcl / vector.lisp
1 ;;;; permutation vectors
2
3 ;;;; This software is part of the SBCL system. See the README file for
4 ;;;; more information.
5
6 ;;;; This software is derived from software originally released by Xerox
7 ;;;; Corporation. Copyright and release statements follow. Later modifications
8 ;;;; to the software are in the public domain and are provided with
9 ;;;; absolutely no warranty. See the COPYING and CREDITS files for more
10 ;;;; information.
11
12 ;;;; copyright information from original PCL sources:
13 ;;;;
14 ;;;; Copyright (c) 1985, 1986, 1987, 1988, 1989, 1990 Xerox Corporation.
15 ;;;; All rights reserved.
16 ;;;;
17 ;;;; Use and copying of this software and preparation of derivative works based
18 ;;;; upon this software are permitted. Any distribution of this software or
19 ;;;; derivative works must comply with all applicable United States export
20 ;;;; control laws.
21 ;;;;
22 ;;;; This software is made available AS IS, and Xerox Corporation makes no
23 ;;;; warranty about the software, its performance or its conformity to any
24 ;;;; specification.
25
26 (in-package "SB-PCL")
27
28 ;;;; Up to 1.0.9.24 SBCL used to have a sketched out implementation
29 ;;;; for optimizing GF calls inside method bodies using a PV approach,
30 ;;;; inherited from the original PCL. This was never completed, and
31 ;;;; was removed at that point to make the code easier to understand
32 ;;;; -- but:
33 ;;;;
34 ;;;; FIXME: It would be possible to optimize GF calls inside method
35 ;;;; bodies using permutation vectors: if all the arguments to the
36 ;;;; GF are specializers parameters, we can assign a permutation index
37 ;;;; to each such (GF . ARGS) tuple inside a method body, and use this
38 ;;;; to cache effective method functions.
39 \f
40 (declaim (inline make-pv-table))
41 (defstruct (pv-table (:predicate pv-tablep)
42                      (:copier nil))
43   (cache nil :type (or cache null))
44   (pv-size 0 :type fixnum)
45   (slot-name-lists nil :type list))
46
47 (defun make-pv-table-type-declaration (var)
48   `(type pv-table ,var))
49
50 ;;; Used for interning parts of SLOT-NAME-LISTS, as part of
51 ;;; PV-TABLE interning -- just to save space.
52 (defvar *slot-name-lists* (make-hash-table :test 'equal))
53
54 ;;; Used for interning PV-TABLES, keyed by the SLOT-NAME-LISTS
55 ;;; used.
56 (defvar *pv-tables* (make-hash-table :test 'equal))
57
58 ;;; ...and one lock to rule them. Spinlock because for certain (rare)
59 ;;; cases this lock might be grabbed in the course of method dispatch
60 ;;; -- and mostly this is already under the *big-compiler-lock*.
61 (defvar *pv-lock*
62   (sb-thread::make-spinlock :name "pv table index lock"))
63
64 (defun intern-pv-table (&key slot-name-lists)
65   (flet ((intern-slot-names (slot-names)
66            ;; FIXME: NIL at the head of the list is a remnant from
67            ;; old purged code, that hasn't been quite cleaned up yet.
68            ;; ...but as long as we assume it is there, we may as well
69            ;; assert it.
70            (aver (not (car slot-names)))
71            (or (gethash slot-names *slot-name-lists*)
72                (setf (gethash slot-names *slot-name-lists*) slot-names)))
73          (%intern-pv-table (snl)
74            (or (gethash snl *pv-tables*)
75                (setf (gethash snl *pv-tables*)
76                      (make-pv-table :slot-name-lists snl
77                                     :pv-size (reduce #'+ snl
78                                                      :key (lambda (slots)
79                                                             (length (cdr slots)))))))))
80     (sb-thread::with-spinlock (*pv-lock*)
81       (%intern-pv-table (mapcar #'intern-slot-names slot-name-lists)))))
82 \f
83 (defun optimize-slot-value-by-class-p (class slot-name type)
84   (or (not (eq *boot-state* 'complete))
85       (let ((slotd (find-slot-definition class slot-name)))
86         (and slotd
87              (slot-accessor-std-p slotd type)))))
88
89 (defun compute-pv-slot (slot-name wrapper class)
90   (when (optimize-slot-value-by-class-p class slot-name 'all)
91     (car (find-slot-cell wrapper slot-name))))
92
93 (defun compute-pv (slot-name-lists wrappers)
94   (unless (listp wrappers)
95     (setq wrappers (list wrappers)))
96   (let (elements)
97     (dolist (slot-names slot-name-lists)
98       (when slot-names
99         (let* ((wrapper (pop wrappers))
100                (std-p (typep wrapper 'wrapper))
101                (class (wrapper-class* wrapper)))
102           (dolist (slot-name (cdr slot-names))
103             (push (if std-p
104                       (compute-pv-slot slot-name wrapper class)
105                       nil)
106                   elements)))))
107     (let* ((n (length elements))
108            (pv (make-array n)))
109       (loop for i from (1- n) downto 0
110          do (setf (svref pv i) (pop elements)))
111       pv)))
112
113 (defun pv-table-lookup (pv-table pv-wrappers)
114   (let* ((slot-name-lists (pv-table-slot-name-lists pv-table))
115          (cache (or (pv-table-cache pv-table)
116                     (setf (pv-table-cache pv-table)
117                           (make-cache :key-count (- (length slot-name-lists)
118                                                     (count nil slot-name-lists))
119                                       :value t
120                                       :size 2)))))
121     (multiple-value-bind (hitp value) (probe-cache cache pv-wrappers)
122       (if hitp
123           value
124           (let* ((pv (compute-pv slot-name-lists pv-wrappers))
125                  (new-cache (fill-cache cache pv-wrappers pv)))
126             ;; This is safe: if another thread races us here the loser just
127             ;; misses the next time as well.
128             (unless (eq new-cache cache)
129               (setf (pv-table-cache pv-table) new-cache))
130             pv)))))
131
132 (defun make-pv-type-declaration (var)
133   `(type simple-vector ,var))
134 \f
135 (defun can-optimize-access (form required-parameters env)
136   (destructuring-bind (op var-form slot-name-form &optional new-value) form
137       (let ((type (ecase op
138                     (slot-value 'reader)
139                     (set-slot-value 'writer)
140                     (slot-boundp 'boundp)))
141             (var (extract-the var-form))
142             (slot-name (constant-form-value slot-name-form env)))
143         (when (symbolp var)
144           (let* ((rebound? (caddr (var-declaration '%variable-rebinding var env)))
145                  (parameter-or-nil (car (memq (or rebound? var)
146                                               required-parameters))))
147             (when parameter-or-nil
148               (let* ((class-name (caddr (var-declaration '%class
149                                                          parameter-or-nil
150                                                          env)))
151                      (class (find-class class-name nil)))
152                 (when (or (not (eq *boot-state* 'complete))
153                           (and class (not (class-finalized-p class))))
154                   (setq class nil))
155                 (when (and class-name (not (eq class-name t)))
156                   (when (or (null type)
157                             (not (and class
158                                       (memq *the-class-structure-object*
159                                             (class-precedence-list class))))
160                             (optimize-slot-value-by-class-p class slot-name type))
161                     (values (cons parameter-or-nil (or class class-name))
162                             slot-name
163                             new-value))))))))))
164
165 ;;; Check whether the binding of the named variable is modified in the
166 ;;; method body.
167 (defun parameter-modified-p (parameter-name env)
168   (let ((modified-variables (macroexpand '%parameter-binding-modified env)))
169     (memq parameter-name modified-variables)))
170
171 (defun optimize-slot-value (form slots required-parameters env)
172   (multiple-value-bind (sparameter slot-name)
173       (can-optimize-access form required-parameters env)
174     (if sparameter
175         (let ((optimized-form
176                (optimize-instance-access slots :read sparameter
177                                          slot-name nil)))
178              ;; We don't return the optimized form directly, since there's
179              ;; still a chance that we'll find out later on that the
180              ;; optimization should not have been done, for example due to
181              ;; the walker encountering a SETQ on SPARAMETER later on in
182              ;; the body [ see for example clos.impure.lisp test with :name
183              ;; ((:setq :method-parameter) slot-value)) ]. Instead we defer
184              ;; the decision until the compiler macroexpands
185              ;; OPTIMIZED-SLOT-VALUE.
186              ;;
187              ;; Note that we must still call OPTIMIZE-INSTANCE-ACCESS at
188              ;; this point (instead of when expanding
189              ;; OPTIMIZED-SLOT-VALUE), since it mutates the structure of
190              ;; SLOTS. If that mutation isn't done during the walking,
191              ;; MAKE-METHOD-LAMBDA-INTERNAL won't wrap a correct PV-BINDING
192              ;; form around the body, and compilation will fail.  -- JES,
193              ;; 2006-09-18
194              `(optimized-slot-value ,form ,(car sparameter) ,optimized-form))
195            `(accessor-slot-value ,@(cdr form)))))
196
197 (defmacro optimized-slot-value (form parameter-name optimized-form
198                                 &environment env)
199   ;; Either use OPTIMIZED-FORM or fall back to the safe
200   ;; ACCESSOR-SLOT-VALUE.
201   (if (parameter-modified-p parameter-name env)
202       `(accessor-slot-value ,@(cdr form))
203       optimized-form))
204
205 (defun optimize-set-slot-value (form slots required-parameters env)
206   (multiple-value-bind (sparameter slot-name new-value)
207       (can-optimize-access form required-parameters env)
208     (if sparameter
209         (let ((optimized-form
210                (optimize-instance-access slots :write sparameter
211                                          slot-name new-value)))
212              ;; See OPTIMIZE-SLOT-VALUE
213              `(optimized-set-slot-value ,form ,(car sparameter) ,optimized-form))
214            `(accessor-set-slot-value ,@(cdr form)))))
215
216 (defmacro optimized-set-slot-value (form parameter-name optimized-form
217                                     &environment env)
218   (cond ((safe-code-p env)
219          ;; Don't optimize slot value setting in safe code, since the
220          ;; optimized version will fail to catch some type errors
221          ;; (for example when a subclass declares a tighter type for
222          ;; the slot than a superclass).
223          `(safe-set-slot-value ,@(cdr form)))
224         ((parameter-modified-p parameter-name env)
225          `(accessor-set-slot-value ,@(cdr form)))
226         (t
227          optimized-form)))
228
229 (defun optimize-slot-boundp (form slots required-parameters env)
230   (multiple-value-bind (sparameter slot-name)
231       (can-optimize-access form required-parameters env)
232     (if sparameter
233         (let ((optimized-form
234                (optimize-instance-access slots :boundp sparameter
235                                          slot-name nil)))
236           ;; See OPTIMIZE-SLOT-VALUE
237           `(optimized-slot-boundp ,form ,(car sparameter) ,optimized-form))
238         `(accessor-slot-boundp ,@(cdr form)))))
239
240 (defmacro optimized-slot-boundp (form parameter-name optimized-form
241                                  &environment env)
242   (if (parameter-modified-p parameter-name env)
243       `(accessor-slot-boundp ,@(cdr form))
244       optimized-form))
245
246 ;;; The SLOTS argument is an alist, the CAR of each entry is the name
247 ;;; of a required parameter to the function. The alist is in order, so
248 ;;; the position of an entry in the alist corresponds to the
249 ;;; argument's position in the lambda list.
250 (defun optimize-instance-access (slots read/write sparameter slot-name
251                                  new-value)
252   (let ((class (if (consp sparameter) (cdr sparameter) *the-class-t*))
253         (parameter (if (consp sparameter) (car sparameter) sparameter)))
254     (if (and (eq *boot-state* 'complete)
255              (classp class)
256              (memq *the-class-structure-object* (class-precedence-list class)))
257         (let ((slotd (find-slot-definition class slot-name)))
258           (ecase read/write
259             (:read
260              `(,(slot-definition-defstruct-accessor-symbol slotd) ,parameter))
261             (:write
262              `(setf (,(slot-definition-defstruct-accessor-symbol slotd)
263                      ,parameter)
264                     ,new-value))
265             (:boundp
266              t)))
267         (let* ((parameter-entry (assq parameter slots))
268                (slot-entry      (assq slot-name (cdr parameter-entry)))
269                (position (posq parameter-entry slots))
270                (pv-offset-form (list 'pv-offset ''.PV-OFFSET.)))
271           (unless parameter-entry
272             (bug "slot optimization bewilderment: O-I-A"))
273           (unless slot-entry
274             (setq slot-entry (list slot-name))
275             (push slot-entry (cdr parameter-entry)))
276           (push pv-offset-form (cdr slot-entry))
277           (ecase read/write
278             (:read
279              `(instance-read ,pv-offset-form ,parameter ,position
280                              ',slot-name ',class))
281             (:write
282              `(let ((.new-value. ,new-value))
283                 (instance-write ,pv-offset-form ,parameter ,position
284                                 ',slot-name ',class .new-value.)))
285             (:boundp
286              `(instance-boundp ,pv-offset-form ,parameter ,position
287                                ',slot-name ',class)))))))
288
289 (define-walker-template pv-offset) ; These forms get munged by mutate slots.
290 (defmacro pv-offset (arg) arg)
291 (define-walker-template instance-accessor-parameter)
292 (defmacro instance-accessor-parameter (x) x)
293
294 ;;; It is safe for these two functions to be wrong. They just try to
295 ;;; guess what the most likely case will be.
296 (defun generate-fast-class-slot-access-p (class-form slot-name-form)
297   (let ((class (and (constantp class-form) (constant-form-value class-form)))
298         (slot-name (and (constantp slot-name-form)
299                         (constant-form-value slot-name-form))))
300     (and (eq *boot-state* 'complete)
301          (standard-class-p class)
302          (not (eq class *the-class-t*)) ; shouldn't happen, though.
303          (let ((slotd (find-slot-definition class slot-name)))
304            (and slotd (eq :class (slot-definition-allocation slotd)))))))
305
306 (defun skip-fast-slot-access-p (class-form slot-name-form type)
307   (let ((class (and (constantp class-form) (constant-form-value class-form)))
308         (slot-name (and (constantp slot-name-form)
309                         (constant-form-value slot-name-form))))
310     (and (eq *boot-state* 'complete)
311          (standard-class-p class)
312          (not (eq class *the-class-t*)) ; shouldn't happen, though.
313          ;; FIXME: Is this really right? "Don't skip if there is
314          ;; no slot definition."
315          (let ((slotd (find-slot-definition class slot-name)))
316            (and slotd
317                 (not (slot-accessor-std-p slotd type)))))))
318
319 (defmacro instance-read-internal (pv slots pv-offset default &optional kind)
320   (unless (member kind '(nil :instance :class))
321     (error "illegal kind argument to ~S: ~S" 'instance-read-internal kind))
322   (let* ((index (gensym))
323          (value index))
324     `(locally (declare #.*optimize-speed*)
325        (let ((,index (svref ,pv ,pv-offset)))
326          (setq ,value (typecase ,index
327                         ;; FIXME: the line marked by KLUDGE below (and
328                         ;; the analogous spot in
329                         ;; INSTANCE-WRITE-INTERNAL) is there purely to
330                         ;; suppress a type mismatch warning that
331                         ;; propagates through to user code.
332                         ;; Presumably SLOTS at this point can never
333                         ;; actually be NIL, but the compiler seems to
334                         ;; think it could, so we put this here to shut
335                         ;; it up.  (see also mail Rudi Schlatte
336                         ;; sbcl-devel 2003-09-21) -- CSR, 2003-11-30
337                         ,@(when (or (null kind) (eq kind :instance))
338                                 `((fixnum
339                                    (and ,slots ; KLUDGE
340                                         (clos-slots-ref ,slots ,index)))))
341                         ,@(when (or (null kind) (eq kind :class))
342                                 `((cons (cdr ,index))))
343                         (t +slot-unbound+)))
344          (if (eq ,value +slot-unbound+)
345              ,default
346              ,value)))))
347
348 (defmacro instance-read (pv-offset parameter position slot-name class)
349   (if (skip-fast-slot-access-p class slot-name 'reader)
350       `(accessor-slot-value ,parameter ,slot-name)
351       `(instance-read-internal .pv. ,(slot-vector-symbol position)
352         ,pv-offset (accessor-slot-value ,parameter ,slot-name)
353         ,(if (generate-fast-class-slot-access-p class slot-name)
354              :class :instance))))
355
356 (defmacro instance-write-internal (pv slots pv-offset new-value default
357                                       &optional kind)
358   (unless (member kind '(nil :instance :class))
359     (error "illegal kind argument to ~S: ~S" 'instance-write-internal kind))
360   (let* ((index (gensym)))
361     `(locally (declare #.*optimize-speed*)
362        (let ((,index (svref ,pv ,pv-offset)))
363          (typecase ,index
364            ,@(when (or (null kind) (eq kind :instance))
365                    `((fixnum (and ,slots
366                                   (setf (clos-slots-ref ,slots ,index)
367                                         ,new-value)))))
368            ,@(when (or (null kind) (eq kind :class))
369                    `((cons (setf (cdr ,index) ,new-value))))
370            (t ,default))))))
371
372 (defmacro instance-write (pv-offset parameter position slot-name class
373                           new-value)
374   (if (skip-fast-slot-access-p class slot-name 'writer)
375       `(accessor-set-slot-value ,parameter ,slot-name ,new-value)
376       `(instance-write-internal .pv. ,(slot-vector-symbol position)
377         ,pv-offset ,new-value
378         (accessor-set-slot-value ,parameter ,slot-name ,new-value)
379         ,(if (generate-fast-class-slot-access-p class slot-name)
380              :class :instance))))
381
382 (defmacro instance-boundp-internal (pv slots pv-offset default
383                                     &optional kind)
384   (unless (member kind '(nil :instance :class))
385     (error "illegal kind argument to ~S: ~S" 'instance-boundp-internal kind))
386   (let* ((index (gensym)))
387     `(locally (declare #.*optimize-speed*)
388        (let ((,index (svref ,pv ,pv-offset)))
389          (typecase ,index
390            ,@(when (or (null kind) (eq kind :instance))
391                    `((fixnum (not (and ,slots
392                                        (eq (clos-slots-ref ,slots ,index)
393                                            +slot-unbound+))))))
394            ,@(when (or (null kind) (eq kind :class))
395                    `((cons (not (eq (cdr ,index) +slot-unbound+)))))
396            (t ,default))))))
397
398 (defmacro instance-boundp (pv-offset parameter position slot-name class)
399   (if (skip-fast-slot-access-p class slot-name 'boundp)
400       `(accessor-slot-boundp ,parameter ,slot-name)
401       `(instance-boundp-internal .pv. ,(slot-vector-symbol position)
402         ,pv-offset (accessor-slot-boundp ,parameter ,slot-name)
403         ,(if (generate-fast-class-slot-access-p class slot-name)
404              :class :instance))))
405
406 ;;; This magic function has quite a job to do indeed.
407 ;;;
408 ;;; The careful reader will recall that <slots> contains all of the
409 ;;; optimized slot access forms produced by OPTIMIZE-INSTANCE-ACCESS.
410 ;;; Each of these is a call to either INSTANCE-READ or INSTANCE-WRITE.
411 ;;;
412 ;;; At the time these calls were produced, the first argument was
413 ;;; specified as the symbol .PV-OFFSET.; what we have to do now is
414 ;;; convert those pv-offset arguments into the actual number that is
415 ;;; the correct offset into the pv.
416 ;;;
417 ;;; But first, oh but first, we sort <slots> a bit so that for each
418 ;;; argument we have the slots in alphabetical order. This
419 ;;; canonicalizes the PV-TABLE's a bit and will hopefully lead to
420 ;;; having fewer PV's floating around. Even if the gain is only
421 ;;; modest, it costs nothing.
422 (defun slot-name-lists-from-slots (slots)
423   (let ((slots (mutate-slots slots)))
424     (let* ((slot-name-lists
425             (mapcar (lambda (parameter-entry)
426                       (cons nil (mapcar #'car (cdr parameter-entry))))
427                     slots)))
428       (mapcar (lambda (r+snl)
429                 (when (or (car r+snl) (cdr r+snl))
430                   r+snl))
431               slot-name-lists))))
432
433 (defun mutate-slots (slots)
434   (let ((sorted-slots (sort-slots slots))
435         (pv-offset -1))
436     (dolist (parameter-entry sorted-slots)
437       (dolist (slot-entry (cdr parameter-entry))
438         (incf pv-offset)
439         (dolist (form (cdr slot-entry))
440           (setf (cadr form) pv-offset))))
441     sorted-slots))
442
443 (defun symbol-pkg-name (sym)
444   (let ((pkg (symbol-package sym)))
445     (if pkg (package-name pkg) "")))
446
447 ;;; FIXME: Because of the existence of UNINTERN and RENAME-PACKAGE,
448 ;;; the part of this ordering which is based on SYMBOL-PKG-NAME is not
449 ;;; stable. This ordering is only used in to
450 ;;; SLOT-NAME-LISTS-FROM-SLOTS, where it serves to "canonicalize the
451 ;;; PV-TABLE's a bit and will hopefully lead to having fewer PV's
452 ;;; floating around", so it sounds as though the instability won't
453 ;;; actually lead to bugs, just small inefficiency. But still, it
454 ;;; would be better to reimplement this function as a comparison based
455 ;;; on SYMBOL-HASH:
456 ;;;   * stable comparison
457 ;;;   * smaller code (here, and in being able to discard SYMBOL-PKG-NAME)
458 ;;;   * faster code.
459 (defun symbol-lessp (a b)
460   (if (eq (symbol-package a)
461           (symbol-package b))
462       (string-lessp (symbol-name a)
463                     (symbol-name b))
464       (string-lessp (symbol-pkg-name a)
465                     (symbol-pkg-name b))))
466
467 (defun symbol-or-cons-lessp (a b)
468   (etypecase a
469     (symbol (etypecase b
470               (symbol (symbol-lessp a b))
471               (cons t)))
472     (cons   (etypecase b
473               (symbol nil)
474               (cons (if (eq (car a) (car b))
475                         (symbol-or-cons-lessp (cdr a) (cdr b))
476                         (symbol-or-cons-lessp (car a) (car b))))))))
477
478 (defun sort-slots (slots)
479   (mapcar (lambda (parameter-entry)
480             (cons (car parameter-entry)
481                   (sort (cdr parameter-entry)   ;slot entries
482                         #'symbol-or-cons-lessp
483                         :key #'car)))
484           slots))
485
486 \f
487 ;;;; This needs to work in terms of metatypes and also needs to work
488 ;;;; for automatically generated reader and writer functions.
489 ;;;; Automatically generated reader and writer functions use this
490 ;;;; stuff too.
491
492 (defmacro pv-binding ((required-parameters slot-name-lists pv-table-form)
493                       &body body)
494   (let (slot-vars pv-parameters)
495     (loop for slots in slot-name-lists
496           for required-parameter in required-parameters
497           for i from 0
498           do (when slots
499                (push required-parameter pv-parameters)
500                (push (slot-vector-symbol i) slot-vars)))
501     `(pv-binding1 (,pv-table-form
502                    ,(nreverse pv-parameters) ,(nreverse slot-vars))
503        ,@body)))
504
505 (defmacro pv-binding1 ((pv-table-form pv-parameters slot-vars)
506                        &body body)
507   `(pv-env (,pv-table-form ,pv-parameters)
508      (let (,@(mapcar (lambda (slot-var p) `(,slot-var (get-slots-or-nil ,p)))
509                      slot-vars pv-parameters))
510        (declare (ignorable ,@(mapcar #'identity slot-vars)))
511        ,@body)))
512
513 ;;; This will only be visible in PV-ENV when the default MAKE-METHOD-LAMBDA is
514 ;;; overridden.
515 (define-symbol-macro pv-env-environment overridden)
516
517 (defmacro pv-env (&environment env
518                   (pv-table-form pv-parameters)
519                   &rest forms)
520   ;; Decide which expansion to use based on the state of the PV-ENV-ENVIRONMENT
521   ;; symbol-macrolet.
522   (if (eq (macroexpand 'pv-env-environment env) 'default)
523       `(locally ,@forms)
524       `(let* ((.pv-table. ,pv-table-form)
525               (.pv. (pv-table-lookup-pv-args .pv-table. ,@pv-parameters)))
526         (declare ,(make-pv-type-declaration '.pv.))
527         ,@forms)))
528
529 (defvar *non-var-declarations*
530   ;; FIXME: VALUES was in this list, conditionalized with #+CMU, but I
531   ;; don't *think* CMU CL had, or SBCL has, VALUES declarations. If
532   ;; SBCL doesn't have 'em, VALUES should probably be removed from
533   ;; this list.
534   '(values
535     %method-name
536     %method-lambda-list
537     optimize
538     ftype
539     muffle-conditions
540     inline
541     notinline))
542
543 (defvar *var-declarations-with-arg*
544   '(%class
545     type))
546
547 (defvar *var-declarations-without-arg*
548   '(ignore
549     ignorable special dynamic-extent
550     ;; FIXME: Possibly this entire list and variable could go away.
551     ;; If not, certainly we should remove all these built-in typenames
552     ;; from the list, and replace them with a test for "is it a type
553     ;; name?" (CLTL1 allowed only built-in type names as declarations,
554     ;; but ANSI CL allows any type name as a declaration.)
555     array atom base-char bignum bit bit-vector character compiled-function
556     complex cons double-float extended-char
557     fixnum float function hash-table integer
558     keyword list long-float nil null number package pathname random-state ratio
559     rational readtable sequence short-float signed-byte simple-array
560     simple-bit-vector simple-string simple-vector single-float standard-char
561     stream string symbol t unsigned-byte vector))
562
563 (defun split-declarations (body args maybe-reads-params-p)
564   (let ((inner-decls nil)
565         (outer-decls nil)
566         decl)
567     (loop (when (null body) (return nil))
568           (setq decl (car body))
569           (unless (and (consp decl)
570                        (eq (car decl) 'declare))
571             (return nil))
572           (dolist (form (cdr decl))
573             (when (consp form)
574               (let ((declaration-name (car form)))
575                 (if (member declaration-name *non-var-declarations*)
576                     (push `(declare ,form) outer-decls)
577                     (let ((arg-p
578                            (member declaration-name
579                                    *var-declarations-with-arg*))
580                           (non-arg-p
581                            (member declaration-name
582                                    *var-declarations-without-arg*))
583                           (dname (list (pop form)))
584                           (inners nil) (outers nil))
585                       (unless (or arg-p non-arg-p)
586                         ;; FIXME: This warning, and perhaps the
587                         ;; various *VAR-DECLARATIONS-FOO* and/or
588                         ;; *NON-VAR-DECLARATIONS* variables,
589                         ;; could probably go away now that we're not
590                         ;; trying to be portable between different
591                         ;; CLTL1 hosts the way PCL was. (Note that to
592                         ;; do this right, we need to be able to handle
593                         ;; user-defined (DECLAIM (DECLARATION FOO))
594                         ;; stuff.)
595                         (warn "The declaration ~S is not understood by ~S.~@
596                                Please put ~S on one of the lists ~S,~%~S, or~%~S.~@
597                         (Assuming it is a variable declaration without argument)."
598                               declaration-name 'split-declarations
599                               declaration-name
600                               '*non-var-declarations*
601                               '*var-declarations-with-arg*
602                               '*var-declarations-without-arg*)
603                         (push declaration-name *var-declarations-without-arg*))
604                       (when arg-p
605                         (setq dname (append dname (list (pop form)))))
606                       (case (car dname)
607                         (%class (push `(declare (,@dname ,@form)) inner-decls))
608                         (t
609                          (dolist (var form)
610                            (if (member var args)
611                                ;; Quietly remove IGNORE declarations
612                                ;; on args when a next-method is
613                                ;; involved, to prevent compiler
614                                ;; warnings about ignored args being
615                                ;; read.
616                                (unless (and maybe-reads-params-p
617                                             (eq (car dname) 'ignore))
618                                  (push var outers))
619                                (push var inners)))
620                          (when outers
621                            (push `(declare (,@dname ,@outers)) outer-decls))
622                          (when inners
623                            (push
624                             `(declare (,@dname ,@inners))
625                             inner-decls)))))))))
626           (setq body (cdr body)))
627     (values outer-decls inner-decls body)))
628
629 ;;; Pull a name out of the %METHOD-NAME declaration in the function
630 ;;; body given, or return NIL if no %METHOD-NAME declaration is found.
631 (defun body-method-name (body)
632   (multiple-value-bind (real-body declarations documentation)
633       (parse-body body)
634     (declare (ignore real-body documentation))
635     (let ((name-decl (get-declaration '%method-name declarations)))
636       (and name-decl
637            (destructuring-bind (name) name-decl
638              name)))))
639
640 ;;; Convert a lambda expression containing a SB-PCL::%METHOD-NAME
641 ;;; declaration (which is a naming style internal to PCL) into an
642 ;;; SB-INT:NAMED-LAMBDA expression (which is a naming style used
643 ;;; throughout SBCL, understood by the main compiler); or if there's
644 ;;; no SB-PCL::%METHOD-NAME declaration, then just return the original
645 ;;; lambda expression.
646 (defun name-method-lambda (method-lambda)
647   (let ((method-name (body-method-name (cddr method-lambda))))
648     (if method-name
649         `(named-lambda (slow-method ,method-name) ,(rest method-lambda))
650         method-lambda)))
651
652 (defun make-method-initargs-form-internal (method-lambda initargs env)
653   (declare (ignore env))
654   (let (method-lambda-args
655         lmf ; becomes body of function
656         lmf-params)
657     (if (not (and (= 3 (length method-lambda))
658                   (= 2 (length (setq method-lambda-args (cadr method-lambda))))
659                   (consp (setq lmf (third method-lambda)))
660                   (eq 'simple-lexical-method-functions (car lmf))
661                   (eq (car method-lambda-args)
662                       (cadr (setq lmf-params (cadr lmf))))
663                   (eq (cadr method-lambda-args)
664                       (caddr lmf-params))))
665         `(list* :function ,(name-method-lambda method-lambda)
666                 ',initargs)
667         (let* ((lambda-list (car lmf-params))
668                (nreq 0)
669                (restp nil)
670                (args nil))
671           (dolist (arg lambda-list)
672             (when (member arg '(&optional &rest &key))
673               (setq restp t)
674               (return nil))
675             (when (eq arg '&aux)
676               (return nil))
677             (incf nreq)
678             (push arg args))
679           (setq args (nreverse args))
680           (setf (getf (getf initargs 'plist) :arg-info) (cons nreq restp))
681           (make-method-initargs-form-internal1
682            initargs (cddr lmf) args lmf-params restp)))))
683
684 (defun lambda-list-parameter-names (lambda-list)
685   ;; Given a valid lambda list, extract the parameter names.
686   (loop for x in lambda-list
687         with res = nil
688         do (unless (member x lambda-list-keywords)
689              (if (consp x)
690                  (let ((name (car x)))
691                    (if (consp name)
692                        ;; ... ((:BAR FOO) 1)
693                        (push (second name) res)
694                        ;; ... (FOO 1)
695                        (push name res))
696                    ;; ... (... 1 FOO-P)
697                    (let ((name-p (cddr x)))
698                      (when name-p
699                        (push (car name-p) res))))
700                  ;; ... FOO
701                  (push x res)))
702         finally (return res)))
703
704 (defun make-method-initargs-form-internal1
705     (initargs body req-args lmf-params restp)
706   (let* (;; The lambda-list of the method, minus specifiers
707          (lambda-list (car lmf-params))
708          ;; Names of the parameters that will be in the outermost lambda-list
709          ;; (and whose bound declarations thus need to be in OUTER-DECLS).
710          (outer-parameters req-args)
711          ;; The lambda-list used by BIND-ARGS
712          (bind-list lambda-list)
713          (setq-p (getf (cdr lmf-params) :setq-p))
714          (auxp (member '&aux bind-list))
715          (call-next-method-p (getf (cdr lmf-params) :call-next-method-p)))
716     ;; Try to use the normal function call machinery instead of BIND-ARGS
717     ;; binding the arguments, unless:
718     (unless (or ;; If all arguments are required, BIND-ARGS will be a no-op
719                 ;; in any case.
720                 (and (not restp) (not auxp))
721                 ;; CALL-NEXT-METHOD wants to use BIND-ARGS, and needs a
722                 ;; list of all non-required arguments.
723                 call-next-method-p)
724       (setf ;; We don't want a binding for .REST-ARG.
725             restp nil
726             ;; Get all the parameters for declaration parsing
727             outer-parameters (lambda-list-parameter-names lambda-list)
728             ;; Ensure that BIND-ARGS won't do anything (since
729             ;; BIND-LIST won't contain any non-required parameters,
730             ;; and REQ-ARGS will be of an equal length). We still want
731             ;; to pass BIND-LIST to FAST-LEXICAL-METHOD-FUNCTIONS so
732             ;; that BIND-FAST-LEXICAL-METHOD-FUNCTIONS can take care
733             ;; of rebinding SETQd required arguments around the method
734             ;; body.
735             bind-list req-args))
736     (multiple-value-bind (outer-decls inner-decls body-sans-decls)
737         (split-declarations
738          body outer-parameters (or call-next-method-p setq-p))
739       (let* ((rest-arg (when restp
740                          '.rest-arg.))
741              (fmf-lambda-list (if rest-arg
742                                   (append req-args (list '&rest rest-arg))
743                                   (if call-next-method-p
744                                       req-args
745                                       lambda-list))))
746         `(list*
747           :function
748           (let* ((fmf (,(if (body-method-name body) 'named-lambda 'lambda)
749                         ,@(when (body-method-name body)
750                                 ;; function name
751                                 (list (cons 'fast-method (body-method-name body))))
752                         ;; The lambda-list of the FMF
753                         (.pv. .next-method-call. ,@fmf-lambda-list)
754                         ;; body of the function
755                         (declare (ignorable .pv. .next-method-call.)
756                                  (disable-package-locks pv-env-environment))
757                         ,@outer-decls
758                         (symbol-macrolet ((pv-env-environment default))
759                           (fast-lexical-method-functions
760                               (,bind-list .next-method-call. ,req-args ,rest-arg
761                                 ,@(cdddr lmf-params))
762                             ,@inner-decls
763                             ,@body-sans-decls))))
764                  (mf (%make-method-function fmf nil)))
765             (set-funcallable-instance-function
766              mf (method-function-from-fast-function fmf ',(getf initargs 'plist)))
767             mf)
768           ',initargs)))))
769
770 ;;; Use arrays and hash tables and the fngen stuff to make this much
771 ;;; better. It doesn't really matter, though, because a function
772 ;;; returned by this will get called only when the user explicitly
773 ;;; funcalls a result of method-function. BUT, this is needed to make
774 ;;; early methods work.
775 (defun method-function-from-fast-function (fmf plist)
776   (declare (type function fmf))
777   (let* ((method-function nil)
778          (snl (getf plist :slot-name-lists))
779          (pv-table (when snl
780                      (intern-pv-table :slot-name-lists snl)))
781          (arg-info (getf plist :arg-info))
782          (nreq (car arg-info))
783          (restp (cdr arg-info)))
784     (setq method-function
785           (lambda (method-args next-methods)
786             (let* ((pv (when pv-table
787                          (get-pv method-args pv-table)))
788                    (nm (car next-methods))
789                    (nms (cdr next-methods))
790                    (nmc (when nm
791                           (make-method-call
792                            :function (if (std-instance-p nm)
793                                          (method-function nm)
794                                          nm)
795                            :call-method-args (list nms)))))
796               (apply fmf pv nmc method-args))))
797     ;; FIXME: this looks dangerous.
798     (let* ((fname (%fun-name fmf)))
799       (when (and fname (eq (car fname) 'fast-method))
800         (set-fun-name method-function (cons 'slow-method (cdr fname)))))
801     method-function))
802
803 ;;; this is similar to the above, only not quite.  Only called when
804 ;;; the MOP is heavily involved.  Not quite parallel to
805 ;;; METHOD-FUNCTION-FROM-FAST-METHOD-FUNCTION, because we can close
806 ;;; over the actual PV-CELL in this case.
807 (defun method-function-from-fast-method-call (fmc)
808   (let* ((fmf (fast-method-call-function fmc))
809          (pv (fast-method-call-pv fmc))
810          (arg-info (fast-method-call-arg-info fmc))
811          (nreq (car arg-info))
812          (restp (cdr arg-info)))
813     (lambda (method-args next-methods)
814       (let* ((nm (car next-methods))
815              (nms (cdr next-methods))
816              (nmc (when nm
817                     (make-method-call
818                      :function (if (std-instance-p nm)
819                                    (method-function nm)
820                                    nm)
821                      :call-method-args (list nms)))))
822         (apply fmf pv nmc method-args)))))
823
824 (defun get-pv (method-args pv-table)
825   (let ((pv-wrappers (pv-wrappers-from-all-args pv-table method-args)))
826     (when pv-wrappers
827       (pv-table-lookup pv-table pv-wrappers))))
828
829 (defun pv-table-lookup-pv-args (pv-table &rest pv-parameters)
830   (pv-table-lookup pv-table (pv-wrappers-from-pv-args pv-parameters)))
831
832 (defun pv-wrappers-from-pv-args (&rest args)
833   (loop for arg in args
834         collect (valid-wrapper-of arg)))
835
836 (defun pv-wrappers-from-all-args (pv-table args)
837   (loop for snl in (pv-table-slot-name-lists pv-table)
838         and arg in args
839         when snl
840         collect (valid-wrapper-of arg)))
841
842 ;;; Return the subset of WRAPPERS which is used in the cache
843 ;;; of PV-TABLE.
844 (defun pv-wrappers-from-all-wrappers (pv-table wrappers)
845   (loop for snl in (pv-table-slot-name-lists pv-table) and w in wrappers
846         when snl
847         collect w))