Problem in general : we have map 8*8 and we have to fill the empty squares with number from 1 to 6.But in each column and raw number should be met only 1 time.Two squares in each row and column are left empty.Numbers from both sides,up and down show us the first number,that should appear(but it can appear after two empty squares).
So,now i have this code,which finally works on swi-prolog for 4*4 map.
:- module(ab, [ab/0]).
:- [library(clpfd)].
gen_row(Ls):-length(Ls, 4), Ls ins 0..3.
transpose(Ms, Ts) :-
%must_be(list(list), Ms),
( Ms = [] -> Ts = []
; Ms = [F|_],
transpose(F, Ms, Ts)
).
transpose([], _, []).
transpose([_|Rs], Ms, [Ts|Tss]) :-
lists_firsts_rests(Ms, Ts, Ms1),
transpose(Rs, Ms1, Tss).
lists_firsts_rests([], [], []).
lists_firsts_rests([[F|Os]|Rest], [F|Fs], [Os|Oss]) :-
lists_firsts_rests(Rest, Fs, Oss).
ab :-
Rows = [R1,R2,R3,R4],
maplist(gen_row, Rows),
transpose(Rows, [C1,C2,C3,C4]),
maplist(all_distinct, [R1,R2,R3,R4]),
maplist(all_distinct, [C1,C2,C3,C4]),
start(R2, 3),
start(R3, 3),
finish(R3, 2),
start(C3, 1),
finish(C2, 2),
maplist(writeln, [R1,R2,R3,R4]).
finish(X, V) :-
reverse(X, Y),
start(Y, V).
start([0,Y|_], Y).
start([Y|_], Y).
But,it doesn't support the problem with 2 empty places for bigger area,like 8*8 puzzle.Any hint's?
you must get transpose/2 from the other question and replace all_distinct/1 with fd_all_distinct/2.
Also, get writeln and replace write here maplist(write, [R1,R2,R3,R4]).
edit A simple solution would be to extend the 'encoding' of the finite domain, reserving two digits as blanks, instead of just the 0, and extending the logic already seen in answer posted to the other question.
For analogy I'll call third_end_view, and would be (in Gnu Prolog)
/* File: third_end_view_puzzle.pl
Author: Carlo,,,
Created: Oct 10 2012
Purpose: help to solve extended Second End View puzzle
https://stackoverflow.com/q/12797708/874024
*/
:- include(transpose) .
third_end_view_puzzle :-
length(Rows, 8),
maplist(gen_row(8), Rows),
transpose(Rows, Cols),
maplist(fd_all_different, Rows),
maplist(fd_all_different, Cols),
Rows = [R1,R2,R3,R4,R5,R6,R7,R8],
Cols = [C1,C2,C3,C4,C5,C6,C7,C8],
start(R1, 4),
start(R2, 2),
start(R3, 3),
start(R4, 5),
start(R5, 3),
finish(R1, 6),
finish(R2, 4),
finish(R3, 2),
finish(R5, 1),
finish(R7, 2),
start(C2, 3),
start(C3, 4),
start(C4, 3),
start(C5, 5),
% start(C6, 4),
start(C7, 1),
% finish(C1, 3),
% finish(C2, 2),
finish(C3, 5),
finish(C4, 5),
finish(C5, 6),
finish(C6, 1),
finish(C7, 4),
maplist(fd_labeling, Rows),
nl,
maplist(out_row, Rows).
gen_row(N, Ls) :-
length(Ls, N),
fd_domain(Ls, 1, N).
out_row([]) :- nl.
out_row([H|T]) :-
(H >= 7 -> write('-') ; write(H)),
write(' '),
out_row(T).
% constraint: Num is max third in that direction
start(Vars, Num) :-
Vars = [A,B,C|_],
A #= Num #\/ (A #>= 7 #/\ B #= Num) #\/ (A #>= 7 #/\ B #>= 7 #/\ C #= Num).
finish(Var, Num) :-
reverse(Var, Rev), start(Rev, Num).
I have used a simpler condition, without reification, to state the 'third view from direction'.
As previously, you see that some constraint (those commented out) make the puzzle unsolvable.
test:
| ?- third_end_view_puzzle.
4 3 - - 5 2 1 6
2 1 - 3 - 5 6 4
3 5 4 1 - 6 2 -
5 4 6 2 1 3 - -
- - 3 6 2 4 5 1
1 6 2 4 3 - - 5
6 - 1 5 4 - 3 2
- 2 5 - 6 1 4 3
true ?