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