1/* 2 This file is part of the hashtbl library. 3 4 hashtbl is free software; you can redistribute it and/or modify it under 5 the terms of the GNU LGPL. See README.md for details. 6 */ 7 8:- module(utils, [ 9 hashtbl_default_size/1, 10 hashtbl_bucket/5, 11 hashtbl_load/2, 12 hashtbl_buckets/2, 13 hashtbl_get/3, 14 hashtbl_get_all/3, 15 hashtbl_enumerate/3, 16 hashtbl_to_list/2, 17 hashtbl_map/3, 18 hashtbl_fold/4, 19 hashtbl_iter/2, 20 key_value_cons/4 21 ]).
54hashtbl_default_size(31).
63hashtbl_bucket(Table, Key, BucketTerm, BucketIdx, Bucket) :-
64 arg(2, Table, BucketTerm),
65 functor(BucketTerm, buckets, Buckets),
66 term_hash(Key, Hash),
67 BucketIdx is Hash rem Buckets + 1,
68 arg(BucketIdx, BucketTerm, Bucket).
73hashtbl_load(Table, Load) :-
74 arg(1, Table, meta(Load)).
79hashtbl_buckets(Table, Buckets) :-
80 arg(2, Table, BucketTerm),
81 functor(BucketTerm, buckets, Buckets).
nb_hashtbl_get(Table, Key, _)
to test whether Key is
present in Table.
89hashtbl_get(Table, Key, Value) :-
90 hashtbl_bucket(Table, Key, _BucketTerm, _BucketIdx, Bucket),
91 memberchk(Key-[Value|_], Bucket).
99hashtbl_get_all(Table, Key, Value) :-
100 hashtbl_bucket(Table, Key, _BucketTerm, _BucketIdx, Bucket),
101 member(Key-Values, Bucket),
102 member(Value, Values).
If Key is ground, this behaves like hashtbl_get_all/3 for that Key. However, hashtbl_get_all/3 is more efficient in this case.
113hashtbl_enumerate(Table, Key, Value) :-
114 arg(2, Table, BucketTerm),
115 arg(_Idx, BucketTerm, Bucket),
116 member(Key-Values, Bucket),
117 member(Value, Values).
123hashtbl_to_list(Table, Pairs) :-
124 hashtbl_fold(Table, key_value_cons, [], Pairs0),
125 reverse(Pairs0, Pairs).
130key_value_cons(Key, Value, Acc, [Key-Value|Acc]).
Goal(K, V, V1)
for each V in Values
and unifies KVs1 with a list of the corresponding Key-V1 pairs.
Backtracks if Goal backtracks.137:- meta_predicate hashtbl_call_map_goal( , , ). 138hashtbl_call_map_goal(Goal, K-Values, K-Values1) :- 139 maplist(call(Goal, K), Values, Values1).
Goal(Key, Value, Value1)
and
unifies TableOut with a hash table containing all Key-Value1 pairs.
Deterministic if Goal is deterministic. If Goal backtracks,
hashtbl_map/3 enumerates several TableOut tables accordingly.147:- meta_predicate hashtbl_map( , , ). 148hashtbl_map(Table, Goal, TableOut) :- 149 Table =.. [Hashtbl, Metadata, BucketTerm], 150 BucketTerm =.. [buckets | Buckets], 151 maplist(maplist(hashtbl_call_map_goal(Goal)), Buckets, BucketsOut), 152 BucketTermOut =.. [buckets | BucketsOut], 153 functor(TableOut, Hashtbl, 2), 154 TableOut =.. [Hashtbl, Metadata, BucketTermOut].
Goal(Key, Value, Acc, Result)
for
each Key and each corresponding Value. Backtracks if Goal backtracks.160:- meta_predicate hashtbl_call_fold_goal( , , , ). 161hashtbl_call_fold_goal(Goal, K-Values, Acc, Result) :- 162 foldl(call(Goal, K), Values, Acc, Result).
Goal(Key,
Value, Acc, Result)
, using each call's Result as the next call's
accumulator Acc, and unifying Result with the final call's Result.
Deterministic if Goal is deterministic. If Goal backtracks, enumerates
several results accordingly.171:- meta_predicate hashtbl_fold( , , , ). 172hashtbl_fold(Table, Goal, Acc, Result) :- 173 arg(2, Table, BucketTerm), 174 BucketTerm =.. [buckets | Buckets], 175 foldl(foldl(hashtbl_call_fold_goal(Goal)), Buckets, Acc, Result).
Goal(Key, Value)
on each Key and
each corresponding Value. Backtracks if Goal backtracks.181:- meta_predicate hashtbl_call_iter_goal( , ). 182hashtbl_call_iter_goal(Goal, K-Values) :- 183 maplist(call(Goal, K), Values).
Goal(Key, Value)
for every Key and Value stored in Table. This
is useful to ensure that all entries satisfy some predicate, or for
Goal's side effects. Deterministic if Goal is deterministic.190:- meta_predicate hashtbl_iter( , ). 191hashtbl_iter(Table, Goal) :- 192 arg(2, Table, BucketTerm), 193 BucketTerm =.. [buckets | Buckets], 194 maplist(maplist(hashtbl_call_iter_goal(Goal)), Buckets). 195 196 197% Various utilities used by the tests of the concrete hash table 198% implementations. *Not* exported to avoid polluting the interface, even if 199% it's only an internal one. Also, not commented. 200test_hashtbl_incr(_K, V, V1) :- 201 V1 is V + 1. 202 203test_hashtbl_sum(_K, V, Acc, Sum) :- 204 Sum is Acc + V. 205 206test_hashtbl_cons(Head, Tail, Acc, cons(Head-Tail, Acc)). 207 208test_hashtbl_nb_sum(Sum, _K, V) :- 209 Sum = sum(Acc), 210 Acc1 is Acc + V, 211 nb_setarg(1, Sum, Acc1). 212 213test_k_ab_table(k, a). 214test_k_ab_table(k, b). 215 216always_false(_, _) :- 217 false
Common utilities of the hashtbl library
Both variants of the hashtbl library share a common data representation: A hash table is a term nb_hashtbl/2 or p_hashtbl/2. The first argument contains metadata such as the hash table's current load. The second is a term bucket/N containing the hash buckets. Hash buckets are lists of Key-Values pairs where Key is a hash table key (a ground term) and Values is the list of Values associated with that key. Each key only occurs once in the table. When several values are added for the same key, later ones come before the older ones in the Values list. They have "higher priority" and are said to "shadow" the older values.
Due to this common representation of hash tables, many operations are identical on the two variants, differing only in the outermost functor. These non-destructive common operations, such as getting values from the table, or mapping higher-order predicates over the table, are defined in this module.
The concrete implementations of the hash tables use the predicates from this module. This is the only intended use of this module: It should be treated as internal to the library. Clients of the library should use one of the concrete hash table modules.
/