Search code examples
prologclpfdfailure-sliceprolog-dif

How to prevent duplicates in generated sequences by using dif/2?


This question came up while answering another question on StackOverflow on (generalizing a bit) generating all sequences formed out of a finite set of elements with no duplicate occurrences.

As Boris rightly indicated in the comments, there are many existing solutions to this problem. However, I am interested in a solution that does not use an accumulator (i.e., a list of already picked elements against which a newly selected element is to be compared) but that uses dif/2 statements instead.

To illustrate, in my following program I have 4 elements and, after 4 recursive calls, a couple of div/2 statements which state that the 4 elements that have been chosen until now are pairswise dissimilar. From this one can deduce that it makes no sense to continue the recursion and look for a fifth element, since there are no elements left given the div/2 statements. Is there a way to encode this 'knowledge' into the program so that it no longer loops?

:- use_module(library(apply)).
:- use_module(library(dif)).

sequences([]).
sequences([H|T]):-
  maplist(dif(H), T),
  between(1, 4, H),
  sequences(T).

Current, looping behavior:

?- sequences(X).
X = [] ;
X = [1] ;
...
X = [4, 3, 1, 2] ;
X = [4, 3, 2, 1] ;
<LOOP>

Solution

  • Tiny issue to start with — the name: sequences/1 suggests a list of sequences (whatever a sequence is), it should be rather sequence/1.

    You are demanding quite a lot of a poor Prolog system: You are demanding stronger consistency. At any price, I presume.

    My immediate reactio (use library(clpfd)!) does not work, let's see why

    ?- length(Xs,N),Xs ins 1..4, all_distinct(Xs).
    

    It loops just as much as your version, which can be best seen with this :

    ?- length(Xs,N), false, Xs ins 1..4, all_distinct(Xs).
    

    So already length/2 alone is wrong. Maybe I reiterate to your program, and try to identify why your program does not terminate:

    sequences([]) :- false.
    sequences([H|T]):-
      maplist(dif(H), T), false
      between(1, 4, H),
      sequences(T).
    
    ?- sequences(X), false.
    

    Our dearest declarative poster child maplist/2 caught in flagranti! OK, maybe we should not be that harsh. After all, honest non-termination of a predicate is always preferable to an unscrupulously unsound or incomplete hack.

    What we need to understand is that all_distinct/1 requires the length of the list to be known, and all domains must be present, too.

    sequence(Xs) :-
       sequence_aux(Xs, []).
    
    sequence_aux([], _).
    sequence_aux([X|Xs], Ys) :-
       X in 1..4,
       all_distinct([X|Ys]),
       sequence_aux(Xs, [X|Ys]).
    
     ?- sequence(X). 
    

    Now terminates.

    @mat may note that all_distinct([_]) might be removed. Maybe even more than that.

    If you do not like this solution because it uses an extra argument, you will need to implement a safer maplist/2.

    fmaplist(C_1, Xs) :-
        freeze(Xs, fmaplist_aux(C_1, Xs)).
    
    fmaplist_aux(_C_1, []).
    fmaplist_aux(C_1, [X|Xs]) :-
       call(C_1, X),
       freeze(Xs, fmaplist_aux(C_1, Xs)).
    

    Now you can use your original program verbatim. But I do not feel very good at it. Understanding the precise borders of non-termination in a program with freeze is much more difficult.


    As an aside: you might try to get correct variable names in SWI for answer substitutions because the _G772-like numbering does not permit to re-paste an answer back into the toplevel shell and get correct results.