Did you know ... Search Documentation:
lists.pl -- SICStus 4-compatible library(lists).
PublicShow source
See also
- https://sicstus.sics.se/sicstus/docs/4.6.0/html/sicstus.html/lib_002dlists.html
To be done
- This library is incomplete. As of SICStus 4.6.0, the following predicates are missing:
Source rev(+List, ?Reversed) is semidet
Same as reverse/2, but List must be a proper list.
Source shorter_list(?Short, ?Long) is nondet
True if Short is a shorter list than Long. The lists' contents are insignificant, only the lengths matter. Mode -Short, +Long can be used to enumerate list skeletons shorter than Long.
Source prefix(?List, ?Prefix) is nondet
True if Prefix is a prefix of List. Not the same as prefix/2 in SICStus 3 or SWI - the arguments are reversed!
Source proper_prefix(?List, ?Prefix) is nondet
True if Prefix is a prefix of List, but is not List itself.
Source suffix(?List, ?Prefix) is nondet
True if Suffix is a suffix of List. Not the same as suffix/2 in SICStus 3 - the arguments are reversed!
Source proper_suffix(?List, ?Prefix) is nondet
True if Suffix is a suffix of List, but is not List itself.
Source scanlist(:Pred, ?Xs, ?V1, ?V) is nondet
Source scanlist(:Pred, ?Xs, ?Ys, ?V1, ?V) is nondet
Source scanlist(:Pred, ?Xs, ?Ys, ?Zs, ?V1, ?V) is nondet
Same as foldl/[4,5,6].
Compatibility
- SICStus 4

Re-exported predicates

The following predicates are exported from this file while their implementation is defined in imported modules or non-module files loaded by this module.

Source include(:Goal, +List1, ?List2) is det
Filter elements for which Goal succeeds. True if List2 contains those elements Xi of List1 for which call(Goal, Xi) succeeds.
See also
- exclude/3, partition/4, convlist/3.
Compatibility
- Older versions of SWI-Prolog had sublist/3 with the same arguments and semantics.
Source exclude(:Goal, +List1, ?List2) is det
Filter elements for which Goal fails. True if List2 contains those elements Xi of List1 for which call(Goal, Xi) fails.
See also
- include/3, partition/4
Source partition(:Pred, +List, ?Less, ?Equal, ?Greater) is semidet
Filter List according to Pred in three sets. For each element Xi of List, its destination is determined by call(Pred, Xi, Place), where Place must be unified to one of <, = or >. Pred must be deterministic.
See also
- partition/4
Source maplist(:Goal, ?List1)
Source maplist(:Goal, ?List1, ?List2)
Source maplist(:Goal, ?List1, ?List2, ?List3)
Source maplist(:Goal, ?List1, ?List2, ?List3, ?List4)
True if Goal is successfully applied on all matching elements of the list. The maplist family of predicates is defined as:
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 [].

Source maplist(:Goal, ?List1)
Source maplist(:Goal, ?List1, ?List2)
Source maplist(:Goal, ?List1, ?List2, ?List3)
Source maplist(:Goal, ?List1, ?List2, ?List3, ?List4)
True if Goal is successfully applied on all matching elements of the list. The maplist family of predicates is defined as:
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 [].

Source maplist(:Goal, ?List1)
Source maplist(:Goal, ?List1, ?List2)
Source maplist(:Goal, ?List1, ?List2, ?List3)
Source maplist(:Goal, ?List1, ?List2, ?List3, ?List4)
True if Goal is successfully applied on all matching elements of the list. The maplist family of predicates is defined as:
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 [].

