35
36:- module(hashtable,
37 [ ht_new/1, 38 ht_is_hashtable/1, 39 ht_size/2, 40
41 ht_put/3, 42 ht_update/4, 43 ht_put_new/3, 44 ht_put/5, 45 ht_del/3, 46
47 ht_get/3, 48 ht_gen/3, 49 ht_pairs/2, 50 ht_keys/2 51 ]). 52:- autoload(library(error), [must_be/2]).
80ht_new(ht(0,0,[](_))).
86ht_is_hashtable(HT) :-
87 nonvar(HT),
88 HT = ht(Load, Size, Buckets),
89 integer(Load),
90 integer(Size),
91 compound_name_arity(Buckets, [], Arity),
92 Arity =:= Size*2+1.
98ht_size(ht(Count, _Size, _Buckets), Count).
104ht_put(HT, Key, Value) :-
105 must_be(nonvar, Key),
106 ht_put(HT, Key, Value, _, _, _).
113ht_put_new(HT, Key, Value) :-
114 must_be(nonvar, Key),
115 ht_put(HT, Key, Value, _, _, true).
131ht_update(HT, Key, Old, New) :-
132 must_be(nonvar, Key),
133 ht_put(HT, Key, New, _, Old, false).
144ht_put(HT, Key, Value, IfNew, Old) :-
145 must_be(nonvar, Key),
146 ht_put(HT, Key, Value, IfNew, Old, _).
147
148ht_put(HT, Key, Value, IfNew, Old, IsNew) :-
149 HT = ht(Load, Size, Buckets),
150 ( Load >= Size//2
151 -> ht_resize(HT),
152 ht_put(HT, Key, Value, IfNew, Old, IsNew)
153 ; variant_hash(Key, I0),
154 I is I0 mod Size,
155 put_(Buckets, I, Size, Key, Old, IfNew, Value, IsNew),
156 ( IsNew == true
157 -> Load2 is Load+1,
158 setarg(1, HT, Load2)
159 ; true
160 )
161 ).
162
163put_(Buckets, I, Size, Key, Old, IfNew, Value, IsNew) :-
164 ht_kv(Buckets, I, K, V),
165 ( var(K)
166 -> IsNew = true,
167 Old = IfNew,
168 K = Key,
169 V = Value
170 ; K == Key
171 -> IsNew = false,
172 Old = V,
173 ht_put_v(Buckets, I, Value)
174 ; I2 is (I+1) mod Size,
175 put_(Buckets, I2, Size, Key, Old, IfNew, Value, IsNew)
176 ).
177
178ht_resize(HT) :-
179 HT = ht(_Load, Size, Buckets),
180 NewSize is max(4, Size*2),
181 NewArity is NewSize*2+1,
182 compound_name_arity(NewBuckets, [], NewArity),
183 copy_members(0, Size, Buckets, NewSize, NewBuckets),
184 setarg(2, HT, NewSize),
185 setarg(3, HT, NewBuckets).
186
187copy_members(I, OSize, OBuckets, NSize, NBuckets) :-
188 I < OSize,
189 !,
190 ht_kv(OBuckets, I, K, V),
191 ( nonvar(K)
192 -> variant_hash(K, I0),
193 NI is I0 mod NSize,
194 copy_(NBuckets, NI, NSize, K, V)
195 ; true
196 ),
197 I2 is I+1,
198 copy_members(I2, OSize, OBuckets, NSize, NBuckets).
199copy_members(_, _, _, _, _).
200
201copy_(Buckets, I, Size, Key, Value) :-
202 ht_kv(Buckets, I, K, V),
203 ( var(K)
204 -> K = Key,
205 V = Value
206 ; I2 is (I+1) mod Size,
207 copy_(Buckets, I2, Size, Key, Value)
208 ).
216ht_del(HT, Key, Value) :-
217 must_be(nonvar, Key),
218 HT = ht(Load, Size, Buckets),
219 Load > 0,
220 variant_hash(Key, I0),
221 I is I0 mod Size,
222 del_(Buckets, I, Size, Key, Value),
223 Load2 is Load - 1,
224 setarg(1, HT, Load2).
225
226del_(Buckets, I, Size, Key, Value) :-
227 ht_kv(Buckets, I, K, V),
228 ( var(K)
229 -> fail
230 ; K == Key
231 -> V = Value,
232 ht_put_kv(Buckets, I, _, _),
233 del_shift(Buckets, I, I, Size)
234 ; I2 is (I+1) mod Size,
235 del_(Buckets, I2, Size, Key, Value)
236 ).
237
238del_shift(Buckets, I0, J, Size) :-
239 I is (I0+1) mod Size,
240 ht_kv(Buckets, I, K, V),
241 ( var(K)
242 -> true
243 ; variant_hash(K, Hash),
244 R is Hash mod Size,
245 ( ( I >= R, R > J
246 ; R > J, J > I
247 ; J > I, I >= R
248 )
249 -> del_shift(Buckets, I, J, Size)
250 ; ht_put_kv(Buckets, J, K, V),
251 ht_put_kv(Buckets, I, _, _),
252 del_shift(Buckets, I, I, Size)
253 )
254 ).
261ht_get(ht(Load, Size, Buckets), Key, Value) :-
262 Load > 0,
263 must_be(nonvar, Key),
264 variant_hash(Key, I0),
265 I is I0 mod Size,
266 get_(Buckets, I, Size, Key, Value).
267
268get_(Buckets, I, Size, Key, Value) :-
269 ht_kv(Buckets, I, K, V),
270 ( Key == K
271 -> Value = V
272 ; nonvar(K)
273 -> I2 is (I+1) mod Size,
274 get_(Buckets, I2, Size, Key, Value)
275 ).
276
277ht_k(Buckets, I, K) :-
278 IK is I*2+1,
279 arg(IK, Buckets, K).
280
281ht_kv(Buckets, I, K, V) :-
282 IK is I*2+1,
283 IV is IK+1,
284 arg(IK, Buckets, K),
285 arg(IV, Buckets, V).
286
287ht_put_kv(Buckets, I, K, V) :-
288 IK is I*2+1,
289 IV is IK+1,
290 setarg(IK, Buckets, K),
291 setarg(IV, Buckets, V).
292
293ht_put_v(Buckets, I, V) :-
294 IV is I*2+2,
295 setarg(IV, Buckets, V).
302ht_gen(HT, Key, Value) :-
303 HT = ht(_, Size, Buckets),
304 End is Size - 1,
305 between(0, End, I),
306 ht_kv(Buckets, I, K, V),
307 nonvar(K),
308 K = Key,
309 V = Value.
316ht_pairs(HT, Pairs) :-
317 ht_is_hashtable(HT),
318 !,
319 HT = ht(_Load, Size, Buckets),
320 pairs_(0, Size, Buckets, Pairs0),
321 sort(Pairs0, Pairs).
322ht_pairs(HT, Pairs) :-
323 must_be(list(pair), Pairs),
324 ht_new(HT),
325 ht_fill(Pairs, HT).
326
327pairs_(I, Size, Buckets, Pairs) :-
328 ( I < Size
329 -> ht_kv(Buckets, I, K, V),
330 ( nonvar(K)
331 -> Pairs = [K-V|T],
332 I2 is I+1,
333 pairs_(I2, Size, Buckets, T)
334 ; I2 is I+1,
335 pairs_(I2, Size, Buckets, Pairs)
336 )
337 ; Pairs = []
338 ).
339
340ht_fill([], _).
341ht_fill([K-V|T], HT) :-
342 ht_put(HT, K, V),
343 ht_fill(T, HT).
349ht_keys(HT, Keys) :-
350 HT = ht(_Load, Size, Buckets),
351 keys_(0, Size, Buckets, Keys0),
352 sort(Keys0, Keys).
353
354keys_(I, Size, Buckets, Keys) :-
355 ( I < Size
356 -> ht_k(Buckets, I, K),
357 ( nonvar(K)
358 -> Keys = [K|T],
359 I2 is I+1,
360 keys_(I2, Size, Buckets, T)
361 ; I2 is I+1,
362 keys_(I2, Size, Buckets, Keys)
363 )
364 ; Keys = []
365 )
Hash tables
Hash tables are one of the many key-value representations available to SWI-Prolog.
This module implements a hash table as a mutable and backtrackable data structure. The hash table is implemented as a closed hash table, where the buckets array is implemented using an unbounded arity compound term. Elements in this array are manipulated using setarg/3.
Hash tables allow for any Prolog data types as keys or values, except that the key cannot be a variable. Applications that require a plain variable as key can do so by wrapping all keys in a compound, e.g.,
k(Var)
. */