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