Source convlist(:Goal, +ListIn, -ListOut) is det
Similar to maplist/3, but elements for which call(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].
Compatibility
- Also appears in YAP library(maplist) and SICStus library(lists).
Source transpose(+Matrix, ?Transpose)
Transpose a list of lists of the same length. Example:
?- 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|...], ... , [...|...]].
Source same_length(?List1, ?List2, ?Length) is nondet
True if List1 and List2 both have length Length.
Source scanlist(:Pred, ?Xs, ?V1, ?V) is nondet
Source scanlist(:Pred, ?Xs, ?Ys, ?V1, ?V) is nondet
Source scanlist(:Pred, ?Xs, ?Ys, ?Zs, ?V1, ?V) is nondet
Same as foldl/[4,5,6].
Compatibility
- SICStus 4
Source scanlist(:Pred, ?Xs, ?V1, ?V) is nondet
Source scanlist(:Pred, ?Xs, ?Ys, ?V1, ?V) is nondet
Source scanlist(:Pred, ?Xs, ?Ys, ?Zs, ?V1, ?V) is nondet
Same as foldl/[4,5,6].
Compatibility
- SICStus 4
Source append(+ListOfLists, ?List)
Concatenate a list of lists. Is true if ListOfLists is a list of lists, and List is the concatenation of these lists.
Arguments:
ListOfLists- must be a list of possibly partial lists
Source select(?Elem, ?List1, ?List2)
Is true when List1, with Elem removed, results in List2. This implementation is determinsitic if the last element of List1 has been selected.
Source selectchk(+Elem, +List, -Rest) is semidet
Semi-deterministic removal of first element in List that unifies with Elem.
Source select(?X, ?XList, ?Y, ?YList) is nondet
Select from two lists at the same position. True if XList is unifiable with YList apart a single element at the same position that is unified with X in XList and with Y in YList. A typical use for this predicate is to replace an element, as shown in the example below. All possible substitutions are performed on backtracking.
?- select(b, [a,b,c,b], 2, X).
X = [a, 2, c, b] ;
X = [a, b, c, 2] ;
false.
See also
- selectchk/4 provides a semidet version.
Source selectchk(?X, ?XList, ?Y, ?YList) is semidet
Semi-deterministic version of select/4.
Source nextto(?X, ?Y, ?List)
True if Y directly follows X in List.
Source delete(+List1, @Elem, -List2) is det
Delete matching elements from a list. True when List2 is a list with all elements from List1 except for those that unify with Elem. Matching Elem with elements of List1 is uses \+ Elem \= H, which implies that Elem is not changed.
See also
- select/3, subtract/3.
deprecated
- There are too many ways in which one might want to delete elements from a list to justify the name. Think of matching (= vs. ==), delete first/all, be deterministic or not.
Source nth0(?Index, ?List, ?Elem)
True when Elem is the Index'th element of List. Counting starts at 0.
Errors
- type_error(integer, Index) if Index is not an integer or unbound.
See also
- nth1/3.
Source nth1(?Index, ?List, ?Elem)
Is true when Elem is the Index'th element of List. Counting starts at 1.
See also
- nth0/3.
Source nth0(?N, ?List, ?Elem, ?Rest) is det
Select/insert element at index. True when Elem is the N'th (0-based) element of List and Rest is the remainder (as in by select/3) of List. For example:
?- 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].
Source nth1(?N, ?List, ?Elem, ?Rest) is det
As nth0/4, but counting starts at 1.
Source last(?List, ?Last)
Succeeds when Last is the last element of List. This predicate is semidet if List is a list and multi if List is a partial list.
Compatibility
- There is no de-facto standard for the argument order of last/2. Be careful when porting code or use append(_, [Last], List) as a portable alternative.
Source proper_length(@List, -Length) is semidet
True when Length is the number of elements in the proper list List. This is equivalent to
proper_length(List, Length) :-
      is_list(List),
      length(List, Length).
Source same_length(?List1, ?List2)
Is true when List1 and List2 are lists with the same number of elements. The predicate is deterministic if at least one of the arguments is a proper list. It is non-deterministic if both arguments are partial lists.
See also
- length/2
Source reverse(?List1, ?List2)
Is true when the elements of List2 are in reverse order compared to List1. This predicate is deterministic if either list is a proper list. If both lists are partial lists backtracking generates increasingly long lists.
Source permutation(?Xs, ?Ys) is nondet
True when Xs is a permutation of Ys. This can solve for Ys given Xs or Xs given Ys, or even enumerate Xs and Ys together. The predicate permutation/2 is primarily intended to generate permutations. Note that a list of length N has N! permutations, and unbounded permutation generation becomes prohibitively expensive, even for rather short lists (10! = 3,628,800).

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.
Errors
- type_error(list, Arg) if either argument is not a proper or partial list.
Source clumped(+Items, -Pairs)
Pairs is a list of 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].
Compatibility
- SICStus
Source max_member(-Max, +List) is semidet
True when Max is the largest member in the standard order of terms. Fails if List is empty.
See also
- compare/3
- max_list/2 for the maximum of a list of numbers.
Source min_member(-Min, +List) is semidet
True when Min is the smallest member in the standard order of terms. Fails if List is empty.
See also
- compare/3
- min_list/2 for the minimum of a list of numbers.
Source max_member(:Pred, -Max, +List) is semidet
True when Max is the largest member according to Pred, which must be a 2-argument callable that behaves like (@=<)/2. Fails if List is empty. The following call is equivalent to max_member/2:
?- max_member(@=<, X, [6,1,8,4]).
X = 8.
See also
- max_list/2 for the maximum of a list of numbers.
Source min_member(:Pred, -Min, +List) is semidet
True when Min is the smallest member according to Pred, which must be a 2-argument callable that behaves like (@=<)/2. Fails if List is empty. The following call is equivalent to max_member/2:
?- min_member(@=<, X, [6,1,8,4]).
X = 1.
See also
- min_list/2 for the minimum of a list of numbers.

Undocumented predicates

The following predicates are exported, but not or incorrectly documented.

Source proper_suffix_length(Arg1, Arg2, Arg3)
Source append_length(Arg1, Arg2, Arg3)
Source keys_and_values(Arg1, Arg2, Arg3)
Source sublist(Arg1, Arg2, Arg3)
Source append_length(Arg1, Arg2, Arg3, Arg4)
Source suffix_length(Arg1, Arg2, Arg3)
Source last(Arg1, Arg2, Arg3)
Source sumlist(Arg1, Arg2)
Source remove_dups(Arg1, Arg2)
Source cons(Arg1, Arg2, Arg3)
Source subseq1(Arg1, Arg2)
Source tail(Arg1, Arg2)
Source proper_prefix_length(Arg1, Arg2, Arg3)
Source sublist(Arg1, Arg2, Arg3, Arg4)
Source head(Arg1, Arg2)
 is_list(Arg1)
Source subseq0(Arg1, Arg2)
Source subseq(Arg1, Arg2, Arg3)
Source prefix_length(Arg1, Arg2, Arg3)
Source sublist(Arg1, Arg2, Arg3, Arg4, Arg5)