1
2%   File   : LISTUT.PL
3%   Author : Bob Welham, Lawrence Byrd, and R.A.O'Keefe
4%   Converted to NIP: K Johnson, 11.8.87
5%   Updated: 12 February 1985
6%   Purpose: list processing utilities
7
8%   I am not sure how much of the original code was by Bob Welham
9%   and how much by Lawrence Byrd.  The layout and comments are by
10%   R.A.O'Keefe, as are nth*, same_length, shorter_list, and subseq*.
11%   Keys_and_values has moved to PROJEC.PL.
12
13:- module(listut).			% SEPIA header
14
15:-comment(categories, ["Data Structures"]).
16:- comment(summary, "List processing utilities").
17:- comment(author, "Bob Welham, Lawrence Byrd, R.A.O'Keefe, Joachim Schimpf").
18:- comment(copyright, 'This file is in the public domain').
19:- comment(date, "$Date: 2013/02/09 20:27:57 $").
20
21:- export
22%	append/3,			%   List x List -> List
23	correspond/4,			%   Elem <- List x List -> Elem
24	delete/3,			%   List x Elem -> List
25	last/2,				%   List -> Elem
26	nextto/3,			%   Elem, Elem <- List
27	nmember/3,			%   Elem <- Set -> Integer
28	nmembers/3,			%   List x Set -> Set
29	nth0/3,				%   Integer x List -> Elem
30	nth0/4,				%   Integer x List -> Elem x List
31	nth1/3,				%   Integer x List -> Elem
32	nth1/4,				%   Integer x List -> Elem x List
33	numlist/3,			%   Integer x Integer -> List
34	perm/2,				%   List -> List
35	perm2/4,			%   Elem x Elem -> Elem x Elem
36	remove_dups/2,			%   List -> Set
37	rev/2,				%   List -> List
38%	reverse/2,			%   List -> List
39	same_length/2,			%   List x List ->
40	select/4,			%   Elem x List x Elem -> List
41	shorter_list/2,			%   List x List ->
42	subseq/3,			%   List -> List x List
43	subseq0/2,			%   List -> List
44	subseq1/2,			%   List -> List
45	sumlist/2.			%   List -> Integer
46
47% We reexport the built-in versions in order to keep the
48% interface of listut unchanged, and at the same time
49% avoid ambiguous import warnings in the importer
50:- reexport
51	append/3,
52%	delete/3,			% conflicting semantics!
53	reverse/2
54   from sepia_kernel.
55
56:- local select/3.
57
58:- mode
59%	append(?, ?, ?),
60	correspond(?, +, +, ?),
61	delete(+, +, -),
62	last(?, ?),
63	nextto(?, ?, ?),
64	nmember(?, +, ?),
65	nmembers(+, +, -),
66	nth0(?, ?, ?),
67	nth0(?, ?, ?, ?),
68	nth1(?, ?, ?),
69	nth1(?, ?, ?, ?),
70	numlist(+, +, ?),
71	perm(?, ?),
72	perm2(?,?, ?,?),
73	remove_dups(+, ?),
74	rev(?, ?),
75%	reverse(?, ?),
76%	reverse(?, +, ?),
77	same_length(?, ?),
78	select(?, ?, ?, ?),
79	shorter_list(?, +),
80	subseq(?, ?, ?),
81	subseq0(+, ?),
82	subseq1(+, ?),
83	sumlist(+, ?),
84	sumlist(+, +, ?).
85
86
87%   append(Prefix, Suffix, Combined)
88%   is true when all three arguments are lists, and the members of Combined
89%   are the members of Prefix followed by the members of Suffix.  It may be
90%   used to form Combined from a given Prefix and Suffix, or to take a given
91%   Combined apart.  E.g. we could define member/2 (from SetUtl.Pl) as
92%	member(X, L) :- append(_, [X|_], L).
93%
94%append([], L, L).
95%append([H|T], L, [H|R]) :-
96%	append(T, L, R).
97
98
99
100%   correspond(X, Xlist, Ylist, Y)
101%   is true when Xlist and Ylist are lists, X is an element of Xlist, Y is
102%   an element of Ylist, and X and Y are in similar places in their lists.
103
104correspond(X, [X|_], [Y|_], Y) :- !.
105correspond(X, [_|T], [_|U], Y) :-
106	correspond(X, T, U, Y).
107
108%   delete(List, Elem, Residue)
109%   is true when List is a list, in which Elem may or may not occur, and
110%   Residue is a copy of List with all elements equal to Elem deleted.
111
112delete([], _, []) :- !.
113delete([Kill|Tail], Kill, Rest) :- !,
114	delete(Tail, Kill, Rest).
115
116	delete([Head|Tail], Kill, [Head|Rest]) :- !,
117		delete(Tail, Kill, Rest).
118
119%   last(Last, List)
120%   is true when List is a List and Last is its last element.  This could
121%   be defined as last(X,L) :- append(_, [X], L).
122
123last(Last, [Last]) :- !.
124last(Last, [_|List]) :-
125	last(Last, List).
126
127%   nextto(X, Y, List)
128%   is true when X and Y appear side-by-side in List.  It could be written as
129%	nextto(X, Y, List) :- append(_, [X,Y], List).
130%   It may be used to enumerate successive pairs from the list.
131
132nextto(X,Y, [X,Y|_]).
133nextto(X,Y, [_|List]) :-
134	nextto(X,Y, List).
135
136%   nmember(Elem, List, Index) Possible Calling Sequences
137%   nmember(+,+,-) or nmember(-,+,+) or nmember(-,+,-).
138%   True when Elem is the Indexth member of List.
139%   It may be used to select a particular element, or to find where some
140%   given element occurs, or to enumerate the elements and indices togther.
141
142nmember(Elem, [Elem|_], 1).
143nmember(Elem, [_|List], N) :-
144	nmember(Elem, List, M),
145	N is M+1.
146
147% nmembers(+Indices, +Answers, -Ans) or nmembers(-Indices, +Answers, +Ans)
148% (But not nmembers(-,+,-), it loops.)
149% Like nmember/3 except that it looks for a list of arguments in a list
150% of positions.
151% eg.   nmembers([3,5,1], [a,b,c,d,e,f,g,h], [c,e,a]) is true
152
153nmembers([], _, []).
154nmembers([N|Rest], Answers, [Ans|RestAns]) :-
155	nmember(Ans, Answers, N),
156	nmembers(Rest, Answers, RestAns).
157
158%   nth0(?N, ?List, ?Elem) is true when Elem is the Nth member of List,
159%   counting the first as element 0.  (That is, throw away the first
160%   N elements and unify Elem with the next.)
161%   nth1(?N, ?List, ?Elem) is the same as nth0, except that it counts from
162%   1, that is nth(1, [H|_], H).
163
164:- comment(nth0/3, [
165    amode:(nth0(+,+,-) is det),
166    amode:(nth0(-,+,-) is nondet),
167    amode:(nth0(-,-,-) is nondet),
168    args:["I":"Integer position index, counting from 0",
169    	"List":"A list",
170	"Elem":"Any term"],
171    summary:"Access nth element of a list",
172    see_also:[nth1/3,nth0/4,nth1/4],
173    desc:html("\
174	Succeeds when Elem is the Nth member of List, counting the
175	first as element 0.  (That is, throw away the first N elements
176	and unify Elem with the next.)
177    ")]).
178
179nth0(I, Xs, X) :-
180	var(I),
181	nth_nd(I, Xs, X, 0).
182nth0(I, Xs, X) :-
183	nonvar(I),
184	nth0_det(I, Xs, X).
185
186    nth0_det(0, [X|_], El) :- !, El=X.
187    nth0_det(I, [_|Xs], El) :-
188	succ(I1, I),
189	nth0_det(I1, Xs, El).
190
191
192:- comment(nth1/3, [
193    amode:(nth1(+,+,-) is det),
194    amode:(nth1(-,+,-) is nondet),
195    amode:(nth1(-,-,-) is nondet),
196    args:["I":"Integer position index, counting from 1",
197    	"List":"A list",
198	"Elem":"Any term"],
199    summary:"Access nth element of a list",
200    see_also:[nth0/3,nth0/4,nth1/4],
201    desc:html("\
202	Succeeds when Elem is the Nth member of List, counting the
203	first as element 1.
204    ")]).
205
206nth1(I, Xs, X) :-
207	var(I),
208	nth_nd(I, Xs, X, 1).
209nth1(I, Xs, X) :-
210	nonvar(I),
211	nth1_det(I, Xs, X).
212
213    nth1_det(1, [X|_], El) :- !, El=X.
214    nth1_det(I, [_|Xs], El) :-
215	succ(I1, I),
216	nth1_det(I1, Xs, El).
217
218    nth_nd(N, [X|_], X, N).
219    nth_nd(N, [_|Xs], El, I) :-
220	succ(I, I1),
221	nth_nd(N, Xs, El, I1).
222
223
224%   nth0(?N, ?List, ?Elem, ?Rest) unifies Elem with the Nth element of List,
225%   counting from 0, and Rest with the other elements.  It can be used
226%   to select the Nth element of List (yielding Elem and Rest), or to
227%   insert Elem after the Nth (counting from 1) element of Rest, when
228%   it yields List, e.g. nth0(2, List, c, [a,b,d,e]) unifies List with
229%   [a,b,c,d,e].  nth1 is the same except that it counts from 1.  nth1
230%   can be used to insert Elem before the Nth element (couting from 1) of Rest.
231
232:- comment(nth0/4, [
233    amode:(nth0(+,+,-,-) is det),
234    amode:(nth0(-,+,-,-) is nondet),
235    amode:(nth0(-,-,-,-) is nondet),
236    args:["I":"Integer position index, counting from 0",
237    	"List":"A list",
238	"Elem":"Any term",
239	"Rest":"A list"],
240    summary:"Access nth element and remainder of a list",
241    see_also:[nth0/3,nth1/3,nth1/4],
242    desc:html("\
243	Unifies Elem with the Nth element of List, counting from 0,
244	and Rest with the other elements.  It can be used to select
245	the Nth (counting from 0) element of List (yielding Elem and
246	Rest), or to insert Elem after the Nth (counting from 1)
247	element of Rest, when it yields List, e.g. nth0(2, List, c,
248	[a,b,d,e]) unifies List with [a,b,c,d,e].
249    ")]).
250
251nth0(I, Xs, X, Rest) :-
252	var(I),
253	nth_nd(I, Xs, X, Rest, 0).
254nth0(I, Xs, X, Rest) :-
255	nonvar(I),
256	nth0_det(I, Xs, X, Rest).
257
258    nth0_det(0, [X|Xs], El, Rs) :- !, El=X, Rs=Xs.
259    nth0_det(I, [X|Xs], El, [X|Rs]) :-
260	succ(I1, I),
261	nth0_det(I1, Xs, El, Rs).
262
263
264:- comment(nth1/4, [
265    amode:(nth1(+,+,-,-) is det),
266    amode:(nth1(-,+,-,-) is nondet),
267    amode:(nth1(-,-,-,-) is nondet),
268    args:["I":"Integer position index, counting from 1",
269    	"List":"A list",
270	"Elem":"Any term",
271	"Rest":"A list"],
272    summary:"Access nth element and remainder of a list",
273    see_also:[nth0/3,nth1/3,nth0/4],
274    desc:html("\
275	Unifies Elem with the Nth element of List, counting from 1,
276	and Rest with the other elements.  It can be used to select
277	the Nth element of List (yielding Elem and Rest), or to insert
278	Elem before the Nth (counting from 1) element of Rest, when it
279	yields List, e.g. nth1(3, List, c, [a,b,d,e]) unifies List
280	with [a,b,c,d,e].
281    ")]).
282
283nth1(I, Xs, X, Rest) :-
284	var(I),
285	nth_nd(I, Xs, X, Rest, 1).
286nth1(I, Xs, X, Rest) :-
287	nonvar(I),
288	nth1_det(I, Xs, X, Rest).
289
290    nth1_det(1, [X|Xs], El, Rs) :- !, El=X, Rs=Xs.
291    nth1_det(I, [X|Xs], El, [X|Rs]) :-
292	succ(I1, I),
293	nth1_det(I1, Xs, El, Rs).
294
295    nth_nd(N, [X|Xs], X, Xs, N).
296    nth_nd(N, [X|Xs], El, [X|Rs], I) :-
297	succ(I, I1),
298	nth_nd(N, Xs, El, Rs, I1).
299
300
301%   numlist(Lower, Upper, List)
302%   is true when List is [Lower, ..., Upper]
303%   Note that Lower and Upper must be integers, not expressions, and
304%   that if Upper < Lower numlist will FAIL rather than producing an
305%   empty list.
306
307numlist(Upper, Upper, [Upper]) :- !.
308numlist(Lower, Upper, [Lower|Rest]) :-
309	Lower < Upper,
310	Next is Lower+1,
311	numlist(Next, Upper, Rest).
312
313
314
315%   perm(List, Perm)
316%   is true when List and Perm are permutations of each other.  Of course,
317%   if you just want to test that, the best way is to keysort/2 the two
318%   lists and see if the results are the same.  Or you could use list_to_bag
319%   (from BagUtl.Pl) to see if they convert to the same bag.  The point of
320%   perm is to generate permutations.  The arguments may be either way round,
321%   the only effect will be the order in which the permutations are tried.
322%   Be careful: this is quite efficient, but the number of permutations of an
323%   N-element list is N!, even for a 7-element list that is 5040.
324
325perm([], []).
326perm(List, [First|Perm]) :-
327	select(First, List, Rest),	%  tries each List element in turn
328	perm(Rest, Perm).
329
330
331
332
333%   perm2(A,B, C,D)
334%   is true when {A,B} = {C,D}.  It is very useful for writing pattern
335%   matchers over commutative operators.  It is used more than perm is.
336
337perm2(X,Y, X,Y).
338perm2(X,Y, Y,X).
339
340%   remove_dups(List, Pruned)
341%   removes duplicated elements from List.  Beware: if the List has
342%   non-ground elements, the result may surprise you.
343
344remove_dups(List, Pruned) :-
345	sort(List, Pruned).
346
347%   reverse(List, Reversed)
348%   is true when List and Reversed are lists with the same elements
349%   but in opposite orders.  rev/2 is a synonym for reverse/2.
350
351rev(List, Reversed) :-
352	reverse(List, Reversed).
353
354%reverse(List, Reversed) :-
355%	reverse(List, [], Reversed).
356%
357%reverse([], Reversed, Reversed).
358%reverse([Head|Tail], Sofar, Reversed) :-
359%	reverse(Tail, [Head|Sofar], Reversed).
360
361
362%   same_length(?List1, ?List2)
363%   is true when List1 and List2 are both lists and have the same number
364%   of elements.  No relation between the values of their elements is
365%   implied.
366%   Modes same_length(-,+) and same_length(+,-) generate either list given
367%   the other; mode same_length(-,-) generates two lists of the same length,
368%   in which case the arguments will be bound to lists of length 0, 1, 2, ...
369
370same_length([], []).
371same_length([_|List1], [_|List2]) :-
372	same_length(List1, List2).
373
374%   select(X, Xlist, Y, Ylist)
375% >> NB  This is select/4, not select/3 !!
376%   is true when X is the Kth member of Xlist and Y the Kth element of Ylist
377%   for some K, and apart from that Xlist and Ylist are the same.  You can
378%   use it to replace X by Y or vice versa.
379
380select(X, [X|Tail], Y, [Y|Tail]).
381select(X, [Head|Xlist], Y, [Head|Ylist]) :-
382	select(X, Xlist, Y, Ylist).
383
384%   shorter_list(Short, Long)
385%   is true when Short is a list is strictly shorter than Long.  Long
386%   doesn't have to be a proper list provided it is long enough.  This
387%   can be used to generate lists shorter than Long, lengths 0, 1, 2...
388%   will be tried, but backtracking will terminate with a list that is
389%   one element shorter than Long.  It cannot be used to generate lists
390%   longer than Short, because it doesn't look at all the elements of the
391%   longer list.
392
393shorter_list([], [_|_]).
394shorter_list([_|Short], [_|Long]) :-
395	shorter_list(Short, Long).
396
397
398
399%   subseq(Sequence, SubSequence, Complement)
400%   is true when SubSequence and Complement are both subsequences of the
401%   list Sequence (the order of corresponding elements being preserved)
402%   and every element of Sequence which is not in SubSequence is in the
403%   Complement and vice versa.  That is,
404%   length(Sequence) = length(SubSequence)+length(Complement), e.g.
405%   subseq([1,2,3,4], [1,3,4], [2]).  This was written to generate subsets
406%   and their complements together, but can also be used to interleave two
407%   lists in all possible ways.  Note that if S1 is a subset of S2, it will
408%   be generated *before S2 as a SubSequence and *after it as a Complement.
409
410subseq([], [], []).
411subseq([Head|Tail], Sbsq, [Head|Cmpl]) :-
412	subseq(Tail, Sbsq, Cmpl).
413subseq([Head|Tail], [Head|Sbsq], Cmpl) :-
414	subseq(Tail, Sbsq, Cmpl).
415
416
417
418%   subseq0(Sequence, SubSequence)
419%   is true when SubSequence is a subsequence of Sequence, but may
420%   be Sequence itself.   Thus subseq0([a,b], [a,b]) is true as well
421%   as subseq0([a,b], [a]).
422
423%   subseq1(Sequence, SubSequence)
424%   is true when SubSequence is a proper subsequence of Sequence,
425%   that is it contains at least one element less.
426
427%   ?- setof(X, subseq0([a,b,c],X), Xs).
428%   Xs = [[],[a],[a,b],[a,b,c],[a,c],[b],[b,c],[c]]
429%   ?- bagof(X, subseq0([a,b,c,d],X), Xs).
430%   Xs = [[a,b,c,d],[b,c,d],[c,d],[d],[],[c],[b,d],[b],[b,c],[a,c,d],
431%	  [a,d],[a],[a,c],[a,b,d],[a,b],[a,b,c]]
432
433subseq0(List, List).
434
435subseq0(List, Rest) :-
436	subseq1(List, Rest).
437
438
439subseq1([_|Tail], Rest) :-
440	subseq0(Tail, Rest).
441
442subseq1([Head|Tail], [Head|Rest]) :-
443	subseq1(Tail, Rest).
444
445%   sumlist(Numbers, Total)
446%   is true when Numbers is a list of integers, and Total is their sum.
447
448sumlist(Numbers, Total) :-
449	sumlist(Numbers, 0, Total).
450
451sumlist([], Total, Total).
452sumlist([Head|Tail], Sofar, Total) :-
453	Next is Sofar+Head,
454	sumlist(Tail, Next, Total).
455
456
457%   copied from setutl.pl:
458%   select(?Element, ?Set, ?Residue)
459%   is true when Set is a list, Element occurs in Set, and Residue is
460%   everything in Set except Element (things stay in the same order).
461
462select(Element, [Element|Rest], Rest).
463select(Element, [Head|Tail], [Head|Rest]) :-
464	select(Element, Tail, Rest).
465
466
467