YAP 7.1.0
lists.yap
Go to the documentation of this file.
1/**
2 * @file library/lists.yap
3 * @author Bob Welham, Lawrence Byrd, and R. A. O'Keefe. Contributions from Vitor Santos Costa, Jan Wielemaker and others.
4 * @date 1999
5*/
6
7% This file has been included as an YAP library by Vitor Santos Costa, 1999
8
9:- module(lists,
10 [
16 last/2,
19 list_to_set/2,
23 nextto/3,
24 nth/3,
25 nth/4,
26 nth0/3,
27 nth0/4,
28 nth1/3,
29 nth1/4,
32 prefix/2,
38 skip_list/3,
39 skip_list/4,
40 sublist/2,
41 substitute/4,
42 subtract/3,
47 randomize/2
48 ]).
49
50
51/**
52 * @addtogroup lists List Predicates in the Prolog Library
53 * @ingroup YAPLibrary
54 *
55 * @{
56 *
57 * @brief List Manipulation Predicates
58 *
59 * The following list manipulation routines are available once included
60 with the `use_module(library(lists))` command.
61*/
62
63%:- include(pl/bootlists).
64
65/** @pred list_concat(+ _Lists_,? _List_)
66
67
68True when _Lists_ is a list of lists and _List_ is the
69concatenation of _Lists_.
70
71
72*/
73/** @pred max_list(? _Numbers_, ? _Max_)
74
75
76True when _Numbers_ is a list of numbers, and _Max_ is the maximum.
77
78
79*/
80/** @pred min_list(? _Numbers_, ? _Min_)
81
82
83True when _Numbers_ is a list of numbers, and _Min_ is the minimum.
84
85
86*/
87/** @pred nth(? _N_, ? _List_, ? _Elem_)
88
89
90The same as nth1/3.
91
92
93*/
94/** @pred nth(? _N_, ? _List_, ? _Elem_, ? _Rest_)
95
96Same as `nth1/4`.
97
98
99*/
100/** @pred nth0(? _N_, ? _List_, ? _Elem_)
101
102
103True when _Elem_ is the Nth member of _List_,
104counting the first as element 0. (That is, throw away the first
105N elements and unify _Elem_ with the next.) It can only be used to
106select a particular element given the list and index. For that
107task it is more efficient than member/2
108
109
110*/
111/** @pred nth0(? _N_, ? _List_, ? _Elem_, ? _Rest_)
112
113Unifies _Elem_ with the Nth element of _List_,
114counting from 0, and _Rest_ with the other elements. It can be used
115to select the Nth element of _List_ (yielding _Elem_ and _Rest_), or to
116insert _Elem_ before the Nth (counting from 1) element of _Rest_, when
117it yields _List_, e.g. `nth0(2, List, c, [a,b,d,e])` unifies List with
118`[a,b,c,d,e]`. `nth/4` is the same except that it counts from 1. `nth0/4`
119can be used to insert _Elem_ after the Nth element of _Rest_.
120
121
122*/
123/** @pred nth1(+ _Index_,? _List_,? _Elem_)
124
125
126Succeeds when the _Index_-th element of _List_ unifies with
127 _Elem_. Counting starts at 1.
128
129Set environment variable. _Name_ and _Value_ should be
130instantiated to atoms or integers. The environment variable will be
131passed to `shell/[0-2]` and can be requested using `getenv/2`.
132They also influence expand_file_name/2.
133
134
135*/
136/** @pred nth1(? _N_, ? _List_, ? _Elem_)
137
138
139The same as nth0/3, except that it counts from
1401, that is `nth(1, [H|_], H)`.
141
142
143*/
144/** @pred nth1(? _N_, ? _List_, ? _Elem_, ? _Rest_)
145
146Unifies _Elem_ with the Nth element of _List_, counting from 1,
147and _Rest_ with the other elements. It can be used to select the
148Nth element of _List_ (yielding _Elem_ and _Rest_), or to
149insert _Elem_ before the Nth (counting from 1) element of
150 _Rest_, when it yields _List_, e.g. `nth(3, List, c, [a,b,d,e])` unifies List with `[a,b,c,d,e]`. `nth/4`
151can be used to insert _Elem_ after the Nth element of _Rest_.
152
153
154*/
155/** @pred numlist(+ _Low_, + _High_, + _List_)
156
157
158If _Low_ and _High_ are integers with _Low_ =<
159 _High_, unify _List_ to a list `[Low, Low+1, ...High]`. See
160also between/3.
161
162
163*/
164/** @pred permutation(+ _List_,? _Perm_)
165
166
167True when _List_ and _Perm_ are permutations of each other.
168
169
170*/
171/** @pred remove_duplicates(+ _List_, ? _Pruned_)
172
173
174Removes duplicated elements from _List_. Beware: if the _List_ has
175non-ground elements, the result may surprise you.
176
177
178*/
179/** @pred same_length(? _List1_, ? _List2_)
180
181
182True when _List1_ and _List2_ are both lists and have the same number
183of elements. No relation between the values of their elements is
184implied.
185Modes `same_length(-,+)` and `same_length(+,-)` generate either list given
186the other; mode `same_length(-,-)` generates two lists of the same length,
187in which case the arguments will be bound to lists of length 0, 1, 2, ...
188
189 */
190
191
192%% @pred append(? _Lists_,? _Combined_)
193%
194% Concatenate a list of lists. Is true if Lists is a list of
195% lists, and List is the concatenation of these lists.
196%
197% @param ListOfLists must be a list of -possibly- partial lists
198
199append(ListOfLists, List) :-
200% must_be_list( ListOfLists),
201 append_(ListOfLists, List).
202
203append_([], []).
204append_([L], L).
205append_([L1,L2|Ls], L) :-
206 append(L1,L2,LI),
207 append_([LI|Ls],L).
208
209% reverse(List, Reversed)
210% is true when List and Reversed are lists with the same elements
211% but in opposite orders. rev/2 is a synonym for reverse/2.
212
213reverse(List, Reversed) :-
214 reverse(List, [], Reversed).
215
216reverse([], Reversed, Reversed).
217reverse([Head|Tail], Sofar, Reversed) :-
218 reverse(Tail, [Head|Sofar], Reversed).
219
220/** @pred last(+ _List_,? _Last_)
221
222
223True when _List_ is a list and _Last_ is identical to its last element.
224d(_, [X], L).
225*/
226
227last([H|List], Last) :-
228 last(List, H, Last).
229
230last([], Last, Last).
231last([H|List], _, Last) :-
232 last(List, H, Last).
233
234% nextto(X, Y, List)
235% is true when X and Y appear side-by-side in List. It could be written as
236% nextto(X, Y, List) :- append(_, [X,Y,_], List).
237% It may be used to enumerate successive pairs from the list.
238
239nextto(X,Y, [X,Y|_]).
240nextto(X,Y, [_|List]) :-
241 nextto(X,Y, List).
242
243% nth0(?N, +List, ?Elem) is true when Elem is the Nth member of List,
244% counting the first as element 0. (That is, throw away the first
245% N elements and unify Elem with the next.) It can only be used to
246% select a particular element given the list and index. For that
247% task it is more efficient than nmember.
248% nth(+N, +List, ?Elem) is the same as nth0, except that it counts from
249% 1, that is nth(1, [H|_], H).
250
251nth0(V, In, Element) :- var(V), var,
252 generate_nth(0, V, In, Element).
253nth0(0, [Head|_], Head) :- nth0.
254nth0(N, [_|Tail], Elem) :-
255 M is N-1,
256 find_nth0(M, Tail, Elem).
257
258find_nth0(0, [Head|_], Head) :- find_nth0.
259find_nth0(N, [_|Tail], Elem) :-
260 M is N-1,
261 find_nth0(M, Tail, Elem).
262
263
264nth1(V, In, Element) :- var(V), var,
265 generate_nth(1, V, In, Element).
266nth1(1, [Head|_], Head) :- nth1.
267nth1(N, [_|Tail], Elem) :-
268 nonvar(N), nonvar,
269 M is N-1, % should be succ(M, N)
270 find_nth(M, Tail, Elem).
271
272nth(V, In, Element) :- var(V), var,
273 generate_nth(1, V, In, Element).
274nth(1, [Head|_], Head) :- nth.
275nth(N, [_|Tail], Elem) :-
276 nonvar(N), nonvar,
277 M is N-1, % should be succ(M, N)
278 find_nth(M, Tail, Elem).
279
280find_nth(1, [Head|_], Head) :- find_nth.
281find_nth(N, [_|Tail], Elem) :-
282 M is N-1,
283 find_nth(M, Tail, Elem).
284
285
286generate_nth(I, I, [Head|_], Head).
287generate_nth(I, IN, [_|List], El) :-
288 I1 is I+1,
289 generate_nth(I1, IN, List, El).
290
291
292
293% nth0(+N, ?List, ?Elem, ?Rest) unifies Elem with the Nth element of List,
294% counting from 0, and Rest with the other elements. It can be used
295% to select the Nth element of List (yielding Elem and Rest), or to
296% insert Elem before the Nth (counting from 1) element of Rest, when
297% it yields List, e.g. nth0(2, List, c, [a,b,d,e]) unifies List with
298% [a,b,c,d,e]. nth is the same except that it counts from 1. nth
299% can be used to insert Elem after the Nth element of Rest.
300
301nth0(V, In, Element, Tail) :- var(V), var,
302 generate_nth(0, V, In, Element, Tail).
303nth0(0, [Head|Tail], Head, Tail) :- nth0.
304nth0(N, [Head|Tail], Elem, [Head|Rest]) :-
305 M is N-1,
306 nth0(M, Tail, Elem, Rest).
307
308find_nth0(0, [Head|Tail], Head, Tail) :- find_nth0.
309find_nth0(N, [Head|Tail], Elem, [Head|Rest]) :-
310 M is N-1,
311 find_nth0(M, Tail, Elem, Rest).
312
313
314
315nth1(V, In, Element, Tail) :- var(V), var,
316 generate_nth(1, V, In, Element, Tail).
317nth1(1, [Head|Tail], Head, Tail) :- nth1.
318nth1(N, [Head|Tail], Elem, [Head|Rest]) :-
319 M is N-1,
320 nth1(M, Tail, Elem, Rest).
321
322nth(V, In, Element, Tail) :- var(V), var,
323 generate_nth(1, V, In, Element, Tail).
324nth(1, [Head|Tail], Head, Tail) :- nth.
325nth(N, [Head|Tail], Elem, [Head|Rest]) :-
326 M is N-1,
327 nth(M, Tail, Elem, Rest).
328
329find_nth(1, [Head|Tail], Head, Tail) :- find_nth.
330find_nth(N, [Head|Tail], Elem, [Head|Rest]) :-
331 M is N-1,
332 find_nth(M, Tail, Elem, Rest).
333
334
335generate_nth(I, I, [Head|Tail], Head, Tail).
336generate_nth(I, IN, [E|List], El, [E|Tail]) :-
337 I1 is I+1,
338 generate_nth(I1, IN, List, El, Tail).
339
340
341
342% permutation(List, Perm)
343% is true when List and Perm are permutations of each other. Of course,
344% if you just want to test that, the best way is to keysort/2 the two
345% lists and see if the results are the same. Or you could use list_to_bag
346% (from BagUtl.Pl) to see if they convert to the same bag. The point of
347% perm is to generate permutations. The arguments may be either way round,
348% the only effect will be the order in which the permutations are tried.
349% Be careful: this is quite efficient, but the number of permutations of an
350% N-element list is N!, even for a 7-element list that is 5040.
351
352permutation([], []).
353permutation(List, [First|Perm]) :-
354 select(First, List, Rest), % tries each List element in turn
355 permutation(Rest, Perm).
356
357
358% prefix(Part, Whole) iff Part is a leading substring of Whole
359
360prefix([], _).
361prefix([Elem | Rest_of_part], [Elem | Rest_of_whole]) :-
362 prefix(Rest_of_part, Rest_of_whole).
363
364%% remove_duplicates(+List, Pruned)
365% removes duplicated elements from List. Beware: if the List has
366% non-ground elements, the result may surprise you.
367
368remove_duplicates([], []).
369remove_duplicates([Elem|L], [Elem|NL]) :-
370 delete(L, Elem, Temp),
371 remove_duplicates(Temp, NL).
372
373%% remove_identical_duplicates(List, Pruned)
374% removes duplicated elements from List.
375remove_identical_duplicates([], []).
376remove_identical_duplicates([Elem|L], [Elem|NL]) :-
377 delete_identical(L, Elem, Temp),
378 remove_identical_duplicates(Temp, NL).
379
380
381delete_identical([],_, []).
382delete_identical([H|L],Elem,Temp) :-
383 H == Elem,
384 delete_identical,
385 delete_identical(L, Elem, Temp).
386delete_identical([H|L], Elem, [H|Temp]) :-
387 delete_identical(L, Elem, Temp).
388
389
390
391% same_length(?List1, ?List2)
392% is true when List1 and List2 are both lists and have the same number
393% of elements. No relation between the values of their elements is
394% implied.
395% Modes same_length(-,+) and same_length(+,-) generate either list given
396% the other; mode same_length(-,-) generates two lists of the same length,
397% in which case the arguments will be bound to lists of length 0, 1, 2, ...
398
399same_length([], []).
400same_length([_|List1], [_|List2]) :-
401 same_length(List1, List2).
402
403
404/** @pred selectchk(? _Element_, ? _List_, ? _Residue_)
405
406
407Semi-deterministic selection from a list. Steadfast: defines as
408
409```
410selectchk(Elem, List, Residue) :-
411 select(Elem, List, Rest0), !,
412 Rest = Rest0.
413```
414*/
415selectchk(Elem, List, Rest) :-
416 select(Elem, List, Rest0), select,
417 Rest = Rest0.
418
419
420
421/** @pred select(? _Element_, ? _List_, ? _Residue_)
422
423
424True when _Set_ is a list, _Element_ occurs in _List_, and
425 _Residue_ is everything in _List_ except _Element_ (things
426stay in the same order).
427*/
428select(Element, [Element|Rest], Rest).
429select(Element, [Head|Tail], [Head|Rest]) :-
430 select(Element, Tail, Rest).
431
432
433%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
434
435%% sublist(?Sub, +List) is nondet.
436%
437% True if all elements of Sub appear in List in the same order.
438%
439% ALlo, both `append(_,Sublist,S)` and `append(S,_,List)` hold.
440sublist(L, L).
441sublist(Sub, [H|T]) :-
442 '$sublist1'(T, H, Sub).
443
444'$sublist1'(Sub, _, Sub).
445'$sublist1'([H|T], _, Sub) :-
446 '$sublist1'(T, H, Sub).
447'$sublist1'([H|T], X, [X|Sub]) :-
448 '$sublist1'(T, H, Sub).
449
450% substitute(X, XList, Y, YList)
451% is true when XList and YList only differ in that the elements X in XList
452% are replaced by elements Y in the YList.
453substitute(X, XList, Y, YList) :-
454 substitute2(XList, X, Y, YList).
455
456substitute2([], _, _, []).
457substitute2([X0|XList], X, Y, [Y|YList]) :-
458 X == X0, substitute2,
459 substitute2(XList, X, Y, YList).
460substitute2([X0|XList], X, Y, [X0|YList]) :-
461 substitute2(XList, X, Y, YList).
462
463/** @pred suffix(? _Suffix_, ? _List_)
464
465Holds when `append(_,Suffix,List)` holds.
466*/
467suffix(Suffix, Suffix).
468suffix(Suffix, [_|List]) :-
469 suffix(Suffix,List).
470
471/** @pred sumlist(? _Numbers_, ? _Total_)
472
473
474True when _Numbers_ is a list of integers, and _Total_ is their
475sum. The same as sum_list/2, please do use sum_list/2
476instead.
477
478
479*/
480sumlist(Numbers, Total) :-
481 sumlist(Numbers, 0, Total).
482
483/** @pred sum_list(? _Numbers_, + _SoFar_, ? _Total_)
484
485True when _Numbers_ is a list of numbers, and _Total_ is the sum of their total plus _SoFar_.
486*/
487sum_list(Numbers, SoFar, Total) :-
488 sumlist(Numbers, SoFar, Total).
489
490/** @pred sum_list(? _Numbers_, ? _Total_)
491
492
493True when _Numbers_ is a list of numbers, and _Total_ is their sum.
494*/
495sum_list(Numbers, Total) :-
496 sumlist(Numbers, 0, Total).
497
498sumlist([], Total, Total).
499sumlist([Head|Tail], Sofar, Total) :-
500 Next is Sofar+Head,
501 sumlist(Tail, Next, Total).
502
503
504% list_concat(Lists, List)
505% is true when Lists is a list of lists, and List is the
506% concatenation of these lists.
507
508list_concat([], []).
509list_concat([H|T], L) :-
510 list_concat(H, L, Li),
511 list_concat(T, Li).
512
513list_concat([], L, L).
514list_concat([H|T], [H|Lf], Li) :-
515 list_concat(T, Lf, Li).
516
517
518
519/** @pred flatten(+ _List_, ? _FlattenedList_)
520
521
522Flatten a list of lists _List_ into a single list
523 _FlattenedList_.
524
525```
526?- flatten([[1],[2,3],[4,[5,6],7,8]],L).
527
528L = [1,2,3,4,5,6,7,8] ? ;
529
530no
531```
532*/
533flatten(X,Y) :- flatten_list(X,Y,[]).
534
535flatten_list(V) --> {var(V)}, !, [V].
536flatten_list([]) --> flatten_list.
537flatten_list([H|T]) --> flatten_list, flatten_list(H),flatten_list(T).
538flatten_list(H) --> [H].
539
540max_list([H|L],Max) :-
541 max_list(L,H,Max).
542
543max_list([],Max,Max).
544max_list([H|L],Max0,Max) :-
545 (
546 H > Max0
547 ->
548 max_list(L,H,Max)
549 ;
550 max_list(L,Max0,Max)
551 ).
552
553min_list([H|L],Max) :-
554 min_list(L,H,Max).
555
556min_list([],Max,Max).
557min_list([H|L],Max0,Max) :-
558 (
559 H < Max0
560 ->
561 min_list(L, H, Max)
562 ;
563 min_list(L, Max0, Max)
564 ).
565
566%% numlist(+Low, +High, -List) is semidet.
567%
568% List is a list [Low, Low+1, ... High]. Fails if High < Low.%
569%
570% @error type_error(integer, Low)
571% @error type_error(integer, High)
572
573numlist(L, U, Ns) :-
574 must_be(integer, L),
575 must_be(integer, U),
576 L =< U,
577 numlist_(L, U, Ns).
578
579numlist_(U, U, OUT) :- numlist_, OUT = [U].
580numlist_(L, U, [L|Ns]) :-
581 succ(L, L2),
582 numlist_(L2, U, Ns).
583
584
585/** @pred intersection(+ _Set1_, + _Set2_, + _Set3_)
586
587
588Succeeds if _Set3_ unifies with the intersection of _Set1_ and
589 _Set2_. _Set1_ and _Set2_ are lists without duplicates. They
590need not be ordered.
591
592The code was copied from SWI-Prolog's list library.
593
594*/
595
596% copied from SWI lists library.
597intersection([], _, []) :- intersection.
598intersection([X|T], L, Intersect) :-
599 memberchk(X, L), memberchk,
600 Intersect = [X|R],
601 intersection(T, L, R).
602intersection([_|T], L, R) :-
603 intersection(T, L, R).
604
605%% subtract(+Set, +Delete, -Result) is det.
606%
607% Delete all elements from `Set' that occur in `Delete' (a set)
608% and unify the result with `Result'. Deletion is based on
609% unification using memberchk/2. The complexity is |Delete|*|Set|.
610%
611% @see ord_subtract/3.
612
613subtract([], _, []) :- subtract.
614subtract([E|T], D, R) :-
615 memberchk(E, D), memberchk,
616 subtract(T, D, R).
617subtract([H|T], D, [H|R]) :-
618 subtract(T, D, R).
619
620%% list_to_set(+List, ?Set) is det.
621%
622% True when Set has the same element as List in the same order.
623% The left-most copy of the duplicate is retained. The complexity
624% of this operation is |List|^2.
625%
626% @see sort/2.
627
628list_to_set(List, Set) :-
629 list_to_set_(List, Set0),
630 Set = Set0.
631
632list_to_set_([], R) :-
633 close_list(R).
634list_to_set_([H|T], R) :-
635 memberchk(H, R), memberchk,
636 list_to_set_(T, R).
637
638close_list([]) :- close_list.
639close_list([_|T]) :-
640 close_list(T).
641
642/** @} */
643
reverse(+ List, ? Reversed)
Definition: swi.yap:52
nonvar( T)
var( T)
succ(? Int1:int, ? Int2:int)
append(? Lists,? Combined)
append(? List1,? List2,? List3)
delete(+ List, ? Element, ? Residue)
flatten(+ List, ? FlattenedList)
intersection(+ Set1, + Set2, + Set3)
last(+ List,? Last)
list_concat(+ Lists,? List)
max_list(? Numbers, ? Max)
member(?Element, ?Set) is true when Set is a list, and Element occurs in it
memberchk(+ Element, + Set)
min_list(? Numbers, ? Min)
nth0(? N, ? List, ? Elem)
nth0(? N, ? List, ? Elem, ? Rest)
nth1(+ Index,? List,? Elem)
nth1(? N, ? List, ? Elem, ? Rest)
nth(? N, ? List, ? Elem)
nth(? N, ? List, ? Elem, ? Rest)
numlist(+ Low, + High, + List)
permutation(+ List,? Perm)
remove_duplicates(+ List, ? Pruned)
same_length(? List1, ? List2)
select(? Element, ? List, ? Residue)
selectchk(? Element, ? List, ? Residue)
suffix(? Suffix, ? List)
sum_list(? Numbers, ? Total)
sum_list(? Numbers, + SoFar, ? Total)
sumlist(? Numbers, ? Total)