Search code examples
listprologinstantiationswi-prologclpfd

Arguments are not sufficiently instantiated on list sum


I am trying to constraint the sum of a list, but my code fails at label().

.pl:

:- use_module(library(clpfd)).

solve(L, Dim) :-
    length(L, 5), % define 5 diagonals
    SkipVars is Dim - 2, % to skip variables
    init_sublists_above_center(L, Dim, SkipVars),
    init_center(L, 2, Dim),
    init_sublists_below_center(L, 3, Dim, 1),
    flatten(L, FlatL),
    collect_vars(FlatL, _),
    writeln("list="+L),
    constraint_sum(L, 38).

collect_vars([], NewL):-
    all_different(NewL).
collect_vars([H|T], NewL) :-
    H == 0,
    collect_vars(T, NewL).
collect_vars([H|T], NewL) :-
    append(NewL, [H], NewestL),
    collect_vars(T, NewestL).

constraint_sum([], _).
constraint_sum([H|T], Sum) :-
    writeln(H),
    label(H),
    sum_list(H, Sum),
    constraint_sum(T, Sum). 

init_sublists_above_center([H|T], Dim, SkipVars) :-
    length(H, Dim),
    init_zeroes(H, SkipVars),
    NewSkipVars is SkipVars + 1,
    NewSkipVars =< Dim,
    init_sublists_above_center(T, Dim, NewSkipVars).
init_sublists_above_center(_, _, _).

init_sublists_below_center(_, _, Dim, Fill) :-
    End is Dim - 2,
    Fill == End.
init_sublists_below_center([H|T], ToSkip, Dim, Fill) :-
    ToSkip == 0,
    length(H, Dim),
    init_zeroes_start(H, Fill),
    NewFill is Fill + 1,
    init_sublists_below_center(T, 0, Dim, NewFill).
init_sublists_below_center([_|T], ToSkip, Dim, Fill) :-
    NewToSkip is ToSkip - 1,
    init_sublists_below_center(T, NewToSkip, Dim, Fill).

init_center(_, ToSkip, _) :-
    ToSkip == -1.
init_center([H|_], ToSkip, Dim) :-
    ToSkip == 0,
    length(H, Dim),
    init_center(_, -1, _).

init_center([_|T], ToSkip, Dim) :-
    NewToSkip is ToSkip - 1,
    init_center(T, NewToSkip, Dim).

init_zeroes([], _).
init_zeroes([H|T], Fill) :-
    Fill == 0,
    H is 0,
    init_zeroes(T, Fill).
init_zeroes([_|T], Fill) :-
    NewFill is Fill - 1,
    init_zeroes(T, NewFill).

init_zeroes_start(_, Fill) :-
    Fill == 0.
init_zeroes_start([H|T], Fill) :-
    H is 0,
    NewFill is Fill - 1,
    init_zeroes_start(T, NewFill).

Output:

7 ?- solve(L, 5).
list= + [[_G15351,_G15407,_G15466,0,0],[_G15525,_G15584,_G15643,_G15702,0],[_G15761,_G15820,_G15879,_G15938,_G15997],[0,_G16056,_G16115,_G16174,_G16233],[0,0,_G16292,_G16351,_G16410]]
[_G15351,_G15407,_G15466,0,0]
ERROR: Arguments are not sufficiently instantiated

Any ideas please?


EDIT:

After running the debugger:, I think that the error is inside label(), at this point:

finite_domain(Var) :-
        (   fd_get(Var, Dom, _) ->
            (   domain_infimum(Dom, n(_)), domain_supremum(Dom, n(_)) -> true
            ;   instantiation_error(Var)
            )
        ;   integer(Var) -> true
        ;   must_be(integer, Var)
        ).

Solution

  • Use the graphical debugger to step through your code:

    ?- gtrace, solve(L, 5).
    

    As you will see, label/1 has nothing whatsoever to do with this error.

    Instead of sum_list/2, use the CLP(FD) constraint sum/3: It works in all directions and lets you see answers for your query.

    That being said, I recommend you take a huge step back and really consider what you are doing here.

    For example, why are you mixing side-effects (write/1) with pure code? Focus on a clear declarative description of the problem, and let the toplevel do the reporting for you.

    Also, it is highly unusual to need extra-logical predicates like (==)/2 so frequently. For example, write:

    sublists_below_center(_, _, Dim, End) :-
        End #= Dim - 2.
    

    to make the relation between the arguments perfectly clear without resorting to extra-logical language elements.

    Using flatten/2 is almost always a bad idea and typically indicates a problem in your data structure design. Use append/2 to remove one level of nesting.

    Why are you still using primitive arithmetic if you are already importing the CLP(FD) library? Use (#=)/2 etc. throughout.

    Also your predicate names indicate that you are thinking way too imperatively about your problem. Focus on a pure declarative description of what a solution of your problem looks like, and Prolog will do the rest for you. Avoid imperative names. Instead, use names that describe what holds under what conditions.