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

Undocumented predicates

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

 is_list(Arg1)
Source subseq(Arg1, Arg2, Arg3)
Source reverse(Arg1, Arg2)
Source nth1(Arg1, Arg2, Arg3, Arg4)
Source delete(Arg1, Arg2, Arg3)
Source select(Arg1, Arg2, Arg3)
Source proper_suffix_length(Arg1, Arg2, Arg3)
Source append_length(Arg1, Arg2, Arg3)
Source head(Arg1, Arg2)
Source keys_and_values(Arg1, Arg2, Arg3)
Source min_member(Arg1, Arg2, Arg3)
Source clumped(Arg1, Arg2)
Source same_length(Arg1, Arg2)
Source sumlist(Arg1, Arg2)
Source nth0(Arg1, Arg2, Arg3, Arg4)
Source nextto(Arg1, Arg2, Arg3)
Source sublist(Arg1, Arg2, Arg3, Arg4, Arg5)
Source selectchk(Arg1, Arg2, Arg3)
Source append(Arg1, Arg2)
Source prefix_length(Arg1, Arg2, Arg3)
Source max_member(Arg1, Arg2, Arg3)
Source min_member(Arg1, Arg2)
Source proper_length(Arg1, Arg2)
Source sublist(Arg1, Arg2, Arg3)
Source remove_dups(Arg1, Arg2)
Source nth1(Arg1, Arg2, Arg3)
Source subseq1(Arg1, Arg2)
Source last(Arg1, Arg2, Arg3)
Source sublist(Arg1, Arg2, Arg3, Arg4)
Source proper_prefix_length(Arg1, Arg2, Arg3)
Source select(Arg1, Arg2, Arg3, Arg4)
Source max_member(Arg1, Arg2)
Source permutation(Arg1, Arg2)
Source last(Arg1, Arg2)
Source nth0(Arg1, Arg2, Arg3)
Source subseq0(Arg1, Arg2)
Source tail(Arg1, Arg2)
Source selectchk(Arg1, Arg2, Arg3, Arg4)
Source suffix_length(Arg1, Arg2, Arg3)
Source cons(Arg1, Arg2, Arg3)
Source append_length(Arg1, Arg2, Arg3, Arg4)