* Added patch by Jon Sneyers
[chr.git] / chr_hashtable_store.pl
blobb71ccd3643328ae7e8f9d2065abdeedeca06b2ec
1 % author: Tom Schrijvers
2 % email: Tom.Schrijvers@cs.kuleuven.ac.be
3 % copyright: K.U.Leuven, 2004
5 :- module(chr_hashtable_store,
6 [ new_ht/1,
7 lookup_ht/3,
8 insert_ht/3,
9 delete_ht/3,
10 value_ht/2
11 ]).
13 :- use_module(pairlist).
14 :- use_module(hprolog).
15 :- use_module(library(lists)).
17 initial_capacity(1).
19 new_ht(HT) :-
20 initial_capacity(Capacity),
21 new_ht(Capacity,HT).
23 new_ht(Capacity,HT) :-
24 functor(T1,t,Capacity),
25 HT = ht(Capacity,0,Table),
26 Table = T1.
28 lookup_ht(HT,Term,Values) :-
29 term_hash(Term,Hash),
30 int_lookup_ht(HT,Hash,Term,Values).
32 int_lookup_ht(HT,Hash,Key,Values) :-
33 HT = ht(Capacity,_,Table),
34 Index is (Hash mod Capacity) + 1,
35 arg(Index,Table,Bucket),
36 nonvar(Bucket),
37 ( Bucket = K-Vs,
38 K == Key ->
39 Values = Vs
41 lookup_eq(Bucket,Key,Values)
44 insert_ht(HT,Term,Value) :-
45 term_hash(Term,Hash),
46 ( int_lookup_ht(HT,Hash,Term,Values),
47 hprolog:memberchk_eq(Value,Values) ->
48 true
50 int_insert_ht(HT,Hash,Term,Value)
53 int_insert_ht(HT,Hash,Key,Value) :-
54 HT = ht(Capacity0,Load,Table0),
55 ( Load == Capacity0 ->
56 expand_ht(HT),
57 arg(3,HT,Table),
58 Capacity is Capacity0 * 2
60 Table = Table0,
61 Capacity = Capacity0
63 NLoad is Load + 1,
64 setarg(2,HT,NLoad),
65 Index is (Hash mod Capacity) + 1,
66 arg(Index,Table,Bucket),
67 ( var(Bucket) ->
68 Bucket = Key-[Value]
69 ; Bucket = K-Vs ->
70 ( K == Key ->
71 setarg(2,Bucket,[Value|Vs])
73 setarg(Index,Table,[Key-[Value],Bucket])
75 ; lookup_pair_eq(Bucket,Key,Pair) ->
76 Pair = _-Vs,
77 setarg(2,Pair,[Value|Vs])
79 setarg(Index,Table,[Key-[Value]|Bucket])
83 lookup_pair_eq([P | KVs],Key,Pair) :-
84 P = K-_,
85 ( K == Key ->
86 P = Pair
88 lookup_pair_eq(KVs,Key,Pair)
91 delete_ht(HT,Term,Value) :-
92 term_hash(Term,Hash),
93 ( int_lookup_ht(HT,Hash,Term,Values),
94 hprolog:memberchk_eq(Value,Values) ->
95 int_delete_ht(HT,Hash,Term,Value)
97 true
100 int_delete_ht(HT,Hash,Key,Value) :-
101 HT = ht(Capacity,Load,Table),
102 NLoad is Load - 1,
103 setarg(2,HT,NLoad),
104 Index is (Hash mod Capacity) + 1,
105 arg(Index,Table,Bucket),
106 ( Bucket = _-Vs ->
107 delete(Vs,Value,NVs),
108 ( NVs == [] ->
109 setarg(Index,Table,_)
111 setarg(2,Bucket,NVs)
114 lookup_pair_eq(Bucket,Key,Pair),
115 Pair = _-Vs,
116 delete(Vs,Value,NVs),
117 ( NVs == [] ->
118 pairlist:delete_eq(Bucket,Key,NBucket),
119 setarg(Index,Table,NBucket)
121 setarg(2,Pair,NVs)
125 %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
126 value_ht(HT,Value) :-
127 HT = ht(Capacity,_,Table),
128 value_ht(1,Capacity,Table,Value).
130 value_ht(I,N,Table,Value) :-
131 I =< N,
132 arg(I,Table,Bucket),
134 nonvar(Bucket),
135 ( Bucket = _-Vs ->
136 true
138 member(_-Vs,Bucket)
140 member(Value,Vs)
142 J is I + 1,
143 value_ht(J,N,Table,Value)
146 values_ht(HT,Values) :-
147 HT = ht(Capacity,_,Table),
148 values_ht(1,Capacity,Table,Values).
149 values_ht(I,N,Table,Values) :-
150 ( I =< N ->
151 arg(I,Table,Bucket),
152 ( nonvar(Bucket) ->
153 ( Bucket = _-Vs ->
154 append(Vs,Tail,Values)
156 append_snd(Bucket,Tail,Values)
159 Values = Tail
161 J is I + 1,
162 values_ht(J,N,Table,Tail)
164 Values = []
167 append_snd([],L,L).
168 append_snd([_-H|Ps],L,NL) :-
169 append(H,T,NL),
170 append_snd(Ps,L,T).
171 %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
173 expand_ht(HT) :-
174 HT = ht(Capacity,_,Table),
175 NewCapacity is Capacity * 2,
176 functor(NewTable,t,NewCapacity),
177 setarg(1,HT,NewCapacity),
178 setarg(3,HT,NewTable),
179 expand_copy(Table,1,Capacity,NewTable,NewCapacity).
181 expand_copy(Table,I,N,NewTable,NewCapacity) :-
182 ( I > N ->
183 true
185 arg(I,Table,Bucket),
186 ( var(Bucket) ->
187 true
188 ; Bucket = Key - Value ->
189 expand_insert(NewTable,NewCapacity,Key,Value)
191 expand_inserts(Bucket,NewTable,NewCapacity)
193 J is I + 1,
194 expand_copy(Table,J,N,NewTable,NewCapacity)
197 expand_inserts([],_,_).
198 expand_inserts([K-V|R],Table,Capacity) :-
199 expand_insert(Table,Capacity,K,V),
200 expand_inserts(R,Table,Capacity).
202 expand_insert(Table,Capacity,K,V) :-
203 term_hash(K,Hash),
204 Index is (Hash mod Capacity) + 1,
205 arg(Index,Table,Bucket),
206 ( var(Bucket) ->
207 Bucket = K - V
208 ; Bucket = _-_ ->
209 setarg(Index,Table,[K-V,Bucket])
211 setarg(Index,Table,[K-V|Bucket])
213 %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
214 term_hash(Term,Hash) :-
215 hash_term(Term,Hash).