Search code examples
prologbacktrackingsudokuclpfd

Non-branching version of 'bagof'


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.


Solution

  • 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.