可以将文章内容翻译成中文,广告屏蔽插件可能会导致该功能失效(如失效,请关闭广告屏蔽插件后再试):
问题:
I have the following code :
size(5).
black(1,3).
black(2,3).
black(3,2).
black(4,3).
black(5,1).
black(5,5).
words([do,ore,ma,lis,ur,as,po, so,pirus, oker,al,adam, ik]) .
:- use_module(library(lists),[nth1/3, select/3]).
crossword(Puzzle) :-
words(WordList),
word2chars(WordList,CharsList),
make_empty_words(EmptyWords) ,
fill_in(CharsList,EmptyWords),
word2chars(Puzzle,EmptyWords).
word2chars([],[]).
word2chars([Word|RestWords] ,[Chars|RestChars] ) :-
atom_chars(Word,Chars),
word2chars(RestWords,RestChars).
fill_in([],[]).
fill_in([Word|RestWords],Puzzle) :-
select(Word,Puzzle,RestPuzzle),
fill_in(RestWords,RestPuzzle).
make_empty_words(EmptyWords) :-
size(Size),
make_puzzle(Size,Puzzle),
findall(black(I,J),black(I,J),Blacks) ,
fillblacks(Blacks,Puzzle),
empty_words(Puzzle,EmptyWords).
make_puzzle(Size,Puzzle) :-
length(Puzzle,Size),
make_lines(Puzzle,Size).
make_lines([],_).
make_lines([L|Ls],Size) :-
length(L,Size),
make_lines(Ls,Size).
fillblacks([],_).
fillblacks([black(I,J)|Blacks],Puzzle) :-
nth1(I,Puzzle,LineI),
nth1(J,LineI,black),
fillblacks(Blacks,Puzzle).
empty_words(Puzzle,EmptyWords) :-
empty_words(Puzzle,EmptyWords,TailEmptyWords),
size(Size),
transpose(Size,Puzzle,[],TransposedPuzzle),
empty_words(TransposedPuzzle,TailEmptyWords,[] ).
empty_words([],Es,Es).
empty_words([L|Ls],Es,EsTail) :-
empty_words_on_one_line(L,Es,Es1) ,
empty_words(Ls,Es1,EsTail).
empty_words_on_one_line([], Tail, Tail).
empty_words_on_one_line([V1,V2|L],[[V1,V2|Vars]|R],Tail) :-
var(V1), var(V2), !,
more_empty(L,RestL,Vars),
empty_words_on_one_line(RestL,R,Tail) .
empty_words_on_one_line([_| RestL],R, Tail) :-
empty_words_on_one_line(RestL,R,Tail) .
more_empty([],[],[]).
more_empty([V|R],RestL,Vars) :-
( var(V) ->
Vars = [V|RestVars],
more_empty(R,RestL,RestVars)
;
RestL = R,
Vars = []
).
transpose(N,Puzzle,Acc,TransposedPuzzle) :-
( N == 0 ->
TransposedPuzzle = Acc
;
nth_elements(N,Puzzle,OneVert),
M is N - 1,
transpose(M,Puzzle,[OneVert|Acc], TransposedPuzzle)
).
nth_elements(_,[],[]).
nth_elements(N,[X|R],[NthX| S]) :-
nth1(N,X,NthX),
nth_elements(N,R,S).
It is used for solving a crossword like this:
The black squares places are given by default in the code but I want to find a way to give the black squares places by input when I want to query crossword.
something like this:
black(Y1,X1).
black(Y2,X2).
black(Y3,X3).
black(Y4,X4).
black(Y5,X5).
black(Y6,X6).
crossword(Puzzle,Y1,X1,Y2,X2,...) :-
words(WordList),
word2chars(WordList,CharsList),
make_empty_words(EmptyWords,Size) ,
fill_in(CharsList,EmptyWords),
word2chars(Puzzle,EmptyWords).
回答1:
As @lurker mentioned I tried rewriting the code and giving the black squares as input to program as below:
:- use_module(library(lists),[nth1/3, select/3]).
crossword(Puzzle,Size,Blacks,WordList) :-
word2chars(WordList,CharsList),
make_empty_words(EmptyWords,Size,Blacks) ,
fill_in(CharsList,EmptyWords),
word2chars(Puzzle,EmptyWords).
word2chars([],[]).
word2chars([Word|RestWords] ,[Chars|RestChars] ) :-
atom_chars(Word,Chars),
word2chars(RestWords,RestChars).
fill_in([],[]).
fill_in([Word|RestWords],Puzzle) :-
select(Word,Puzzle,RestPuzzle),
fill_in(RestWords,RestPuzzle).
make_empty_words(EmptyWords,Size,Blacks) :-
make_puzzle(Size,Puzzle),
fillblacks(Blacks,Puzzle),
empty_words(Puzzle,EmptyWords).
make_puzzle(Size,Puzzle) :-
length(Puzzle,Size),
make_lines(Puzzle,Size).
make_lines([],_).
make_lines([L|Ls],Size) :-
length(L,Size),
make_lines(Ls,Size).
fillblacks([],_).
fillblacks([black(I,J)|Blacks],Puzzle) :-
nth1(I,Puzzle,LineI),
nth1(J,LineI,black),
fillblacks(Blacks,Puzzle).
empty_words(Puzzle,EmptyWords) :-
empty_words(Puzzle,EmptyWords,TailEmptyWords),
transpose(Size,Puzzle,[],TransposedPuzzle),
empty_words(TransposedPuzzle,TailEmptyWords,[] ).
empty_words([],Es,Es).
empty_words([L|Ls],Es,EsTail) :-
empty_words_on_one_line(L,Es,Es1) ,
empty_words(Ls,Es1,EsTail).
empty_words_on_one_line([], Tail, Tail).
empty_words_on_one_line([V1,V2|L],[[V1,V2|Vars]|R],Tail) :-
var(V1), var(V2), !,
more_empty(L,RestL,Vars),
empty_words_on_one_line(RestL,R,Tail) .
empty_words_on_one_line([_| RestL],R, Tail) :-
empty_words_on_one_line(RestL,R,Tail) .
more_empty([],[],[]).
more_empty([V|R],RestL,Vars) :-
( var(V)
-> Vars = [V|RestVars],
more_empty(R,RestL,RestVars)
; RestL = R,
Vars = []
).
transpose(N,Puzzle,Acc,TransposedPuzzle) :-
( N == 0
-> TransposedPuzzle = Acc
; nth_elements(N,Puzzle,OneVert),
M is N - 1,
transpose(M,Puzzle,[OneVert|Acc], TransposedPuzzle)
).
nth_elements(_,[],[]).
nth_elements(N,[X|R],[NthX| S]) :-
nth1(N,X,NthX),
nth_elements(N,R,S).
now by the following input the code returns the answer to the puzzle:
crossword(Puzzle,5,[black(1,3),black(2,3),black(3,2),black(4,3),
black(5,1),black(5,5)],[do,ore,ma,lis,ur,as,pu, so,pirus, uker,al,adam, ik]).
And the output will be:
Puzzle = [as,pu,do,ik,ore,ma,ur,lis,adam,so,al,pirus,uker]
回答2:
Very nice, +1 for solving it yourself.
In addition, I would like to show you how to use DCGs to obtain predicates with fewer arguments for empty_words/2
and its related predicates, which are therefore easier to understand. Further, transpose/2
is already available as a library predicate in SICStus Prolog and SWI (see its source code if you are interested in how it is implemented), so I use that instead. Notice that size/1
is no longer necessary.
:- use_module(library(clpfd)). % for transpose/2 in SWI-Prolog
empty_words(Puzzle,EmptyWords) :-
phrase(empty_words(Puzzle), EmptyWords, RestEmptyWords),
transpose(Puzzle, TransposedPuzzle),
phrase(empty_words(TransposedPuzzle), RestEmptyWords).
empty_words([]) --> [].
empty_words([L|Ls]) --> empty_words_on_one_line(L), empty_words(Ls).
empty_words_on_one_line([]) --> [].
empty_words_on_one_line([V1,V2|Ls0]) -->
{ var(V1), var(V2) }, !,
[[V1,V2|Vars]],
{ more_empty(Ls0, Ls, Vars) },
empty_words_on_one_line(Ls) .
empty_words_on_one_line([_|Ls]) --> empty_words_on_one_line(Ls).
The other predicates remain unchanged.
Your fill_in/2
is available as permutation/2
.
maplist/2
can help you in other places, like:
maplist(length_list(Size), Puzzle)
to replace make_lines/2
with a short definition of length_list/2
that I leave as a simple exercise.