0.9.6.52:
[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 (unless (eq test 'eq)
203                                   (make-array size+1
204                                               :element-type '(unsigned-byte #.sb!vm:n-word-bits)
205                                               :initial-element +magic-hash-vector-value+))
206                    :spinlock (sb!thread::make-spinlock))))
207       (declare (type index size+1 scaled-size length))
208       ;; Set up the free list, all free. These lists are 0 terminated.
209       (do ((i 1 (1+ i)))
210           ((>= i size))
211         (setf (aref next-vector i) (1+ i)))
212       (setf (aref next-vector size) 0)
213       (setf (hash-table-next-free-kv table) 1)
214       (setf (hash-table-needing-rehash table) 0)
215       (setf (aref kv-vector 0) table)
216       table)))
217
218 (defun hash-table-count (hash-table)
219   #!+sb-doc
220   "Return the number of entries in the given HASH-TABLE."
221   (declare (type hash-table hash-table)
222            (values index))
223   (hash-table-number-entries hash-table))
224
225 #!+sb-doc
226 (setf (fdocumentation 'hash-table-rehash-size 'function)
227       "Return the rehash-size HASH-TABLE was created with.")
228
229 #!+sb-doc
230 (setf (fdocumentation 'hash-table-rehash-threshold 'function)
231       "Return the rehash-threshold HASH-TABLE was created with.")
232
233 (defun hash-table-size (hash-table)
234   #!+sb-doc
235   "Return a size that can be used with MAKE-HASH-TABLE to create a hash
236    table that can hold however many entries HASH-TABLE can hold without
237    having to be grown."
238   (hash-table-rehash-trigger hash-table))
239
240 #!+sb-doc
241 (setf (fdocumentation 'hash-table-test 'function)
242       "Return the test HASH-TABLE was created with.")
243
244 #!+sb-doc
245 (setf (fdocumentation 'hash-table-weak-p 'function)
246       "Return T if HASH-TABLE will not keep entries for keys that would
247    otherwise be garbage, and NIL if it will.")
248 \f
249 ;;;; accessing functions
250
251 ;;; Make new vectors for the table, extending the table based on the
252 ;;; rehash-size.
253 (defun rehash (table)
254   (declare (type hash-table table))
255   (let* ((old-kv-vector (hash-table-table table))
256          (old-next-vector (hash-table-next-vector table))
257          (old-hash-vector (hash-table-hash-vector table))
258          (old-size (length old-next-vector))
259          (new-size
260           (let ((rehash-size (hash-table-rehash-size table)))
261             (etypecase rehash-size
262               (fixnum
263                (+ rehash-size old-size))
264               (float
265                (the index (truncate (* rehash-size old-size)))))))
266          (new-kv-vector (make-array (* 2 new-size)
267                                     :initial-element +empty-ht-slot+))
268          (new-next-vector (make-array new-size
269                                       :element-type '(unsigned-byte #.sb!vm:n-word-bits)
270                                       :initial-element 0))
271          (new-hash-vector (when old-hash-vector
272                             (make-array new-size
273                                         :element-type '(unsigned-byte #.sb!vm:n-word-bits)
274                                         :initial-element +magic-hash-vector-value+)))
275          (old-index-vector (hash-table-index-vector table))
276          (new-length (almost-primify
277                       (truncate (/ (float new-size)
278                                 (hash-table-rehash-threshold table)))))
279          (new-index-vector (make-array new-length
280                                        :element-type '(unsigned-byte #.sb!vm:n-word-bits)
281                                        :initial-element 0)))
282     (declare (type index new-size new-length old-size))
283
284     ;; Disable GC tricks on the OLD-KV-VECTOR.
285     (set-header-data old-kv-vector sb!vm:vector-normal-subtype)
286
287     ;; FIXME: here and in several other places in the hash table code,
288     ;; loops like this one are used when FILL or REPLACE would be
289     ;; appropriate.  why are standard CL functions not used?
290     ;; Performance issues?  General laziness?  -- NJF, 2004-03-10
291
292     ;; Copy over the kv-vector. The element positions should not move
293     ;; in case there are active scans.
294     (dotimes (i (* old-size 2))
295       (declare (type index i))
296       (setf (aref new-kv-vector i) (aref old-kv-vector i)))
297
298     ;; Copy over the hash-vector.
299     (when old-hash-vector
300       (dotimes (i old-size)
301         (setf (aref new-hash-vector i) (aref old-hash-vector i))))
302
303     (setf (hash-table-next-free-kv table) 0)
304     (setf (hash-table-needing-rehash table) 0)
305     ;; Rehash all the entries; last to first so that after the pushes
306     ;; the chains are first to last.
307     (do ((i (1- new-size) (1- i)))
308         ((zerop i))
309       (let ((key (aref new-kv-vector (* 2 i)))
310             (value (aref new-kv-vector (1+ (* 2 i)))))
311         (cond ((and (eq key +empty-ht-slot+)
312                     (eq value +empty-ht-slot+))
313                ;; Slot is empty, push it onto the free list.
314                (setf (aref new-next-vector i)
315                      (hash-table-next-free-kv table))
316                (setf (hash-table-next-free-kv table) i))
317               ((and new-hash-vector
318                     (not (= (aref new-hash-vector i) +magic-hash-vector-value+)))
319                ;; Can use the existing hash value (not EQ based)
320                (let* ((hashing (aref new-hash-vector i))
321                       (index (rem hashing new-length))
322                       (next (aref new-index-vector index)))
323                  (declare (type index index)
324                           (type hash hashing))
325                  ;; Push this slot into the next chain.
326                  (setf (aref new-next-vector i) next)
327                  (setf (aref new-index-vector index) i)))
328               (t
329                ;; EQ base hash.
330                ;; Enable GC tricks.
331                (set-header-data new-kv-vector
332                                 sb!vm:vector-valid-hashing-subtype)
333                (let* ((hashing (pointer-hash key))
334                       (index (rem hashing new-length))
335                       (next (aref new-index-vector index)))
336                  (declare (type index index)
337                           (type hash hashing))
338                  ;; Push this slot onto the next chain.
339                  (setf (aref new-next-vector i) next)
340                  (setf (aref new-index-vector index) i))))))
341     (setf (hash-table-table table) new-kv-vector)
342     (setf (hash-table-index-vector table) new-index-vector)
343     (setf (hash-table-next-vector table) new-next-vector)
344     (setf (hash-table-hash-vector table) new-hash-vector)
345     ;; Shrink the old vectors to 0 size to help the conservative GC.
346     (shrink-vector old-kv-vector 0)
347     (shrink-vector old-index-vector 0)
348     (shrink-vector old-next-vector 0)
349     (when old-hash-vector
350       (shrink-vector old-hash-vector 0))
351     (setf (hash-table-rehash-trigger table) new-size))
352   (values))
353
354 ;;; Use the same size as before, re-using the vectors.
355 (defun rehash-without-growing (table)
356   (declare (type hash-table table))
357   (let* ((kv-vector (hash-table-table table))
358          (next-vector (hash-table-next-vector table))
359          (hash-vector (hash-table-hash-vector table))
360          (size (length next-vector))
361          (index-vector (hash-table-index-vector table))
362          (length (length index-vector)))
363     (declare (type index size length))
364
365     ;; Disable GC tricks, they will be re-enabled during the re-hash
366     ;; if necesary.
367     (set-header-data kv-vector sb!vm:vector-normal-subtype)
368
369     ;; Rehash all the entries.
370     (setf (hash-table-next-free-kv table) 0)
371     (setf (hash-table-needing-rehash table) 0)
372     (dotimes (i size)
373       (setf (aref next-vector i) 0))
374     (dotimes (i length)
375       (setf (aref index-vector i) 0))
376     (do ((i (1- size) (1- i)))
377         ((zerop i))
378       (let ((key (aref kv-vector (* 2 i)))
379             (value (aref kv-vector (1+ (* 2 i)))))
380         (cond ((and (eq key +empty-ht-slot+)
381                     (eq value +empty-ht-slot+))
382                ;; Slot is empty, push it onto free list.
383                (setf (aref next-vector i) (hash-table-next-free-kv table))
384                (setf (hash-table-next-free-kv table) i))
385               ((and hash-vector (not (= (aref hash-vector i) +magic-hash-vector-value+)))
386                ;; Can use the existing hash value (not EQ based)
387                (let* ((hashing (aref hash-vector i))
388                       (index (rem hashing length))
389                       (next (aref index-vector index)))
390                  (declare (type index index))
391                  ;; Push this slot into the next chain.
392                  (setf (aref next-vector i) next)
393                  (setf (aref index-vector index) i)))
394               (t
395                ;; EQ base hash.
396                ;; Enable GC tricks.
397                (set-header-data kv-vector sb!vm:vector-valid-hashing-subtype)
398                (let* ((hashing (pointer-hash key))
399                       (index (rem hashing length))
400                       (next (aref index-vector index)))
401                  (declare (type index index)
402                           (type hash hashing))
403                  ;; Push this slot into the next chain.
404                  (setf (aref next-vector i) next)
405                  (setf (aref index-vector index) i)))))))
406   (values))
407
408 (defun flush-needing-rehash (table)
409   (let* ((kv-vector (hash-table-table table))
410          (index-vector (hash-table-index-vector table))
411          (next-vector (hash-table-next-vector table))
412          (length (length index-vector)))
413     (do ((next (hash-table-needing-rehash table)))
414         ((zerop next))
415       (declare (type index next))
416       (let* ((key (aref kv-vector (* 2 next)))
417              (hashing (pointer-hash key))
418              (index (rem hashing length))
419              (temp (aref next-vector next)))
420         (setf (aref next-vector next) (aref index-vector index))
421         (setf (aref index-vector index) next)
422         (setf next temp))))
423   (setf (hash-table-needing-rehash table) 0)
424   (values))
425
426 (defun gethash (key hash-table &optional default)
427   #!+sb-doc
428   "Finds the entry in HASH-TABLE whose key is KEY and returns the associated
429    value and T as multiple values, or returns DEFAULT and NIL if there is no
430    such entry. Entries can be added using SETF."
431   (declare (type hash-table hash-table)
432            (values t (member t nil)))
433   (gethash3 key hash-table default))
434
435 (defun gethash2 (key hash-table)
436   #!+sb-doc
437   "Two argument version of GETHASH"
438   (declare (type hash-table hash-table)
439            (values t (member t nil)))
440   (gethash3 key hash-table nil))
441
442 (defun gethash3 (key hash-table default)
443   #!+sb-doc
444   "Three argument version of GETHASH"
445   (declare (type hash-table hash-table)
446            (values t (member t nil)))
447   (with-spinlock-and-without-gcing ((hash-table-spinlock hash-table))
448    (cond ((= (get-header-data (hash-table-table hash-table))
449              sb!vm:vector-must-rehash-subtype)
450           (rehash-without-growing hash-table))
451          ((not (zerop (hash-table-needing-rehash hash-table)))
452           (flush-needing-rehash hash-table)))
453
454    ;; First check the cache.  Use EQ here for speed.
455    (let ((cache (hash-table-cache hash-table))
456          (table (hash-table-table hash-table)))
457
458      (if (and cache (< cache (length table)) (eq (aref table cache) key))
459          (values (aref table (1+ cache)) t)
460
461        ;; Search for key in the hash table.
462        (multiple-value-bind (hashing eq-based)
463            (funcall (hash-table-hash-fun hash-table) key)
464          (declare (type hash hashing))
465          (let* ((index-vector (hash-table-index-vector hash-table))
466                 (length (length index-vector))
467                 (index (rem hashing length))
468                 (next (aref index-vector index))
469                 (next-vector (hash-table-next-vector hash-table))
470                 (hash-vector (hash-table-hash-vector hash-table))
471                 (test-fun (hash-table-test-fun hash-table)))
472            (declare (type index index))
473            ;; Search next-vector chain for a matching key.
474            (if (or eq-based (not hash-vector))
475                (do ((next next (aref next-vector next)))
476                    ((zerop next) (values default nil))
477                  (declare (type index next))
478                  (when (eq key (aref table (* 2 next)))
479                    (setf (hash-table-cache hash-table) (* 2 next))
480                    (return (values (aref table (1+ (* 2 next))) t))))
481              (do ((next next (aref next-vector next)))
482                  ((zerop next) (values default nil))
483                (declare (type index next))
484                (when (and (= hashing (aref hash-vector next))
485                           (funcall test-fun key (aref table (* 2 next))))
486                  ;; Found.
487                  (setf (hash-table-cache hash-table) (* 2 next))
488                  (return (values (aref table (1+ (* 2 next))) t)))))))))))
489
490 ;;; so people can call #'(SETF GETHASH)
491 (defun (setf gethash) (new-value key table &optional default)
492   (declare (ignore default))
493   (%puthash key table new-value))
494
495 (defun %puthash (key hash-table value)
496   (declare (type hash-table hash-table))
497   (aver (hash-table-index-vector hash-table))
498   (with-spinlock-and-without-gcing ((hash-table-spinlock hash-table))
499    ;; We need to rehash here so that a current key can be found if it
500    ;; exists. Check that there is room for one more entry. May not be
501    ;; needed if the key is already present.
502    (cond ((zerop (hash-table-next-free-kv hash-table))
503           (rehash hash-table))
504          ((= (get-header-data (hash-table-table hash-table))
505              sb!vm:vector-must-rehash-subtype)
506           (rehash-without-growing hash-table))
507          ((not (zerop (hash-table-needing-rehash hash-table)))
508           (flush-needing-rehash hash-table)))
509
510    (let ((cache (hash-table-cache hash-table))
511          (kv-vector (hash-table-table hash-table)))
512
513      ;; Check the cache
514      (if (and cache (< cache (length kv-vector)) (eq (aref kv-vector cache) key))
515          ;; If cached, just store here
516          (setf (aref kv-vector (1+ cache)) value)
517
518        ;; Search for key in the hash table.
519        (multiple-value-bind (hashing eq-based)
520            (funcall (hash-table-hash-fun hash-table) key)
521          (declare (type hash hashing))
522          (let* ((index-vector (hash-table-index-vector hash-table))
523                 (length (length index-vector))
524                 (index (rem hashing length))
525                 (next (aref index-vector index))
526                 (kv-vector (hash-table-table hash-table))
527                 (next-vector (hash-table-next-vector hash-table))
528                 (hash-vector (hash-table-hash-vector hash-table))
529                 (test-fun (hash-table-test-fun hash-table)))
530            (declare (type index index))
531
532            (cond ((or eq-based (not hash-vector))
533                   (when eq-based
534                     (set-header-data kv-vector sb!vm:vector-valid-hashing-subtype))
535
536                   ;; Search next-vector chain for a matching key.
537                   (do ((next next (aref next-vector next)))
538                       ((zerop next))
539                     (declare (type index next))
540                     (when (eq key (aref kv-vector (* 2 next)))
541                       ;; Found, just replace the value.
542                       (setf (hash-table-cache hash-table) (* 2 next))
543                       (setf (aref kv-vector (1+ (* 2 next))) value)
544                       (return-from %puthash value))))
545                  (t
546                   ;; Search next-vector chain for a matching key.
547                   (do ((next next (aref next-vector next)))
548                       ((zerop next))
549                     (declare (type index next))
550                     (when (and (= hashing (aref hash-vector next))
551                                (funcall test-fun key
552                                         (aref kv-vector (* 2 next))))
553                       ;; Found, just replace the value.
554                       (setf (hash-table-cache hash-table) (* 2 next))
555                       (setf (aref kv-vector (1+ (* 2 next))) value)
556                       (return-from %puthash value)))))
557
558            ;; Pop a KV slot off the free list
559            (let ((free-kv-slot (hash-table-next-free-kv hash-table)))
560              ;; Double-check for overflow.
561              (aver (not (zerop free-kv-slot)))
562              (setf (hash-table-next-free-kv hash-table)
563                    (aref next-vector free-kv-slot))
564              (incf (hash-table-number-entries hash-table))
565
566              (setf (hash-table-cache hash-table) (* 2 free-kv-slot))
567              (setf (aref kv-vector (* 2 free-kv-slot)) key)
568              (setf (aref kv-vector (1+ (* 2 free-kv-slot))) value)
569
570              ;; Setup the hash-vector if necessary.
571              (when hash-vector
572                (if (not eq-based)
573                    (setf (aref hash-vector free-kv-slot) hashing)
574                    (aver (= (aref hash-vector free-kv-slot)
575                             +magic-hash-vector-value+))))
576
577              ;; Push this slot into the next chain.
578              (setf (aref next-vector free-kv-slot) next)
579              (setf (aref index-vector index) free-kv-slot)))))))
580   value)
581
582 (defun remhash (key hash-table)
583   #!+sb-doc
584   "Remove the entry in HASH-TABLE associated with KEY. Return T if there
585    was such an entry, or NIL if not."
586   (declare (type hash-table hash-table)
587            (values (member t nil)))
588   (with-spinlock-and-without-gcing ((hash-table-spinlock hash-table))
589    ;; We need to rehash here so that a current key can be found if it
590    ;; exists.
591    (cond ((= (get-header-data (hash-table-table hash-table))
592              sb!vm:vector-must-rehash-subtype)
593           (rehash-without-growing hash-table))
594          ((not (zerop (hash-table-needing-rehash hash-table)))
595           (flush-needing-rehash hash-table)))
596
597    ;; For now, just clear the cache
598    (setf (hash-table-cache hash-table) nil)
599
600    ;; Search for key in the hash table.
601    (multiple-value-bind (hashing eq-based)
602        (funcall (hash-table-hash-fun hash-table) key)
603      (declare (type hash hashing))
604      (let* ((index-vector (hash-table-index-vector hash-table))
605             (length (length index-vector))
606             (index (rem hashing length))
607             (next (aref index-vector index))
608             (table (hash-table-table hash-table))
609             (next-vector (hash-table-next-vector hash-table))
610             (hash-vector (hash-table-hash-vector hash-table))
611             (test-fun (hash-table-test-fun hash-table)))
612        (declare (type index index next))
613        (flet ((clear-slot (chain-vector prior-slot-location slot-location)
614                 ;; Mark slot as empty.
615                 (setf (aref table (* 2 slot-location)) +empty-ht-slot+
616                       (aref table (1+ (* 2 slot-location))) +empty-ht-slot+)
617                 ;; Update the prior pointer in the chain to skip this.
618                 (setf (aref chain-vector prior-slot-location)
619                       (aref next-vector slot-location))
620                 ;; Push KV slot onto free chain.
621                 (setf (aref next-vector slot-location)
622                       (hash-table-next-free-kv hash-table))
623                 (setf (hash-table-next-free-kv hash-table) slot-location)
624                 (when hash-vector
625                   (setf (aref hash-vector slot-location)
626                         +magic-hash-vector-value+))
627                 (decf (hash-table-number-entries hash-table))
628                 t))
629          (cond ((zerop next)
630                 nil)
631                ((if (or eq-based (not hash-vector))
632                     (eq key (aref table (* 2 next)))
633                     (and (= hashing (aref hash-vector next))
634                          (funcall test-fun key (aref table (* 2 next)))))
635                 (clear-slot index-vector index next))
636                ;; Search next-vector chain for a matching key.
637                ((or eq-based (not hash-vector))
638                 ;; EQ based
639                 (do ((prior next next)
640                      (next (aref next-vector next) (aref next-vector next)))
641                     ((zerop next) nil)
642                   (declare (type index next))
643                   (when (eq key (aref table (* 2 next)))
644                     (return-from remhash (clear-slot next-vector prior next)))))
645                (t
646                 ;; not EQ based
647                 (do ((prior next next)
648                      (next (aref next-vector next) (aref next-vector next)))
649                     ((zerop next) nil)
650                   (declare (type index next))
651                   (when (and (= hashing (aref hash-vector next))
652                              (funcall test-fun key (aref table (* 2 next))))
653                     (return-from remhash (clear-slot next-vector prior next)))))))))))
654
655 (defun clrhash (hash-table)
656   #!+sb-doc
657   "This removes all the entries from HASH-TABLE and returns the hash table
658    itself."
659   (declare (optimize speed))
660   (with-spinlock-and-without-gcing ((hash-table-spinlock hash-table))
661     (let* ((kv-vector (hash-table-table hash-table))
662            (next-vector (hash-table-next-vector hash-table))
663            (hash-vector (hash-table-hash-vector hash-table))
664            (size (length next-vector))
665            (index-vector (hash-table-index-vector hash-table)))
666       ;; Disable GC tricks.
667       (set-header-data kv-vector sb!vm:vector-normal-subtype)
668       ;; Mark all slots as empty by setting all keys and values to magic
669       ;; tag.
670       (aver (eq (aref kv-vector 0) hash-table))
671       (fill kv-vector +empty-ht-slot+ :start 2)
672       ;; Set up the free list, all free.
673       (do ((i 1 (1+ i)))
674           ((>= i (1- size)))
675           (setf (aref next-vector i) (1+ i)))
676       (setf (aref next-vector (1- size)) 0)
677       (setf (hash-table-next-free-kv hash-table) 1)
678       (setf (hash-table-needing-rehash hash-table) 0)
679       ;; Clear the index-vector.
680       (fill index-vector 0)
681       ;; Clear the hash-vector.
682       (when hash-vector
683         (fill hash-vector +magic-hash-vector-value+)))
684     (setf (hash-table-cache hash-table) nil)
685     (setf (hash-table-number-entries hash-table) 0))
686   hash-table)
687 \f
688 ;;;; MAPHASH
689
690 ;;; FIXME: This should be made into a compiler transform for two reasons:
691 ;;;   1. It would then be available for compiling the entire system,
692 ;;;      not only parts of the system which are defined after DEFUN MAPHASH.
693 ;;;   2. It could be conditional on compilation policy, so that
694 ;;;      it could be compiled as a full call instead of an inline
695 ;;;      expansion when SPACE>SPEED.
696 (declaim (inline maphash))
697 (defun maphash (function-designator hash-table)
698   #!+sb-doc
699   "For each entry in HASH-TABLE, call the designated two-argument function
700    on the key and value of the entry. Return NIL."
701   (let ((fun (%coerce-callable-to-fun function-designator))
702         (size (length (hash-table-next-vector hash-table))))
703     (declare (type function fun))
704     (do ((i 1 (1+ i)))
705         ((>= i size))
706       (declare (type index i))
707       (let* ((kv-vector (hash-table-table hash-table))
708              (key (aref kv-vector (* 2 i)))
709              (value (aref kv-vector (1+ (* 2 i)))))
710         (unless (and (eq key +empty-ht-slot+)
711                      (eq value +empty-ht-slot+))
712           (funcall fun key value))))))
713 \f
714 ;;;; methods on HASH-TABLE
715
716 ;;; Return a list of keyword args and values to use for MAKE-HASH-TABLE
717 ;;; when reconstructing HASH-TABLE.
718 (defun %hash-table-ctor-args (hash-table)
719   (when (hash-table-weak-p hash-table)
720     ;; FIXME: This might actually work with no trouble, but as of
721     ;; sbcl-0.6.12.10 when this code was written, weak hash tables
722     ;; weren't working yet, so I couldn't test it. When weak hash
723     ;; tables are supported again, this should be fixed.
724     (error "can't dump weak hash tables readably")) ; defensive programming..
725   `(:test             ',(hash-table-test             hash-table)
726     :size             ',(hash-table-size             hash-table)
727     :rehash-size      ',(hash-table-rehash-size      hash-table)
728     :rehash-threshold ',(hash-table-rehash-threshold hash-table)))
729
730 ;;; Return an association list representing the same data as HASH-TABLE.
731 (defun %hash-table-alist (hash-table)
732   (let ((result nil))
733     (maphash (lambda (key value)
734                (push (cons key value) result))
735              hash-table)
736     result))
737
738 ;;; Stuff an association list into HASH-TABLE. Return the hash table,
739 ;;; so that we can use this for the *PRINT-READABLY* case in
740 ;;; PRINT-OBJECT (HASH-TABLE T) without having to worry about LET
741 ;;; forms and readable gensyms and stuff.
742 (defun %stuff-hash-table (hash-table alist)
743   (dolist (x alist)
744     (setf (gethash (car x) hash-table) (cdr x)))
745   hash-table)
746
747 (def!method print-object ((hash-table hash-table) stream)
748   (declare (type stream stream))
749   (cond ((or (not *print-readably*) (not *read-eval*))
750          (print-unreadable-object (hash-table stream :type t :identity t)
751            (format stream
752                    ":TEST ~S :COUNT ~S"
753                    (hash-table-test hash-table)
754                    (hash-table-count hash-table))))
755         (t
756          (with-standard-io-syntax
757           (format stream
758                   "#.~W"
759                   `(%stuff-hash-table (make-hash-table ,@(%hash-table-ctor-args
760                                                           hash-table))
761                                      ',(%hash-table-alist hash-table)))))))
762
763 (def!method make-load-form ((hash-table hash-table) &optional environment)
764   (declare (ignore environment))
765   (values `(make-hash-table ,@(%hash-table-ctor-args hash-table))
766           `(%stuff-hash-table ,hash-table ',(%hash-table-alist hash-table))))