![Click to show exports only All predicates](/linkedpolitics/swish/pldoc/res/private.png)
apply.pl -- Apply predicates on a list
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:
?- maplist(=, [foo, foo], [X, Y]). ?- maplist(=(foo), [X, Y]).
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. 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. partition(:Pred, +List, ?Included, ?Excluded) is det
- Filter elements of List according to Pred. True if Included
contains all elements for which
call(Pred, X)
succeeds and Excluded contains the remaining elements. 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. maplist(:Goal, ?List1)
maplist(:Goal, ?List1, ?List2)
maplist(:Goal, ?List1, ?List2, ?List3)
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
[]
. 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].
foldl(:Goal, +List, +V0, -V)
foldl(:Goal, +List1, +List2, +V0, -V)
foldl(:Goal, +List1, +List2, +List3, +V0, -V)
foldl(:Goal, +List1, +List2, +List3, +List4, +V0, -V)
- Fold an ensemble of m (0 <= m <= 4) lists of length n
head-to-tail ("fold-left"), using columns of m list elements as
arguments for Goal. The
foldl
family of predicates is defined as follows, with V0 an initial value and V the final value of the folding operation: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<n-1>, V).
No implementation for a corresponding
foldr
is given. Afoldr
implementation would consist in first calling reverse/2 on each of the m input lists, then applying the appropriatefoldl
. This is actually more efficient than using a properly programmed-out recursive algorithm that cannot be tail-call optimized. scanl(:Goal, +List, +V0, -Values)
scanl(:Goal, +List1, +List2, +V0, -Values)
scanl(:Goal, +List1, +List2, +List3, +V0, -Values)
scanl(:Goal, +List1, +List2, +List3, +List4, +V0, -Values)
- Scan an ensemble of m (0 <= m <= 4) lists of length n
head-to-tail ("scan-left"), using columns of m list elements as
arguments for Goal. The
scanl
family of predicates is defined as follows, with V0 an initial value and V the final value of the scanning operation: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<n-1>, Vn).
scanl
behaves like afoldl
that collects the sequence of values taken on by the Vx accumulator into a list.
Undocumented predicates
The following predicates are exported, but not or incorrectly documented.
maplist(Arg1, Arg2, Arg3)
foldl(Arg1, Arg2, Arg3, Arg4, Arg5, Arg6)
scanl(Arg1, Arg2, Arg3, Arg4, Arg5, Arg6)
foldl(Arg1, Arg2, Arg3, Arg4, Arg5, Arg6, Arg7)
scanl(Arg1, Arg2, Arg3, Arg4, Arg5)
scanl(Arg1, Arg2, Arg3, Arg4, Arg5, Arg6, Arg7)
maplist(Arg1, Arg2, Arg3, Arg4)
maplist(Arg1, Arg2, Arg3, Arg4, Arg5)
foldl(Arg1, Arg2, Arg3, Arg4, Arg5)