0.9.15.41: preparation for weak hash tables
[sbcl.git] / src / code / target-hash-table.lisp
1 ;;;; that part of the implementation of HASH-TABLE which lives solely
2 ;;;; on the target system, not on the cross-compilation host
3
4 ;;;; This software is part of the SBCL system. See the README file for
5 ;;;; more information.
6 ;;;;
7 ;;;; This software is derived from the CMU CL system, which was
8 ;;;; written at Carnegie Mellon University and released into the
9 ;;;; public domain. The software is in the public domain and is
10 ;;;; provided with absolutely no warranty. See the COPYING and CREDITS
11 ;;;; files for more information.
12
13 (in-package "SB!IMPL")
14 \f
15 ;;;; utilities
16
17 ;; This stuff is performance critical and unwind-protect is too
18 ;; slow. And without the locking the next vector can get cyclic
19 ;; causing looping in a WITHOUT-GCING form, SHRINK-VECTOR can corrupt
20 ;; memory and who knows what else.
21 (defmacro with-spinlock-and-without-gcing ((spinlock) &body body)
22   #!-sb-thread
23   (declare (ignore spinlock))
24   (with-unique-names (old-gc-inhibit)
25     `(let ((,old-gc-inhibit *gc-inhibit*)
26            (*gc-inhibit* t))
27        (unwind-protect
28             (progn
29               #!+sb-thread
30               (sb!thread::get-spinlock ,spinlock)
31               ,@body)
32          #!+sb-thread
33          (sb!thread::release-spinlock ,spinlock)
34          (let ((*gc-inhibit* ,old-gc-inhibit))
35            ;; the test is racy, but it can err only on the overeager side
36            (sb!kernel::maybe-handle-pending-gc))))))
37
38 (eval-when (:compile-toplevel :load-toplevel :execute)
39   (defconstant max-hash sb!xc:most-positive-fixnum))
40
41 (deftype hash ()
42   `(integer 0 ,max-hash))
43
44 ;;; FIXME: Does this always make a nonnegative FIXNUM? If so, then
45 ;;; explain why. If not (or if the reason it always makes a
46 ;;; nonnegative FIXNUM is only the accident that pointers in supported
47 ;;; architectures happen to be in the lower half of the address
48 ;;; space), then fix it.
49 #!-sb-fluid (declaim (inline pointer-hash))
50 (defun pointer-hash (key)
51   (declare (values hash))
52   (truly-the hash (%primitive sb!c:make-fixnum key)))
53
54 #!-sb-fluid (declaim (inline eq-hash))
55 (defun eq-hash (key)
56   (declare (values hash (member t nil)))
57   (values (pointer-hash key)
58           (oddp (get-lisp-obj-address key))))
59
60 #!-sb-fluid (declaim (inline equal-hash))
61 (defun equal-hash (key)
62   (declare (values hash (member t nil)))
63   (values (sxhash key) nil))
64
65 #!-sb-fluid (declaim (inline eql-hash))
66 (defun eql-hash (key)
67   (declare (values hash (member t nil)))
68   (if (numberp key)
69       (equal-hash key)
70       (eq-hash key)))
71
72 (defun equalp-hash (key)
73   (declare (values hash (member t nil)))
74   (values (psxhash key) nil))
75
76 (defun almost-primify (num)
77   (declare (type index num))
78   #!+sb-doc
79   "Return an almost prime number greater than or equal to NUM."
80   (if (= (rem num 2) 0)
81       (setq num (+ 1 num)))
82   (if (= (rem num 3) 0)
83       (setq num (+ 2 num)))
84   (if (= (rem num 7) 0)
85       (setq num (+ 4 num)))
86   num)
87 \f
88 ;;;; user-defined hash table tests
89
90 (defvar *hash-table-tests* nil)
91
92 (defun define-hash-table-test (name test-fun hash-fun)
93   #!+sb-doc
94   "Define a new kind of hash table test."
95   (declare (type symbol name)
96            (type function test-fun hash-fun))
97   (setf *hash-table-tests*
98         (cons (list name test-fun hash-fun)
99               (remove name *hash-table-tests* :test #'eq :key #'car)))
100   name)
101 \f
102 ;;;; construction and simple accessors
103
104 (defconstant +min-hash-table-size+ 16)
105 (defconstant +min-hash-table-rehash-threshold+ (float 1/16 1.0))
106
107 (defun make-hash-table (&key (test 'eql)
108                              (size +min-hash-table-size+)
109                              (rehash-size 1.5)
110                              (rehash-threshold 1)
111                              (weak-p nil))
112   #!+sb-doc
113   "Create and return a new hash table. The keywords are as follows:
114      :TEST -- Indicates what kind of test to use.
115      :SIZE -- A hint as to how many elements will be put in this hash
116        table.
117      :REHASH-SIZE -- Indicates how to expand the table when it fills up.
118        If an integer, add space for that many elements. If a floating
119        point number (which must be greater than 1.0), multiply the size
120        by that amount.
121      :REHASH-THRESHOLD -- Indicates how dense the table can become before
122        forcing a rehash. Can be any positive number <=1, with density
123        approaching zero as the threshold approaches 0. Density 1 means an
124        average of one entry per bucket.
125      :WEAK-P -- (This is an extension from CMU CL, not currently supported
126        in SBCL 0.6.6, but perhaps supported in a future version.) If T,
127        don't keep entries if the key would otherwise be garbage."
128   (declare (type (or function symbol) test))
129   (declare (type unsigned-byte size))
130   (when weak-p
131     (error "stub: unsupported WEAK-P option"))
132   (multiple-value-bind (test test-fun hash-fun)
133       (cond ((or (eq test #'eq) (eq test 'eq))
134              (values 'eq #'eq #'eq-hash))
135             ((or (eq test #'eql) (eq test 'eql))
136              (values 'eql #'eql #'eql-hash))
137             ((or (eq test #'equal) (eq test 'equal))
138              (values 'equal #'equal #'equal-hash))
139             ((or (eq test #'equalp) (eq test 'equalp))
140              (values 'equalp #'equalp #'equalp-hash))
141             (t
142              ;; FIXME: I'd like to remove *HASH-TABLE-TESTS* stuff.
143              ;; Failing that, I'd like to rename it to
144              ;; *USER-HASH-TABLE-TESTS*.
145              (dolist (info *hash-table-tests*
146                            (error "unknown :TEST for MAKE-HASH-TABLE: ~S"
147                                   test))
148                (destructuring-bind (test-name test-fun hash-fun) info
149                  (when (or (eq test test-name) (eq test test-fun))
150                    (return (values test-name test-fun hash-fun)))))))
151     (let* ((size (max +min-hash-table-size+
152                       (min size
153                            ;; SIZE is just a hint, so if the user asks
154                            ;; for a SIZE which'd be too big for us to
155                            ;; easily implement, we bump it down.
156                            (floor array-dimension-limit 1024))))
157            (rehash-size (if (integerp rehash-size)
158                             rehash-size
159                             (float rehash-size 1.0)))
160            ;; FIXME: Original REHASH-THRESHOLD default should be 1.0,
161            ;; not 1, to make it easier for the compiler to avoid
162            ;; boxing.
163            (rehash-threshold (max +min-hash-table-rehash-threshold+
164                                   (float rehash-threshold 1.0)))
165            (size+1 (1+ size))           ; The first element is not usable.
166            ;; KLUDGE: The most natural way of expressing the below is
167            ;; (round (/ (float size+1) rehash-threshold)), and indeed
168            ;; it was expressed like that until 0.7.0. However,
169            ;; MAKE-HASH-TABLE is called very early in cold-init, and
170            ;; the SPARC has no primitive instructions for rounding,
171            ;; but only for truncating; therefore, we fudge this issue
172            ;; a little. The other uses of truncate, below, similarly
173            ;; used to be round. -- CSR, 2002-10-01
174            ;;
175            ;; Note that this has not yet been audited for
176            ;; correctness. It just seems to work. -- CSR, 2002-11-02
177            (scaled-size (truncate (/ (float size+1) rehash-threshold)))
178            (length (almost-primify (max scaled-size
179                                         (1+ +min-hash-table-size+))))
180            (index-vector (make-array length
181                                      :element-type
182                                      '(unsigned-byte #.sb!vm:n-word-bits)
183                                      :initial-element 0))
184            ;; needs to be the same length as the KV vector
185            ;; (FIXME: really?  why doesn't the code agree?)
186            (next-vector (make-array size+1
187                                     :element-type
188                                     '(unsigned-byte #.sb!vm:n-word-bits)))
189            (kv-vector (make-array (* 2 size+1)
190                                   :initial-element +empty-ht-slot+))
191            (table (%make-hash-table
192                    :test test
193                    :test-fun test-fun
194                    :hash-fun hash-fun
195                    :rehash-size rehash-size
196                    :rehash-threshold rehash-threshold
197                    :rehash-trigger size
198                    :table kv-vector
199                    :weak-p weak-p
200                    :index-vector index-vector
201                    :next-vector next-vector
202                    :hash-vector
203                    (unless (eq test 'eq)
204                      (make-array size+1
205                                  :element-type '(unsigned-byte
206                                                  #.sb!vm:n-word-bits)
207                                  :initial-element +magic-hash-vector-value+))
208                    :spinlock (sb!thread::make-spinlock))))
209       (declare (type index size+1 scaled-size length))
210       ;; Set up the free list, all free. These lists are 0 terminated.
211       (do ((i 1 (1+ i)))
212           ((>= i size))
213         (setf (aref next-vector i) (1+ i)))
214       (setf (aref next-vector size) 0)
215       (setf (hash-table-next-free-kv table) 1)
216       (setf (hash-table-needing-rehash table) 0)
217       (setf (aref kv-vector 0) table)
218       table)))
219
220 (defun hash-table-count (hash-table)
221   #!+sb-doc
222   "Return the number of entries in the given HASH-TABLE."
223   (declare (type hash-table hash-table)
224            (values index))
225   (hash-table-number-entries hash-table))
226
227 #!+sb-doc
228 (setf (fdocumentation 'hash-table-rehash-size 'function)
229       "Return the rehash-size HASH-TABLE was created with.")
230
231 #!+sb-doc
232 (setf (fdocumentation 'hash-table-rehash-threshold 'function)
233       "Return the rehash-threshold HASH-TABLE was created with.")
234
235 (defun hash-table-size (hash-table)
236   #!+sb-doc
237   "Return a size that can be used with MAKE-HASH-TABLE to create a hash
238    table that can hold however many entries HASH-TABLE can hold without
239    having to be grown."
240   (hash-table-rehash-trigger hash-table))
241
242 #!+sb-doc
243 (setf (fdocumentation 'hash-table-test 'function)
244       "Return the test HASH-TABLE was created with.")
245
246 #!+sb-doc
247 (setf (fdocumentation 'hash-table-weak-p 'function)
248       "Return T if HASH-TABLE will not keep entries for keys that would
249    otherwise be garbage, and NIL if it will.")
250 \f
251 ;;;; accessing functions
252
253 ;;; Make new vectors for the table, extending the table based on the
254 ;;; rehash-size.
255 (defun rehash (table)
256   (declare (type hash-table table))
257   (let* ((old-kv-vector (hash-table-table table))
258          (old-next-vector (hash-table-next-vector table))
259          (old-hash-vector (hash-table-hash-vector table))
260          (old-size (length old-next-vector))
261          (new-size
262           (let ((rehash-size (hash-table-rehash-size table)))
263             (etypecase rehash-size
264               (fixnum
265                (+ rehash-size old-size))
266               (float
267                (the index (truncate (* rehash-size old-size)))))))
268          (new-kv-vector (make-array (* 2 new-size)
269                                     :initial-element +empty-ht-slot+))
270          (new-next-vector
271           (make-array new-size
272                       :element-type '(unsigned-byte #.sb!vm:n-word-bits)
273                       :initial-element 0))
274          (new-hash-vector
275           (when old-hash-vector
276             (make-array new-size
277                         :element-type '(unsigned-byte #.sb!vm:n-word-bits)
278                         :initial-element +magic-hash-vector-value+)))
279          (old-index-vector (hash-table-index-vector table))
280          (new-length (almost-primify
281                       (truncate (/ (float new-size)
282                                 (hash-table-rehash-threshold table)))))
283          (new-index-vector
284           (make-array new-length
285                       :element-type '(unsigned-byte #.sb!vm:n-word-bits)
286                       :initial-element 0)))
287     (declare (type index new-size new-length old-size))
288
289     ;; Disable GC tricks on the OLD-KV-VECTOR.
290     (set-header-data old-kv-vector sb!vm:vector-normal-subtype)
291
292     ;; FIXME: here and in several other places in the hash table code,
293     ;; loops like this one are used when FILL or REPLACE would be
294     ;; appropriate.  why are standard CL functions not used?
295     ;; Performance issues?  General laziness?  -- NJF, 2004-03-10
296
297     ;; Copy over the kv-vector. The element positions should not move
298     ;; in case there are active scans.
299     (dotimes (i (* old-size 2))
300       (declare (type index i))
301       (setf (aref new-kv-vector i) (aref old-kv-vector i)))
302
303     ;; Copy over the hash-vector.
304     (when old-hash-vector
305       (dotimes (i old-size)
306         (setf (aref new-hash-vector i) (aref old-hash-vector i))))
307
308     (setf (hash-table-next-free-kv table) 0)
309     (setf (hash-table-needing-rehash table) 0)
310     ;; Rehash all the entries; last to first so that after the pushes
311     ;; the chains are first to last.
312     (do ((i (1- new-size) (1- i)))
313         ((zerop i))
314       (let ((key (aref new-kv-vector (* 2 i)))
315             (value (aref new-kv-vector (1+ (* 2 i)))))
316         (cond ((and (eq key +empty-ht-slot+)
317                     (eq value +empty-ht-slot+))
318                ;; Slot is empty, push it onto the free list.
319                (setf (aref new-next-vector i)
320                      (hash-table-next-free-kv table))
321                (setf (hash-table-next-free-kv table) i))
322               ((and new-hash-vector
323                     (not (= (aref new-hash-vector i)
324                             +magic-hash-vector-value+)))
325                ;; Can use the existing hash value (not EQ based)
326                (let* ((hashing (aref new-hash-vector i))
327                       (index (rem hashing new-length))
328                       (next (aref new-index-vector index)))
329                  (declare (type index index)
330                           (type hash hashing))
331                  ;; Push this slot into the next chain.
332                  (setf (aref new-next-vector i) next)
333                  (setf (aref new-index-vector index) i)))
334               (t
335                ;; EQ base hash.
336                ;; Enable GC tricks.
337                (set-header-data new-kv-vector
338                                 sb!vm:vector-valid-hashing-subtype)
339                (let* ((hashing (pointer-hash key))
340                       (index (rem hashing new-length))
341                       (next (aref new-index-vector index)))
342                  (declare (type index index)
343                           (type hash hashing))
344                  ;; Push this slot onto the next chain.
345                  (setf (aref new-next-vector i) next)
346                  (setf (aref new-index-vector index) i))))))
347     (setf (hash-table-table table) new-kv-vector)
348     (setf (hash-table-index-vector table) new-index-vector)
349     (setf (hash-table-next-vector table) new-next-vector)
350     (setf (hash-table-hash-vector table) new-hash-vector)
351     ;; Shrink the old vectors to 0 size to help the conservative GC.
352     (%shrink-vector old-kv-vector 0)
353     (%shrink-vector old-index-vector 0)
354     (%shrink-vector old-next-vector 0)
355     (when old-hash-vector
356       (%shrink-vector old-hash-vector 0))
357     (setf (hash-table-rehash-trigger table) new-size))
358   (values))
359
360 ;;; Use the same size as before, re-using the vectors.
361 (defun rehash-without-growing (table)
362   (declare (type hash-table table))
363   (let* ((kv-vector (hash-table-table table))
364          (next-vector (hash-table-next-vector table))
365          (hash-vector (hash-table-hash-vector table))
366          (size (length next-vector))
367          (index-vector (hash-table-index-vector table))
368          (length (length index-vector)))
369     (declare (type index size length))
370
371     ;; Disable GC tricks, they will be re-enabled during the re-hash
372     ;; if necesary.
373     (set-header-data kv-vector sb!vm:vector-normal-subtype)
374
375     ;; Rehash all the entries.
376     (setf (hash-table-next-free-kv table) 0)
377     (setf (hash-table-needing-rehash table) 0)
378     (dotimes (i size)
379       (setf (aref next-vector i) 0))
380     (dotimes (i length)
381       (setf (aref index-vector i) 0))
382     (do ((i (1- size) (1- i)))
383         ((zerop i))
384       (let ((key (aref kv-vector (* 2 i)))
385             (value (aref kv-vector (1+ (* 2 i)))))
386         (cond ((and (eq key +empty-ht-slot+)
387                     (eq value +empty-ht-slot+))
388                ;; Slot is empty, push it onto free list.
389                (setf (aref next-vector i) (hash-table-next-free-kv table))
390                (setf (hash-table-next-free-kv table) i))
391               ((and hash-vector (not (= (aref hash-vector i)
392                                         +magic-hash-vector-value+)))
393                ;; Can use the existing hash value (not EQ based)
394                (let* ((hashing (aref hash-vector i))
395                       (index (rem hashing length))
396                       (next (aref index-vector index)))
397                  (declare (type index index))
398                  ;; Push this slot into the next chain.
399                  (setf (aref next-vector i) next)
400                  (setf (aref index-vector index) i)))
401               (t
402                ;; EQ base hash.
403                ;; Enable GC tricks.
404                (set-header-data kv-vector sb!vm:vector-valid-hashing-subtype)
405                (let* ((hashing (pointer-hash key))
406                       (index (rem hashing length))
407                       (next (aref index-vector index)))
408                  (declare (type index index)
409                           (type hash hashing))
410                  ;; Push this slot into the next chain.
411                  (setf (aref next-vector i) next)
412                  (setf (aref index-vector index) i)))))))
413   (values))
414
415 (defun flush-needing-rehash (table)
416   (let* ((kv-vector (hash-table-table table))
417          (index-vector (hash-table-index-vector table))
418          (next-vector (hash-table-next-vector table))
419          (length (length index-vector)))
420     (do ((next (hash-table-needing-rehash table)))
421         ((zerop next))
422       (declare (type index next))
423       (let* ((key (aref kv-vector (* 2 next)))
424              (hashing (pointer-hash key))
425              (index (rem hashing length))
426              (temp (aref next-vector next)))
427         (setf (aref next-vector next) (aref index-vector index))
428         (setf (aref index-vector index) next)
429         (setf next temp))))
430   (setf (hash-table-needing-rehash table) 0)
431   (values))
432
433 (defun gethash (key hash-table &optional default)
434   #!+sb-doc
435   "Finds the entry in HASH-TABLE whose key is KEY and returns the associated
436    value and T as multiple values, or returns DEFAULT and NIL if there is no
437    such entry. Entries can be added using SETF."
438   (declare (type hash-table hash-table)
439            (values t (member t nil)))
440   (gethash3 key hash-table default))
441
442 (defun gethash2 (key hash-table)
443   #!+sb-doc
444   "Two argument version of GETHASH"
445   (declare (type hash-table hash-table)
446            (values t (member t nil)))
447   (gethash3 key hash-table nil))
448
449 (defun gethash3 (key hash-table default)
450   #!+sb-doc
451   "Three argument version of GETHASH"
452   (declare (type hash-table hash-table)
453            (values t (member t nil)))
454   (with-spinlock-and-without-gcing ((hash-table-spinlock hash-table))
455    (cond ((= (get-header-data (hash-table-table hash-table))
456              sb!vm:vector-must-rehash-subtype)
457           (rehash-without-growing hash-table))
458          ((not (zerop (hash-table-needing-rehash hash-table)))
459           (flush-needing-rehash hash-table)))
460
461    ;; First check the cache.  Use EQ here for speed.
462    (let ((cache (hash-table-cache hash-table))
463          (table (hash-table-table hash-table)))
464
465      (if (and cache (< cache (length table)) (eq (aref table cache) key))
466          (values (aref table (1+ cache)) t)
467
468        ;; Search for key in the hash table.
469        (multiple-value-bind (hashing eq-based)
470            (funcall (hash-table-hash-fun hash-table) key)
471          (declare (type hash hashing))
472          (let* ((index-vector (hash-table-index-vector hash-table))
473                 (length (length index-vector))
474                 (index (rem hashing length))
475                 (next (aref index-vector index))
476                 (next-vector (hash-table-next-vector hash-table))
477                 (hash-vector (hash-table-hash-vector hash-table))
478                 (test-fun (hash-table-test-fun hash-table)))
479            (declare (type index index))
480            ;; Search next-vector chain for a matching key.
481            (if (or eq-based (not hash-vector))
482                (do ((next next (aref next-vector next)))
483                    ((zerop next) (values default nil))
484                  (declare (type index next))
485                  (when (eq key (aref table (* 2 next)))
486                    (setf (hash-table-cache hash-table) (* 2 next))
487                    (return (values (aref table (1+ (* 2 next))) t))))
488              (do ((next next (aref next-vector next)))
489                  ((zerop next) (values default nil))
490                (declare (type index next))
491                (when (and (= hashing (aref hash-vector next))
492                           (funcall test-fun key (aref table (* 2 next))))
493                  ;; Found.
494                  (setf (hash-table-cache hash-table) (* 2 next))
495                  (return (values (aref table (1+ (* 2 next))) t)))))))))))
496
497 ;;; so people can call #'(SETF GETHASH)
498 (defun (setf gethash) (new-value key table &optional default)
499   (declare (ignore default))
500   (%puthash key table new-value))
501
502 (defun %puthash (key hash-table value)
503   (declare (type hash-table hash-table))
504   (aver (hash-table-index-vector hash-table))
505   (with-spinlock-and-without-gcing ((hash-table-spinlock hash-table))
506    ;; We need to rehash here so that a current key can be found if it
507    ;; exists. Check that there is room for one more entry. May not be
508    ;; needed if the key is already present.
509    (cond ((zerop (hash-table-next-free-kv hash-table))
510           (rehash hash-table))
511          ((= (get-header-data (hash-table-table hash-table))
512              sb!vm:vector-must-rehash-subtype)
513           (rehash-without-growing hash-table))
514          ((not (zerop (hash-table-needing-rehash hash-table)))
515           (flush-needing-rehash hash-table)))
516
517    (let ((cache (hash-table-cache hash-table))
518          (kv-vector (hash-table-table hash-table)))
519
520      ;; Check the cache
521      (if (and cache (< cache (length kv-vector))
522               (eq (aref kv-vector cache) key))
523          ;; If cached, just store here
524          (setf (aref kv-vector (1+ cache)) value)
525
526        ;; Search for key in the hash table.
527        (multiple-value-bind (hashing eq-based)
528            (funcall (hash-table-hash-fun hash-table) key)
529          (declare (type hash hashing))
530          (let* ((index-vector (hash-table-index-vector hash-table))
531                 (length (length index-vector))
532                 (index (rem hashing length))
533                 (next (aref index-vector index))
534                 (kv-vector (hash-table-table hash-table))
535                 (next-vector (hash-table-next-vector hash-table))
536                 (hash-vector (hash-table-hash-vector hash-table))
537                 (test-fun (hash-table-test-fun hash-table)))
538            (declare (type index index))
539
540            (cond ((or eq-based (not hash-vector))
541                   (when eq-based
542                     (set-header-data kv-vector
543                                      sb!vm:vector-valid-hashing-subtype))
544
545                   ;; Search next-vector chain for a matching key.
546                   (do ((next next (aref next-vector next)))
547                       ((zerop next))
548                     (declare (type index next))
549                     (when (eq key (aref kv-vector (* 2 next)))
550                       ;; Found, just replace the value.
551                       (setf (hash-table-cache hash-table) (* 2 next))
552                       (setf (aref kv-vector (1+ (* 2 next))) value)
553                       (return-from %puthash value))))
554                  (t
555                   ;; Search next-vector chain for a matching key.
556                   (do ((next next (aref next-vector next)))
557                       ((zerop next))
558                     (declare (type index next))
559                     (when (and (= hashing (aref hash-vector next))
560                                (funcall test-fun key
561                                         (aref kv-vector (* 2 next))))
562                       ;; Found, just replace the value.
563                       (setf (hash-table-cache hash-table) (* 2 next))
564                       (setf (aref kv-vector (1+ (* 2 next))) value)
565                       (return-from %puthash value)))))
566
567            ;; Pop a KV slot off the free list
568            (let ((free-kv-slot (hash-table-next-free-kv hash-table)))
569              ;; Double-check for overflow.
570              (aver (not (zerop free-kv-slot)))
571              (setf (hash-table-next-free-kv hash-table)
572                    (aref next-vector free-kv-slot))
573              (incf (hash-table-number-entries hash-table))
574
575              (setf (hash-table-cache hash-table) (* 2 free-kv-slot))
576              (setf (aref kv-vector (* 2 free-kv-slot)) key)
577              (setf (aref kv-vector (1+ (* 2 free-kv-slot))) value)
578
579              ;; Setup the hash-vector if necessary.
580              (when hash-vector
581                (if (not eq-based)
582                    (setf (aref hash-vector free-kv-slot) hashing)
583                    (aver (= (aref hash-vector free-kv-slot)
584                             +magic-hash-vector-value+))))
585
586              ;; Push this slot into the next chain.
587              (setf (aref next-vector free-kv-slot) next)
588              (setf (aref index-vector index) free-kv-slot)))))))
589   value)
590
591 (defun remhash (key hash-table)
592   #!+sb-doc
593   "Remove the entry in HASH-TABLE associated with KEY. Return T if there
594    was such an entry, or NIL if not."
595   (declare (type hash-table hash-table)
596            (values (member t nil)))
597   (with-spinlock-and-without-gcing ((hash-table-spinlock hash-table))
598    ;; We need to rehash here so that a current key can be found if it
599    ;; exists.
600    (cond ((= (get-header-data (hash-table-table hash-table))
601              sb!vm:vector-must-rehash-subtype)
602           (rehash-without-growing hash-table))
603          ((not (zerop (hash-table-needing-rehash hash-table)))
604           (flush-needing-rehash hash-table)))
605
606    ;; For now, just clear the cache
607    (setf (hash-table-cache hash-table) nil)
608
609    ;; Search for key in the hash table.
610    (multiple-value-bind (hashing eq-based)
611        (funcall (hash-table-hash-fun hash-table) key)
612      (declare (type hash hashing))
613      (let* ((index-vector (hash-table-index-vector hash-table))
614             (length (length index-vector))
615             (index (rem hashing length))
616             (next (aref index-vector index))
617             (table (hash-table-table hash-table))
618             (next-vector (hash-table-next-vector hash-table))
619             (hash-vector (hash-table-hash-vector hash-table))
620             (test-fun (hash-table-test-fun hash-table)))
621        (declare (type index index next))
622        (flet ((clear-slot (chain-vector prior-slot-location slot-location)
623                 ;; Mark slot as empty.
624                 (setf (aref table (* 2 slot-location)) +empty-ht-slot+
625                       (aref table (1+ (* 2 slot-location))) +empty-ht-slot+)
626                 ;; Update the prior pointer in the chain to skip this.
627                 (setf (aref chain-vector prior-slot-location)
628                       (aref next-vector slot-location))
629                 ;; Push KV slot onto free chain.
630                 (setf (aref next-vector slot-location)
631                       (hash-table-next-free-kv hash-table))
632                 (setf (hash-table-next-free-kv hash-table) slot-location)
633                 (when hash-vector
634                   (setf (aref hash-vector slot-location)
635                         +magic-hash-vector-value+))
636                 (decf (hash-table-number-entries hash-table))
637                 t))
638          (cond ((zerop next)
639                 nil)
640                ((if (or eq-based (not hash-vector))
641                     (eq key (aref table (* 2 next)))
642                     (and (= hashing (aref hash-vector next))
643                          (funcall test-fun key (aref table (* 2 next)))))
644                 (clear-slot index-vector index next))
645                ;; Search next-vector chain for a matching key.
646                ((or eq-based (not hash-vector))
647                 ;; EQ based
648                 (do ((prior next next)
649                      (next (aref next-vector next) (aref next-vector next)))
650                     ((zerop next) nil)
651                   (declare (type index next))
652                   (when (eq key (aref table (* 2 next)))
653                     (return-from remhash (clear-slot next-vector prior next)))))
654                (t
655                 ;; not EQ based
656                 (do ((prior next next)
657                      (next (aref next-vector next) (aref next-vector next)))
658                     ((zerop next) nil)
659                   (declare (type index next))
660                   (when (and (= hashing (aref hash-vector next))
661                              (funcall test-fun key (aref table (* 2 next))))
662                     (return-from remhash
663                       (clear-slot next-vector prior next)))))))))))
664
665 (defun clrhash (hash-table)
666   #!+sb-doc
667   "This removes all the entries from HASH-TABLE and returns the hash table
668    itself."
669   (declare (optimize speed))
670   (with-spinlock-and-without-gcing ((hash-table-spinlock hash-table))
671     (let* ((kv-vector (hash-table-table hash-table))
672            (next-vector (hash-table-next-vector hash-table))
673            (hash-vector (hash-table-hash-vector hash-table))
674            (size (length next-vector))
675            (index-vector (hash-table-index-vector hash-table)))
676       ;; Disable GC tricks.
677       (set-header-data kv-vector sb!vm:vector-normal-subtype)
678       ;; Mark all slots as empty by setting all keys and values to magic
679       ;; tag.
680       (aver (eq (aref kv-vector 0) hash-table))
681       (fill kv-vector +empty-ht-slot+ :start 2)
682       ;; Set up the free list, all free.
683       (do ((i 1 (1+ i)))
684           ((>= i (1- size)))
685           (setf (aref next-vector i) (1+ i)))
686       (setf (aref next-vector (1- size)) 0)
687       (setf (hash-table-next-free-kv hash-table) 1)
688       (setf (hash-table-needing-rehash hash-table) 0)
689       ;; Clear the index-vector.
690       (fill index-vector 0)
691       ;; Clear the hash-vector.
692       (when hash-vector
693         (fill hash-vector +magic-hash-vector-value+)))
694     (setf (hash-table-cache hash-table) nil)
695     (setf (hash-table-number-entries hash-table) 0))
696   hash-table)
697 \f
698 ;;;; MAPHASH
699
700 ;;; FIXME: This should be made into a compiler transform for two reasons:
701 ;;;   1. It would then be available for compiling the entire system,
702 ;;;      not only parts of the system which are defined after DEFUN MAPHASH.
703 ;;;   2. It could be conditional on compilation policy, so that
704 ;;;      it could be compiled as a full call instead of an inline
705 ;;;      expansion when SPACE>SPEED.
706 (declaim (inline maphash))
707 (defun maphash (function-designator hash-table)
708   #!+sb-doc
709   "For each entry in HASH-TABLE, call the designated two-argument function
710    on the key and value of the entry. Return NIL."
711   (let ((fun (%coerce-callable-to-fun function-designator))
712         (size (length (hash-table-next-vector hash-table))))
713     (declare (type function fun))
714     (do ((i 1 (1+ i)))
715         ((>= i size))
716       (declare (type index i))
717       (let* ((kv-vector (hash-table-table hash-table))
718              (key (aref kv-vector (* 2 i)))
719              (value (aref kv-vector (1+ (* 2 i)))))
720         (unless (and (eq key +empty-ht-slot+)
721                      (eq value +empty-ht-slot+))
722           (funcall fun key value))))))
723 \f
724 ;;;; methods on HASH-TABLE
725
726 ;;; Return a list of keyword args and values to use for MAKE-HASH-TABLE
727 ;;; when reconstructing HASH-TABLE.
728 (defun %hash-table-ctor-args (hash-table)
729   (when (hash-table-weak-p hash-table)
730     ;; FIXME: This might actually work with no trouble, but as of
731     ;; sbcl-0.6.12.10 when this code was written, weak hash tables
732     ;; weren't working yet, so I couldn't test it. When weak hash
733     ;; tables are supported again, this should be fixed.
734     (error "can't dump weak hash tables readably")) ; defensive programming..
735   `(:test             ',(hash-table-test             hash-table)
736     :size             ',(hash-table-size             hash-table)
737     :rehash-size      ',(hash-table-rehash-size      hash-table)
738     :rehash-threshold ',(hash-table-rehash-threshold hash-table)))
739
740 ;;; Return an association list representing the same data as HASH-TABLE.
741 (defun %hash-table-alist (hash-table)
742   (let ((result nil))
743     (maphash (lambda (key value)
744                (push (cons key value) result))
745              hash-table)
746     result))
747
748 ;;; Stuff an association list into HASH-TABLE. Return the hash table,
749 ;;; so that we can use this for the *PRINT-READABLY* case in
750 ;;; PRINT-OBJECT (HASH-TABLE T) without having to worry about LET
751 ;;; forms and readable gensyms and stuff.
752 (defun %stuff-hash-table (hash-table alist)
753   (dolist (x alist)
754     (setf (gethash (car x) hash-table) (cdr x)))
755   hash-table)
756
757 (def!method print-object ((hash-table hash-table) stream)
758   (declare (type stream stream))
759   (cond ((or (not *print-readably*) (not *read-eval*))
760          (print-unreadable-object (hash-table stream :type t :identity t)
761            (format stream
762                    ":TEST ~S :COUNT ~S"
763                    (hash-table-test hash-table)
764                    (hash-table-count hash-table))))
765         (t
766          (with-standard-io-syntax
767           (format stream
768                   "#.~W"
769                   `(%stuff-hash-table (make-hash-table ,@(%hash-table-ctor-args
770                                                           hash-table))
771                                      ',(%hash-table-alist hash-table)))))))
772
773 (def!method make-load-form ((hash-table hash-table) &optional environment)
774   (declare (ignore environment))
775   (values `(make-hash-table ,@(%hash-table-ctor-args hash-table))
776           `(%stuff-hash-table ,hash-table ',(%hash-table-alist hash-table))))