% This LaTeX document was generated using the LaTeX backend of PlDoc, % The SWI-Prolog documentation system \section{library(apply): Apply predicates on a list} \label{sec:apply} \begin{tags} \mtag{See also}- \file{apply_macros.pl} provides compile-time expansion for part of this library. \\- \url{http://www.cs.otago.ac.nz/staffpriv/ok/pllib.htm} \\- Unit test code in \file{src/Tests/library/test_apply.pl} \tag{To be done} Add \predref{include}{4}, \predref{include}{5}, \predref{exclude}{4}, \predref{exclude}{5} \end{tags} This module defines meta-predicates that apply a predicate on all members of a list. All predicates support partial application in the Goal argument. This means that these calls are identical: \begin{code} ?- maplist(=, [foo, foo], [X, Y]). ?- maplist(=(foo), [X, Y]). \end{code} \vspace{0.7cm} \begin{description} \predicate[det]{include}{3}{:Goal, +List1, ?List2} Filter elements for which \arg{Goal} succeeds. True if \arg{List2} contains those elements Xi of \arg{List1} for which \verb$call(Goal, Xi)$ succeeds. \begin{tags} \tag{See also} \predref{exclude}{3}, \predref{partition}{4}, \predref{convlist}{3}. \tag{Compatibility} Older versions of SWI-Prolog had \predref{sublist}{3} with the same arguments and semantics. \end{tags} \predicate[det]{exclude}{3}{:Goal, +List1, ?List2} Filter elements for which \arg{Goal} fails. True if \arg{List2} contains those elements Xi of \arg{List1} for which \verb$call(Goal, Xi)$ fails. \begin{tags} \tag{See also} \predref{include}{3}, \predref{partition}{4} \end{tags} \predicate[det]{partition}{4}{:Pred, +List, ?Included, ?Excluded} Filter elements of \arg{List} according to \arg{Pred}. True if \arg{Included} contains all elements for which \verb$call(Pred, X)$ succeeds and \arg{Excluded} contains the remaining elements. \begin{tags} \tag{See also} \predref{include}{3}, \predref{exclude}{3}, \predref{partition}{5}. \end{tags} \predicate[semidet]{partition}{5}{:Pred, +List, ?Less, ?Equal, ?Greater} Filter \arg{List} according to \arg{Pred} in three sets. For each element Xi of \arg{List}, its destination is determined by \verb$call(Pred, Xi, Place)$, where Place must be unified to one of \verb$<$, \verb$=$ or \verb$>$. \arg{Pred} must be deterministic. \begin{tags} \tag{See also} \predref{partition}{4} \end{tags} \predicate{maplist}{2}{:Goal, ?List1} \nodescription \predicate{maplist}{3}{:Goal, ?List1, ?List2} \nodescription \predicate{maplist}{4}{:Goal, ?List1, ?List2, ?List3} \nodescription \predicate{maplist}{5}{:Goal, ?List1, ?List2, ?List3, ?List4} True if \arg{Goal} is successfully applied on all matching elements of the list. The maplist family of predicates is defined as: \begin{code} 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). \end{code} This family of predicates is deterministic iff \arg{Goal} is deterministic and \arg{List1} is a proper list, i.e., a list that ends in \verb$[]$. \predicate[det]{convlist}{3}{:Goal, +ListIn, -ListOut} Similar to \predref{maplist}{3}, but elements for which \verb$call(Goal, ElemIn, _)$ fails are omitted from \arg{ListOut}. For example (using \file{library(yall)}): \begin{code} ?- convlist([X,Y]>>(integer(X), Y is X^2), [3, 5, foo, 2], L). L = [9, 25, 4]. \end{code} \begin{tags} \tag{Compatibility} Also appears in YAP \verb$library(maplist)$ and SICStus \verb$library(lists)$. \end{tags} \predicate{foldl}{4}{:Goal, +List, +V0, -V} \nodescription \predicate{foldl}{5}{:Goal, +List1, +List2, +V0, -V} \nodescription \predicate{foldl}{6}{:Goal, +List1, +List2, +List3, +V0, -V} \nodescription \predicate{foldl}{7}{:Goal, +List1, +List2, +List3, +List4, +V0, -V} Fold an ensemble of \textit{m} (0 \Sel{} \textit{m} \Sel{} 4) lists of length \textit{n} head-to-tail ("fold-left"), using columns of \textit{m} list elements as arguments for \arg{Goal}. The \const{foldl} family of predicates is defined as follows, with \arg{V0} an initial value and \arg{V} the final value of the folding operation: \begin{code} foldl(G, [X_11, ..., X_1n], [X_21, ..., X_2n], ..., [X_m1, ..., X_mn], V0, V) :- call(G, X_11, ..., X_m1, V0, V1), call(G, X_12, ..., X_m2, V1, V2), ... call(G, X_1n, ..., X_mn, V, V). \end{code} No implementation for a corresponding \const{foldr} is given. A \const{foldr} implementation would consist in first calling \predref{reverse}{2} on each of the \textit{m} input lists, then applying the appropriate \const{foldl}. This is actually more efficient than using a properly programmed-out recursive algorithm that cannot be tail-call optimized. \predicate{scanl}{4}{:Goal, +List, +V0, -Values} \nodescription \predicate{scanl}{5}{:Goal, +List1, +List2, +V0, -Values} \nodescription \predicate{scanl}{6}{:Goal, +List1, +List2, +List3, +V0, -Values} \nodescription \predicate{scanl}{7}{:Goal, +List1, +List2, +List3, +List4, +V0, -Values} Scan an ensemble of \textit{m} (0 \Sel{} \textit{m} \Sel{} 4) lists of length \textit{n} head-to-tail ("scan-left"), using columns of \textit{m} list elements as arguments for \arg{Goal}. The \const{scanl} family of predicates is defined as follows, with \arg{V0} an initial value and \arg{V} the final value of the scanning operation: \begin{code} scanl(G, [X_11, ..., X_1n], [X_21, ..., X_2n], ..., [X_m1, ..., X_mn], V0, [V0, V1, ..., Vn] ) :- call(G, X_11, ..., X_m1, V0, V1), call(G, X_12, ..., X_m2, V1, V2), ... call(G, X_1n, ..., X_mn, V, Vn). \end{code} \const{scanl} behaves like a \const{foldl} that collects the sequence of values taken on by the \arg{Vx} accumulator into a list. \end{description}