1%   File   : MAP.PL
2%   Author : R.A.O'Keefe
3%   Updated: 7 June 1984
4%   Purpose: Implement finite maps.
5%   Needs  : list_to_assoc from ASSOC.PL, ord_disjoint from ORDSET.PL
6
7/*  A finite map is a function from terms to terms with a finite
8    domain.  This definition actually implies that its domain
9    consists of ground terms, and the code below assumes that.
10    The representation is similar to the representation for bags
11    (indeed a bag could be regarded as a map from keys to integers),
12    that is, the empty map is 'map' and any other map is
13	map(Key,Val,Map)
14    where Map is a finite map and Key is @< than every key in Map.
15*/
16
17:- module(map).			% SEPIA header
18:- export
19	is_map/1,		%  map ->
20	list_to_map/2,		%  list -> map
21	map_agree/2,		%  map x map ->
22	map_compose/3,		%  map x map -> map
23	map_disjoint/2,		%  map x map ->
24	map_domain/2,		%  map -> ordset
25	map_exclude/3,		%  map x ordset -> map
26	map_include/3,		%  map x ordset -> map
27	map_invert/2,		%  map -> map
28	map_map/3,		%  relation x map -> map
29	map_range/2,		%  map -> ordset
30	map_to_assoc/2,		%  map -> tree
31	map_union/3,		%  map x map -> map
32	map_update/3,		%  map x map -> map
33	map_update/4,		%  map x key x val -> map
34	map_value/3,		%  map x dom -> rng
35	portray_map/1.		%  map ->
36
37:- lib(ordset), lib(assoc), lib(apply).
38:- import ord_disjoint/2 from ordset.
39:- import list_to_assoc/4 from assoc.
40
41:- mode
42	is_map(+),
43	    is_map(+, +),
44	list_to_map(+, ?),
45	    list_to_map_(+, ?),
46	map_agree(+, +),
47	    map_agree(+, +, +, +, +, +, +),
48	map_compose(+, +, ?),
49	    map_compose_(+, +, ?),
50		map_compose_(+, +, +, +, +, +, +, ?),
51	map_disjoint(+, +),
52	map_domain(+, ?),
53	map_exclude(+, +, ?),
54	    map_exclude(+, +, +, +, +, +, ?),
55	map_include(+, +, ?),
56	    map_include(+, +, +, +, +, +, ?),
57	map_invert(+, ?),
58	    map_invert_(+, -),
59	map_map(+, +, ?),
60	map_range(+, ?),
61	    map_range_(+, -),
62	map_to_assoc(+, ?),
63	map_to_list(+, ?),
64	map_union(+, +, ?),
65	    map_union(+, +, +, +, +, +, +, ?),
66	map_update(+, +, ?),
67	    map_update(+, +, +, +, +, +, +, ?),
68	map_update(+, +, +, ?),
69	    map_update(+, +, +, +, +, +, ?),
70	map_value(+, +, ?),
71	    map_value(+, +, +, +, ?),
72	portray_map(+),
73	    portray_map(+, +).
74
75%   is_map(Thing)
76%   is true when Thing is a map.  If you use the predicates in this
77%   file, you have no way of constructing a map with an unbound tail,
78%   so such structures are NOT recognised as bags (this avoids a
79%   possible infinite loop.
80
81is_map(map).
82is_map(map(Key,_,Map)) :-
83	nonvar(Map),
84	is_map(Map, Key).
85
86is_map(map, _).
87is_map(map(Key,_,Map), PreviousKey) :-
88	nonvar(Map),
89	PreviousKey @< Key,
90	is_map(Map, Key).
91
92%   list_to_map(+KeyValList, ?Map)
93%   takes a list of Key-Value pairs and orders them to form a representation
94%   of a finite map.  The list may not have two elements with the same Key.
95
96list_to_map(List, Map) :-
97	keysort(List, Sorted),
98	list_to_map_(Sorted, Map).
99
100list_to_map_([], map).
101list_to_map_([Key-Val|List], map(Key,Val,Map)) :-
102	list_to_map_(List, Map).
103
104
105
106%   map_agree(+Map1, Map2)
107%   is true if whenever Map1 and Map2 have a key in common, they
108%   agree on its value.  If they have no keys in common they agree.
109
110map_agree(_, map) :- !.
111map_agree(map, _).
112map_agree(map(Key1,Val1,Map1), map(Key2,Val2,Map2)) :-
113	compare(R, Key1, Key2),
114	map_agree(R, Key1, Val1, Map1, Key2, Val2, Map2).
115
116map_agree(<, _, _, Map1, Key2, Val2, Map2) :-
117	map_agree(Map1, map(Key2,Val2,Map2)).
118map_agree(>, Key1, Val1, Map1, _, _, Map2) :-
119	map_agree(map(Key1,Val1,Map1), Map2).
120map_agree(=, _, Val, Map1, _, Val, Map2) :-
121	map_agree(Map1, Map2).
122
123
124
125%   map_compose(Map1, Map2, Composition)
126%   constructs Map1 o Map2.  That is, for each K-T in Map1 such that
127%   there is a T-V in Map2, K-V is in Composition.  The way this is
128%   done requires the range of Map1 to be ground as well as the domains
129%   of both maps, but then any fast composition has the same problem.
130
131map_compose(Map1, Map2, Composition) :-
132	map_invert_(Map1, Inv0),
133	keysort(Inv0, Inv1),
134	map_compose_(Inv1, Map2, Mid0),
135	keysort(Mid0, Mid1),
136	list_to_map_(Mid1, Composition).
137
138map_compose_(_, map, []) :- !.
139map_compose_([], _, []).
140map_compose_([Val1-Key1|Map1], map(Key2,Val2,Map2), Composition) :-
141	compare(R, Val1, Key2),
142	map_compose_(R, Val1, Key1, Map1, Key2, Val2, Map2, Composition).
143
144map_compose_(<, _, _, Map1, Key2, Val2, Map2, Composition) :-
145	map_compose_(Map1, map(Key2,Val2,Map2), Composition).
146map_compose_(>, Val1, Key1, Map1, _, _, Map2, Composition) :-
147	map_compose_([Val1-Key1|Map1], Map2, Composition).
148map_compose_(=, Com, Key1, Map1, Com, Val2, Map2, [Key1-Val2|Composition]) :-
149	map_compose_(Map1, map(Com,Val2,Map2), Composition).
150
151
152
153%   map_disjoint(+Map1, +Map2)
154%   is true when the two maps have no domain elements in common.
155%   That is, if K-V1 is in Map1, there is no K-V2 in Map2 and conversely.
156%   This implementation assumes you have loaded the ordered sets package.
157
158map_disjoint(Map1, Map2) :-
159	map_domain(Map1, Dom1),
160	map_domain(Map2, Dom2),
161	ord_disjoint(Dom1, Dom2).
162
163
164
165%   map_domain(+Map, ?Domain)
166%   unifies Domain with the ordered set representation of the domain
167%   of the finite map Map.  As the keys (domain elements) of Map are
168%   in ascending order and there are no duplicates, this is trivial.
169
170map_domain(map, []).
171map_domain(map(Key,_,Map), [Key|Domain]) :-
172	map_domain(Map, Domain).
173
174
175
176%   map_exclude(+Map, +Set, ?Restricted)
177%   constructs a restriction of the Map by dropping members of the Set
178%   from the Restricted map's domain.  That is, Restricted and Map agree,
179%   but domain(Restricted) = domain(Map)\Set.
180%   Set must be an *ordered* set.
181
182map_exclude(Map, [], Map) :- !.
183map_exclude(map, _, map).
184map_exclude(map(Key,Val,Map), [Elt|Set], Restricted) :-
185	compare(R, Key, Elt),
186	map_exclude(R, Key, Val, Map, Elt, Set, Restricted).
187
188map_exclude(<, Key, Val, Map, Elt, Set, map(Key,Val,Restricted)) :-
189	map_exclude(Map, [Elt|Set], Restricted).
190map_exclude(>, Key, Val, Map, _, Set, Restricted) :-
191	map_exclude(map(Key,Val,Map), Set, Restricted).
192map_exclude(=, _, _, Map, _, Set, Restricted) :-
193	map_exclude(Map, Set, Restricted).
194
195
196
197%   map_include(+Map, +Set, ?Restricted)
198%   constructs a restriction of the Map by dropping everything which is
199%   NOT a member of Set from the restricted map's domain.  That is, the
200%   Restricted and original Map agree, but
201%   domain(Restricted) = domain(Map) intersection Set.
202%   Set must be an *ordered* set.
203
204map_include(Map, [], Map) :- !.
205map_include(map, _, map).
206map_include(map(Key,Val,Map), [Elt|Set], Restricted) :-
207	compare(R, Key, Elt),
208	map_include(R, Key, Val, Map, Elt, Set, Restricted).
209
210map_include(<, _, _, Map, Elt, Set, Restricted) :-
211	map_include(Map, [Elt|Set], Restricted).
212map_include(>, Key, Val, Map, _, Set, Restricted) :-
213	map_include(map(Key,Val,Map), Set, Restricted).
214map_include(=, Key, Val, Map, _, Set, map(Key,Val,Restricted)) :-
215	map_include(Map, Set, Restricted).
216
217
218
219%   map_invert(+Map, ?Inverse)
220%   unifies Inverse with the inverse of a finite invertible map.
221%   All we do is swap the pairs round, sort, and check that the
222%   result is indeed a map.
223
224map_invert(Map, Inverse) :-
225	map_invert_(Map, Inv0),
226	keysort(Inv0, Inv1),
227	list_to_map_(Inv1, Inverse).
228
229%   map_invert_ takes a list of key-value pairs and swaps the pairs around.
230
231map_invert_(map, []).
232map_invert_(map(Key,Val,Map), [Val-Key|Inv]) :-
233	map_invert_(Map, Inv).
234
235
236
237%   map_map(+Predicate, +Map1, ?Map2)
238%   composes Map1 with the Predicate, so that K-V2 is in Map2 if
239%   K-V1 is in Map1 and Predicate(V1,V2).  Really, the predicate
240%   should come second, but there is this convention that the
241%   predicate being mapped always comes first.  It doesn't do
242%   marvels for Dec-10 Prolog's indexing either.
243
244:- tool(map_map/3, map_map/4).
245
246map_map(_, map, map, _).
247map_map(Pred, map(K,V1,Map1), map(K,V2,Map2), Module) :-
248	apply(Pred, [V1,V2])@Module,
249	map_map(Pred, Map1, Map2, Module).
250
251
252
253%   map_range(+Map, ?Range)
254%   unifies Range with the ordered set representation of the range of the
255%   finite map Map.  Note that the cardinality (length) of the domain and
256%   the range are seldom equal, except of course for invertible maps.
257
258map_range(Map, Range) :-
259	map_range_(Map, Random),
260	sort(Random, Range).
261
262map_range_(map, []).
263map_range_(map(_,Val,Map), [Val|Range]) :-
264	map_range_(Map, Range).
265
266
267
268%   map_to_assoc(+Map, ?Assoc)
269%   converts a finite map held as an ordered list of Key-Val pairs to
270%   an ordered binary tree such as the library file ASSOC works on.
271%   This predicate calls an internal routine of that file, so both
272%   must be compiled or both interpreted.  Eventually the two files
273%   should be combined.
274
275map_to_assoc(Map, Assoc) :-
276	map_to_list(Map, List),
277	length(List, N),
278	list_to_assoc(N, List, Assoc, []).
279
280
281
282%   map_to_list(+Map, ?KeyValList)
283%   converts a map from its compact form to a list of Key-Val pairs
284%   such as keysort yields or list_to_assoc wants.
285
286map_to_list(map, []).
287map_to_list(map(Key,Val,Map), [Key-Val|List]) :-
288	map_to_list(Map, List).
289
290
291
292%   map_union(+Map1, +Map2, ?Union)
293%   forms the union of the two given maps.  That is Union(X) =
294%   Map1(X) if it is defined, or Map2(X) if that is defined.
295%   But when both are defined, both must agree.  (See map_update
296%   for a version where Map2 overrides Map1.)
297
298map_union(Map, map, Map) :- !.
299map_union(map, Map, Map).
300map_union(map(Key1,Val1,Map1), map(Key2,Val2,Map2), Union) :-
301	compare(R, Key1, Key2),
302	map_union(R, Key1, Val1, Map1, Key2, Val2, Map2, Union).
303
304map_union(<, Key1, Val1, Map1, Key2, Val2, Map2, map(Key1,Val1,Union)) :-
305	map_union(Map1, map(Key2,Val2,Map2), Union).
306map_union(>, Key1, Val1, Map1, Key2, Val2, Map2, map(Key2,Val2,Union)) :-
307	map_union(map(Key1,Val1,Map1), Map2, Union).
308map_union(=, Key, Val, Map1, Key, Val, Map2, map(Key,Val,Union)) :-
309	map_union(Map1, Map2, Union).
310
311
312
313%   map_update(+Base, +Overlay, ?Updated)
314%   combines the finite maps Base and Overlay as map_union does,
315%   except that when both define values for the same key, the
316%   Overlay value is taken regardless of the Base value.  This
317%   is useful for changing maps (you may know it as the "mu" function).
318
319map_update(Map, map, Map) :- !.
320map_update(map, Map, Map).
321map_update(map(Key1,Val1,Map1), map(Key2,Val2,Map2), Updated) :-
322	compare(R, Key1, Key2),
323	map_update(R, Key1, Val1, Map1, Key2, Val2, Map2, Updated).
324
325map_update(<, Key1, Val1, Map1, Key2, Val2, Map2, map(Key1,Val1,Updated)) :-
326	map_update(Map1, map(Key2,Val2,Map2), Updated).
327map_update(>, Key1, Val1, Map1, Key2, Val2, Map2, map(Key2,Val2,Updated)) :-
328	map_update(map(Key1,Val1,Map1), Map2, Updated).
329map_update(=, _, _, Map1, Key, Val, Map2, map(Key,Val,Updated)) :-
330	map_update(Map1, Map2, Updated).
331
332
333
334%   map_update(+Map, +Key, +Val, ?Updated)
335%   computes an Updated map which is the same as Map except that the
336%   image of Key is Val, rather than the image it had under Map if any.
337%   This is an O(N) operation, not O(1).  By using trees we could get
338%   O(lgN).  Eventually this package should be merged with ASSOC.PL.
339
340map_update(map, Key, Val, map(Key,Val,map)).
341map_update(map(Key1,Val1,Map), Key, Val, Updated) :-
342	compare(R, Key1, Key),
343	map_update(R, Key1, Val1, Map, Key, Val, Updated).
344
345map_update(<, Key1, Val1, Map, Key, Val, map(Key1,Val1,Updated)) :-
346	map_update(Map, Key, Val, Updated).
347map_update(=, _, _, Map, Key, Val, map(Key,Val,Map)).
348map_update(>, Key1, Val1, Map, Key, Val, map(Key,Val,map(Key1,Val1,Map))).
349
350
351
352%   map_value(+Map, +Arg, ?Result)
353%   applies the finite map Map to an argument, and unifies Result with
354%   the answer.  It fails if Arg is not in the domain of Map, or if the
355%   value does not unify with Result.  Note that this operation is O(N)
356%   like all the others; this package is really meant for working on
357%   maps as wholes.  We can achieve O(lgN) by using trees (as in ASSOC),
358%   and eventually MAP and ASSOC should be merged.  In the mean time,
359%   use map_to_assoc to convert a map to a tree for faster lookup.
360
361map_value(map(Key,Val,Map), Arg, Result) :-
362	compare(R, Key, Arg),
363	map_value(R, Val, Map, Arg, Result).
364
365map_value(<, _, Map, Arg, Result) :- !,
366	map_value(Map, Arg, Result).
367map_value(=, Result, _, _, Result).
368
369
370
371%   portray_map(+Map)
372%   writes a finite Map to the current output stream in a pretty
373%   form so that you can easily see what it is.  Note that a map
374%   written out this way can NOT be read back in.  The point of
375%   this predicate is that you can add a clause
376%	portray(X) :- is_map(X), !, portray_map(X).
377%   to get maps displayed nicely by print/1.
378
379portray_map(map) :- !,
380	write('map{'), write('}').
381portray_map(Map) :-
382	portray_map(Map, 'map{').
383
384portray_map(map, _) :-
385	write('}').
386portray_map(map(Key,Val,Map), Prefix) :-
387	write(Prefix),
388	print(Key), write('->'), print(Val),
389	!,
390	portray_map(Map, ', ').
391
392