Lists as Sequences -- library(lists)

library(lists) provides a large number of list processing operations. See also lib-lis-basics, which describes the more basic list processing operations that are provided by library(basics).

The predicates defined by this library file are:


is_list(+List)
is true when List is instantiated to a proper list: that is, to either [] or [_|Tail] where Tail is a proper list. A variable, or a list that ends with a variable, will fail this test.
append(+ListOfLists, ?List)
is true when ListOfLists is a list [L1,...,Ln] of lists, List is a list, and appending L1, ..., Ln together yields List. If ListOfLists is not a proper list, append/2 will fail. Additionally, either List should be a proper list, or each of L1, ..., Ln should be a proper list. The behavior on non-lists is undefined. ListOfLists must be proper because for any given solution, infinitely many more can be obtained by inserting nils ([]) into ListOfList.
append(?Prefix, ?Tail1, ?List1, ?Tail2, ?List2)
is logically equivalent to:
          append(Prefix, Tail1, List1),
          append(Prefix, Tail2, List2).
          

but is much more efficient. append/5 is guaranteed to halt in finite time if any one of Prefix, List1, or List2 is a proper list.

You can use append/5 to add a common Prefix to the front of Tail1 and Tail2, to remove a common Prefix from List1 and List2, or in several other ways.

Here is an example of the use of append/5. The task is to check whether Word1 and Word2 are the same except for exactly one insertion, deletion, or transposition error.

          spell(i, Word1, Word2) :-
             append(_, Suffix, Word1, [_|Suffix], Word2).
          spell(d, Word1, Word2) :-
             append(_, [_|Suffix], Word1, Suffix, Word2).
          spell(t, Word1, Word2) :-
             append(_, [X,Y|Suffix], Word1, [Y,X|Suffix], Word2).
          
          | ?- spell(E, Word1, "fog"),
               print(E-Word1), nl, fail.
          i-"og"
          i-"fg"
          i-"fo"
          d-[_682,102,111,103]
          d-[102,_682,111,103]
          d-[102,111,_682,103]
          d-[102,111,103,_682]
          t-"ofg"
          t-"fgo"
          no
          

correspond(?X, ?Xlist, ?Ylist, ?Y)
is true when Xlist and Ylist are lists, X is an element of Xlist, Y is an element of Ylist, and X and Y are in corresponding places in their lists. Nothing is said about the other elements of the two lists, nor even whether they are the same length. Only one solution is ever found, as the procedure for correspond/4 contains a cut. For a logical predicate having similar effects (that is, one that finds all solutions), see select/4. Either Xlist or Ylist should be a proper list.
delete(+List, +Elem, ?Residue)
is true when List is a list, in which Elem may or may not occur, and Residue is a copy of List with all elements equal to Elem deleted. To extract a single copy of Elem, use select(Elem, List, Residue). For a given Elem and Residue, there are infinitely many Lists containing Elem or not. Therefore, this predicate only works one way around: List must be a proper list and Elem should be instantiated. Only one solution is ever found.
delete(+List, +Elem, +Count, ?Residue)
is true when List is a list, in which Elem may or may not occur, and Count is a non-negative integer. Residue is a copy of List with the first Count elements equal to Elem deleted. If List has fewer than Count elements equal to Count, all of them are deleted. If List is not proper, delete/4 may fail. Elem and the elements of List should be sufficiently instantiated for \= to be sound.
keys_and_values(?KeyValList, ?KeyList, ?ValList)
is true when all three arguments are lists of the same length (at least one of them should be a proper list), and are of the form
          KeyValList = [K1-V1,K2-V2,...,Kn-Vn]
          KeyList    = [K1,   K2   ,...,Kn   ]
          ValList    = [   V1,   V2,...,   Vn]
          

That is, the ith element of KeyValList is a pair Ki-Vi, where Ki is the ith element of KeyList and Vi is the ith element of ValList. The main point of this, of course, is that KeyValList is the kind of list that the built-in predicate keysort/2 sorts, where the Ki are the keys that are sorted on and the Vi go along for the ride. You can, for example, sort a list without discarding duplicate elements, using

          msort(Raw, Sorted) :-
                  keys_and_values(RawKV, Raw, _),
                  keysort(RawKV, SortedKV),
                  keys_and_values(SortedKV, Sorted, _).
          

