dd1714
dd1714

Reputation: 139

Prolog: Arguments are not sufficiently instantiated

I have the following problem:

Generate all sub-strings of a length 2*n+1, formed from values of 0, 1 or -1, so a1 = ..., a2n+1 = 0 and |a(i+1) - ai| = 1 or 2, for every 1 <= i <= 2n.

This is what I did:

change(0).
change(1).
change(-1).

%gets the last element from a list
lastE([X],X).
lastE([_|L],X) :-
    last(L,X).

%checks if |N-M|=1 or 2
calc(N,M) :-
    (  1 is abs(N-M)
    ;  2 is abs(N-M),
       !
    ).

%generates all lists of length N with values -1,0,1
generate([],0) :-
   !.
generate([H|T],N):-
    change(H),
    N1 is N-1,
    generate(T,N1).

%validates a list to be correct (last element=0, |a(i+1) - ai| = 1 or 2)
valid(L) :-
   valid(L,_,3).

valid([E],_,_) :-
    lastE([E],0).
valid([H|[H1|T]],_,3) :-
    valid([H1|T],H,H1).
valid([_|[H1|T]],N,M) :-
    calc(N,M),
    valid([H1|T],M,H1).

All of the above code works correctly (I tested it). But with the following code for genAll, I get the Arguments are not sufficiently instantiated error.

genAll(N) :-
    N1 = 2*N,
    N2 = N1+1,
    generate(L1,N2),
    valid(L1),
    write('['),
    printl(L1).

printl([]) :-
    write(']').
printl([0|T]) :-
    write('0 '),
    printl(T).
printl([1|T]) :-
    write('1 '),
    printl(T).
printl([-1|T]) :-
    write('-1 '),
    printl(T).

I am not sure what is wrong.

Upvotes: 3

Views: 769

Answers (1)

repeat
repeat

Reputation: 18726

In this answer (which is mostly guesswork) we use .

:- use_module(library(clpfd)).

n_qfd33721532(N, Zs) :-
   Zs = [E|Es],
   N*2 + 1 #= L,
   length(Zs, L),
   Zs ins -1..1,
   last(Zs, 0),
   chain_neq(Es, E).

chain_neq([], _).
chain_neq([E1|Es], E0) :-
   E0 #\= E1,
   chain_neq(Es, E1).

Sample query:

?- n_qfd33721532(N, Zs), labeling([], Zs).
  N = 0, Zs = [0]
; N = 1, Zs = [-1, 1, 0]
; N = 1, Zs = [ 0,-1, 0]
; N = 1, Zs = [ 0, 1, 0]
; N = 1, Zs = [ 1,-1, 0]
; N = 2, Zs = [-1, 0,-1, 1, 0]
; N = 2, Zs = [-1, 0, 1,-1, 0]
; N = 2, Zs = [-1, 1,-1, 1, 0]
; N = 2, Zs = [-1, 1, 0,-1, 0]
; N = 2, Zs = [-1, 1, 0, 1, 0]
; N = 2, Zs = [ 0,-1, 0,-1, 0]
; N = 2, Zs = [ 0,-1, 0, 1, 0]
; N = 2, Zs = [ 0,-1, 1,-1, 0]
; N = 2, Zs = [ 0, 1,-1, 1, 0]
; N = 2, Zs = [ 0, 1, 0,-1, 0]
; N = 2, Zs = [ 0, 1, 0, 1, 0]
; N = 2, Zs = [ 1,-1, 0,-1, 0]
; N = 2, Zs = [ 1,-1, 0, 1, 0]
; N = 2, Zs = [ 1,-1, 1,-1, 0]
; N = 2, Zs = [ 1, 0,-1, 1, 0]
; N = 2, Zs = [ 1, 0, 1,-1, 0]
; N = 3, Zs = [-1, 0,-1, 0,-1, 1, 0] 
...

Upvotes: 3

Related Questions