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