
apply.pl -- Apply predicates on a listThis 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 detcall(Goal, Xi) succeeds.
exclude(:Goal, +List1, ?List2) is detcall(Goal, Xi) fails.
partition(:Pred, +List, ?Included, ?Excluded) is detcall(Pred, X) succeeds and
Excluded contains the remaining elements.
partition(:Pred, +List, ?Less, ?Equal, ?Greater) is semidetcall(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)
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 detcall(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)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. A foldr
implementation would consist in first calling reverse/2 on each of
the m input lists, then applying the appropriate foldl. 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)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 a foldl that collects the sequence of
values taken on by the Vx accumulator into a list.