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