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