Skip to content

Instantly share code, notes, and snippets.

@ademar111190
Created August 1, 2012 06:21
Show Gist options
  • Star 1 You must be signed in to star a gist
  • Fork 0 You must be signed in to fork a gist
  • Save ademar111190/3224223 to your computer and use it in GitHub Desktop.
Save ademar111190/3224223 to your computer and use it in GitHub Desktop.
prolog sudoku solver
:- use_module(library(bounds)).
:- use_module(library(clp_distinct)).
suudoku(P) :-
Rows = [R1,R2,R3,R4,R5,R6,R7,R8,R9],
problem(P, Rows),
append_all(Rows, Vars),
vars_in(Vars, 1, 9),
Vars in 1..9,
row_constraint(Rows),
column_constraint(R1, R2, R3, R4, R5, R6, R7, R8, R9),
block_constraint(R1, R2, R3),
block_constraint(R4, R5, R6),
block_constraint(R7, R8, R9),
(labeling([ff], Vars) -> true),
display_rows(Rows).
display_rows([]).
display_rows([[X1,X2,X3,X4,X5,X6,X7,X8,X9]|Rows]) :-
format('~d ~d ~d ~d ~d ~d ~d ~d ~d \n',
[X1,X2,X3,X4,X5,X6,X7,X8,X9]),
display_rows(Rows).
row_constraint([]).
row_constraint([R|Rt]) :-
all_distinct(R),
row_constraint(Rt).
column_constraint([], [], [], [], [], [], [], [], []).
column_constraint([X1|R1], [X2|R2], [X3|R3], [X4|R4], [X5|R5], [X6|R6],
[X7|R7], [X8|R8], [X9|R9]) :-
all_distinct([X1,X2,X3,X4,X5,X6,X7,X8,X9]),
column_constraint(R1, R2, R3, R4, R5, R6, R7, R8, R9).
block_constraint([], [], []).
block_constraint([X1,X2,X3|R1], [X4,X5,X6|R2], [X7,X8,X9|R3]) :-
all_distinct([X1,X2,X3,X4,X5,X6,X7,X8,X9]),
block_constraint(R1, R2, R3).
append_all([], []).
append_all([P|R], X) :-
append(P, Y, X),
append_all(R, Y).
problem(1, P) :- % coloque aqui o sudoku a ser solucionado pode have mais de 1
P=[
[_,_,5,3,_,_,_,_,_],
[8,_,_,_,_,_,_,2,_],
[_,7,_,_,1,_,5,_,_],
[4,_,_,_,_,5,3,_,_],
[_,1,_,_,7,_,_,_,6],
[_,_,3,2,_,_,_,8,_],
[_,6,_,5,_,_,_,_,9],
[_,_,4,_,_,_,_,3,_],
[_,_,_,_,_,9,7,_,_]
].
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment