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