Skip to content

Instantly share code, notes, and snippets.

@kevinyang372
Last active January 29, 2020 07:38
Show Gist options
  • Save kevinyang372/2d063324ef0cfcaefba3225c75770795 to your computer and use it in GitHub Desktop.
Save kevinyang372/2d063324ef0cfcaefba3225c75770795 to your computer and use it in GitHub Desktop.
N*N Sudoku solver
read -d '' Program <<EOF
% Prolog Sudoku Solver (C) 2007 Markus Triska (triska@gmx.at)
% Modified by Yunfan Yang.
% Public domain code.
% We need this module to use some of the constraint programming extensions to Prolog
:- use_module(library(clpfd)).
% Pss is a list of lists representing the game board.
sudoku(Pss, Dimension) :-
length(Pss, L),
flatten(Pss, Ps), %breaks down inner structure
K is Dimension^2,
Ps ins 1..K, %checks if in range
maplist(all_distinct, Pss), % finding if all values are unique in each row
columns(Pss, L), % finding if all values are unique in each column
blocks(Pss, Dimension), % finding if all values are unique in each block
label(Ps).
% rowN gets the Nth element in row
rowN([H|_],1,H):-!.
rowN([_|T],I,X) :-
I1 is I-1,
rowN(T,I1,X).
% columnN gets the Nth column
columnN([],_,[]).
columnN([H|T], I, [R|X]):-
rowN(H, I, R),
columnN(T, I, X).
% check whether columns have distinct numbers
columns(_, 0).
columns(A, N) :-
columnN(A, N, X),
all_distinct(X),
K is N - 1,
columns(A, K).
% split array into N parts
part([], _, []).
part(L, N, [DL|DLTail]) :-
length(DL, N),
append(DL, LTail, L),
part(LTail, N, DLTail).
% check whether blocks have distinct numbers
blocks(A, Dimension) :-
part(A, Dimension, NX),
check(NX, Dimension, X),
maplist(all_distinct, X).
% get and concatenate N row blocks
check([], _, []).
check([Head|Tail], Dimension, F) :-
append(NX, X, F),
vertical(Head, Dimension, 1, NX),
check(Tail, Dimension, X).
% get and concatenate N column blocks
vertical(_, Dimension, I, []) :-
I > Dimension * Dimension, !.
vertical(A, Dimension, I, X) :-
s(A, 0, I, Dimension, NX),
append([NX], F, X),
Next is I + Dimension,
vertical(A, Dimension, Next, F).
% slice into N * N dimension blocks
s(_, Dimension, _, Dimension, []).
s(A, C, I, Dimension, X) :-
Index is I + C,
columnN(A, Index, NX),
append(NX, Base, X),
Next is C + 1,
s(A, Next, I, Dimension, Base).
problem(1, [[_,_,5, _,_,7, _,_,2],
[_,7,_, _,8,_, _,4,_],
[8,_,_, 1,_,_, 3,_,_],
[6,_,_, 9,_,_, 5,_,_],
[_,9,_, _,3,_, _,8,_],
[_,_,3, _,_,8, _,_,6],
[_,_,4, _,_,1, _,_,8],
[_,3,_, _,5,_, _,7,_],
[1,_,_, 3,_,_, 6,_,_]]).
problem(2, [[23,_,_,_,7,_,_,1,_,_,2,14,_,_,13,20,_,_,_,6,_,11,16,15,17],
[2,_,18,_,_,25,_,16,_,17,_,_,20,5,6,_,22,4,_,8,_,_,9,_,23],
[_,19,_,_,_,10,21,9,_,_,_,22,1,_,8,_,11,_,_,_,_,_,3,_,2],
[_,_,_,12,8,_,18,_,13,2,_,11,_,_,17,_,21,10,_,_,19,20,5,_,24],
[25,_,16,15,_,_,20,_,_,_,10,_,_,7,23,3,18,_,_,_,_,1,_,8,4],
[7,_,_,21,9,8,_,22,1,12,13,2,14,18,_,19,_,6,_,_,17,25,_,_,15],
[_,2,_,_,3,17,_,_,16,_,6,_,_,20,_,22,4,_,_,12,_,_,_,_,7],
[_,24,_,20,5,23,_,_,9,_,8,_,_,_,12,_,_,17,16,15,_,14,18,3,13],
[8,4,_,1,12,_,_,18,_,_,_,25,11,_,15,21,_,23,_,7,24,19,20,5,6],
[17,_,_,_,15,24,19,_,5,6,23,_,21,9,_,18,14,_,_,_,_,_,1,_,_],
[_,_,23,10,21,12,8,_,22,1,_,13,_,14,18,_,_,5,19,_,_,17,_,_,_],
[_,_,_,14,18,15,_,25,11,_,5,6,_,19,_,4,_,12,22,1,7,23,10,_,9],
[5,6,24,_,20,7,_,_,21,_,_,8,4,_,_,_,_,15,_,16,_,_,14,_,3],
[12,8,_,_,_,13,_,14,_,3,15,17,_,11,16,_,23,_,21,9,6,24,19,20,5],
[15,17,25,_,16,6,24,_,_,5,7,23,_,_,9,_,_,13,_,_,_,_,_,_,12],
[_,21,_,7,_,_,1,_,8,4,_,18,_,_,_,_,20,19,_,24,11,16,15,17,_],
[_,_,_,_,_,_,16,15,_,25,_,20,_,6,24,_,_,_,_,4,_,9,_,23,10],
[19,20,_,_,24,_,9,_,_,10,22,_,12,8,_,_,_,11,_,_,18,3,_,_,_],
[22,1,12,_,_,_,_,13,2,14,_,_,_,17,25,_,9,_,23,_,_,_,6,_,19],
[_,16,_,17,_,_,5,6,_,19,_,_,7,23,10,13,_,18,2,_,1,_,8,_,_],
[21,9,_,_,10,1,12,_,_,_,_,_,13,2,14,_,5,_,24,_,_,15,_,_,11],
[18,3,13,2,_,_,15,17,_,11,20,5,6,24,19,_,_,1,_,_,9,7,23,_,_],
[20,_,_,_,_,_,7,23,10,_,_,_,_,4,22,_,15,16,25,11,_,13,2,_,_],
[1,12,8,4,22,3,13,_,_,18,16,_,_,_,_,23,7,9,10,21,5,_,_,19,_],
[_,_,_,_,_,5,_,24,19,_,9,_,_,_,_,_,_,_,14,18,_,8,4,_,1]
]).
:- problem(2, Rows), sudoku(Rows, 5), maplist(writeln, Rows), halt.
%%%%%%%%%%%%%%% No KB code below here %%%%%%%%%%%%%%%%%%
EOF
swipl --quiet -s <(echo "$Program") <<EOF
%%%%%%%%%%%%%%%%%%% Query code here: %%%%%%%%%%%%%%%%%%%
EOF
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment