35
36:- module(assoc,
37 [ empty_assoc/1, 38 is_assoc/1, 39 assoc_to_list/2, 40 assoc_to_keys/2, 41 assoc_to_values/2, 42 gen_assoc/3, 43 get_assoc/3, 44 get_assoc/5, 45 list_to_assoc/2, 46 map_assoc/2, 47 map_assoc/3, 48 max_assoc/3, 49 min_assoc/3, 50 ord_list_to_assoc/2, 51 put_assoc/4, 52 del_assoc/4, 53 del_min_assoc/4, 54 del_max_assoc/4 55 ]). 56:- use_module(library(error)).
67:- meta_predicate
68 map_assoc(1, ?),
69 map_assoc(2, ?, ?).
75empty_assoc(t).
82assoc_to_list(Assoc, List) :-
83 assoc_to_list(Assoc, List, []).
84
85assoc_to_list(t(Key,Val,_,L,R), List, Rest) :-
86 assoc_to_list(L, List, [Key-Val|More]),
87 assoc_to_list(R, More, Rest).
88assoc_to_list(t, List, List).
96assoc_to_keys(Assoc, List) :-
97 assoc_to_keys(Assoc, List, []).
98
99assoc_to_keys(t(Key,_,_,L,R), List, Rest) :-
100 assoc_to_keys(L, List, [Key|More]),
101 assoc_to_keys(R, More, Rest).
102assoc_to_keys(t, List, List).
111assoc_to_values(Assoc, List) :-
112 assoc_to_values(Assoc, List, []).
113
114assoc_to_values(t(_,Value,_,L,R), List, Rest) :-
115 assoc_to_values(L, List, [Value|More]),
116 assoc_to_values(R, More, Rest).
117assoc_to_values(t, List, List).
126is_assoc(Assoc) :-
127 is_assoc(Assoc, _Min, _Max, _Depth).
128
129is_assoc(t,X,X,0) :- !.
130is_assoc(t(K,_,-,t,t),K,K,1) :- !, ground(K).
131is_assoc(t(K,_,>,t,t(RK,_,-,t,t)),K,RK,2) :-
132 133 !, ground((K,RK)), K @< RK.
134
135is_assoc(t(K,_,<,t(LK,_,-,t,t),t),LK,K,2) :-
136 137 !, ground((LK,K)), LK @< K.
138
139is_assoc(t(K,_,B,L,R),Min,Max,Depth) :-
140 is_assoc(L,Min,LMax,LDepth),
141 is_assoc(R,RMin,Max,RDepth),
142 143 compare(Rel,RDepth,LDepth),
144 balance(Rel,B),
145 146 ground((LMax,K,RMin)),
147 LMax @< K,
148 K @< RMin,
149 Depth is max(LDepth, RDepth)+1.
150
152balance(=,-).
153balance(<,<).
154balance(>,>).
164gen_assoc(Key, Assoc, Value) :-
165 ( ground(Key)
166 -> get_assoc(Key, Assoc, Value)
167 ; gen_assoc_(Key, Assoc, Value)
168 ).
169
170gen_assoc_(Key, t(_,_,_,L,_), Val) :-
171 gen_assoc_(Key, L, Val).
172gen_assoc_(Key, t(Key,Val,_,_,_), Val).
173gen_assoc_(Key, t(_,_,_,_,R), Val) :-
174 gen_assoc_(Key, R, Val).
183get_assoc(Key, Assoc, Val) :-
184 must_be(assoc, Assoc),
185 get_assoc_(Key, Assoc, Val).
186
187:- if(current_predicate('$btree_find_node'/5)). 188get_assoc_(Key, Tree, Val) :-
189 Tree \== t,
190 '$btree_find_node'(Key, Tree, 0x010405, Node, =),
191 arg(2, Node, Val).
192:- else. 193get_assoc_(Key, t(K,V,_,L,R), Val) :-
194 compare(Rel, Key, K),
195 get_assoc(Rel, Key, V, L, R, Val).
196
197get_assoc(=, _, Val, _, _, Val).
198get_assoc(<, Key, _, Tree, _, Val) :-
199 get_assoc(Key, Tree, Val).
200get_assoc(>, Key, _, _, Tree, Val) :-
201 get_assoc(Key, Tree, Val).
202:- endif.
209get_assoc(Key, t(K,V,B,L,R), Val, t(K,NV,B,NL,NR), NVal) :-
210 compare(Rel, Key, K),
211 get_assoc(Rel, Key, V, L, R, Val, NV, NL, NR, NVal).
212
213get_assoc(=, _, Val, L, R, Val, NVal, L, R, NVal).
214get_assoc(<, Key, V, L, R, Val, V, NL, R, NVal) :-
215 get_assoc(Key, L, Val, NL, NVal).
216get_assoc(>, Key, V, L, R, Val, V, L, NR, NVal) :-
217 get_assoc(Key, R, Val, NR, NVal).
227list_to_assoc(List, Assoc) :-
228 ( List = [] -> Assoc = t
229 ; keysort(List, Sorted),
230 ( ord_pairs(Sorted)
231 -> length(Sorted, N),
232 list_to_assoc(N, Sorted, [], _, Assoc)
233 ; domain_error(unique_key_pairs, List)
234 )
235 ).
236
237list_to_assoc(1, [K-V|More], More, 1, t(K,V,-,t,t)) :- !.
238list_to_assoc(2, [K1-V1,K2-V2|More], More, 2, t(K2,V2,<,t(K1,V1,-,t,t),t)) :- !.
239list_to_assoc(N, List, More, Depth, t(K,V,Balance,L,R)) :-
240 N0 is N - 1,
241 RN is N0 div 2,
242 Rem is N0 mod 2,
243 LN is RN + Rem,
244 list_to_assoc(LN, List, [K-V|Upper], LDepth, L),
245 list_to_assoc(RN, Upper, More, RDepth, R),
246 Depth is LDepth + 1,
247 compare(B, RDepth, LDepth), balance(B, Balance).
257ord_list_to_assoc(Sorted, Assoc) :-
258 ( Sorted = [] -> Assoc = t
259 ; ( ord_pairs(Sorted)
260 -> length(Sorted, N),
261 list_to_assoc(N, Sorted, [], _, Assoc)
262 ; domain_error(key_ordered_pairs, Sorted)
263 )
264 ).
270ord_pairs([K-_V|Rest]) :-
271 ord_pairs(Rest, K).
272ord_pairs([], _K).
273ord_pairs([K-_V|Rest], K0) :-
274 K0 @< K,
275 ord_pairs(Rest, K).
281map_assoc(Pred, T) :-
282 map_assoc_(T, Pred).
283
284map_assoc_(t, _).
285map_assoc_(t(_,Val,_,L,R), Pred) :-
286 map_assoc_(L, Pred),
287 call(Pred, Val),
288 map_assoc_(R, Pred).
295map_assoc(Pred, T0, T) :-
296 map_assoc_(T0, Pred, T).
297
298map_assoc_(t, _, t).
299map_assoc_(t(Key,Val,B,L0,R0), Pred, t(Key,Ans,B,L1,R1)) :-
300 map_assoc_(L0, Pred, L1),
301 call(Pred, Val, Ans),
302 map_assoc_(R0, Pred, R1).
309max_assoc(t(K,V,_,_,R), Key, Val) :-
310 max_assoc(R, K, V, Key, Val).
311
312max_assoc(t, K, V, K, V).
313max_assoc(t(K,V,_,_,R), _, _, Key, Val) :-
314 max_assoc(R, K, V, Key, Val).
321min_assoc(t(K,V,_,L,_), Key, Val) :-
322 min_assoc(L, K, V, Key, Val).
323
324min_assoc(t, K, V, K, V).
325min_assoc(t(K,V,_,L,_), _, _, Key, Val) :-
326 min_assoc(L, K, V, Key, Val).
334put_assoc(Key, A0, Value, A) :-
335 insert(A0, Key, Value, A, _).
336
337insert(t, Key, Val, t(Key,Val,-,t,t), yes).
338insert(t(Key,Val,B,L,R), K, V, NewTree, WhatHasChanged) :-
339 compare(Rel, K, Key),
340 insert(Rel, t(Key,Val,B,L,R), K, V, NewTree, WhatHasChanged).
341
342insert(=, t(Key,_,B,L,R), _, V, t(Key,V,B,L,R), no).
343insert(<, t(Key,Val,B,L,R), K, V, NewTree, WhatHasChanged) :-
344 insert(L, K, V, NewL, LeftHasChanged),
345 adjust(LeftHasChanged, t(Key,Val,B,NewL,R), left, NewTree, WhatHasChanged).
346insert(>, t(Key,Val,B,L,R), K, V, NewTree, WhatHasChanged) :-
347 insert(R, K, V, NewR, RightHasChanged),
348 adjust(RightHasChanged, t(Key,Val,B,L,NewR), right, NewTree, WhatHasChanged).
349
350adjust(no, Oldree, _, Oldree, no).
351adjust(yes, t(Key,Val,B0,L,R), LoR, NewTree, WhatHasChanged) :-
352 table(B0, LoR, B1, WhatHasChanged, ToBeRebalanced),
353 rebalance(ToBeRebalanced, t(Key,Val,B0,L,R), B1, NewTree, _, _).
354
357table(- , left , < , yes , no ) :- !.
358table(- , right , > , yes , no ) :- !.
359table(< , left , - , no , yes ) :- !.
360table(< , right , - , no , no ) :- !.
361table(> , left , - , no , no ) :- !.
362table(> , right , - , no , yes ) :- !.
370del_min_assoc(Tree, Key, Val, NewTree) :-
371 del_min_assoc(Tree, Key, Val, NewTree, _DepthChanged).
372
373del_min_assoc(t(Key,Val,_B,t,R), Key, Val, R, yes) :- !.
374del_min_assoc(t(K,V,B,L,R), Key, Val, NewTree, Changed) :-
375 del_min_assoc(L, Key, Val, NewL, LeftChanged),
376 deladjust(LeftChanged, t(K,V,B,NewL,R), left, NewTree, Changed).
384del_max_assoc(Tree, Key, Val, NewTree) :-
385 del_max_assoc(Tree, Key, Val, NewTree, _DepthChanged).
386
387del_max_assoc(t(Key,Val,_B,L,t), Key, Val, L, yes) :- !.
388del_max_assoc(t(K,V,B,L,R), Key, Val, NewTree, Changed) :-
389 del_max_assoc(R, Key, Val, NewR, RightChanged),
390 deladjust(RightChanged, t(K,V,B,L,NewR), right, NewTree, Changed).
397del_assoc(Key, A0, Value, A) :-
398 delete(A0, Key, Value, A, _).
399
401delete(t(Key,Val,B,L,R), K, V, NewTree, WhatHasChanged) :-
402 compare(Rel, K, Key),
403 delete(Rel, t(Key,Val,B,L,R), K, V, NewTree, WhatHasChanged).
404
408delete(=, t(Key,Val,_B,t,R), Key, Val, R, yes) :- !.
409delete(=, t(Key,Val,_B,L,t), Key, Val, L, yes) :- !.
410delete(=, t(Key,Val,>,L,R), Key, Val, NewTree, WhatHasChanged) :-
411 412 del_min_assoc(R, K, V, NewR, RightHasChanged),
413 deladjust(RightHasChanged, t(K,V,>,L,NewR), right, NewTree, WhatHasChanged),
414 !.
415delete(=, t(Key,Val,B,L,R), Key, Val, NewTree, WhatHasChanged) :-
416 417 del_max_assoc(L, K, V, NewL, LeftHasChanged),
418 deladjust(LeftHasChanged, t(K,V,B,NewL,R), left, NewTree, WhatHasChanged),
419 !.
420
421delete(<, t(Key,Val,B,L,R), K, V, NewTree, WhatHasChanged) :-
422 delete(L, K, V, NewL, LeftHasChanged),
423 deladjust(LeftHasChanged, t(Key,Val,B,NewL,R), left, NewTree, WhatHasChanged).
424delete(>, t(Key,Val,B,L,R), K, V, NewTree, WhatHasChanged) :-
425 delete(R, K, V, NewR, RightHasChanged),
426 deladjust(RightHasChanged, t(Key,Val,B,L,NewR), right, NewTree, WhatHasChanged).
427
428deladjust(no, OldTree, _, OldTree, no).
429deladjust(yes, t(Key,Val,B0,L,R), LoR, NewTree, RealChange) :-
430 deltable(B0, LoR, B1, WhatHasChanged, ToBeRebalanced),
431 rebalance(ToBeRebalanced, t(Key,Val,B0,L,R), B1, NewTree, WhatHasChanged, RealChange).
432
435deltable(- , right , < , no , no ) :- !.
436deltable(- , left , > , no , no ) :- !.
437deltable(< , right , - , yes , yes ) :- !.
438deltable(< , left , - , yes , no ) :- !.
439deltable(> , right , - , yes , no ) :- !.
440deltable(> , left , - , yes , yes ) :- !.
442
452
453
454rebalance(no, t(K,V,_,L,R), B, t(K,V,B,L,R), Changed, Changed).
455rebalance(yes, OldTree, _, NewTree, _, RealChange) :-
456 avl_geq(OldTree, NewTree, RealChange).
457
458avl_geq(t(A,VA,>,Alpha,t(B,VB,>,Beta,Gamma)),
459 t(B,VB,-,t(A,VA,-,Alpha,Beta),Gamma), yes) :- !.
460avl_geq(t(A,VA,>,Alpha,t(B,VB,-,Beta,Gamma)),
461 t(B,VB,<,t(A,VA,>,Alpha,Beta),Gamma), no) :- !.
462avl_geq(t(B,VB,<,t(A,VA,<,Alpha,Beta),Gamma),
463 t(A,VA,-,Alpha,t(B,VB,-,Beta,Gamma)), yes) :- !.
464avl_geq(t(B,VB,<,t(A,VA,-,Alpha,Beta),Gamma),
465 t(A,VA,>,Alpha,t(B,VB,<,Beta,Gamma)), no) :- !.
466avl_geq(t(A,VA,>,Alpha,t(B,VB,<,t(X,VX,B1,Beta,Gamma),Delta)),
467 t(X,VX,-,t(A,VA,B2,Alpha,Beta),t(B,VB,B3,Gamma,Delta)), yes) :-
468 !,
469 table2(B1, B2, B3).
470avl_geq(t(B,VB,<,t(A,VA,>,Alpha,t(X,VX,B1,Beta,Gamma)),Delta),
471 t(X,VX,-,t(A,VA,B2,Alpha,Beta),t(B,VB,B3,Gamma,Delta)), yes) :-
472 !,
473 table2(B1, B2, B3).
474
475table2(< ,- ,> ).
476table2(> ,< ,- ).
477table2(- ,- ,- ).
478
479
480 483
484:- multifile
485 error:has_type/2. 486
487error:has_type(assoc, X) :-
488 ( X == t
489 -> true
490 ; compound(X),
491 functor(X, t, 5)
492 )
Binary associations
Assocs are Key-Value associations implemented as a balanced binary tree (AVL tree).
library(pairs)
,library(rbtrees)