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 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.

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