006728f1ec17c0f1c7a7dcb019543a829b576ac6
[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: We have removed the persistent use of this function throughout
272 ;;; the PCL codebase, instead opting to use INVALID-WRAPPER-P, which 
273 ;;; abstractly tests the return result of this function for invalidness.
274 ;;; However, part of the original comment that is still applicable follows.
275 ;;;   --njf, 2002-05-02
276 ;;;
277 ;;; FIXME: It would probably be even better to switch the sense of the
278 ;;; WRAPPER-STATE function, renaming it to WRAPPER-INVALID and making it
279 ;;; synonymous with LAYOUT-INVALID. Then the INVALID-WRAPPER-P function
280 ;;; would become trivial and would go away (replaced with
281 ;;; WRAPPER-INVALID), since all the various invalid wrapper states would
282 ;;; become generalized boolean "true" values. -- 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 (defconstant +first-wrapper-cache-number-index+ 0)
368
369 (declaim (inline next-wrapper-cache-number-index))
370 (defun next-wrapper-cache-number-index (field-number)
371   (and (< field-number #.(1- wrapper-cache-number-vector-length))
372        (1+ field-number)))
373
374 ;;; FIXME: Why are there two layers here, with one operator trivially
375 ;;; defined in terms of the other? It'd be nice either to have a
376 ;;; comment explaining why the separation is valuable, or to collapse
377 ;;; it into a single layer.
378 ;;;
379 ;;; FIXME (?): These are logically inline functions, but they need to
380 ;;; be SETFable, and for now it seems not worth the trouble to DEFUN
381 ;;; both inline FOO and inline (SETF FOO) for each one instead of a
382 ;;; single macro. Perhaps the best thing would be to make them
383 ;;; immutable (since it seems sort of surprising and gross to be able
384 ;;; to modify hash values) so that they can become inline functions
385 ;;; with no muss or fuss. I (WHN) didn't do this only because I didn't
386 ;;; know whether any code anywhere depends on the values being
387 ;;; modified.
388 (defmacro cache-number-vector-ref (cnv n)
389   `(wrapper-cache-number-vector-ref ,cnv ,n))
390 (defmacro wrapper-cache-number-vector-ref (wrapper n)
391   `(sb-kernel:layout-clos-hash ,wrapper ,n))
392
393 (declaim (inline wrapper-class*))
394 (defun wrapper-class* (wrapper)
395   (or (wrapper-class wrapper)
396       (find-structure-class
397        (cl:class-name (sb-kernel:layout-class wrapper)))))
398
399 ;;; The wrapper cache machinery provides general mechanism for
400 ;;; trapping on the next access to any instance of a given class. This
401 ;;; mechanism is used to implement the updating of instances when the
402 ;;; class is redefined (MAKE-INSTANCES-OBSOLETE). The same mechanism
403 ;;; is also used to update generic function caches when there is a
404 ;;; change to the superclasses of a class.
405 ;;;
406 ;;; Basically, a given wrapper can be valid or invalid. If it is
407 ;;; invalid, it means that any attempt to do a wrapper cache lookup
408 ;;; using the wrapper should trap. Also, methods on
409 ;;; SLOT-VALUE-USING-CLASS check the wrapper validity as well. This is
410 ;;; done by calling CHECK-WRAPPER-VALIDITY.
411
412 (declaim (inline invalid-wrapper-p))
413 (defun invalid-wrapper-p (wrapper)
414   (neq (wrapper-state wrapper) t))
415
416 (defvar *previous-nwrappers* (make-hash-table))
417
418 (defun invalidate-wrapper (owrapper state nwrapper)
419   (ecase state
420     ((:flush :obsolete)
421      (let ((new-previous ()))
422        ;; First off, a previous call to INVALIDATE-WRAPPER may have
423        ;; recorded OWRAPPER as an NWRAPPER to update to. Since
424        ;; OWRAPPER is about to be invalid, it no longer makes sense to
425        ;; update to it.
426        ;;
427        ;; We go back and change the previously invalidated wrappers so
428        ;; that they will now update directly to NWRAPPER. This
429        ;; corresponds to a kind of transitivity of wrapper updates.
430        (dolist (previous (gethash owrapper *previous-nwrappers*))
431          (when (eq state :obsolete)
432            (setf (car previous) :obsolete))
433          (setf (cadr previous) nwrapper)
434          (push previous new-previous))
435
436        (let ((ocnv (wrapper-cache-number-vector owrapper)))
437          (dotimes (i sb-kernel:layout-clos-hash-length)
438            (setf (cache-number-vector-ref ocnv i) 0)))
439        (push (setf (wrapper-state owrapper) (list state nwrapper))
440              new-previous)
441
442        (setf (gethash owrapper *previous-nwrappers*) ()
443              (gethash nwrapper *previous-nwrappers*) new-previous)))))
444
445 (defun check-wrapper-validity (instance)
446   (let* ((owrapper (wrapper-of instance)))
447     (if (not (invalid-wrapper-p owrapper))
448         owrapper
449         (let* ((state (wrapper-state owrapper))
450                (nwrapper
451                 (ecase (car state)
452                   (:flush
453                    (flush-cache-trap owrapper (cadr state) instance))
454                   (:obsolete
455                    (obsolete-instance-trap owrapper (cadr state) instance)))))
456           ;; This little bit of error checking is superfluous. It only
457           ;; checks to see whether the person who implemented the trap
458           ;; handling screwed up. Since that person is hacking
459           ;; internal PCL code, and is not a user, this should be
460           ;; needless. Also, since this directly slows down instance
461           ;; update and generic function cache refilling, feel free to
462           ;; take it out sometime soon.
463           ;;
464           ;; FIXME: We probably need to add a #+SB-PARANOID feature to
465           ;; make stuff like this optional. Until then, it stays in.
466           (cond ((neq nwrapper (wrapper-of instance))
467                  (error "wrapper returned from trap not wrapper of instance"))
468                 ((invalid-wrapper-p nwrapper)
469                  (error "wrapper returned from trap invalid")))
470           nwrapper))))
471 \f
472 (defvar *free-caches* nil)
473
474 (defun get-cache (nkeys valuep limit-fn nlines)
475   (let ((cache (or (sb-sys:without-interrupts (pop *free-caches*))
476                    (make-cache))))
477     (declare (type cache cache))
478     (multiple-value-bind (cache-mask actual-size line-size nlines)
479         (compute-cache-parameters nkeys valuep nlines)
480       (setf (cache-nkeys cache) nkeys
481             (cache-valuep cache) valuep
482             (cache-nlines cache) nlines
483             (cache-field cache) +first-wrapper-cache-number-index+
484             (cache-limit-fn cache) limit-fn
485             (cache-mask cache) cache-mask
486             (cache-size cache) actual-size
487             (cache-line-size cache) line-size
488             (cache-max-location cache) (let ((line (1- nlines)))
489                                          (if (= nkeys 1)
490                                              (* line line-size)
491                                              (1+ (* line line-size))))
492             (cache-vector cache) (get-cache-vector actual-size)
493             (cache-overflow cache) nil)
494       cache)))
495
496 (defun get-cache-from-cache (old-cache new-nlines
497                              &optional (new-field +first-wrapper-cache-number-index+))
498   (let ((nkeys (cache-nkeys old-cache))
499         (valuep (cache-valuep old-cache))
500         (cache (or (sb-sys:without-interrupts (pop *free-caches*))
501                    (make-cache))))
502     (declare (type cache cache))
503     (multiple-value-bind (cache-mask actual-size line-size nlines)
504         (if (= new-nlines (cache-nlines old-cache))
505             (values (cache-mask old-cache) (cache-size old-cache)
506                     (cache-line-size old-cache) (cache-nlines old-cache))
507             (compute-cache-parameters nkeys valuep new-nlines))
508       (setf (cache-owner cache) (cache-owner old-cache)
509             (cache-nkeys cache) nkeys
510             (cache-valuep cache) valuep
511             (cache-nlines cache) nlines
512             (cache-field cache) new-field
513             (cache-limit-fn cache) (cache-limit-fn old-cache)
514             (cache-mask cache) cache-mask
515             (cache-size cache) actual-size
516             (cache-line-size cache) line-size
517             (cache-max-location cache) (let ((line (1- nlines)))
518                                          (if (= nkeys 1)
519                                              (* line line-size)
520                                              (1+ (* line line-size))))
521             (cache-vector cache) (get-cache-vector actual-size)
522             (cache-overflow cache) nil)
523       cache)))
524
525 (defun copy-cache (old-cache)
526   (let* ((new-cache (copy-cache-internal old-cache))
527          (size (cache-size old-cache))
528          (old-vector (cache-vector old-cache))
529          (new-vector (get-cache-vector size)))
530     (declare (simple-vector old-vector new-vector))
531     (dotimes-fixnum (i size)
532       (setf (svref new-vector i) (svref old-vector i)))
533     (setf (cache-vector new-cache) new-vector)
534     new-cache))
535
536 (defun free-cache (cache)
537   (free-cache-vector (cache-vector cache))
538   (setf (cache-vector cache) #())
539   (setf (cache-owner cache) nil)
540   (push cache *free-caches*)
541   nil)
542
543 (defun compute-line-size (x)
544   (power-of-two-ceiling x))
545
546 (defun compute-cache-parameters (nkeys valuep nlines-or-cache-vector)
547   ;;(declare (values cache-mask actual-size line-size nlines))
548   (declare (fixnum nkeys))
549   (if (= nkeys 1)
550       (let* ((line-size (if valuep 2 1))
551              (cache-size (if (typep nlines-or-cache-vector 'fixnum)
552                              (the fixnum
553                                   (* line-size
554                                      (the fixnum
555                                           (power-of-two-ceiling
556                                             nlines-or-cache-vector))))
557                              (cache-vector-size nlines-or-cache-vector))))
558         (declare (fixnum line-size cache-size))
559         (values (logxor (the fixnum (1- cache-size)) (the fixnum (1- line-size)))
560                 cache-size
561                 line-size
562                 (the (values fixnum t) (floor cache-size line-size))))
563       (let* ((line-size (power-of-two-ceiling (if valuep (1+ nkeys) nkeys)))
564              (cache-size (if (typep nlines-or-cache-vector 'fixnum)
565                              (the fixnum
566                                   (* line-size
567                                      (the fixnum
568                                           (power-of-two-ceiling
569                                             nlines-or-cache-vector))))
570                              (1- (cache-vector-size nlines-or-cache-vector)))))
571         (declare (fixnum line-size cache-size))
572         (values (logxor (the fixnum (1- cache-size)) (the fixnum (1- line-size)))
573                 (the fixnum (1+ cache-size))
574                 line-size
575                 (the (values fixnum t) (floor cache-size line-size))))))
576 \f
577 ;;; the various implementations of computing a primary cache location from
578 ;;; wrappers. Because some implementations of this must run fast there are
579 ;;; several implementations of the same algorithm.
580 ;;;
581 ;;; The algorithm is:
582 ;;;
583 ;;;  SUM       over the wrapper cache numbers,
584 ;;;  ENSURING  that the result is a fixnum
585 ;;;  MASK      the result against the mask argument.
586
587 ;;; The basic functional version. This is used by the cache miss code to
588 ;;; compute the primary location of an entry.
589 (defun compute-primary-cache-location (field mask wrappers)
590
591   (declare (type field-type field) (fixnum mask))
592   (if (not (listp wrappers))
593       (logand mask
594               (the fixnum (wrapper-cache-number-vector-ref wrappers field)))
595       (let ((location 0) (i 0))
596         (declare (fixnum location i))
597         (dolist (wrapper wrappers)
598           ;; First add the cache number of this wrapper to location.
599           (let ((wrapper-cache-number (wrapper-cache-number-vector-ref wrapper
600                                                                        field)))
601             (declare (fixnum wrapper-cache-number))
602             (if (zerop wrapper-cache-number)
603                 (return-from compute-primary-cache-location 0)
604                 (setq location
605                       (the fixnum (+ location wrapper-cache-number)))))
606           ;; Then, if we are working with lots of wrappers, deal with
607           ;; the wrapper-cache-number-mask stuff.
608           (when (and (not (zerop i))
609                      (zerop (mod i wrapper-cache-number-adds-ok)))
610             (setq location
611                   (logand location wrapper-cache-number-mask)))
612           (incf i))
613         (the fixnum (1+ (logand mask location))))))
614
615 ;;; This version is called on a cache line. It fetches the wrappers
616 ;;; from the cache line and determines the primary location. Various
617 ;;; parts of the cache filling code call this to determine whether it
618 ;;; is appropriate to displace a given cache entry.
619 ;;;
620 ;;; If this comes across a wrapper whose CACHE-NO is 0, it returns the
621 ;;; symbol invalid to suggest to its caller that it would be provident
622 ;;; to blow away the cache line in question.
623 (defun compute-primary-cache-location-from-location (to-cache
624                                                      from-location
625                                                      &optional
626                                                      (from-cache to-cache))
627   (declare (type cache to-cache from-cache) (fixnum from-location))
628   (let ((result 0)
629         (cache-vector (cache-vector from-cache))
630         (field (cache-field to-cache))
631         (mask (cache-mask to-cache))
632         (nkeys (cache-nkeys to-cache)))
633     (declare (type field-type field) (fixnum result mask nkeys)
634              (simple-vector cache-vector))
635     (dotimes-fixnum (i nkeys)
636       (let* ((wrapper (cache-vector-ref cache-vector (+ i from-location)))
637              (wcn (wrapper-cache-number-vector-ref wrapper field)))
638         (declare (fixnum wcn))
639         (setq result (+ result wcn)))
640       (when (and (not (zerop i))
641                  (zerop (mod i wrapper-cache-number-adds-ok)))
642         (setq result (logand result wrapper-cache-number-mask))))
643     (if (= nkeys 1)
644         (logand mask result)
645         (the fixnum (1+ (logand mask result))))))
646 \f
647 ;;;  NIL              means nothing so far, no actual arg info has NILs
648 ;;;                in the metatype
649 ;;;  CLASS          seen all sorts of metaclasses
650 ;;;                (specifically, more than one of the next 4 values)
651 ;;;  T          means everything so far is the class T
652 ;;;  STANDARD-CLASS   seen only standard classes
653 ;;;  BUILT-IN-CLASS   seen only built in classes
654 ;;;  STRUCTURE-CLASS  seen only structure classes
655 (defun raise-metatype (metatype new-specializer)
656   (let ((slot      (find-class 'slot-class))
657         (std       (find-class 'std-class))
658         (standard  (find-class 'standard-class))
659         (fsc       (find-class 'funcallable-standard-class))
660         (structure (find-class 'structure-class))
661         (built-in  (find-class 'built-in-class)))
662     (flet ((specializer->metatype (x)
663              (let ((meta-specializer
664                      (if (eq *boot-state* 'complete)
665                          (class-of (specializer-class x))
666                          (class-of x))))
667                (cond ((eq x *the-class-t*) t)
668                      ((*subtypep meta-specializer std)
669                       'standard-instance)
670                      ((*subtypep meta-specializer standard)
671                       'standard-instance)
672                      ((*subtypep meta-specializer fsc)
673                       'standard-instance)
674                      ((*subtypep meta-specializer structure)
675                       'structure-instance)
676                      ((*subtypep meta-specializer built-in)
677                       'built-in-instance)
678                      ((*subtypep meta-specializer slot)
679                       'slot-instance)
680                      (t (error "PCL cannot handle the specializer ~S (meta-specializer ~S)."
681                                new-specializer
682                                meta-specializer))))))
683       ;; We implement the following table. The notation is
684       ;; that X and Y are distinct meta specializer names.
685       ;;
686       ;;   NIL    <anything>    ===>  <anything>
687       ;;    X      X        ===>      X
688       ;;    X      Y        ===>    CLASS
689       (let ((new-metatype (specializer->metatype new-specializer)))
690         (cond ((eq new-metatype 'slot-instance) 'class)
691               ((null metatype) new-metatype)
692               ((eq metatype new-metatype) new-metatype)
693               (t 'class))))))
694
695 (defmacro with-dfun-wrappers ((args metatypes)
696                               (dfun-wrappers invalid-wrapper-p
697                                              &optional wrappers classes types)
698                               invalid-arguments-form
699                               &body body)
700   `(let* ((args-tail ,args) (,invalid-wrapper-p nil) (invalid-arguments-p nil)
701           (,dfun-wrappers nil) (dfun-wrappers-tail nil)
702           ,@(when wrappers
703               `((wrappers-rev nil) (types-rev nil) (classes-rev nil))))
704      (dolist (mt ,metatypes)
705        (unless args-tail
706          (setq invalid-arguments-p t)
707          (return nil))
708        (let* ((arg (pop args-tail))
709               (wrapper nil)
710               ,@(when wrappers
711                   `((class *the-class-t*)
712                     (type t))))
713          (unless (eq mt t)
714            (setq wrapper (wrapper-of arg))
715            (when (invalid-wrapper-p wrapper)
716              (setq ,invalid-wrapper-p t)
717              (setq wrapper (check-wrapper-validity arg)))
718            (cond ((null ,dfun-wrappers)
719                   (setq ,dfun-wrappers wrapper))
720                  ((not (consp ,dfun-wrappers))
721                   (setq dfun-wrappers-tail (list wrapper))
722                   (setq ,dfun-wrappers (cons ,dfun-wrappers dfun-wrappers-tail)))
723                  (t
724                   (let ((new-dfun-wrappers-tail (list wrapper)))
725                     (setf (cdr dfun-wrappers-tail) new-dfun-wrappers-tail)
726                     (setf dfun-wrappers-tail new-dfun-wrappers-tail))))
727            ,@(when wrappers
728                `((setq class (wrapper-class* wrapper))
729                  (setq type `(class-eq ,class)))))
730          ,@(when wrappers
731              `((push wrapper wrappers-rev)
732                (push class classes-rev)
733                (push type types-rev)))))
734      (if invalid-arguments-p
735          ,invalid-arguments-form
736          (let* (,@(when wrappers
737                     `((,wrappers (nreverse wrappers-rev))
738                       (,classes (nreverse classes-rev))
739                       (,types (mapcar (lambda (class)
740                                         `(class-eq ,class))
741                                       ,classes)))))
742            ,@body))))
743 \f
744 ;;;; some support stuff for getting a hold of symbols that we need when
745 ;;;; building the discriminator codes. It's OK for these to be interned
746 ;;;; symbols because we don't capture any user code in the scope in which
747 ;;;; these symbols are bound.
748
749 (defvar *dfun-arg-symbols* '(.ARG0. .ARG1. .ARG2. .ARG3.))
750
751 (defun dfun-arg-symbol (arg-number)
752   (or (nth arg-number (the list *dfun-arg-symbols*))
753       (intern (format nil ".ARG~A." arg-number) *pcl-package*)))
754
755 (defvar *slot-vector-symbols* '(.SLOTS0. .SLOTS1. .SLOTS2. .SLOTS3.))
756
757 (defun slot-vector-symbol (arg-number)
758   (or (nth arg-number (the list *slot-vector-symbols*))
759       (intern (format nil ".SLOTS~A." arg-number) *pcl-package*)))
760
761 ;; FIXME: There ought to be a good way to factor out the idiom:
762 ;;
763 ;; (dotimes (i (length metatypes))
764 ;;   (push (dfun-arg-symbol i) lambda-list))
765 ;;
766 ;; used in the following four functions into common code that we can
767 ;; declare inline or something.  --njf 2001-12-20
768 (defun make-dfun-lambda-list (metatypes applyp)
769   (let ((lambda-list nil))
770     (dotimes (i (length metatypes))
771       (push (dfun-arg-symbol i) lambda-list))
772     (when applyp
773       (push '&rest lambda-list)
774       (push '.dfun-rest-arg. lambda-list))
775     (nreverse lambda-list)))
776
777 (defun make-dlap-lambda-list (metatypes applyp)
778   (let ((lambda-list nil))
779     (dotimes (i (length metatypes))
780       (push (dfun-arg-symbol i) lambda-list))
781     ;; FIXME: This is translated directly from the old PCL code.
782     ;; It didn't have a (PUSH '.DFUN-REST-ARG. LAMBDA-LIST) or
783     ;; something similar, so we don't either.  It's hard to see how
784     ;; this could be correct, since &REST wants an argument after
785     ;; it.  This function works correctly because the caller
786     ;; magically tacks on something after &REST.  The calling functions
787     ;; (in dlisp.lisp) should be fixed and this function rewritten.
788     ;; --njf 2001-12-20
789     (when applyp
790       (push '&rest lambda-list))
791     (nreverse lambda-list)))
792
793 ;; FIXME: The next two functions suffer from having a `.DFUN-REST-ARG.'
794 ;; in their lambda lists, but no corresponding `&REST' symbol.  We assume
795 ;; this should be the case by analogy with the previous two functions.
796 ;; It works, and I don't know why.  Check the calling functions and
797 ;; fix these too.  --njf 2001-12-20
798 (defun make-emf-call (metatypes applyp fn-variable &optional emf-type)
799   (let ((required
800          (let ((required nil))
801            (dotimes (i (length metatypes))
802              (push (dfun-arg-symbol i) required))
803            (nreverse required))))
804     `(,(if (eq emf-type 'fast-method-call)
805            'invoke-effective-method-function-fast
806            'invoke-effective-method-function)
807       ,fn-variable ,applyp ,@required ,@(when applyp `(.dfun-rest-arg.)))))
808
809 (defun make-fast-method-call-lambda-list (metatypes applyp)
810   (let ((reversed-lambda-list nil))
811     (push '.pv-cell. reversed-lambda-list)
812     (push '.next-method-call. reversed-lambda-list)
813     (dotimes (i (length metatypes))
814       (push (dfun-arg-symbol i) reversed-lambda-list))
815     (when applyp
816       (push '.dfun-rest-arg. reversed-lambda-list))
817     (nreverse reversed-lambda-list)))
818 \f
819 (defmacro with-local-cache-functions ((cache) &body body)
820   `(let ((.cache. ,cache))
821      (declare (type cache .cache.))
822      (labels ((cache () .cache.)
823               (nkeys () (cache-nkeys .cache.))
824               (line-size () (cache-line-size .cache.))
825               (vector () (cache-vector .cache.))
826               (valuep () (cache-valuep .cache.))
827               (nlines () (cache-nlines .cache.))
828               (max-location () (cache-max-location .cache.))
829               (limit-fn () (cache-limit-fn .cache.))
830               (size () (cache-size .cache.))
831               (mask () (cache-mask .cache.))
832               (field () (cache-field .cache.))
833               (overflow () (cache-overflow .cache.))
834               ;;
835               ;; Return T IFF this cache location is reserved.  The
836               ;; only time this is true is for line number 0 of an
837               ;; nkeys=1 cache.
838               ;;
839               (line-reserved-p (line)
840                 (declare (fixnum line))
841                 (and (= (nkeys) 1)
842                      (= line 0)))
843               ;;
844               (location-reserved-p (location)
845                 (declare (fixnum location))
846                 (and (= (nkeys) 1)
847                      (= location 0)))
848               ;;
849               ;; Given a line number, return the cache location.
850               ;; This is the value that is the second argument to
851               ;; cache-vector-ref.  Basically, this deals with the
852               ;; offset of nkeys>1 caches and multiplies by line
853               ;; size.
854               ;;          
855               (line-location (line)
856                 (declare (fixnum line))
857                 (when (line-reserved-p line)
858                   (error "line is reserved"))
859                 (if (= (nkeys) 1)
860                     (the fixnum (* line (line-size)))
861                     (the fixnum (1+ (the fixnum (* line (line-size)))))))
862               ;;
863               ;; Given a cache location, return the line.  This is
864               ;; the inverse of LINE-LOCATION.
865               ;;          
866               (location-line (location)
867                 (declare (fixnum location))
868                 (if (= (nkeys) 1)
869                     (floor location (line-size))
870                     (floor (the fixnum (1- location)) (line-size))))
871               ;;
872               ;; Given a line number, return the wrappers stored at
873               ;; that line.  As usual, if nkeys=1, this returns a
874               ;; single value.  Only when nkeys>1 does it return a
875               ;; list.  An error is signalled if the line is
876               ;; reserved.
877               ;;
878               (line-wrappers (line)
879                 (declare (fixnum line))
880                 (when (line-reserved-p line) (error "Line is reserved."))
881                 (location-wrappers (line-location line)))
882               ;;
883               (location-wrappers (location) ; avoid multiplies caused by line-location
884                 (declare (fixnum location))
885                 (if (= (nkeys) 1)
886                     (cache-vector-ref (vector) location)
887                     (let ((list (make-list (nkeys)))
888                           (vector (vector)))
889                       (declare (simple-vector vector))
890                       (dotimes (i (nkeys) list)
891                         (declare (fixnum i))
892                         (setf (nth i list)
893                               (cache-vector-ref vector (+ location i)))))))
894               ;;
895               ;; Given a line number, return true IFF the line's
896               ;; wrappers are the same as wrappers.
897               ;;
898               (line-matches-wrappers-p (line wrappers)
899                 (declare (fixnum line))
900                 (and (not (line-reserved-p line))
901                      (location-matches-wrappers-p (line-location line)
902                                                   wrappers)))
903               ;;
904               (location-matches-wrappers-p (loc wrappers) ; must not be reserved
905                 (declare (fixnum loc))
906                 (let ((cache-vector (vector)))
907                   (declare (simple-vector cache-vector))
908                   (if (= (nkeys) 1)
909                       (eq wrappers (cache-vector-ref cache-vector loc))
910                       (dotimes (i (nkeys) t)
911                         (declare (fixnum i))
912                         (unless (eq (pop wrappers)
913                                     (cache-vector-ref cache-vector (+ loc i)))
914                           (return nil))))))
915               ;;
916               ;; Given a line number, return the value stored at that line.
917               ;; If valuep is NIL, this returns NIL.  As with line-wrappers,
918               ;; an error is signalled if the line is reserved.
919               ;; 
920               (line-value (line)
921                 (declare (fixnum line))
922                 (when (line-reserved-p line) (error "Line is reserved."))
923                 (location-value (line-location line)))
924               ;;
925               (location-value (loc)
926                 (declare (fixnum loc))
927                 (and (valuep)
928                      (cache-vector-ref (vector) (+ loc (nkeys)))))
929               ;;
930               ;; Given a line number, return true IFF that line has data in
931               ;; it.  The state of the wrappers stored in the line is not
932               ;; checked.  An error is signalled if line is reserved.
933               (line-full-p (line)
934                 (when (line-reserved-p line) (error "Line is reserved."))
935                 (not (null (cache-vector-ref (vector) (line-location line)))))
936               ;;
937               ;; Given a line number, return true IFF the line is full and
938               ;; there are no invalid wrappers in the line, and the line's
939               ;; wrappers are different from wrappers.
940               ;; An error is signalled if the line is reserved.
941               ;;
942               (line-valid-p (line wrappers)
943                 (declare (fixnum line))
944                 (when (line-reserved-p line) (error "Line is reserved."))
945                 (location-valid-p (line-location line) wrappers))
946               ;;
947               (location-valid-p (loc wrappers)
948                 (declare (fixnum loc))
949                 (let ((cache-vector (vector))
950                       (wrappers-mismatch-p (null wrappers)))
951                   (declare (simple-vector cache-vector))
952                   (dotimes (i (nkeys) wrappers-mismatch-p)
953                     (declare (fixnum i))
954                     (let ((wrapper (cache-vector-ref cache-vector (+ loc i))))
955                       (when (or (null wrapper)
956                                 (invalid-wrapper-p wrapper))
957                         (return nil))
958                       (unless (and wrappers
959                                    (eq wrapper
960                                        (if (consp wrappers)
961                                            (pop wrappers)
962                                            wrappers)))
963                         (setq wrappers-mismatch-p t))))))
964               ;;
965               ;; How many unreserved lines separate line-1 and line-2.
966               ;;
967               (line-separation (line-1 line-2)
968                 (declare (fixnum line-1 line-2))
969                 (let ((diff (the fixnum (- line-2 line-1))))
970                   (declare (fixnum diff))
971                   (when (minusp diff)
972                     (setq diff (+ diff (nlines)))
973                     (when (line-reserved-p 0)
974                       (setq diff (1- diff))))
975                   diff))
976               ;;
977               ;; Given a cache line, get the next cache line.  This will not
978               ;; return a reserved line.
979               ;; 
980               (next-line (line)
981                 (declare (fixnum line))
982                 (if (= line (the fixnum (1- (nlines))))
983                     (if (line-reserved-p 0) 1 0)
984                     (the fixnum (1+ line))))
985               ;;
986               (next-location (loc)
987                 (declare (fixnum loc))
988                 (if (= loc (max-location))
989                     (if (= (nkeys) 1)
990                         (line-size)
991                         1)
992                     (the fixnum (+ loc (line-size)))))
993               ;;
994               ;; Given a line which has a valid entry in it, this
995               ;; will return the primary cache line of the wrappers
996               ;; in that line.  We just call
997               ;; COMPUTE-PRIMARY-CACHE-LOCATION-FROM-LOCATION, this
998               ;; is an easier packaging up of the call to it.
999               ;; 
1000               (line-primary (line)
1001                 (declare (fixnum line))
1002                 (location-line (line-primary-location line)))
1003               ;;
1004               (line-primary-location (line)
1005                 (declare (fixnum line))
1006                 (compute-primary-cache-location-from-location
1007                  (cache) (line-location line))))
1008        (declare (ignorable #'cache #'nkeys #'line-size #'vector #'valuep
1009                            #'nlines #'max-location #'limit-fn #'size
1010                            #'mask #'field #'overflow #'line-reserved-p
1011                            #'location-reserved-p #'line-location
1012                            #'location-line #'line-wrappers #'location-wrappers
1013                            #'line-matches-wrappers-p
1014                            #'location-matches-wrappers-p
1015                            #'line-value #'location-value #'line-full-p
1016                            #'line-valid-p #'location-valid-p
1017                            #'line-separation #'next-line #'next-location
1018                            #'line-primary #'line-primary-location))
1019        ,@body)))
1020 \f
1021 ;;; Here is where we actually fill, recache and expand caches.
1022 ;;;
1023 ;;; The functions FILL-CACHE and PROBE-CACHE are the ONLY external
1024 ;;; entrypoints into this code.
1025 ;;;
1026 ;;; FILL-CACHE returns 1 value: a new cache
1027 ;;;
1028 ;;;   a wrapper field number
1029 ;;;   a cache
1030 ;;;   a mask
1031 ;;;   an absolute cache size (the size of the actual vector)
1032 ;;; It tries to re-adjust the cache every time it makes a new fill.
1033 ;;; The intuition here is that we want uniformity in the number of
1034 ;;; probes needed to find an entry. Furthermore, adjusting has the
1035 ;;; nice property of throwing out any entries that are invalid.
1036 (defvar *cache-expand-threshold* 1.25)
1037
1038 (defun fill-cache (cache wrappers value &optional free-cache-p)
1039
1040   ;; FILL-CACHE won't return if WRAPPERS is nil, might as well check..
1041   (unless wrappers
1042     (error "fill-cache: WRAPPERS arg is NIL!"))
1043
1044   (or (fill-cache-p nil cache wrappers value)
1045       (and (< (ceiling (* (cache-count cache) 1.25))
1046               (if (= (cache-nkeys cache) 1)
1047                   (1- (cache-nlines cache))
1048                   (cache-nlines cache)))
1049            (adjust-cache cache wrappers value free-cache-p))
1050       (expand-cache cache wrappers value free-cache-p)))
1051
1052 (defvar *check-cache-p* nil)
1053
1054 (defmacro maybe-check-cache (cache)
1055   `(progn
1056      (when *check-cache-p*
1057        (check-cache ,cache))
1058      ,cache))
1059
1060 (defun check-cache (cache)
1061   (with-local-cache-functions (cache)
1062     (let ((location (if (= (nkeys) 1) 0 1))
1063           (limit (funcall (limit-fn) (nlines))))
1064       (dotimes-fixnum (i (nlines) cache)
1065         (when (and (not (location-reserved-p location))
1066                    (line-full-p i))
1067           (let* ((home-loc (compute-primary-cache-location-from-location
1068                             cache location))
1069                  (home (location-line (if (location-reserved-p home-loc)
1070                                           (next-location home-loc)
1071                                           home-loc)))
1072                  (sep (when home (line-separation home i))))
1073             (when (and sep (> sep limit))
1074               (error "bad cache ~S ~@
1075                       value at location ~W: ~W lines from its home. The limit is ~W."
1076                      cache location sep limit))))
1077         (setq location (next-location location))))))
1078
1079 (defun probe-cache (cache wrappers &optional default limit-fn)
1080   ;;(declare (values value))
1081   (unless wrappers
1082     ;; FIXME: This and another earlier test on a WRAPPERS arg can
1083     ;; be compact assertoids.
1084     (error "WRAPPERS arg is NIL!"))
1085   (with-local-cache-functions (cache)
1086     (let* ((location (compute-primary-cache-location (field) (mask) wrappers))
1087            (limit (funcall (or limit-fn (limit-fn)) (nlines))))
1088       (declare (fixnum location limit))
1089       (when (location-reserved-p location)
1090         (setq location (next-location location)))
1091       (dotimes-fixnum (i (1+ limit))
1092         (when (location-matches-wrappers-p location wrappers)
1093           (return-from probe-cache (or (not (valuep))
1094                                        (location-value location))))
1095         (setq location (next-location location)))
1096       (dolist (entry (overflow))
1097         (when (equal (car entry) wrappers)
1098           (return-from probe-cache (or (not (valuep))
1099                                        (cdr entry)))))
1100       default)))
1101
1102 (defun map-cache (function cache &optional set-p)
1103   (with-local-cache-functions (cache)
1104     (let ((set-p (and set-p (valuep))))
1105       (dotimes-fixnum (i (nlines) cache)
1106         (unless (or (line-reserved-p i) (not (line-valid-p i nil)))
1107           (let ((value (funcall function (line-wrappers i) (line-value i))))
1108             (when set-p
1109               (setf (cache-vector-ref (vector) (+ (line-location i) (nkeys)))
1110                     value)))))
1111       (dolist (entry (overflow))
1112         (let ((value (funcall function (car entry) (cdr entry))))
1113           (when set-p
1114             (setf (cdr entry) value))))))
1115   cache)
1116
1117 (defun cache-count (cache)
1118   (with-local-cache-functions (cache)
1119     (let ((count 0))
1120       (declare (fixnum count))
1121       (dotimes-fixnum (i (nlines) count)
1122         (unless (line-reserved-p i)
1123           (when (line-full-p i)
1124             (incf count)))))))
1125
1126 (defun entry-in-cache-p (cache wrappers value)
1127   (declare (ignore value))
1128   (with-local-cache-functions (cache)
1129     (dotimes-fixnum (i (nlines))
1130       (unless (line-reserved-p i)
1131         (when (equal (line-wrappers i) wrappers)
1132           (return t))))))
1133
1134 ;;; returns T or NIL
1135 (defun fill-cache-p (forcep cache wrappers value)
1136   (with-local-cache-functions (cache)
1137     (let* ((location (compute-primary-cache-location (field) (mask) wrappers))
1138            (primary (location-line location)))
1139       (declare (fixnum location primary))
1140       (multiple-value-bind (free emptyp)
1141           (find-free-cache-line primary cache wrappers)
1142         (when (or forcep emptyp)
1143           (when (not emptyp)
1144             (push (cons (line-wrappers free) (line-value free))
1145                   (cache-overflow cache)))
1146           ;;(fill-line free wrappers value)
1147           (let ((line free))
1148             (declare (fixnum line))
1149             (when (line-reserved-p line)
1150               (error "attempt to fill a reserved line"))
1151             (let ((loc (line-location line))
1152                   (cache-vector (vector)))
1153               (declare (fixnum loc) (simple-vector cache-vector))
1154               (cond ((= (nkeys) 1)
1155                      (setf (cache-vector-ref cache-vector loc) wrappers)
1156                      (when (valuep)
1157                        (setf (cache-vector-ref cache-vector (1+ loc)) value)))
1158                     (t
1159                      (let ((i 0))
1160                        (declare (fixnum i))
1161                        (dolist (w wrappers)
1162                          (setf (cache-vector-ref cache-vector (+ loc i)) w)
1163                          (setq i (the fixnum (1+ i)))))
1164                      (when (valuep)
1165                        (setf (cache-vector-ref cache-vector (+ loc (nkeys)))
1166                              value))))
1167               (maybe-check-cache cache))))))))
1168
1169 (defun fill-cache-from-cache-p (forcep cache from-cache from-line)
1170   (declare (fixnum from-line))
1171   (with-local-cache-functions (cache)
1172     (let ((primary (location-line
1173                     (compute-primary-cache-location-from-location
1174                      cache (line-location from-line) from-cache))))
1175       (declare (fixnum primary))
1176       (multiple-value-bind (free emptyp)
1177           (find-free-cache-line primary cache)
1178         (when (or forcep emptyp)
1179           (when (not emptyp)
1180             (push (cons (line-wrappers free) (line-value free))
1181                   (cache-overflow cache)))
1182           ;;(transfer-line from-cache-vector from-line cache-vector free)
1183           (let ((from-cache-vector (cache-vector from-cache))
1184                 (to-cache-vector (vector))
1185                 (to-line free))
1186             (declare (fixnum to-line))
1187             (if (line-reserved-p to-line)
1188                 (error "transferring something into a reserved cache line")
1189                 (let ((from-loc (line-location from-line))
1190                       (to-loc (line-location to-line)))
1191                   (declare (fixnum from-loc to-loc))
1192                   (modify-cache to-cache-vector
1193                                 (dotimes-fixnum (i (line-size))
1194                                   (setf (cache-vector-ref to-cache-vector
1195                                                           (+ to-loc i))
1196                                         (cache-vector-ref from-cache-vector
1197                                                           (+ from-loc i)))))))
1198             (maybe-check-cache cache)))))))
1199
1200 ;;; Returns NIL or (values <field> <cache-vector>)
1201 ;;;
1202 ;;; This is only called when it isn't possible to put the entry in the
1203 ;;; cache the easy way. That is, this function assumes that
1204 ;;; FILL-CACHE-P has been called as returned NIL.
1205 ;;;
1206 ;;; If this returns NIL, it means that it wasn't possible to find a
1207 ;;; wrapper field for which all of the entries could be put in the
1208 ;;; cache (within the limit).
1209 (defun adjust-cache (cache wrappers value free-old-cache-p)
1210   (with-local-cache-functions (cache)
1211     (let ((ncache (get-cache-from-cache cache (nlines) (field))))
1212       (do ((nfield (cache-field ncache) (next-wrapper-cache-number-index nfield)))
1213           ((null nfield) (free-cache ncache) nil)
1214         (setf (cache-field ncache) nfield)
1215         (labels ((try-one-fill-from-line (line)
1216                    (fill-cache-from-cache-p nil ncache cache line))
1217                  (try-one-fill (wrappers value)
1218                    (fill-cache-p nil ncache wrappers value)))
1219           (if (and (dotimes-fixnum (i (nlines) t)
1220                      (when (and (null (line-reserved-p i))
1221                                 (line-valid-p i wrappers))
1222                        (unless (try-one-fill-from-line i) (return nil))))
1223                    (dolist (wrappers+value (cache-overflow cache) t)
1224                      (unless (try-one-fill (car wrappers+value) (cdr wrappers+value))
1225                        (return nil)))
1226                    (try-one-fill wrappers value))
1227               (progn (when free-old-cache-p (free-cache cache))
1228                      (return (maybe-check-cache ncache)))
1229               (flush-cache-vector-internal (cache-vector ncache))))))))
1230
1231 ;;; returns: (values <cache>)
1232 (defun expand-cache (cache wrappers value free-old-cache-p)
1233   ;;(declare (values cache))
1234   (with-local-cache-functions (cache)
1235     (let ((ncache (get-cache-from-cache cache (* (nlines) 2))))
1236       (labels ((do-one-fill-from-line (line)
1237                  (unless (fill-cache-from-cache-p nil ncache cache line)
1238                    (do-one-fill (line-wrappers line) (line-value line))))
1239                (do-one-fill (wrappers value)
1240                  (setq ncache (or (adjust-cache ncache wrappers value t)
1241                                   (fill-cache-p t ncache wrappers value))))
1242                (try-one-fill (wrappers value)
1243                  (fill-cache-p nil ncache wrappers value)))
1244         (dotimes-fixnum (i (nlines))
1245           (when (and (null (line-reserved-p i))
1246                      (line-valid-p i wrappers))
1247             (do-one-fill-from-line i)))
1248         (dolist (wrappers+value (cache-overflow cache))
1249           (unless (try-one-fill (car wrappers+value) (cdr wrappers+value))
1250             (do-one-fill (car wrappers+value) (cdr wrappers+value))))
1251         (unless (try-one-fill wrappers value)
1252           (do-one-fill wrappers value))
1253         (when free-old-cache-p (free-cache cache))
1254         (maybe-check-cache ncache)))))
1255 \f
1256 ;;; This is the heart of the cache filling mechanism. It implements
1257 ;;; the decisions about where entries are placed.
1258 ;;;
1259 ;;; Find a line in the cache at which a new entry can be inserted.
1260 ;;;
1261 ;;;   <line>
1262 ;;;   <empty?>     is <line> in fact empty?
1263 (defun find-free-cache-line (primary cache &optional wrappers)
1264   ;;(declare (values line empty?))
1265   (declare (fixnum primary))
1266   (with-local-cache-functions (cache)
1267     (when (line-reserved-p primary) (setq primary (next-line primary)))
1268     (let ((limit (funcall (limit-fn) (nlines)))
1269           (wrappedp nil)
1270           (lines nil)
1271           (p primary) (s primary))
1272       (declare (fixnum p s limit))
1273       (block find-free
1274         (loop
1275          ;; Try to find a free line starting at <s>. <p> is the
1276          ;; primary line of the entry we are finding a free
1277          ;; line for, it is used to compute the separations.
1278          (do* ((line s (next-line line))
1279                (nsep (line-separation p s) (1+ nsep)))
1280               (())
1281            (declare (fixnum line nsep))
1282            (when (null (line-valid-p line wrappers)) ;If this line is empty or
1283              (push line lines)          ;invalid, just use it.
1284              (return-from find-free))
1285            (when (and wrappedp (>= line primary))
1286              ;; have gone all the way around the cache, time to quit
1287              (return-from find-free-cache-line (values primary nil)))
1288            (let ((osep (line-separation (line-primary line) line)))
1289              (when (>= osep limit)
1290                (return-from find-free-cache-line (values primary nil)))
1291              (when (cond ((= nsep limit) t)
1292                          ((= nsep osep) (zerop (random 2)))
1293                          ((> nsep osep) t)
1294                          (t nil))
1295                ;; See whether we can displace what is in this line so that we
1296                ;; can use the line.
1297                (when (= line (the fixnum (1- (nlines)))) (setq wrappedp t))
1298                (setq p (line-primary line))
1299                (setq s (next-line line))
1300                (push line lines)
1301                (return nil)))
1302            (when (= line (the fixnum (1- (nlines)))) (setq wrappedp t)))))
1303       ;; Do all the displacing.
1304       (loop
1305        (when (null (cdr lines)) (return nil))
1306        (let ((dline (pop lines))
1307              (line (car lines)))
1308          (declare (fixnum dline line))
1309          ;;Copy from line to dline (dline is known to be free).
1310          (let ((from-loc (line-location line))
1311                (to-loc (line-location dline))
1312                (cache-vector (vector)))
1313            (declare (fixnum from-loc to-loc) (simple-vector cache-vector))
1314            (modify-cache cache-vector
1315                          (dotimes-fixnum (i (line-size))
1316                            (setf (cache-vector-ref cache-vector
1317                                                    (+ to-loc i))
1318                                  (cache-vector-ref cache-vector
1319                                                    (+ from-loc i)))
1320                            (setf (cache-vector-ref cache-vector
1321                                                    (+ from-loc i))
1322                                  nil))))))
1323       (values (car lines) t))))
1324
1325 (defun default-limit-fn (nlines)
1326   (case nlines
1327     ((1 2 4) 1)
1328     ((8 16)  4)
1329     (otherwise 6)))
1330
1331 (defvar *empty-cache* (make-cache)) ; for defstruct slot initial value forms