YAP 7.1.0
assoc.yap
Go to the documentation of this file.
2/**
3 * @file assoc.yap
4 * @author VITOR SANTOS COSTA <vsc@VITORs-MBP.lan>
5 * @date Tue Nov 17 13:53:34 2015
6 *
7 * @brief Red-Black Implementation of Association Lists.
8 *
9 * This file has been included as an YAP library by Vitor Santos Costa, 1999
10 *
11 * Note: the keys should be bound, the associated values need not be.
12*/
13
14:- module(assoc, [
31 assoc_to_keys/2,
34 ]).
35
36/**
37
38@defgroup Assoc Association Maps
39@{
40@ingroup YAPLibrary
41
42The following association list manipulation predicates are available
43once included with the `use_module(library(assoc))` command. The
44original library used Richard O'Keefe's implementation, on top of
45unbalanced binary trees. The current code utilises code from the
46red-black trees library and emulates the SICStus Prolog interface.
47
48The library exports the following definitions:
49
50
51*/
52
53
54
55:- meta_predicate map_assoc(2, +, -), map_assoc(1, +).
56
58 ,
59 ,
60 ,
61 ,
62 ,
63 ,
64 ,
65 ,
66 ,
67 ,
68 ,
69 ,
70 ,
71 ,
72 ,
73 ,
74 ,
75 ,
76 ,
77
78 ]).
79
80/** @pred empty_assoc(+ _Assoc_)
81
82Succeeds if association list _Assoc_ is empty.
83
84*/
86
87/** @pred assoc_to_list(+ _Assoc_,? _List_)
88
89
90Given an association list _Assoc_ unify _List_ with a list of
91the form _Key-Val_, where the elements _Key_ are in ascending
92order.
93
94
95*/
96assoc_to_list(t, L) :- soc_to_list, L = [].
97assoc_to_list(T, L) :-
98 rb_visit(T, L).
99
100/** @pred is_assoc(+ _Assoc_)
101
102Succeeds if _Assoc_ is an association list, that is, if it is a
103red-black tree.
104*/
105is_assoc(t) :- _assoc.
106is_assoc(T) :-
107 is_rbtree(T).
108
109/** @pred min_assoc(+ _Assoc_,- _Key_,? _Value_)
110
111
112Given the association list
113 _Assoc_, _Key_ in the smallest key in the list, and _Value_
114the associated value.
115
116
117*/
118min_assoc(T,K,V) :-
119 rb_min(T,K,V).
120
121/** @pred max_assoc(+ _Assoc_,- _Key_,? _Value_)
122
123
124Given the association list
125 _Assoc_, _Key_ in the largest key in the list, and _Value_
126the associated value.
127
128
129*/
130max_assoc(T,K,V) :-
131 rb_max(T,K,V).
132
133/** @pred gen_assoc( ?Key, +Assoc, ?Valu_)
134
135
136Given the association list _Assoc_, unify _Key_ and _Value_
137with a key-value pair in the list. It can be used to enumerate all elements
138in the association list.
139*/
140gen_assoc(K, T, V) :-
141 rb_in(K,V,T).
142
143/** @pred get_assoc(+ _Key_,+ _Assoc_,? _Value_)
144
145
146If _Key_ is one of the elements in the association list _Assoc_,
147return the associated value.
148*/
149get_assoc(K,T,V) :-
150 rb_lookup(K,V,T).
151
152/** @pred get_assoc(+ _Key_,+ _Assoc_,? _Value_,+ _NAssoc_,? _NValue_)
153
154
155If _Key_ is one of the elements in the association list _Assoc_,
156return the associated value _Value_ and a new association list
157 _NAssoc_ where _Key_ is associated with _NValue_.
158
159
160*/
161get_assoc(K,T,V,NT,NV) :-
162 rb_update(T,K,V,NV,NT).
163
164/** @pred get_next_assoc(+ _Key_,+ _Assoc_,? _Next_,? _Value_)
165
166If _Key_ is one of the elements in the association list _Assoc_,
167return the next key, _Next_, and its value, _Value_.
168
169
170*/
171get_next_assoc(K,T,KN,VN) :-
172 rb_next(T,K,KN,VN).
173
174/** @pred get_prev_assoc(+ _Key_,+ _Assoc_,? _Next_,? _Value_)
175
176
177If _Key_ is one of the elements in the association list _Assoc_,
178return the previous key, _Next_, and its value, _Value_.
179
180
181*/
182get_prev_assoc(K,T,KP,VP) :-
183 rb_previous(T,K,KP,VP).
184
185/** @pred list_to_assoc(+ _List_,? _Assoc_)
186
187
188Given a list _List_ such that each element of _List_ is of the
189form _Key-Val_, and all the _Keys_ are unique, _Assoc_ is
190the corresponding association list.
191
192
193*/
194list_to_assoc(L, T) :-
195 list_to_rbtree(L, T).
196
197/** @pred ord_list_to_assoc(+ _List_,? _Assoc_)
198
199
200Given an ordered list _List_ such that each element of _List_ is
201of the form _Key-Val_, and all the _Keys_ are unique, _Assoc_ is
202the corresponding association list.
203
204*/
205ord_list_to_assoc(L, T) :-
206 ord_list_to_rbtree(L, T).
207
208/** @pred map_assoc(+ _Pred_,+ _Assoc_)
209
210
211Succeeds if the unary predicate name _Pred_( _Val_) holds for every
212element in the association list.
213
214
215*/
216map_assoc(_,t) :- map_assoc.
217map_assoc(P, T) :-
218 yap_flag(typein_module, M0),
219 extract_mod(P, M0, M, G),
220 functor(G, Name, 1),
221 rb_map(T, M:Name).
222
223/** @pred map_assoc(+ _Pred_,+ _Assoc_,? _New_)
224
225Given the binary predicate name _Pred_ and the association list
226 _Assoc_, _New_ in an association list with keys in _Assoc_,
227and such that if _Key-Val_ is in _Assoc_, and _Key-Ans_ is in
228 _New_, then _Pred_( _Val_, _Ans_) holds.*/
229map_assoc(_, t, t) :-
230 map_assoc.
231map_assoc(P, T, NT) :-
232 yap_flag(typein_module, M0),
233 extract_mod(P, M0, M, G),
234 functor(G, Name, 2),
235 rb_map(T, M:Name, NT).
236
237
238extract_mod(G,_,_) :- var(G), var, var.
239extract_mod(M:G, _, FM, FG ) :- extract_mod,
240 extract_mod(G, M, FM, FG ).
241extract_mod(G, M, M, G ).
242
243/** @pred put_assoc(+ _Key_,+ _Assoc_,+ _Val_,+ _New_)
244
245The association list _New_ includes and element of association
246 _key_ with _Val_, and all elements of _Assoc_ that did not
247have key _Key_.
248
249*/
250put_assoc(K, T, V, NT) :-
251 rb_update(T, K, V, NT), rb_update.
252put_assoc(K, t, V, NT) :- put_assoc,
253 put_assoc:rb_new(K,V,NT).
254put_assoc(K, T, V, NT) :-
255 rb_insert(T, K, V, NT).
256
257/** @pred del_assoc(+ _Key_, + _Assoc_, ? _Val_, ? _NewAssoc_)
258
259
260Succeeds if _NewAssoc_ is an association list, obtained by removing
261the element with _Key_ and _Val_ from the list _Assoc_.
262
263
264*/
265del_assoc(K, T, V, NT) :-
266 rb_delete(T, K, V, NT).
267
268/** @pred del_min_assoc(+ _Assoc_, ? _Key_, ? _Val_, ? _NewAssoc_)
269
270
271Succeeds if _NewAssoc_ is an association list, obtained by removing
272the smallest element of the list, with _Key_ and _Val_
273from the list _Assoc_.
274
275*/
276del_min_assoc(T, K, V, NT) :-
277 rb_del_min(T, K, V, NT).
278
279/** @pred del_max_assoc(+ _Assoc_, ? _Key_, ? _Val_, ? _NewAssoc_)
280
281
282Succeeds if _NewAssoc_ is an association list, obtained by removing
283the largest element of the list, with _Key_ and _Val_ from the
284list _Assoc_.
285
286*/
287del_max_assoc(T, K, V, NT) :-
288 rb_del_max(T, K, V, NT).
289
290
291assoc_to_keys(T, Ks) :-
292 rb_keys(T, Ks).
293
294
295/**
296@}
297*/
298
yap_flag( ?Param, ?Value)
assoc_to_list(+ Assoc,? List)
del_assoc(+ Key, + Assoc, ? Val, ? NewAssoc)
del_max_assoc(+ Assoc, ? Key, ? Val, ? NewAssoc)
del_min_assoc(+ Assoc, ? Key, ? Val, ? NewAssoc)
empty_assoc(+ Assoc)
gen_assoc( ?Key, +Assoc, ?Valu_)
get_assoc(+ Key,+ Assoc,? Value)
get_assoc(+ Key,+ Assoc,? Value,+ NAssoc,? NValue)
get_next_assoc(+ Key,+ Assoc,? Next,? Value)
get_prev_assoc(+ Key,+ Assoc,? Next,? Value)
is_assoc(+ Assoc)
list_to_assoc(+ List,? Assoc)
map_assoc(+ Pred,+ Assoc)
map_assoc(+ Pred,+ Assoc,? New)
max_assoc(+ Assoc,- Key,? Value)
min_assoc(+ Assoc,- Key,? Value)
ord_list_to_assoc(+ List,? Assoc)
put_assoc(+ Key,+ Assoc,+ Val,+ New)
use_module( +Files )
functor( T, F, N)
var( T)
rb_del_max( +T, -Key, -Val, -TN)
rb_del_min(+T, -Key, -Val, -TN)
rb_delete(+T, +Key, -Val, -TN)
rb_empty(?T)
rb_insert(+ T0,+ Key,? Value,+ TF)
rb_keys(+ T,+ Keys)
rb_lookup(+Key, -Value, +T)
rb_map(+ T,+ G,- TN)
rb_max( +T, -Key, -Value)
rb_min(+T, -Key, -Value)
rb_next(+T, +Key, -Next,-Value)
rb_previous(+T, +Key, -Previous, -Value)
rb_update(+T, +Key, +NewVal, -TN)
rb_update(+T, +Key, ?OldVal, +NewVal, -TN)
rb_visit(+ T,- Pairs)