5c5bdb7372e0ac336aa806fe140926ca476aee44
[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 ;;; Code for detecting concurrent accesses to the same table from
18 ;;; multiple threads. Only compiled in when the :SB-HASH-TABLE-DEBUG
19 ;;; feature is enabled. The main reason for the existence of this code
20 ;;; is to detect thread-unsafe uses of hash-tables in sbcl itself,
21 ;;; where debugging anythign can be impossible after an important
22 ;;; internal hash-table has been corrupted. It's plausible that this
23 ;;; could be useful for some user code too, but the runtime cost is
24 ;;; really too high to enable it by default.
25 (defmacro with-concurrent-access-check (hash-table operation &body body)
26   (declare (ignorable hash-table operation)
27            (type (member :read :write) operation))
28   #!-sb-hash-table-debug
29   `(progn ,@body)
30   #!+sb-hash-table-debug
31   (let ((thread-slot-accessor (if (eq operation :read)
32                                   'hash-table-reading-thread
33                                   'hash-table-writing-thread)))
34     (once-only ((hash-table hash-table))
35       `(progn
36          (flet ((body-fun ()
37                   ,@body)
38                 (error-fun ()
39                   ;; Don't signal more errors for this table.
40                   (setf (hash-table-signal-concurrent-access ,hash-table) nil)
41                   (cerror "Ignore the concurrent access"
42                           "Concurrent access to ~A" ,hash-table)))
43            (declare (inline body-fun))
44            (if (hash-table-signal-concurrent-access ,hash-table)
45                (unwind-protect
46                     (progn
47                       (unless (and (null (hash-table-writing-thread
48                                           ,hash-table))
49                                    ,@(when (eq operation :write)
50                                            `((null (hash-table-reading-thread
51                                                     ,hash-table)))))
52                         (error-fun))
53                       (setf (,thread-slot-accessor ,hash-table)
54                             sb!thread::*current-thread*)
55                       (body-fun))
56                  (unless (and ,@(when (eq operation :read)
57                                   `((null (hash-table-writing-thread
58                                            ,hash-table))))
59                               ,@(when (eq operation :write)
60                                   ;; no readers are allowed while writing
61                                   `((null (hash-table-reading-thread
62                                            ,hash-table))
63                                     (eq (hash-table-writing-thread
64                                          ,hash-table)
65                                         sb!thread::*current-thread*))))
66                    (error-fun))
67                  (when (eq (,thread-slot-accessor ,hash-table)
68                            sb!thread::*current-thread*)
69                    ;; this is not 100% correct here and may hide
70                    ;; concurrent access in rare circumstances.
71                    (setf (,thread-slot-accessor ,hash-table) nil)))
72                (body-fun)))))))
73
74 #!-sb-fluid (declaim (inline eq-hash))
75 (defun eq-hash (key)
76   (declare (values hash (member t nil)))
77   (values (pointer-hash key)
78           (oddp (get-lisp-obj-address key))))
79
80 #!-sb-fluid (declaim (inline equal-hash))
81 (defun equal-hash (key)
82   (declare (values hash (member t nil)))
83   (typecase key
84     ;; For some types the definition of EQUAL implies a special hash
85     ((or string cons number bit-vector pathname)
86      (values (sxhash key) nil))
87     ;; Otherwise use an EQ hash, rather than SXHASH, since the values
88     ;; of SXHASH will be extremely badly distributed due to the
89     ;; requirements of the spec fitting badly with our implementation
90     ;; strategy.
91     (t
92      (eq-hash key))))
93
94 #!-sb-fluid (declaim (inline eql-hash))
95 (defun eql-hash (key)
96   (declare (values hash (member t nil)))
97   (if (numberp key)
98       (equal-hash key)
99       (eq-hash key)))
100
101 (defun equalp-hash (key)
102   (declare (values hash (member t nil)))
103   (typecase key
104     ;; Types requiring special treatment. Note that PATHNAME and
105     ;; HASH-TABLE are caught by the STRUCTURE-OBJECT test.
106     ((or array cons number character structure-object)
107      (values (psxhash key) nil))
108     (t
109      (eq-hash key))))
110
111 (declaim (inline index-for-hashing))
112 (defun index-for-hashing (hash length)
113   (declare (type hash hash length))
114   ;; We're using power of two tables which obviously are very
115   ;; sensitive to the exact values of the low bits in the hash
116   ;; value. Do a little shuffling of the value to mix the high bits in
117   ;; there too.
118   (truly-the index
119              (logand (1- length)
120                      (+ (logxor #b11100101010001011010100111
121                                 hash)
122                         (ash hash -3)
123                         (ash hash -12)
124                         (ash hash -20)))))
125
126 \f
127 ;;;; user-defined hash table tests
128
129 (defvar *user-hash-table-tests* nil)
130
131 (defun register-hash-table-test (name hash-fun)
132   (declare (symbol name) (function hash-fun))
133   (unless (fboundp name)
134     (error "Cannot register ~S has a hash table test: undefined function."
135            name))
136   (with-single-package-locked-error
137       (:symbol name "defining ~S as a hash table test")
138     (let* ((test-fun (fdefinition name))
139            (this (list name test-fun hash-fun))
140            (spec (assoc name *user-hash-table-tests*)))
141       (cond (spec
142              (unless (and (eq (second spec) test-fun)
143                           (eq (third spec) hash-fun))
144                (style-warn "Redefining hash table test ~S." name)
145                (setf (cdr spec) (cdr this))))
146             (t
147              (push this *user-hash-table-tests*)))))
148   name)
149
150 (defmacro define-hash-table-test (name hash-function)
151   #!+sb-doc
152   "Defines NAME as a new kind of hash table test for use with the :TEST
153 argument to MAKE-HASH-TABLE, and associates a default HASH-FUNCTION with it.
154
155 NAME must be a symbol naming a global two argument equivalence predicate.
156 Afterwards both 'NAME and #'NAME can be used with :TEST argument. In both
157 cases HASH-TABLE-TEST will return the symbol NAME.
158
159 HASH-FUNCTION must be a symbol naming a global hash function consistent with
160 the predicate, or be a LAMBDA form implementing one in the current lexical
161 environment. The hash function must compute the same hash code for any two
162 objects for which NAME returns true, and subsequent calls with already hashed
163 objects must always return the same hash code.
164
165 Note: The :HASH-FUNCTION keyword argument to MAKE-HASH-TABLE can be used to
166 override the specified default hash-function.
167
168 Attempting to define NAME in a locked package as hash-table test causes a
169 package lock violation.
170
171 Examples:
172
173   ;;; 1.
174
175   ;; We want to use objects of type FOO as keys (by their
176   ;; names.) EQUALP would work, but would make the names
177   ;; case-insensitive -- wich we don't want.
178   (defstruct foo (name nil :type (or null string)))
179
180   ;; Define an equivalence test function and a hash function.
181   (defun foo-name= (f1 f2) (equal (foo-name f1) (foo-name f2)))
182   (defun sxhash-foo-name (f) (sxhash (foo-name f)))
183
184   (define-hash-table-test foo-name= sxhash-foo-name)
185
186   ;; #'foo-name would work too.
187   (defun make-foo-table () (make-hash-table :test 'foo-name=))
188
189   ;;; 2.
190
191   (defun == (x y) (= x y))
192
193   (define-hash-table-test ==
194     (lambda (x)
195       ;; Hash codes must be consistent with test, so
196       ;; not (SXHASH X), since
197       ;;   (= 1 1.0)                   => T
198       ;;   (= (SXHASH 1) (SXHASH 1.0)) => NIL
199       ;; Note: this doesn't deal with complex numbers or
200       ;; bignums too large to represent as double floats.
201       (sxhash (coerce x 'double-float))))
202
203   ;; #'== would work too
204   (defun make-number-table () (make-hash-table :test '==))
205 "
206   (check-type name symbol)
207   (if (member name '(eq eql equal equalp))
208       (error "Cannot redefine standard hash table test ~S." name)
209       (cond ((symbolp hash-function)
210              `(register-hash-table-test ',name (symbol-function ',hash-function)))
211             ((and (consp hash-function) (eq 'lambda (car hash-function)))
212              `(register-hash-table-test ',name #',hash-function))
213             (t
214              (error "Malformed HASH-FUNCTION: ~S" hash-function)))))
215 \f
216 ;;;; construction and simple accessors
217
218 (defconstant +min-hash-table-size+ 16)
219 (defconstant +min-hash-table-rehash-threshold+ (float 1/16 1.0))
220
221 (defun make-hash-table (&key
222                         (test 'eql)
223                         (size +min-hash-table-size+)
224                         (rehash-size 1.5)
225                         (rehash-threshold 1)
226                         (hash-function nil)
227                         (weakness nil)
228                         (synchronized))
229   #!+sb-doc
230   "Create and return a new hash table. The keywords are as follows:
231
232   :TEST
233     Determines how keys are compared. Must a designator for one of the
234     standard hash table tests, or a hash table test defined using
235     SB-EXT:DEFINE-HASH-TABLE-TEST. Additionally, when an explicit
236     HASH-FUNCTION is provided (see below), any two argument equivalence
237     predicate can be used as the TEST.
238
239   :SIZE
240     A hint as to how many elements will be put in this hash table.
241
242   :REHASH-SIZE
243     Indicates how to expand the table when it fills up. If an integer, add
244     space for that many elements. If a floating point number (which must be
245     greater than 1.0), multiply the size by that amount.
246
247   :REHASH-THRESHOLD
248     Indicates how dense the table can become before forcing a rehash. Can be
249     any positive number <=1, with density approaching zero as the threshold
250     approaches 0. Density 1 means an average of one entry per bucket.
251
252   :HASH-FUNCTION
253     If NIL (the default), a hash function based on the TEST argument is used,
254     which then must be one of the standardized hash table test functions, or
255     one for which a default hash function has been defined using
256     SB-EXT:DEFINE-HASH-TABLE-TEST. If HASH-FUNCTION is specified, the TEST
257     argument can be any two argument predicate consistent with it. The
258     HASH-FUNCTION is expected to return a non-negative fixnum hash code.
259
260   :WEAKNESS
261     When :WEAKNESS is not NIL, garbage collection may remove entries from the
262     hash table. The value of :WEAKNESS specifies how the presence of a key or
263     value in the hash table preserves their entries from garbage collection.
264
265     Valid values are:
266
267       :KEY means that the key of an entry must be live to guarantee that the
268         entry is preserved.
269
270       :VALUE means that the value of an entry must be live to guarantee that
271         the entry is preserved.
272
273       :KEY-AND-VALUE means that both the key and the value must be live to
274         guarantee that the entry is preserved.
275
276       :KEY-OR-VALUE means that either the key or the value must be live to
277         guarantee that the entry is preserved.
278
279       NIL (the default) means that entries are always preserved.
280
281   :SYNCHRONIZED
282     If NIL (the default), the hash-table may have multiple concurrent readers,
283     but results are undefined if a thread writes to the hash-table
284     concurrently with another reader or writer. If T, all concurrent accesses
285     are safe, but note that CLHS 3.6 (Traversal Rules and Side Effects)
286     remains in force. See also: SB-EXT:WITH-LOCKED-HASH-TABLE. This keyword
287     argument is experimental, and may change incompatibly or be removed in the
288     future."
289   (declare (type (or function symbol) test))
290   (declare (type unsigned-byte size))
291   (multiple-value-bind (test test-fun hash-fun)
292       (cond ((or (eq test #'eq) (eq test 'eq))
293              (values 'eq #'eq #'eq-hash))
294             ((or (eq test #'eql) (eq test 'eql))
295              (values 'eql #'eql #'eql-hash))
296             ((or (eq test #'equal) (eq test 'equal))
297              (values 'equal #'equal #'equal-hash))
298             ((or (eq test #'equalp) (eq test 'equalp))
299              (values 'equalp #'equalp #'equalp-hash))
300             (t
301              ;; FIXME: It would be nice to have a compiler-macro
302              ;; that resolved this at compile time: we could grab
303              ;; the alist cell in a LOAD-TIME-VALUE, etc.
304              (dolist (info *user-hash-table-tests*
305                       (if hash-function
306                           (if (functionp test)
307                               (values (%fun-name test) test nil)
308                               (values test (%coerce-callable-to-fun test) nil))
309                        (error "Unknown :TEST for MAKE-HASH-TABLE: ~S"
310                               test)))
311                (destructuring-bind (test-name test-fun hash-fun) info
312                  (when (or (eq test test-name) (eq test test-fun))
313                    (return (values test-name test-fun hash-fun)))))))
314     (when hash-function
315       (setf hash-fun
316             ;; Quickly check if the function has return return type which
317             ;; guarantees that the secondary return value is always NIL:
318             ;; (VALUES * &OPTIONAL), (VALUES * NULL ...) or (VALUES *
319             ;; &OPTIONAL NULL ...)
320             (let* ((actual (%coerce-callable-to-fun hash-function))
321                    (type-spec (%fun-type actual))
322                    (return-spec (when (consp type-spec)
323                                   (caddr type-spec)))
324                    (extra-vals (when (consp return-spec)
325                                  (cddr return-spec))))
326               (if (and (consp extra-vals)
327                        (or (eq 'null (car extra-vals))
328                            (and (eq '&optional (car extra-vals))
329                                 (or (not (cdr extra-vals))
330                                     (eq 'null (cadr extra-vals))))))
331                   actual
332                   ;; If there is a potential secondary value, make sure we
333                   ;; don't accidentally claim EQ based hashing...
334                   (lambda (object)
335                     (declare (optimize (safety 0) (speed 3)))
336                     (values (funcall actual object) nil))))))
337     (let* ((size (max +min-hash-table-size+
338                       (min size
339                            ;; SIZE is just a hint, so if the user asks
340                            ;; for a SIZE which'd be too big for us to
341                            ;; easily implement, we bump it down.
342                            (floor array-dimension-limit 1024))))
343            (rehash-size (if (integerp rehash-size)
344                             rehash-size
345                             (float rehash-size 1.0)))
346            ;; FIXME: Original REHASH-THRESHOLD default should be 1.0,
347            ;; not 1, to make it easier for the compiler to avoid
348            ;; boxing.
349            (rehash-threshold (max +min-hash-table-rehash-threshold+
350                                   (float rehash-threshold 1.0)))
351            (size+1 (1+ size))       ; The first element is not usable.
352            ;; KLUDGE: The most natural way of expressing the below is
353            ;; (round (/ (float size+1) rehash-threshold)), and indeed
354            ;; it was expressed like that until 0.7.0. However,
355            ;; MAKE-HASH-TABLE is called very early in cold-init, and
356            ;; the SPARC has no primitive instructions for rounding,
357            ;; but only for truncating; therefore, we fudge this issue
358            ;; a little. The other uses of truncate, below, similarly
359            ;; used to be round. -- CSR, 2002-10-01
360            ;;
361            ;; Note that this has not yet been audited for
362            ;; correctness. It just seems to work. -- CSR, 2002-11-02
363            (scaled-size (truncate (/ (float size+1) rehash-threshold)))
364            (length (power-of-two-ceiling (max scaled-size
365                                               (1+ +min-hash-table-size+))))
366            (index-vector (make-array length
367                                      :element-type
368                                      '(unsigned-byte #.sb!vm:n-word-bits)
369                                      :initial-element 0))
370            ;; Needs to be the half the length of the KV vector to link
371            ;; KV entries - mapped to indeces at 2i and 2i+1 -
372            ;; together.
373            (next-vector (make-array size+1
374                                     :element-type
375                                     '(unsigned-byte #.sb!vm:n-word-bits)))
376            (kv-vector (make-array (* 2 size+1)
377                                   :initial-element +empty-ht-slot+))
378            (table (%make-hash-table
379                    :test test
380                    :test-fun test-fun
381                    :hash-fun hash-fun
382                    :rehash-size rehash-size
383                    :rehash-threshold rehash-threshold
384                    :rehash-trigger size
385                    :table kv-vector
386                    :weakness weakness
387                    :index-vector index-vector
388                    :next-vector next-vector
389                    :hash-vector
390                    (unless (eq test 'eq)
391                      (make-array size+1
392                                  :element-type '(unsigned-byte
393                                                  #.sb!vm:n-word-bits)
394                                  :initial-element +magic-hash-vector-value+))
395                    :synchronized-p synchronized)))
396       (declare (type index size+1 scaled-size length))
397       ;; Set up the free list, all free. These lists are 0 terminated.
398       (do ((i 1 (1+ i)))
399           ((>= i size))
400         (setf (aref next-vector i) (1+ i)))
401       (setf (aref next-vector size) 0)
402       (setf (hash-table-next-free-kv table) 1)
403       (setf (aref kv-vector 0) table)
404       table)))
405
406 (defun hash-table-count (hash-table)
407   #!+sb-doc
408   "Return the number of entries in the given HASH-TABLE."
409   (declare (type hash-table hash-table)
410            (values index))
411   (hash-table-number-entries hash-table))
412
413 #!+sb-doc
414 (setf (fdocumentation 'hash-table-rehash-size 'function)
415       "Return the rehash-size HASH-TABLE was created with.")
416
417 #!+sb-doc
418 (setf (fdocumentation 'hash-table-rehash-threshold 'function)
419       "Return the rehash-threshold HASH-TABLE was created with.")
420
421 #!+sb-doc
422 (setf (fdocumentation 'hash-table-synchronized-p 'function)
423       "Returns T if HASH-TABLE is synchronized.")
424
425 (defun hash-table-size (hash-table)
426   #!+sb-doc
427   "Return a size that can be used with MAKE-HASH-TABLE to create a hash
428    table that can hold however many entries HASH-TABLE can hold without
429    having to be grown."
430   (hash-table-rehash-trigger hash-table))
431
432 #!+sb-doc
433 (setf (fdocumentation 'hash-table-test 'function)
434       "Return the test HASH-TABLE was created with.")
435
436 #!+sb-doc
437 (setf (fdocumentation 'hash-table-weakness 'function)
438       "Return the WEAKNESS of HASH-TABLE which is one of NIL, :KEY,
439 :VALUE, :KEY-AND-VALUE, :KEY-OR-VALUE.")
440
441 ;;; Called when we detect circular chains in a hash-table.
442 (defun signal-corrupt-hash-table (hash-table)
443   (error "Corrupt NEXT-chain in ~A. This is probably caused by ~
444 multiple threads accessing the same hash-table without locking."
445          hash-table))
446
447 \f
448 ;;;; accessing functions
449
450 ;;; Make new vectors for the table, extending the table based on the
451 ;;; rehash-size.
452 (defun rehash (table)
453   (declare (type hash-table table))
454   (aver *gc-inhibit*)
455   (let* ((old-kv-vector (hash-table-table table))
456          (old-next-vector (hash-table-next-vector table))
457          (old-hash-vector (hash-table-hash-vector table))
458          (old-size (length old-next-vector))
459          (new-size
460           (power-of-two-ceiling
461            (let ((rehash-size (hash-table-rehash-size table)))
462              (etypecase rehash-size
463                (fixnum
464                 (+ rehash-size old-size))
465                (float
466                 (the index (truncate (* rehash-size old-size))))))))
467          (new-kv-vector (make-array (* 2 new-size)
468                                     :initial-element +empty-ht-slot+))
469          (new-next-vector
470           (make-array new-size
471                       :element-type '(unsigned-byte #.sb!vm:n-word-bits)
472                       :initial-element 0))
473          (new-hash-vector
474           (when old-hash-vector
475             (make-array new-size
476                         :element-type '(unsigned-byte #.sb!vm:n-word-bits)
477                         :initial-element +magic-hash-vector-value+)))
478          (new-length new-size)
479          (new-index-vector
480           (make-array new-length
481                       :element-type '(unsigned-byte #.sb!vm:n-word-bits)
482                       :initial-element 0)))
483     (declare (type index new-size new-length old-size))
484
485     ;; Disable GC tricks on the OLD-KV-VECTOR.
486     (set-header-data old-kv-vector sb!vm:vector-normal-subtype)
487
488     ;; Non-empty weak hash tables always need GC support.
489     (when (and (hash-table-weakness table) (plusp (hash-table-count table)))
490       (set-header-data new-kv-vector sb!vm:vector-valid-hashing-subtype))
491
492     ;; FIXME: here and in several other places in the hash table code,
493     ;; loops like this one are used when FILL or REPLACE would be
494     ;; appropriate.  why are standard CL functions not used?
495     ;; Performance issues?  General laziness?  -- NJF, 2004-03-10
496
497     ;; Copy over the kv-vector. The element positions should not move
498     ;; in case there are active scans.
499     (dotimes (i (* old-size 2))
500       (declare (type index i))
501       (setf (aref new-kv-vector i) (aref old-kv-vector i)))
502
503     ;; Copy over the hash-vector.
504     (when old-hash-vector
505       (dotimes (i old-size)
506         (setf (aref new-hash-vector i) (aref old-hash-vector i))))
507
508     (setf (hash-table-next-free-kv table) 0)
509     ;; Rehash all the entries; last to first so that after the pushes
510     ;; the chains are first to last.
511     (do ((i (1- new-size) (1- i)))
512         ((zerop i))
513       (declare (type index/2 i))
514       (let ((key (aref new-kv-vector (* 2 i)))
515             (value (aref new-kv-vector (1+ (* 2 i)))))
516         (cond ((and (eq key +empty-ht-slot+)
517                     (eq value +empty-ht-slot+))
518                ;; Slot is empty, push it onto the free list.
519                (setf (aref new-next-vector i)
520                      (hash-table-next-free-kv table))
521                (setf (hash-table-next-free-kv table) i))
522               ((and new-hash-vector
523                     (not (= (aref new-hash-vector i)
524                             +magic-hash-vector-value+)))
525                ;; Can use the existing hash value (not EQ based)
526                (let* ((hashing (aref new-hash-vector i))
527                       (index (index-for-hashing hashing new-length))
528                       (next (aref new-index-vector index)))
529                  (declare (type index index)
530                           (type hash hashing))
531                  ;; Push this slot into the next chain.
532                  (setf (aref new-next-vector i) next)
533                  (setf (aref new-index-vector index) i)))
534               (t
535                ;; EQ base hash.
536                ;; Enable GC tricks.
537                (set-header-data new-kv-vector
538                                 sb!vm:vector-valid-hashing-subtype)
539                (let* ((hashing (pointer-hash key))
540                       (index (index-for-hashing hashing new-length))
541                       (next (aref new-index-vector index)))
542                  (declare (type index index)
543                           (type hash hashing))
544                  ;; Push this slot onto the next chain.
545                  (setf (aref new-next-vector i) next)
546                  (setf (aref new-index-vector index) i))))))
547     (setf (hash-table-table table) new-kv-vector)
548     (setf (hash-table-index-vector table) new-index-vector)
549     (setf (hash-table-next-vector table) new-next-vector)
550     (setf (hash-table-hash-vector table) new-hash-vector)
551     ;; Fill the old kv-vector with 0 to help the conservative GC. Even
552     ;; if nothing else were zeroed, it's important to clear the
553     ;; special first cells in old-kv-vector.
554     (fill old-kv-vector 0)
555     (setf (hash-table-rehash-trigger table) new-size)
556     (setf (hash-table-needs-rehash-p table) nil))
557   (values))
558
559 ;;; Use the same size as before, re-using the vectors.
560 (defun rehash-without-growing (table)
561   (declare (type hash-table table))
562   (aver *gc-inhibit*)
563   (let* ((kv-vector (hash-table-table table))
564          (next-vector (hash-table-next-vector table))
565          (hash-vector (hash-table-hash-vector table))
566          (size (length next-vector))
567          (index-vector (hash-table-index-vector table))
568          (length (length index-vector)))
569     (declare (type index size length))
570
571     ;; Non-empty weak hash tables always need GC support.
572     (unless (and (hash-table-weakness table) (plusp (hash-table-count table)))
573       ;; Disable GC tricks, they will be re-enabled during the re-hash
574       ;; if necessary.
575       (set-header-data kv-vector sb!vm:vector-normal-subtype))
576
577     ;; Rehash all the entries.
578     (setf (hash-table-next-free-kv table) 0)
579     (dotimes (i size)
580       (setf (aref next-vector i) 0))
581     (dotimes (i length)
582       (setf (aref index-vector i) 0))
583     (do ((i (1- size) (1- i)))
584         ((zerop i))
585       (declare (type index/2 i))
586       (let ((key (aref kv-vector (* 2 i)))
587             (value (aref kv-vector (1+ (* 2 i)))))
588         (cond ((and (eq key +empty-ht-slot+)
589                     (eq value +empty-ht-slot+))
590                ;; Slot is empty, push it onto free list.
591                (setf (aref next-vector i) (hash-table-next-free-kv table))
592                (setf (hash-table-next-free-kv table) i))
593               ((and hash-vector (not (= (aref hash-vector i)
594                                         +magic-hash-vector-value+)))
595                ;; Can use the existing hash value (not EQ based)
596                (let* ((hashing (aref hash-vector i))
597                       (index (index-for-hashing hashing length))
598                       (next (aref index-vector index)))
599                  (declare (type index index))
600                  ;; Push this slot into the next chain.
601                  (setf (aref next-vector i) next)
602                  (setf (aref index-vector index) i)))
603               (t
604                ;; EQ base hash.
605                ;; Enable GC tricks.
606                (set-header-data kv-vector sb!vm:vector-valid-hashing-subtype)
607                (let* ((hashing (pointer-hash key))
608                       (index (index-for-hashing hashing length))
609                       (next (aref index-vector index)))
610                  (declare (type index index)
611                           (type hash hashing))
612                  ;; Push this slot into the next chain.
613                  (setf (aref next-vector i) next)
614                  (setf (aref index-vector index) i)))))))
615   ;; Clear the rehash bit only at the very end, otherwise another thread
616   ;; might see a partially rehashed table as a normal one.
617   (setf (hash-table-needs-rehash-p table) nil)
618   (values))
619
620 (declaim (inline maybe-rehash))
621 (defun maybe-rehash (hash-table ensure-free-slot-p)
622   (when (hash-table-weakness hash-table)
623     (aver *gc-inhibit*))
624   (flet ((rehash-p ()
625            (and ensure-free-slot-p
626                 (zerop (hash-table-next-free-kv hash-table))))
627          (rehash-without-growing-p ()
628            (hash-table-needs-rehash-p hash-table)))
629     (declare (inline rehash-p rehash-without-growing-p))
630     (cond ((rehash-p)
631            ;; Use recursive locks since for weak tables the lock has
632            ;; already been acquired. GC must be inhibited to prevent
633            ;; the GC from seeing a rehash in progress.
634            (sb!thread::with-recursive-system-lock
635                ((hash-table-lock hash-table) :without-gcing t)
636              ;; Repeat the condition inside the lock to ensure that if
637              ;; two reader threads enter MAYBE-REHASH at the same time
638              ;; only one rehash is performed.
639              (when (rehash-p)
640                (rehash hash-table))))
641           ((rehash-without-growing-p)
642            (sb!thread::with-recursive-system-lock
643                ((hash-table-lock hash-table) :without-gcing t)
644              (when (rehash-without-growing-p)
645                (rehash-without-growing hash-table)))))))
646
647 (declaim (inline update-hash-table-cache))
648 (defun update-hash-table-cache (hash-table index)
649   (unless (hash-table-weakness hash-table)
650     (setf (hash-table-cache hash-table) index)))
651
652 (defmacro with-hash-table-locks ((hash-table
653                                   &key (operation :write) inline pin
654                                   (synchronized `(hash-table-synchronized-p ,hash-table)))
655                                  &body body)
656   (declare (type (member :read :write) operation))
657   (with-unique-names (body-fun)
658     `(flet ((,body-fun ()
659               (with-concurrent-access-check ,hash-table ,operation
660                 (locally (declare (inline ,@inline))
661                   ,@body))))
662        (if (hash-table-weakness ,hash-table)
663            (sb!thread::with-recursive-system-lock
664                ((hash-table-lock ,hash-table) :without-gcing t)
665              (,body-fun))
666            (with-pinned-objects ,pin
667              (if ,synchronized
668                  ;; We use a "system" lock here because it is very
669                  ;; slightly faster, as it doesn't re-enable
670                  ;; interrupts.
671                  (sb!thread::with-recursive-system-lock
672                      ((hash-table-lock ,hash-table))
673                    (,body-fun))
674                  (,body-fun)))))))
675
676 (defun gethash (key hash-table &optional default)
677   #!+sb-doc
678   "Finds the entry in HASH-TABLE whose key is KEY and returns the
679 associated value and T as multiple values, or returns DEFAULT and NIL
680 if there is no such entry. Entries can be added using SETF."
681   (declare (type hash-table hash-table)
682            (values t (member t nil)))
683   (gethash3 key hash-table default))
684
685 (declaim (maybe-inline %gethash3))
686 (defun %gethash3 (key hash-table default)
687   (declare (type hash-table hash-table)
688            (optimize speed)
689            (values t (member t nil)))
690   (tagbody
691    start
692      (let ((start-epoch sb!kernel::*gc-epoch*))
693        (macrolet ((result (value foundp)
694                     ;; When the table has multiple concurrent readers,
695                     ;; it's possible that there was a GC after this
696                     ;; thread called MAYBE-REHASH from %GETHASH3, and
697                     ;; some other thread then rehashed the table. If
698                     ;; this happens, we might not find the key even if
699                     ;; it's in the table. To protect against this,
700                     ;; redo the lookup if the GC epoch counter has changed.
701                     ;; -- JES,  2007-09-30
702                     `(if (and (not ,foundp)
703                               (not (eq start-epoch sb!kernel::*gc-epoch*)))
704                          (go start)
705                          (return-from %gethash3 (values ,value ,foundp))))
706                   (overflow ()
707                     ;; The next-vector chain is circular. This is caused
708                     ;; caused by thread-unsafe mutations of the table.
709                     `(signal-corrupt-hash-table hash-table)))
710          (maybe-rehash hash-table nil)
711          ;; Note that it's OK for a GC + a REHASH-WITHOUT-GROWING to
712          ;; be triggered by another thread after this point, since the
713          ;; GC epoch check will catch it.
714          (let ((cache (hash-table-cache hash-table))
715                (table (hash-table-table hash-table)))
716            ;; First check the cache.  Use EQ here for speed.
717            (if (and cache
718                     (< cache (length table))
719                     (eq (aref table cache) key))
720                (let ((value (aref table (1+ cache))))
721                  (result value t))
722                ;; Search for key in the hash table.
723                (multiple-value-bind (hashing eq-based)
724                    (funcall (hash-table-hash-fun hash-table) key)
725                  (declare (type hash hashing))
726                  (let* ((index-vector (hash-table-index-vector hash-table))
727                         (length (length index-vector))
728                         (index (index-for-hashing hashing length))
729                         (next (aref index-vector index))
730                         (next-vector (hash-table-next-vector hash-table))
731                         (hash-vector (hash-table-hash-vector hash-table))
732                         (test-fun (hash-table-test-fun hash-table)))
733                    (declare (type index index))
734                    ;; Search next-vector chain for a matching key.
735                    (if (or eq-based (not hash-vector))
736                        (do ((next next (aref next-vector next))
737                             (i 0 (1+ i)))
738                            ((zerop next) (result default nil))
739                          (declare (type index/2 next i))
740                          (when (> i length)
741                            (overflow))
742                          (when (eq key (aref table (* 2 next)))
743                            (update-hash-table-cache hash-table (* 2 next))
744                            (let ((value (aref table (1+ (* 2 next)))))
745                              (result value t))))
746                        (do ((next next (aref next-vector next))
747                             (i 0 (1+ i)))
748                            ((zerop next) (result default nil))
749                          (declare (type index/2 next i))
750                          (when (> i length)
751                            (overflow))
752                          (when (and (= hashing (aref hash-vector next))
753                                     (funcall test-fun key
754                                              (aref table (* 2 next))))
755                            ;; Found.
756                            (update-hash-table-cache hash-table (* 2 next))
757                            (let ((value (aref table (1+ (* 2 next)))))
758                              (result value t)))))))))))))
759
760 (defun gethash3 (key hash-table default)
761   "Three argument version of GETHASH"
762   (declare (type hash-table hash-table))
763   (with-hash-table-locks (hash-table :operation :read :inline (%gethash3)
764                                      :pin (key))
765     (%gethash3 key hash-table default)))
766
767 ;;; so people can call #'(SETF GETHASH)
768 (defun (setf gethash) (new-value key table &optional default)
769   (declare (ignore default))
770   (%puthash key table new-value))
771
772 (declaim (maybe-inline %%puthash))
773 (defun %%puthash (key hash-table value)
774   (declare (optimize speed))
775   ;; We need to rehash here so that a current key can be found if it
776   ;; exists. Check that there is room for one more entry. May not be
777   ;; needed if the key is already present.
778   (maybe-rehash hash-table t)
779   ;; Search for key in the hash table.
780   (multiple-value-bind (hashing eq-based)
781       (funcall (hash-table-hash-fun hash-table) key)
782     (declare (type hash hashing))
783     (let* ((index-vector (hash-table-index-vector hash-table))
784            (length (length index-vector))
785            (index (index-for-hashing hashing length))
786            (next (aref index-vector index))
787            (kv-vector (hash-table-table hash-table))
788            (next-vector (hash-table-next-vector hash-table))
789            (hash-vector (hash-table-hash-vector hash-table))
790            (test-fun (hash-table-test-fun hash-table)))
791       (declare (type index index next))
792       (when (hash-table-weakness hash-table)
793         (set-header-data kv-vector sb!vm:vector-valid-hashing-subtype))
794       (cond ((or eq-based (not hash-vector))
795              (when eq-based
796                (set-header-data kv-vector
797                                 sb!vm:vector-valid-hashing-subtype))
798              ;; Search next-vector chain for a matching key.
799              (do ((next next (aref next-vector next))
800                   (i 0 (1+ i)))
801                  ((zerop next))
802                (declare (type index/2 next i))
803                (when (> i length)
804                  (signal-corrupt-hash-table hash-table))
805                (when (eq key (aref kv-vector (* 2 next)))
806                  ;; Found, just replace the value.
807                  (update-hash-table-cache hash-table (* 2 next))
808                  (setf (aref kv-vector (1+ (* 2 next))) value)
809                  (return-from %%puthash value))))
810             (t
811              ;; Search next-vector chain for a matching key.
812              (do ((next next (aref next-vector next))
813                   (i 0 (1+ i)))
814                  ((zerop next))
815                (declare (type index/2 next i))
816                (when (> i length)
817                  (signal-corrupt-hash-table hash-table))
818                (when (and (= hashing (aref hash-vector next))
819                           (funcall test-fun key
820                                    (aref kv-vector (* 2 next))))
821                  ;; Found, just replace the value.
822                  (update-hash-table-cache hash-table (* 2 next))
823                  (setf (aref kv-vector (1+ (* 2 next))) value)
824                  (return-from %%puthash value)))))
825       ;; Pop a KV slot off the free list
826       (let ((free-kv-slot (hash-table-next-free-kv hash-table)))
827         (declare (type index/2 free-kv-slot))
828         ;; Double-check for overflow.
829         (aver (not (zerop free-kv-slot)))
830         (setf (hash-table-next-free-kv hash-table)
831               (aref next-vector free-kv-slot))
832         (incf (hash-table-number-entries hash-table))
833         (update-hash-table-cache hash-table (* 2 free-kv-slot))
834         (setf (aref kv-vector (* 2 free-kv-slot)) key)
835         (setf (aref kv-vector (1+ (* 2 free-kv-slot))) value)
836         ;; Setup the hash-vector if necessary.
837         (when hash-vector
838           (if (not eq-based)
839               (setf (aref hash-vector free-kv-slot) hashing)
840               (aver (= (aref hash-vector free-kv-slot)
841                        +magic-hash-vector-value+))))
842         ;; Push this slot into the next chain.
843         (setf (aref next-vector free-kv-slot) next)
844         (setf (aref index-vector index) free-kv-slot)))
845     value))
846
847 (defun %puthash (key hash-table value)
848   (declare (type hash-table hash-table))
849   (aver (hash-table-index-vector hash-table))
850   (macrolet ((put-it (lockedp)
851                `(let ((cache (hash-table-cache hash-table))
852                       (kv-vector (hash-table-table hash-table)))
853                   ;; Check the cache
854                   (if (and cache
855                            (< cache (length kv-vector))
856                            (eq (aref kv-vector cache) key))
857                       ;; If cached, just store here
858                       (setf (aref kv-vector (1+ cache)) value)
859                       ;; Otherwise do things the hard way
860                       ,(if lockedp
861                            '(%%puthash key hash-table value)
862                            '(with-hash-table-locks
863                              (hash-table :inline (%%puthash) :pin (key)
864                               :synchronized nil)
865                              (%%puthash key hash-table value)))))))
866     (if (hash-table-synchronized-p hash-table)
867         (with-hash-table-locks (hash-table :pin (key) :synchronized t)
868           (put-it t))
869         (put-it nil))))
870
871 (declaim (maybe-inline %remhash))
872 (defun %remhash (key hash-table)
873   ;; We need to rehash here so that a current key can be found if it
874   ;; exists.
875   ;;
876   ;; Note that if a GC happens after MAYBE-REHASH returns and another
877   ;; thread the accesses the table (triggering a rehash), we might not
878   ;; find the key even if it is in the table. But that's ok, since the
879   ;; only concurrent case that we safely allow is multiple readers
880   ;; with no writers.
881   (maybe-rehash hash-table nil)
882   ;; Search for key in the hash table.
883   (multiple-value-bind (hashing eq-based)
884       (funcall (hash-table-hash-fun hash-table) key)
885     (declare (type hash hashing))
886     (let* ((index-vector (hash-table-index-vector hash-table))
887            (length (length index-vector))
888            (index (index-for-hashing hashing length))
889            (next (aref index-vector index))
890            (table (hash-table-table hash-table))
891            (next-vector (hash-table-next-vector hash-table))
892            (hash-vector (hash-table-hash-vector hash-table))
893            (test-fun (hash-table-test-fun hash-table)))
894       (declare (type index index)
895                (type index/2 next))
896       (flet ((clear-slot (chain-vector prior-slot-location slot-location)
897                (declare (type index/2 slot-location))
898                ;; Mark slot as empty.
899                (setf (aref table (* 2 slot-location)) +empty-ht-slot+
900                      (aref table (1+ (* 2 slot-location))) +empty-ht-slot+)
901                ;; Update the prior pointer in the chain to skip this.
902                (setf (aref chain-vector prior-slot-location)
903                      (aref next-vector slot-location))
904                ;; Push KV slot onto free chain.
905                (setf (aref next-vector slot-location)
906                      (hash-table-next-free-kv hash-table))
907                (setf (hash-table-next-free-kv hash-table) slot-location)
908                (when hash-vector
909                  (setf (aref hash-vector slot-location)
910                        +magic-hash-vector-value+))
911                ;; On parallel accesses this may turn out to be a
912                ;; type-error, so don't turn down the safety!
913                (decf (hash-table-number-entries hash-table))
914                t))
915         (cond ((zerop next)
916                nil)
917               ((if (or eq-based (not hash-vector))
918                    (eq key (aref table (* 2 next)))
919                    (and (= hashing (aref hash-vector next))
920                         (funcall test-fun key (aref table (* 2 next)))))
921                (clear-slot index-vector index next))
922               ;; Search next-vector chain for a matching key.
923               ((or eq-based (not hash-vector))
924                ;; EQ based
925                (do ((prior next next)
926                     (i 0 (1+ i))
927                     (next (aref next-vector next) (aref next-vector next)))
928                    ((zerop next) nil)
929                  (declare (type index next))
930                  (when (> i length)
931                    (signal-corrupt-hash-table hash-table))
932                  (when (eq key (aref table (* 2 next)))
933                    (return-from %remhash (clear-slot next-vector prior next)))))
934               (t
935                ;; not EQ based
936                (do ((prior next next)
937                     (i 0 (1+ i))
938                     (next (aref next-vector next) (aref next-vector next)))
939                    ((zerop next) nil)
940                  (declare (type index/2 next))
941                  (when (> i length)
942                    (signal-corrupt-hash-table hash-table))
943                  (when (and (= hashing (aref hash-vector next))
944                             (funcall test-fun key (aref table (* 2 next))))
945                    (return-from %remhash
946                      (clear-slot next-vector prior next))))))))))
947
948 (defun remhash (key hash-table)
949   #!+sb-doc
950   "Remove the entry in HASH-TABLE associated with KEY. Return T if
951 there was such an entry, or NIL if not."
952   (declare (type hash-table hash-table)
953            (values (member t nil)))
954   (with-hash-table-locks (hash-table :inline (%remhash) :pin (key))
955     ;; For now, just clear the cache
956     (setf (hash-table-cache hash-table) nil)
957     (%remhash key hash-table)))
958
959 (defun clrhash (hash-table)
960   #!+sb-doc
961   "This removes all the entries from HASH-TABLE and returns the hash
962 table itself."
963   (when (plusp (hash-table-number-entries hash-table))
964     (with-hash-table-locks (hash-table)
965       (let* ((kv-vector (hash-table-table hash-table))
966              (next-vector (hash-table-next-vector hash-table))
967              (hash-vector (hash-table-hash-vector hash-table))
968              (size (length next-vector))
969              (index-vector (hash-table-index-vector hash-table)))
970         ;; Disable GC tricks.
971         (set-header-data kv-vector sb!vm:vector-normal-subtype)
972         ;; Mark all slots as empty by setting all keys and values to magic
973         ;; tag.
974         (aver (eq (aref kv-vector 0) hash-table))
975         (fill kv-vector +empty-ht-slot+ :start 2)
976         ;; Set up the free list, all free.
977         (do ((i 1 (1+ i)))
978             ((>= i (1- size)))
979           (setf (aref next-vector i) (1+ i)))
980         (setf (aref next-vector (1- size)) 0)
981         (setf (hash-table-next-free-kv hash-table) 1)
982         ;; Clear the index-vector.
983         (fill index-vector 0)
984         ;; Clear the hash-vector.
985         (when hash-vector
986           (fill hash-vector +magic-hash-vector-value+)))
987       (setf (hash-table-cache hash-table) nil)
988       (setf (hash-table-number-entries hash-table) 0)))
989   hash-table)
990
991 \f
992 ;;;; MAPHASH
993
994 ;;; FIXME: This should be made into a compiler transform for two reasons:
995 ;;;   1. It would then be available for compiling the entire system,
996 ;;;      not only parts of the system which are defined after DEFUN MAPHASH.
997 ;;;   2. It could be conditional on compilation policy, so that
998 ;;;      it could be compiled as a full call instead of an inline
999 ;;;      expansion when SPACE>SPEED.
1000 (declaim (inline maphash))
1001 (defun maphash (function-designator hash-table)
1002   #!+sb-doc
1003   "For each entry in HASH-TABLE, call the designated two-argument function on
1004 the key and value of the entry. Return NIL.
1005
1006 Consequences are undefined if HASH-TABLE is mutated during the call to
1007 MAPHASH, except for changing or removing elements corresponding to the
1008 current key. The applies to all threads, not just the current one --
1009 even for synchronized hash-tables. If the table may be mutated by
1010 another thread during iteration, use eg. SB-EXT:WITH-LOCKED-HASH-TABLE
1011 to protect the MAPHASH call."
1012   ;; This essentially duplicates WITH-HASH-TABLE-ITERATOR, so
1013   ;; any changes here should be reflected there as well.
1014   (let ((fun (%coerce-callable-to-fun function-designator))
1015         (size (length (hash-table-next-vector hash-table))))
1016     (declare (type function fun))
1017     (do ((i 1 (1+ i)))
1018         ((>= i size))
1019       (declare (type index/2 i))
1020       (let* ((kv-vector (hash-table-table hash-table))
1021              (key (aref kv-vector (* 2 i)))
1022              (value (aref kv-vector (1+ (* 2 i)))))
1023         ;; We are running without locking or WITHOUT-GCING. For a weak
1024         ;; :VALUE hash table it's possible that the GC hit after KEY
1025         ;; was read and now the entry is gone. So check if either the
1026         ;; key or the value is empty.
1027         (unless (or (eq key +empty-ht-slot+)
1028                     (eq value +empty-ht-slot+))
1029           (funcall fun key value))))))
1030 \f
1031 ;;;; methods on HASH-TABLE
1032
1033 ;;; Return a list of keyword args and values to use for MAKE-HASH-TABLE
1034 ;;; when reconstructing HASH-TABLE.
1035 (defun %hash-table-ctor-args (hash-table)
1036   `(:test             ',(hash-table-test             hash-table)
1037     :size             ',(hash-table-size             hash-table)
1038     :rehash-size      ',(hash-table-rehash-size      hash-table)
1039     :rehash-threshold ',(hash-table-rehash-threshold hash-table)
1040     :weakness         ',(hash-table-weakness         hash-table)))
1041
1042 ;;; Return an association list representing the same data as HASH-TABLE.
1043 (defun %hash-table-alist (hash-table)
1044   (let ((result nil))
1045     (maphash (lambda (key value)
1046                (push (cons key value) result))
1047              hash-table)
1048     result))
1049
1050 ;;; Stuff an association list into HASH-TABLE. Return the hash table,
1051 ;;; so that we can use this for the *PRINT-READABLY* case in
1052 ;;; PRINT-OBJECT (HASH-TABLE T) without having to worry about LET
1053 ;;; forms and readable gensyms and stuff.
1054 (defun %stuff-hash-table (hash-table alist)
1055   (dolist (x alist)
1056     (setf (gethash (car x) hash-table) (cdr x)))
1057   hash-table)
1058
1059 (def!method print-object ((hash-table hash-table) stream)
1060   (declare (type stream stream))
1061   (cond ((or (not *print-readably*) (not *read-eval*))
1062          (print-unreadable-object (hash-table stream :type t :identity t)
1063            (format stream
1064                    ":TEST ~S :COUNT ~S~@[ :WEAKNESS ~S~]"
1065                    (hash-table-test hash-table)
1066                    (hash-table-count hash-table)
1067                    (hash-table-weakness hash-table))))
1068         (t
1069          (write-string "#." stream)
1070          (write `(%stuff-hash-table (make-hash-table ,@(%hash-table-ctor-args
1071                                                           hash-table))
1072                                      ',(%hash-table-alist hash-table))
1073                 :stream stream))))
1074
1075 (def!method make-load-form ((hash-table hash-table) &optional environment)
1076   (declare (ignore environment))
1077   (values `(make-hash-table ,@(%hash-table-ctor-args hash-table))
1078           `(%stuff-hash-table ,hash-table ',(%hash-table-alist hash-table))))
1079
1080 \f