2

So I have a predicate:

compatible([],_).
compatible(_,[]).
compatible([HA|TA],[HB|TB]) :-
    HA \= HB,
    compatible(TA,TB).

It currently takes two lists and determines if they are pairwise compatible returning true if so and false if not.

For example:

?- compatible([8,2,6,3,67],[7,4,7,4,3]).
true 

?- compatible([8,2,6,3,3],[7,4,7,4,3]).
false.

The 2nd call returned false because a 3 was in the 5th position of both lists.

My question is how can I modify this predicate so it recursively checks more than 2 lists. Potentially, the predicate could check a list of lists that contains 1,2,3,4,5 or perhaps even infinite lists. It would return false if any of the lists weren't compatible with one another.

Therefore I could check 3 lists like so:

let Y = [[8,2,6,3,67],[7,4,7,4,3],[1,3,42,1,52]]
then...

?- compatible(Y).
true 

let Z = [[8,2,6,3,67],[7,4,7,4,3],[1,3,6,1,52]]
then...

?- compatible(Z).
false.

where the 2nd call fails because a 6 was in the 3rd position of list 1 and 3.

sanic
  • 2,065
  • 4
  • 20
  • 33
  • 1
    And now a more important question: are you only going to work with numbers (integers)? Or can the elements of the lists be other Prolog terms? And what Prolog are you using? (I am asking because I cannot recognize the `let Y = ...` syntax) –  Oct 09 '15 at 06:21
  • these are just ints, and it's SWI-Prolog, the "let Y=" was just pseudo code to represent the list. Thank you for helping solve the problem! – sanic Oct 09 '15 at 06:46

3 Answers3

5

If all the sublists are of the same length, and if the elements are always integers, you can define your problem in terms of two predicates provided by library(clpfd):

compatible(Ls) :-
    transpose(Ls, T),
    maplist(all_different, T).

With this definition, your examples:

?- compatible([[8,2,6,3,67],[7,4,7,4,3],[1,3,42,1,52]]).
true.

?- compatible([[8,2,6,3,67],[7,4,7,4,3],[1,3,6,1,52]]).
false.

If the sublists can have different lengths, you should first find the shortest, and cut the rest to that length.

If the elements of the lists can be arbitrary Prolog terms, take a look at this question. In short:

all_different_terms([]).
all_different_terms([H|T]) :-
    maplist(dif(H), T),
    all_different_terms(T).

Note the use of dif/2 instead of \=/2.

?- compatible_terms([[a,b,c],[d,e,f],[g,h,i]]).
true.

?- compatible_terms([[a,b,c],[d,e,f],[a,h,i]]).
false.

The definition of all_different_terms/1 should also give you an idea how to implement your initial suggestion, reusing the predicate compatible/2 that you have already defined:

all_compatible([]).
all_compatible([H|T]) :-
    maplist(compatible(H), T),
    all_compatible(T).
Community
  • 1
  • 1
  • I really appreciate both you and "user27815", you both have finally solved my week long problem! Thank you! – sanic Oct 09 '15 at 06:44
  • 3
    @jankyCoder I strongly recommend to you to compare transpose+all_different to a manually coded recursion. It is never a good idea to write more code if you can write less code :) –  Oct 09 '15 at 06:47
  • 1
    @jankyCoder My question, "why do you _insist_ on writing a recursive predicate" still stands. Is it somehow a requirement? –  Oct 09 '15 at 06:48
  • I guess I thought it was the best way to approach this but I'm rather new at Prolog so it was just a best guess. I have been enlightened! – sanic Oct 09 '15 at 06:51
  • 2
    @jankyCoder I really don't think there is ever a "best" way to do anything (unless you are a Pythonista, of course). But as I was saying, writing less is nice, because it takes less time and you have less opportunities to make silly mistakes. –  Oct 09 '15 at 06:55
  • @jankyCoder Since the accepted answer shows a somewhat questionable solution, please take a look at the bottom of my answer: I have added a more "idiomatic" Prolog solution that does what you seem to have been after initially. –  Oct 09 '15 at 11:26
4

Writing recursive Prolog code can be a good exercise, a lot of fun, a rewarding activity, but getting the nitty-gritty details of recursion right can be hard, particularly for novices!

Luckily, there's another way; one that can lift you up to a higher-level, to a more idiomatic way of logic programming, which immediately enables you to do lots of things.

For your "pairwise compatibility" problem, consider using pairwise/2 in combination with that compatible/1 predicate you already have! Here's how:

