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