Add to library(apply): any/2 (or include/2); foldl helper

I need a predicate that succeeds if any element in a list satisfies a condition. As far as I can tell, there isn’t one; this works but is (a) not obvious and (b) inefficient (scans the whole list and also constructs a list that isn’t really used):

include(Goal, LIist) :-
    include(Goal, List, [_|_]). 

So, I suggest adding include/2 to library(apply) [or perhaps call it any/2]).
Note that maplist/2 is the same as all/2 (which succeeds if all elements in the list satisfy a condition).
We might also want an exclude/2 (or none/2) that succeeds if none of the elements satisfy a condition.

include/3 can be implemented using foldl/4, although it’s a bit clunky. This helper predicate makes it easier to implement include/3 using foldl/4; and it’s also useful in other situations (I often find myself writing this, or something similar):

foldl_helper(Pred, X, In, Out) :-
    (  call(Pred, X, Y)
    -> Out = [Y|In]
    ;  Out = In
    )

(Possibly *-> would be better than ->; for example maplist/3 can backtrack over multiple results for its Goal.)
(foldl_helper is a terrible name but I can’t think of a better one.)

BTW, the library doesn’t have a foldr – I’m guessing that it isn’t needed for logic programming, only for functional programming … is that correct?

1 Like

:slight_smile: I guess it is needed, in some cases. There have been two attempts in the recent past but the resolution seems to have been, “foldr is just reverse + foldl so do that instead”. The full discussions are in PR35 and PR727.

Maybe you need to show how you use this. Isn’t partition/4 doing this already? (A misleading name btw…)

No I mean convlist/3.

I was thinking of something simpler: the helper could be used to implement convlist/3, except this also reverses, so I guess I’d need foldr/4 (or maybe my definition of foldl_helper/4 is somehow backwards):

if_even_then_odd(X, Y) :- X mod 2 =:= 0, Y is X + 1.
?- foldl(foldl_helper(if_even_then_odd), [2,3,4,5,6,7,8], [], Z).
Z = [9, 7, 5, 3].

Anyway, my immediate (small) suggestion was for include/2 (or any/2).

Hmm, I still don’t get it :sweat_smile:

?- convlist(if_even_then_odd, [2,3,4,5,6,7,8], R).
R = [3, 5, 7, 9].

The following seems not your solution. Could you explain
what’s wrong with this “solution.” I must be missing something.

positive(X):- X>0.

% ?- maplist(positive, [1,2]).
%@ true.

% ?- maplist(positive, [-1,2]).
%@ false.

We didn’t even exactly discuss the definitions so far I guess. To make it easier I might start with the C++ alternatives, called all_of, any_of, none_of. Summarizing a bit:

all_of: Checks if unary predicate p returns true for all elements.

any_of: Checks if unary predicate p returns true for at least one element

none_of: Checks if unary predicate p returns true for no elements

With these, here is one attempt at definitions (using what you Peter have posted so far)

all_of(Pred, L) :-
    maplist(Pred, L).

any_of(Pred, L) :-
    once( member(X, L), call(Pred, X) ).

none_of(Pred, L) :-
    forall(member(X, L), \+ call(Pred, X)).

Is that roughly what you had in mind @peter.ludemann ?

The any/2 predicate succeeds if at least one element in the list satisfies a condition. This does what I want, but is inefficient:

any(Goal, List) :- include(Goal, List, [_|_]).

That is, include/3 generates a list with at least one element, which means that at least one element X in List satisfied call(Goal,X).

Yes, that’s roughly what I had in mind. (Ignore my other bit about a “foldl helper”, at least for now)

The corresponding Python functions are:
all()
any()
(none() would be not any()) (I think – it’s late at night and I always have to triple-check de Morgan’s laws)

Thanks for clarification, @Boris and @peter.ludemann. Now it is clear.

Wait, does this mean that any_of could be \+ none_of? :exploding_head:

1 Like

As a prologer, some_of sounds better naming, though my personal impression.

1 Like

I think we can all agree that maplist/2 is a strange way of saying all_of :smiley:

∃x ∈ A, P(x) ⇔ ¬[∀x ∈ A, ¬P(x)]

And:

any_of(Goal, List) :- \+ include(Goal, List, []).

(but not efficient)
which is equivalent to

any_of(Goal, List) :- include(Goal, List, [_|_]).

or (as @Boris wrote):

any_of(Goal, List) :- once( ( member(X, List), call(Goal, X) ) ).

As maplist(p, [a1,a2,…,an]) means all_of ai p(ai) is true, i.e. p(p1), p(a2), …, p(an) (conjuntive reading). In this sence, I thought maplist is already a universal quatifier (all_of =forall=all). I prefer rather to rename maplist to all to introduce a new name. This is my personal opinion.

The all/none is fairly trivial, but the “any” depends a lot on how we want to handle bindings and non-determinism. For bindings, we both have problems with a non-ground goal as with non-ground list elements. For example, if we found one element for which Goal succeeds, do we continue with the remainder of the list or not? If Goal is (now) ground and the remainder of the list is ground, this merely burns CPU cycles. Otherwise it could be meaningful.

I’m afraid a general definition that satisfies all use cases is hard to give and it seems that, given a particular use case, we have quite a few ways to solve this.

Reading the comment and agreeing, I feel pessimistic about any_of implentation, with similar feeling about constrained setof and findall. However I notice that recently I frequently use findall mostly on easy preprocessing data for ZDD. There should be a safe but useful class of usage of any_of.

I wonder if the well-founded semantics could be applied to restrict queries discussed here, though I am not familiar with that semantics for prolog. If you investigated such restriction, I appreciate if you could touch here for us. Well-founded semantics sounds useful to make clear behavioural semantics, not in “declarative semantics”.

maplist(dif(X), [Y, Z, U]) and any_of(sleep, [10, 20, 30]) might be well-founded in that sense, though declartive one (intention of the query) is not so clear. I am writing without knowing what I am writing. Problem is vague for my sight.

1 Like

Don’t we have that problem with any predicate that runs over lists, not just “any”?
e.g.:

?- include(dif(1), [0,1,2,1,4], Z).
Z = [0, 2, 4].

?- include(dif(1), [0,1,2,X,4], Z), X=1.
false.

Seeing the queries, which is impressive, include looks like
a way of producing conjunctive constraint. If so, any_of
produces disjunctive constraint, and none_of is a variant producers
based on de Morgan law, as you showed. Now I feel I had taken things too serious.