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