% This LaTeX document was generated using the LaTeX backend of PlDoc, % The SWI-Prolog documentation system \section{library(lists): List Manipulation} \label{sec:lists} \begin{tags} \tag{Compatibility} Virtually every Prolog system has \file{library(lists)}, but the set of provided predicates is diverse. There is a fair agreement on the semantics of most of these predicates, although error handling may vary. \end{tags} This library provides commonly accepted basic predicates for list manipulation in the Prolog community. Some additional list manipulations are built-in. See e.g., \predref{memberchk}{2}, \predref{length}{2}. The implementation of this library is copied from many places. These include: "The Craft of Prolog", the DEC-10 Prolog library (LISTRO.PL) and the YAP lists library. Some predicates are reimplemented based on their specification by Quintus and SICStus.\vspace{0.7cm} \begin{description} \predicate{member}{2}{?Elem, ?List} True if \arg{Elem} is a member of \arg{List}. The SWI-Prolog definition differs from the classical one. Our definition avoids unpacking each list element twice and provides determinism on the last element. E.g. this is deterministic: \begin{code} member(X, [One]). \end{code} \begin{tags} \tag{author} Gertjan van Noord \end{tags} \predicate{append}{3}{?List1, ?List2, ?List1AndList2} \arg{List1AndList2} is the concatenation of \arg{List1} and \arg{List2} \predicate{append}{2}{+ListOfLists, ?List} Concatenate a list of lists. Is true if \arg{ListOfLists} is a list of lists, and \arg{List} is the concatenation of these lists. \begin{arguments} \arg{ListOfLists} & must be a list of \textit{possibly} partial lists \\ \end{arguments} \predicate{prefix}{2}{?Part, ?Whole} True iff \arg{Part} is a leading substring of \arg{Whole}. This is the same as \verb$append(Part, _, Whole)$. \predicate{select}{3}{?Elem, ?List1, ?List2} Is true when \arg{List1}, with \arg{Elem} removed, results in \arg{List2}. This implementation is determinsitic if the last element of \arg{List1} has been selected. \predicate[semidet]{selectchk}{3}{+Elem, +List, -Rest} Semi-deterministic removal of first element in \arg{List} that unifies with \arg{Elem}. \predicate[nondet]{select}{4}{?X, ?XList, ?Y, ?YList} Select from two lists at the same position. True if \arg{XList} is unifiable with \arg{YList} apart a single element at the same position that is unified with \arg{X} in \arg{XList} and with \arg{Y} in \arg{YList}. A typical use for this predicate is to \textit{replace} an element, as shown in the example below. All possible substitutions are performed on backtracking. \begin{code} ?- select(b, [a,b,c,b], 2, X). X = [a, 2, c, b] ; X = [a, b, c, 2] ; false. \end{code} \begin{tags} \tag{See also} \predref{selectchk}{4} provides a semidet version. \end{tags} \predicate[semidet]{selectchk}{4}{?X, ?XList, ?Y, ?YList} Semi-deterministic version of \predref{select}{4}. \predicate{nextto}{3}{?X, ?Y, ?List} True if \arg{Y} directly follows \arg{X} in \arg{List}. \predicate[det]{delete}{3}{+List1, @Elem, -List2} Delete matching elements from a list. True when \arg{List2} is a list with all elements from \arg{List1} except for those that unify with \arg{Elem}. Matching \arg{Elem} with elements of \arg{List1} is uses \verb$\+ Elem \= H$, which implies that \arg{Elem} is not changed. \begin{tags} \tag{See also} \predref{select}{3}, \predref{subtract}{3}. \tag{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. \Sequal{}), delete first/all, be deterministic or not. \end{tags} \predicate{nth0}{3}{?Index, ?List, ?Elem} True when \arg{Elem} is the \arg{Index}'th element of \arg{List}. Counting starts at 0. \begin{tags} \tag{Errors} \verb$type_error(integer, Index)$ if \arg{Index} is not an integer or unbound. \tag{See also} \predref{nth1}{3}. \end{tags} \predicate{nth1}{3}{?Index, ?List, ?Elem} Is true when \arg{Elem} is the \arg{Index}'th element of \arg{List}. Counting starts at 1. \begin{tags} \tag{See also} \predref{nth0}{3}. \end{tags} \predicate[det]{nth0}{4}{?N, ?List, ?Elem, ?Rest} Select/insert element at index. True when \arg{Elem} is the \arg{N}'th (0-based) element of \arg{List} and \arg{Rest} is the remainder (as in by \predref{select}{3}) of \arg{List}. For example: \begin{code} ?- 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. \end{code} \begin{code} ?- nth0(1, L, a1, [a,b]). L = [a, a1, b]. \end{code} \predicate[det]{nth1}{4}{?N, ?List, ?Elem, ?Rest} As \predref{nth0}{4}, but counting starts at 1. \predicate{last}{2}{?List, ?Last} Succeeds when \arg{Last} is the last element of \arg{List}. This predicate is \const{semidet} if \arg{List} is a list and \const{multi} if \arg{List} is a partial list. \begin{tags} \tag{Compatibility} There is no de-facto standard for the argument order of \predref{last}{2}. Be careful when porting code or use \verb$append(_, [Last], List)$ as a portable alternative. \end{tags} \predicate[semidet]{proper_length}{2}{@List, -Length} True when \arg{Length} is the number of elements in the proper list \arg{List}. This is equivalent to \begin{code} proper_length(List, Length) :- is_list(List), length(List, Length). \end{code} \predicate{same_length}{2}{?List1, ?List2} Is true when \arg{List1} and \arg{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. \begin{tags} \tag{See also} \predref{length}{2} \end{tags} \predicate{reverse}{2}{?List1, ?List2} Is true when the elements of \arg{List2} are in reverse order compared to \arg{List1}. This predicate is deterministic if either list is a proper list. If both lists are \textit{partial lists} backtracking generates increasingly long lists. \predicate[nondet]{permutation}{2}{?Xs, ?Ys} True when \arg{Xs} is a permutation of \arg{Ys}. This can solve for \arg{Ys} given \arg{Xs} or \arg{Xs} given \arg{Ys}, or even enumerate \arg{Xs} and \arg{Ys} together. The predicate \predref{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 \arg{Xs} and \arg{Ys} are provided and both lists have equal length the order is \Sbar{}\arg{Xs}\Sbar{}\Shat{}2. Simply testing whether \arg{Xs} is a permutation of \arg{Ys} can be achieved in order log(\Sbar{}\arg{Xs}\Sbar{}) using \predref{msort}{2} as illustrated below with the \const{semidet} predicate \predref{is_permutation}{2}: \begin{code} is_permutation(Xs, Ys) :- msort(Xs, Sorted), msort(Ys, Sorted). \end{code} The example below illustrates that \arg{Xs} and \arg{Ys} being proper lists is not a sufficient condition to use the above replacement. \begin{code} ?- permutation([1,2], [X,Y]). X = 1, Y = 2 ; X = 2, Y = 1 ; false. \end{code} \begin{tags} \tag{Errors} \verb$type_error(list, Arg)$ if either argument is not a proper or partial list. \end{tags} \predicate[det]{flatten}{2}{+NestedList, -FlatList} Is true if \arg{FlatList} is a non-nested version of \arg{NestedList}. Note that empty lists are removed. In standard Prolog, this implies that the atom '\Snil{}' is removed too. In SWI7, \verb$[]$ is distinct from '\Snil{}'. Ending up needing \predref{flatten}{2} often indicates, like \predref{append}{3} for appending two lists, a bad design. Efficient code that generates lists from generated small lists must use difference lists, often possible through grammar rules for optimal readability. \begin{tags} \tag{See also} \predref{append}{2} \end{tags} \predicate{clumped}{2}{+Items, -Pairs} \arg{Pairs} is a list of \verb$Item-Count$ pairs that represents the \textit{run length encoding} of \arg{Items}. For example: \begin{code} ?- clumped([a,a,b,a,a,a,a,c,c,c], R). R = [a-2, b-1, a-4, c-3]. \end{code} \begin{tags} \tag{Compatibility} SICStus \end{tags} \predicate[nondet]{subseq}{3}{+List, -SubList, -Complement} \nodescription \predicate[nondet]{subseq}{3}{-List, +SubList, +Complement} Is true when \arg{SubList} contains a subset of the elements of \arg{List} in the same order and \arg{Complement} contains all elements of \arg{List} not in \arg{SubList}, also in the order they appear in \arg{List}. \begin{tags} \tag{Compatibility} SICStus. The SWI-Prolog version raises an error for less instantiated modes as these do not terminate. \end{tags} \predicate[semidet]{max_member}{2}{-Max, +List} True when \arg{Max} is the largest member in the standard order of terms. Fails if \arg{List} is empty. \begin{tags} \mtag{See also}- \predref{compare}{3} \\- \predref{max_list}{2} for the maximum of a list of numbers. \end{tags} \predicate[semidet]{min_member}{2}{-Min, +List} True when \arg{Min} is the smallest member in the standard order of terms. Fails if \arg{List} is empty. \begin{tags} \mtag{See also}- \predref{compare}{3} \\- \predref{min_list}{2} for the minimum of a list of numbers. \end{tags} \predicate[semidet]{max_member}{3}{:Pred, -Max, +List} True when \arg{Max} is the largest member according to \arg{Pred}, which must be a 2-argument callable that behaves like (\Stle{})/2. Fails if \arg{List} is empty. The following call is equivalent to \predref{max_member}{2}: \begin{code} ?- max_member(@=<, X, [6,1,8,4]). X = 8. \end{code} \begin{tags} \tag{See also} \predref{max_list}{2} for the maximum of a list of numbers. \end{tags} \predicate[semidet]{min_member}{3}{:Pred, -Min, +List} True when \arg{Min} is the smallest member according to \arg{Pred}, which must be a 2-argument callable that behaves like (\Stle{})/2. Fails if \arg{List} is empty. The following call is equivalent to \predref{max_member}{2}: \begin{code} ?- min_member(@=<, X, [6,1,8,4]). X = 1. \end{code} \begin{tags} \tag{See also} \predref{min_list}{2} for the minimum of a list of numbers. \end{tags} \predicate[det]{sum_list}{2}{+List, -Sum} \arg{Sum} is the result of adding all numbers in \arg{List}. \predicate[semidet]{max_list}{2}{+List:list(number), -Max:number} True if \arg{Max} is the largest number in \arg{List}. Fails if \arg{List} is empty. \begin{tags} \tag{See also} \predref{max_member}{2}. \end{tags} \predicate[semidet]{min_list}{2}{+List:list(number), -Min:number} True if \arg{Min} is the smallest number in \arg{List}. Fails if \arg{List} is empty. \begin{tags} \tag{See also} \predref{min_member}{2}. \end{tags} \predicate[semidet]{numlist}{3}{+Low, +High, -List} \arg{List} is a list [\arg{Low}, \arg{Low}+1, ... \arg{High}]. Fails if \arg{High} $<$ \arg{Low}. \begin{tags} \mtag{Errors}- \verb$type_error(integer, Low)$ \\- \verb$type_error(integer, High)$ \end{tags} \predicate[semidet]{is_set}{1}{@Set} True if \arg{Set} is a proper list without duplicates. Equivalence is based on \predref{\Sequal}{2}. The implementation uses \predref{sort}{2}, which implies that the complexity is N*\verb$log(N)$ and the predicate may cause a resource-error. There are no other error conditions. \predicate[det]{list_to_set}{2}{+List, ?Set} True when \arg{Set} has the same elements as \arg{List} in the same order. The left-most copy of duplicate elements is retained. \arg{List} may contain variables. Elements \textit{E1} and \textit{E2} are considered duplicates iff \textit{E1} \Sequal{} \textit{E2} holds. The complexity of the implementation is N*\verb$log(N)$. \begin{tags} \tag{Errors} \arg{List} is type-checked. \tag{See also} \predref{sort}{2} can be used to create an ordered set. Many set operations on ordered sets are order N rather than order N\Spow{}2. The \predref{list_to_set}{2} predicate is more expensive than \predref{sort}{2} because it involves, two sorts and a linear scan. \tag{Compatibility} Up to version 6.3.11, \predref{list_to_set}{2} had complexity N\Spow{}2 and equality was tested using \predref{\Seq}{2}. \end{tags} \predicate[det]{intersection}{3}{+Set1, +Set2, -Set3} True if \arg{Set3} unifies with the intersection of \arg{Set1} and \arg{Set2}. The complexity of this predicate is \Sbar{}\arg{Set1}\Sbar{}*\Sbar{}\arg{Set2}\Sbar{}. A \textit{set} is defined to be an unordered list without duplicates. Elements are considered duplicates if they can be unified. \begin{tags} \tag{See also} \predref{ord_intersection}{3}. \end{tags} \predicate[det]{union}{3}{+Set1, +Set2, -Set3} True if \arg{Set3} unifies with the union of the lists \arg{Set1} and \arg{Set2}. The complexity of this predicate is \Sbar{}\arg{Set1}\Sbar{}*\Sbar{}\arg{Set2}\Sbar{}. A \textit{set} is defined to be an unordered list without duplicates. Elements are considered duplicates if they can be unified. \begin{tags} \tag{See also} \predref{ord_union}{3} \end{tags} \predicate[semidet]{subset}{2}{+SubSet, +Set} True if all elements of \arg{SubSet} belong to \arg{Set} as well. Membership test is based on \predref{memberchk}{2}. The complexity is \Sbar{}\arg{SubSet}\Sbar{}*\Sbar{}\arg{Set}\Sbar{}. A \textit{set} is defined to be an unordered list without duplicates. Elements are considered duplicates if they can be unified. \begin{tags} \tag{See also} \predref{ord_subset}{2}. \end{tags} \predicate[det]{subtract}{3}{+Set, +Delete, -Result} \arg{Delete} all elements in \arg{Delete} from \arg{Set}. Deletion is based on unification using \predref{memberchk}{2}. The complexity is \Sbar{}\arg{Delete}\Sbar{}*\Sbar{}\arg{Set}\Sbar{}. A \textit{set} is defined to be an unordered list without duplicates. Elements are considered duplicates if they can be unified. \begin{tags} \tag{See also} \predref{ord_subtract}{3}. \end{tags} \end{description}