keys_and_values/3 can also be used for constructing the input (list) argument of list_to_map/2 and for decomposing the result of map_to_list/2 -- see library(maps) (lib-abs).

          | ?- keys_and_values([light-dark,
                                    near-far,
                                    wet-dry],
                                    Keys, Vals).
          
          Keys = [light,near,wet],
          Vals = [dark,far,dry]
          
          | ?- keys_and_values(Pairs, [light,near,wet],
          |                           [dark,far,dry]).
          
          Pairs = [light-dark,near-far,wet-dry]
          

last(?Last, +List)
is true when List is a list and Last is its last element. This could be defined as
          last(X, L) :-
             append(_, [X], L).
          

nextto(?X, ?Y, +List)
is true when X and Y appear side-by-side in List. It could be defined as
          nextto(X, Y, List) :- append(_, [X,Y|_], List).
          

nextto/3 may be used to enumerate successive pairs from List. List should be a proper list.

nth0(?N, ?List, ?Elem)
is true when Elem is the Nth member of List, counting the first as element 0 (that is, throw away the first N elements and unify Elem with the next one). Note that the argument pattern resembles that of arg/3. Unlike arg/3 (but like genarg/3; see lib-tma-arg), nth0/3 can be used to solve for either N or Elem. If used to solve for N, List should be a proper list.
nth0(?N, ?List, ?Elem, ?Rest)
unifies Elem with the Nth element of List, counting from 0, and Rest with the remaining elements. nth0/4 can be used to select the Nth element of List (yielding Elem and Rest), or to insert Elem before the Nth (counting from 0) element of Rest, (yielding List). Either N should be instantiated, or List should be a proper list, or Rest should be a proper list; any one is enough.
          | ?- nth0(2, List, c, [a,b,d,e]).
          
          List = [a,b,c,d,e]
          
          | ?- nth0(2, [a,b,c,d,e], Elem, Rest).
          
          Elem = c,
          Rest = [a,b,d,e]
          
          | ?- nth0(N, [a,b,c,d,e], c, Rest).
          
          N = 2,
          Rest = [a,b,d,e]
          
          | ?- nth0(1, List, Elem, Rest).
          
          List = [_973,Elem|_976],
          Elem = _755,
          Rest = [_973|_976]
          

nth1(?N, ?List, ?Elem)
is the same as nth0/3, except that it counts from 1 so that, for example,
          nth1(1, [H|T], H)
          

is true. List should be a proper list.

nth1(?N, ?List, ?Elem, ?Rest)
is the same as nth0/4 except that it counts from 1. It can be used to select the Nth element of List (yielding Elem and Rest), or to insert Elem before the N+1st element of Rest, when it yields List. Either N should be instantiated, or List should be a proper list, or Rest should be a proper list; any one is enough.
          | ?- nth1(3, List, c, [a,b,d,e]).
          
          List = [a,b,c,d,e]
          
          | ?- nth1(3, [a,b,c,d,e], Elem, Rest).
          
          Elem = c
          Rest = [a,b,d,e]
          
          | ?- nth1(N, [a,b,c,d,e], c, Rest).
          
          N = 3
          Rest = [a,b,d,e]
          
          | ?- nth1(1, List, Elem, Rest).
          
          List = [Elem|Rest],
          Elem = _755,
          Rest = _770
          

perm(+List, ?Perm)
is true when List and Perm are permutations of each other. If you simply want to test this, the best way is to sort the two lists and see if the results are the same; use samsort/2 from library(samsort) (lib-abs) in preference to sort/2.

The point of perm/2 is to generate permutations; it only works if List is a proper list. perm/2 should not be used in new programs; use permutation/2 instead.

