Skip to content

Instantly share code, notes, and snippets.

@SamirTalwar
Last active November 29, 2020 12:56
Show Gist options
  • Save SamirTalwar/1315f2b46366c91e2a93a5aba837be48 to your computer and use it in GitHub Desktop.
Save SamirTalwar/1315f2b46366c91e2a93a5aba837be48 to your computer and use it in GitHub Desktop.
% vim: set syntax=prolog
:- use_module(library(clpfd)).
:- initialization(main, main).
puzzle([
[_, _, _, _, _, _, 4, _, 3],
[_, _, _, _, _, _, _, _, _],
[_, _, _, _, _, _, _, _, 6],
[_, _, _, _, _, _, _, _, _],
[_, _, _, _, _, _, _, _, _],
[_, _, _, _, _, _, _, _, _],
[4, _, _, _, _, _, _, _, _],
[_, _, _, _, _, _, _, _, _],
[3, _, 7, _, _, _, _, _, _]
]).
main(_) :- main.
main :-
puzzle(Puzzle),
solve(Puzzle),
render(Puzzle).
solve(Puzzle) :-
% Constrain the values.
append(Puzzle, Cells),
Cells ins 1..9,
% Apply Sudoku rules.
rows(Puzzle),
columns(Puzzle),
squares(Puzzle),
% Apply custom rules.
cages(Puzzle),
thermometers(Puzzle),
bees(Puzzle),
% And solve.
label(Cells).
rows(Puzzle) :-
Rows = Puzzle,
maplist(all_distinct, Rows).
columns(Puzzle) :-
transpose(Puzzle, Columns),
maplist(all_distinct, Columns).
squares(Puzzle) :-
squares(Puzzle, Squares),
maplist(all_distinct, Squares).
squares([A, B, C, D, E, F, G, H, I], Squares) :-
flattened_squares([A, B, C], X),
flattened_squares([D, E, F], Y),
flattened_squares([G, H, I], Z),
append([X, Y, Z], Squares).
flattened_squares([[], [], []], []).
flattened_squares([[A1, A2, A3 | As],
[B1, B2, B3 | Bs],
[C1, C2, C3 | Cs]],
[[A1, A2, A3, B1, B2, B3, C1, C2, C3] | Rest]) :-
flattened_squares([As, Bs, Cs], Rest).
cages(PuzzleA) :-
rotated(PuzzleA, PuzzleB, PuzzleC, PuzzleD),
caged(PuzzleA),
caged(PuzzleB),
caged(PuzzleC),
caged(PuzzleD).
caged([
[_, _, _, _, _, _, _, _, _],
[_, _, _, _, A, B, C, _, _],
[_, _, _, _, D, E, F, _, _],
[_, _, _, _, G, H, I, _, _],
[_, _, _, _, _, _, _, _, _],
[_, _, _, _, _, _, _, _, _],
[_, _, _, _, _, _, _, _, _],
[_, _, _, _, _, _, _, _, _],
[_, _, _, _, _, _, _, _, _]
]) :-
all_distinct([A, B, C, D, E, F, G, H, I]).
thermometers(PuzzleA) :-
rotated(PuzzleA, PuzzleB, PuzzleC, PuzzleD),
thermometersE(PuzzleA),
thermometersE(PuzzleB),
thermometersE(PuzzleC),
thermometersE(PuzzleD).
thermometersE([
[_, _, _, _, _, _, _, _, _],
[_, _, _, _, _, _, _, _, _],
[_, _, _, _, _, _, _, _, _],
[_, _, _, _, _, _, A, B, C],
[_, _, _, _, _, _, D, E, F],
[_, _, _, _, _, _, G, H, I],
[_, _, _, _, _, _, _, _, _],
[_, _, _, _, _, _, _, _, _],
[_, _, _, _, _, _, _, _, _]
]) :-
less_than(A, B, C),
less_than(D, E, F),
less_than(G, H, I).
bees([
[_, A, _, _, _, _, _, F, _],
[_, B, _, _, _, _, G, H, E],
[_, C, _, _, _, _, _, _, _],
[_, _, _, _, _, _, _, _, _],
[_, _, _, _, _, _, _, _, _],
[_, _, _, _, _, _, _, _, _],
[_, P, _, _, _, _, _, _, _],
[N, O, _, _, _, _, _, I, _],
[_, M, _, _, _, _, L, K, J]
]) :-
less_than(A, B, C),
less_than(E, F, G, H),
less_than(I, J, K, L),
less_than(M, N, O, P).
rotated(MatrixA, MatrixB, MatrixC, MatrixD) :-
transpose(MatrixA, TransposedMatrixA),
maplist(reverse, TransposedMatrixA, MatrixB),
reverse(MatrixA, FlippedMatrixA),
maplist(reverse, FlippedMatrixA, MatrixC),
reverse(TransposedMatrixA, MatrixD).
less_than(A, B, C) :-
chain([A, B, C], #<).
less_than(A, B, C, D) :-
chain([A, B, C, D], #<).
render(Puzzle) :-
format("\n"),
maplist(render_row, Puzzle).
render_row([Value]) :-
render_cell(Value),
format("\n").
render_row([Value | Rest]) :-
render_cell(Value),
format(" "),
render_row(Rest).
render_cell(Value) :-
% Print the range if we don't know the answer, for debugging purposes.
var(Value),
fd_dom(Value, Domain),
format("(~p)", [Domain]);
% If we do know the answer, render it.
format("~d", [Value]).
@SamirTalwar
Copy link
Author

Found at https://twitter.com/jneen_/status/1330704906785796097, which shows a much prettier version of the rules.

Rules

@SamirTalwar
Copy link
Author

You can run this with SWI-Prolog:

swipl jneen_puzzle.pl

If you don't have it installed, you can acquire it easily with Nix:

nix run nixpkgs.swiProlog -c swipl jneen_puzzle.pl

Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment