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