permutation(?List, ?Perm)
is true when List and Perm are permutations of each other. Unlike perm/2, it will work even when List is not a proper list. permutation/2 will return reasonable results when Perm is also not proper, but will still backtrack forever unless one of the arguments is proper. Be careful: permutation/2 is is quite efficient, but the number of permutations of an N-element list is N! (N-factorial). Even for a 7-element list that is 5040.
perm2(?A, ?B, ?C, ?D)
is true when [A, B] is a permutation of [C, D]. perm2/4 is very useful for writing pattern matchers over commutative operators. It is used more often than perm/2. perm2/4 is not really an operation on lists. perm2/4 is in library(lists) only because permutation/2 is there.
remove_dups(+List, ?Pruned)
removes duplicated elements from List, which should be a proper list. If List contains non-ground elements, Pruned may contain elements that unify. Two elements will be considered duplicates if and only if all possible substitutions cause them to be identical.
          | ?- remove_dups([X,X], L).
          
          X = _123
          L = [X]
          
          | ?- remove_dups([X,Y], L).
          
          X = _123
          Y = _126
          L = [X,Y]
          
          | ?- remove_dups([3,1,4,1], L).
          
          L = [1,3,4]
          

remove_dups/2 does not preserve the original order of the elements of List.

rev(+List, ?Reversed)
is true when List and Reversed are lists with the same elements but in opposite orders. List must be supplied as a proper list; if List is partial, rev/2 may find a solution, but if backtracked into will backtrack forever, trying ever longer lists. Use rev/2 only when you know that List is proper; it is then twice as fast as calling reverse/2.
reverse(?List, ?Reversed)
is true when List and Reversed are lists with the same elements but in opposite orders. Either List or Reversed should be a proper list: given either argument the other can be found. If both are partial, reverse/2 will keep trying longer instances of both. If you want an invertible relation, use this. If you only want the reversal to work one way around, rev/2 is adequate.
same_length(?List1, ?List2)
is true when List1 and List2 are both lists and have the same number of elements. No relation between the elements of List1 and List2 is implied. This predicate may be used to generate either list given the other, or indeed to generate two lists of the same length, in which case the arguments will be bound to lists of length 0, 1, 2, and so on. same_length/2 is supplied to make it easier to write invertible predicates, transferring the proper list status of either argument to the other. same_length(List1, List2) has the same effect as the following call to same_length/3:
          same_length(List1, List2, _ /* any length */)
          

same_length(?List1, ?List2, ?Length)
is true when List1 and List2 are both lists and have the same number of elements, and Length is an integer that is the common length of the two lists. No relation between the elements of List1 and List2 is implied. This predicate may be used to generate any of its arguments. If Length is given, or if either List1 or List2 is a proper list at the time of call, same_length/3 is determinate and terminates. Otherwise it will backtrack forever, binding its arguments to lists of length 0, 1, 2, and so on. same_length/3 is logically equivalent to
          length(List1, Length),
          length(List2, Length)
          

except that if List2 is known and the other arguments are not, this code will not terminate if backtracked into, while same_length/3 will terminate determinately.

select(?X, ?Xlist, ?Y, ?Ylist)
is true when X is the Kth element of Xlist and Y the Kth element of Ylist for some K, and apart from that element Xlist and Ylist are the same. You can use select/4 to replace X by Y or vice versa. Either Xlist or Ylist should be a proper list.
selectchk(?X, ?Xlist, ?Y, ?Ylist)
is to select/4 what memberchk/2 is to member/2 in library(basics).
shorter_list(?Short, ?Long)
is true when Short is a list strictly shorter than Long. No relation between the elements of Short and Long is implied. Long does not have to be a proper list provided it has one more element than Short. This can be used to generate lists shorter than Long; lengths 0, 1, 2, and so on will be tried, but backtracking will terminate with a list that is one element shorter than Long. shorter_list/2 cannot be used to generate lists longer than Short, because it does not look at all the elements of the longer list.
subseq(?Sequence, ?SubSequence, ?Complement)
is true when SubSequence and Complement are both subsequences of the list Sequence (the order of corresponding elements being preserved) and every element of Sequence that is not in SubSequence is in Complement and vice versa. Among other things, this means that
          length(Sequence) = length(SubSequence) +
                             length(Complement)
          

