sudoku and for
This commit is contained in:
79
library/gecode/clp_examples/sudoku.yap
Normal file
79
library/gecode/clp_examples/sudoku.yap
Normal file
@@ -0,0 +1,79 @@
|
||||
|
||||
|
||||
:- style_check(all).
|
||||
|
||||
:- use_module(library(gecode/clpfd)).
|
||||
:- use_module(library(maplist)).
|
||||
|
||||
|
||||
sudoku( Ex ) :-
|
||||
problem(Ex, Els),
|
||||
output(Els).
|
||||
|
||||
%
|
||||
% gecode constraints
|
||||
%
|
||||
problem(Ex, Els) :- ex(Ex, Exs),
|
||||
length(Els, 81),
|
||||
Els ins 1..9,
|
||||
M <== matrix( Els, [dim=[9,9]] ),
|
||||
% select rows
|
||||
for( I in 0..8 , all_different(M[I,*]) ),
|
||||
% select cols
|
||||
for( J in 0..8, all_different(M[*,J]) ),
|
||||
% select squares
|
||||
for( [I,J] ins 0..2 ,
|
||||
all_different(M[I*3+(0..2),J*3+(0..2)]) ),
|
||||
ex(Ex, Exs),
|
||||
maplist( bound, Els, Exs),
|
||||
labeling( [], Els ).
|
||||
|
||||
|
||||
% The gecode interface doesn't support wake-ups on binding constained variables, this is the closest.
|
||||
%
|
||||
bound(El, X) :-
|
||||
( nonvar(X) -> El #= X ; true ).
|
||||
|
||||
%
|
||||
% output using matrix library
|
||||
%
|
||||
output(Els) :-
|
||||
M <== matrix( Els, [dim=[9,9]] ),
|
||||
for( I in 0..2 , output(M, I) ),
|
||||
output_line.
|
||||
|
||||
output(M, I) :-
|
||||
output_line,
|
||||
for( J in 0..2 , output_row(M, J+I*3) ).
|
||||
|
||||
output_row( M, Row ) :-
|
||||
L <== M[Row,_],
|
||||
format('| ~d ~d ~d | ~d ~d ~d | ~d ~d ~d |~n', L).
|
||||
|
||||
output_line :-
|
||||
format(' ~|~`-t~24+~n', []).
|
||||
|
||||
ex( 1, [
|
||||
_,6,_,1,_,4,_,5,_,
|
||||
_,_,8,3,_,5,6,_,_,
|
||||
2,_,_,_,_,_,_,_,1,
|
||||
8,_,_,4,_,7,_,_,6,
|
||||
_,_,6,_,_,_,3,_,_,
|
||||
7,_,_,9,_,1,_,_,4,
|
||||
5,_,_,_,_,_,_,_,2,
|
||||
_,_,7,2,_,6,9,_,_,
|
||||
_,4,_,5,_,8,_,7,_
|
||||
] ).
|
||||
|
||||
|
||||
ex(2, [
|
||||
_,_,1,_,8,_,6,_,4,
|
||||
_,3,7,6,_,_,_,_,_,
|
||||
5,_,_,_,_,_,_,_,_,
|
||||
_,_,_,_,_,5,_,_,_,
|
||||
_,_,6,_,1,_,8,_,_,
|
||||
_,_,_,4,_,_,_,_,_,
|
||||
_,_,_,_,_,_,_,_,3,
|
||||
_,_,_,_,_,7,5,2,_,
|
||||
8,_,2,_,9,_,7,_,_
|
||||
] ).
|
@@ -1,20 +1,48 @@
|
||||
|
||||
:- style_check( all ).
|
||||
|
||||
:- use_module(library(gecode/clpfd)).
|
||||
:- use_module(library(maplist)).
|
||||
|
||||
t0 :-
|
||||
test0(X),
|
||||
writeln(X).
|
||||
|
||||
test0(X) :-
|
||||
X in 1..10,
|
||||
X #= 2.
|
||||
|
||||
t1 :-
|
||||
test1(X),
|
||||
writeln(X),
|
||||
fail.
|
||||
t1.
|
||||
|
||||
test1(X) :-
|
||||
X in 1..10,
|
||||
Y in 3..7,
|
||||
Z in 1..4,
|
||||
X / Y #= Z,
|
||||
labeling([], [X]).
|
||||
|
||||
t2 :-
|
||||
test2(X),
|
||||
writeln(X),
|
||||
fail.
|
||||
t2.
|
||||
|
||||
test2(X) :-
|
||||
X in 1..10,
|
||||
X / 4 #= 2,
|
||||
labeling([], [X]).
|
||||
|
||||
t3 :-
|
||||
test3(X),
|
||||
writeln(X),
|
||||
fail.
|
||||
t3.
|
||||
|
||||
|
||||
test3(A) :-
|
||||
A = [X,Y,Z],
|
||||
A ins 1..4,
|
||||
@@ -22,6 +50,13 @@ test3(A) :-
|
||||
lex_chain(A),
|
||||
all_different(A),
|
||||
labeling([], [X,Y,Z]).
|
||||
|
||||
t4 :-
|
||||
test4(X),
|
||||
writeln(X),
|
||||
fail.
|
||||
t4.
|
||||
|
||||
test4(A) :-
|
||||
A = [X,Y,Z],
|
||||
A ins 1..4,
|
||||
@@ -31,12 +66,26 @@ test4(A) :-
|
||||
min(A, 1),
|
||||
all_different(A),
|
||||
labeling([], [X,Y,Z]).
|
||||
|
||||
t5 :-
|
||||
test5(X),
|
||||
writeln(X),
|
||||
fail.
|
||||
t5.
|
||||
|
||||
test5(A) :-
|
||||
A = [X,Y,Z],
|
||||
A ins 0..1,
|
||||
in_relation( A, [[0,0,0],[0,1,0],[1,0,0]] ),
|
||||
X #> 0,
|
||||
labeling([], A).
|
||||
|
||||
t6 :-
|
||||
test6(X),
|
||||
writeln(X),
|
||||
fail.
|
||||
t6.
|
||||
|
||||
test6(A+B) :-
|
||||
A = [X,Y,Z],
|
||||
B = [X1,Y1,Z1],
|
||||
@@ -50,12 +99,27 @@ test6(A+B) :-
|
||||
Y1 #\= Z1,
|
||||
labeling([], A),
|
||||
labeling([], B).
|
||||
|
||||
t7 :-
|
||||
test7(X),
|
||||
writeln(X),
|
||||
fail.
|
||||
t7.
|
||||
|
||||
test7(A) :-
|
||||
A = [X,Y,Z],
|
||||
A ins 0..1,
|
||||
in_dfa( A, 0, [t(0,0,0),t(0,1,1),t(1,0,0),t(-1,0,0)], [0]),
|
||||
X #> 0,
|
||||
labeling([], A).
|
||||
|
||||
t8 :-
|
||||
test8(X),
|
||||
writeln(X),
|
||||
fail.
|
||||
t8.
|
||||
|
||||
|
||||
test8(A+B) :-
|
||||
A = [X,Y,Z,W],
|
||||
B = [X1,Y1,Z1,W1],
|
||||
|
Reference in New Issue
Block a user