0.7.0.6:
[sbcl.git] / src / pcl / cache.lisp
1 ;;;; the basics of the PCL wrapper cache mechanism
2
3 ;;;; This software is part of the SBCL system. See the README file for
4 ;;;; more information.
5
6 ;;;; This software is derived from software originally released by Xerox
7 ;;;; Corporation. Copyright and release statements follow. Later modifications
8 ;;;; to the software are in the public domain and are provided with
9 ;;;; absolutely no warranty. See the COPYING and CREDITS files for more
10 ;;;; information.
11
12 ;;;; copyright information from original PCL sources:
13 ;;;;
14 ;;;; Copyright (c) 1985, 1986, 1987, 1988, 1989, 1990 Xerox Corporation.
15 ;;;; All rights reserved.
16 ;;;;
17 ;;;; Use and copying of this software and preparation of derivative works based
18 ;;;; upon this software are permitted. Any distribution of this software or
19 ;;;; derivative works must comply with all applicable United States export
20 ;;;; control laws.
21 ;;;;
22 ;;;; This software is made available AS IS, and Xerox Corporation makes no
23 ;;;; warranty about the software, its performance or its conformity to any
24 ;;;; specification.
25
26 (in-package "SB-PCL")
27 \f
28 ;;; The caching algorithm implemented:
29 ;;;
30 ;;; << put a paper here >>
31 ;;;
32 ;;; For now, understand that as far as most of this code goes, a cache
33 ;;; has two important properties. The first is the number of wrappers
34 ;;; used as keys in each cache line. Throughout this code, this value
35 ;;; is always called NKEYS. The second is whether or not the cache
36 ;;; lines of a cache store a value. Throughout this code, this always
37 ;;; called VALUEP.
38 ;;;
39 ;;; Depending on these values, there are three kinds of caches.
40 ;;;
41 ;;; NKEYS = 1, VALUEP = NIL
42 ;;;
43 ;;; In this kind of cache, each line is 1 word long. No cache locking
44 ;;; is needed since all read's in the cache are a single value.
45 ;;; Nevertheless line 0 (location 0) is reserved, to ensure that
46 ;;; invalid wrappers will not get a first probe hit.
47 ;;;
48 ;;; To keep the code simpler, a cache lock count does appear in
49 ;;; location 0 of these caches, that count is incremented whenever
50 ;;; data is written to the cache. But, the actual lookup code (see
51 ;;; make-dlap) doesn't need to do locking when reading the cache.
52 ;;;
53 ;;; NKEYS = 1, VALUEP = T
54 ;;;
55 ;;; In this kind of cache, each line is 2 words long. Cache locking
56 ;;; must be done to ensure the synchronization of cache reads. Line 0
57 ;;; of the cache (location 0) is reserved for the cache lock count.
58 ;;; Location 1 of the cache is unused (in effect wasted).
59 ;;;
60 ;;; NKEYS > 1
61 ;;;
62 ;;; In this kind of cache, the 0 word of the cache holds the lock
63 ;;; count. The 1 word of the cache is line 0. Line 0 of these caches
64 ;;; is not reserved.
65 ;;;
66 ;;; This is done because in this sort of cache, the overhead of doing
67 ;;; the cache probe is high enough that the 1+ required to offset the
68 ;;; location is not a significant cost. In addition, because of the
69 ;;; larger line sizes, the space that would be wasted by reserving
70 ;;; line 0 to hold the lock count is more significant.
71 \f
72 ;;; caches
73 ;;;
74 ;;; A cache is essentially just a vector. The use of the individual
75 ;;; `words' in the vector depends on particular properties of the
76 ;;; cache as described above.
77 ;;;
78 ;;; This defines an abstraction for caches in terms of their most
79 ;;; obvious implementation as simple vectors. But, please notice that
80 ;;; part of the implementation of this abstraction, is the function
81 ;;; lap-out-cache-ref. This means that most port-specific
82 ;;; modifications to the implementation of caches will require
83 ;;; corresponding port-specific modifications to the lap code
84 ;;; assembler.
85 (defmacro cache-vector-ref (cache-vector location)
86   `(svref (the simple-vector ,cache-vector)
87           (sb-ext:truly-the fixnum ,location)))
88
89 (defmacro cache-vector-size (cache-vector)
90   `(array-dimension (the simple-vector ,cache-vector) 0))
91
92 (defun allocate-cache-vector (size)
93   (make-array size :adjustable nil))
94
95 (defmacro cache-vector-lock-count (cache-vector)
96   `(cache-vector-ref ,cache-vector 0))
97
98 (defun flush-cache-vector-internal (cache-vector)
99   (sb-sys:without-interrupts
100     (fill (the simple-vector cache-vector) nil)
101     (setf (cache-vector-lock-count cache-vector) 0))
102   cache-vector)
103
104 (defmacro modify-cache (cache-vector &body body)
105   `(sb-sys:without-interrupts
106      (multiple-value-prog1
107        (progn ,@body)
108        (let ((old-count (cache-vector-lock-count ,cache-vector)))
109          (declare (fixnum old-count))
110          (setf (cache-vector-lock-count ,cache-vector)
111                (if (= old-count most-positive-fixnum)
112                    1 (the fixnum (1+ old-count))))))))
113
114 (deftype field-type ()
115   '(mod #.sb-kernel:layout-clos-hash-length))
116
117 (eval-when (:compile-toplevel :load-toplevel :execute)
118 (defun power-of-two-ceiling (x)
119   (declare (fixnum x))
120   ;;(expt 2 (ceiling (log x 2)))
121   (the fixnum (ash 1 (integer-length (1- x)))))
122 ) ; EVAL-WHEN
123
124 (defconstant +nkeys-limit+ 256)
125
126 (defstruct (cache (:constructor make-cache ())
127                   (:copier copy-cache-internal))
128   (owner nil)
129   (nkeys 1 :type (integer 1 #.+nkeys-limit+))
130   (valuep nil :type (member nil t))
131   (nlines 0 :type fixnum)
132   (field 0 :type field-type)
133   (limit-fn #'default-limit-fn :type function)
134   (mask 0 :type fixnum)
135   (size 0 :type fixnum)
136   (line-size 1 :type (integer 1 #.(power-of-two-ceiling (1+ +nkeys-limit+))))
137   (max-location 0 :type fixnum)
138   (vector #() :type simple-vector)
139   (overflow nil :type list))
140
141 #-sb-fluid (declaim (sb-ext:freeze-type cache))
142
143 (defmacro cache-lock-count (cache)
144   `(cache-vector-lock-count (cache-vector ,cache)))
145 \f
146 ;;; some facilities for allocation and freeing caches as they are needed
147
148 ;;; This is done on the assumption that a better port of PCL will
149 ;;; arrange to cons these all in the same static area. Given that, the
150 ;;; fact that PCL tries to reuse them should be a win.
151
152 (defvar *free-cache-vectors* (make-hash-table :size 16 :test 'eql))
153
154 ;;; Return a cache that has had FLUSH-CACHE-VECTOR-INTERNAL called on
155 ;;; it. This returns a cache of exactly the size requested, it won't
156 ;;; ever return a larger cache.
157 (defun get-cache-vector (size)
158   (let ((entry (gethash size *free-cache-vectors*)))
159     (sb-sys:without-interrupts
160       (cond ((null entry)
161              (setf (gethash size *free-cache-vectors*) (cons 0 nil))
162              (get-cache-vector size))
163             ((null (cdr entry))
164              (incf (car entry))
165              (flush-cache-vector-internal (allocate-cache-vector size)))
166             (t
167              (let ((cache (cdr entry)))
168                (setf (cdr entry) (cache-vector-ref cache 0))
169                (flush-cache-vector-internal cache)))))))
170
171 (defun free-cache-vector (cache-vector)
172   (let ((entry (gethash (cache-vector-size cache-vector) *free-cache-vectors*)))
173     (sb-sys:without-interrupts
174       (if (null entry)
175           (error
176            "attempt to free a cache-vector not allocated by GET-CACHE-VECTOR")
177           (let ((thread (cdr entry)))
178             (loop (unless thread (return))
179                   (when (eq thread cache-vector)
180                     (error "freeing a cache twice"))
181                   (setq thread (cache-vector-ref thread 0)))
182             (flush-cache-vector-internal cache-vector) ; to help the GC
183             (setf (cache-vector-ref cache-vector 0) (cdr entry))
184             (setf (cdr entry) cache-vector)
185             nil)))))
186
187 ;;; This is just for debugging and analysis. It shows the state of the
188 ;;; free cache resource.
189 #+sb-show
190 (defun show-free-cache-vectors ()
191   (let ((elements ()))
192     (maphash (lambda (s e) (push (list s e) elements)) *free-cache-vectors*)
193     (setq elements (sort elements #'< :key #'car))
194     (dolist (e elements)
195       (let* ((size (car e))
196              (entry (cadr e))
197              (allocated (car entry))
198              (head (cdr entry))
199              (free 0))
200         (loop (when (null head) (return t))
201               (setq head (cache-vector-ref head 0))
202               (incf free))
203         (format t
204                 "~&There are  ~4D caches of size  ~4D. (~D free  ~3D%)"
205                 allocated
206                 size
207                 free
208                 (floor (* 100 (/ free (float allocated)))))))))
209 \f
210 ;;;; wrapper cache numbers
211
212 ;;; The constant WRAPPER-CACHE-NUMBER-ADDS-OK controls the number of
213 ;;; non-zero bits wrapper cache numbers will have.
214 ;;;
215 ;;; The value of this constant is the number of wrapper cache numbers
216 ;;; which can be added and still be certain the result will be a
217 ;;; fixnum. This is used by all the code that computes primary cache
218 ;;; locations from multiple wrappers.
219 ;;;
220 ;;; The value of this constant is used to derive the next two which
221 ;;; are the forms of this constant which it is more convenient for the
222 ;;; runtime code to use.
223 (defconstant wrapper-cache-number-length
224   (integer-length sb-kernel:layout-clos-hash-max))
225 (defconstant wrapper-cache-number-mask sb-kernel:layout-clos-hash-max)
226 (defconstant wrapper-cache-number-adds-ok
227   (truncate most-positive-fixnum sb-kernel:layout-clos-hash-max))
228 \f
229 ;;;; wrappers themselves
230
231 ;;; This caching algorithm requires that wrappers have more than one
232 ;;; wrapper cache number. You should think of these multiple numbers
233 ;;; as being in columns. That is, for a given cache, the same column
234 ;;; of wrapper cache numbers will be used.
235 ;;;
236 ;;; If at some point the cache distribution of a cache gets bad, the
237 ;;; cache can be rehashed by switching to a different column.
238 ;;;
239 ;;; The columns are referred to by field number which is that number
240 ;;; which, when used as a second argument to wrapper-ref, will return
241 ;;; that column of wrapper cache number.
242 ;;;
243 ;;; This code is written to allow flexibility as to how many wrapper
244 ;;; cache numbers will be in each wrapper, and where they will be
245 ;;; located. It is also set up to allow port specific modifications to
246 ;;; `pack' the wrapper cache numbers on machines where the addressing
247 ;;; modes make that a good idea.
248
249 ;;; In SBCL, as in CMU CL, we want to do type checking as early as
250 ;;; possible; structures help this. The structures are hard-wired to
251 ;;; have a fixed number of cache hash values, and that number must
252 ;;; correspond to the number of cache lines we use.
253 (defconstant wrapper-cache-number-vector-length
254   sb-kernel:layout-clos-hash-length)
255
256 (unless (boundp '*the-class-t*)
257   (setq *the-class-t* nil))
258
259 (defmacro wrapper-class (wrapper)
260   `(sb-kernel:class-pcl-class (sb-kernel:layout-class ,wrapper)))
261 (defmacro wrapper-no-of-instance-slots (wrapper)
262   `(sb-kernel:layout-length ,wrapper))
263
264 ;;; WRAPPER-STATE returns T (not generalized boolean, but T exactly)
265 ;;; iff the wrapper is valid. Any other return value denotes some
266 ;;; invalid state. Special conventions have been set up for certain
267 ;;; invalid states, e.g. obsoleteness or flushedness, but I (WHN
268 ;;; 19991204) haven't been motivated to reverse engineer them from the
269 ;;; code and document them here.
270 ;;;
271 ;;; FIXME: This is awkward and unmnemonic. There is a function
272 ;;; (INVALID-WRAPPER-P) to test this return result abstractly for
273 ;;; invalidness but it's not called consistently; the functions that
274 ;;; need to know whether a wrapper is invalid often test (EQ
275 ;;; (WRAPPER-STATE X) T), ick. It would be good to use the abstract
276 ;;; test instead. It would probably be even better to switch the sense
277 ;;; of the WRAPPER-STATE function, renaming it to WRAPPER-INVALID and
278 ;;; making it synonymous with LAYOUT-INVALID. Then the
279 ;;; INVALID-WRAPPER-P function would become trivial and would go away
280 ;;; (replaced with WRAPPER-INVALID), since all the various invalid
281 ;;; wrapper states would become generalized boolean "true" values. --
282 ;;; WHN 19991204
283 #-sb-fluid (declaim (inline wrapper-state (setf wrapper-state)))
284 (defun wrapper-state (wrapper)
285   (let ((invalid (sb-kernel:layout-invalid wrapper)))
286     (cond ((null invalid)
287            t)
288           ((atom invalid)
289            ;; some non-PCL object. INVALID is probably :INVALID. We
290            ;; should arguably compute the new wrapper here instead of
291            ;; returning NIL, but we don't bother, since
292            ;; OBSOLETE-INSTANCE-TRAP can't use it.
293            '(:obsolete nil))
294           (t
295            invalid))))
296 (defun (setf wrapper-state) (new-value wrapper)
297   (setf (sb-kernel:layout-invalid wrapper)
298         (if (eq new-value t)
299             nil
300           new-value)))
301
302 (defmacro wrapper-instance-slots-layout (wrapper)
303   `(%wrapper-instance-slots-layout ,wrapper))
304 (defmacro wrapper-class-slots (wrapper)
305   `(%wrapper-class-slots ,wrapper))
306 (defmacro wrapper-cache-number-vector (x) x)
307
308 ;;; This is called in BRAID when we are making wrappers for classes
309 ;;; whose slots are not initialized yet, and which may be built-in
310 ;;; classes. We pass in the class name in addition to the class.
311 (defun boot-make-wrapper (length name &optional class)
312   (let ((found (cl:find-class name nil)))
313     (cond
314      (found
315       (unless (sb-kernel:class-pcl-class found)
316         (setf (sb-kernel:class-pcl-class found) class))
317       (aver (eq (sb-kernel:class-pcl-class found) class))
318       (let ((layout (sb-kernel:class-layout found)))
319         (aver layout)
320         layout))
321      (t
322       (make-wrapper-internal
323        :length length
324        :class (sb-kernel:make-standard-class :name name :pcl-class class))))))
325
326 ;;; The following variable may be set to a STANDARD-CLASS that has
327 ;;; already been created by the lisp code and which is to be redefined
328 ;;; by PCL. This allows STANDARD-CLASSes to be defined and used for
329 ;;; type testing and dispatch before PCL is loaded.
330 (defvar *pcl-class-boot* nil)
331
332 ;;; In SBCL, as in CMU CL, the layouts (a.k.a wrappers) for built-in
333 ;;; and structure classes already exist when PCL is initialized, so we
334 ;;; don't necessarily always make a wrapper. Also, we help maintain
335 ;;; the mapping between CL:CLASS and PCL::CLASS objects.
336 (defun make-wrapper (length class)
337   (cond
338    ((typep class 'std-class)
339     (make-wrapper-internal
340      :length length
341      :class
342      (let ((owrap (class-wrapper class)))
343        (cond (owrap
344               (sb-kernel:layout-class owrap))
345              ((*subtypep (class-of class)
346                          *the-class-standard-class*)
347               (cond ((and *pcl-class-boot*
348                           (eq (slot-value class 'name) *pcl-class-boot*))
349                      (let ((found (cl:find-class (slot-value class 'name))))
350                        (unless (sb-kernel:class-pcl-class found)
351                          (setf (sb-kernel:class-pcl-class found) class))
352                        (aver (eq (sb-kernel:class-pcl-class found) class))
353                        found))
354                     (t
355                      (sb-kernel:make-standard-class :pcl-class class))))
356              (t
357               (sb-kernel:make-random-pcl-class :pcl-class class))))))
358    (t
359     (let* ((found (cl:find-class (slot-value class 'name)))
360            (layout (sb-kernel:class-layout found)))
361       (unless (sb-kernel:class-pcl-class found)
362         (setf (sb-kernel:class-pcl-class found) class))
363       (aver (eq (sb-kernel:class-pcl-class found) class))
364       (aver layout)
365       layout))))
366
367 ;;; FIXME: The immediately following macros could become inline functions.
368
369 (defmacro first-wrapper-cache-number-index ()
370   0)
371
372 (defmacro next-wrapper-cache-number-index (field-number)
373   `(and (< ,field-number #.(1- wrapper-cache-number-vector-length))
374         (1+ ,field-number)))
375
376 (defmacro cache-number-vector-ref (cnv n)
377   `(wrapper-cache-number-vector-ref ,cnv ,n))
378
379 (defmacro wrapper-cache-number-vector-ref (wrapper n)
380   `(sb-kernel:layout-clos-hash ,wrapper ,n))
381
382 (defmacro class-no-of-instance-slots (class)
383   `(wrapper-no-of-instance-slots (class-wrapper ,class)))
384
385 (defmacro wrapper-class* (wrapper)
386   `(let ((wrapper ,wrapper))
387      (or (wrapper-class wrapper)
388          (find-structure-class
389           (cl:class-name (sb-kernel:layout-class wrapper))))))
390
391 ;;; The wrapper cache machinery provides general mechanism for
392 ;;; trapping on the next access to any instance of a given class. This
393 ;;; mechanism is used to implement the updating of instances when the
394 ;;; class is redefined (MAKE-INSTANCES-OBSOLETE). The same mechanism
395 ;;; is also used to update generic function caches when there is a
396 ;;; change to the superclasses of a class.
397 ;;;
398 ;;; Basically, a given wrapper can be valid or invalid. If it is
399 ;;; invalid, it means that any attempt to do a wrapper cache lookup
400 ;;; using the wrapper should trap. Also, methods on
401 ;;; SLOT-VALUE-USING-CLASS check the wrapper validity as well. This is
402 ;;; done by calling CHECK-WRAPPER-VALIDITY.
403
404 ;;; FIXME: could become inline function
405 (defmacro invalid-wrapper-p (wrapper)
406   `(neq (wrapper-state ,wrapper) t))
407
408 (defvar *previous-nwrappers* (make-hash-table))
409
410 (defun invalidate-wrapper (owrapper state nwrapper)
411   (ecase state
412     ((:flush :obsolete)
413      (let ((new-previous ()))
414        ;; First off, a previous call to INVALIDATE-WRAPPER may have
415        ;; recorded OWRAPPER as an NWRAPPER to update to. Since
416        ;; OWRAPPER is about to be invalid, it no longer makes sense to
417        ;; update to it.
418        ;;
419        ;; We go back and change the previously invalidated wrappers so
420        ;; that they will now update directly to NWRAPPER. This
421        ;; corresponds to a kind of transitivity of wrapper updates.
422        (dolist (previous (gethash owrapper *previous-nwrappers*))
423          (when (eq state :obsolete)
424            (setf (car previous) :obsolete))
425          (setf (cadr previous) nwrapper)
426          (push previous new-previous))
427
428        (let ((ocnv (wrapper-cache-number-vector owrapper)))
429          (dotimes (i sb-kernel:layout-clos-hash-length)
430            (setf (cache-number-vector-ref ocnv i) 0)))
431        (push (setf (wrapper-state owrapper) (list state nwrapper))
432              new-previous)
433
434        (setf (gethash owrapper *previous-nwrappers*) ()
435              (gethash nwrapper *previous-nwrappers*) new-previous)))))
436
437 (defun check-wrapper-validity (instance)
438   (let* ((owrapper (wrapper-of instance))
439          (state (wrapper-state owrapper)))
440     (if (eq state t)
441         owrapper
442         (let ((nwrapper
443                 (ecase (car state)
444                   (:flush
445                     (flush-cache-trap owrapper (cadr state) instance))
446                   (:obsolete
447                     (obsolete-instance-trap owrapper (cadr state) instance)))))
448           ;; This little bit of error checking is superfluous. It only
449           ;; checks to see whether the person who implemented the trap
450           ;; handling screwed up. Since that person is hacking
451           ;; internal PCL code, and is not a user, this should be
452           ;; needless. Also, since this directly slows down instance
453           ;; update and generic function cache refilling, feel free to
454           ;; take it out sometime soon.
455           ;;
456           ;; FIXME: We probably need to add a #+SB-PARANOID feature to
457           ;; make stuff like this optional. Until then, it stays in.
458           (cond ((neq nwrapper (wrapper-of instance))
459                  (error "wrapper returned from trap not wrapper of instance"))
460                 ((invalid-wrapper-p nwrapper)
461                  (error "wrapper returned from trap invalid")))
462           nwrapper))))
463
464 (defmacro check-wrapper-validity1 (object)
465   (let ((owrapper (gensym)))
466     `(let ((,owrapper (sb-kernel:layout-of object)))
467        (if (sb-kernel:layout-invalid ,owrapper)
468            (check-wrapper-validity ,object)
469            ,owrapper))))
470 \f
471 (defvar *free-caches* nil)
472
473 (defun get-cache (nkeys valuep limit-fn nlines)
474   (let ((cache (or (sb-sys:without-interrupts (pop *free-caches*))
475                    (make-cache))))
476     (declare (type cache cache))
477     (multiple-value-bind (cache-mask actual-size line-size nlines)
478         (compute-cache-parameters nkeys valuep nlines)
479       (setf (cache-nkeys cache) nkeys
480             (cache-valuep cache) valuep
481             (cache-nlines cache) nlines
482             (cache-field cache) (first-wrapper-cache-number-index)
483             (cache-limit-fn cache) limit-fn
484             (cache-mask cache) cache-mask
485             (cache-size cache) actual-size
486             (cache-line-size cache) line-size
487             (cache-max-location cache) (let ((line (1- nlines)))
488                                          (if (= nkeys 1)
489                                              (* line line-size)
490                                              (1+ (* line line-size))))
491             (cache-vector cache) (get-cache-vector actual-size)
492             (cache-overflow cache) nil)
493       cache)))
494
495 (defun get-cache-from-cache (old-cache new-nlines
496                              &optional (new-field (first-wrapper-cache-number-index)))
497   (let ((nkeys (cache-nkeys old-cache))
498         (valuep (cache-valuep old-cache))
499         (cache (or (sb-sys:without-interrupts (pop *free-caches*))
500                    (make-cache))))
501     (declare (type cache cache))
502     (multiple-value-bind (cache-mask actual-size line-size nlines)
503         (if (= new-nlines (cache-nlines old-cache))
504             (values (cache-mask old-cache) (cache-size old-cache)
505                     (cache-line-size old-cache) (cache-nlines old-cache))
506             (compute-cache-parameters nkeys valuep new-nlines))
507       (setf (cache-owner cache) (cache-owner old-cache)
508             (cache-nkeys cache) nkeys
509             (cache-valuep cache) valuep
510             (cache-nlines cache) nlines
511             (cache-field cache) new-field
512             (cache-limit-fn cache) (cache-limit-fn old-cache)
513             (cache-mask cache) cache-mask
514             (cache-size cache) actual-size
515             (cache-line-size cache) line-size
516             (cache-max-location cache) (let ((line (1- nlines)))
517                                          (if (= nkeys 1)
518                                              (* line line-size)
519                                              (1+ (* line line-size))))
520             (cache-vector cache) (get-cache-vector actual-size)
521             (cache-overflow cache) nil)
522       cache)))
523
524 (defun copy-cache (old-cache)
525   (let* ((new-cache (copy-cache-internal old-cache))
526          (size (cache-size old-cache))
527          (old-vector (cache-vector old-cache))
528          (new-vector (get-cache-vector size)))
529     (declare (simple-vector old-vector new-vector))
530     (dotimes-fixnum (i size)
531       (setf (svref new-vector i) (svref old-vector i)))
532     (setf (cache-vector new-cache) new-vector)
533     new-cache))
534
535 (defun free-cache (cache)
536   (free-cache-vector (cache-vector cache))
537   (setf (cache-vector cache) #())
538   (setf (cache-owner cache) nil)
539   (push cache *free-caches*)
540   nil)
541
542 (defun compute-line-size (x)
543   (power-of-two-ceiling x))
544
545 (defun compute-cache-parameters (nkeys valuep nlines-or-cache-vector)
546   ;;(declare (values cache-mask actual-size line-size nlines))
547   (declare (fixnum nkeys))
548   (if (= nkeys 1)
549       (let* ((line-size (if valuep 2 1))
550              (cache-size (if (typep nlines-or-cache-vector 'fixnum)
551                              (the fixnum
552                                   (* line-size
553                                      (the fixnum
554                                           (power-of-two-ceiling
555                                             nlines-or-cache-vector))))
556                              (cache-vector-size nlines-or-cache-vector))))
557         (declare (fixnum line-size cache-size))
558         (values (logxor (the fixnum (1- cache-size)) (the fixnum (1- line-size)))
559                 cache-size
560                 line-size
561                 (the (values fixnum t) (floor cache-size line-size))))
562       (let* ((line-size (power-of-two-ceiling (if valuep (1+ nkeys) nkeys)))
563              (cache-size (if (typep nlines-or-cache-vector 'fixnum)
564                              (the fixnum
565                                   (* line-size
566                                      (the fixnum
567                                           (power-of-two-ceiling
568                                             nlines-or-cache-vector))))
569                              (1- (cache-vector-size nlines-or-cache-vector)))))
570         (declare (fixnum line-size cache-size))
571         (values (logxor (the fixnum (1- cache-size)) (the fixnum (1- line-size)))
572                 (the fixnum (1+ cache-size))
573                 line-size
574                 (the (values fixnum t) (floor cache-size line-size))))))
575 \f
576 ;;; the various implementations of computing a primary cache location from
577 ;;; wrappers. Because some implementations of this must run fast there are
578 ;;; several implementations of the same algorithm.
579 ;;;
580 ;;; The algorithm is:
581 ;;;
582 ;;;  SUM       over the wrapper cache numbers,
583 ;;;  ENSURING  that the result is a fixnum
584 ;;;  MASK      the result against the mask argument.
585
586 ;;; The basic functional version. This is used by the cache miss code to
587 ;;; compute the primary location of an entry.
588 (defun compute-primary-cache-location (field mask wrappers)
589
590   (declare (type field-type field) (fixnum mask))
591   (if (not (listp wrappers))
592       (logand mask
593               (the fixnum (wrapper-cache-number-vector-ref wrappers field)))
594       (let ((location 0) (i 0))
595         (declare (fixnum location i))
596         (dolist (wrapper wrappers)
597           ;; First add the cache number of this wrapper to location.
598           (let ((wrapper-cache-number (wrapper-cache-number-vector-ref wrapper
599                                                                        field)))
600             (declare (fixnum wrapper-cache-number))
601             (if (zerop wrapper-cache-number)
602                 (return-from compute-primary-cache-location 0)
603                 (setq location
604                       (the fixnum (+ location wrapper-cache-number)))))
605           ;; Then, if we are working with lots of wrappers, deal with
606           ;; the wrapper-cache-number-mask stuff.
607           (when (and (not (zerop i))
608                      (zerop (mod i wrapper-cache-number-adds-ok)))
609             (setq location
610                   (logand location wrapper-cache-number-mask)))
611           (incf i))
612         (the fixnum (1+ (logand mask location))))))
613
614 ;;; This version is called on a cache line. It fetches the wrappers
615 ;;; from the cache line and determines the primary location. Various
616 ;;; parts of the cache filling code call this to determine whether it
617 ;;; is appropriate to displace a given cache entry.
618 ;;;
619 ;;; If this comes across a wrapper whose CACHE-NO is 0, it returns the
620 ;;; symbol invalid to suggest to its caller that it would be provident
621 ;;; to blow away the cache line in question.
622 (defun compute-primary-cache-location-from-location (to-cache
623                                                      from-location
624                                                      &optional
625                                                      (from-cache to-cache))
626   (declare (type cache to-cache from-cache) (fixnum from-location))
627   (let ((result 0)
628         (cache-vector (cache-vector from-cache))
629         (field (cache-field to-cache))
630         (mask (cache-mask to-cache))
631         (nkeys (cache-nkeys to-cache)))
632     (declare (type field-type field) (fixnum result mask nkeys)
633              (simple-vector cache-vector))
634     (dotimes-fixnum (i nkeys)
635       (let* ((wrapper (cache-vector-ref cache-vector (+ i from-location)))
636              (wcn (wrapper-cache-number-vector-ref wrapper field)))
637         (declare (fixnum wcn))
638         (setq result (+ result wcn)))
639       (when (and (not (zerop i))
640                  (zerop (mod i wrapper-cache-number-adds-ok)))
641         (setq result (logand result wrapper-cache-number-mask))))
642     (if (= nkeys 1)
643         (logand mask result)
644         (the fixnum (1+ (logand mask result))))))
645 \f
646 ;;;  NIL              means nothing so far, no actual arg info has NILs
647 ;;;                in the metatype
648 ;;;  CLASS          seen all sorts of metaclasses
649 ;;;                (specifically, more than one of the next 4 values)
650 ;;;  T          means everything so far is the class T
651 ;;;  STANDARD-CLASS   seen only standard classes
652 ;;;  BUILT-IN-CLASS   seen only built in classes
653 ;;;  STRUCTURE-CLASS  seen only structure classes
654 (defun raise-metatype (metatype new-specializer)
655   (let ((slot      (find-class 'slot-class))
656         (std       (find-class 'std-class))
657         (standard  (find-class 'standard-class))
658         (fsc       (find-class 'funcallable-standard-class))
659         (structure (find-class 'structure-class))
660         (built-in  (find-class 'built-in-class)))
661     (flet ((specializer->metatype (x)
662              (let ((meta-specializer
663                      (if (eq *boot-state* 'complete)
664                          (class-of (specializer-class x))
665                          (class-of x))))
666                (cond ((eq x *the-class-t*) t)
667                      ((*subtypep meta-specializer std)
668                       'standard-instance)
669                      ((*subtypep meta-specializer standard)
670                       'standard-instance)
671                      ((*subtypep meta-specializer fsc)
672                       'standard-instance)
673                      ((*subtypep meta-specializer structure)
674                       'structure-instance)
675                      ((*subtypep meta-specializer built-in)
676                       'built-in-instance)
677                      ((*subtypep meta-specializer slot)
678                       'slot-instance)
679                      (t (error "PCL cannot handle the specializer ~S (meta-specializer ~S)."
680                                new-specializer
681                                meta-specializer))))))
682       ;; We implement the following table. The notation is
683       ;; that X and Y are distinct meta specializer names.
684       ;;
685       ;;   NIL    <anything>    ===>  <anything>
686       ;;    X      X        ===>      X
687       ;;    X      Y        ===>    CLASS
688       (let ((new-metatype (specializer->metatype new-specializer)))
689         (cond ((eq new-metatype 'slot-instance) 'class)
690               ((null metatype) new-metatype)
691               ((eq metatype new-metatype) new-metatype)
692               (t 'class))))))
693
694 (defmacro with-dfun-wrappers ((args metatypes)
695                               (dfun-wrappers invalid-wrapper-p
696                                              &optional wrappers classes types)
697                               invalid-arguments-form
698                               &body body)
699   `(let* ((args-tail ,args) (,invalid-wrapper-p nil) (invalid-arguments-p nil)
700           (,dfun-wrappers nil) (dfun-wrappers-tail nil)
701           ,@(when wrappers
702               `((wrappers-rev nil) (types-rev nil) (classes-rev nil))))
703      (dolist (mt ,metatypes)
704        (unless args-tail
705          (setq invalid-arguments-p t)
706          (return nil))
707        (let* ((arg (pop args-tail))
708               (wrapper nil)
709               ,@(when wrappers
710                   `((class *the-class-t*)
711                     (type t))))
712          (unless (eq mt t)
713            (setq wrapper (wrapper-of arg))
714            (when (invalid-wrapper-p wrapper)
715              (setq ,invalid-wrapper-p t)
716              (setq wrapper (check-wrapper-validity arg)))
717            (cond ((null ,dfun-wrappers)
718                   (setq ,dfun-wrappers wrapper))
719                  ((not (consp ,dfun-wrappers))
720                   (setq dfun-wrappers-tail (list wrapper))
721                   (setq ,dfun-wrappers (cons ,dfun-wrappers dfun-wrappers-tail)))
722                  (t
723                   (let ((new-dfun-wrappers-tail (list wrapper)))
724                     (setf (cdr dfun-wrappers-tail) new-dfun-wrappers-tail)
725                     (setf dfun-wrappers-tail new-dfun-wrappers-tail))))
726            ,@(when wrappers
727                `((setq class (wrapper-class* wrapper))
728                  (setq type `(class-eq ,class)))))
729          ,@(when wrappers
730              `((push wrapper wrappers-rev)
731                (push class classes-rev)
732                (push type types-rev)))))
733      (if invalid-arguments-p
734          ,invalid-arguments-form
735          (let* (,@(when wrappers
736                     `((,wrappers (nreverse wrappers-rev))
737                       (,classes (nreverse classes-rev))
738                       (,types (mapcar (lambda (class)
739                                         `(class-eq ,class))
740                                       ,classes)))))
741            ,@body))))
742 \f
743 ;;;; some support stuff for getting a hold of symbols that we need when
744 ;;;; building the discriminator codes. It's OK for these to be interned
745 ;;;; symbols because we don't capture any user code in the scope in which
746 ;;;; these symbols are bound.
747
748 (defvar *dfun-arg-symbols* '(.ARG0. .ARG1. .ARG2. .ARG3.))
749
750 (defun dfun-arg-symbol (arg-number)
751   (or (nth arg-number (the list *dfun-arg-symbols*))
752       (intern (format nil ".ARG~A." arg-number) *pcl-package*)))
753
754 (defvar *slot-vector-symbols* '(.SLOTS0. .SLOTS1. .SLOTS2. .SLOTS3.))
755
756 (defun slot-vector-symbol (arg-number)
757   (or (nth arg-number (the list *slot-vector-symbols*))
758       (intern (format nil ".SLOTS~A." arg-number) *pcl-package*)))
759
760 ;; FIXME: There ought to be a good way to factor out the idiom:
761 ;;
762 ;; (dotimes (i (length metatypes))
763 ;;   (push (dfun-arg-symbol i) lambda-list))
764 ;;
765 ;; used in the following six functions into common code that we can
766 ;; declare inline or something.  --njf 2001-12-20
767 (defun make-dfun-lambda-list (metatypes applyp)
768   (let ((lambda-list nil))
769     (dotimes (i (length metatypes))
770       (push (dfun-arg-symbol i) lambda-list))
771     (when applyp
772       (push '&rest lambda-list)
773       (push '.dfun-rest-arg. lambda-list))
774     (nreverse lambda-list)))
775
776 (defun make-dlap-lambda-list (metatypes applyp)
777   (let ((lambda-list nil))
778     (dotimes (i (length metatypes))
779       (push (dfun-arg-symbol i) lambda-list))
780     ;; FIXME: This is translated directly from the old PCL code.
781     ;; It didn't have a (PUSH '.DFUN-REST-ARG. LAMBDA-LIST) or
782     ;; something similar, so we don't either.  It's hard to see how
783     ;; this could be correct, since &REST wants an argument after
784     ;; it.  This function works correctly because the caller
785     ;; magically tacks on something after &REST.  The calling functions
786     ;; (in dlisp.lisp) should be fixed and this function rewritten.
787     ;; --njf 2001-12-20
788     (when applyp
789       (push '&rest lambda-list))
790     (nreverse lambda-list)))
791
792 ;; FIXME: The next four functions suffer from having a `.DFUN-REST-ARG.'
793 ;; in their lambda lists, but no corresponding `&REST' symbol.  We assume
794 ;; this should be the case by analogy with the previous two functions.
795 ;; It works, and I don't know why.  Check the calling functions and
796 ;; fix these too.  --njf 2001-12-20
797 (defun make-emf-call (metatypes applyp fn-variable &optional emf-type)
798   (let ((required
799          (let ((required nil))
800            (dotimes (i (length metatypes))
801              (push (dfun-arg-symbol i) required))
802            (nreverse required))))
803     `(,(if (eq emf-type 'fast-method-call)
804            'invoke-effective-method-function-fast
805            'invoke-effective-method-function)
806       ,fn-variable ,applyp ,@required ,@(when applyp `(.dfun-rest-arg.)))))
807
808 (defun make-dfun-call (metatypes applyp fn-variable)
809   (let ((required
810          (let ((required nil))
811            (dotimes (i (length metatypes))
812              (push (dfun-arg-symbol i) required))
813            (nreverse required))))
814     (if applyp
815         `(function-apply   ,fn-variable ,@required .dfun-rest-arg.)
816         `(function-funcall ,fn-variable ,@required))))
817
818 (defun make-dfun-arg-list (metatypes applyp)
819   (let ((required
820          (let ((required nil))
821            (dotimes (i (length metatypes))
822              (push (dfun-arg-symbol i) required))
823            (nreverse required))))
824     (if applyp
825         `(list* ,@required .dfun-rest-arg.)
826         `(list ,@required))))
827
828 (defun make-fast-method-call-lambda-list (metatypes applyp)
829   (let ((lambda-list nil))
830     (push '.pv-cell. lambda-list)
831     (push '.next-method-call. lambda-list)
832     (dotimes (i (length metatypes))
833       (push (dfun-arg-symbol i) lambda-list))
834     (when applyp
835       (push '.dfun-rest-arg. lambda-list))
836     (nreverse lambda-list)))
837
838 \f
839 ;;;; a comment from some PCL implementor:
840 ;;;;     Its too bad Common Lisp compilers freak out when you have a
841 ;;;;   DEFUN with a lot of LABELS in it. If I could do that I could
842 ;;;;   make this code much easier to read and work with.
843 ;;;;     Ahh Scheme...
844 ;;;;     In the absence of that, the following little macro makes the
845 ;;;;   code that follows a little bit more reasonable. I would like to
846 ;;;;   add that having to practically write my own compiler in order to
847 ;;;;   get just this simple thing is something of a drag.
848 ;;;;
849 ;;;; KLUDGE: Maybe we could actually implement this as LABELS now,
850 ;;;; since AFAIK CMU CL doesn't freak out when you have a DEFUN with a
851 ;;;; lot of LABELS in it (and if it does we can fix it instead of
852 ;;;; working around it). -- WHN 19991204
853
854 (eval-when (:compile-toplevel :load-toplevel :execute)
855
856 (defvar *cache* nil)
857
858 ;;; FIXME: should be undefined after bootstrapping
859 (defparameter *local-cache-functions*
860   '((cache () .cache.)
861     (nkeys () (cache-nkeys .cache.))
862     (line-size () (cache-line-size .cache.))
863     (vector () (cache-vector .cache.))
864     (valuep () (cache-valuep .cache.))
865     (nlines () (cache-nlines .cache.))
866     (max-location () (cache-max-location .cache.))
867     (limit-fn () (cache-limit-fn .cache.))
868     (size () (cache-size .cache.))
869     (mask () (cache-mask .cache.))
870     (field () (cache-field .cache.))
871     (overflow () (cache-overflow .cache.))
872
873     ;; Return T IFF this cache location is reserved. The only time
874     ;; this is true is for line number 0 of an nkeys=1 cache.
875     (line-reserved-p (line)
876       (declare (fixnum line))
877       (and (= (nkeys) 1)
878            (= line 0)))
879     (location-reserved-p (location)
880       (declare (fixnum location))
881       (and (= (nkeys) 1)
882            (= location 0)))
883     ;; Given a line number, return the cache location. This is the
884     ;; value that is the second argument to cache-vector-ref. Basically,
885     ;; this deals with the offset of nkeys>1 caches and multiplies
886     ;; by line size.
887     (line-location (line)
888       (declare (fixnum line))
889       (when (line-reserved-p line)
890         (error "Line is reserved."))
891       (if (= (nkeys) 1)
892           (the fixnum (* line (line-size)))
893           (the fixnum (1+ (the fixnum (* line (line-size)))))))
894
895     ;; Given a cache location, return the line. This is the inverse
896     ;; of LINE-LOCATION.
897     (location-line (location)
898       (declare (fixnum location))
899       (if (= (nkeys) 1)
900           (floor location (line-size))
901           (floor (the fixnum (1- location)) (line-size))))
902
903     ;; Given a line number, return the wrappers stored at that line.
904     ;; As usual, if nkeys=1, this returns a single value. Only when
905     ;; nkeys>1 does it return a list. An error is signalled if the
906     ;; line is reserved.
907     (line-wrappers (line)
908       (declare (fixnum line))
909       (when (line-reserved-p line) (error "Line is reserved."))
910       (location-wrappers (line-location line)))
911     (location-wrappers (location) ; avoid multiplies caused by line-location
912       (declare (fixnum location))
913       (if (= (nkeys) 1)
914           (cache-vector-ref (vector) location)
915           (let ((list (make-list (nkeys)))
916                 (vector (vector)))
917             (declare (simple-vector vector))
918             (dotimes-fixnum (i (nkeys) list)
919               (setf (nth i list) (cache-vector-ref vector (+ location i)))))))
920
921     ;; Given a line number, return true IFF the line's
922     ;; wrappers are the same as wrappers.
923     (line-matches-wrappers-p (line wrappers)
924       (declare (fixnum line))
925       (and (not (line-reserved-p line))
926            (location-matches-wrappers-p (line-location line) wrappers)))
927     (location-matches-wrappers-p (loc wrappers) ; must not be reserved
928       (declare (fixnum loc))
929       (let ((cache-vector (vector)))
930         (declare (simple-vector cache-vector))
931         (if (= (nkeys) 1)
932             (eq wrappers (cache-vector-ref cache-vector loc))
933             (dotimes-fixnum (i (nkeys) t)
934               (unless (eq (pop wrappers)
935                           (cache-vector-ref cache-vector (+ loc i)))
936                 (return nil))))))
937
938     ;; Given a line number, return the value stored at that line.
939     ;; If valuep is NIL, this returns NIL. As with line-wrappers,
940     ;; an error is signalled if the line is reserved.
941     (line-value (line)
942       (declare (fixnum line))
943       (when (line-reserved-p line) (error "Line is reserved."))
944       (location-value (line-location line)))
945     (location-value (loc)
946       (declare (fixnum loc))
947       (and (valuep)
948            (cache-vector-ref (vector) (+ loc (nkeys)))))
949
950     ;; Given a line number, return true iff that line has data in
951     ;; it. The state of the wrappers stored in the line is not
952     ;; checked. An error is signalled if line is reserved.
953     (line-full-p (line)
954       (when (line-reserved-p line) (error "Line is reserved."))
955       (not (null (cache-vector-ref (vector) (line-location line)))))
956
957     ;; Given a line number, return true iff the line is full and
958     ;; there are no invalid wrappers in the line, and the line's
959     ;; wrappers are different from wrappers.
960     ;; An error is signalled if the line is reserved.
961     (line-valid-p (line wrappers)
962       (declare (fixnum line))
963       (when (line-reserved-p line) (error "Line is reserved."))
964       (location-valid-p (line-location line) wrappers))
965     (location-valid-p (loc wrappers)
966       (declare (fixnum loc))
967       (let ((cache-vector (vector))
968             (wrappers-mismatch-p (null wrappers)))
969         (declare (simple-vector cache-vector))
970         (dotimes-fixnum (i (nkeys) wrappers-mismatch-p)
971           (let ((wrapper (cache-vector-ref cache-vector (+ loc i))))
972             (when (or (null wrapper)
973                       (invalid-wrapper-p wrapper))
974               (return nil))
975             (unless (and wrappers
976                          (eq wrapper
977                              (if (consp wrappers) (pop wrappers) wrappers)))
978               (setq wrappers-mismatch-p t))))))
979
980     ;; how many unreserved lines separate line-1 and line-2
981     (line-separation (line-1 line-2)
982      (declare (fixnum line-1 line-2))
983      (let ((diff (the fixnum (- line-2 line-1))))
984        (declare (fixnum diff))
985        (when (minusp diff)
986          (setq diff (+ diff (nlines)))
987          (when (line-reserved-p 0)
988            (setq diff (1- diff))))
989        diff))
990
991     ;; Given a cache line, get the next cache line. This will not
992     ;; return a reserved line.
993     (next-line (line)
994      (declare (fixnum line))
995      (if (= line (the fixnum (1- (nlines))))
996          (if (line-reserved-p 0) 1 0)
997          (the fixnum (1+ line))))
998     (next-location (loc)
999       (declare (fixnum loc))
1000       (if (= loc (max-location))
1001           (if (= (nkeys) 1)
1002               (line-size)
1003               1)
1004           (the fixnum (+ loc (line-size)))))
1005
1006     ;; Given a line which has a valid entry in it, this will return
1007     ;; the primary cache line of the wrappers in that line. We just
1008     ;; call COMPUTE-PRIMARY-CACHE-LOCATION-FROM-LOCATION, this is an
1009     ;; easier packaging up of the call to it.
1010     (line-primary (line)
1011       (declare (fixnum line))
1012       (location-line (line-primary-location line)))
1013     (line-primary-location (line)
1014      (declare (fixnum line))
1015      (compute-primary-cache-location-from-location
1016        (cache) (line-location line)))))
1017
1018 (defmacro with-local-cache-functions ((cache) &body body)
1019   `(let ((.cache. ,cache))
1020      (declare (type cache .cache.))
1021      (macrolet ,(mapcar (lambda (fn)
1022                           `(,(car fn) ,(cadr fn)
1023                             `(let (,,@(mapcar (lambda (var)
1024                                                 ``(,',var ,,var))
1025                                               (cadr fn)))
1026                                ,@',(cddr fn))))
1027                         *local-cache-functions*)
1028        ,@body)))
1029
1030 ) ; EVAL-WHEN
1031 \f
1032 ;;; Here is where we actually fill, recache and expand caches.
1033 ;;;
1034 ;;; The functions FILL-CACHE and PROBE-CACHE are the ONLY external
1035 ;;; entrypoints into this code.
1036 ;;;
1037 ;;; FILL-CACHE returns 1 value: a new cache
1038 ;;;
1039 ;;;   a wrapper field number
1040 ;;;   a cache
1041 ;;;   a mask
1042 ;;;   an absolute cache size (the size of the actual vector)
1043 ;;; It tries to re-adjust the cache every time it makes a new fill.
1044 ;;; The intuition here is that we want uniformity in the number of
1045 ;;; probes needed to find an entry. Furthermore, adjusting has the
1046 ;;; nice property of throwing out any entries that are invalid.
1047 (defvar *cache-expand-threshold* 1.25)
1048
1049 (defun fill-cache (cache wrappers value &optional free-cache-p)
1050
1051   ;; FILL-CACHE won't return if WRAPPERS is nil, might as well check..
1052   (unless wrappers
1053     (error "fill-cache: WRAPPERS arg is NIL!"))
1054
1055   (or (fill-cache-p nil cache wrappers value)
1056       (and (< (ceiling (* (cache-count cache) 1.25))
1057               (if (= (cache-nkeys cache) 1)
1058                   (1- (cache-nlines cache))
1059                   (cache-nlines cache)))
1060            (adjust-cache cache wrappers value free-cache-p))
1061       (expand-cache cache wrappers value free-cache-p)))
1062
1063 (defvar *check-cache-p* nil)
1064
1065 (defmacro maybe-check-cache (cache)
1066   `(progn
1067      (when *check-cache-p*
1068        (check-cache ,cache))
1069      ,cache))
1070
1071 (defun check-cache (cache)
1072   (with-local-cache-functions (cache)
1073     (let ((location (if (= (nkeys) 1) 0 1))
1074           (limit (funcall (limit-fn) (nlines))))
1075       (dotimes-fixnum (i (nlines) cache)
1076         (when (and (not (location-reserved-p location))
1077                    (line-full-p i))
1078           (let* ((home-loc (compute-primary-cache-location-from-location
1079                             cache location))
1080                  (home (location-line (if (location-reserved-p home-loc)
1081                                           (next-location home-loc)
1082                                           home-loc)))
1083                  (sep (when home (line-separation home i))))
1084             (when (and sep (> sep limit))
1085               (error "bad cache ~S ~@
1086                       value at location ~W: ~W lines from its home. The limit is ~W."
1087                      cache location sep limit))))
1088         (setq location (next-location location))))))
1089
1090 (defun probe-cache (cache wrappers &optional default limit-fn)
1091   ;;(declare (values value))
1092   (unless wrappers
1093     ;; FIXME: This and another earlier test on a WRAPPERS arg can
1094     ;; be compact assertoids.
1095     (error "WRAPPERS arg is NIL!"))
1096   (with-local-cache-functions (cache)
1097     (let* ((location (compute-primary-cache-location (field) (mask) wrappers))
1098            (limit (funcall (or limit-fn (limit-fn)) (nlines))))
1099       (declare (fixnum location limit))
1100       (when (location-reserved-p location)
1101         (setq location (next-location location)))
1102       (dotimes-fixnum (i (1+ limit))
1103         (when (location-matches-wrappers-p location wrappers)
1104           (return-from probe-cache (or (not (valuep))
1105                                        (location-value location))))
1106         (setq location (next-location location)))
1107       (dolist (entry (overflow))
1108         (when (equal (car entry) wrappers)
1109           (return-from probe-cache (or (not (valuep))
1110                                        (cdr entry)))))
1111       default)))
1112
1113 (defun map-cache (function cache &optional set-p)
1114   (with-local-cache-functions (cache)
1115     (let ((set-p (and set-p (valuep))))
1116       (dotimes-fixnum (i (nlines) cache)
1117         (unless (or (line-reserved-p i) (not (line-valid-p i nil)))
1118           (let ((value (funcall function (line-wrappers i) (line-value i))))
1119             (when set-p
1120               (setf (cache-vector-ref (vector) (+ (line-location i) (nkeys)))
1121                     value)))))
1122       (dolist (entry (overflow))
1123         (let ((value (funcall function (car entry) (cdr entry))))
1124           (when set-p
1125             (setf (cdr entry) value))))))
1126   cache)
1127
1128 (defun cache-count (cache)
1129   (with-local-cache-functions (cache)
1130     (let ((count 0))
1131       (declare (fixnum count))
1132       (dotimes-fixnum (i (nlines) count)
1133         (unless (line-reserved-p i)
1134           (when (line-full-p i)
1135             (incf count)))))))
1136
1137 (defun entry-in-cache-p (cache wrappers value)
1138   (declare (ignore value))
1139   (with-local-cache-functions (cache)
1140     (dotimes-fixnum (i (nlines))
1141       (unless (line-reserved-p i)
1142         (when (equal (line-wrappers i) wrappers)
1143           (return t))))))
1144
1145 ;;; returns T or NIL
1146 (defun fill-cache-p (forcep cache wrappers value)
1147   (with-local-cache-functions (cache)
1148     (let* ((location (compute-primary-cache-location (field) (mask) wrappers))
1149            (primary (location-line location)))
1150       (declare (fixnum location primary))
1151       (multiple-value-bind (free emptyp)
1152           (find-free-cache-line primary cache wrappers)
1153         (when (or forcep emptyp)
1154           (when (not emptyp)
1155             (push (cons (line-wrappers free) (line-value free))
1156                   (cache-overflow cache)))
1157           ;;(fill-line free wrappers value)
1158           (let ((line free))
1159             (declare (fixnum line))
1160             (when (line-reserved-p line)
1161               (error "attempt to fill a reserved line"))
1162             (let ((loc (line-location line))
1163                   (cache-vector (vector)))
1164               (declare (fixnum loc) (simple-vector cache-vector))
1165               (cond ((= (nkeys) 1)
1166                      (setf (cache-vector-ref cache-vector loc) wrappers)
1167                      (when (valuep)
1168                        (setf (cache-vector-ref cache-vector (1+ loc)) value)))
1169                     (t
1170                      (let ((i 0))
1171                        (declare (fixnum i))
1172                        (dolist (w wrappers)
1173                          (setf (cache-vector-ref cache-vector (+ loc i)) w)
1174                          (setq i (the fixnum (1+ i)))))
1175                      (when (valuep)
1176                        (setf (cache-vector-ref cache-vector (+ loc (nkeys)))
1177                              value))))
1178               (maybe-check-cache cache))))))))
1179
1180 (defun fill-cache-from-cache-p (forcep cache from-cache from-line)
1181   (declare (fixnum from-line))
1182   (with-local-cache-functions (cache)
1183     (let ((primary (location-line
1184                     (compute-primary-cache-location-from-location
1185                      cache (line-location from-line) from-cache))))
1186       (declare (fixnum primary))
1187       (multiple-value-bind (free emptyp)
1188           (find-free-cache-line primary cache)
1189         (when (or forcep emptyp)
1190           (when (not emptyp)
1191             (push (cons (line-wrappers free) (line-value free))
1192                   (cache-overflow cache)))
1193           ;;(transfer-line from-cache-vector from-line cache-vector free)
1194           (let ((from-cache-vector (cache-vector from-cache))
1195                 (to-cache-vector (vector))
1196                 (to-line free))
1197             (declare (fixnum to-line))
1198             (if (line-reserved-p to-line)
1199                 (error "transferring something into a reserved cache line")
1200                 (let ((from-loc (line-location from-line))
1201                       (to-loc (line-location to-line)))
1202                   (declare (fixnum from-loc to-loc))
1203                   (modify-cache to-cache-vector
1204                                 (dotimes-fixnum (i (line-size))
1205                                   (setf (cache-vector-ref to-cache-vector
1206                                                           (+ to-loc i))
1207                                         (cache-vector-ref from-cache-vector
1208                                                           (+ from-loc i)))))))
1209             (maybe-check-cache cache)))))))
1210
1211 ;;; Returns NIL or (values <field> <cache-vector>)
1212 ;;;
1213 ;;; This is only called when it isn't possible to put the entry in the
1214 ;;; cache the easy way. That is, this function assumes that
1215 ;;; FILL-CACHE-P has been called as returned NIL.
1216 ;;;
1217 ;;; If this returns NIL, it means that it wasn't possible to find a
1218 ;;; wrapper field for which all of the entries could be put in the
1219 ;;; cache (within the limit).
1220 (defun adjust-cache (cache wrappers value free-old-cache-p)
1221   (with-local-cache-functions (cache)
1222     (let ((ncache (get-cache-from-cache cache (nlines) (field))))
1223       (do ((nfield (cache-field ncache) (next-wrapper-cache-number-index nfield)))
1224           ((null nfield) (free-cache ncache) nil)
1225         (setf (cache-field ncache) nfield)
1226         (labels ((try-one-fill-from-line (line)
1227                    (fill-cache-from-cache-p nil ncache cache line))
1228                  (try-one-fill (wrappers value)
1229                    (fill-cache-p nil ncache wrappers value)))
1230           (if (and (dotimes-fixnum (i (nlines) t)
1231                      (when (and (null (line-reserved-p i))
1232                                 (line-valid-p i wrappers))
1233                        (unless (try-one-fill-from-line i) (return nil))))
1234                    (dolist (wrappers+value (cache-overflow cache) t)
1235                      (unless (try-one-fill (car wrappers+value) (cdr wrappers+value))
1236                        (return nil)))
1237                    (try-one-fill wrappers value))
1238               (progn (when free-old-cache-p (free-cache cache))
1239                      (return (maybe-check-cache ncache)))
1240               (flush-cache-vector-internal (cache-vector ncache))))))))
1241
1242 ;;; returns: (values <cache>)
1243 (defun expand-cache (cache wrappers value free-old-cache-p)
1244   ;;(declare (values cache))
1245   (with-local-cache-functions (cache)
1246     (let ((ncache (get-cache-from-cache cache (* (nlines) 2))))
1247       (labels ((do-one-fill-from-line (line)
1248                  (unless (fill-cache-from-cache-p nil ncache cache line)
1249                    (do-one-fill (line-wrappers line) (line-value line))))
1250                (do-one-fill (wrappers value)
1251                  (setq ncache (or (adjust-cache ncache wrappers value t)
1252                                   (fill-cache-p t ncache wrappers value))))
1253                (try-one-fill (wrappers value)
1254                  (fill-cache-p nil ncache wrappers value)))
1255         (dotimes-fixnum (i (nlines))
1256           (when (and (null (line-reserved-p i))
1257                      (line-valid-p i wrappers))
1258             (do-one-fill-from-line i)))
1259         (dolist (wrappers+value (cache-overflow cache))
1260           (unless (try-one-fill (car wrappers+value) (cdr wrappers+value))
1261             (do-one-fill (car wrappers+value) (cdr wrappers+value))))
1262         (unless (try-one-fill wrappers value)
1263           (do-one-fill wrappers value))
1264         (when free-old-cache-p (free-cache cache))
1265         (maybe-check-cache ncache)))))
1266 \f
1267 ;;; This is the heart of the cache filling mechanism. It implements
1268 ;;; the decisions about where entries are placed.
1269 ;;;
1270 ;;; Find a line in the cache at which a new entry can be inserted.
1271 ;;;
1272 ;;;   <line>
1273 ;;;   <empty?>     is <line> in fact empty?
1274 (defun find-free-cache-line (primary cache &optional wrappers)
1275   ;;(declare (values line empty?))
1276   (declare (fixnum primary))
1277   (with-local-cache-functions (cache)
1278     (when (line-reserved-p primary) (setq primary (next-line primary)))
1279     (let ((limit (funcall (limit-fn) (nlines)))
1280           (wrappedp nil)
1281           (lines nil)
1282           (p primary) (s primary))
1283       (declare (fixnum p s limit))
1284       (block find-free
1285         (loop
1286          ;; Try to find a free line starting at <s>. <p> is the
1287          ;; primary line of the entry we are finding a free
1288          ;; line for, it is used to compute the separations.
1289          (do* ((line s (next-line line))
1290                (nsep (line-separation p s) (1+ nsep)))
1291               (())
1292            (declare (fixnum line nsep))
1293            (when (null (line-valid-p line wrappers)) ;If this line is empty or
1294              (push line lines)          ;invalid, just use it.
1295              (return-from find-free))
1296            (when (and wrappedp (>= line primary))
1297              ;; have gone all the way around the cache, time to quit
1298              (return-from find-free-cache-line (values primary nil)))
1299            (let ((osep (line-separation (line-primary line) line)))
1300              (when (>= osep limit)
1301                (return-from find-free-cache-line (values primary nil)))
1302              (when (cond ((= nsep limit) t)
1303                          ((= nsep osep) (zerop (random 2)))
1304                          ((> nsep osep) t)
1305                          (t nil))
1306                ;; See whether we can displace what is in this line so that we
1307                ;; can use the line.
1308                (when (= line (the fixnum (1- (nlines)))) (setq wrappedp t))
1309                (setq p (line-primary line))
1310                (setq s (next-line line))
1311                (push line lines)
1312                (return nil)))
1313            (when (= line (the fixnum (1- (nlines)))) (setq wrappedp t)))))
1314       ;; Do all the displacing.
1315       (loop
1316        (when (null (cdr lines)) (return nil))
1317        (let ((dline (pop lines))
1318              (line (car lines)))
1319          (declare (fixnum dline line))
1320          ;;Copy from line to dline (dline is known to be free).
1321          (let ((from-loc (line-location line))
1322                (to-loc (line-location dline))
1323                (cache-vector (vector)))
1324            (declare (fixnum from-loc to-loc) (simple-vector cache-vector))
1325            (modify-cache cache-vector
1326                          (dotimes-fixnum (i (line-size))
1327                            (setf (cache-vector-ref cache-vector
1328                                                    (+ to-loc i))
1329                                  (cache-vector-ref cache-vector
1330                                                    (+ from-loc i)))
1331                            (setf (cache-vector-ref cache-vector
1332                                                    (+ from-loc i))
1333                                  nil))))))
1334       (values (car lines) t))))
1335
1336 (defun default-limit-fn (nlines)
1337   (case nlines
1338     ((1 2 4) 1)
1339     ((8 16)  4)
1340     (otherwise 6)))
1341
1342 (defvar *empty-cache* (make-cache)) ; for defstruct slot initial value forms
1343 \f
1344 ;;; Pre-allocate generic function caches. The hope is that this will
1345 ;;; put them nicely together in memory, and that that may be a win. Of
1346 ;;; course the first GC copy will probably blow that out, this really
1347 ;;; wants to be wrapped in something that declares the area static.
1348 ;;;
1349 ;;; This preallocation only creates about 25% more caches than PCL
1350 ;;; itself uses. Some ports may want to preallocate some more of
1351 ;;; these.
1352 ;;;
1353 ;;; KLUDGE: Isn't something very similar going on in precom1.lisp? Do
1354 ;;; we need it both here and there? Why? -- WHN 19991203
1355 (eval-when (:load-toplevel)
1356   (dolist (n-size '((1 513) (3 257) (3 129) (14 128) (6 65)
1357                     (2 64) (7 33) (16 32) (16 17) (32 16)
1358                     (64 9) (64 8) (6 5) (128 4) (35 2)))
1359     (let ((n (car n-size))
1360           (size (cadr n-size)))
1361       (mapcar #'free-cache-vector
1362               (mapcar #'get-cache-vector
1363                       (make-list n :initial-element size))))))
1364
1365 (defun caches-to-allocate ()
1366   (sort (let ((l nil))
1367           (maphash (lambda (size entry)
1368                      (push (list (car entry) size) l))
1369                    sb-pcl::*free-caches*)
1370           l)
1371         #'>
1372         :key #'cadr))