micro-optimize SKIP-FAST-SLOT-ACCESS-P
[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 \f
28 (defmacro instance-slot-index (wrapper slot-name)
29   `(let ((pos 0))
30      (declare (fixnum pos))
31      (block loop
32        (dolist (sn (wrapper-instance-slots-layout ,wrapper))
33          (when (eq ,slot-name sn) (return-from loop pos))
34          (incf pos)))))
35 \f
36 (defstruct (pv-table (:predicate pv-tablep)
37                      (:constructor make-pv-table-internal
38                                    (slot-name-lists call-list))
39                      (:copier nil))
40   (cache nil :type (or cache null))
41   (pv-size 0 :type fixnum)
42   (slot-name-lists nil :type list)
43   (call-list nil :type list))
44
45 #-sb-fluid (declaim (sb-ext:freeze-type pv-table))
46
47 ;;; FIXME: The comment below seem to indicate that this was intended
48 ;;; to be actually used, however, it isn't anymore, and was commented
49 ;;; out at 0.9.13.47. Also removed was code in MAKE-PV-TABLE that
50 ;;; pushed each new PV-TABLE onto this list. --NS 2006-06-18
51 ;;;
52 ;;;   help new slot-value-using-class methods affect fast iv access
53 ;;;
54 ;;;  (defvar *all-pv-table-list* nil)
55
56 (declaim (inline make-pv-table))
57 (defun make-pv-table (&key slot-name-lists call-list)
58   (make-pv-table-internal slot-name-lists call-list))
59
60 (defun make-pv-table-type-declaration (var)
61   `(type pv-table ,var))
62
63 (defvar *slot-name-lists-inner* (make-hash-table :test 'equal))
64 (defvar *slot-name-lists-outer* (make-hash-table :test 'equal))
65
66 ;;; Entries in this are lists of (table . pv-offset-list).
67 (defvar *pv-key-to-pv-table-table* (make-hash-table :test 'equal))
68
69 (defun intern-pv-table (&key slot-name-lists call-list)
70   (let ((new-p nil))
71     (flet ((inner (x)
72              (or (gethash x *slot-name-lists-inner*)
73                  (setf (gethash x *slot-name-lists-inner*) (copy-list x))))
74            (outer (x)
75              (or (gethash x *slot-name-lists-outer*)
76                  (setf (gethash x *slot-name-lists-outer*)
77                        (let ((snl (copy-list (cdr x)))
78                              (cl (car x)))
79                          (setq new-p t)
80                          (make-pv-table :slot-name-lists snl
81                                         :call-list cl))))))
82       (let ((pv-table
83              (outer (mapcar #'inner (cons call-list slot-name-lists)))))
84         (when new-p
85           (let ((pv-index 0))
86             (dolist (slot-name-list slot-name-lists)
87               (dolist (slot-name (cdr slot-name-list))
88                 (note-pv-table-reference slot-name pv-index pv-table)
89                 (incf pv-index)))
90             (dolist (gf-call call-list)
91               (note-pv-table-reference gf-call pv-index pv-table)
92               (incf pv-index))
93             (setf (pv-table-pv-size pv-table) pv-index)))
94         pv-table))))
95
96 (defun note-pv-table-reference (ref pv-offset pv-table)
97   (let ((entry (gethash ref *pv-key-to-pv-table-table*)))
98     (when (listp entry)
99       (let ((table-entry (assq pv-table entry)))
100         (when (and (null table-entry)
101                    (> (length entry) 8))
102           (let ((new-table-table (make-hash-table :size 16 :test 'eq)))
103             (dolist (table-entry entry)
104               (setf (gethash (car table-entry) new-table-table)
105                     (cdr table-entry)))
106             (setf (gethash ref *pv-key-to-pv-table-table*) new-table-table)))
107         (when (listp entry)
108           (if (null table-entry)
109               (let ((new (cons pv-table pv-offset)))
110                 (if (consp entry)
111                     (push new (cdr entry))
112                     (setf (gethash ref *pv-key-to-pv-table-table*)
113                           (list new))))
114               (push pv-offset (cdr table-entry)))
115           (return-from note-pv-table-reference nil))))
116     (let ((list (gethash pv-table entry)))
117       (if (consp list)
118           (push pv-offset (cdr list))
119           (setf (gethash pv-table entry) (list pv-offset)))))
120   nil)
121
122 (defun map-pv-table-references-of (ref function)
123   (let ((entry (gethash ref *pv-key-to-pv-table-table*)))
124     (if (listp entry)
125         (dolist (table+pv-offset-list entry)
126           (funcall function
127                    (car table+pv-offset-list)
128                    (cdr table+pv-offset-list)))
129         (maphash function entry)))
130   ref)
131 \f
132 (defun optimize-slot-value-by-class-p (class slot-name type)
133   (or (not (eq *boot-state* 'complete))
134       (let ((slotd (find-slot-definition class slot-name)))
135         (and slotd
136              (slot-accessor-std-p slotd type)))))
137
138 (defun compute-pv-slot (slot-name wrapper class class-slots)
139   (if (symbolp slot-name)
140       (when (optimize-slot-value-by-class-p class slot-name 'all)
141         (or (instance-slot-index wrapper slot-name)
142             (assq slot-name class-slots)))
143       (when (consp slot-name)
144         (case (first slot-name)
145           ((reader writer)
146            (when (eq *boot-state* 'complete)
147              (let ((gf (gdefinition (second slot-name))))
148                (when (generic-function-p gf)
149                  (accessor-values1 gf (first slot-name) class)))))
150           (t (bug "Don't know how to deal with ~S in ~S"
151                   slot-name 'compute-pv-slots))))))
152
153 (defun compute-pv (slot-name-lists wrappers)
154   (unless (listp wrappers)
155     (setq wrappers (list wrappers)))
156   (let (elements)
157     (dolist (slot-names slot-name-lists
158              (make-permutation-vector (nreverse elements)))
159       (when slot-names
160         (let* ((wrapper (pop wrappers))
161                (std-p (typep wrapper 'wrapper))
162                (class (wrapper-class* wrapper))
163                (class-slots (and std-p (wrapper-class-slots wrapper))))
164           (dolist (slot-name (cdr slot-names))
165             (push (if std-p
166                       (compute-pv-slot slot-name wrapper class class-slots)
167                       nil)
168                   elements)))))))
169
170 (defun compute-calls (call-list wrappers)
171   (declare (ignore call-list wrappers))
172   #||
173   (map 'vector
174        (lambda (call)
175          (compute-emf-from-wrappers call wrappers))
176        call-list)
177   ||#
178   '#())
179
180 #|| ; Need to finish this, then write the maintenance functions.
181 (defun compute-emf-from-wrappers (call wrappers)
182   (when call
183     (destructuring-bind (gf-name nreq restp arg-info) call
184       (if (eq gf-name 'make-instance)
185           (error "should not get here") ; there is another mechanism for this.
186           (lambda (&rest args)
187             (if (not (eq *boot-state* 'complete))
188                 (apply (gdefinition gf-name) args)
189                 (let* ((gf (gdefinition gf-name))
190                        (arg-info (arg-info-reader gf))
191                        (classes '?)
192                        (types '?)
193                        (emf (cache-miss-values-internal gf arg-info
194                                                         wrappers classes types
195                                                         'caching)))
196                   (update-all-pv-tables call wrappers emf)
197                   (invoke-emf emf args))))))))
198 ||#
199
200 (defun make-permutation-vector (indexes)
201   (make-array (length indexes) :initial-contents indexes))
202
203 (defun pv-table-lookup (pv-table pv-wrappers)
204   (let* ((slot-name-lists (pv-table-slot-name-lists pv-table))
205          (call-list (pv-table-call-list pv-table))
206          (cache (or (pv-table-cache pv-table)
207                     (setf (pv-table-cache pv-table)
208                           (make-cache :key-count (- (length slot-name-lists)
209                                                     (count nil slot-name-lists))
210                                       :value t
211                                       :size 2)))))
212     (multiple-value-bind (hitp value) (probe-cache cache pv-wrappers)
213       (if hitp
214           value
215           (let* ((pv (compute-pv slot-name-lists pv-wrappers))
216                  (calls (compute-calls call-list pv-wrappers))
217                  (pv-cell (cons pv calls))
218                  (new-cache (fill-cache cache pv-wrappers pv-cell)))
219             ;; This is safe: if another thread races us here the loser just
220             ;; misses the next time as well.
221             (unless (eq new-cache cache)
222               (setf (pv-table-cache pv-table) new-cache))
223             pv-cell)))))
224
225 (defun make-pv-type-declaration (var)
226   `(type simple-vector ,var))
227
228 (defmacro copy-pv (pv)
229   `(copy-seq ,pv))
230
231 (defun make-calls-type-declaration (var)
232   `(type simple-vector ,var))
233
234 (defmacro callsref (calls index)
235   `(svref ,calls ,index))
236
237 (defvar *pv-table-cache-update-info* nil)
238
239 (defun update-pv-table-cache-info (class)
240   (let ((slot-names-for-pv-table-update nil)
241         (new-icui nil))
242     (dolist (icu *pv-table-cache-update-info*)
243       (if (eq (car icu) class)
244           (pushnew (cdr icu) slot-names-for-pv-table-update)
245           (push icu new-icui)))
246     (setq *pv-table-cache-update-info* new-icui)
247     (when slot-names-for-pv-table-update
248       (update-all-pv-table-caches class slot-names-for-pv-table-update))))
249
250 (defun update-all-pv-table-caches (class slot-names)
251   (let* ((cwrapper (class-wrapper class))
252          (std-p (typep cwrapper 'wrapper))
253          (class-slots (and std-p (wrapper-class-slots cwrapper)))
254          (new-values
255           (mapcar
256            (lambda (slot-name)
257              (cons slot-name
258                    (if std-p
259                        (compute-pv-slot slot-name cwrapper class class-slots)
260                        nil)))
261            slot-names))
262          (pv-tables nil))
263     (dolist (slot-name slot-names)
264       (map-pv-table-references-of
265        slot-name
266        (lambda (pv-table pv-offset-list)
267          (declare (ignore pv-offset-list))
268          (pushnew pv-table pv-tables))))
269     (dolist (pv-table pv-tables)
270       (let* ((cache (pv-table-cache pv-table))
271              (slot-name-lists (pv-table-slot-name-lists pv-table))
272              (pv-size (pv-table-pv-size pv-table))
273              (pv-map (make-array pv-size :initial-element nil)))
274         (let ((map-index 0) (param-index 0))
275           (dolist (slot-name-list slot-name-lists)
276             (dolist (slot-name (cdr slot-name-list))
277               (let ((a (assoc slot-name new-values)))
278                 (setf (svref pv-map map-index)
279                       (and a (cons param-index (cdr a)))))
280               (incf map-index))
281             (incf param-index)))
282         (when cache
283           (map-cache (lambda (wrappers pv-cell)
284                        (update-slots-in-pv wrappers (car pv-cell)
285                                            cwrapper pv-size pv-map))
286                      cache))))))
287
288 (defun update-slots-in-pv (wrappers pv cwrapper pv-size pv-map)
289   (if (atom wrappers)
290       (when (eq cwrapper wrappers)
291         (dotimes-fixnum (i pv-size)
292           (let ((map (svref pv-map i)))
293             (when map
294               (aver (= (car map) 0))
295               (setf (svref pv i) (cdr map))))))
296       (when (memq cwrapper wrappers)
297         (let ((param 0))
298           (dolist (wrapper wrappers)
299             (when (eq wrapper cwrapper)
300               (dotimes-fixnum (i pv-size)
301                 (let ((map (svref pv-map i)))
302                   (when (and map (= (car map) param))
303                     (setf (svref pv i) (cdr map))))))
304             (incf param))))))
305 \f
306 (defun can-optimize-access (form required-parameters env)
307   (destructuring-bind (op var-form slot-name-form &optional new-value) form
308       (let ((type (ecase op
309                     (slot-value 'reader)
310                     (set-slot-value 'writer)
311                     (slot-boundp 'boundp)))
312             (var (extract-the var-form))
313             (slot-name (constant-form-value slot-name-form env)))
314         (when (symbolp var)
315           (let* ((rebound? (caddr (var-declaration '%variable-rebinding var env)))
316                  (parameter-or-nil (car (memq (or rebound? var)
317                                               required-parameters))))
318             (when parameter-or-nil
319               (let* ((class-name (caddr (var-declaration '%class
320                                                          parameter-or-nil
321                                                          env)))
322                      (class (find-class class-name nil)))
323                 (when (or (not (eq *boot-state* 'complete))
324                           (and class (not (class-finalized-p class))))
325                   (setq class nil))
326                 (when (and class-name (not (eq class-name t)))
327                   (when (or (null type)
328                             (not (and class
329                                       (memq *the-class-structure-object*
330                                             (class-precedence-list class))))
331                             (optimize-slot-value-by-class-p class slot-name type))
332                     (values (cons parameter-or-nil (or class class-name))
333                             slot-name
334                             new-value))))))))))
335
336 ;;; Check whether the binding of the named variable is modified in the
337 ;;; method body.
338 (defun parameter-modified-p (parameter-name env)
339   (let ((modified-variables (macroexpand '%parameter-binding-modified env)))
340     (memq parameter-name modified-variables)))
341
342 (defun optimize-slot-value (form slots required-parameters env)
343   (multiple-value-bind (sparameter slot-name)
344       (can-optimize-access form required-parameters env)
345     (if sparameter
346         (let ((optimized-form
347                (optimize-instance-access slots :read sparameter
348                                          slot-name nil)))
349              ;; We don't return the optimized form directly, since there's
350              ;; still a chance that we'll find out later on that the
351              ;; optimization should not have been done, for example due to
352              ;; the walker encountering a SETQ on SPARAMETER later on in
353              ;; the body [ see for example clos.impure.lisp test with :name
354              ;; ((:setq :method-parameter) slot-value)) ]. Instead we defer
355              ;; the decision until the compiler macroexpands
356              ;; OPTIMIZED-SLOT-VALUE.
357              ;;
358              ;; Note that we must still call OPTIMIZE-INSTANCE-ACCESS at
359              ;; this point (instead of when expanding
360              ;; OPTIMIZED-SLOT-VALUE), since it mutates the structure of
361              ;; SLOTS. If that mutation isn't done during the walking,
362              ;; MAKE-METHOD-LAMBDA-INTERNAL won't wrap a correct PV-BINDING
363              ;; form around the body, and compilation will fail.  -- JES,
364              ;; 2006-09-18
365              `(optimized-slot-value ,form ,(car sparameter) ,optimized-form))
366            `(accessor-slot-value ,@(cdr form)))))
367
368 (defmacro optimized-slot-value (form parameter-name optimized-form
369                                 &environment env)
370   ;; Either use OPTIMIZED-FORM or fall back to the safe
371   ;; ACCESSOR-SLOT-VALUE.
372   (if (parameter-modified-p parameter-name env)
373       `(accessor-slot-value ,@(cdr form))
374       optimized-form))
375
376 (defun optimize-set-slot-value (form slots required-parameters env)
377   (multiple-value-bind (sparameter slot-name new-value)
378       (can-optimize-access form required-parameters env)
379     (if sparameter
380         (let ((optimized-form
381                (optimize-instance-access slots :write sparameter
382                                          slot-name new-value)))
383              ;; See OPTIMIZE-SLOT-VALUE
384              `(optimized-set-slot-value ,form ,(car sparameter) ,optimized-form))
385            `(accessor-set-slot-value ,@(cdr form)))))
386
387 (defmacro optimized-set-slot-value (form parameter-name optimized-form
388                                     &environment env)
389   (cond ((safe-code-p env)
390          ;; Don't optimize slot value setting in safe code, since the
391          ;; optimized version will fail to catch some type errors
392          ;; (for example when a subclass declares a tighter type for
393          ;; the slot than a superclass).
394          `(safe-set-slot-value ,@(cdr form)))
395         ((parameter-modified-p parameter-name env)
396          `(accessor-set-slot-value ,@(cdr form)))
397         (t
398          optimized-form)))
399
400 (defun optimize-slot-boundp (form slots required-parameters env)
401   (multiple-value-bind (sparameter slot-name)
402       (can-optimize-access form required-parameters env)
403     (if sparameter
404         (let ((optimized-form
405                (optimize-instance-access slots :boundp sparameter
406                                          slot-name nil)))
407           ;; See OPTIMIZE-SLOT-VALUE
408           `(optimized-slot-boundp ,form ,(car sparameter) ,optimized-form))
409         `(accessor-slot-boundp ,@(cdr form)))))
410
411 (defmacro optimized-slot-boundp (form parameter-name optimized-form
412                                  &environment env)
413   (if (parameter-modified-p parameter-name env)
414       `(accessor-slot-boundp ,@(cdr form))
415       optimized-form))
416
417 ;;; The SLOTS argument is an alist, the CAR of each entry is the name
418 ;;; of a required parameter to the function. The alist is in order, so
419 ;;; the position of an entry in the alist corresponds to the
420 ;;; argument's position in the lambda list.
421 (defun optimize-instance-access (slots
422                                  read/write
423                                  sparameter
424                                  slot-name
425                                  new-value)
426   (let ((class (if (consp sparameter) (cdr sparameter) *the-class-t*))
427         (parameter (if (consp sparameter) (car sparameter) sparameter)))
428     (if (and (eq *boot-state* 'complete)
429              (classp class)
430              (memq *the-class-structure-object* (class-precedence-list class)))
431         (let ((slotd (find-slot-definition class slot-name)))
432           (ecase read/write
433             (:read
434              `(,(slot-definition-defstruct-accessor-symbol slotd) ,parameter))
435             (:write
436              `(setf (,(slot-definition-defstruct-accessor-symbol slotd)
437                      ,parameter)
438                     ,new-value))
439             (:boundp
440              t)))
441         (let* ((parameter-entry (assq parameter slots))
442                (slot-entry      (assq slot-name (cdr parameter-entry)))
443                (position (posq parameter-entry slots))
444                (pv-offset-form (list 'pv-offset ''.PV-OFFSET.)))
445           (unless parameter-entry
446             (bug "slot optimization bewilderment: O-I-A"))
447           (unless slot-entry
448             (setq slot-entry (list slot-name))
449             (push slot-entry (cdr parameter-entry)))
450           (push pv-offset-form (cdr slot-entry))
451           (ecase read/write
452             (:read
453              `(instance-read ,pv-offset-form ,parameter ,position
454                              ',slot-name ',class))
455             (:write
456              `(let ((.new-value. ,new-value))
457                 (instance-write ,pv-offset-form ,parameter ,position
458                                 ',slot-name ',class .new-value.)))
459             (:boundp
460              `(instance-boundp ,pv-offset-form ,parameter ,position
461                                ',slot-name ',class)))))))
462
463 (define-walker-template pv-offset) ; These forms get munged by mutate slots.
464 (defmacro pv-offset (arg) arg)
465 (define-walker-template instance-accessor-parameter)
466 (defmacro instance-accessor-parameter (x) x)
467
468 ;;; It is safe for these two functions to be wrong. They just try to
469 ;;; guess what the most likely case will be.
470 (defun generate-fast-class-slot-access-p (class-form slot-name-form)
471   (let ((class (and (constantp class-form) (constant-form-value class-form)))
472         (slot-name (and (constantp slot-name-form)
473                         (constant-form-value slot-name-form))))
474     (and (eq *boot-state* 'complete)
475          (standard-class-p class)
476          (not (eq class *the-class-t*)) ; shouldn't happen, though.
477          (let ((slotd (find-slot-definition class slot-name)))
478            (and slotd (eq :class (slot-definition-allocation slotd)))))))
479
480 (defun skip-fast-slot-access-p (class-form slot-name-form type)
481   (let ((class (and (constantp class-form) (constant-form-value class-form)))
482         (slot-name (and (constantp slot-name-form)
483                         (constant-form-value slot-name-form))))
484     (and (eq *boot-state* 'complete)
485          (standard-class-p class)
486          (not (eq class *the-class-t*)) ; shouldn't happen, though.
487          ;; FIXME: Is this really right? "Don't skip if there is
488          ;; no slot definition."
489          (let ((slotd (find-slot-definition class slot-name)))
490            (and slotd
491                 (not (slot-accessor-std-p slotd type)))))))
492
493 (defmacro instance-read-internal (pv slots pv-offset default &optional kind)
494   (unless (member kind '(nil :instance :class :default))
495     (error "illegal kind argument to ~S: ~S" 'instance-read-internal kind))
496   (if (eq kind :default)
497       default
498       (let* ((index (gensym))
499              (value index))
500         `(locally (declare #.*optimize-speed*)
501           (let ((,index (svref ,pv ,pv-offset)))
502             (setq ,value (typecase ,index
503                            ;; FIXME: the line marked by KLUDGE below
504                            ;; (and the analogous spot in
505                            ;; INSTANCE-WRITE-INTERNAL) is there purely
506                            ;; to suppress a type mismatch warning that
507                            ;; propagates through to user code.
508                            ;; Presumably SLOTS at this point can never
509                            ;; actually be NIL, but the compiler seems
510                            ;; to think it could, so we put this here
511                            ;; to shut it up.  (see also mail Rudi
512                            ;; Schlatte sbcl-devel 2003-09-21) -- CSR,
513                            ;; 2003-11-30
514                            ,@(when (or (null kind) (eq kind :instance))
515                                `((fixnum
516                                   (and ,slots ; KLUDGE
517                                    (clos-slots-ref ,slots ,index)))))
518                            ,@(when (or (null kind) (eq kind :class))
519                                `((cons (cdr ,index))))
520                            (t +slot-unbound+)))
521             (if (eq ,value +slot-unbound+)
522                 ,default
523                 ,value))))))
524
525 (defmacro instance-read (pv-offset parameter position slot-name class)
526   (if (skip-fast-slot-access-p class slot-name 'reader)
527       `(accessor-slot-value ,parameter ,slot-name)
528       `(instance-read-internal .pv. ,(slot-vector-symbol position)
529         ,pv-offset (accessor-slot-value ,parameter ,slot-name)
530         ,(if (generate-fast-class-slot-access-p class slot-name)
531              :class :instance))))
532
533 (defmacro instance-write-internal (pv slots pv-offset new-value default
534                                       &optional kind)
535   (unless (member kind '(nil :instance :class :default))
536     (error "illegal kind argument to ~S: ~S" 'instance-write-internal kind))
537   (if (eq kind :default)
538       default
539       (let* ((index (gensym)))
540         `(locally (declare #.*optimize-speed*)
541           (let ((,index (svref ,pv ,pv-offset)))
542             (typecase ,index
543               ,@(when (or (null kind) (eq kind :instance))
544                   `((fixnum (and ,slots
545                              (setf (clos-slots-ref ,slots ,index)
546                                    ,new-value)))))
547               ,@(when (or (null kind) (eq kind :class))
548                   `((cons (setf (cdr ,index) ,new-value))))
549               (t ,default)))))))
550
551 (defmacro instance-write (pv-offset
552                           parameter
553                           position
554                           slot-name
555                           class
556                           new-value)
557   (if (skip-fast-slot-access-p class slot-name 'writer)
558       `(accessor-set-slot-value ,parameter ,slot-name ,new-value)
559       `(instance-write-internal .pv. ,(slot-vector-symbol position)
560         ,pv-offset ,new-value
561         (accessor-set-slot-value ,parameter ,slot-name ,new-value)
562         ,(if (generate-fast-class-slot-access-p class slot-name)
563              :class :instance))))
564
565 (defmacro instance-boundp-internal (pv slots pv-offset default
566                                        &optional kind)
567   (unless (member kind '(nil :instance :class :default))
568     (error "illegal kind argument to ~S: ~S" 'instance-boundp-internal kind))
569   (if (eq kind :default)
570       default
571       (let* ((index (gensym)))
572         `(locally (declare #.*optimize-speed*)
573           (let ((,index (svref ,pv ,pv-offset)))
574             (typecase ,index
575               ,@(when (or (null kind) (eq kind :instance))
576                   `((fixnum (not (and ,slots
577                                       (eq (clos-slots-ref ,slots ,index)
578                                           +slot-unbound+))))))
579               ,@(when (or (null kind) (eq kind :class))
580                   `((cons (not (eq (cdr ,index) +slot-unbound+)))))
581               (t ,default)))))))
582
583 (defmacro instance-boundp (pv-offset parameter position slot-name class)
584   (if (skip-fast-slot-access-p class slot-name 'boundp)
585       `(accessor-slot-boundp ,parameter ,slot-name)
586       `(instance-boundp-internal .pv. ,(slot-vector-symbol position)
587         ,pv-offset (accessor-slot-boundp ,parameter ,slot-name)
588         ,(if (generate-fast-class-slot-access-p class slot-name)
589              :class :instance))))
590
591 ;;; This magic function has quite a job to do indeed.
592 ;;;
593 ;;; The careful reader will recall that <slots> contains all of the
594 ;;; optimized slot access forms produced by OPTIMIZE-INSTANCE-ACCESS.
595 ;;; Each of these is a call to either INSTANCE-READ or INSTANCE-WRITE.
596 ;;;
597 ;;; At the time these calls were produced, the first argument was
598 ;;; specified as the symbol .PV-OFFSET.; what we have to do now is
599 ;;; convert those pv-offset arguments into the actual number that is
600 ;;; the correct offset into the pv.
601 ;;;
602 ;;; But first, oh but first, we sort <slots> a bit so that for each
603 ;;; argument we have the slots in alphabetical order. This
604 ;;; canonicalizes the PV-TABLE's a bit and will hopefully lead to
605 ;;; having fewer PV's floating around. Even if the gain is only
606 ;;; modest, it costs nothing.
607 (defun slot-name-lists-from-slots (slots calls)
608   (multiple-value-bind (slots calls) (mutate-slots-and-calls slots calls)
609     (let* ((slot-name-lists
610             (mapcar (lambda (parameter-entry)
611                       (cons nil (mapcar #'car (cdr parameter-entry))))
612                     slots))
613            (call-list
614             (mapcar #'car calls)))
615       (dolist (call call-list)
616         (dolist (arg (cdr call))
617           (when (integerp arg)
618             (setf (car (nth arg slot-name-lists)) t))))
619       (setq slot-name-lists (mapcar (lambda (r+snl)
620                                       (when (or (car r+snl) (cdr r+snl))
621                                         r+snl))
622                                     slot-name-lists))
623       (let ((cvt (apply #'vector
624                         (let ((i -1))
625                           (mapcar (lambda (r+snl)
626                                     (when r+snl (incf i)))
627                                   slot-name-lists)))))
628         (setq call-list (mapcar (lambda (call)
629                                   (cons (car call)
630                                         (mapcar (lambda (arg)
631                                                   (if (integerp arg)
632                                                       (svref cvt arg)
633                                                       arg))
634                                                 (cdr call))))
635                                 call-list)))
636       (values slot-name-lists call-list))))
637
638 (defun mutate-slots-and-calls (slots calls)
639   (let ((sorted-slots (sort-slots slots))
640         (sorted-calls (sort-calls (cdr calls)))
641         (pv-offset -1))
642     (dolist (parameter-entry sorted-slots)
643       (dolist (slot-entry (cdr parameter-entry))
644         (incf pv-offset)
645         (dolist (form (cdr slot-entry))
646           (setf (cadr form) pv-offset))))
647     (dolist (call-entry sorted-calls)
648       (incf pv-offset)
649       (dolist (form (cdr call-entry))
650         (setf (cadr form) pv-offset)))
651     (values sorted-slots sorted-calls)))
652
653 (defun symbol-pkg-name (sym)
654   (let ((pkg (symbol-package sym)))
655     (if pkg (package-name pkg) "")))
656
657 ;;; FIXME: Because of the existence of UNINTERN and RENAME-PACKAGE,
658 ;;; the part of this ordering which is based on SYMBOL-PKG-NAME is not
659 ;;; stable. This ordering is only used in to
660 ;;; SLOT-NAME-LISTS-FROM-SLOTS, where it serves to "canonicalize the
661 ;;; PV-TABLE's a bit and will hopefully lead to having fewer PV's
662 ;;; floating around", so it sounds as though the instability won't
663 ;;; actually lead to bugs, just small inefficiency. But still, it
664 ;;; would be better to reimplement this function as a comparison based
665 ;;; on SYMBOL-HASH:
666 ;;;   * stable comparison
667 ;;;   * smaller code (here, and in being able to discard SYMBOL-PKG-NAME)
668 ;;;   * faster code.
669 (defun symbol-lessp (a b)
670   (if (eq (symbol-package a)
671           (symbol-package b))
672       (string-lessp (symbol-name a)
673                     (symbol-name b))
674       (string-lessp (symbol-pkg-name a)
675                     (symbol-pkg-name b))))
676
677 (defun symbol-or-cons-lessp (a b)
678   (etypecase a
679     (symbol (etypecase b
680               (symbol (symbol-lessp a b))
681               (cons t)))
682     (cons   (etypecase b
683               (symbol nil)
684               (cons (if (eq (car a) (car b))
685                         (symbol-or-cons-lessp (cdr a) (cdr b))
686                         (symbol-or-cons-lessp (car a) (car b))))))))
687
688 (defun sort-slots (slots)
689   (mapcar (lambda (parameter-entry)
690             (cons (car parameter-entry)
691                   (sort (cdr parameter-entry)   ;slot entries
692                         #'symbol-or-cons-lessp
693                         :key #'car)))
694           slots))
695
696 (defun sort-calls (calls)
697   (sort calls #'symbol-or-cons-lessp :key #'car))
698 \f
699 ;;;; This needs to work in terms of metatypes and also needs to work
700 ;;;; for automatically generated reader and writer functions.
701 ;;;; Automatically generated reader and writer functions use this
702 ;;;; stuff too.
703
704 (defmacro pv-binding ((required-parameters slot-name-lists pv-table-form)
705                       &body body)
706   (let (slot-vars pv-parameters)
707     (loop for slots in slot-name-lists
708           for required-parameter in required-parameters
709           for i from 0
710           do (when slots
711                (push required-parameter pv-parameters)
712                (push (slot-vector-symbol i) slot-vars)))
713     `(pv-binding1 (.pv. .calls. ,pv-table-form
714                    ,(nreverse pv-parameters) ,(nreverse slot-vars))
715        ,@body)))
716
717 (defmacro pv-binding1 ((pv calls pv-table-form pv-parameters slot-vars)
718                        &body body)
719   `(pv-env (,pv ,calls ,pv-table-form ,pv-parameters)
720      (let (,@(mapcar (lambda (slot-var p) `(,slot-var (get-slots-or-nil ,p)))
721                      slot-vars pv-parameters))
722        (declare (ignorable ,@(mapcar #'identity slot-vars)))
723        ,@body)))
724
725 ;;; This will only be visible in PV-ENV when the default MAKE-METHOD-LAMBDA is
726 ;;; overridden.
727 (define-symbol-macro pv-env-environment overridden)
728
729 (defmacro pv-env (&environment env
730                   (pv calls pv-table-form pv-parameters)
731                   &rest forms)
732   ;; Decide which expansion to use based on the state of the PV-ENV-ENVIRONMENT
733   ;; symbol-macrolet.
734   (if (eq (macroexpand 'pv-env-environment env) 'default)
735       `(let ((,pv (car .pv-cell.))
736              (,calls (cdr .pv-cell.)))
737          (declare ,(make-pv-type-declaration pv)
738                   ,(make-calls-type-declaration calls))
739          ,pv ,calls
740          ,@forms)
741       `(let* ((.pv-table. ,pv-table-form)
742               (.pv-cell. (pv-table-lookup-pv-args .pv-table. ,@pv-parameters))
743               (,pv (car .pv-cell.))
744               (,calls (cdr .pv-cell.)))
745         (declare ,(make-pv-type-declaration pv))
746         (declare ,(make-calls-type-declaration calls))
747         ,pv ,calls
748         ,@forms)))
749
750 (defvar *non-var-declarations*
751   ;; FIXME: VALUES was in this list, conditionalized with #+CMU, but I
752   ;; don't *think* CMU CL had, or SBCL has, VALUES declarations. If
753   ;; SBCL doesn't have 'em, VALUES should probably be removed from
754   ;; this list.
755   '(values
756     %method-name
757     %method-lambda-list
758     optimize
759     ftype
760     muffle-conditions
761     inline
762     notinline))
763
764 (defvar *var-declarations-with-arg*
765   '(%class
766     type))
767
768 (defvar *var-declarations-without-arg*
769   '(ignore
770     ignorable special dynamic-extent
771     ;; FIXME: Possibly this entire list and variable could go away.
772     ;; If not, certainly we should remove all these built-in typenames
773     ;; from the list, and replace them with a test for "is it a type
774     ;; name?" (CLTL1 allowed only built-in type names as declarations,
775     ;; but ANSI CL allows any type name as a declaration.)
776     array atom base-char bignum bit bit-vector character compiled-function
777     complex cons double-float extended-char
778     fixnum float function hash-table integer
779     keyword list long-float nil null number package pathname random-state ratio
780     rational readtable sequence short-float signed-byte simple-array
781     simple-bit-vector simple-string simple-vector single-float standard-char
782     stream string symbol t unsigned-byte vector))
783
784 (defun split-declarations (body args maybe-reads-params-p)
785   (let ((inner-decls nil)
786         (outer-decls nil)
787         decl)
788     (loop (when (null body) (return nil))
789           (setq decl (car body))
790           (unless (and (consp decl)
791                        (eq (car decl) 'declare))
792             (return nil))
793           (dolist (form (cdr decl))
794             (when (consp form)
795               (let ((declaration-name (car form)))
796                 (if (member declaration-name *non-var-declarations*)
797                     (push `(declare ,form) outer-decls)
798                     (let ((arg-p
799                            (member declaration-name
800                                    *var-declarations-with-arg*))
801                           (non-arg-p
802                            (member declaration-name
803                                    *var-declarations-without-arg*))
804                           (dname (list (pop form)))
805                           (inners nil) (outers nil))
806                       (unless (or arg-p non-arg-p)
807                         ;; FIXME: This warning, and perhaps the
808                         ;; various *VAR-DECLARATIONS-FOO* and/or
809                         ;; *NON-VAR-DECLARATIONS* variables,
810                         ;; could probably go away now that we're not
811                         ;; trying to be portable between different
812                         ;; CLTL1 hosts the way PCL was. (Note that to
813                         ;; do this right, we need to be able to handle
814                         ;; user-defined (DECLAIM (DECLARATION FOO))
815                         ;; stuff.)
816                         (warn "The declaration ~S is not understood by ~S.~@
817                                Please put ~S on one of the lists ~S,~%~S, or~%~S.~@
818                         (Assuming it is a variable declaration without argument)."
819                               declaration-name 'split-declarations
820                               declaration-name
821                               '*non-var-declarations*
822                               '*var-declarations-with-arg*
823                               '*var-declarations-without-arg*)
824                         (push declaration-name *var-declarations-without-arg*))
825                       (when arg-p
826                         (setq dname (append dname (list (pop form)))))
827                       (case (car dname)
828                         (%class (push `(declare (,@dname ,@form)) inner-decls))
829                         (t
830                          (dolist (var form)
831                            (if (member var args)
832                                ;; Quietly remove IGNORE declarations
833                                ;; on args when a next-method is
834                                ;; involved, to prevent compiler
835                                ;; warnings about ignored args being
836                                ;; read.
837                                (unless (and maybe-reads-params-p
838                                             (eq (car dname) 'ignore))
839                                  (push var outers))
840                                (push var inners)))
841                          (when outers
842                            (push `(declare (,@dname ,@outers)) outer-decls))
843                          (when inners
844                            (push
845                             `(declare (,@dname ,@inners))
846                             inner-decls)))))))))
847           (setq body (cdr body)))
848     (values outer-decls inner-decls body)))
849
850 ;;; Pull a name out of the %METHOD-NAME declaration in the function
851 ;;; body given, or return NIL if no %METHOD-NAME declaration is found.
852 (defun body-method-name (body)
853   (multiple-value-bind (real-body declarations documentation)
854       (parse-body body)
855     (declare (ignore real-body documentation))
856     (let ((name-decl (get-declaration '%method-name declarations)))
857       (and name-decl
858            (destructuring-bind (name) name-decl
859              name)))))
860
861 ;;; Convert a lambda expression containing a SB-PCL::%METHOD-NAME
862 ;;; declaration (which is a naming style internal to PCL) into an
863 ;;; SB-INT:NAMED-LAMBDA expression (which is a naming style used
864 ;;; throughout SBCL, understood by the main compiler); or if there's
865 ;;; no SB-PCL::%METHOD-NAME declaration, then just return the original
866 ;;; lambda expression.
867 (defun name-method-lambda (method-lambda)
868   (let ((method-name (body-method-name (cddr method-lambda))))
869     (if method-name
870         `(named-lambda (slow-method ,method-name) ,(rest method-lambda))
871         method-lambda)))
872
873 (defun make-method-initargs-form-internal (method-lambda initargs env)
874   (declare (ignore env))
875   (let (method-lambda-args
876         lmf ; becomes body of function
877         lmf-params)
878     (if (not (and (= 3 (length method-lambda))
879                   (= 2 (length (setq method-lambda-args (cadr method-lambda))))
880                   (consp (setq lmf (third method-lambda)))
881                   (eq 'simple-lexical-method-functions (car lmf))
882                   (eq (car method-lambda-args)
883                       (cadr (setq lmf-params (cadr lmf))))
884                   (eq (cadr method-lambda-args)
885                       (caddr lmf-params))))
886         `(list* :function ,(name-method-lambda method-lambda)
887                 ',initargs)
888         (let* ((lambda-list (car lmf-params))
889                (nreq 0)
890                (restp nil)
891                (args nil))
892           (dolist (arg lambda-list)
893             (when (member arg '(&optional &rest &key))
894               (setq restp t)
895               (return nil))
896             (when (eq arg '&aux)
897               (return nil))
898             (incf nreq)
899             (push arg args))
900           (setq args (nreverse args))
901           (setf (getf (getf initargs 'plist) :arg-info) (cons nreq restp))
902           (make-method-initargs-form-internal1
903            initargs (cddr lmf) args lmf-params restp)))))
904
905 (defun lambda-list-parameter-names (lambda-list)
906   ;; Given a valid lambda list, extract the parameter names.
907   (loop for x in lambda-list
908         with res = nil
909         do (unless (member x lambda-list-keywords)
910              (if (consp x)
911                  (let ((name (car x)))
912                    (if (consp name)
913                        ;; ... ((:BAR FOO) 1)
914                        (push (second name) res)
915                        ;; ... (FOO 1)
916                        (push name res))
917                    ;; ... (... 1 FOO-P)
918                    (let ((name-p (cddr x)))
919                      (when name-p
920                        (push (car name-p) res))))
921                  ;; ... FOO
922                  (push x res)))
923         finally (return res)))
924
925 (defun make-method-initargs-form-internal1
926     (initargs body req-args lmf-params restp)
927   (let* (;; The lambda-list of the method, minus specifiers
928          (lambda-list (car lmf-params))
929          ;; Names of the parameters that will be in the outermost lambda-list
930          ;; (and whose bound declarations thus need to be in OUTER-DECLS).
931          (outer-parameters req-args)
932          ;; The lambda-list used by BIND-ARGS
933          (bind-list lambda-list)
934          (setq-p (getf (cdr lmf-params) :setq-p))
935          (auxp (member '&aux bind-list))
936          (call-next-method-p (getf (cdr lmf-params) :call-next-method-p)))
937     ;; Try to use the normal function call machinery instead of BIND-ARGS
938     ;; binding the arguments, unless:
939     (unless (or ;; If all arguments are required, BIND-ARGS will be a no-op
940                 ;; in any case.
941                 (and (not restp) (not auxp))
942                 ;; CALL-NEXT-METHOD wants to use BIND-ARGS, and needs a
943                 ;; list of all non-required arguments.
944                 call-next-method-p)
945       (setf ;; We don't want a binding for .REST-ARG.
946             restp nil
947             ;; Get all the parameters for declaration parsing
948             outer-parameters (lambda-list-parameter-names lambda-list)
949             ;; Ensure that BIND-ARGS won't do anything (since
950             ;; BIND-LIST won't contain any non-required parameters,
951             ;; and REQ-ARGS will be of an equal length). We still want
952             ;; to pass BIND-LIST to FAST-LEXICAL-METHOD-FUNCTIONS so
953             ;; that BIND-FAST-LEXICAL-METHOD-FUNCTIONS can take care
954             ;; of rebinding SETQd required arguments around the method
955             ;; body.
956             bind-list req-args))
957     (multiple-value-bind (outer-decls inner-decls body-sans-decls)
958         (split-declarations
959          body outer-parameters (or call-next-method-p setq-p))
960       (let* ((rest-arg (when restp
961                          '.rest-arg.))
962              (fmf-lambda-list (if rest-arg
963                                   (append req-args (list '&rest rest-arg))
964                                   (if call-next-method-p
965                                       req-args
966                                       lambda-list))))
967         `(list*
968           :function
969           (let* ((fmf (,(if (body-method-name body) 'named-lambda 'lambda)
970                         ,@(when (body-method-name body)
971                                 ;; function name
972                                 (list (cons 'fast-method (body-method-name body))))
973                         ;; The lambda-list of the FMF
974                         (.pv-cell. .next-method-call. ,@fmf-lambda-list)
975                         ;; body of the function
976                         (declare (ignorable .pv-cell. .next-method-call.)
977                                  (disable-package-locks pv-env-environment))
978                         ,@outer-decls
979                         (symbol-macrolet ((pv-env-environment default))
980                           (fast-lexical-method-functions
981                               (,bind-list .next-method-call. ,req-args ,rest-arg
982                                 ,@(cdddr lmf-params))
983                             ,@inner-decls
984                             ,@body-sans-decls))))
985                  (mf (%make-method-function fmf nil)))
986             (set-funcallable-instance-function
987              mf (method-function-from-fast-function fmf ',(getf initargs 'plist)))
988             mf)
989           ',initargs)))))
990
991 ;;; Use arrays and hash tables and the fngen stuff to make this much
992 ;;; better. It doesn't really matter, though, because a function
993 ;;; returned by this will get called only when the user explicitly
994 ;;; funcalls a result of method-function. BUT, this is needed to make
995 ;;; early methods work.
996 (defun method-function-from-fast-function (fmf plist)
997   (declare (type function fmf))
998   (let* ((method-function nil)
999          (calls (getf plist :call-list))
1000          (snl (getf plist :slot-name-lists))
1001          (pv-table (when (or calls snl)
1002                      (intern-pv-table :call-list calls :slot-name-lists snl)))
1003          (arg-info (getf plist :arg-info))
1004          (nreq (car arg-info))
1005          (restp (cdr arg-info)))
1006     (setq method-function
1007           (lambda (method-args next-methods)
1008             (let* ((pv-cell (when pv-table
1009                               (get-pv-cell method-args pv-table)))
1010                    (nm (car next-methods))
1011                    (nms (cdr next-methods))
1012                    (nmc (when nm
1013                           (make-method-call
1014                            :function (if (std-instance-p nm)
1015                                          (method-function nm)
1016                                          nm)
1017                            :call-method-args (list nms)))))
1018               (apply fmf pv-cell nmc method-args))))
1019     ;; FIXME: this looks dangerous.
1020     (let* ((fname (%fun-name fmf)))
1021       (when (and fname (eq (car fname) 'fast-method))
1022         (set-fun-name method-function (cons 'slow-method (cdr fname)))))
1023     method-function))
1024
1025 ;;; this is similar to the above, only not quite.  Only called when
1026 ;;; the MOP is heavily involved.  Not quite parallel to
1027 ;;; METHOD-FUNCTION-FROM-FAST-METHOD-FUNCTION, because we can close
1028 ;;; over the actual PV-CELL in this case.
1029 (defun method-function-from-fast-method-call (fmc)
1030   (let* ((fmf (fast-method-call-function fmc))
1031          (pv-cell (fast-method-call-pv-cell fmc))
1032          (arg-info (fast-method-call-arg-info fmc))
1033          (nreq (car arg-info))
1034          (restp (cdr arg-info)))
1035     (lambda (method-args next-methods)
1036       (let* ((nm (car next-methods))
1037              (nms (cdr next-methods))
1038              (nmc (when nm
1039                     (make-method-call
1040                      :function (if (std-instance-p nm)
1041                                    (method-function nm)
1042                                    nm)
1043                      :call-method-args (list nms)))))
1044         (apply fmf pv-cell nmc method-args)))))
1045
1046 (defun get-pv-cell (method-args pv-table)
1047   (let ((pv-wrappers (pv-wrappers-from-all-args pv-table method-args)))
1048     (when pv-wrappers
1049       (pv-table-lookup pv-table pv-wrappers))))
1050
1051 (defun pv-table-lookup-pv-args (pv-table &rest pv-parameters)
1052   (pv-table-lookup pv-table (pv-wrappers-from-pv-args pv-parameters)))
1053
1054 (defun pv-wrappers-from-pv-args (&rest args)
1055   (let (wrappers)
1056     (dolist (arg args (if (cdr wrappers) (nreverse wrappers) (car wrappers)))
1057       (let ((wrapper (wrapper-of arg)))
1058         (push (if (invalid-wrapper-p wrapper)
1059                   (check-wrapper-validity wrapper)
1060                   wrapper)
1061               wrappers)))))
1062
1063 (defun pv-wrappers-from-all-args (pv-table args)
1064   (loop for snl in (pv-table-slot-name-lists pv-table) and arg in args
1065         when snl
1066           collect (wrapper-of arg) into wrappers
1067         finally (return (if (cdr wrappers) wrappers (car wrappers)))))
1068
1069 ;;; Return the subset of WRAPPERS which is used in the cache
1070 ;;; of PV-TABLE.
1071 (defun pv-wrappers-from-all-wrappers (pv-table wrappers)
1072   (loop for snl in (pv-table-slot-name-lists pv-table) and w in wrappers
1073         when snl
1074           collect w into result
1075         finally (return (if (cdr result) result (car result)))))
1076