- 1.1.5
Prolog metapredicates for set comprehension like setof/3 were introduced by David Warren in 1982
to collect goal instantiations by backtracking.
This necessitated indeed a special mechanism to add to Prolog,
which is used for bagof/3, findall/3, forall/2, foreach/2, or aggregate/3 for instance.
This approach to set comprehension is correct for the goal success semantics of Prolog,
but incorrect for the answer constraint semantics,
e.g. universal quantifier constraint for_all/2 defined here compared to standard forall/2 foreach/2 metapredicates:
?- L=[A, B, C], for_all(X in L, X=1). % constraint posted for all elements
L = [1, 1, 1],
A = B, B = C, C = 1.
?- L=[A, B, C], forall(member(X, L), X=1). % satisfiability test for all elements
L = [A, B, C].
?- L=[A, B, C], foreach(member(X, L), X=1). % idem
L = [A, B, C].
?- L=[A, B, C], for_all([X, Y] in L, X=Y).
L = [C, C, C],
A = B, B = C.
?- L=[A, B, C], forall((member(X, L), member(Y, L)), X=Y).
L = [A, B, C].
?- use_module(library(clpfd)).
true.
?- L=[A, B, C], forall(member(X, L), X#>1).
L = [A, B, C].
?- L=[A, B, C], for_all(X in L, X#>1).
L = [A, B, C],
clpfd:(A in 2..sup),
clpfd:(B in 2..sup),
clpfd:(C in 2..sup).
?- forall(member(X, [1, 2, 3]), Y#>X).
true.
?- for_all(X in [1, 2, 3], Y#>X).
clpfd:(Y in 4..sup).
We provide here metapredicates for comprehension by iteration, instead of backtracking, which
- rename comprehension variables and raise an error if they are instantiated (they can be attributed and will be renamed without attributes),
- constrain the calling context variables,
- possibly non-deterministically, if the conditions or goal are non-deterministic.
The comprehension variables must be given with a mandatory "in" domain, and optionally a "where" condition.
The "in" domain must be either a domain of integers (i.e. union \/ of intervals ..) or a list of terms.
Shorthand notations are evaluated in the domain.
?- for_all([I, J] in 1..3 where I<J, writeln(I-J)).
1-2
1-3
2-3
true.
?- for_all([I in 1..3, J in I+1..3], writeln(I-J)).
1-2
1-3
2-3
true.
list_of/3 collects the elements defined by comprehension in a list:
?- list_of([I, J] in 1..3 where I<J, I-J, List).
List = [1-2, 1-3, 2-3].
aggregate_for/6 expresses a relation on the application of a binary operator between elements defined by comprehension:
?- aggregate_for(X in 1..5, X+1, +, 0, =, Term).
Term = 1+1+(2+1+(3+1+(4+1+(5+1+0)))).
?- use_module(library(clpfd)).
true.
?- aggregate_for(X in 1..5, X+1, +, 0, #=, Result).
Result = 20.
The "where" condition in intensional definitions can bind or constrain context variables.
In particular, if the "where" condition is a constraint, the constraint is posted and thus tested for satisfiability, not entailment.
The example below illustrates the difference: X=Y is satisfiable and posted for all X, Y,
whereas in the second query, the condition X==Y is just a test and succeeds on the elements where it is satisfied without changing L:
?- L=[A, B, C], for_all([X, Y] in L where X=Y, true).
L = [C, C, C],
A = B, B = C.
?- L=[A, B, C], for_all([X, Y] in L where X==Y, true).
L = [A, B, C].
The "where" condition goal can also be non-deterministic,
making the comprehension metapredicate non-deterministic in this case.