and

          subseq([1,2,3,4], [1,3,4], [2]).
          

subseq/3 was written to generate subsets and their complements together from Sequence, but can also be used to interleave two lists Subsequence and Complement in all possible ways. Either Sequence should be a proper list, or both SubSequence and Complement should both be proper lists. Note that if S1 is a subset of S2, it will be generated before S2 as a SubSequence and after it as a Complement. To be specific, take S1 = [a], S2 = [a,c], Sequence = [a,b,c]:

          | ?- subseq([a,b,c], Sub, Com).
          
          Sub = [],
          Com = [a,b,c] ;
          
          Sub = [c],
          Com = [a,b] ;
          
          Sub = [b],
          Com = [a,c] ;       % S2 generated as Complement
          
          Sub = [b,c],
          Com = [a] ;         % S1 generated as Complement
                               % (AFTER S2)
          Sub = [a],           % S1 generated as SubSequence
          Com = [b,c] ;       % (BEFORE S2)
          
          Sub = [a,c],         % S2 generated as SubSequence
          Com = [b] ;
          
          Sub = [a,b],
          Com = [c] ;
          
          Sub = [a,b,c],
          Com = [] ;
          
          no               % these 8 are all the solutions.
          

Further examples of the use of subseq/3 are:

          | ?- subseq([1,2,3,4], X, [2]).
          
          X = [1,3,4]
          
          | ?- subseq([a,b], Subs, Comp).
          
          Subs = [],
          Comp = [a,b] ;
          
          Subs = [b],
          Comp = [a] ;
          
          Subs = [a],
          Comp = [b] ;
          
          Subs = [a,b],
          Comp = [] ;
          
          no
          
          | ?- subseq(Seq, [@], [#]).
          
          Seq = [#,@] ;
          
          Seq = [@,#] ;
          
          no
          

subseq0(+Sequence, ?SubSequence)
is true when SubSequence is a subsequence of Sequence, but may be Sequence itself. Thus:
          | ?- subseq0([a,b], [a,b]).
          
          yes
          | ?- subseq0([a,b], [a]).
          
          yes
          

Also,

          | ?- setof(X, subseq0([a,b,c],X), Xs).
          
          Xs = [[],[a],[a,b],[a,b,c],[a,c],[b],[b,c],[c]]
          
          | ?- bagof(X, subseq0([a,b,c,d],X), Xs).
          
          Xs = [[a,b,c,d],[b,c,d],[c,d],[d],[],[c],[b,d],
          [b],[b,c],[a,c,d],[a,d],[a],[a,c],[a,b,d],[a,b],
          [a,b,c]]
          

Sequence must be a proper list.

subseq1(+Sequence, ?SubSequence)
is true when SubSequence is a proper subsequence of Sequence; that is, SubSequence contains at least one element less than Sequence. Sequence must be a proper list.
          | ?- % note that [a,b,c] does NOT appear in Xs:
          |    setof(X, subseq1([a,b,c],X), Xs).
          
          Xs = [[],[a],[a,b],[a,c],[b],[b,c],[c]]
          
          | ?- % note that [a,b,c,d] does NOT appear in Xs:
          |    bagof(X, subseq1([a,b,c,d],X), Xs).
          
          Xs = [[b,c,d],[c,d],[d],[],[c],[b,d],[b],[b,c],
          [a,c,d],[a,d],[a],[a,c],[a,b,d],[a,b],[a,b,c]]
          

sumlist(+Numbers, ?Total)
is true when Numbers is a proper list of numbers, and Total is their sum. Note that a list of arithmetic expressions will not work. If any of the Numbers is a floating-point number, Total will be a floating-point number; otherwise it will be an integer.
transpose(?X, ?Y)
is true when X is a list of the form [[X11,...,X1m],...,[Xn1,...,Xnm]] and Y is its transpose, that is, Y = [[X11,...,Xn1],...,[X1m,...,Xnm]].

To make the transpose/2 invertible, all the sublists of the list being transposed must be of the same length. If they are not, it will fail.