Reputation: 3318
I want to use the results from "extract" (W) in valid_seq which is then use in valid_columns.
I have tried this so far, but it does not work:
extract(_,[],[]).
extract(K,[X|Y],[H|L]) :- nth1(K,X,H), extract(K,Y,L).
valid_columns([],[]).
valid_columns([H|L],[X|Y],K) :- b_w(X),
extract(K,X,W),
valid_seq(H,W),
K1 is K+1,
valid_columns(L,Y,K1).
EDIT:
I am trying to solve a nonogram. So from each list of lines, I have to extract the columns to validate them. This is the function "extract"
Once the columns are extracted I need to validate them. Ex
valid_column([[1,1,1,1,1],[1,0,0,0,0],[1,1,1,1,1],[0,0,0,0,1],[1,1,1,1,1]],[3,1],1).
false.
Here I am asking if the first value in each [] complies to [3,1]. In this case should be true. As I have [1 1 1 0 1].
And this is my code:
test_cst(0,[0|S],S).
test_cst(0,[],[]).
test_cst(N,[1|T],S):-
N1 is N-1,
test_cst(N1,T,S).
valid_seq([],[]).
valid_seq(L,[0|T]):-valid_seq(L,T).
valid_seq([H|L],[1|T]):-test_cst(H,[1|T],S),valid_seq(L,S).
b_w([]).
b_w([H|L]) :- H is 0, b_w(L);H is 1, b_w(L).
valid_lines([],[]).
valid_lines([H|L],[X|Y]) :- b_w(X),
valid_seq(H,X),
valid_lines(L,Y).
extract(_,[],[]).
extract(K,[X|Y],[H|L]) :- nth1(K,X,H), extract(K,Y,L).
valid_columns([],_,_).
valid_columns([H|L],X,K) :- valid_column(X,H,K),
K1 is K+1,
valid_columns(L,X,K1).
valid_column(X,H,K) :- b_w(X),
extract(K,X,W),
valid_seq(H,W).
Upvotes: 0
Views: 264
Reputation: 60034
If available, you can put library(apply) to good use:
?- maplist(nth1(I), [[a,b,c],[1,2,3],[x,y,z]], X).
I = 1,
X = [a, 1, x] ;
...
I'm suggesting its usage since it simplifies the code, removing irrelevant details, that blurry your relations.
For your question, you're passing to b_w/1 a list of lists, while it should be a list. If you have library(yall) available, b_w/1 can be rewritten like
b_w(L) :- maplist([X]>>(X=0;X=1), L).
Upvotes: 1