| Did you know ... | Search Documentation: |
| lists.pl -- SICStus 4-compatible library(lists). |
rev(+List, ?Reversed) is semidet
shorter_list(?Short, ?Long) is nondet
prefix(?List, ?Prefix) is nondet
proper_prefix(?List, ?Prefix) is nondet
suffix(?List, ?Prefix) is nondet
proper_suffix(?List, ?Prefix) is nondet
scanlist(:Pred, ?Xs, ?V1, ?V) is nondet
scanlist(:Pred, ?Xs, ?Ys, ?V1, ?V) is nondet
scanlist(:Pred, ?Xs, ?Ys, ?Zs, ?V1, ?V) is nondetThe following predicates are exported from this file while their implementation is defined in imported modules or non-module files loaded by this module.
include(:Goal, +List1, ?List2) is detcall(Goal, Xi) succeeds.
exclude(:Goal, +List1, ?List2) is detcall(Goal, Xi) fails.
partition(:Pred, +List, ?Less, ?Equal, ?Greater) is semidetcall(Pred, Xi, Place),
where Place must be unified to one of <, = or >.
Pred must be deterministic.
maplist(:Goal, ?List1)
maplist(:Goal, ?List1, ?List2)
maplist(:Goal, ?List1, ?List2, ?List3)
maplist(:Goal, ?List1, ?List2, ?List3, ?List4)
maplist(G, [X_11, ..., X_1n],
[X_21, ..., X_2n],
...,
[X_m1, ..., X_mn]) :-
call(G, X_11, ..., X_m1),
call(G, X_12, ..., X_m2),
...
call(G, X_1n, ..., X_mn).
This family of predicates is deterministic iff Goal is deterministic
and List1 is a proper list, i.e., a list that ends in [].
maplist(:Goal, ?List1)
maplist(:Goal, ?List1, ?List2)
maplist(:Goal, ?List1, ?List2, ?List3)
maplist(:Goal, ?List1, ?List2, ?List3, ?List4)
maplist(G, [X_11, ..., X_1n],
[X_21, ..., X_2n],
...,
[X_m1, ..., X_mn]) :-
call(G, X_11, ..., X_m1),
call(G, X_12, ..., X_m2),
...
call(G, X_1n, ..., X_mn).
This family of predicates is deterministic iff Goal is deterministic
and List1 is a proper list, i.e., a list that ends in [].
maplist(:Goal, ?List1)
maplist(:Goal, ?List1, ?List2)
maplist(:Goal, ?List1, ?List2, ?List3)
maplist(:Goal, ?List1, ?List2, ?List3, ?List4)
maplist(G, [X_11, ..., X_1n],
[X_21, ..., X_2n],
...,
[X_m1, ..., X_mn]) :-
call(G, X_11, ..., X_m1),
call(G, X_12, ..., X_m2),
...
call(G, X_1n, ..., X_mn).
This family of predicates is deterministic iff Goal is deterministic
and List1 is a proper list, i.e., a list that ends in [].
convlist(:Goal, +ListIn, -ListOut) is detcall(Goal, ElemIn, _)
fails are omitted from ListOut. For example (using library(yall)):
?- convlist([X,Y]>>(integer(X), Y is X^2),
[3, 5, foo, 2], L).
L = [9, 25, 4].
transpose(+Matrix, ?Transpose)?- transpose([[1,2,3],[4,5,6],[7,8,9]], Ts). Ts = [[1, 4, 7], [2, 5, 8], [3, 6, 9]].
This predicate is useful in many constraint programs. Consider for instance Sudoku:
sudoku(Rows) :-
length(Rows, 9), maplist(same_length(Rows), Rows),
append(Rows, Vs), Vs ins 1..9,
maplist(all_distinct, Rows),
transpose(Rows, Columns),
maplist(all_distinct, Columns),
Rows = [As,Bs,Cs,Ds,Es,Fs,Gs,Hs,Is],
blocks(As, Bs, Cs), blocks(Ds, Es, Fs), blocks(Gs, Hs, Is).
blocks([], [], []).
blocks([N1,N2,N3|Ns1], [N4,N5,N6|Ns2], [N7,N8,N9|Ns3]) :-
all_distinct([N1,N2,N3,N4,N5,N6,N7,N8,N9]),
blocks(Ns1, Ns2, Ns3).
problem(1, [[_,_,_,_,_,_,_,_,_],
[_,_,_,_,_,3,_,8,5],
[_,_,1,_,2,_,_,_,_],
[_,_,_,5,_,7,_,_,_],
[_,_,4,_,_,_,1,_,_],
[_,9,_,_,_,_,_,_,_],
[5,_,_,_,_,_,_,7,3],
[_,_,2,_,1,_,_,_,_],
[_,_,_,_,4,_,_,_,9]]).
Sample query:
?- problem(1, Rows), sudoku(Rows), maplist(portray_clause, Rows). [9, 8, 7, 6, 5, 4, 3, 2, 1]. [2, 4, 6, 1, 7, 3, 9, 8, 5]. [3, 5, 1, 9, 2, 8, 7, 4, 6]. [1, 2, 8, 5, 3, 7, 6, 9, 4]. [6, 3, 4, 8, 9, 2, 1, 5, 7]. [7, 9, 5, 4, 6, 1, 8, 3, 2]. [5, 1, 9, 2, 8, 6, 4, 7, 3]. [4, 7, 2, 3, 1, 9, 5, 6, 8]. [8, 6, 3, 7, 4, 5, 2, 1, 9]. Rows = [[9, 8, 7, 6, 5, 4, 3, 2|...], ... , [...|...]].
same_length(?List1, ?List2, ?Length) is nondet
scanlist(:Pred, ?Xs, ?V1, ?V) is nondet
scanlist(:Pred, ?Xs, ?Ys, ?V1, ?V) is nondet
scanlist(:Pred, ?Xs, ?Ys, ?Zs, ?V1, ?V) is nondet
scanlist(:Pred, ?Xs, ?V1, ?V) is nondet
scanlist(:Pred, ?Xs, ?Ys, ?V1, ?V) is nondet
scanlist(:Pred, ?Xs, ?Ys, ?Zs, ?V1, ?V) is nondet
append(+ListOfLists, ?List)
select(?Elem, ?List1, ?List2)
selectchk(+Elem, +List, -Rest) is semidet
select(?X, ?XList, ?Y, ?YList) is nondet?- select(b, [a,b,c,b], 2, X). X = [a, 2, c, b] ; X = [a, b, c, 2] ; false.
selectchk(?X, ?XList, ?Y, ?YList) is semidet
nextto(?X, ?Y, ?List)
delete(+List1, @Elem, -List2) is det\+ Elem \=
H, which implies that Elem is not changed.
nth0(?Index, ?List, ?Elem)
nth1(?Index, ?List, ?Elem)
nth0(?N, ?List, ?Elem, ?Rest) is det?- nth0(I, [a,b,c], E, R). I = 0, E = a, R = [b, c] ; I = 1, E = b, R = [a, c] ; I = 2, E = c, R = [a, b] ; false.
?- nth0(1, L, a1, [a,b]). L = [a, a1, b].
nth1(?N, ?List, ?Elem, ?Rest) is det
last(?List, ?Last)semidet if List is a list and multi if List is
a partial list.
proper_length(@List, -Length) is semidet
proper_length(List, Length) :-
is_list(List),
length(List, Length).
same_length(?List1, ?List2)
reverse(?List1, ?List2)
permutation(?Xs, ?Ys) is nondet
If both Xs and Ys are provided and both lists have equal length
the order is |Xs|^2. Simply testing whether Xs is a permutation
of Ys can be achieved in order log(|Xs|) using msort/2 as
illustrated below with the semidet predicate is_permutation/2:
is_permutation(Xs, Ys) :- msort(Xs, Sorted), msort(Ys, Sorted).
The example below illustrates that Xs and Ys being proper lists is not a sufficient condition to use the above replacement.
?- permutation([1,2], [X,Y]). X = 1, Y = 2 ; X = 2, Y = 1 ; false.
clumped(+Items, -Pairs)Item-Count pairs that represents the run
length encoding of Items. For example:
?- clumped([a,a,b,a,a,a,a,c,c,c], R). R = [a-2, b-1, a-4, c-3].
max_member(-Max, +List) is semidet
min_member(-Min, +List) is semidet
max_member(:Pred, -Max, +List) is semidet?- max_member(@=<, X, [6,1,8,4]). X = 8.
min_member(:Pred, -Min, +List) is semidet?- min_member(@=<, X, [6,1,8,4]). X = 1.
The following predicates are exported, but not or incorrectly documented.
proper_suffix_length(Arg1, Arg2, Arg3)
append_length(Arg1, Arg2, Arg3)
keys_and_values(Arg1, Arg2, Arg3)
head(Arg1, Arg2)
subseq0(Arg1, Arg2)
tail(Arg1, Arg2)
suffix_length(Arg1, Arg2, Arg3)
append_length(Arg1, Arg2, Arg3, Arg4)
remove_dups(Arg1, Arg2)
subseq1(Arg1, Arg2)
sublist(Arg1, Arg2, Arg3, Arg4)
sumlist(Arg1, Arg2)
proper_prefix_length(Arg1, Arg2, Arg3)
cons(Arg1, Arg2, Arg3)
subseq(Arg1, Arg2, Arg3)
sublist(Arg1, Arg2, Arg3, Arg4, Arg5)
sublist(Arg1, Arg2, Arg3)
prefix_length(Arg1, Arg2, Arg3)
last(Arg1, Arg2, Arg3)