1% ----------------------------------------------------------------------
2% BEGIN LICENSE BLOCK
3% Version: CMPL 1.1
4%
5% The contents of this file are subject to the Cisco-style Mozilla Public
6% License Version 1.1 (the "License"); you may not use this file except
7% in compliance with the License.  You may obtain a copy of the License
8% at www.eclipse-clp.org/license.
9%
10% Software distributed under the License is distributed on an "AS IS"
11% basis, WITHOUT WARRANTY OF ANY KIND, either express or implied.  See
12% the License for the specific language governing rights and limitations
13% under the License.
14%
15% The Original Code is  The ECLiPSe Constraint Logic Programming System.
16% The Initial Developer of the Original Code is  Cisco Systems, Inc.
17% Portions created by the Initial Developer are
18% Copyright (C) 1989-2006 Cisco Systems, Inc.  All Rights Reserved.
19%
20% Contributor(s): ECRC GmbH
21% Contributor(s): IC-Parc, Imperal College London
22%
23% END LICENSE BLOCK
24%
25% System:	ECLiPSe Constraint Logic Programming System
26% Version:	$Id: lists.pl,v 1.9 2015/04/30 23:40:47 jschimpf Exp $
27% ----------------------------------------------------------------------
28
29/*
30 * SEPIA PROLOG SOURCE MODULE
31 *
32 * IDENTIFICATION:	lists.pl
33 *
34 * DESCRIPTION: 	List manipulation library predicates
35 *			Some of them are already needed in the kernel,
36 *			defined there, and reexported here.
37 *
38 * CONTENTS:
39 *	member/2,
40 *	memberchk/2,
41 *	append/3,
42 *	nonmember/2,
43 *	delete/3,
44 *	intersection/3,
45 *	subtract/3,
46 *	union/3,
47 *	list_check/3,
48 *	length/2.
49 *
50 */
51
52%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
53:- module(lists).
54
55:- comment(categories, ["Data Structures","Programming Utilities"]).
56:- comment(summary, "Predicates for list manipulation").
57:- comment(copyright, "Cisco Systems, Inc").
58:- comment(date, "$Date: 2015/04/30 23:40:47 $").
59:- comment(desc, html("<p>
60    Library containing various simple list manipulation predicates which
61    require no special form of lists. For ordered lists see library(ordset).
62    A number of basic list processing predicates (is_list/1, append/3,
63    member/2, length/2 etc) are available by default and do not require
64    this library to be loaded.
65</p><p>
66    Note that in the predicate descriptions for this library, the '+' mode
67    in the mode specification for list-valued arguments indicates that the
68    list argument is required to be a proper list in the sense of is_list/1,
69    i.e. all list tails must be recursively instantiated.
70</p>
71")).
72
73
74% Make sure that the important operators are ok
75:-	op(1100, xfy, ;),
76	op(1050, xfy, ->).
77
78:- pragma(system).
79
80:- export
81	checklist/2,
82	flatten/2,
83	flatten/3,
84	collection_to_list/2,
85	halve/3,
86	intersection/3,
87	maplist/3,
88	print_list/1,
89	select/3,
90	shuffle/2,
91	splice/3,
92	subset/2,
93	union/3.
94
95:- reexport
96	append/3,
97	delete/3,
98	length/2,
99	member/2,
100	memberchk/2,
101	nonmember/2,
102	subtract/3,
103	reverse/2
104    from sepia_kernel.
105
106
107:- tool(maplist/3, maplist_body/4).
108:- meta_predicate(maplist(2,*,*)).
109:- tool(checklist/2, checklist_body/3).
110:- meta_predicate(checklist(1,*)).
111:- tool(print_list/1, print_list_/2).
112
113
114
115% intersection(L1, L2, L3)
116% L3 is the intersection of L1 and L2, with arguments ordered as in L1
117
118intersection([], _, []).
119intersection([Head|L1tail], L2, L3) :-
120	memberchk(Head, L2),
121	!,
122	L3 = [Head|L3tail],
123	intersection(L1tail, L2, L3tail).
124intersection([_|L1tail], L2, L3) :-
125	intersection(L1tail, L2, L3).
126
127
128% union(L1, L2, L3)
129% L3 is (L1-L2) + L2
130
131union([], L, L).
132union([Head|L1tail], L2, L3) :-
133	memberchk(Head, L2),
134	!,
135	union(L1tail, L2, L3).
136union([Head|L1tail], L2, [Head|L3tail]) :-
137	union(L1tail, L2, L3tail).
138
139% subset(Subset, S)
140
141subset([],[]).
142subset([X|L],[X|S]) :-
143    subset(L,S).
144subset(L, [_|S]) :-
145    subset(L,S).
146
147
148% list_check(List, 0, Length)
149% succeeds iff List is a proper list and Length is its length
150
151list_check(L, _, _) :-
152	var(L),
153	!,
154	fail.
155list_check([], N, N).
156list_check([_|T], SoFar, Res) :-
157	New is SoFar+1,
158	list_check(T, New, Res).
159
160
161maplist_body(_, [], [], _).
162maplist_body(Pred, [H1|T1], [H2|T2], M) :-
163	Pred =.. PL,
164	append(PL, [H1, H2], NewPred),
165	Call =.. NewPred,
166	call(Call)@M,
167	maplist_body(Pred, T1, T2, M).
168
169checklist_body(_, [], _).
170checklist_body(Pred, [Head|Tail], M) :-
171	Pred =.. PL,
172	append(PL, [Head], NewPred),
173	Call =.. NewPred,
174	call(Call)@M,
175	checklist_body(Pred, Tail, M).
176
177flatten(List, Flat) :-
178	flatten_aux(List, Flat, []).
179
180flatten_aux([], Res, Cont) :- -?-> !, Res = Cont.
181flatten_aux([Head|Tail], Res, Cont) :-
182	-?->
183	!,
184	flatten_aux(Head, Res, Cont1),
185	flatten_aux(Tail, Cont1, Cont).
186flatten_aux(Term, [Term|Cont], Cont).
187
188    % Depth-limited flatten.
189flatten(Depth, List, Flat) :-
190	( Depth > 0 ->
191	    flatten_aux(Depth, List, Flat, [])
192	;
193	    Flat = List
194	).
195
196flatten_aux(_Depth, [], Res, Cont) :- -?-> !, Res = Cont.
197flatten_aux(Depth, [Head|Tail], Res, Cont) :-
198	-?->
199	!,
200	( Depth > 0 ->
201	    Depth1 is Depth - 1,
202	    flatten_aux(Depth1, Head, Res, Cont1)
203	;
204	    Res = [Head|Cont1]
205	),
206	flatten_aux(Depth, Tail, Cont1, Cont).
207flatten_aux(_, Term, [Term|Cont], Cont).
208
209
210% TEMPORARY: local subscript/3
211
212:- local subscript/3.
213:- tool(subscript/3, subscript/4).
214
215%
216% subscript(+Matrix, +IndexList, ?Element)
217%
218subscript(Mat, Index, X, M) :-
219	var(Index), !,
220	( get_flag(coroutine,on) ->
221	    suspend(subscript(Mat, Index, X, M), 2, Index->inst)
222	;
223	    error(4, subscript(Mat,Index,X), M)
224	).
225subscript(Mat, [], X, _M) :- !, X = Mat.
226subscript(Mat, [IExpr|IExprs], X, M) :- !,
227	subscript3(Mat, IExpr, X, M, IExprs).
228subscript(Mat, Index, X, M) :-
229	error(5, subscript(Mat,Index,X), M).
230
231    subscript3(Mat, IExpr, X, M, IExprs) :-
232	var(Mat), !,
233	( get_flag(coroutine,on) ->
234	    suspend(subscript(Mat,[IExpr|IExprs],X,M), 2, Mat->inst)
235	;
236	    error(4, subscript(Mat,[IExpr|IExprs],X), M)
237	).
238    subscript3(Mat, IExpr, X, M, IExprs) :-
239	compound(Mat), !,
240	subscript1(Mat, IExpr, X, M, IExprs).
241    subscript3(Mat, IExpr, X, M, IExprs) :-
242	is_handle(Mat), !,
243	( IExprs = [] ->
244	    eval(IExpr, I)@M,
245	    xget(Mat, I, X)
246	;
247	    error(6, subscript(Mat,[IExpr|IExprs],X), M)
248	).
249    subscript3(Mat, IExpr, X, M, IExprs) :-
250	string(Mat), !,
251	( IExprs = [] ->
252	    eval(IExpr, I)@M,
253	    string_code(Mat, I, X)
254	;
255	    error(6, subscript(Mat,[IExpr|IExprs],X), M)
256	).
257    subscript3(Mat, IExpr, X, M, IExprs) :-
258	error(5, subscript(Mat,[IExpr|IExprs],X), M).
259
260    subscript1(Mat, IExpr, X, M, IExprs) :- integer(IExpr), !,
261	arg(IExpr, Mat, Row),
262	subscript(Row, IExprs, X, M).
263    subscript1(Mat, Min..Max, Xs, M, IExprs) :- -?-> !,
264	eval(Min, Imin)@M,
265	eval(Max, Imax)@M,
266	% code for returning sub-arrays
267	Offset is Imin-1,
268	N is Imax-Offset,
269	( N >= 0 ->
270	    functor(Xs, [], N),
271	    ( foreacharg(X,Xs,J), param(Offset,Mat,IExprs,M) do
272		I is J+Offset,
273		arg(I, Mat, Row),
274		subscript(Row, IExprs, X, M)
275	    )
276	;
277	    error(6, subscript(Mat,[Min..Max|IExprs],Xs), M)
278	).
279    subscript1(Mat, IExpr, X, M, IExprs) :-
280	eval(IExpr, I)@M,
281	arg(I, Mat, Row),
282	subscript(Row, IExprs, X, M).
283
284
285:- comment(collection_to_list/2, [
286    summary:"Convert a \"collection\" into a list",
287    amode:(collection_to_list(+,-) is semidet),
288    args:["Collection":"A term to be interpreted as a collection",
289    	"List":"Output list"],
290    fail_if:"Collection is not a collection",
291    desc:html("\
292   Converts various \"collection\" data structures into a list.  Fails if it
293   does not know how to do this.  The supported collection types are:
294<DL>
295   <DT>List<DD>
296	The list is returned unchanged.
297   <DT>Array<DD>
298	The array is converted into a list using array_list/2.
299   <DT>Subscript reference Array[...]<DD>
300	subscript/3 is called to evaluate the subscript reference.  If this
301	results in a single array element, a one-element list is returned.
302	If subscript/3 results in a sub-array, this is converted into a list.
303	For multi-dimensional sub-arrays, only the top level is converted
304	into a list (no implicit flattening).
305   <DT>flatten(N, Collection)<DD>
306	If the collection is nested (multi-dimensional), the top N nesting
307	levels of the structure are converted into a flat list.
308   <DT>flatten(Collection)<DD>
309	If the collection is nested (multi-dimensional), all nesting
310	structure is removed and a flat list is returned.  All subterms that
311	look like list or array will be interpreted as such (including []).
312</DL>
313"),
314    eg:"\
315   ?- collection_to_list([a,b,[c,d]], List).
316   List = [a, b, [c, d]]
317   Yes
318   ?- collection_to_list([](a,b,[c,d]), List).
319   List = [a, b, [c, d]]
320   Yes
321   ?- collection_to_list([]([](a,b),[](c,d)), List).
322   List = [[](a, b), [](c, d)]
323   Yes
324   ?- A = []([](a,b),[](c,d)),
325      collection_to_list(A[1..2,1], List).
326   List = [a, c]
327   Yes
328   ?- A = []([](a,b,c),[](d,e,f)),
329      collection_to_list(A[1..2,2..3], List).
330   List = [[](b, c), [](e, f)]
331   Yes
332   ?- collection_to_list(flatten([a,b,[c,d]]), List).
333   List = [a, b, c, d]
334   Yes
335   ?- collection_to_list(flatten([](a,b,[c,d])), List).
336   List = [a, b, c, d]
337   Yes
338   ?- A = []([](a,b,c),[](d,e,f)),
339      collection_to_list(flatten(A[1..2,2..3]), List).
340   List = [b, c, e, f]
341   Yes
342   ?- L = [[a,b],[[c,d],[e,f]],g],
343      collection_to_list(flatten(1, L), List).
344   List = [a, b, [c, d], [e, f], g]
345   Yes
346",
347    see_also:[collection_to_array/2, subscript/3, flatten/2, flatten/3]]).
348
349
350:- export collection_to_list/2.
351collection_to_list(flatten(Xs), Ys) ?- !,
352	collection_to_list0(Xs, Ys1, []),
353	flatten_list_elements(-1, Ys1, Ys, []).
354collection_to_list(flatten(D,Xs), Ys) ?- !,
355	collection_to_list0(Xs, Ys1, []),
356	( D>0 -> flatten_list_elements(D, Ys1, Ys, []) ; Ys=Ys1 ).
357collection_to_list(Xs, Ys) :-
358	collection_to_list0(Xs, Ys, []).
359
360    % Xs is a list, D>0 or D<0
361    flatten_list_elements(D, Xs, Ys, Ys0) :-
362	(
363	    foreach(X,Xs),
364	    fromto(Ys,Ys1,Ys2,Ys0),
365	    param(D)
366	do
367	    % X is either sub-collection or element
368	    ( collection_to_list0(X, Zs, Zs0) ->
369	        D1 is D-1,
370		( D1==0 ->
371		    Ys1 = Zs, Ys2 = Zs0
372		;
373		    Zs0 = [],
374		    flatten_list_elements(D1, Zs, Ys1, Ys2)
375		)
376	    ;
377		Ys1 = [X|Ys2]
378	    )
379	).
380
381    collection_to_list0(X, _Ys, _Ys0) :- var(X), !,
382	fail.		%throw(instantiation_error).
383    collection_to_list0([], Ys, Ys0) :- !,
384	Ys=Ys0.		% interpret as empty collection
385    collection_to_list0(Xs, Ys, Ys0) :- Xs = [_|_], !,
386	% assume proper list
387	( Ys0==[] -> Ys=Xs % avoid copying
388	; append(Xs, Ys0, Ys)
389	).
390    collection_to_list0(Xz, Ys, Ys0) :- is_array(Xz), !,
391	sepia_kernel:array_list(Xz, Ys, Ys0).
392    collection_to_list0(subscript(Array, Indices), Ys, Ys0) :- !,
393	( ( foreach(I,Indices) do integer(I) ) ->
394	    arg(Indices, Array, Element),
395	    Ys = [Element|Ys0]
396	;
397	    subscript(Array, Indices, SubArray),
398	    sepia_kernel:array_list(SubArray, Ys, Ys0)
399	).
400    collection_to_list0(_X, _Ys, _Ys0) :-
401	fail.		%throw(type_error).
402
403
404:- comment(collection_to_array/2, [
405    summary:"Convert a \"collection\" into a list",
406    amode:(collection_to_array(+,-) is semidet),
407    fail_if:"Collection is not a collection",
408    args:["Collection":"A term to be interpreted as a collection",
409    	"List":"Output array"],
410    desc:html("\
411   Converts various \"collection\" data structures into an array.  Fails if it
412   does not know how to do this.  The supported collection types are:
413<DL>
414   <DT>List<DD>
415	The list is converted into an array using array_list/2.
416   <DT>Array<DD>
417	The array is returned unchanged.
418   <DT>Subscript reference Array[...]<DD>
419	subscript/3 is called to evaluate the subscript reference.  If this
420	results in a single array element, a one-element array is returned.
421	If subscript/3 results in a sub-array, this is returned.
422   <DT>flatten(N, Collection)<DD>
423	If the collection is nested (multi-dimensional), the top N nesting
424	levels of the structure are converted into a flat array.
425   <DT>flatten(Collection)<DD>
426	If the collection is nested (multi-dimensional), all nesting
427	structure is removed and a flat array is returned.  All subterms that
428	look like list or array will be interpreted as such (including []).
429</DL>
430"),
431    eg:"\
432   ?- collection_to_array([a,b,[c,d]], Array).
433   Array = [](a, b, [c, d])
434   Yes
435   ?- collection_to_array(flatten([a,b,[c,d]]), Array).
436   Array = [](a, b, c, d)
437   Yes
438   ?- collection_to_array(flatten([](a,b,[c,d])), Array).
439   Array = [](a, b, c, d)
440   Yes
441   ?- A = []([](a,b,c),[](d,e,f)),
442      collection_to_array(flatten(A[1..2,2..3]), Array).
443   Array = [](b, c, e, f)
444   Yes
445   ?- L = [[a,b],[[c,d],[e,f]],g],
446      collection_to_array(flatten(1, L), Array).
447   Array = [](a, b, [c, d], [e, f], g)
448   Yes
449",
450    see_also:[collection_to_list/2, subscript/3, array_flat/3]]).
451
452
453:- export collection_to_array/2.
454collection_to_array(flatten(Xs), Yz) ?- !,
455	collection_to_array0(Xs, Yz1),
456	flatten_array_elements(-1, Yz1, Yz).
457collection_to_array(flatten(D,Xs), Yz) ?- !,
458	collection_to_array0(Xs, Yz1),
459	( D>0 -> flatten_array_elements(D, Yz1, Yz) ; Yz=Yz1 ).
460collection_to_array(Xs, Yz) :-
461	collection_to_array0(Xs, Yz).
462
463    % Xz is an array, D>0 or D<0
464    flatten_array_elements(D, Xz, Yz) :-
465	(
466	    foreacharg(X,Xz),
467	    fromto(Ys,Ys1,Ys2,[]),
468	    param(D)
469	do
470	    % X is either sub-collection or element
471	    ( collection_to_list0(X, Zs, Zs0) ->
472	        D1 is D-1,
473		( D1==0 ->
474		    Ys1 = Zs, Ys2 = Zs0
475		;
476		    Zs0 = [],
477		    flatten_list_elements(D1, Zs, Ys1, Ys2)
478		)
479	    ;
480		Ys1 = [X|Ys2]
481	    )
482	),
483	array_list(Yz, Ys).
484
485    collection_to_array0(X, _Yz) :- var(X), !,
486	fail.		%throw(instantiation_error).
487    collection_to_array0([], Yz) :- !,
488	Yz = [].	% interpret as empty collection
489    collection_to_array0(Xs, Yz) :- Xs = [_|_], !,
490	array_list(Yz, Xs).
491    collection_to_array0(Xz, Yz) :- is_array(Xz), !,
492    	Yz = Xz.
493    collection_to_array0(subscript(Array, Indices), Yz) :- !,
494	( ( foreach(I,Indices) do integer(I) ) ->
495	    arg(Indices, Array, Element),
496	    Yz = [](Element)
497	;
498	    subscript(Array, Indices, Yz)
499	).
500    collection_to_array0(_X, _Yz) :-
501	fail.		%throw(type_error).
502
503
504:- comment(halve/3, [
505    summary:"Split a list in the middle",
506    amode:(halve(+,-,-) is det),
507    template:"halve(+List, ?Front, ?Back)",
508    desc:html("Returns two lists (Front and Back) which can be concatenated to give
509	the original List. The length of the sub-lists is half the length of
510	the original. If the original length is odd, Front is one longer"),
511    eg:"\
512	halve([a,b,c,d,e,f], [a,b,c], [d,e,f])
513	halve([a,b,c,d,e,f,g], [a,b,c,d], [e,f,g])",
514    see_also:[append/3]]).
515
516halve(List, Front, Back) :-
517	halve(List, List, Front, Back).
518
519    halve([], Back0, Front, Back) :- !, Front=[], Back=Back0.
520%   halve([_], Back0, Front, Back) :- !, Front=[], Back=Back0.	% Front=<Back
521    halve([_], [X|Rs], Front, Back) :- !, Front=[X], Back=Rs.	% Front>=Back
522    halve([_,_|Es], [X|Rs], [X|Fs], Back) :-
523	halve(Es, Rs, Fs, Back).
524
525
526:- comment(splice/3, [
527    summary:"Merge two lists by interleaving the elements",
528    args:["Odds":"List or variable",
529    	"Evens":"List or variable",
530	"List":"Variable or list"],
531    amode:(splice(+,+,-) is det),
532    amode:(splice(-,-,+) is multi),
533    desc:html("Create a new list by alternating elements from two input lists,
534    	starting with the first. When one input list is longer, its extra
535	elements form the tail of the result list.
536	<P>
537	The reverse mode splice(-,-,+) is nondeterministic, and
538	the most balanced solution(s) will be found first."),
539    eg:"\
540?- splice([1,2,3], [a,b,c], X).
541X = [1, a, 2, b, 3, c]
542Yes (0.00s cpu)
543
544?- splice([1,2,3], [a,b,c,d,e], X).
545X = [1, a, 2, b, 3, c, d, e]
546Yes (0.00s cpu)
547
548?- splice(A, B, [1,a,2,b,3,c]).
549A = [1, 2, 3]
550B = [a, b, c]
551More (0.00s cpu) ? ;
552A = [1, 2, 3, c]
553B = [a, b]
554More (0.00s cpu) ? ;
555A = [1, 2]
556B = [a, b, 3, c]
557More (0.00s cpu) ? ;
558A = [1, 2, b, 3, c]
559B = [a]
560More (0.00s cpu) ? ;
561A = [1]
562B = [a, 2, b, 3, c]
563More (0.00s cpu) ? ;
564A = [1, a, 2, b, 3, c]
565B = []
566More (0.00s cpu) ? ;
567A = []
568B = [1, a, 2, b, 3, c]
569Yes (0.00s cpu)
570",
571    see_also:[merge/3]]).
572
573splice(Ls, Rs, LRs) :- Ls = [_|_],
574	splice1(Ls, Rs, LRs).
575splice([], Rs, Rs).
576
577    splice1([L|Ls], [R|Rs], [L,R|LRs]) :-
578	splice(Ls, Rs, LRs).
579    splice1(Ls, [], Ls).
580
581
582% Shuffle a list
583% This neat method seems to be from Lee Naish
584
585:- comment(shuffle/2, [
586	summary:"Shuffle a list, ie randomize the element order",
587	amode:(shuffle(+,-) is det),
588	template:"shuffle(+List, ?ShuffledList)",
589	see_also:[msort/2]]).
590
591shuffle(L, R) :-
592        add_random_keys(L, KL),
593        keysort(KL, KR),
594        rm_keys(KR, R).
595
596        % add random key to each list element
597add_random_keys([], []).
598add_random_keys([A|L], [K-A|KL]) :-
599        random(K),
600        add_random_keys(L, KL).
601
602        % remove keys from association list
603rm_keys([], []).
604rm_keys([_K-A|KL], [A|L]) :-
605        rm_keys(KL, L).
606
607
608:- comment(print_list / 1, [
609	summary:"Print the elements of a list, one per line",
610	amode:(print_list(+) is det),
611	template:"print_list(+List)"
612    ]).
613
614print_list_([], _).
615print_list_([H|T], M) :-
616	writeln(H)@M,
617	print_list_(T, M).
618
619
620:- comment(middle_out/2, [
621	summary:"Reorder a list such that the middle elements come first",
622	amode:(middle_out(+,-) is det),
623	args:["List":"A list", "Reordered":"A variable or list"],
624	eg:"
625?- middle_out([1,2,3,4,5], Zs).
626Zs = [3, 2, 4, 1, 5]
627Yes (0.00s cpu)
628
629?- middle_out([1,2,3,4,5,6], Zs).
630Zs = [3, 4, 2, 5, 1, 6]
631Yes (0.00s cpu)
632	",
633	see_also:[reverse/2]]).
634
635:- export middle_out/2.
636middle_out(XsYs, Zs) :-
637	middle_out(XsYs, XsYs, [], Zs0),
638	!, Zs=Zs0.
639
640    middle_out([], Ys, Zs, Zs) :- evens(Zs, Ys).
641    middle_out([_], [Y|Ys], Zs, [Y|Zs]) :- evens(Zs, Ys).
642    middle_out([_,_|XsYs], [X|Xs], XYs, Zs) :-
643	middle_out(XsYs, Xs, [X,_Y|XYs], Zs).
644
645    evens([], []).
646    evens([_,Y|XYs], [Y|Ys]) :- evens(XYs, Ys).
647
648
649
650%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
651
652:- comment(select / 3, [
653	summary:"Succeeds if List2 is List1 less an occurence of Element in List1.\n\n",
654	amode:(select(+,+,-) is nondet),	% redundant, but common
655	amode:(select(-,+,-) is nondet),	% redundant, but common
656	amode:(select(-,-,-) is multi),
657	template:"select(?Element, ?List1, ?List2)",
658	desc:html("\
659   Unifies the list List2 with the list List1 less an occurence of Element.
660   Any alternative solutions are provided on backtracking.
661<P>
662   This predicate can be used to select an element from a list, delete an
663   element or insert it.
664<P>
665   The definition of this Prolog library predicate is:
666<PRE>
667    select(A, [A|B], B).
668    select(A, [B, C|D], [B|E]) :-
669	    select(A, [C|D], E).
670</PRE>
671   This predicate does not perform any type testing functions.
672   "),
673	args:["?Element" : "Prolog term.", "?List1" : "List or variable.", "?List2" : "List or variable."],
674	resat:"   Yes.",
675	fail_if:"   Fails if List2 does not unify with List1 less an occurence of Element.\n\n",
676	eg:"
677Success:
678    [eclipse]: select(X,[1,M,X],L), writeln((M,X,L)), fail.
679    _g66 , 1 , [_g66, 1]
680    _g66 , _g66 , [1, _g66]
681    _g66 , _g72 , [1, _g66]
682    no (more) solution.
683
684    [eclipse]: select(3,[1,3,5,3],L).
685    L = [1, 5, 3]    More? (;)
686    L = [1, 3, 5]
687    yes.
688
689    [eclipse]: select(X,L,[a,b]), writeln((X,L)), fail.
690    _g66 , [_g66, a, b]
691    _g66 , [a, _g66, b]
692    _g66 , [a, b, _g66]
693    no (more) solution.
694
695    select(X,[1,2],L).   (gives X=1 L=[2]; X=2 L=[1]).
696
697Fail:
698    select(1,[1,2,1,3],[2,3]).
699	",
700	see_also:[subtract / 3, member / 2]]).
701
702select(A, [A|C], C).
703select(A, [B|C], [B|D]) :-
704	select(A, C, D).
705
706
707:- comment(delete / 3, [
708	summary:"Succeeds if List2 is List1 less an occurence of Element in List1.\n\n",
709	amode:(delete(+,+,-) is nondet),	% redundant, but common
710	amode:(delete(-,+,-) is nondet),	% redundant, but common
711	amode:(delete(-,-,-) is multi),
712	template:"delete(?Element, ?List1, ?List2)",
713	desc:html("\
714   Unifies the list List2 with the list List1 less an occurence of Element.
715   Any alternative solutions are provided on backtracking.
716<P>
717   This predicate can be used to select an element from a list, delete an
718   element or insert it.
719<P>
720   The definition of this Prolog library predicate is:
721<PRE>
722    delete(A, [A|B], B).
723    delete(A, [B, C|D], [B|E]) :-
724	    delete(A, [C|D], E).
725</PRE>
726   This predicate does not perform any type testing functions.
727   "),
728	args:["?Element" : "Prolog term.", "?List1" : "List or variable.", "?List2" : "List or variable."],
729	resat:"   Yes.",
730	fail_if:"   Fails if List2 does not unify with List1 less an occurence of Element.\n\n",
731	eg:"\nSuccess:\n   [eclipse]: delete(X,[1,M,X],L), writeln((M,X,L)), fail.\n   _g66 , 1 , [_g66, 1]\n   _g66 , _g66 , [1, _g66]\n   _g66 , _g72 , [1, _g66]\n   no (more) solution.\n\n   [eclipse]: delete(3,[1,3,5,3],L).\n   L = [1, 5, 3]    More? (;)\n   L = [1, 3, 5]\n   yes.\n\n   [eclipse]: delete(X,L,[a,b]), writeln((X,L)), fail.\n   _g66 , [_g66, a, b]\n   _g66 , [a, _g66, b]\n   _g66 , [a, b, _g66]\n   no (more) solution.\n\n   delete(X,[1,2],L).   (gives X=1 L=[2]; X=2 L=[1]).\nFail:\n   delete(1,[1,2,1,3],[2,3]).\n\n\n\n",
732	see_also:[subtract / 3, member / 2]]).
733
734:- comment(intersection / 3, [
735	summary:"Succeeds if Common unifies with the list which contains the common elements\nof List1 and List2.\n\n",
736	amode:(intersection(+,+,-) is det),
737	template:"intersection(+List1, +List2, ?Common)",
738	desc:html("\
739   Common is unified with a list which contains the common elements of
740   List1 and List2.
741<P>
742   The definition of this Prolog library predicate is:
743<PRE>
744intersection([], _, []).
745intersection([Head|L1tail], L2, L3) :-
746        memberchk(Head, L2),
747        !,
748        L3 = [Head|L3tail],
749        intersection(L1tail, L2, L3tail).
750intersection([_|L1tail], L2, L3) :-
751        intersection(L1tail, L2, L3).
752</PRE>
753   This predicate does not perform any type testing functions.
754<P>
755   This predicate works properly for set operations only, so repeated
756   elements and variable elements should not be used in the lists.
757	"),
758	args:["+List1" : "List.", "+List2" : "List.", "?Common" : "List or variable."],
759	resat:"   Yes.",
760	fail_if:"   Fails if Common does not unify with the list which contains the common\n   elements of List1 and List2.\n\n",
761	eg:"\nSuccess:\n   intersection([1,2],[2,3],L).     (gives L=[2]).\n   intersection([a,d],[a,b,c],[a]).\n\nFail:\n   intersection([a,b],[a,b],[b]).\n\n\n",
762	see_also:[subtract / 3, memberchk / 2, union / 3]]).
763
764:- comment(length / 2, [
765	summary:"Succeeds if the length of list List is N.\n\n",
766	amode:(length(+,+) is semidet),
767	amode:(length(+,-) is det),
768	amode:(length(-,+) is det),
769	amode:(length(-,-) is multi),
770	template:"length(?List, ?N)",
771	desc:html("\
772   Unifies N with the length of list List.  length/2 can be used to create
773   a list List of length N. The definition of this Prolog library predicate
774   is:
775<PRE>
776length(List, Length) :-
777        ( var(Length) ->
778          length(List, 0, Length)
779        ;
780          Length >= 0,
781          length1(List, Length) ).
782
783length([], Length, Length).
784length([_|L], N, Length) :-
785        N1 is N+1,
786        length(L, N1, Length).
787
788length1([], 0) :- !.
789length1([_|L], Length) :-
790        N1 is Length-1,
791        length1(L, N1).
792</PRE>
793   This predicate does not perform any type testing functions.
794	"),
795	args:["?List" : "List or variable.", "?N" : "Integer or variable."],
796	resat:"   Yes.",
797	fail_if:"   Fails if the length of list List does not unify with N.\n\n",
798	eg:"\nSuccess:\n  length([1,2,3],N).   (gives N=3).\n  length([1,2,1,X],N). (gives X=_g84; N=4).\n  length(L,2).         (gives L=[_g62,_g72]). % creates list\nFail:\n  length([1,2,3],2).\n\n\n",
799	see_also:[append / 3]]).
800
801:- comment(member / 2, [
802	summary:"Succeeds if Term unifies with a member of the list List.\n\n",
803	amode:(member(-,+) is nondet),
804	amode:(member(+,-) is nondet),
805	amode:(member(-,-) is multi),
806	template:"member(?Term, ?List)",
807	desc:html("\
808   Tries to unify Term with an element of the list List.
809<P>
810   If Term is a variable and List is a list, all the members of the list
811   List are found on backtracking.
812<P>
813   If List is not instantiated, member/2 binds List to a new partial list
814   containing the element Term.
815<P>
816   The definition of this Prolog library predicate is:
817<PRE>
818       member(X,[X|_]).
819       member(X,[Y|T]) :- member(X,T).
820</PRE>
821   This predicate does not perform any type testing functions.
822	"),
823	args:["?Term" : "Prolog term.", "?List" : "List or variable."],
824	resat:"   Yes.",
825	fail_if:"   Fails if Term does not unify with a member of the list List.\n\n",
826	eg:"\nSuccess:\n      member(q,[1,2,3,p,q,r]).\n      member(q,[1,2,F]).      (gives F=q).\n      member(X,[1,X]).        (gives X=1; X=_g118).\n      member(X,[2,I]).        (gives X=2 I=_g114; X=_g94 I=_g94).\n      member(1,L).            (gives L=[1|_g64];\n                                     L=[_g62,1|_g68] etc).\n\nFail:\n      member(4,[1,2,3]).\n\n\n\n",
827	see_also:[memberchk / 2]]).
828
829:- comment(memberchk / 2, [
830	summary:"Succeeds if Term is a member of the list List.\n\n",
831	amode:(memberchk(+,+) is semidet),
832	amode:(memberchk(+,-) is det),
833	template:"memberchk(+Term, ?List)",
834	desc:html("\
835   Unifies Term with the first matching element of the list List.
836<P>
837   If List is not instantiated, memberchk/2 binds List to a new partial
838   list containing an element Term.
839<P>
840   The definition of this Prolog library predicate is:
841<PRE>
842memberchk(X,[X|_]) :- !.
843memberchk(X,[_|T]):- memberchk(X,T).
844</PRE>
845   This predicate does not perform any type testing functions.
846	"),
847	args:["+Term" : "Prolog term.", "?List" : "List or a variable."],
848	resat:"   No.",
849	fail_if:"   Fails if Term is not a member of the list List.\n\n",
850	eg:"\nSuccess:\n      memberchk(0,[1,B,2]). (gives B=0).\n      memberchk(1,[1,X]).   (gives X=_g76).\n      memberchk(1,X), memberchk(2,X).\n                            (gives X=[1,2|_g98]).\n\nFail:\n      memberchk(0,[1,2,3,4]).\n\n\n\n",
851	see_also:[member / 2]]).
852
853:- comment(nonmember / 2, [
854	summary:"Succeeds if Element is not an element of the list List.\n\n",
855	amode:(nonmember(+,+) is semidet),
856	template:"nonmember(+Element, +List)",
857	desc:html("\
858   Used to check that Element is not a member of the list List.
859<P>
860   The definition of this Prolog library predicate is:
861<PRE>
862nonmember(Arg,[Arg|_]) :-
863        !,
864        fail.
865nonmember(Arg,[_|Tail]) :-
866        !,
867        nonmember(Arg,Tail).
868nonmember(_,[]).
869</PRE>
870   This predicate does not perform any type testing functions.
871	"),
872	args:["+Element" : "Prolog term.", "+List" : "List."],
873	resat:"   No.",
874	fail_if:"   Fails if Element is an element of the list List.\n\n",
875	eg:"\nSuccess:\n  nonmember(q,[1,2,3,4,5,6,7]).\n\nFail:\n  nonmember(1,[1,2,3]).\n  nonmember(q,[1,2,2,X]). % X and q are unifiable\n\n\n\n",
876	see_also:[member / 2, memberchk / 2]]).
877
878:- comment(subtract / 3, [
879	summary:"Succeeds if Remainder is the list which contains those elements of List1\nwhich are not in List2.\n\n",
880	amode:(subtract(+,+,-) is det),
881	template:"subtract(+List1, +List2, ?Remainder)",
882	desc:html("\
883   Unifies Remainder with a list containing those elements of List1 which
884   are not in List2.
885<P>
886   The definition of this Prolog library Predicate is:
887<PRE>
888subtract([], _, []).
889subtract([Head|Tail], L2, L3) :-
890        memberchk(Head, L2),
891        !,
892        subtract(Tail, L2, L3).
893subtract([Head|Tail1], L2, [Head|Tail3]) :-
894        subtract(Tail1, L2, Tail3).
895</PRE>
896   This predicate does not perform any type testing functions.
897<P>
898   This predicate works properly for set operations only, so repeated
899   elements and variable elements should not be used.
900	"),
901	args:["+List1" : "List.", "+List2" : "List.", "?Remainder" : "List or variable."],
902	resat:"   No.",
903	fail_if:"   Fails if if Remainder does not unify with the list which contains those\n   elements of List1 which are not in List2.\n\n",
904	eg:"\nSuccess:\n   subtract([1,2,3,4],[1],R).     (gives R=[2,3,4]).\n   subtract([1,2,3],[3,4],R).     (gives R=[1,2]).\n   subtract([1,1,2,3],[2],[1,1,3]).\nFail:\n   subtract([1,1,2,3],[1],[1,2,3]). % Fails - List2 and\n                                    % Remainder share elements\n\n\n\n",
905	see_also:[intersection / 3, union / 3]]).
906
907:- comment(union / 3, [
908	summary:"Succeeds if Union is the list which contains the union of elements in List1\nand those in List2.\n\n",
909	amode:(union(+,+,-) is det),
910	template:"union(+List1, +List2, ?Union)",
911	desc:html("\
912   Used to create the list of elements in List1 and not in List2, added to
913   those in List2.
914<P>
915   The definition of this Prolog library predicate is:
916<PRE>
917union([], L, L).
918union([Head|L1tail], L2, L3) :-
919        memberchk(Head, L2),
920        !,
921        union(L1tail, L2, L3).
922union([Head|L1tail], L2, [Head|L3tail]) :-
923        union(L1tail, L2, L3tail).
924</PRE>
925   This predicate does not perform any type testing functions.
926<P>
927   This predicate works properly for set operations only, so repeated
928   elements and variable elements should not be used.
929	"),
930	args:["+List1" : "List.", "+List2" : "List.", "?Union" : "List or variable."],
931	resat:"   No.",
932	fail_if:"   Fails if Union does not unify with the list which contains the union of\n   elements in List1 and those in List2.\n\n",
933	eg:"\nSuccess:\n      union([1,2,3],[1,3],L).     (gives L=[2,1,3]).\n\nFail:\n      union([1,2,3,2],[1,3],[1,2,3]).  % repeated elements\n\n\n\n",
934	see_also:[subtract / 3, intersection / 3]]).
935
936:- comment(reverse / 2, [
937	summary:"Succeeds if Reversed is the reversed list List.\n\n",
938	amode:(reverse(+,-) is det),
939	template:"reverse(+List, ?Reversed)",
940	desc:html("\
941   The List is reversed and the resulting list is unified with Reverse.
942<P>
943   The definition of this Prolog library predicate is:
944<PRE>
945reverse(List, Rev) :-
946        reverse(List, Rev, []).
947
948reverse([], L, L).
949reverse([H|T], L, SoFar) :-
950        reverse(T, L, [H|SoFar]).
951</PRE>
952   This predicate does not perform any type testing functions.
953	"),
954	args:["+List" : "A List.", "?Reversed" : "List or variable."],
955	resat:"   No.",
956	fail_if:"   Fails if Reverse does not unify with the reversed version of List.\n\n",
957	eg:"\nSuccess:\n    [eclipse]: reverse([1,2,3,4,5], X).\n    X = [5, 4, 3, 2, 1]\n    yes.\n\n\n\n\n",
958	see_also:[append / 3, member / 2]]).
959
960:- comment(append / 3, [
961	summary:"Succeeds if List3 is the result of appending List2 to List1.\n\n",
962	amode:(append(+,+,-) is det),
963	amode:(append(-,-,+) is multi),
964	template:"append(?List1, ?List2, ?List3)",
965	desc:html("\
966   Unifies List3 to the result of appending List2 to List1.  On
967   backtracking append/3 gives all possible solutions for List1 and List2,
968   if both are uninstantiated.
969<P>
970   The definition of this Prolog library predicate is:
971<PRE>
972append([],X,X).
973append([X|L1],L2,[X|L3]):-
974        append(L1,L2,L3).
975</PRE>
976   This predicate does not perform any type testing functions.
977	"),
978	args:["?List1" : "List or variable.", "?List2" : "List or variable.", "?List3" : "List or variable."],
979	resat:"   Yes.",
980	fail_if:"   Fails if List3 does not unify with the result of appending List2 to\n   List1.\n\n",
981	eg:"\nSuccess:\n  append([1,2],L2,[1,2,3,4]). (gives L2=[3,4]).\n  append([1,B],L2,[A,2,3,4]). (gives B=2 L2=[3,4] A=1).\n  append([1,2],L2,L3).        (gives L2=L2 L3=[1,2|L2]).\n  append([1],[2,3],L3).     (gives L3=[1,2,3]).\n\n  [eclipse]: append(L1,L2,[1,2]), writeln((L1,L2)), fail.\n  [] , [1, 2]\n  [1] , [2]\n  [1, 2] , []\n  no (more) solution.\nFail:\n  append(L1,[3],[1,2,3,4]).\n  append(1,L2,[1,2]).\n\n\n",
982	see_also:[union / 3]]).
983
984:- comment(checklist / 2, [
985	summary:"Succeeds if Pred(Elem) succeeds for every element of List.\n\n",
986	amode:(checklist(+,+)),
987	template:"checklist(+Pred, +List)",
988	desc:html("\
989   checklist/3 succeeds if for every element of List, the invocation of
990   Pred with one aditional argument which is this element succeeds.
991<P>
992   The definition of this Prolog library predicate is:
993<PRE>
994:- tool(checklist/3, checklist_body/4).
995
996checklist_body(_, [], _).
997checklist_body(Pred, [Head|Tail], M) :-
998    Pred =.. PL,
999    append(PL, [Head], NewPred),
1000    Call =.. NewPred,
1001    call(Call)@M,
1002    checklist_body(Pred, Tail, M).
1003</PRE>
1004   This predicate does not perform any type testing functions.
1005	"),
1006	args:["+Pred" : "Atom or compound term.", "+List" : "List."],
1007	resat:"Resatisfiable if at least for one element of List the invocation of Pred with this additional argument is resatisfiable.",
1008	fail_if:"Fails if at least for one element of List the invocation of Pred with this additional argument fails.",
1009	eg:"\nSuccess:\n  checklist(integer, [1, 3, 5]).\n  checklist(spy, [var/1, functor/3]).\n\nFail:\n  checklist(current_op(_, _), [+, -, =]).\n  (fails because the precedence of = does not match that of +)\n\n\n\n",
1010	see_also:[maplist / 3]]).
1011
1012:- comment(flatten / 2, [
1013	summary:"Succeeds if FlatList is the list of all elements in NestedList, as found in\na left-to-right, depth-first traversal of NestedList.\n\n",
1014	amode:(flatten(+,-) is det),
1015	template:"flatten(+NestedList, ?FlatList)",
1016	desc:html("\
1017   FlatList is the list built from all the non-list elements of NestedList
1018   and the flattened sublists.  The sequence of elements in FlatList is
1019   determined by a left-to-right, depth-first traversal of NestedList.
1020<P>
1021   The definition of this Prolog library predicate is:
1022<PRE>
1023flatten(List, Flat) :-
1024	flatten_aux(List, Flat, []).
1025
1026flatten_aux([], Res, Cont) :- -?-> !, Res = Cont.
1027flatten_aux([Head|Tail], Res, Cont) :-
1028	-?->
1029	!,
1030	flatten_aux(Head, Res, Cont1),
1031	flatten_aux(Tail, Cont1, Cont).
1032flatten_aux(Term, [Term|Cont], Cont).
1033</PRE>
1034   This predicate does not perform any type testing functions.
1035	"),
1036	args:["+NestedList" : "A List.", "?FlatList" : "List or variable."],
1037	resat:"   No.",
1038	fail_if:"   Fails if FlatList does not unify with the flattened version of\n   NestedList.\n\n",
1039	eg:"\nSuccess:\n    [eclipse]: flatten([[1,2,[3,4],5],6,[7]], L).\n    L = [1, 2, 3, 4, 5, 6, 7]\n    yes.\n\nFail:\n    [eclipse]: flatten([1,[3],2], [1,2,3]).\n    no.\n\n\n\n",
1040	see_also:[flatten / 3, sort / 2, sort / 4, length / 2, member / 2]]).
1041
1042:- comment(flatten / 3, [
1043	summary:"Depth-limited list flattening",
1044	amode:(flatten(++,+,-) is det),
1045	template:"flatten(++MaxDepth, +NestedList, ?FlatList)",
1046	args:[
1047	    "++MaxDepth" : "Maximum depth to flatten.",
1048	    "+NestedList" : "List.",
1049	    "?FlatList" : "List or variable."
1050	],
1051	desc:html("\
1052   Like flatten/2, but does not flatten beyond the specified depth MaxDepth.
1053   So flatten(0, List, Flat) just unifies Flat and List (no flattening),
1054   flatten(1, List, Flat) just flattens the top-level list of List, etc.
1055<P>
1056   This predicate does not perform any type testing functions.
1057	"),
1058	resat:"   No.",
1059	fail_if:"   Fails if FlatList does not unify with the flattened version of\n   NestedList.\n\n",
1060	eg:"
1061   Success:
1062      [eclipse]: flatten(0, [[1,2,[3,4],5],6,[7]], L).
1063      L = [[1, 2, [3, 4], 5], 6, [7]]
1064      yes.
1065      [eclipse]: flatten(1, [[1,2,[3,4],5],6,[7]], L).
1066      L = [1, 2, [3, 4], 5, 6, 7]
1067      yes.
1068      [eclipse]: flatten(2, [[1,2,[3,4],5],6,[7]], L).
1069      L = [1, 2, 3, 4, 5, 6, 7]
1070      yes.
1071      [eclipse]: flatten(3, [[1,2,[3,4],5],6,[7]], L).
1072      L = [1, 2, 3, 4, 5, 6, 7]
1073      yes.
1074
1075   Fail:
1076      [eclipse]: flatten(2, [1,[3],2], [1,2,3]).
1077      no.
1078",
1079	see_also:[flatten / 2, sort / 2, sort / 4, length / 2, member / 2]]).
1080
1081:- comment(maplist / 3, [
1082	summary:"Succeeds if Pred(Old, New) succeeds for corresponding pairs of elements\nfrom OldList and NewList.\n\n",
1083	amode:(maplist(+,+,-)),
1084	amode:(maplist(+,-,+)),
1085	template:"maplist(+Pred, ?OldList, ?NewList)",
1086	desc:html("\
1087   Either OldList or NewList should be a proper list.  maplist/3 succeeds
1088   if for every corresponding pair of elements Old, New of the two lists
1089   OldList and NewList the invocation of Pred with two aditional arguments
1090   Old and New succeeds.
1091<P>
1092   The definition of this Prolog library predicate is:
1093<PRE>
1094:- tool(maplist/3, maplist_body/4).
1095
1096maplist_body(_, [], [], _).
1097maplist_body(Pred, [H1|T1], [H2|T2], M) :-
1098    Pred =.. PL,
1099    append(PL, [H1, H2], NewPred),
1100    Call =.. NewPred,
1101    call(Call)@M,
1102    maplist_body(Pred, T1, T2, M).
1103</PRE>
1104   This predicate does not perform any type testing functions.
1105	"),
1106	args:["+Pred" : "Atom or compound term.", "?OldList" : "List or variable.", "?NewList" : "List or variable."],
1107	resat:"Resatisfiable if at least for one pair of corresponding elements of OldList and NewList the invocation of Pred with these two additional arguments is resatisfiable",
1108	fail_if:"Fails if at least for one pair of corresponding elements of OldList and NewList the invocation of Pred with these two additional arguments fails",
1109	eg:"\nSuccess:\n  maplist(integer_atom, [1, 2, 3], ['1', '2', '3']).\n  maplist(sin, [0, 1, 2], X).\n      (gives X = [0.0, 0.841471, 0.909297])\n  maplist(get_flag(var/1), [skip, type, spy], [off, built_in, off]).\nFail:\n  maplist(type_of, [1, a, \"a\"], [integer, atom, atom]).\n\n\n\n",
1110	see_also:[checklist / 2]]).
1111
1112:- comment(subset / 2, [
1113	summary:"Succeeds if List is the list which contains all elements from SubList in\nthe same order as in SubList.\n\n",
1114	amode:(subset(-,+) is multi),
1115	template:"subset(?SubList, +List)",
1116	desc:html("\
1117   Used to test if a specified list contains all elements of another list,
1118   or to generate all sublists of a given list.
1119<P>
1120   The definition of this Prolog library predicate is:
1121<PRE>
1122        subset([],[]).
1123        subset([X|L],[X|S]) :-
1124            subset(L,S).
1125        subset(L, [_|S]) :-
1126            subset(L,S).
1127</PRE>
1128   This predicate does not perform any type testing functions.
1129<P>
1130   This predicate works properly for set operations only, so repeated
1131   elements, variable elements and unsorted lists should not be used.
1132	"),
1133	args:["?SubList" : "A term which unifies with a list.", "+List" : "A term which unifies with a list."],
1134	resat:"   Yes.",
1135	fail_if:"   Fails if SubList does not unify with a list whose elements are all\n   contained in List in the same order as in SubList.\n\n",
1136	eg:"\nSuccess:\n      subset([1,3], [1,2,3]).\n      subset(X, [1,3,4]).        % backtracks over all subsets\n\nFail:\n      subset([2,1], [1,2,3]).   % different order\n\n\n\n",
1137	see_also:[union / 3, subtract / 3, intersection / 3]]).
1138