Non-branching version of 'bagof'

103 Views Asked by At

I'm trying to implement a sudoku-like puzzle solver that involves groups in prolog, and where one of the rules is that the same value cannot be repeated in the same group. My code 'works', but it ends up 'splitting into two branches':

:- use_module(library(clpfd)).

solve(Input) :-
    append(Input, Items),
    bagof(V, member(G-V, Items), Group),
    length(Group, Len),
    Group ins 1..Len,
    all_distinct(Group).

input(I) :- I = [
    [a-1, b-_],
    [a-_, b-1]
].

?- input(I), solve(I)
I = [[a-1, b-_], [a-2, b-1]] ;
I = [[a-1, b-2], [a-_, b-1]].

Ideally with this example I'd want it to return a single I value with all values filled, but I'm at a loss as to what's even happening. Why is it branching like this? What should I try to do so it doesn't branch?

Edit: I've changed all values to use 'X-Y' format. Also, here's a more complex example of what I want to achieve:

input(I) :- I = [[a-1, b-_, b-2],
                 [a-_, c-_, b-1],
                 [a-2, a-4, b-3]].

?- input(I), solve(I).
I = [[a-1, b-4, b-2],
     [a-3, c-1, b-1],
     [a-2, a-4, b-3]].

The current algorithm correctly solves for each group, but in a different branch each.

2

There are 2 best solutions below

2
notoria On BEST ANSWER

This should do the trick:

input(I) :- I = [
    [a-1, b-_],
    [a-_, b-1]
].
input(I) :- I = [[a-1, b-_, b-2],
                 [a-_, c-_, b-1],
                 [a-2, a-4, b-3]].

solve(Input) :-
    append(Input, Items),
    findall(ID, member(ID-_, Items), IDs),
    \+ (member(ID, IDs), \+ ground(ID), throw(error(instatiation_error,solve/1))),
    bagof(
        ID-Group-Len,
        (   member(ID, IDs),
            bagof(V, member(ID-V, Items), Group),
            length(Group, Len)
        ),
        Groups
    ),
    maplist(constraints, Groups).

constraints(_-Group-Len) :-
    Group ins 1..Len,
    all_distinct(Group).

But if the ID isn't ground (contains a variable) then it will throw an exception.

9
false On

First, whenever you are loading a Prolog file, read the warnings listed. Practically all systems (Scryer, SICStus, SWI) warn you about a singleton variable G. And in fact, that is your direct problem:

?- input(I), append(I,Items), bagof(V, member((G, V), Items), Group).
   I = [[(a,1),(b,_A)],[(a,_B),(b,1)]],
   Items = [(a,1),(b,_A),(a,_B),(b,1)],
   G = a, Group = [1,_B]
;  I = [[(a,1),(b,_A)],[(a,_B),(b,1)]],
   Items = [(a,1),(b,_A),(a,_B),(b,1)],
   G = b, Group = [_A,1].

So bagof/3 has two answers, once for G = a and the other for G = b. But you are not interested in this variable. So instead, quantify that variable accordingly.

?- input(I), append(I,Items), bagof(V, G^member((G, V), Items), Group).
   I = [[(a,1),(b,_A)],[(a,_B),(b,1)]],
   Items = [(a,1),(b,_A),(a,_B),(b,1)],
   Group = [1,_A,_B,1].

In general, there are four remarks:

  1. Mixing constraints and bagof/3 or for that matter setof/3 does not work in general. In your case you had quite some luck because at the point in time of executing bagof, there wasn't any constraint yet. But generally, prefer direct definitions like maplist/3 instead. In fact with library(lambda) you could write
..., maplist(\ (_,V)^V^true, Items, Group), ...
  1. It is more common in Prolog to use a minus for pairs than this comma. Thus [a-1,b-2] in place of [(a,1),(b,2)].

  2. In programs using finite domain constrains the part responsible for modeling (the core relation) is often separated from the actual search part (the labeling part). Currently, there is no labeling part in your program at all. So you cannot be sure if what you got is true or not.

  3. On the one hand you want that all second arguments of your pairs are distinct, but then you are stating that two of them should be 1. This cannot be true.