Refactor CALL-WITH-EACH-GLOBALDB-NAME
[sbcl.git] / src / compiler / info-vector.lisp
blob4175f25854e9a13079a49fbe08161ff86599a63a
1 ;;;; This software is part of the SBCL system. See the README file for
2 ;;;; more information.
3 ;;;;
4 ;;;; This software is derived from the CMU CL system, which was
5 ;;;; written at Carnegie Mellon University and released into the
6 ;;;; public domain. The software is in the public domain and is
7 ;;;; provided with absolutely no warranty. See the COPYING and CREDITS
8 ;;;; files for more information.
10 (in-package "SB!C")
12 ;;;; This file implements abstract types which map globaldb Info-Number/Name
13 ;;;; pairs to data values. The database itself is defined in 'globaldb'.
15 ;;; Quasi-lockfree concurrent hashtable
16 ;;; ===================================
18 ;; References:
19 ;; http://trac.clozure.com/ccl/wiki/Internals/LockFreeHashTables
20 ;; https://github.com/boundary/high-scale-lib/blob/master/src/main/java/org/cliffc/high_scale_lib/NonBlockingHashMap.java
22 ;; The basic hashable is a lightweight one using prime number sizing strategy,
23 ;; and a secondary hash for re-probing that is not necessarily co-prime with
24 ;; the table size (as it would be, ideally), and no support for deletion.
26 ;; The lock-free logic differs from each of the preceding reference algorithms.
27 ;; The Java algorithm is truly lock-free: death of any thread will never impede
28 ;; progress in other threads. The CCL algorithm is only quasi-lock-free, as is
29 ;; ours. Were a rehashing thread to terminate abnormally while holding the
30 ;; rehash mutex, all other threads will likely starve at some point.
32 ;; Unlike the CCL algorithm, we allow reading/writing concurrently with rehash.
33 ;; Most operations will never notice that the rehasher has acquired a mutex,
34 ;; because the only case where writers compete for the mutex is in trying
35 ;; to claim a new cell in a storage vector that is being transported, and where
36 ;; the rehasher has already visited the desired cell. Since the rehasher will
37 ;; never re-visit a cell, it disallows updates that it could not perceive.
38 ;; The Java algorithm has additional complexity imposed upon it by the
39 ;; feature that rehashing work is parceling out fairly to threads,
40 ;; whereas we avoid that by having one rehasher transport all cells.
42 ;; A marker for cells that may be claimed by a writer
43 (defconstant +empty-key+ 0)
44 ;; A marker for cells that may NOT be claimed by a writer.
45 (defconstant +unavailable-key+ -1)
47 ;; We have a 24-bit cell index. This is generous,
48 ;; allowing for ~5 million Names assuming 60% load factor.
49 (deftype info-cell-index () `(unsigned-byte 24))
51 ;; An INFO-STORAGE is a vector of a 3-element header followed by all keys
52 ;; and then all values. This way we can simply use FILL to set all keys to 0
53 ;; and all values to NIL.
54 (defconstant +info-keys-offset+ 3)
55 (defstruct (info-storage (:type vector) (:constructor nil) (:copier nil))
56 ;; Capacity refers to pairs of vector elements. The lower bound is to
57 ;; try (in vain) to elide a check for division by 0 in the secondary hash.
58 ;; The upper bound is harmlessly wrong by a factor of 2 because
59 ;; INFO-CELL-INDEX should be the max physical cell that can be addressed.
60 ;; No problem - you'll run out of memory before hitting the edge anyway.
61 (capacity 0 :type (and (integer 3 *) info-cell-index)) ; immutable
62 ;; Make a new storage if count exceeds this
63 (threshold 0 :type info-cell-index) ; immutable
64 (next nil :type simple-vector) ; Pending INFO-STORAGE during rehash
65 ;; keys ... data ...
68 (defun make-info-storage (n-cells-min &optional (load-factor .7))
69 ;; If you ask for 40 entries at 50% load, you get (PRIMIFY 80) entries.
70 (let* ((n-cells (primify (ceiling n-cells-min load-factor)))
71 (a (make-array (+ +info-keys-offset+ (* 2 n-cells))))
72 (end (+ +info-keys-offset+ n-cells)))
73 (setf (info-storage-capacity a) n-cells
74 ;; The threshold should be approximately the same as
75 ;; the number you asked for in the first place.
76 (info-storage-threshold a) (floor (* n-cells load-factor))
77 (info-storage-next a) #()) ; type-correct initial value
78 (fill a +empty-key+ :start +info-keys-offset+ :end end)
79 (fill a nil :start end)
80 a))
82 (defstruct (info-hashtable (:conc-name info-env-))
83 (storage (make-info-storage 30) :type simple-vector)
84 (comparator #'equal :type function)
85 (hash-function #'globaldb-sxhashoid :type function)
86 (mutex (sb!thread:make-mutex))
87 ;; COUNT is always at *least* as large as the key count.
88 ;; If no insertions are in progress, it is exactly right.
89 (count 0 :type word))
91 (def!method print-object ((self info-hashtable) stream)
92 (declare (stream stream))
93 (print-unreadable-object (self stream :type t :identity t)
94 (format stream "~D/~D entr~:@P" (info-env-count self)
95 (info-storage-capacity (info-env-storage self)))))
97 ;; We can't assume that the host lisp supports a CAS operation for info-gethash
98 ;; or info-puthash, but that's fine because there's only one thread.
99 (defmacro info-cas (storage index oldval newval)
100 #+sb-xc-host
101 `(let ((actual-old (svref ,storage ,index)))
102 (if (eq actual-old ,oldval)
103 (progn (setf (svref ,storage ,index) ,newval) actual-old)
104 (error "xc bug. CAS expected ~S got ~S" actual-old ,oldval)))
105 #-sb-xc-host
106 `(cas (svref ,storage ,index) ,oldval ,newval))
108 ;; Similarly we need a way to atomically adjust the hashtable count.
109 (declaim (inline info-env-adjust-count))
110 (defun info-env-adjust-count (table delta)
111 #+sb-xc-host
112 (prog1 (info-env-count table) (incf (info-env-count table) delta))
113 #-sb-xc-host
114 ;; Inform the compiler that this is not possibly a bignum,
115 ;; since it's true upper bound is the info storage threshold.
116 (truly-the info-cell-index (atomic-incf (info-env-count table) delta)))
118 (declaim (inline make-info-forwarding-pointer
119 info-forwarding-pointer-target
120 info-value-moved-p)
121 (ftype (sfunction (t) simple-vector) info-env-rehash)
122 (ftype (sfunction (t t) simple-vector) %wait-for-rehash))
124 ;; Concurrent access relies on a forwarding pointer being placed into
125 ;; transported value cells. Since this is not a fully general hashtable,
126 ;; we can use fixnums as forwarding pointers, as they're otherwise
127 ;; never present as a value.
128 #+sb-xc-host
129 (progn
130 (defun make-info-forwarding-pointer (index) index)
131 (defun info-forwarding-pointer-target (pointer) pointer)
132 (defun info-value-moved-p (val) (fixnump val)))
134 ;; However, here is a forwarding-pointer representation that allows fixnums
135 ;; as legal values in the table, so, since it's more general, ... why not?
136 #-sb-xc-host
137 (progn
138 (defun make-info-forwarding-pointer (index)
139 (declare (type info-cell-index index) (optimize (safety 0)))
140 (%make-lisp-obj (+ (ash index 8) sb!vm:unbound-marker-widetag)))
141 (defun info-forwarding-pointer-target (marker)
142 (ash (get-lisp-obj-address marker) -8))
143 (defun info-value-moved-p (x)
144 (eq (logand (get-lisp-obj-address x) #xff)
145 sb!vm:unbound-marker-widetag)))
147 ;; The common skeleton of {Get, Put, Rehash} operations. Probe key cells until
148 ;; either a hit occurs, in which case the :HIT form is executed and looping
149 ;; stops; or an empty slot is seen in which case the :MISS code is executed.
150 ;; :MISS should contain a GO or RETURN on success, otherwise probing continues.
151 ;; No precaution exists against probing forever, such as could happen if the
152 ;; probing strategy fails to visit all candidate free cells.
154 ;; Stepping is done by subtracting a secondary hash rather than adding,
155 ;; as this allows testing for wraparound by comparison to a constant
156 ;; instead of against storage capacity. Nonlinear probing jumps around in
157 ;; the L1 cache regardless, as they key space is a ring so the "direction"
158 ;; of probing is irrelevant. [In contrast, linear probing usually benefits
159 ;; from scanning physically forward, preferably within a cache line,
160 ;; but for practical purposes linear probing is worse.]
162 (defmacro !do-probe-sequence ((storage key table &optional hash)
163 &key probe hit miss)
164 (with-unique-names (test miss-fn len key-index step)
165 (once-only ((storage storage) (key key) (table table)
166 (hashval
167 `(the fixnum
168 ,(or hash
169 `(funcall (info-env-hash-function ,table) ,key)))))
170 `(macrolet ((key-index () ; expose key+value indices to invoking code
171 ',key-index)
172 (value-index ()
173 '(+ (info-storage-capacity ,storage) ,key-index))
174 (,test ()
175 `(let ((probed-key (svref ,',storage ,',key-index)))
176 ,',probe ; could keep a tally of the probes
177 ;; Optimistically test for hit first, then markers
178 (cond ((funcall (info-env-comparator ,',table)
179 probed-key ,',key)
180 (go :hit))
181 ((or (eql probed-key +unavailable-key+)
182 (eql probed-key +empty-key+))
183 (,',miss-fn))))))
184 (let* ((,len (info-storage-capacity ,storage))
185 (,key-index (+ (rem ,hashval ,len) +info-keys-offset+))
186 (,step 0))
187 (declare (type info-cell-index ,key-index ,step))
188 (dx-flet ((,miss-fn () ,miss))
189 (tagbody
190 (,test)
191 ;; only need the second hash if didn't hit on first try
192 (setq ,step (1+ (rem ,hashval (- ,len 2))))
193 :loop
194 (setq ,key-index (let ((next (- ,key-index ,step)))
195 (if (< next +info-keys-offset+)
196 (+ next ,len)
197 next)))
198 (,test)
199 (go :loop)
200 :HIT))
201 ,hit)))))
203 ;; Wait for ENV's storage to change to something other than STORAGE, and
204 ;; return the new one. As long as rehash finishes in finite time, every thread
205 ;; makes progess. We don't protect against untimely death of the thread
206 ;; that holds the lock.
208 (defun %wait-for-rehash (env storage)
209 ;; kinda spin, except not quite that bad
210 (loop (sb!thread:thread-yield) ; relinquish time slice, supposing it helps
211 (if (eq (info-env-storage env) storage)
212 ;; Grab and release the mutex for no other reason than to
213 ;; observe that a rehasher doesn't (for the moment) have it.
214 (sb!thread:with-mutex ((info-env-mutex env))) ; do nothing, retry
215 (return (info-env-storage env)))))
217 ;; Look in info-environment ENV for the name KEY. Arguments are like GETHASH.
219 ;; Invariant: any KEY's value is present in at most 1 storage.
220 ;; Uniqueness of the location ensures that when writing with CAS, the place is
221 ;; either current, or CAS fails in a way that informs the writer of a new place.
222 ;; At most one probing sequence occurs, in that hitting a key might entail
223 ;; more than one forwarding but never a re-probing.
224 ;; The same is not true on insert, for which probing restart is quite common.
225 ;; When chasing values, INFO-STORAGE-NEXT may or may not be EQ to what is in
226 ;; INFO-ENV-STORAGE, depending whether rehash is still running, has completed,
227 ;; or started all over again before the reader got a chance to chase one time.
229 (defun info-gethash (key env &aux (storage (info-env-storage env)))
230 (!do-probe-sequence (storage key env)
231 :miss (return-from info-gethash nil)
232 ;; With 99% certainty the :READ barrier is needed for non-x86, and if not,
233 ;; it can't hurt. 'info-storage-next' can be empty until at least one cell
234 ;; has been forwarded, but in general an unsynchronized read might be
235 ;; perceived as executing before a conditional that guards whether the
236 ;; read should happen at all. 'storage-next' has the deceptive look of a
237 ;; data dependency but it's not - it's a control dependency which as per
238 ;; the 'memory-barriers.txt' document at kernel.org, demands a barrier.
239 ;; The subsequent ref to storage (if the loop iterates) has a
240 ;; data-dependency, and will never be reordered except on an Alpha :-(
241 ;; so we _don't_ need a barrier after resetting 'storage' and 'index'.
242 :hit (let ((index (value-index)))
243 (loop (let ((value
244 (sb!thread:barrier (:read) (svref storage index))))
245 (if (info-value-moved-p value)
246 (setq storage (info-storage-next storage)
247 index (info-forwarding-pointer-target value))
248 (return value)))))))
250 ;; ENV and KEY are as above. UPDATE-PROC is invoked with the old value stored
251 ;; for KEY and it should return the possibly-unchanged new value to put.
253 ;; Note a tiny problem of semantics on 'miss' - for an instant after winning
254 ;; CAS of a new key, that key appears to exist with the default value NIL,
255 ;; causing readers to think "FOUND-P" = T which might have a different sense
256 ;; from "not found". If a Name is transiently "found" despite having no data,
257 ;; nobody cares, at least for globaldb. Remedies, if desired, involve either:
258 ;; 1. Making a "no value" marker that is distinct from NIL.
259 ;; 2. Placing keys/value pairs in adjacent cells and using double-wide CAS.
260 ;; The reason we don't care about this anomaly is that we have to
261 ;; look in an Info-Vector [q.v.] anyway to get the whole picture.
263 (defun info-puthash (env key update-proc)
264 (aver (not (member key '(0 -1))))
265 (labels ((follow/update (array value-index)
266 (let ((value ; see INFO-GETHASH for this barrier's rationale
267 (sb!thread:barrier (:read) (svref array value-index))))
268 (if (info-value-moved-p value)
269 (follow/update (info-storage-next array)
270 (info-forwarding-pointer-target value))
271 (update array value-index value))))
272 (update (array index oldval)
273 ;; invariant: OLDVAL is not a forwarding pointer.
274 (let ((newval (funcall update-proc oldval)))
275 (if (eq newval oldval)
276 oldval ; forgo update
277 (named-let put ((array array) (index index))
278 (let ((actual-old (info-cas array index oldval newval)))
279 ;; Unlike above, this read of storage-next can not
280 ;; be perceived as having occurred prior to CAS.
281 ;; x86 synchronizes at every locked instruction, and our
282 ;; PPC CAS vops sync as a nececessity of performing CAS.
283 (cond ((eq oldval actual-old) newval) ; win
284 ((info-value-moved-p actual-old) ; forwarded
285 (put (info-storage-next array)
286 (info-forwarding-pointer-target actual-old)))
287 (t ; collision with another writer
288 (update array index actual-old)))))))))
289 (named-let probe ((hashval (funcall (info-env-hash-function env) key))
290 (storage (info-env-storage env)))
291 (!do-probe-sequence (storage key env hashval)
292 :hit (follow/update storage (value-index))
293 :miss
294 (progn
295 (let ((old-count (info-env-adjust-count env 1)))
296 (declare (type info-cell-index old-count))
297 (when (>= old-count (info-storage-threshold storage))
298 (sb!thread:with-mutex ((info-env-mutex env))
299 ;; any thread could have beaten us to rehashing
300 (when (eq (info-env-storage env) storage)
301 (info-env-rehash env)))
302 (info-env-adjust-count env -1) ; prepare to retry
303 (return-from probe (probe hashval (info-env-storage env)))))
304 ;; Attempt to claim KEY-INDEX
305 (let ((oldkey (info-cas storage (key-index) +empty-key+ key)))
306 (when (eql oldkey +empty-key+) ; successful claim
307 ;; Optimistically assume that nobody else rewrote the value
308 (return-from probe (update storage (value-index) nil)))
309 (info-env-adjust-count env -1) ; failed
310 ;; The fallthrough branch of this COND is ordinary CAS failure where
311 ;; somebody else wanted this slot, and won. Looping tries again.
312 (cond ((funcall (info-env-comparator env) oldkey key) ; coincidence
313 (return-from probe (follow/update storage (value-index))))
314 ((eql oldkey +unavailable-key+) ; Highly unlikely
315 ;; as preemptive check up above ensured no rehash needed.
316 (return-from probe
317 (probe hashval (%wait-for-rehash env storage)))))))))))
319 ;; Rehash ENV to a larger storage. When writing a key into new storage,
320 ;; key cells are uniquely owned by this thread without contention.
321 ;; Other threads may not look in new storage without first observing that
322 ;; a key's value was definitely moved.
323 ;; The rehasher marks empty cells as unusable so that writers can't insert
324 ;; into the subsequence of storage already visited. The rehasher must of
325 ;; course vie for the cell it is trying to mark as unusable.
327 (defun info-env-rehash (env)
328 (let* ((old-count (info-env-count env))
329 (old-storage (info-env-storage env))
330 ;; the new storage begins life at ~50% capacity
331 (new-storage (make-info-storage (ceiling old-count .5)))
332 (old-capacity (info-storage-capacity old-storage))
333 (new-capacity (info-storage-capacity new-storage)))
335 (sb!thread:barrier (:write) ; Publish NEW-STORAGE before scanning keys.
336 (setf (info-storage-next old-storage) new-storage))
338 (loop for old-key-index of-type info-cell-index
339 from +info-keys-offset+ below (+ +info-keys-offset+ old-capacity)
340 ;; If the indexed cell is not in use, try once to prevent subsequent
341 ;; writes by changing the empty marker to 'unavailable'. The outcome
342 ;; determines whether to continue transporting the cell's value.
343 for key = (let ((key (svref old-storage old-key-index)))
344 (if (eql key +empty-key+)
345 (info-cas old-storage old-key-index
346 +empty-key+ +unavailable-key+)
347 key))
348 unless (eql key +empty-key+)
349 do (let* ((new-key-index
350 (block nil
351 (!do-probe-sequence (new-storage key env)
352 :hit (bug "Globaldb rehash failure. Mutated key?")
353 :miss (return (key-index)))))
354 (old-value-index (+ old-key-index old-capacity))
355 (new-value-index (+ new-key-index new-capacity))
356 (value (svref old-storage old-value-index)))
357 (setf (svref new-storage new-key-index) key) ; Q: barrier needed?
358 ;; Copy the current value into the new storage,
359 ;; and CAS in a forwarding pointer. Repeat until successful.
360 (loop
361 ;; Force VALUE to memory before publishing relocated status
362 (sb!thread:barrier (:write)
363 (setf (svref new-storage new-value-index) value))
364 (let ((actual-old
365 (info-cas
366 old-storage old-value-index value
367 (make-info-forwarding-pointer new-value-index))))
368 (if (eq value actual-old)
369 (return)
370 (setq value actual-old))))))
372 ;; Typical of most lockfree algorithms, we've no idea when
373 ;; the old storage can be freed. GC will figure it out.
374 ;; No write barrier needed. Threads still looking at old storage
375 ;; will eventually find all cells unavailable or forwarded.
376 (setf (info-env-storage env) new-storage)))
378 ;; This maphash implementation is not threadsafe.
379 ;; It can be made threadsafe by following forwarded values
380 ;; and skipping over unavailable keys.
382 (defmacro info-maphash (fun env) ; map FUN over each key/value
383 (with-unique-names (f storage capacity i key)
384 `(let* ((,f ,fun)
385 (,storage (info-env-storage ,env))
386 (,capacity (info-storage-capacity ,storage)))
387 (loop for ,i below ,capacity
388 for ,key = (svref ,storage (+ ,i +info-keys-offset+))
389 unless (eql ,key +empty-key+)
390 do (funcall ,f ,key
391 (svref ,storage
392 (+ ,i +info-keys-offset+ ,capacity)))))))
394 ;; CAS is the primitive operation on an info hashtable,
395 ;; and SETF is implemented in terms of CAS. For the most part it is
396 ;; inadvisable to use this for anything other than tinkering at the REPL.
398 (defun (setf info-gethash) (newval key env)
399 (dx-flet ((update (old) (declare (ignore old)) newval))
400 (info-puthash env key #'update)))
402 (defun show-info-env (env)
403 (info-maphash (lambda (k v) (format t "~S -> ~S~%" k v)) env))
405 ;;;; Info-Vectors
406 ;;;; ============
408 ;;; Info for a Name (an arbitrary object) is stored in an Info-Vector,
409 ;;; which is like is a 2-level association list. Info-Vectors are stored in
410 ;;; symbols for most names, or in the global hashtable for "complicated" names.
412 ;;; Such vectors exists in two variations: packed and unpacked.
413 ;;; The representations are nearly equivalent for lookup, but the packed format
414 ;;; is more space-efficient, though difficult to manipulate except by unpacking.
416 ;;; Consider a family of Names whose "root" is SB-MOP:STANDARD-INSTANCE-ACCESS.
417 ;;; 1. SB-MOP:STANDARD-INSTANCE-ACCESS
418 ;;; 2. (SETF SB-MOP:STANDARD-INSTANCE-ACCESS)
419 ;;; 3. (CAS SB-MOP:STANDARD-INSTANCE-ACCESS)
421 ;;; Those three names share one Info-Vector. Conceptually the outer alist key
422 ;;; is NIL for the first of those names, and SETF/CAS for the latter two.
423 ;;; The inner alist key is a number identifying a type of info.
424 ;;; If it were actually an alist, it would look like this:
426 ;;; ((nil (63 . #<fdefn SB-MOP:STANDARD-INSTANCE-ACCESS>) (1 . :FUNCTION) ...)
427 ;;; (SETF (63 . #<fdefn (SETF SB-MOP:STANDARD-INSTANCE-ACCESS)>) ...)
428 ;;; (CAS (63 . #<fdefn (CAS SB-MOP:STANDARD-INSTANCE-ACCESS)>) ...)
429 ;;; ...)
431 ;;; Note:
432 ;;; * The root name is exogenous to the vector - it is not stored.
433 ;;; * The info-number for (:FUNCTION :DEFINITION) is 63, :KIND is 1, etc.
434 ;;; * Names which are lists of length other than 2, or improper lists,
435 ;;; or whose elements are not both symbols, are disqualified.
437 ;;; Packed vector layout
438 ;;; --------------------
439 ;;; Because the keys to the inner lists are integers in the range 0 to 63,
440 ;;; either 5 or 10 keys will fit into a fixnum depending on word size.
441 ;;; This permits one memory read to retrieve a collection of keys. In packed
442 ;;; format, an ordered set of keys ("fields") is called a "descriptor".
444 ;;; Descriptors are stored from element 0 upward in the packed vector,
445 ;;; and data are indexed downward from the last element of the vector.
447 ;;; #(descriptor0 descriptor1 ... descriptorN valueN ... value1 value0)
449 ;;; e.g. The field at absolute index 3 - vector element 0, bit position 18 -
450 ;;; will find its data at index (- END 3). In this manner, it doesn't matter
451 ;;; how many more descriptors exist.
453 ;;; A "group" comprises all the info for a particular Name, and its list
454 ;;; of types may may span descriptors, though rarely.
455 ;;; An "auxilliary key" is the first element of a 2-list Name. It is interposed
456 ;;; within the data portion of the vector after the preceding info group.
457 ;;; Descriptors are self-delimiting in that the first field in a group
458 ;;; indicates the number of additional fields in the group.
460 ;;; Unpacked vector layout
461 ;;; ----------------------
462 ;;; This representation is used transiently during insertion/deletion.
463 ;;; It is a concatenation of plists as a vector, interposing at the splice
464 ;;; points the auxilliary key for the group, except for the root name which
465 ;;; does not store an auxilliary key.
467 ;;; Unpacked vector format looks like:
469 ;;; /- next group starts here
470 ;;; v
471 ;;; #(length type val type val ... KEY length type val ... KEY length ...)
472 ;;; ^
473 ;;; info group for the primary Name, a/k/a "root symbol", starts here
475 ;;; One can envision that the first info group stores its auxilliary key
476 ;;; at vector index -1 when thinking about the correctness of algorithms
477 ;;; that process unpacked info-vectors.
478 ;;; See !TEST-PACKIFY-INFOS for examples of each format.
480 ;;;;; Some stuff moved from 'globaldb.lisp':
482 (defconstant info-num-mask (ldb (byte info-number-bits 0) -1)) ; #b111111
484 ;; Using 6 bits per packed field, 5 infos can be described in a 30-bit fixnum,
485 ;; or 10 in a fixnum on 64-bit machines (regardless of n-fixnum-tag-bits).
486 ;; The eval-when seems to be necessary for building with CCL as host.
487 (eval-when (:compile-toplevel :load-toplevel :execute)
488 (defconstant +infos-per-word+ (floor sb!vm:n-fixnum-bits info-number-bits)))
490 ;; Descriptors are target fixnums
491 (deftype info-descriptor () `(signed-byte ,sb!vm:n-fixnum-bits))
493 ;; Every Name amenable to storage in info-vectors has an auxilliary key
494 ;; as explained above, except that the root name itself has none.
495 (defconstant +no-auxilliary-key+ 0)
497 ;; An empty info-vector. Its 0th field describes that there are no more fields.
498 (defconstant-eqx +nil-packed-infos+ #(0) #'equalp)
500 ;; FDEFINITIONs have an info-number that admits slightly clever logic
501 ;; for INFO-VECTOR-FDEFN. Do not change this constant without
502 ;; careful examination of that function.
503 (defconstant +fdefn-info-num+ info-num-mask)
505 ;; Extract a field from a packed info descriptor.
506 ;; A field is either a count of info-numbers, or an info-number.
507 (declaim (inline packed-info-field))
508 (defun packed-info-field (vector desc-index field-index)
509 ;; Should not need (THE INFO-NUMBER) however type inference
510 ;; seems borked during cross-compilation due to the shadowed LDB
511 ;; (see "don't watch:" in cold/defun-load-or-cload-xcompiler)
512 ;; and in particular it sees especially weird that this message appears
513 ;; note: type assertion too complex to check:
514 ;; (VALUES (UNSIGNED-BYTE 6) &REST T).
515 ;; because nothing here should be possibly-multiple-value-producing.
516 (the info-number
517 (ldb (byte info-number-bits
518 (* (the (mod #.+infos-per-word+) field-index) info-number-bits))
519 (the info-descriptor (svref vector desc-index)))))
521 ;; Compute the number of elements needed to hold unpacked VECTOR after packing.
522 ;; This is not "compute-packed-info-size" since that could be misconstrued
523 ;; and wanting the vector to be already packed.
525 (defun compute-packified-info-size (vector &optional (end (length vector)))
526 (declare (simple-vector vector)) ; unpacked format
527 (let ((index 0) ; index into the unpacked input vector
528 (n-fields 0)) ; will be the total number of packed fields
529 (declare (type index index end n-fields))
530 (loop
531 ;; 'length' is the number of vector elements in this info group,
532 ;; including itself but not including its auxilliary key.
533 (let ((length (the index (svref vector index))))
534 ;; Divide by 2 because we only count one field for the entry, but the
535 ;; input vector had 2 cells per entry. Add 1 because the group's field
536 ;; count is accounted for in the total packed field count.
537 (incf n-fields (1+ (ash length -1)))
538 (incf index (1+ length)) ; jump over the entries, +1 for aux-key
539 (when (>= index end)
540 ;; The first info group lacks an aux-key, making n-fields 1 too high
541 ;; in terms of data cells used, but correct for packed fields.
542 (return (+ (ceiling n-fields +infos-per-word+) (1- n-fields))))))))
544 ;; MAKE-INFO-DESCRIPTOR is basically ASH-LEFT-MODFX, shifting VAL by SHIFT.
545 ;; It is important that info descriptors be target fixnums, but 'cross-modular'
546 ;; isn't loaded early enough to use 'mask-signed-field'.
547 ;; It's not needed on 64-bit host/target combination because 10 fields (60 bits)
548 ;; never touch the sign bit.
549 ;; FIXME: figure out why the definition of ash-left-modfx is
550 ;; conditionalized out for platforms other than x86[-64].
551 ;; It looks like it ought to work whether or not there are vops.
552 (defmacro make-info-descriptor (val shift)
553 (if (> sb!vm:n-fixnum-bits 30)
554 `(ash ,val ,shift)
555 `(logior (if (logbitp (- 29 ,shift) ,val) sb!xc:most-negative-fixnum 0)
556 (ash ,val ,shift))))
558 ;; Convert unpacked vector to packed vector.
559 ;; 'pack-infos' would be a hypothetical accessor for the 'infos' of a 'pack'
560 ;; (whatever that is ...) so verbifying as such makes it more mnemonic to me.
562 (defun packify-infos (input &optional (end (length input)))
563 (declare (simple-vector input))
564 (let* ((output (make-array (compute-packified-info-size input end)))
565 (i -1) ; input index: pre-increment to read the next datum
566 (j -1) ; descriptor index: pre-increment to write
567 (k (length output)) ; data index: pre-decrement to write
568 (field-shift 0)
569 (word 0))
570 (declare (type index-or-minus-1 i j k end)
571 (type (mod #.(1+ (* (1- +infos-per-word+) info-number-bits)))
572 field-shift)
573 (type info-descriptor word))
574 (flet ((put-field (val) ; insert VAL into the current packed descriptor
575 (declare (type info-number val))
576 (setq word (logior (make-info-descriptor val field-shift) word))
577 (if (< field-shift (* (1- +infos-per-word+) info-number-bits))
578 (incf field-shift info-number-bits)
579 (setf (svref output (incf j)) word field-shift 0 word 0))))
580 ;; Truncating divide by 2: count = n-elements in the group @ 2 per entry,
581 ;; +1 for count itself but not including its aux-key.
582 (loop (let ((count (ash (the index (svref input (incf i))) -1)))
583 (put-field count) ; how many infos to follow
584 (dotimes (iter count)
585 (put-field (svref input (incf i))) ; an info-number
586 (setf (svref output (decf k)) (svref input (incf i)))) ; value
587 (when (>= (incf i) end)
588 (return))
589 (setf (svref output (decf k)) (svref input i))))) ; an aux-key
590 (unless (zerop field-shift) ; store the final descriptor word
591 (setf (svref output (incf j)) word))
592 (aver (eql (1+ j) k)) ; last descriptor must be adjacent final data cell
593 output))
595 ;; Within the scope of BODY, bind GENERATOR to a local function which
596 ;; returns the next field from a descriptor in INPUT-VAR, a packed vector.
597 ;; The generator uses DESCRIPTOR-INDEX and updates it as a side-effect.
599 (defmacro !with-packed-info-iterator ((generator input-var
600 &key descriptor-index)
601 &body body)
602 (with-unique-names (input word count)
603 `(let* ((,input (the simple-vector ,input-var))
604 (,descriptor-index -1)
605 (,count 0)
606 (,word 0))
607 (declare (type info-descriptor ,word)
608 (fixnum ,count)
609 (type index-or-minus-1 ,descriptor-index))
610 (flet ((,generator ()
611 (when (zerop ,count)
612 (incf ,descriptor-index)
613 (setq ,word (svref ,input ,descriptor-index)
614 ,count +infos-per-word+))
615 (prog1 (logand ,word info-num-mask)
616 (setq ,word (ash ,word (- info-number-bits)))
617 (decf ,count))))
618 ,@body))))
620 ;; Iterate over VECTOR, binding DATA-INDEX to the index of each aux-key in turn.
621 ;; TOTAL-N-FIELDS is deliberately exposed to invoking code.
623 (defmacro !do-packed-info-vector-aux-key ((vector &optional (data-index (gensym)))
624 step-form &optional result-form)
625 (with-unique-names (descriptor-idx field-idx)
626 (once-only ((vector vector))
627 `(let ((,data-index (length ,vector))
628 (,descriptor-idx 0)
629 (,field-idx 0)
630 (total-n-fields 0))
631 (declare (type index ,data-index ,descriptor-idx total-n-fields)
632 (type (mod #.+infos-per-word+) ,field-idx))
633 ;; Loop through the descriptors in random-access fashion.
634 ;; Skip 1+ n-infos each time, because the 'n-infos' is itself a field
635 ;; that is not accounted for in its own value.
636 (loop (let ((n (1+ (packed-info-field ,vector
637 ,descriptor-idx ,field-idx))))
638 (incf total-n-fields n)
639 (multiple-value-setq (,descriptor-idx ,field-idx)
640 (floor total-n-fields +infos-per-word+))
641 (decf ,data-index n))
642 ;; Done when the ascending index and descending index meet
643 (unless (< ,descriptor-idx ,data-index)
644 (return ,result-form))
645 ,@(if step-form (list step-form)))))))
647 ;; Return all function names that are stored in SYMBOL's info-vector.
648 ;; As an example, (INFO-VECTOR-NAME-LIST 'SB-PCL::DIRECT-SUPERCLASSES) =>
649 ;; ((SB-PCL::SLOT-ACCESSOR :GLOBAL SB-PCL::DIRECT-SUPERCLASSES SB-PCL::READER)
650 ;; (SB-PCL::SLOT-ACCESSOR :GLOBAL SB-PCL::DIRECT-SUPERCLASSES BOUNDP)
651 ;; (SB-PCL::SLOT-ACCESSOR :GLOBAL SB-PCL::DIRECT-SUPERCLASSES SB-PCL::WRITER))
652 (defun info-vector-name-list (symbol)
653 (let ((vector (symbol-info-vector symbol))
654 (list))
655 (when vector
656 (!do-packed-info-vector-aux-key (vector key-index)
657 (push (construct-globaldb-name (svref vector key-index) symbol)
658 list))
659 (nconc (and (plusp (packed-info-field vector 0 0)) (list symbol))
660 (nreverse list)))))
662 ;; Compute the number of elements needed to hold packed VECTOR after unpacking.
663 ;; The unpacked size is the number of auxilliary keys plus the number of entries
664 ;; @ 2 cells per entry, plus the number of length cells which indicate the
665 ;; number of data cells used (including length cells but not aux key cells).
666 ;; Equivalently, it's the number of packed fields times 2 minus 1.
668 (defun compute-unpackified-info-size (vector)
669 (declare (simple-vector vector))
670 (!do-packed-info-vector-aux-key (vector) ()
671 ;; off-by-one: the first info group's auxilliary key is imaginary
672 (1- (truly-the fixnum (ash total-n-fields 1)))))
674 ;; Convert packed INPUT vector to unpacked.
675 ;; If optional OUTPUT is supplied, it is used, otherwise output is allocated.
676 ;; For efficiency the OUTPUT should be provided as a dynamic-extent array.
678 (defun unpackify-infos (input &optional (output nil output-supplied-p))
679 (declare (simple-vector input))
680 (unless output-supplied-p
681 (setq output (make-array (compute-unpackified-info-size input))))
682 (let ((i (length input)) (j -1)) ; input index and output index respectively
683 (declare (type index-or-minus-1 i j))
684 (!with-packed-info-iterator (next-field input :descriptor-index desc-idx)
685 (loop ; over name
686 (let ((n-infos (next-field)))
687 ;; store the info group length, including the length cell in the length
688 (setf (svref output (incf j)) (1+ (ash n-infos 1)))
689 (dotimes (iter n-infos) ; over info-types
690 (setf (svref output (incf j)) (next-field) ; type-num
691 (svref output (incf j)) (svref input (decf i))))) ; value
692 (if (< desc-idx (decf i)) ; as long as the indices haven't met
693 (setf (svref output (incf j)) (svref input i)) ; copy next aux-key
694 (return (if output-supplied-p nil output))))))) ; else done
696 ;; Return the index of the 'length' item for an info group having
697 ;; auxilliary-key KEY in unpacked VECTOR bounded by END (exclusive),
698 ;; or NIL if not found.
700 (defun info-find-aux-key/unpacked (key vector end)
701 (declare (type index end))
702 (if (eql key +no-auxilliary-key+)
703 0 ; the first group's length (= end) is stored here always
704 (let ((index 0))
705 (declare (type index index))
706 (loop
707 ;; skip 'length' cells plus the next aux-key
708 (incf index (1+ (the index (svref vector index))))
709 (cond ((>= index end)
710 (return nil))
711 ;; backward a cell is where the aux-key resides.
712 ((eq (svref vector (1- index)) key)
713 (return index)))))))
715 ;; In packed info VECTOR try to find the auxilliary key SYMBOL.
716 ;; If found, return indices of its data, info descriptor word, and field.
717 ;; If not found, the first value is NIL and the descriptor indices
718 ;; arbitrarily point to the next available descriptor field.
720 (defun info-find-aux-key/packed (vector symbol)
721 ;; explicit bounds checking is done by the code below
722 (declare (optimize (safety 0)))
723 (aver (simple-vector-p vector))
724 (let ((descriptor-idx 0) ; physical index to vector
725 (field-idx 0) ; relative index within current descriptor
726 ;; On each iteration DATA-IDX points to an aux-key cell
727 ;; The first group's imaginary aux-key cell is past the end.
728 (data-idx (length (the simple-vector vector))))
729 (declare (type index descriptor-idx data-idx)
730 (fixnum field-idx)) ; can briefly exceed +infos-per-word+
731 ;; Efficiently skip past N-INFOS infos. If decrementing the data index
732 ;; hits the descriptor index, we're done. Otherwise increment the field
733 ;; index and maybe descriptor index and check again for loop termination.
734 (flet ((skip (n-infos &aux (n-fields (1+ n-infos))) ; return T on success
735 (cond ((<= (decf data-idx n-fields) descriptor-idx) nil)
736 ;; descriptor-idx < data-idx, so potentially more data.
737 ;; If current descriptor has another field, continue.
738 ((< (incf field-idx n-fields) +infos-per-word+) t)
739 (t ; The descriptor index advances.
740 (loop (incf descriptor-idx)
741 (when (< (decf field-idx +infos-per-word+)
742 +infos-per-word+)
743 (return (< descriptor-idx data-idx))))))))
744 (declare (inline skip))
745 ;; While this could compare aux-keys with #'EQUAL, it is not obvious how
746 ;; in general one would pick a symbol from the name as that which
747 ;; is delegated as the one to hold the info-vector.
748 (values (cond ((not (skip (packed-info-field vector 0 0))) nil)
749 ;; At least one aux key is present.
750 ((eq (aref vector data-idx) symbol) data-idx) ; yay
751 ;; aux-key order invariant allows early fail on SETF
752 ((eq symbol 'setf) nil)
754 (loop
755 (cond ((not (skip (packed-info-field vector descriptor-idx
756 field-idx)))
757 (return nil))
758 ((eq (aref vector data-idx) symbol)
759 (return data-idx))))))
760 descriptor-idx field-idx)))) ; can be ignored if 1st val is nil
762 ;; Take a packed info-vector INPUT and insert (AUX-KEY,INFO-NUMBER,VALUE).
763 ;; Packed info-vectors are immutable. Any alteration must create a copy.
764 ;; This is done by unpacking/repacking - it's easy enough and fairly
765 ;; efficient since the temporary vector is stack-allocated.
767 (defun %packed-info-insert (input aux-key info-number value)
768 (declare (simple-vector input) (type info-number info-number))
769 (let* ((n-extra-elts
770 ;; Test if the aux-key has been seen before or needs to be added.
771 (if (and (not (eql aux-key +no-auxilliary-key+))
772 (not (info-find-aux-key/packed input aux-key)))
773 4 ; need space for [aux-key, length, type-num, value]
774 2)) ; only space for [type-num, value]
775 (old-size (compute-unpackified-info-size input))
776 (new-size (+ old-size n-extra-elts))
777 (new (make-array new-size)))
778 (declare (type index old-size new-size)
779 (truly-dynamic-extent new))
780 (unpackify-infos input new)
781 (flet ((insert-at (point v0 v1)
782 (unless (eql point old-size) ; slide right
783 (replace new new :start1 (+ point n-extra-elts) :start2 point))
784 (setf (svref new point) v0
785 (svref new (+ point 1)) v1)))
786 (cond ((= n-extra-elts 4)
787 ;; creating a new aux key. SETF immediately follows the data
788 ;; for the primary Name. All other aux-keys go to the end.
789 (let ((point (if (eq aux-key 'setf) (svref new 0) old-size)))
790 (insert-at point aux-key 3) ; = add 3 data cells not incl. aux-key
791 (setf (svref new (+ point 2)) info-number
792 (svref new (+ point 3)) value)))
794 (let ((data-start (info-find-aux-key/unpacked
795 aux-key new old-size)))
796 ;; it had better be found - it was in the packed vector
797 (aver data-start)
798 ;; fdefn must be the first piece of info for any name.
799 ;; This facilitates implementing SYMBOL-FUNCTION without
800 ;; without completely decoding the vector.
801 (insert-at (+ data-start (if (eql info-number +fdefn-info-num+)
802 1 (svref new data-start)))
803 info-number value)
804 ;; add 2 cells, and verify that re-packing won't
805 ;; overflow the 'count' for this info group.
806 (aver (typep (ash (incf (svref new data-start) 2) -1)
807 'info-number))))))
808 (packify-infos new)))
810 ;; Return T if INFO-VECTOR admits quicker insertion logic - it must have
811 ;; exactly one descriptor for the root name, space for >= 1 more field,
812 ;; and no aux-keys.
813 (declaim (inline info-quickly-insertable-p))
814 (defun info-quickly-insertable-p (input)
815 (let ((n-infos (packed-info-field input 0 0)))
816 ;; We can easily determine if the no-aux-keys constraint is satisfied,
817 ;; because a secondary name's info occupies at least two cells,
818 ;; one for its aux-key and >= 1 for info values.
819 (and (< n-infos (1- +infos-per-word+))
820 (eql n-infos (1- (length input))))))
822 ;; Take a packed info-vector INPUT and return a new one with INFO-NUMBER/VALUE
823 ;; added for the root name. The vector must satisfy INFO-QUICKLY-INSERTABLE-P.
824 ;; This code is separate from PACKED-INFO-INSERT to facilitate writing
825 ;; a unit test of this logic against the complete logic.
827 (defun quick-packed-info-insert (input info-number value)
828 ;; Because INPUT contains 1 descriptor and its corresponding values,
829 ;; the current length is exactly NEW-N, the new number of fields.
830 (let* ((descriptor (svref input 0))
831 (new-n (truly-the info-number (length input)))
832 (new-vect (make-array (1+ new-n))))
833 ;; Two cases: we're either inserting info for the fdefn, or not.
834 (cond ((eq info-number +fdefn-info-num+)
835 ;; fdefn, if present, must remain the first packed field.
836 ;; Replace the lowest field (the count) with +fdefn-info-num+,
837 ;; shift everything left 6 bits, then OR in the new count.
838 (setf (svref new-vect 0)
839 (logior (make-info-descriptor
840 (dpb +fdefn-info-num+ (byte info-number-bits 0)
841 descriptor) info-number-bits) new-n)
842 ;; Packed vectors are indexed "backwards". The first
843 ;; field's info is in the highest numbered cell.
844 (svref new-vect new-n) value)
845 (loop for i from 1 below new-n
846 do (setf (svref new-vect i) (svref input i))))
848 ;; Add a field on the high end and increment the count.
849 (setf (svref new-vect 0)
850 (logior (make-info-descriptor
851 info-number (* info-number-bits new-n))
852 (1+ descriptor))
853 (svref new-vect 1) value)
854 ;; Slide the old data up 1 cell.
855 (loop for i from 2 to new-n
856 do (setf (svref new-vect i) (svref input (1- i))))))
857 new-vect))
859 (declaim (maybe-inline packed-info-insert))
860 (defun packed-info-insert (vector aux-key info-number newval)
861 (if (and (eql aux-key +no-auxilliary-key+)
862 (info-quickly-insertable-p vector))
863 (quick-packed-info-insert vector info-number newval)
864 (%packed-info-insert vector aux-key info-number newval)))
866 ;; Search packed VECTOR for AUX-KEY and INFO-NUMBER, returning
867 ;; the index of the data if found, or NIL if not found.
869 (declaim (ftype (function (simple-vector (or (eql 0) symbol) info-number)
870 (or null index))
871 packed-info-value-index))
873 (defun packed-info-value-index (vector aux-key type-num)
874 (declare (optimize (safety 0))) ; vector bounds are AVERed
875 (let ((data-idx (length vector)) (descriptor-idx 0) (field-idx 0))
876 (declare (type index descriptor-idx)
877 (type (mod #.+infos-per-word+) field-idx))
878 (unless (eql aux-key +no-auxilliary-key+)
879 (multiple-value-setq (data-idx descriptor-idx field-idx)
880 (info-find-aux-key/packed vector aux-key))
881 (unless data-idx
882 (return-from packed-info-value-index nil)))
883 ;; Fetch a descriptor and shift out trailing bits that won't be scanned.
884 (let* ((descriptor (ash (the info-descriptor (aref vector descriptor-idx))
885 (* (- info-number-bits) field-idx)))
886 (n-infos (logand descriptor info-num-mask))
887 ;; Compute n things in this descriptor after extracting one field. e.g.
888 ;; if starting index = 2, there's space for 7 more fields in 60 bits.
889 (swath (min (- +infos-per-word+ field-idx 1) n-infos)))
890 ;; Type inference on n-infos deems it to have no lower bound due to DECF.
891 (declare (type info-descriptor descriptor)
892 (type (unsigned-byte #.info-number-bits) n-infos)
893 (type index data-idx))
894 ;; Repeatedly shift and mask, which is quicker than extracting a field at
895 ;; varying positions. Start by shifting out the n-infos field.
896 (setq descriptor (ash descriptor (- info-number-bits)))
897 (loop
898 (dotimes (j swath)
899 (when (eql type-num (logand descriptor info-num-mask))
900 (return-from packed-info-value-index
901 (the index (- data-idx j 1))))
902 (setq descriptor (ash descriptor (- info-number-bits))))
903 (when (zerop (decf n-infos swath))
904 (return nil))
905 (incf descriptor-idx)
906 (decf data-idx swath)
907 (aver (< descriptor-idx data-idx))
908 (setq descriptor (svref vector descriptor-idx)
909 swath (min n-infos +infos-per-word+))))))
911 ;; Helper for CLEAR-INFO-VALUES when Name has the efficient form.
912 ;; Given packed info-vector INPUT and auxilliary key KEY2
913 ;; return a new vector in which TYPE-NUMS are absent.
914 ;; When none of TYPE-NUMs were present to begin with, return NIL.
916 ;; While this could determine whether it would do anything before unpacking,
917 ;; clearing does not happen often enough to warrant the pre-check.
919 (defun packed-info-remove (input key2 type-nums)
920 (declare (simple-vector input))
921 (when (or (eql (length input) (length +nil-packed-infos+))
922 (and (not (eql key2 +no-auxilliary-key+))
923 (not (info-find-aux-key/packed input key2))))
924 (return-from packed-info-remove nil)) ; do nothing
925 (let* ((end (compute-unpackified-info-size input))
926 (new (make-array end))
927 (data-start 0))
928 (declare (truly-dynamic-extent new) (type index end data-start))
929 (unpackify-infos input new)
930 (let ((start (info-find-aux-key/unpacked key2 new end)))
931 (aver start) ; must be found - it was in the packed vector
932 (setq data-start start)) ; point to the group's length cell
933 (dolist (type-num type-nums)
934 (declare (type info-number type-num))
935 (let ((i (loop for probe from (1+ data-start) by 2
936 repeat (ash (svref new data-start) -1) ; =n-entries
937 when (eql (svref new probe) type-num)
938 return probe)))
939 ;; N.B. the early termination checks aren't just optimizations,
940 ;; they're requirements, because otherwise the loop could smash
941 ;; data that does not belong to this auxilliary key.
942 (cond ((not i)) ; not found - ignore
943 ;; Squash out 2 cells if deleting an info for primary name,
944 ;; or for secondary name with at least one more entry.
945 ((or (eql data-start 0) (> (svref new data-start) 3))
946 (replace new new :start1 i :start2 (+ i 2))
947 (decf end 2)
948 (when (= (decf (svref new data-start) 2) 1)
949 ;; the group is now comprised solely of its length cell
950 (return))) ; so bail out
952 ;; Delete the sole entry for a secondary name
953 ;; by removing aux-key, length, and one entry (a cell pair).
954 (replace new new :start1 (- i 2) :start2 (+ i 2))
955 (decf end 4) ; shorten by 4 cells, and stop now
956 (return)))))
957 (let ((delta (- (length new) end)))
958 (cond ((zerop delta) nil)
959 ;; All empty info-vectors are equivalent, so if
960 ;; unpacked vector has no data, return a constant.
961 ((eql end 1) +nil-packed-infos+)
962 (t (packify-infos new end)))))) ; otherwise repack
964 ;; We need a few magic constants to be shared between the next two functions.
965 (defconstant-eqx !+pcl-reader-name+ (make-symbol "READER") (constantly t))
966 (defconstant-eqx !+pcl-writer-name+ (make-symbol "WRITER") (constantly t))
967 (defconstant-eqx !+pcl-boundp-name+ (make-symbol "BOUNDP") (constantly t))
969 ;; PCL names are physically 4-lists (see "pcl/slot-name")
970 ;; that get treated as 2-component names for globaldb's purposes.
971 ;; Return the kind of PCL slot accessor name that NAME is, if it is one.
972 ;; i.e. it matches (SLOT-ACCESSOR :GLOBAL <sym> READER|WRITER|BOUNDP)
973 ;; When called, NAME is already known to start with 'SLOT-ACCESSOR.
974 ;; This has to be defined before building PCL.
975 (defun pcl-global-accessor-name-p (name)
976 (let* ((cdr (cdr name)) (tail (cdr cdr)) last
977 kind)
978 (if (and (eq (car cdr) :global)
979 (listp tail)
980 (symbolp (car tail))
981 (listp (setq last (cdr tail)))
982 (not (cdr last))
983 ;; Return symbols that can't conflict, in case somebody
984 ;; legitimates (BOUNDP <f>) via DEFINE-FUNCTION-NAME-SYNTAX.
985 ;; Especially important since BOUNDP is an external of CL.
986 (setq kind (case (car last)
987 (sb!pcl::reader !+pcl-reader-name+)
988 (sb!pcl::writer !+pcl-writer-name+)
989 (sb!pcl::boundp !+pcl-boundp-name+))))
990 ;; The first return value is what matters to WITH-GLOBALDB-NAME
991 ;; for deciding whether the name is "simple".
992 ;; Return the KIND first, just in case somehow we end up with
993 ;; (SLOT-ACCESSOR :GLOBAL NIL WRITER) as a name.
994 ;; [It "can't happen" since NIL is a constant though]
995 (values kind (car tail))
996 (values nil nil))))
998 ;; Construct a name from its parts.
999 ;; For PCL global accessors, produce the real name, not the 2-part name.
1000 ;; This operation is not invoked in normal use of globaldb.
1001 ;; It is only for mapping over all names.
1002 (defun construct-globaldb-name (aux-symbol stem)
1003 (cond ((eq aux-symbol !+pcl-reader-name+) (sb!pcl::slot-reader-name stem))
1004 ((eq aux-symbol !+pcl-writer-name+) (sb!pcl::slot-writer-name stem))
1005 ((eq aux-symbol !+pcl-boundp-name+) (sb!pcl::slot-boundp-name stem))
1006 (t (list aux-symbol stem)))) ; something like (SETF frob)
1008 ;; Call FUNCTION with each piece of info in packed VECT using ROOT-SYMBOL
1009 ;; as the primary name. FUNCTION must accept 3 values (NAME INFO-NUMBER VALUE).
1010 (defun %call-with-each-info (function vect root-symbol)
1011 (let ((name root-symbol)
1012 (data-idx (length vect)))
1013 (declare (type index data-idx))
1014 (!with-packed-info-iterator (next-field vect :descriptor-index desc-idx)
1015 (loop ; over name
1016 (dotimes (i (next-field)) ; number of infos for this name
1017 (funcall function name (next-field) (svref vect (decf data-idx))))
1018 (if (< desc-idx (decf data-idx))
1019 (setq name
1020 (construct-globaldb-name (svref vect data-idx) root-symbol))
1021 (return))))))
1024 Info packing example. This example has 2 auxilliary-keys: SETF and CAS.
1026 (!test-packify-infos '(13 :XYZ 18 "nine" 28 :BAR 7 T)
1027 '(SETF 8 NIL 17 :FGX)
1028 '(CAS 6 :MUMBLE 2 :BAZ 47 :FOO))
1030 #(109006134805865284 3010 :FOO :BAZ :MUMBLE CAS :FGX NIL SETF T :BAR "nine" :XYZ)
1032 (format nil "~4,'0o ~20,'0o" 3010 109006134805865284)
1033 => "5702 06032110020734221504"
1034 Reading from right-to-left, converting each 2-digit octal number to decimal:
1035 4, 13, 18, 28, 7, 2, 8, 17, 3, 6, 2, 47
1036 Which is interpreted as:
1037 4 infos for the root name. type numbers: 13, 18, 28, 7
1038 2 infos for SETF auxilliary-key. type numbers: 8, 17
1039 3 infos for CAS auxilliary-key. type numbers: 6, 2, 47
1041 (unpackify-infos (!test-packify-infos ...)) ; same input
1042 => #(9 13 :XYZ 18 "nine" 28 :BAR 7 T
1043 SETF 5 8 NIL 17 :FGX
1044 CAS 7 6 :MUMBLE 2 :BAZ 47 :FOO)
1045 This is interpreted as
1046 root name, 9 cells: {13->:XYZ, 18->"nine", 28->:BAR, 7->T}
1047 SETF, 5 cells: {8->NIL, 17->:FGX}
1048 CAS, 7 cells: {6->:MUMBLE, 2->:BAZ, 47->:FOO}
1051 ;; Reshape inputs per the above commented example to a packed vector.
1052 ;; The info for a symbol's fdefn must precede other info-numbers.
1053 ;; and SETF must be the first aux key if other aux keys are present.
1054 ;; The test function does not enforce these invariants.
1055 ;; N.B. As this function starts with "!", is is omitted from the target image.
1056 (defun !test-packify-infos (&rest lists)
1057 (flet ((check (plist)
1058 (and (evenp (length plist))
1059 (loop for (indicator value) on plist by #'cddr
1060 always (typep indicator 'info-number))))
1061 (add-length-prefix (list) ; computers count better than people
1062 (cons (1+ (length list)) list)))
1063 (unless (and (check (first lists))
1064 (every (lambda (list)
1065 (and (symbolp (car list)) (check (cdr list))))
1066 (rest lists)))
1067 (error "Malformed info entries"))
1068 (packify-infos
1069 (coerce (apply #'append
1070 (cons (add-length-prefix (first lists))
1071 (mapcar (lambda (more)
1072 (cons (car more)
1073 (add-length-prefix (cdr more))))
1074 (rest lists))))
1075 'vector))))
1077 ;; Given a NAME naming a globaldb object, decide whether the NAME has
1078 ;; an efficient or "simple" form, versus a general or "hairy" form.
1079 ;; The efficient form is either a symbol, a (CONS SYMBOL (CONS SYMBOL NULL)),
1080 ;; or a PCL global slot {reader, writer, boundp} function name.
1082 ;; If NAME is "simple", bind KEY2 and KEY1 to the elements
1083 ;; in that order, and execute the SIMPLE code, otherwise execute the HAIRY code.
1084 ;; If ALLOW-ATOM is T - the default - then NAME can be just a symbol
1085 ;; in which case its second component is +NO-AUXILLIARY-KEY+.
1087 (defmacro with-globaldb-name ((key1 key2 &optional (allow-atom t))
1088 name &key simple hairy)
1089 (with-unique-names (rest)
1090 `(let ((,key1 ,name) (,key2 +NO-AUXILLIARY-KEY+))
1091 (if (or ,@(if allow-atom `((symbolp ,key1)))
1092 (if (listp ,key1)
1093 (let ((,rest (cdr ,key1)))
1094 (when (listp ,rest)
1095 (cond ((not (cdr ,rest))
1096 (setq ,key2 (car ,key1) ,key1 (car ,rest))
1097 (and (symbolp ,key1) (symbolp ,key2) ,rest))
1098 ((eq (car ,key1) 'sb!pcl::slot-accessor)
1099 (multiple-value-setq (,key2 ,key1)
1100 (pcl-global-accessor-name-p ,key1))))))))
1101 ,simple
1102 ;; The KEYs remain bound, but they should not be used for anything.
1103 ,hairy))))
1105 ;; Given Info-Vector VECT, return the fdefn that it contains for its root name,
1106 ;; or nil if there is no value. NIL input is acceptable and will return NIL.
1107 (declaim (inline info-vector-fdefn))
1108 (defun info-vector-fdefn (vect)
1109 (when vect
1110 ;; This is safe: Info-Vector invariant requires that it have length >= 1.
1111 (let ((word (the fixnum (svref vect 0))))
1112 ;; Test that the first info-number is +fdefn-info-num+ and its n-infos
1113 ;; field is nonzero. These conditions can be tested simultaneously
1114 ;; using a SIMD-in-a-register idea. The low 6 bits must be nonzero
1115 ;; and the next 6 must be exactly #b111111, so considered together
1116 ;; as a 12-bit unsigned integer it must be >= #b111111000001
1117 (when (>= (ldb (byte (* info-number-bits 2) 0) word)
1118 (1+ (ash +fdefn-info-num+ info-number-bits)))
1119 ;; DATA-REF-WITH-OFFSET doesn't know the info-vector length invariant,
1120 ;; so depite (safety 0) eliding bounds check, FOLD-INDEX-ADDRESSING
1121 ;; wasn't kicking in without (TRULY-THE (INTEGER 1 *)).
1122 (aref vect (1- (truly-the (integer 1 *) (length vect))))))))
1124 ;;; Some of this stuff might belong in 'symbol.lisp', but can't be,
1125 ;;; because 'symbol.lisp' is :NOT-HOST in build-order.
1127 #+sb-xc-host
1128 ;; SYMBOL-INFO is a primitive object accessor defined in 'objdef.lisp'
1129 ;; and UPDATE-SYMBOL-INFO is defined in 'symbol.lisp'.
1130 ;; But in the host Lisp, there is no such thing as a symbol-info slot,
1131 ;; even if the host is SBCL. Instead, symbol-info is kept in the symbol-plist.
1132 (macrolet ((get-it () '(get symbol :sb-xc-globaldb-info)))
1133 (defun symbol-info (symbol) (get-it))
1134 (defun update-symbol-info (symbol update-fn)
1135 ;; Never pass NIL to an update-fn. Pass the minimal info-vector instead,
1136 ;; a vector describing 0 infos and 0 auxilliary keys.
1137 (let ((newval (funcall update-fn (or (get-it) +nil-packed-infos+))))
1138 (when newval
1139 (setf (get-it) newval))
1140 (values))))
1142 ;; Return the globaldb info for SYMBOL. With respect to the state diagram
1143 ;; presented at the definition of SYMBOL-PLIST, if the object in SYMBOL's
1144 ;; info slot is LISTP, it is in state 1 or 3. Either way, take the CDR.
1145 ;; Otherwise, it is in state 2 so return the value as-is.
1146 ;; In terms of this function being named "-vector", implying always a vector,
1147 ;; it is understood that NIL is a proxy for +NIL-PACKED-INFOS+, a vector.
1149 #!-symbol-info-vops (declaim (inline symbol-info-vector))
1150 (defun symbol-info-vector (symbol)
1151 (let ((info-holder (symbol-info symbol)))
1152 (truly-the (or null simple-vector)
1153 (if (listp info-holder) (cdr info-holder) info-holder))))
1155 ;;; The current *INFO-ENVIRONMENT*, a structure of type INFO-HASHTABLE.
1156 (declaim (type info-hashtable *info-environment*))
1157 (defvar *info-environment*)
1159 ;;; Update the INFO-NUMBER for NAME in the global environment,
1160 ;;; setting it to NEW-VALUE. This is thread-safe in the presence
1161 ;;; of multiple readers/writers. Threads simultaneously writing data
1162 ;;; for the same NAME will succeed if the info type numbers differ,
1163 ;;; and the winner is indeterminate if the type numbers are the same.
1165 ;;; It is not usually a good idea to think of globaldb as an arbitrary
1166 ;;; key-to-value map supporting rapid or frequent update for a key.
1167 ;;; This is because each update must shallow-copy any data that existed
1168 ;;; for NAME, as a consequence of the very minimal lockfree protocol.
1170 ;;; If, for example, you wanted to track how many times a full-call to
1171 ;;; each global function was emitted during compilation, you could create
1172 ;;; an info-type (:function :full-calls) and the value of that info-type
1173 ;;; could be a cons cell holding an integer. In this way incrementing
1174 ;;; the cell contents does not affecting the globaldb. In contrast,
1175 ;;; (INCF (INFO :function :full-calls myname)) would perform poorly.
1177 ;;; See also ATOMIC-SET-INFO-VALUE and GET-INFO-VALUE-INITIALIZING
1178 ;;; for atomic read/modify/write operations.
1180 ;;; Return the new value so that this can be conveniently used in a
1181 ;;; SETF function.
1182 (defun set-info-value (name info-number new-value)
1183 (when (typep name 'fixnum)
1184 (error "~D is not a legal INFO name." name))
1185 (let ((name (uncross name)))
1186 ;; If the INFO-NUMBER already exists in VECT, then copy it and
1187 ;; alter one cell; otherwise unpack it, grow the vector, and repack.
1188 (dx-flet ((augment (vect aux-key) ; VECT is a packed vector, never NIL
1189 (declare (simple-vector vect))
1190 (let ((index
1191 (packed-info-value-index vect aux-key info-number)))
1192 (if (not index)
1193 (packed-info-insert vect aux-key info-number new-value)
1194 (let ((copy (copy-seq vect)))
1195 (setf (svref copy index) new-value)
1196 copy)))))
1197 (with-globaldb-name (key1 key2) name
1198 :simple
1199 ;; UPDATE-SYMBOL-INFO never supplies OLD-INFO as NIL.
1200 (dx-flet ((simple-name (old-info) (augment old-info key2)))
1201 (update-symbol-info key1 #'simple-name))
1202 :hairy
1203 ;; INFO-PUTHASH supplies NIL for OLD-INFO if NAME was absent.
1204 (dx-flet ((hairy-name (old-info)
1205 (augment (or old-info +nil-packed-infos+)
1206 +no-auxilliary-key+)))
1207 (info-puthash *info-environment* name #'hairy-name)))))
1208 new-value)
1210 ;; Instead of accepting a new-value, call NEW-VALUE-FUN to compute it
1211 ;; from the existing value. The function receives two arguments:
1212 ;; if there was already a value, that value and T; otherwise two NILs.
1213 ;; Return the newly-computed value. If NEW-VALUE-FUN returns the old value
1214 ;; (compared by EQ) when there was one, then no globaldb update is made.
1215 (defun %atomic-set-info-value (name info-number new-value-fun)
1216 (declare (function new-value-fun))
1217 (when (typep name 'fixnum)
1218 (error "~D is not a legal INFO name." name))
1219 (let ((name (uncross name)) new-value)
1220 (dx-flet ((augment (vect aux-key) ; VECT is a packed vector, never NIL
1221 (declare (simple-vector vect))
1222 (let ((index
1223 (packed-info-value-index vect aux-key info-number)))
1224 (if (not index)
1225 (packed-info-insert
1226 vect aux-key info-number
1227 (setq new-value (funcall new-value-fun nil nil)))
1228 (let ((oldval (svref vect index)))
1229 (setq new-value (funcall new-value-fun oldval t))
1230 (if (eq new-value oldval)
1231 vect ; return the old vector
1232 (let ((copy (copy-seq vect)))
1233 (setf (svref copy index) new-value)
1234 copy)))))))
1235 (with-globaldb-name (key1 key2) name
1236 :simple
1237 ;; UPDATE-SYMBOL-INFO never supplies OLD-INFO as NIL.
1238 (dx-flet ((simple-name (old-info) (augment old-info key2)))
1239 (update-symbol-info key1 #'simple-name))
1240 :hairy
1241 ;; INFO-PUTHASH supplies NIL for OLD-INFO if NAME was absent.
1242 (dx-flet ((hairy-name (old-info)
1243 (augment (or old-info +nil-packed-infos+)
1244 +no-auxilliary-key+)))
1245 (info-puthash *info-environment* name #'hairy-name))))
1246 new-value))
1248 ;; %GET-INFO-VALUE-INITIALIZING is provided as a low-level operation similar
1249 ;; to the above because it does not require info metadata for defaulting,
1250 ;; nor deal with the keyword-based info type designators at all.
1251 ;; In contrast, GET-INFO-VALUE requires metadata.
1252 ;; For this operation to make sense, the objects produced should be permanently
1253 ;; assigned to their name, such as are fdefns and classoid-cells.
1254 ;; Note also that we do not do an initial attempt to read once with INFO,
1255 ;; followed up by a double-checking get-or-set operation. It is assumed that
1256 ;; the user of this already did an initial check, if such is warranted.
1257 (defun %get-info-value-initializing (name info-number creation-thunk)
1258 (when (typep name 'fixnum)
1259 (error "~D is not a legal INFO name." name))
1260 (let ((name (uncross name))
1261 result)
1262 (dx-flet ((get-or-set (info-vect aux-key)
1263 (let ((index
1264 (packed-info-value-index info-vect aux-key info-number)))
1265 (cond (index
1266 (setq result (svref info-vect index))
1267 nil) ; no update to info-vector
1269 ;; Update conflicts possibly for unrelated info-number
1270 ;; can force re-execution. (UNLESS result ...) tries
1271 ;; to avoid calling the thunk more than once.
1272 (unless result
1273 (setq result (funcall creation-thunk)))
1274 (packed-info-insert info-vect aux-key info-number
1275 result))))))
1276 (with-globaldb-name (key1 key2) name
1277 :simple
1278 ;; UPDATE-SYMBOL-INFO never supplies OLD-INFO as NIL.
1279 (dx-flet ((simple-name (old-info) (get-or-set old-info key2)))
1280 (update-symbol-info key1 #'simple-name))
1281 :hairy
1282 ;; INFO-PUTHASH supplies NIL for OLD-INFO if NAME was absent.
1283 (dx-flet ((hairy-name (old-info)
1284 (or (get-or-set (or old-info +nil-packed-infos+)
1285 +no-auxilliary-key+)
1286 ;; Return OLD-INFO to elide writeback. Unlike for
1287 ;; UPDATE-SYMBOL-INFO, NIL is not a no-op marker.
1288 old-info)))
1289 (info-puthash *info-environment* name #'hairy-name))))
1290 result))