How would one implement a not_all_equal/1
predicate, which succeeds if the given list contains at least 2 different elements and fails otherwise?
Here is my attempt (a not very pure one):
not_all_equal(L) :-
( member(H1, L), member(H2, L), H1 \= H2 -> true
; list_to_set(L, S),
not_all_equal_(S)
).
not_all_equal_([H|T]) :-
( member(H1, T), dif(H, H1)
; not_all_equal_(T)
).
This however does not always have the best behaviour:
?- not_all_equal([A,B,C]), A = a, B = b.
A = a,
B = b ;
A = a,
B = b,
dif(a, C) ;
A = a,
B = b,
dif(b, C) ;
false.
In this example, only the first answer should come out, the two other ones are superfluous.
Here's a straightforward way you can do it and preserve logical-purity!
Here are some sample queries using SWI-Prolog 7.7.2.
First, the most general query:
Next, the query the OP gave in the question:
Last, let's put the subgoal
A=a, B=b
upfront:Good, but ideally the last query should have succeeded deterministically!
Enter
library(reif)
First argument indexing takes the principal functor of the first predicate argument (plus a few simple built-in tests) into account to improve the determinism of sufficiently instantiated goals.
This, by itself, does not cover
dif/2
satisfactorily.What can we do? Work with reified term equality/inequality—effectively indexing
dif/2
!Notice the similarities of the new and the old implementation!
Above, the goal
X = E
is redundant on the left-hand side. Let's remove it!Sweet! But, alas, we're not quite done (yet)!
What's going on?
It turns out that the implementation of
dif/3
prevents us from getting a nice answer sequence for the most general query. To do so—without using additional goals forcing fair enumeration—we need a tweaked implementation ofdif/3
, which I calldiffirst/3
:Let's use
diffirst/3
instead ofdif/3
in the definition of predicatesome_dif/2
:So, at long last, here are above queries with the new
some_dif/2
:Query #1 does not terminate, but has the same nice compact answer sequence. Good!
Query #2 is still non-determinstic. Okay. To me this is as good as it gets.
Query #3 has become deterministic: Better now!
The bottom line:
library(reif)
to tame excess non-determinism while preserving logical purity!diffirst/3
should find its way intolibrary(reif)
:)EDIT: more general using a meta-predicate (suggested by a comment; thx!)
Let's generalize
some_dif/2
like so:some/2
can be used with reified predicates other thandiffirst/3
.Here an update to
not_all_equal/1
which now usessome/2
instead ofsome_dif/2
:Above sample queries still give the same answers, so I won't show these here.
Here is a partial implementation using
library(reif)
for SICStus|SWI. It's certainly correct, as it produces an error when it is unable to proceed. But it lacks the generality we'd like to have.Edit: Now I realize that I do not need to add that many
dif/2
goals at all! It suffices that one variable is different to the first one! No need for mutual exclusivity! I still feel a bit insecure to remove thedif(B,C)
goals ...The answers are exactly the same... what is happening here, me thinks. Is this version weaker, that is less consistent?