?- pairwise(compatible, [[8,2,6,3,67],[7,4,7,4,3],[1,3, 6,1,52]]).
false.                               % finite failure, as expected

?- pairwise(compatible, [[8,2,6,3,67],[7,4,7,4,3],[1,3,42,1,52]]).
  true                               % succeeds, as expected
; true                               % (1st redundant answer)
; true                               % (2nd redundant answer)
; true                               % (3rd redundant answer)
; true                               % (4th redundant answer)
; true                               % (5th redundant answer)
; true                               % (6th redundant answer)
; true.                              % (7th redundant answer)

Edit

Good news first: Both above answers are correct! So what does "redundant answers" mean? Are they good? Bad? If so, how bad? How come? And, how can we cope? Let's find out!

  1. Redundant answers are bad and should be disposed of. They are quite common, too.

  2. Redundant answers are not as bad as, say, "losing declarative semantics".

  3. Redundant answers are worse than "useless choicepoints left behind after all answers have been found". For details on that issue look at the explanations given in this answer.

  4. How come? To answer that question, we consider the definition of compatible/1:

    compatible([],_).
    compatible(_,[]).
    compatible([HA|TA],[HB|TB]) :-
        dif(HA,HB),                  % unlike `(\=)/2`, `dif/2` is sound
        compatible(TA,TB).
    

    The two culprit clauses are highlighted. With common-place first argument indexing (and above definition), Prolog is not able to infer that some goals can succeed deterministically.

  5. Can we cope? And, if so, how? Procedural problem—procedural solution, right?! Yes, but we need to choose the wise path lest we trade in declarative semantics for some mere finite speedup—like many quick fixes based on meta-logical Prolog predicates would.

    As luck would have it, we can call first argument indexing to the rescue!

    compatible([],_).
    compatible([X|Xs],Ys) :-
       compatible_(Ys,X,Xs).
    
    compatible_([],_,_).
    compatible_([Y|Ys],X,Xs) :-
       dif(X,Y),
       compatible(Xs,Ys).
    
  6. Better now? Let's run above queries with the improved definition of compatible/1:

    ?- pairwise(compatible, [[8,2,6,3,67],[7,4,7,4,3],[1,3, 6,1,52]]).
    false.                           %  SAME : finitely fails
    
    ?- pairwise(compatible, [[8,2,6,3,67],[7,4,7,4,3],[1,3,42,1,52]]).
    true.                            % BETTER: succeeds deterministically
    
Community
  • 1
  • 1
repeat
  • 18,496
  • 4
  • 54
  • 166
1

This is a non recursive way of doing it.

compatible([],_).
compatible(_,[]).
compatible([HA|TA],[HB|TB]) :-
  HA \= HB,
  compatible(TA,TB).

pairs(ListOfLists,One,Two):-
  select(One,ListOfLists,L1),
  select(Two,L1,L2).

test(ListOfLists):-
   forall(pairs(ListOfLists,A,B),compatible(A,B)).

Otherwise:

compatible([],_).
compatible(_,[]).
compatible([HA|TA],[HB|TB]) :-
  HA \= HB,
  compatible(TA,TB).

compatible_one_many(_,[]).
compatible_one_many(One,Many):-
  Many=[H|T],
  compatible(One,H),
  compatible_one_many(One,T).


test_recursive([]).
test_recursive(ListOfLists):-
  ListOfLists=[H|T],
  compatible_one_many(H,T),
  test_recursive(T).

You use test/2 and test_recursive/2 to check your list of lists are compatible.

user27815
  • 4,767
  • 14
  • 28
  • 2
    pairs/3 returns the same lists swapped: it's (uselessly) O^2. And the question contains the statement "or perhaps even infinite lists." – CapelliC Oct 09 '15 at 06:54
  • 1
    @CapelliC The "perhaps even infinite lists" cannot be well-thought out requirement, don't you think? I might be wrong but with infinitely many lists, you can never conclusively know that the lists are compatible, only that they are **not**. And I wonder how one would use a _predicate_ that goes on forever, as long as the infinitely many lists are compatible: in a separate thread? –  Oct 09 '15 at 06:58
  • 1
    If you want to avoid the problem that @CapelliC mentioned WRT the unnecessary O^2 complexity of your `pairs/3`, take a look at the definition of `all_different_terms/1` in my answer: you can use the same skeleton to write a predicate `all_compatible/1`, simply using `compatible/2` instead of `dif/2`. –  Oct 09 '15 at 07:20
  • I see pairs/3 is not perfect in this case. – user27815 Oct 09 '15 at 13:43